View source with raw comments or as raw
    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-2025, 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(occurs), [sub_term/2]).   49:- autoload(library(option), [option/2, merge_options/3]).   50:- autoload(library(prolog_source), [path_segments_atom/2]).   51:- use_module(library(settings), [setting/2]).   52:- autoload(library(dcg/high_order), [sequence//2, sequence/4]).   53:- autoload(library(error), [must_be/2]).

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. */

 component(?Component, -Features) is nondet
This predicate describes the test components. Features is a dict with the following components:
test:Goal
(Additional) test that must succeed for the component to be functional.
url:URL
URL with additional information, relative to http://www.swi-prolog.org/build/issues/. If not provided, the library file with extension .html is used.
optional:true
If the library does not exist, do not complain.
os:OS
One of windows, unix or linux. If present, the component is only checked for if we are running on a version of the specified operating system.
features:Goal
After successful evaluation that loading and basic operation of the component succeeds, run this to check additional features.
   86% Feature tests
   87component(tcmalloc,
   88          _{ optional:true,
   89             test:test_tcmalloc,
   90             url:'tcmalloc.html',
   91             os:linux
   92           }).
   93component(gmp,
   94          _{ test:current_prolog_flag(bounded, false),
   95             url:'gmp.html'
   96           }).
   97% Packages that depend on foreign libraries
   98component(library(archive), _{features:archive_features}).
   99component(library(cgi), _{}).
  100component(library(crypt), _{}).
  101component(library(bdb), _{}).
  102component(library(double_metaphone), _{}).
  103component(library(editline), _{os:unix}).
  104component(library(filesex), _{}).
  105component(library(http/http_stream), _{}).
  106component(library(json), _{}).
  107component(library(http/jquery), _{features:jquery_file}).
  108component(library(isub), _{}).
  109component(library(janus), _{features:python_version}).
  110component(library(jpl), _{}).
  111component(library(memfile), _{}).
  112component(library(odbc), _{}).
  113component(library(pce),
  114          _{pre:use_foreign_library(pce_principal:foreign(pl2xpce)),
  115            url:'xpce.html'}).
  116component(library(pcre), _{features:pcre_features}).
  117component(library(pdt_console), _{}).
  118component(library(porter_stem), _{}).
  119component(library(process), _{}).
  120component(library(protobufs), _{}).
  121%component(library(readline), _{os:unix}).
  122component(library(readutil), _{}).
  123component(library(rlimit), _{os:unix}).
  124component(library(semweb/rdf_db), _{}).
  125component(library(semweb/rdf_ntriples), _{}).
  126component(library(semweb/turtle), _{}).
  127component(library(sgml), _{}).
  128component(library(sha), _{}).
  129component(library(snowball), _{}).
  130component(library(socket), _{}).
  131component(library(ssl), _{}).
  132component(library(sweep_link), _{features:sweep_emacs_module}).
  133component(library(crypto), _{}).
  134component(library(syslog), _{os:unix}).
  135component(library(table), _{}).
  136component(library(time), _{}).
  137component(library(tipc/tipc), _{os:linux}).
  138component(library(unicode), _{}).
  139component(library(uri), _{}).
  140component(library(uuid), _{}).
  141component(library(yaml), _{}).
  142component(library(zlib), _{}).
  143
  144issue_base('http://www.swi-prolog.org/build/issues/').
  145
  146:- thread_local
  147    issue/1.  148
  149:- meta_predicate
  150    run_silent(0, +).
 check_installation is det
Check features of the installed system. Performs the following tests:
  1. Test whether features that depend on optional libraries are present (e.g., unbounded arithmetic support)
  2. Test that all standard libraries that depend on foreign code are present.
  3. provides a test_installation predicate to run the tests at runtime if the system was built with -DINSTALL_TESTS

If issues are found it prints a diagnostic message with a link to a wiki page with additional information about the issue.

  167check_installation :-
  168    print_message(informational, installation(checking)),
  169    check_installation_(InstallIssues),
  170    check_on_path,
  171    check_config_files(ConfigIssues),
  172    check_autoload,
  173    maplist(print_message(warning), ConfigIssues),
  174    append(InstallIssues, ConfigIssues, Issues),
  175    (   Issues == []
  176    ->  print_message(informational, installation(perfect))
  177    ;   length(Issues, Count),
  178        print_message(warning, installation(imperfect(Count)))
  179    ).
 check_installation(-Issues:list(pair)) is det
As check_installation/0, but additionally returns a list of Component-Problem pairs. Problem is one of optional_not_found (optional component is not present), not_found (component is not present) or failed (component is present but cannot be loaded).
  189check_installation(Issues) :-
  190    check_installation_(Issues0),
  191    maplist(public_issue, Issues0, Issues).
  192
  193public_issue(installation(Term), Source-Issue) :-
  194    functor(Term, Issue, _),
  195    arg(1, Term, Properties),
  196    Source = Properties.source.
  197
  198check_installation_(Issues) :-
  199    retractall(issue(_)),
  200    forall(component(Source, _Properties),
  201           check_component(Source)),
  202    findall(I, retract(issue(I)), Issues).
  203
  204check_component(Source) :-
  205    component(Source, Properties),
  206    !,
  207    check_component(Source, Properties.put(source,Source)).
  208
  209check_component(_Source, Properties) :-
  210    OS = Properties.get(os),
  211    \+ current_os(OS),
  212    !.
  213check_component(Source, Properties) :-
  214    compound(Source),
  215    !,
  216    check_source(Source, Properties).
  217check_component(Feature, Properties) :-
  218    print_message(informational, installation(checking(Feature))),
  219    (   call(Properties.test)
  220    ->  print_message(informational, installation(ok))
  221    ;   print_issue(installation(missing(Properties)))
  222    ).
  223
  224check_source(Source, Properties) :-
  225    exists_source(Source),
  226    !,
  227    print_message(informational, installation(loading(Source))),
  228    (   run_silent(( (   Pre = Properties.get(pre)
  229                     ->  call(Pre)
  230                     ;   true
  231                     ),
  232                     load_files(Source, [silent(true), if(true)])
  233                   ),
  234                   Properties.put(action, load))
  235    ->  test_component(Properties),
  236        print_message(informational, installation(ok)),
  237        check_features(Properties)
  238    ;   true
  239    ).
  240check_source(_Source, Properties) :-
  241    Properties.get(optional) == true,
  242    !,
  243    print_message(silent,
  244                  installation(optional_not_found(Properties))).
  245check_source(_Source, Properties) :-
  246    print_issue(installation(not_found(Properties))).
  247
  248current_os(unix)    :- current_prolog_flag(unix, true).
  249current_os(windows) :- current_prolog_flag(windows, true).
  250current_os(linux)   :- current_prolog_flag(arch, Arch),
  251                       sub_atom(Arch, _, _, _, linux).
 test_component(+Properties) is semidet
Run additional tests to see whether the component really works.
  257test_component(Dict) :-
  258    Test = Dict.get(test),
  259    !,
  260    call(Test).
  261test_component(_).
 check_features(+Properties) is semidet
Check for additional features of the components.
See also
- check_component/1 should be used for checking that the component works.
  270check_features(Dict) :-
  271    Test = Dict.get(features),
  272    !,
  273    catch(Test, Error,
  274          ( print_message(warning, Error),
  275            fail)).
  276check_features(_).
 run_silent(:Goal, +Properties) is semidet
Succeed if Goal succeeds and does not print any errors or warnings.
  284run_silent(Goal, Properties) :-
  285    run_collect_messages(Goal, Result, Messages),
  286    (   Result == true,
  287        Messages == []
  288    ->  true
  289    ;   print_issue(installation(failed(Properties, Result, Messages))),
  290        fail
  291    ).
 run_collect_messages(Goal, Result, Messages) is det
Run Goal, unify Result with 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)
See also
- message_hook/3.
  303:- thread_local
  304    got_message/1.  305
  306run_collect_messages(Goal, Result, Messages) :-
  307    setup_call_cleanup(
  308        asserta((user:thread_message_hook(Term,Kind,Lines) :-
  309                    error_kind(Kind),
  310                    assertz(got_message(message(Term,Kind,Lines)))), Ref),
  311        (   catch(Goal, E, true)
  312        ->  (   var(E)
  313            ->  Result0 = true
  314            ;   Result0 = exception(E)
  315            )
  316        ;   Result0 = false
  317        ),
  318        erase(Ref)),
  319    findall(Msg, retract(got_message(Msg)), Messages),
  320    Result = Result0.
  321
  322error_kind(warning).
  323error_kind(error).
  324
  325
  326                 /*******************************
  327                 *         SPECIAL TESTS        *
  328                 *******************************/
 test_tcmalloc
  332:- if(current_predicate(malloc_property/1)).  333test_tcmalloc :-
  334    malloc_property('generic.current_allocated_bytes'(Bytes)),
  335    Bytes > 1 000 000.
  336:- else.  337test_tcmalloc :-
  338    fail.
  339:- endif.
 archive_features
Report features supported by library(archive).
  345archive_features :-
  346    tmp_file_stream(utf8, Name, Out),
  347    close(Out),
  348    findall(F, archive_filter(F, Name), Filters),
  349    print_message(informational, installation(archive(filters, Filters))),
  350    findall(F, archive_format(F, Name), Formats),
  351    print_message(informational, installation(archive(formats, Formats))),
  352    delete_file(Name).
  353
  354archive_filter(F, Name) :-
  355    a_filter(F),
  356    catch(archive_open(Name, A, [filter(F)]), E, true),
  357    (   var(E)
  358    ->  archive_close(A)
  359    ;   true
  360    ),
  361    \+ subsumes_term(error(domain_error(filter, _),_), E).
  362
  363archive_format(F, Name) :-
  364    a_format(F),
  365    catch(archive_open(Name, A, [format(F)]), E, true),
  366    (   var(E)
  367    ->  archive_close(A)
  368    ;   true
  369    ),
  370    \+ subsumes_term(error(domain_error(format, _),_), E).
  371
  372a_filter(bzip2).
  373a_filter(compress).
  374a_filter(gzip).
  375a_filter(grzip).
  376a_filter(lrzip).
  377a_filter(lzip).
  378a_filter(lzma).
  379a_filter(lzop).
  380a_filter(none).
  381a_filter(rpm).
  382a_filter(uu).
  383a_filter(xz).
  384
  385a_format('7zip').
  386a_format(ar).
  387a_format(cab).
  388a_format(cpio).
  389a_format(empty).
  390a_format(gnutar).
  391a_format(iso9660).
  392a_format(lha).
  393a_format(mtree).
  394a_format(rar).
  395a_format(raw).
  396a_format(tar).
  397a_format(xar).
  398a_format(zip).
 pcre_features
  402pcre_features :-
  403    findall(X, pcre_missing(X), Missing),
  404    (   Missing == []
  405    ->  true
  406    ;   print_message(warning, installation(pcre_missing(Missing)))
  407    ),
  408    (   re_config(compiled_widths(Widths)),
  409        1 =:= Widths /\ 1
  410    ->  true
  411    ;   print_message(warning, installation(pcre_missing('8-bit support')))
  412    ).
  413
  414pcre_missing(X) :-
  415    pcre_must_have(X),
  416    Term =.. [X,true],
  417    \+ catch(re_config(Term), _, fail).
  418
  419pcre_must_have(unicode).
 jquery_file
Test whether jquery.js can be found
  425jquery_file :-
  426    setting(jquery:version, File),
  427    (   absolute_file_name(js(File), Path, [access(read), file_errors(fail)])
  428    ->  print_message(informational, installation(jquery(found(Path))))
  429    ;   print_message(warning, installation(jquery(not_found(File))))
  430    ).
  431
  432sweep_emacs_module :-
  433    with_output_to(string(S), write_sweep_module_location),
  434    split_string(S, "\n", "\n", [VersionInfo|Modules]),
  435    must_be(oneof(["V 1"]), VersionInfo),
  436    (   maplist(check_sweep_lib, Modules)
  437    ->  print_message(informational, installation(sweep(found(Modules))))
  438    ;   print_message(warning, installation(sweep(not_found(Modules))))
  439    ).
  440
  441check_sweep_lib(Line) :-
  442    sub_atom(Line, B, _, A, ' '),
  443    sub_atom(Line, 0, B, _, Type),
  444    must_be(oneof(['L', 'M']), Type),
  445    sub_atom(Line, _, A, 0, Lib),
  446    exists_file(Lib).
  447
  448python_version :-
  449    py_call(sys:version, Version),
  450    print_message(informational, installation(janus(Version))).
 check_on_path
Validate that Prolog is installed in $PATH. Only performed if the running executable is a normal executable file, assuming some special installation such as the WASM version otherwise.
  459check_on_path :-
  460    current_prolog_flag(executable, EXEFlag),
  461    prolog_to_os_filename(EXE, EXEFlag),
  462    file_base_name(EXE, Prog),
  463    absolute_file_name(EXE, AbsExe,
  464                       [ access(execute),
  465                         file_errors(fail)
  466                       ]),
  467    !,
  468    prolog_to_os_filename(AbsExe, OsExe),
  469    (   absolute_file_name(path(Prog), OnPath,
  470                           [ access(execute),
  471                             file_errors(fail)
  472                           ])
  473    ->  (   same_file(EXE, OnPath)
  474        ->  true
  475        ;   absolute_file_name(path(Prog), OnPathAny,
  476                               [ access(execute),
  477                                 file_errors(fail),
  478                                 solutions(all)
  479                               ]),
  480            same_file(EXE, OnPathAny)
  481        ->  print_message(warning, installation(not_first_on_path(OsExe, OnPath)))
  482        ;   print_message(warning, installation(not_same_on_path(OsExe, OnPath)))
  483        )
  484    ;   print_message(warning, installation(not_on_path(OsExe, Prog)))
  485    ).
  486check_on_path.
  487
  488
  489		 /*******************************
  490		 *           RUN TESTS		*
  491		 *******************************/
 test_installation is semidet
 test_installation(+Options) is semidet
Run regression tests in the installed system. Requires the system to be built using
cmake -DINSTALL_TESTS=ON

Options processed:

packages(+Boolean)
When false, do not test the packages
package(+Package)
Only test package package.

When running this predicate the working directory must be writeable and allow for writing executable files. This is due to tests for file system interaction and tests for generating stand-alone executables.

  513test_installation :-
  514    test_installation([]).
  515
  516test_installation(Options) :-
  517    absolute_file_name(swi(test/test),
  518                       TestFile,
  519                       [ access(read),
  520                         file_errors(fail),
  521                         file_type(prolog)
  522                       ]),
  523    !,
  524    test_installation_run(TestFile, Options).
  525test_installation(_Options) :-
  526    print_message(warning, installation(testing(no_installed_tests))).
  527
  528test_installation_run(TestFile, Options) :-
  529    (   option(package(_), Options)
  530    ->  merge_options(Options,
  531                      [ core(false),
  532                        subdirs(false)
  533                      ], TestOptions)
  534    ;   merge_options(Options,
  535                      [ packages(true)
  536                      ], TestOptions)
  537    ),
  538    load_files(user:TestFile),
  539    current_prolog_flag(verbose, Old),
  540    setup_call_cleanup(
  541        set_prolog_flag(verbose, silent),
  542        user:test([], TestOptions),
  543        set_prolog_flag(verbose, Old)).
  544
  545
  546                 /*******************************
  547                 *            MESSAGES          *
  548                 *******************************/
  549
  550:- multifile
  551    prolog:message//1.  552
  553print_issue(Term) :-
  554    assertz(issue(Term)),
  555    print_message(warning, Term).
  556
  557issue_url(Properties, URL) :-
  558    Local = Properties.get(url),
  559    !,
  560    issue_base(Base),
  561    atom_concat(Base, Local, URL).
  562issue_url(Properties, URL) :-
  563    Properties.get(source) = library(Segments),
  564    !,
  565    path_segments_atom(Segments, Base),
  566    file_name_extension(Base, html, URLFile),
  567    issue_base(Issues),
  568    atom_concat(Issues, URLFile, URL).
  569
  570prolog:message(installation(Message)) -->
  571    message(Message).
  572
  573message(checking) -->
  574    { current_prolog_flag(address_bits, Bits) },
  575    { current_prolog_flag(arch, Arch) },
  576    { current_prolog_flag(home, Home) },
  577    { current_prolog_flag(cpu_count, Cores) },
  578    [ 'Checking your SWI-Prolog kit for common issues ...'-[], nl, nl ],
  579    [ 'Version: ~`.t~24| '-[] ], '$messages':prolog_message(version), [nl],
  580    [ 'Address bits: ~`.t~24| ~d'-[Bits] ], [nl],
  581    [ 'Architecture: ~`.t~24| ~w'-[Arch] ], [nl],
  582    [ 'Installed at: ~`.t~24| ~w'-[Home] ], [nl],
  583    [ 'Cores: ~`.t~24| ~w'-[Cores] ], [nl],
  584    [ nl ].
  585message(perfect) -->
  586    [ nl, 'Congratulations, your kit seems sound and complete!'-[] ].
  587message(imperfect(N)) -->
  588    [ 'Found ~w issues.'-[N] ].
  589message(checking(Feature)) -->
  590    [ 'Checking ~w ...'-[Feature], flush ].
  591message(missing(Properties)) -->
  592    [ at_same_line, '~`.t~48| not present'-[] ],
  593    details(Properties).
  594message(loading(Source)) -->
  595    [ 'Loading ~q ...'-[Source], flush ].
  596message(ok) -->
  597    [ at_same_line, '~`.t~48| ok'-[] ].
  598message(optional_not_found(Properties)) -->
  599    [ 'Optional ~q ~`.t~48| not present'-[Properties.source] ].
  600message(not_found(Properties)) -->
  601    [ '~q ~`.t~48| NOT FOUND'-[Properties.source] ],
  602    details(Properties).
  603message(failed(Properties, false, [])) -->
  604    !,
  605    [ at_same_line, '~`.t~48| FAILED'-[] ],
  606    details(Properties).
  607message(failed(Properties, exception(Ex0), [])) -->
  608    !,
  609    { strip_stack(Ex0, Ex),
  610      message_to_string(Ex, Msg) },
  611    [ '~w'-[Msg] ],
  612    details(Properties).
  613message(failed(Properties, true, Messages)) -->
  614    [ at_same_line, '~`.t~48| FAILED'-[] ],
  615    explain(Messages),
  616    details(Properties).
  617message(archive(What, Names)) -->
  618    [ '  Supported ~w: '-[What] ],
  619    list_names(Names).
  620message(pcre_missing(Features)) -->
  621    [ 'Missing libpcre features: '-[] ],
  622    list_names(Features).
  623message(not_first_on_path(EXE, OnPath)) -->
  624    { public_executable(EXE, PublicEXE),
  625      file_base_name(EXE, Prog)
  626    },
  627    [ 'The first ~w on '-[Prog] ], 'PATH', [ ' is ~p, while '-[OnPath], nl ],
  628    [ 'this version is ~p.'-[PublicEXE] ].
  629message(not_same_on_path(EXE, OnPath)) -->
  630    { public_executable(EXE, PublicEXE),
  631      file_base_name(EXE, Prog)
  632    },
  633    [ 'The ~w on '-[Prog] ], 'PATH', [ ' is ~p, while '-[OnPath], nl ],
  634    [ 'this version is ~p.'-[PublicEXE] ].
  635message(not_on_path(EXE, Prog)) -->
  636    { public_bin_dir(EXE, Dir),
  637      prolog_to_os_filename(Dir, OSDir)
  638    },
  639    [ 'Could not find ~w on '-[Prog] ], 'PATH', [ '. '-[], nl ],
  640    [ 'You may wish to add ~p to '-[OSDir] ], 'PATH', [ '. '-[], nl ].
  641message(jquery(found(Path))) -->
  642    [ '  jQuery from ~w'-[Path] ].
  643message(jquery(not_found(File))) -->
  644    [ '  Cannot find jQuery (~w)'-[File] ].
  645message(sweep(found(Paths))) -->
  646    [ '  GNU-Emacs plugin loads'-[] ],
  647    sequence(list_file, Paths).
  648message(sweep(not_found(Paths))) -->
  649    [ '  Could not find all GNU-Emacs libraries'-[] ],
  650    sequence(list_file, Paths).
  651message(testing(no_installed_tests)) -->
  652    [ '  Runtime testing is not enabled.', nl],
  653    [ '  Please recompile the system with INSTALL_TESTS enabled.' ].
  654message(janus(Version)) -->
  655    [ '  Python version ~w'-[Version] ].
  656message(ambiguous_autoload(PI, Paths)) -->
  657    [ 'The predicate ~p can be autoloaded from multiple libraries:'-[PI]],
  658    sequence(list_file, Paths).
  659
  660public_executable(EXE, PublicProg) :-
  661    file_base_name(EXE, Prog),
  662    file_directory_name(EXE, ArchDir),
  663    file_directory_name(ArchDir, BinDir),
  664    file_directory_name(BinDir, Home),
  665    file_directory_name(Home, Lib),
  666    file_directory_name(Lib, Prefix),
  667    atomic_list_concat([Prefix, bin, Prog], /, PublicProg),
  668    exists_file(PublicProg),
  669    same_file(EXE, PublicProg),
  670    !.
  671public_executable(EXE, EXE).
  672
  673public_bin_dir(EXE, Dir) :-
  674    public_executable(EXE, PublicEXE),
  675    file_directory_name(PublicEXE, Dir).
  676
  677
  678
  679'PATH' -->
  680    { current_prolog_flag(windows, true) },
  681    !,
  682    [ '%PATH%'-[] ].
  683'PATH' -->
  684    [ '$PATH'-[] ].
  685
  686strip_stack(error(Error, context(prolog_stack(S), Msg)),
  687            error(Error, context(_, Msg))) :-
  688    nonvar(S).
  689strip_stack(Error, Error).
  690
  691details(Properties) -->
  692    { issue_url(Properties, URL), !
  693    },
  694    [ nl, 'See '-[], url(URL) ].
  695details(_) --> [].
  696
  697explain(Messages) -->
  698    { shared_object_error(Messages) },
  699    !,
  700    [nl],
  701    (   { current_prolog_flag(windows, true) }
  702    ->  [ 'Cannot load required DLL'-[] ]
  703    ;   [ 'Cannot load required shared library'-[] ]
  704    ).
  705explain(Messages) -->
  706    print_messages(Messages).
  707
  708shared_object_error(Messages) :-
  709    sub_term(Term, Messages),
  710    subsumes_term(error(shared_object(open, _Message), _), Term),
  711    !.
  712
  713print_messages([]) --> [].
  714print_messages([message(_Term, _Kind, Lines)|T]) -->
  715    Lines, [nl],
  716    print_messages(T).
  717
  718list_names([]) --> [].
  719list_names([H|T]) -->
  720    [ '~w'-[H] ],
  721    (   {T==[]}
  722    ->  []
  723    ;   [ ', '-[] ],
  724        list_names(T)
  725    ).
  726
  727list_file(File) -->
  728    [ nl, '    '-[], url(File) ].
  729
  730
  731		 /*******************************
  732		 *          CONFIG FILES	*
  733		 *******************************/
 check_config_files
Examines the locations of config files. The config files have moved in version 8.1.15
  740check_config_files :-
  741    check_config_files(Issues),
  742    maplist(print_message(warning), Issues).
  743
  744check_config_files(Issues) :-
  745    findall(Issue, check_config_file(Issue), Issues).
  746
  747check_config_file(config(Id, move(Type, OldFile, NewFile))) :-
  748    old_config(Type, Id, OldFile),
  749    access_file(OldFile, exist),
  750    \+ ( new_config(Type, Id, NewFile),
  751         access_file(NewFile, exist)
  752       ),
  753    once(new_config(Type, Id, NewFile)).
  754check_config_file(config(Id, different(Type, OldFile, NewFile))) :-
  755    old_config(Type, Id, OldFile),
  756    access_file(OldFile, exist),
  757    new_config(Type, Id, NewFile),
  758    access_file(NewFile, exist),
  759    \+ same_file(OldFile, NewFile).
 update_config_files
Move config files from their old location to the new if the file or directory exists in the old location but not in the new.
  766update_config_files :-
  767    old_config(Type, Id, OldFile),
  768    access_file(OldFile, exist),
  769    \+ ( new_config(Type, Id, NewFile),
  770         access_file(NewFile, exist)
  771       ),
  772    (   new_config(Type, Id, NewFile),
  773        \+ same_file(OldFile, NewFile),
  774        create_parent_dir(NewFile)
  775    ->  catch(rename_file(OldFile, NewFile), E,
  776              print_message(warning, E)),
  777        print_message(informational, config(Id, moved(Type, OldFile, NewFile)))
  778    ),
  779    fail.
  780update_config_files.
  781
  782old_config(file, init, File) :-
  783    current_prolog_flag(windows, true),
  784    win_folder(appdata, Base),
  785    atom_concat(Base, '/SWI-Prolog/swipl.ini', File).
  786old_config(file, init, File) :-
  787    expand_file_name('~/.swiplrc', [File]).
  788old_config(directory, lib, Dir) :-
  789    expand_file_name('~/lib/prolog', [Dir]).
  790old_config(directory, xpce, Dir) :-
  791    expand_file_name('~/.xpce', [Dir]).
  792old_config(directory, history, Dir) :-
  793    expand_file_name('~/.swipl-dir-history', [Dir]).
  794old_config(directory, pack, Dir) :-
  795    (   catch(expand_file_name('~/lib/swipl/pack', [Dir]), _, fail)
  796    ;   absolute_file_name(swi(pack), Dir,
  797                           [ file_type(directory), solutions(all) ])
  798    ).
  799
  800new_config(file, init, File) :-
  801    absolute_file_name(user_app_config('init.pl'), File,
  802                       [ solutions(all) ]).
  803new_config(directory, lib, Dir) :-
  804    config_dir(user_app_config(lib), Dir).
  805new_config(directory, xpce, Dir) :-
  806    config_dir(user_app_config(xpce), Dir).
  807new_config(directory, history, Dir) :-
  808    config_dir(user_app_config('dir-history'), Dir).
  809new_config(directory, pack, Dir) :-
  810    config_dir([app_data(pack), swi(pack)], Dir).
  811
  812config_dir(Aliases, Dir) :-
  813    is_list(Aliases),
  814    !,
  815    (   member(Alias, Aliases),
  816        absolute_file_name(Alias, Dir,
  817                           [ file_type(directory), solutions(all) ])
  818    *-> true
  819    ;   member(Alias, Aliases),
  820        absolute_file_name(Alias, Dir,
  821                           [ solutions(all) ])
  822    ).
  823config_dir(Alias, Dir) :-
  824    (   absolute_file_name(Alias, Dir,
  825                           [ file_type(directory), solutions(all) ])
  826    *-> true
  827    ;   absolute_file_name(Alias, Dir,
  828                           [ solutions(all) ])
  829    ).
  830
  831create_parent_dir(NewFile) :-
  832    file_directory_name(NewFile, Dir),
  833    create_parent_dir_(Dir).
  834
  835create_parent_dir_(Dir) :-
  836    exists_directory(Dir),
  837    '$my_file'(Dir),
  838    !.
  839create_parent_dir_(Dir) :-
  840    file_directory_name(Dir, Parent),
  841    Parent \== Dir,
  842    create_parent_dir_(Parent),
  843    make_directory(Dir).
  844
  845prolog:message(config(Id, Issue)) -->
  846    [ 'Config: '-[] ],
  847    config_description(Id),
  848    config_issue(Issue).
  849
  850config_description(init) -->
  851    [ '(user initialization file) '-[], nl ].
  852config_description(lib) -->
  853    [ '(user library) '-[], nl ].
  854config_description(pack) -->
  855    [ '(add-ons) '-[], nl ].
  856config_description(history) -->
  857    [ '(command line history) '-[], nl ].
  858config_description(xpce) -->
  859    [ '(gui) '-[], nl ].
  860
  861config_issue(move(Type, Old, New)) -->
  862    [ '  found ~w "~w"'-[Type, Old], nl ],
  863    [ '  new location is "~w"'-[New] ].
  864config_issue(moved(Type, Old, New)) -->
  865    [ '  found ~w "~w"'-[Type, Old], nl ],
  866    [ '  moved to new location "~w"'-[New] ].
  867config_issue(different(Type, Old, New)) -->
  868    [ '  found different ~w "~w"'-[Type, Old], nl ],
  869    [ '  new location is "~w"'-[New] ].
  870
  871		 /*******************************
  872		 *         AUTO LOADING		*
  873		 *******************************/
 check_autoload
Find possible ambiguous predicates in the autoload index.
  879check_autoload :-
  880    findall(Name/Arity, '$in_library'(Name, Arity, _Path), PIs),
  881    msort(PIs, Sorted),
  882    clumped(Sorted, Clumped),
  883    sort(2, >=, Clumped, ClumpedS),
  884    ambiguous_autoload(ClumpedS).
  885
  886ambiguous_autoload([PI-N|T]) :-
  887    N > 1,
  888    !,
  889    warn_ambiguous_autoload(PI),
  890    ambiguous_autoload(T).
  891ambiguous_autoload(_).
  892
  893warn_ambiguous_autoload(PI) :-
  894    PI = Name/Arity,
  895    findall(PlFile,
  896            ( '$in_library'(Name, Arity, File),
  897              file_name_extension(File, pl, PlFile)
  898            ), PlFiles),
  899    print_message(warning, installation(ambiguous_autoload(PI, PlFiles)))