1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker and Richard O'Keefe 4 E-mail: J.Wielemaker@cs.vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2014-2023, VU University Amsterdam 7 CWI, Amsterdam 8 SWI-Prolog Solutions b.v. 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(check_installation, 38 [ check_installation/0, 39 check_installation/1, % -Issues 40 check_config_files/0, 41 update_config_files/0, 42 test_installation/0, 43 test_installation/1 % +Options 44 ]). 45:- autoload(library(apply), [maplist/2, maplist/3]). 46:- autoload(library(archive), [archive_open/3, archive_close/1]). 47:- autoload(library(lists), [append/3, member/2]). 48:- autoload(library(option), [option/2, merge_options/3]). 49:- autoload(library(prolog_source), [path_segments_atom/2]). 50:- use_module(library(settings), [setting/2]). 51:- autoload(library(dcg/high_order), [sequence//2, sequence/4]). 52:- autoload(library(error), [must_be/2]).
http://www.swi-prolog.org/build/issues/
. If not provided,
the library file with extension .html
is used.windows
, unix
or linux
. If present, the component
is only checked for if we are running on a version of the
specified operating system.85% Feature tests 86component(tcmalloc, 87 _{ optional:true, 88 test:test_tcmalloc, 89 url:'tcmalloc.html', 90 os:linux 91 }). 92component(gmp, 93 _{ test:current_prolog_flag(bounded, false), 94 url:'gmp.html' 95 }). 96% Packages that depend on foreign libraries 97component(library(archive), _{features:archive_features}). 98component(library(cgi), _{}). 99component(library(crypt), _{}). 100component(library(bdb), _{}). 101component(library(double_metaphone), _{}). 102component(library(filesex), _{}). 103component(library(http/http_stream), _{}). 104component(library(http/json), _{}). 105component(library(http/jquery), _{features:jquery_file}). 106component(library(isub), _{}). 107component(library(jpl), _{}). 108component(library(memfile), _{}). 109component(library(odbc), _{}). 110component(library(pce), 111 _{pre:use_foreign_library(pce_principal:foreign(pl2xpce)), 112 url:'xpce.html'}). 113component(library(pcre), _{features:pcre_features}). 114component(library(pdt_console), _{}). 115component(library(porter_stem), _{}). 116component(library(process), _{}). 117component(library(protobufs), _{}). 118component(library(editline), _{os:unix}). 119component(library(readline), _{os:unix}). 120component(library(readutil), _{}). 121component(library(rlimit), _{os:unix}). 122component(library(semweb/rdf_db), _{}). 123component(library(semweb/rdf_ntriples), _{}). 124component(library(semweb/turtle), _{}). 125component(library(sgml), _{}). 126component(library(sha), _{}). 127component(library(snowball), _{}). 128component(library(socket), _{}). 129component(library(ssl), _{}). 130component(library(sweep_link), _{features:sweep_emacs_module}). 131component(library(crypto), _{}). 132component(library(syslog), _{os:unix}). 133component(library(table), _{}). 134component(library(time), _{}). 135component(library(tipc/tipc), _{os:linux}). 136component(library(unicode), _{}). 137component(library(uri), _{}). 138component(library(uuid), _{}). 139component(library(zlib), _{}). 140component(library(yaml), _{}). 141 142issue_base('http://www.swi-prolog.org/build/issues/'). 143 144:- thread_local 145 issue/1. 146 147:- meta_predicate 148 run_silent( , ).
If issues are found it prints a diagnostic message with a link to a wiki page with additional information about the issue.
165check_installation :-
166 print_message(informational, installation(checking)),
167 check_installation_(InstallIssues),
168 check_on_path,
169 check_config_files(ConfigIssues),
170 maplist(print_message(warning), ConfigIssues),
171 append(InstallIssues, ConfigIssues, Issues),
172 ( Issues == []
173 -> print_message(informational, installation(perfect))
174 ; length(Issues, Count),
175 print_message(warning, installation(imperfect(Count)))
176 ).
optional_not_found
(optional component is not present), not_found
(component is
not present) or failed
(component is present but cannot be
loaded).186check_installation(Issues) :- 187 check_installation_(Issues0), 188 maplist(public_issue, Issues0, Issues). 189 190public_issue(installation(Term), Source-Issue) :- 191 functor(Term, Issue, _), 192 arg(1, Term, Properties), 193 Source = Properties.source. 194 195check_installation_(Issues) :- 196 retractall(issue(_)), 197 forall(component(Source, _Properties), 198 check_component(Source)), 199 findall(I, retract(issue(I)), Issues). 200 201check_component(Source) :- 202 component(Source, Properties), 203 !, 204 check_component(Source, Properties.put(source,Source)). 205 206check_component(_Source, Properties) :- 207 OS = Properties.get(os), 208 \+ current_os(OS), 209 !. 210check_component(Source, Properties) :- 211 compound(Source), 212 !, 213 check_source(Source, Properties). 214check_component(Feature, Properties) :- 215 print_message(informational, installation(checking(Feature))), 216 ( call(Properties.test) 217 -> print_message(informational, installation(ok)) 218 ; print_issue(installation(missing(Properties))) 219 ). 220 221check_source(Source, Properties) :- 222 exists_source(Source), 223 !, 224 print_message(informational, installation(loading(Source))), 225 ( run_silent(( ( Pre = Properties.get(pre) 226 -> call(Pre) 227 ; true 228 ), 229 load_files(Source, [silent(true), if(not_loaded)]) 230 ), 231 Properties.put(action, load)) 232 -> test_component(Properties), 233 print_message(informational, installation(ok)), 234 check_features(Properties) 235 ; true 236 ). 237check_source(_Source, Properties) :- 238 Properties.get(optional) == true, 239 !, 240 print_message(silent, 241 installation(optional_not_found(Properties))). 242check_source(_Source, Properties) :- 243 print_issue(installation(not_found(Properties))). 244 245current_os(unix) :- current_prolog_flag(unix, true). 246current_os(windows) :- current_prolog_flag(windows, true). 247current_os(linux) :- current_prolog_flag(arch, Arch), sub_atom(Arch, _, _, _, linux).
253test_component(Dict) :- 254 Test = Dict.get(test), 255 !, 256 call(Test). 257test_component(_).
266check_features(Dict) :- 267 Test = Dict.get(features), 268 !, 269 call(Test). 270check_features(_).
278run_silent(Goal, Properties) :-
279 run_collect_messages(Goal, Result, Messages),
280 ( Result == true,
281 Messages == []
282 -> true
283 ; print_issue(installation(failed(Properties, Result, Messages))),
284 fail
285 ).
true
, false
or exception(Error)
and messages with a list of generated error and warning
messages. Each message is a term:
message(Term,Kind,Lines)
297:- thread_local 298 got_message/1. 299 300run_collect_messages(Goal, Result, Messages) :- 301 setup_call_cleanup( 302 asserta((user:thread_message_hook(Term,Kind,Lines) :- 303 error_kind(Kind), 304 assertz(got_message(message(Term,Kind,Lines)))), Ref), 305 ( catch(Goal, E, true) 306 -> ( var(E) 307 -> Result0 = true 308 ; Result0 = exception(E) 309 ) 310 ; Result0 = false 311 ), 312 erase(Ref)), 313 findall(Msg, retract(got_message(Msg)), Messages), 314 Result = Result0. 315 316error_kind(warning). 317error_kind(error). 318 319 320 /******************************* 321 * SPECIAL TESTS * 322 *******************************/
326:- if(current_predicate(malloc_property/1)). 327test_tcmalloc :- 328 malloc_property('generic.current_allocated_bytes'(Bytes)), 329 Bytes > 1 000 000. 330:- else. 331test_tcmalloc :- 332 fail. 333:- endif.
339archive_features :- 340 tmp_file_stream(utf8, Name, Out), 341 close(Out), 342 findall(F, archive_filter(F, Name), Filters), 343 print_message(informational, installation(archive(filters, Filters))), 344 findall(F, archive_format(F, Name), Formats), 345 print_message(informational, installation(archive(formats, Formats))), 346 delete_file(Name). 347 348archive_filter(F, Name) :- 349 a_filter(F), 350 catch(archive_open(Name, A, [filter(F)]), E, true), 351 ( var(E) 352 -> archive_close(A) 353 ; true 354 ), 355 \+ subsumes_term(error(domain_error(filter, _),_), E). 356 357archive_format(F, Name) :- 358 a_format(F), 359 catch(archive_open(Name, A, [format(F)]), E, true), 360 ( var(E) 361 -> archive_close(A) 362 ; true 363 ), 364 \+ subsumes_term(error(domain_error(format, _),_), E). 365 366a_filter(bzip2). 367a_filter(compress). 368a_filter(gzip). 369a_filter(grzip). 370a_filter(lrzip). 371a_filter(lzip). 372a_filter(lzma). 373a_filter(lzop). 374a_filter(none). 375a_filter(rpm). 376a_filter(uu). 377a_filter(xz). 378 379a_format('7zip'). 380a_format(ar). 381a_format(cab). 382a_format(cpio). 383a_format(empty). 384a_format(gnutar). 385a_format(iso9660). 386a_format(lha). 387a_format(mtree). 388a_format(rar). 389a_format(raw). 390a_format(tar). 391a_format(xar). 392a_format(zip).
396pcre_features :- 397 findall(X, pcre_missing(X), Missing), 398 ( Missing == [] 399 -> true 400 ; print_message(warning, installation(pcre_missing(Missing))) 401 ), 402 ( re_config(compiled_widths(Widths)), 403 1 =:= Widths /\ 1 404 -> true 405 ; print_message(warning, installation(pcre_missing('8-bit support'))) 406 ). 407 408pcre_missing(X) :- 409 pcre_must_have(X), 410 Term =.. [X,true], 411 \+ catch(re_config(Term), _, fail). 412 413pcre_must_have(unicode).
419jquery_file :- 420 setting(jquery:version, File), 421 ( absolute_file_name(js(File), Path, [access(read), file_errors(fail)]) 422 -> print_message(informational, installation(jquery(found(Path)))) 423 ; print_message(warning, installation(jquery(not_found(File)))) 424 ). 425 426sweep_emacs_module :- 427 with_output_to(string(S), write_sweep_module_location), 428 split_string(S, "\n", "\n", [VersionInfo|Modules]), 429 must_be(oneof(["V 1"]), VersionInfo), 430 ( maplist(check_sweep_lib, Modules) 431 -> print_message(informational, installation(sweep(found(Modules)))) 432 ; print_message(warning, installation(sweep(not_found(Modules)))) 433 ). 434 435check_sweep_lib(Line) :- 436 sub_atom(Line, B, _, A, ' '), 437 sub_atom(Line, 0, B, _, Type), 438 must_be(oneof(['L', 'M']), Type), 439 sub_atom(Line, _, A, 0, Lib), 440 exists_file(Lib).
448check_on_path :- 449 current_prolog_flag(executable, EXEFlag), 450 prolog_to_os_filename(EXE, EXEFlag), 451 file_base_name(EXE, Prog), 452 absolute_file_name(EXE, AbsExe, 453 [ access(execute), 454 file_errors(fail) 455 ]), 456 !, 457 prolog_to_os_filename(AbsExe, OsExe), 458 ( absolute_file_name(path(Prog), OnPath, 459 [ access(execute), 460 file_errors(fail) 461 ]) 462 -> ( same_file(EXE, OnPath) 463 -> true 464 ; absolute_file_name(path(Prog), OnPathAny, 465 [ access(execute), 466 file_errors(fail), 467 solutions(all) 468 ]), 469 same_file(EXE, OnPathAny) 470 -> print_message(warning, installation(not_first_on_path(OsExe, OnPath))) 471 ; print_message(warning, installation(not_same_on_path(OsExe, OnPath))) 472 ) 473 ; print_message(warning, installation(not_on_path(OsExe, Prog))) 474 ). 475check_on_path. 476 477 478 /******************************* 479 * RUN TESTS * 480 *******************************/
cmake -DINSTALL_TESTS=ON
Options processed:
false
, do not test the packages497test_installation :- 498 test_installation([]). 499 500test_installation(Options) :- 501 absolute_file_name(swi(test/test), 502 TestFile, 503 [ access(read), 504 file_errors(fail), 505 file_type(prolog) 506 ]), 507 !, 508 test_installation_run(TestFile, Options). 509test_installation(_Options) :- 510 print_message(warning, installation(testing(no_installed_tests))). 511 512test_installation_run(TestFile, Options) :- 513 ( option(package(_), Options) 514 -> merge_options(Options, 515 [ core(false), 516 subdirs(false) 517 ], TestOptions) 518 ; merge_options(Options, 519 [ packages(true) 520 ], TestOptions) 521 ), 522 load_files(user:TestFile), 523 current_prolog_flag(verbose, Old), 524 setup_call_cleanup( 525 set_prolog_flag(verbose, silent), 526 user:test([], TestOptions), 527 set_prolog_flag(verbose, Old)). 528 529 530 /******************************* 531 * MESSAGES * 532 *******************************/ 533 534:- multifile 535 prolog:message//1. 536 537print_issue(Term) :- 538 assertz(issue(Term)), 539 print_message(warning, Term). 540 541issue_url(Properties, URL) :- 542 Local = Properties.get(url), 543 !, 544 issue_base(Base), 545 atom_concat(Base, Local, URL). 546issue_url(Properties, URL) :- 547 Properties.get(source) = library(Segments), 548 !, 549 path_segments_atom(Segments, Base), 550 file_name_extension(Base, html, URLFile), 551 issue_base(Issues), 552 atom_concat(Issues, URLFile, URL). 553 554prologmessage(installation(Message)) --> 555 message(Message). 556 557message(checking) --> 558 { current_prolog_flag(address_bits, Bits) }, 559 { current_prolog_flag(arch, Arch) }, 560 { current_prolog_flag(home, Home) }, 561 { current_prolog_flag(cpu_count, Cores) }, 562 [ 'Checking your SWI-Prolog kit for common issues ...'-[], nl, nl ], 563 [ 'Version: ~`.t~24| '-[] ], '$messages':prolog_message(version), [nl], 564 [ 'Address bits: ~`.t~24| ~d'-[Bits] ], [nl], 565 [ 'Architecture: ~`.t~24| ~w'-[Arch] ], [nl], 566 [ 'Installed at: ~`.t~24| ~w'-[Home] ], [nl], 567 [ 'Cores: ~`.t~24| ~w'-[Cores] ], [nl], 568 [ nl ]. 569message(perfect) --> 570 [ nl, 'Congratulations, your kit seems sound and complete!'-[] ]. 571message(imperfect(N)) --> 572 [ 'Found ~w issues.'-[N] ]. 573message(checking(Feature)) --> 574 [ 'Checking ~w ...'-[Feature], flush ]. 575message(missing(Properties)) --> 576 [ at_same_line, '~`.t~48| not present'-[] ], 577 details(Properties). 578message(loading(Source)) --> 579 [ 'Loading ~q ...'-[Source], flush ]. 580message(ok) --> 581 [ at_same_line, '~`.t~48| ok'-[] ]. 582message(optional_not_found(Properties)) --> 583 [ 'Optional ~q ~`.t~48| not present'-[Properties.source] ]. 584message(not_found(Properties)) --> 585 [ '~q ~`.t~48| NOT FOUND'-[Properties.source] ], 586 details(Properties). 587message(failed(Properties, false, [])) --> 588 !, 589 [ at_same_line, '~`.t~48| FAILED'-[] ], 590 details(Properties). 591message(failed(Properties, exception(Ex0), [])) --> 592 !, 593 { strip_stack(Ex0, Ex), 594 message_to_string(Ex, Msg) }, 595 [ '~w'-[Msg] ], 596 details(Properties). 597message(failed(Properties, true, Messages)) --> 598 [ at_same_line, '~`.t~48| FAILED'-[] ], 599 explain(Messages), 600 details(Properties). 601message(archive(What, Names)) --> 602 [ ' Supported ~w: '-[What] ], 603 list_names(Names). 604message(pcre_missing(Features)) --> 605 [ 'Missing libpcre features: '-[] ], 606 list_names(Features). 607message(not_first_on_path(EXE, OnPath)) --> 608 { public_executable(EXE, PublicEXE), 609 file_base_name(EXE, Prog) 610 }, 611 [ 'The first ~w on '-[Prog] ], 'PATH', [ ' is ~p, while '-[OnPath], nl ], 612 [ 'this version is ~p.'-[PublicEXE] ]. 613message(not_same_on_path(EXE, OnPath)) --> 614 { public_executable(EXE, PublicEXE), 615 file_base_name(EXE, Prog) 616 }, 617 [ 'The ~w on '-[Prog] ], 'PATH', [ ' is ~p, while '-[OnPath], nl ], 618 [ 'this version is ~p.'-[PublicEXE] ]. 619message(not_on_path(EXE, Prog)) --> 620 { public_bin_dir(EXE, Dir), 621 prolog_to_os_filename(Dir, OSDir) 622 }, 623 [ 'Could not find ~w on '-[Prog] ], 'PATH', [ '. '-[], nl ], 624 [ 'You may wish to add ~p to '-[OSDir] ], 'PATH', [ '. '-[], nl ]. 625message(jquery(found(Path))) --> 626 [ ' jQuery from ~w'-[Path] ]. 627message(jquery(not_found(File))) --> 628 [ ' Cannot find jQuery (~w)'-[File] ]. 629message(sweep(found(Paths))) --> 630 [ ' GNU-Emacs plugin loads'-[] ], 631 sequence(list_file, Paths). 632message(sweep(not_found(Paths))) --> 633 [ ' Could not find all GNU-Emacs libraries'-[] ], 634 sequence(list_file, Paths). 635message(testing(no_installed_tests)) --> 636 [ ' Runtime testing is not enabled.', nl], 637 [ ' Please recompile the system with INSTALL_TESTS enabled.' ]. 638 639 640public_executable(EXE, PublicProg) :- 641 file_base_name(EXE, Prog), 642 file_directory_name(EXE, ArchDir), 643 file_directory_name(ArchDir, BinDir), 644 file_directory_name(BinDir, Home), 645 file_directory_name(Home, Lib), 646 file_directory_name(Lib, Prefix), 647 atomic_list_concat([Prefix, bin, Prog], /, PublicProg), 648 exists_file(PublicProg), 649 same_file(EXE, PublicProg), 650 !. 651public_executable(EXE, EXE). 652 653public_bin_dir(EXE, Dir) :- 654 public_executable(EXE, PublicEXE), 655 file_directory_name(PublicEXE, Dir). 656 657 658 659'PATH' --> 660 { current_prolog_flag(windows, true) }, 661 !, 662 [ '%PATH%'-[] ]. 663'PATH' --> 664 [ '$PATH'-[] ]. 665 666strip_stack(error(Error, context(prolog_stack(S), Msg)), 667 error(Error, context(_, Msg))) :- 668 nonvar(S). 669strip_stack(Error, Error). 670 671details(Properties) --> 672 { issue_url(Properties, URL), ! 673 }, 674 [ nl, 'See ~w'-[URL] ]. 675details(_) --> []. 676 677explain(Messages) --> 678 { Messages = [message(error(shared_object(open, _Message), _), _, _)|_] 679 }, 680 !, 681 [nl], 682 ( { current_prolog_flag(windows, true) } 683 -> [ 'Cannot load required DLL'-[] ] 684 ; [ 'Cannot load required shared library'-[] ] 685 ). 686explain(Messages) --> 687 print_messages(Messages). 688 689print_messages([]) --> []. 690print_messages([message(_Term, _Kind, Lines)|T]) --> 691 , [nl], 692 print_messages(T). 693 694list_names([]) --> []. 695list_names([H|T]) --> 696 [ '~w'-[H] ], 697 ( {T==[]} 698 -> [] 699 ; [ ', '-[] ], 700 list_names(T) 701 ). 702 703list_file(File) --> 704 [ nl, ' '-[], url(File) ]. 705 706 707 /******************************* 708 * CONFIG FILES * 709 *******************************/
716check_config_files :- 717 check_config_files(Issues), 718 maplist(print_message(warning), Issues). 719 720check_config_files(Issues) :- 721 findall(Issue, check_config_file(Issue), Issues). 722 723check_config_file(config(Id, move(Type, OldFile, NewFile))) :- 724 old_config(Type, Id, OldFile), 725 access_file(OldFile, exist), 726 \+ ( new_config(Type, Id, NewFile), 727 access_file(NewFile, exist) 728 ), 729 once(new_config(Type, Id, NewFile)). 730check_config_file(config(Id, different(Type, OldFile, NewFile))) :- 731 old_config(Type, Id, OldFile), 732 access_file(OldFile, exist), 733 new_config(Type, Id, NewFile), 734 access_file(NewFile, exist), 735 \+ same_file(OldFile, NewFile).
742update_config_files :- 743 old_config(Type, Id, OldFile), 744 access_file(OldFile, exist), 745 \+ ( new_config(Type, Id, NewFile), 746 access_file(NewFile, exist) 747 ), 748 ( new_config(Type, Id, NewFile), 749 \+ same_file(OldFile, NewFile), 750 create_parent_dir(NewFile) 751 -> catch(rename_file(OldFile, NewFile), E, 752 print_message(warning, E)), 753 print_message(informational, config(Id, moved(Type, OldFile, NewFile))) 754 ), 755 fail. 756update_config_files. 757 758old_config(file, init, File) :- 759 current_prolog_flag(windows, true), 760 win_folder(appdata, Base), 761 atom_concat(Base, '/SWI-Prolog/swipl.ini', File). 762old_config(file, init, File) :- 763 expand_file_name('~/.swiplrc', [File]). 764old_config(directory, lib, Dir) :- 765 expand_file_name('~/lib/prolog', [Dir]). 766old_config(directory, xpce, Dir) :- 767 expand_file_name('~/.xpce', [Dir]). 768old_config(directory, history, Dir) :- 769 expand_file_name('~/.swipl-dir-history', [Dir]). 770old_config(directory, pack, Dir) :- 771 ( catch(expand_file_name('~/lib/swipl/pack', [Dir]), _, fail) 772 ; absolute_file_name(swi(pack), Dir, 773 [ file_type(directory), solutions(all) ]) 774 ). 775 776new_config(file, init, File) :- 777 absolute_file_name(user_app_config('init.pl'), File, 778 [ solutions(all) ]). 779new_config(directory, lib, Dir) :- 780 config_dir(user_app_config(lib), Dir). 781new_config(directory, xpce, Dir) :- 782 config_dir(user_app_config(xpce), Dir). 783new_config(directory, history, Dir) :- 784 config_dir(user_app_config('dir-history'), Dir). 785new_config(directory, pack, Dir) :- 786 config_dir([app_data(pack), swi(pack)], Dir). 787 788config_dir(Aliases, Dir) :- 789 is_list(Aliases), 790 !, 791 ( member(Alias, Aliases), 792 absolute_file_name(Alias, Dir, 793 [ file_type(directory), solutions(all) ]) 794 *-> true 795 ; member(Alias, Aliases), 796 absolute_file_name(Alias, Dir, 797 [ solutions(all) ]) 798 ). 799config_dir(Alias, Dir) :- 800 ( absolute_file_name(Alias, Dir, 801 [ file_type(directory), solutions(all) ]) 802 *-> true 803 ; absolute_file_name(Alias, Dir, 804 [ solutions(all) ]) 805 ). 806 807create_parent_dir(NewFile) :- 808 file_directory_name(NewFile, Dir), 809 create_parent_dir_(Dir). 810 811create_parent_dir_(Dir) :- 812 exists_directory(Dir), 813 '$my_file'(Dir), 814 !. 815create_parent_dir_(Dir) :- 816 file_directory_name(Dir, Parent), 817 Parent \== Dir, 818 create_parent_dir_(Parent), 819 make_directory(Dir). 820 821prologmessage(config(Id, Issue)) --> 822 [ 'Config: '-[] ], 823 config_description(Id), 824 config_issue(Issue). 825 826config_description(init) --> 827 [ '(user initialization file) '-[], nl ]. 828config_description(lib) --> 829 [ '(user library) '-[], nl ]. 830config_description(pack) --> 831 [ '(add-ons) '-[], nl ]. 832config_description(history) --> 833 [ '(command line history) '-[], nl ]. 834config_description(xpce) --> 835 [ '(gui) '-[], nl ]. 836 837config_issue(move(Type, Old, New)) --> 838 [ ' found ~w "~w"'-[Type, Old], nl ], 839 [ ' new location is "~w"'-[New] ]. 840config_issue(moved(Type, Old, New)) --> 841 [ ' found ~w "~w"'-[Type, Old], nl ], 842 [ ' moved to new location "~w"'-[New] ]. 843config_issue(different(Type, Old, New)) --> 844 [ ' found different ~w "~w"'-[Type, Old], nl ], 845 [ ' new location is "~w"'-[New] ]
Check installation issues and features
This library performs checks on the installed system to verify which optional components are available and whether all libraries that load shared objects/DLLs can be loaded. */