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-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]).

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.
   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), _{}).
  141component(library(janus), _{features:python_version}).
  142
  143issue_base('http://www.swi-prolog.org/build/issues/').
  144
  145:- thread_local
  146    issue/1.  147
  148:- meta_predicate
  149    run_silent(0, +).
 check_installation
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.

  166check_installation :-
  167    print_message(informational, installation(checking)),
  168    check_installation_(InstallIssues),
  169    check_on_path,
  170    check_config_files(ConfigIssues),
  171    maplist(print_message(warning), ConfigIssues),
  172    append(InstallIssues, ConfigIssues, Issues),
  173    (   Issues == []
  174    ->  print_message(informational, installation(perfect))
  175    ;   length(Issues, Count),
  176        print_message(warning, installation(imperfect(Count)))
  177    ).
 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).
  187check_installation(Issues) :-
  188    check_installation_(Issues0),
  189    maplist(public_issue, Issues0, Issues).
  190
  191public_issue(installation(Term), Source-Issue) :-
  192    functor(Term, Issue, _),
  193    arg(1, Term, Properties),
  194    Source = Properties.source.
  195
  196check_installation_(Issues) :-
  197    retractall(issue(_)),
  198    forall(component(Source, _Properties),
  199           check_component(Source)),
  200    findall(I, retract(issue(I)), Issues).
  201
  202check_component(Source) :-
  203    component(Source, Properties),
  204    !,
  205    check_component(Source, Properties.put(source,Source)).
  206
  207check_component(_Source, Properties) :-
  208    OS = Properties.get(os),
  209    \+ current_os(OS),
  210    !.
  211check_component(Source, Properties) :-
  212    compound(Source),
  213    !,
  214    check_source(Source, Properties).
  215check_component(Feature, Properties) :-
  216    print_message(informational, installation(checking(Feature))),
  217    (   call(Properties.test)
  218    ->  print_message(informational, installation(ok))
  219    ;   print_issue(installation(missing(Properties)))
  220    ).
  221
  222check_source(Source, Properties) :-
  223    exists_source(Source),
  224    !,
  225    print_message(informational, installation(loading(Source))),
  226    (   run_silent(( (   Pre = Properties.get(pre)
  227                     ->  call(Pre)
  228                     ;   true
  229                     ),
  230                     load_files(Source, [silent(true), if(not_loaded)])
  231                   ),
  232                   Properties.put(action, load))
  233    ->  test_component(Properties),
  234        print_message(informational, installation(ok)),
  235        check_features(Properties)
  236    ;   true
  237    ).
  238check_source(_Source, Properties) :-
  239    Properties.get(optional) == true,
  240    !,
  241    print_message(silent,
  242                  installation(optional_not_found(Properties))).
  243check_source(_Source, Properties) :-
  244    print_issue(installation(not_found(Properties))).
  245
  246current_os(unix)    :- current_prolog_flag(unix, true).
  247current_os(windows) :- current_prolog_flag(windows, true).
  248current_os(linux)   :- current_prolog_flag(arch, Arch), sub_atom(Arch, _, _, _, linux).
 test_component(+Properties) is semidet
Run additional tests to see whether the component really works.
  254test_component(Dict) :-
  255    Test = Dict.get(test),
  256    !,
  257    call(Test).
  258test_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.
  267check_features(Dict) :-
  268    Test = Dict.get(features),
  269    !,
  270    call(Test).
  271check_features(_).
 run_silent(:Goal, +Properties) is semidet
Succeed if Goal succeeds and does not print any errors or warnings.
  279run_silent(Goal, Properties) :-
  280    run_collect_messages(Goal, Result, Messages),
  281    (   Result == true,
  282        Messages == []
  283    ->  true
  284    ;   print_issue(installation(failed(Properties, Result, Messages))),
  285        fail
  286    ).
 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.
  298:- thread_local
  299    got_message/1.  300
  301run_collect_messages(Goal, Result, Messages) :-
  302    setup_call_cleanup(
  303        asserta((user:thread_message_hook(Term,Kind,Lines) :-
  304                    error_kind(Kind),
  305                    assertz(got_message(message(Term,Kind,Lines)))), Ref),
  306        (   catch(Goal, E, true)
  307        ->  (   var(E)
  308            ->  Result0 = true
  309            ;   Result0 = exception(E)
  310            )
  311        ;   Result0 = false
  312        ),
  313        erase(Ref)),
  314    findall(Msg, retract(got_message(Msg)), Messages),
  315    Result = Result0.
  316
  317error_kind(warning).
  318error_kind(error).
  319
  320
  321                 /*******************************
  322                 *         SPECIAL TESTS        *
  323                 *******************************/
 test_tcmalloc
  327:- if(current_predicate(malloc_property/1)).  328test_tcmalloc :-
  329    malloc_property('generic.current_allocated_bytes'(Bytes)),
  330    Bytes > 1 000 000.
  331:- else.  332test_tcmalloc :-
  333    fail.
  334:- endif.
 archive_features
Report features supported by library(archive).
  340archive_features :-
  341    tmp_file_stream(utf8, Name, Out),
  342    close(Out),
  343    findall(F, archive_filter(F, Name), Filters),
  344    print_message(informational, installation(archive(filters, Filters))),
  345    findall(F, archive_format(F, Name), Formats),
  346    print_message(informational, installation(archive(formats, Formats))),
  347    delete_file(Name).
  348
  349archive_filter(F, Name) :-
  350    a_filter(F),
  351    catch(archive_open(Name, A, [filter(F)]), E, true),
  352    (   var(E)
  353    ->  archive_close(A)
  354    ;   true
  355    ),
  356    \+ subsumes_term(error(domain_error(filter, _),_), E).
  357
  358archive_format(F, Name) :-
  359    a_format(F),
  360    catch(archive_open(Name, A, [format(F)]), E, true),
  361    (   var(E)
  362    ->  archive_close(A)
  363    ;   true
  364    ),
  365    \+ subsumes_term(error(domain_error(format, _),_), E).
  366
  367a_filter(bzip2).
  368a_filter(compress).
  369a_filter(gzip).
  370a_filter(grzip).
  371a_filter(lrzip).
  372a_filter(lzip).
  373a_filter(lzma).
  374a_filter(lzop).
  375a_filter(none).
  376a_filter(rpm).
  377a_filter(uu).
  378a_filter(xz).
  379
  380a_format('7zip').
  381a_format(ar).
  382a_format(cab).
  383a_format(cpio).
  384a_format(empty).
  385a_format(gnutar).
  386a_format(iso9660).
  387a_format(lha).
  388a_format(mtree).
  389a_format(rar).
  390a_format(raw).
  391a_format(tar).
  392a_format(xar).
  393a_format(zip).
 pcre_features
  397pcre_features :-
  398    findall(X, pcre_missing(X), Missing),
  399    (   Missing == []
  400    ->  true
  401    ;   print_message(warning, installation(pcre_missing(Missing)))
  402    ),
  403    (   re_config(compiled_widths(Widths)),
  404        1 =:= Widths /\ 1
  405    ->  true
  406    ;   print_message(warning, installation(pcre_missing('8-bit support')))
  407    ).
  408
  409pcre_missing(X) :-
  410    pcre_must_have(X),
  411    Term =.. [X,true],
  412    \+ catch(re_config(Term), _, fail).
  413
  414pcre_must_have(unicode).
 jquery_file
Test whether jquery.js can be found
  420jquery_file :-
  421    setting(jquery:version, File),
  422    (   absolute_file_name(js(File), Path, [access(read), file_errors(fail)])
  423    ->  print_message(informational, installation(jquery(found(Path))))
  424    ;   print_message(warning, installation(jquery(not_found(File))))
  425    ).
  426
  427sweep_emacs_module :-
  428    with_output_to(string(S), write_sweep_module_location),
  429    split_string(S, "\n", "\n", [VersionInfo|Modules]),
  430    must_be(oneof(["V 1"]), VersionInfo),
  431    (   maplist(check_sweep_lib, Modules)
  432    ->  print_message(informational, installation(sweep(found(Modules))))
  433    ;   print_message(warning, installation(sweep(not_found(Modules))))
  434    ).
  435
  436check_sweep_lib(Line) :-
  437    sub_atom(Line, B, _, A, ' '),
  438    sub_atom(Line, 0, B, _, Type),
  439    must_be(oneof(['L', 'M']), Type),
  440    sub_atom(Line, _, A, 0, Lib),
  441    exists_file(Lib).
  442
  443python_version :-
  444    py_call(sys:version, Version),
  445    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.
  454check_on_path :-
  455    current_prolog_flag(executable, EXEFlag),
  456    prolog_to_os_filename(EXE, EXEFlag),
  457    file_base_name(EXE, Prog),
  458    absolute_file_name(EXE, AbsExe,
  459                       [ access(execute),
  460                         file_errors(fail)
  461                       ]),
  462    !,
  463    prolog_to_os_filename(AbsExe, OsExe),
  464    (   absolute_file_name(path(Prog), OnPath,
  465                           [ access(execute),
  466                             file_errors(fail)
  467                           ])
  468    ->  (   same_file(EXE, OnPath)
  469        ->  true
  470        ;   absolute_file_name(path(Prog), OnPathAny,
  471                               [ access(execute),
  472                                 file_errors(fail),
  473                                 solutions(all)
  474                               ]),
  475            same_file(EXE, OnPathAny)
  476        ->  print_message(warning, installation(not_first_on_path(OsExe, OnPath)))
  477        ;   print_message(warning, installation(not_same_on_path(OsExe, OnPath)))
  478        )
  479    ;   print_message(warning, installation(not_on_path(OsExe, Prog)))
  480    ).
  481check_on_path.
  482
  483
  484		 /*******************************
  485		 *           RUN TESTS		*
  486		 *******************************/
 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.
  503test_installation :-
  504    test_installation([]).
  505
  506test_installation(Options) :-
  507    absolute_file_name(swi(test/test),
  508                       TestFile,
  509                       [ access(read),
  510                         file_errors(fail),
  511                         file_type(prolog)
  512                       ]),
  513    !,
  514    test_installation_run(TestFile, Options).
  515test_installation(_Options) :-
  516    print_message(warning, installation(testing(no_installed_tests))).
  517
  518test_installation_run(TestFile, Options) :-
  519    (   option(package(_), Options)
  520    ->  merge_options(Options,
  521                      [ core(false),
  522                        subdirs(false)
  523                      ], TestOptions)
  524    ;   merge_options(Options,
  525                      [ packages(true)
  526                      ], TestOptions)
  527    ),
  528    load_files(user:TestFile),
  529    current_prolog_flag(verbose, Old),
  530    setup_call_cleanup(
  531        set_prolog_flag(verbose, silent),
  532        user:test([], TestOptions),
  533        set_prolog_flag(verbose, Old)).
  534
  535
  536                 /*******************************
  537                 *            MESSAGES          *
  538                 *******************************/
  539
  540:- multifile
  541    prolog:message//1.  542
  543print_issue(Term) :-
  544    assertz(issue(Term)),
  545    print_message(warning, Term).
  546
  547issue_url(Properties, URL) :-
  548    Local = Properties.get(url),
  549    !,
  550    issue_base(Base),
  551    atom_concat(Base, Local, URL).
  552issue_url(Properties, URL) :-
  553    Properties.get(source) = library(Segments),
  554    !,
  555    path_segments_atom(Segments, Base),
  556    file_name_extension(Base, html, URLFile),
  557    issue_base(Issues),
  558    atom_concat(Issues, URLFile, URL).
  559
  560prolog:message(installation(Message)) -->
  561    message(Message).
  562
  563message(checking) -->
  564    { current_prolog_flag(address_bits, Bits) },
  565    { current_prolog_flag(arch, Arch) },
  566    { current_prolog_flag(home, Home) },
  567    { current_prolog_flag(cpu_count, Cores) },
  568    [ 'Checking your SWI-Prolog kit for common issues ...'-[], nl, nl ],
  569    [ 'Version: ~`.t~24| '-[] ], '$messages':prolog_message(version), [nl],
  570    [ 'Address bits: ~`.t~24| ~d'-[Bits] ], [nl],
  571    [ 'Architecture: ~`.t~24| ~w'-[Arch] ], [nl],
  572    [ 'Installed at: ~`.t~24| ~w'-[Home] ], [nl],
  573    [ 'Cores: ~`.t~24| ~w'-[Cores] ], [nl],
  574    [ nl ].
  575message(perfect) -->
  576    [ nl, 'Congratulations, your kit seems sound and complete!'-[] ].
  577message(imperfect(N)) -->
  578    [ 'Found ~w issues.'-[N] ].
  579message(checking(Feature)) -->
  580    [ 'Checking ~w ...'-[Feature], flush ].
  581message(missing(Properties)) -->
  582    [ at_same_line, '~`.t~48| not present'-[] ],
  583    details(Properties).
  584message(loading(Source)) -->
  585    [ 'Loading ~q ...'-[Source], flush ].
  586message(ok) -->
  587    [ at_same_line, '~`.t~48| ok'-[] ].
  588message(optional_not_found(Properties)) -->
  589    [ 'Optional ~q ~`.t~48| not present'-[Properties.source] ].
  590message(not_found(Properties)) -->
  591    [ '~q ~`.t~48| NOT FOUND'-[Properties.source] ],
  592    details(Properties).
  593message(failed(Properties, false, [])) -->
  594    !,
  595    [ at_same_line, '~`.t~48| FAILED'-[] ],
  596    details(Properties).
  597message(failed(Properties, exception(Ex0), [])) -->
  598    !,
  599    { strip_stack(Ex0, Ex),
  600      message_to_string(Ex, Msg) },
  601    [ '~w'-[Msg] ],
  602    details(Properties).
  603message(failed(Properties, true, Messages)) -->
  604    [ at_same_line, '~`.t~48| FAILED'-[] ],
  605    explain(Messages),
  606    details(Properties).
  607message(archive(What, Names)) -->
  608    [ '  Supported ~w: '-[What] ],
  609    list_names(Names).
  610message(pcre_missing(Features)) -->
  611    [ 'Missing libpcre features: '-[] ],
  612    list_names(Features).
  613message(not_first_on_path(EXE, OnPath)) -->
  614    { public_executable(EXE, PublicEXE),
  615      file_base_name(EXE, Prog)
  616    },
  617    [ 'The first ~w on '-[Prog] ], 'PATH', [ ' is ~p, while '-[OnPath], nl ],
  618    [ 'this version is ~p.'-[PublicEXE] ].
  619message(not_same_on_path(EXE, OnPath)) -->
  620    { public_executable(EXE, PublicEXE),
  621      file_base_name(EXE, Prog)
  622    },
  623    [ 'The ~w on '-[Prog] ], 'PATH', [ ' is ~p, while '-[OnPath], nl ],
  624    [ 'this version is ~p.'-[PublicEXE] ].
  625message(not_on_path(EXE, Prog)) -->
  626    { public_bin_dir(EXE, Dir),
  627      prolog_to_os_filename(Dir, OSDir)
  628    },
  629    [ 'Could not find ~w on '-[Prog] ], 'PATH', [ '. '-[], nl ],
  630    [ 'You may wish to add ~p to '-[OSDir] ], 'PATH', [ '. '-[], nl ].
  631message(jquery(found(Path))) -->
  632    [ '  jQuery from ~w'-[Path] ].
  633message(jquery(not_found(File))) -->
  634    [ '  Cannot find jQuery (~w)'-[File] ].
  635message(sweep(found(Paths))) -->
  636    [ '  GNU-Emacs plugin loads'-[] ],
  637    sequence(list_file, Paths).
  638message(sweep(not_found(Paths))) -->
  639    [ '  Could not find all GNU-Emacs libraries'-[] ],
  640    sequence(list_file, Paths).
  641message(testing(no_installed_tests)) -->
  642    [ '  Runtime testing is not enabled.', nl],
  643    [ '  Please recompile the system with INSTALL_TESTS enabled.' ].
  644message(janus(Version)) -->
  645    [ '  Python version ~w'-[Version] ].
  646
  647public_executable(EXE, PublicProg) :-
  648    file_base_name(EXE, Prog),
  649    file_directory_name(EXE, ArchDir),
  650    file_directory_name(ArchDir, BinDir),
  651    file_directory_name(BinDir, Home),
  652    file_directory_name(Home, Lib),
  653    file_directory_name(Lib, Prefix),
  654    atomic_list_concat([Prefix, bin, Prog], /, PublicProg),
  655    exists_file(PublicProg),
  656    same_file(EXE, PublicProg),
  657    !.
  658public_executable(EXE, EXE).
  659
  660public_bin_dir(EXE, Dir) :-
  661    public_executable(EXE, PublicEXE),
  662    file_directory_name(PublicEXE, Dir).
  663
  664
  665
  666'PATH' -->
  667    { current_prolog_flag(windows, true) },
  668    !,
  669    [ '%PATH%'-[] ].
  670'PATH' -->
  671    [ '$PATH'-[] ].
  672
  673strip_stack(error(Error, context(prolog_stack(S), Msg)),
  674            error(Error, context(_, Msg))) :-
  675    nonvar(S).
  676strip_stack(Error, Error).
  677
  678details(Properties) -->
  679    { issue_url(Properties, URL), !
  680    },
  681    [ nl, 'See ~w'-[URL] ].
  682details(_) --> [].
  683
  684explain(Messages) -->
  685    { Messages = [message(error(shared_object(open, _Message), _), _, _)|_]
  686    },
  687    !,
  688    [nl],
  689    (   { current_prolog_flag(windows, true) }
  690    ->  [ 'Cannot load required DLL'-[] ]
  691    ;   [ 'Cannot load required shared library'-[] ]
  692    ).
  693explain(Messages) -->
  694    print_messages(Messages).
  695
  696print_messages([]) --> [].
  697print_messages([message(_Term, _Kind, Lines)|T]) -->
  698    Lines, [nl],
  699    print_messages(T).
  700
  701list_names([]) --> [].
  702list_names([H|T]) -->
  703    [ '~w'-[H] ],
  704    (   {T==[]}
  705    ->  []
  706    ;   [ ', '-[] ],
  707        list_names(T)
  708    ).
  709
  710list_file(File) -->
  711    [ nl, '    '-[], url(File) ].
  712
  713
  714		 /*******************************
  715		 *          CONFIG FILES	*
  716		 *******************************/
 check_config_files
Examines the locations of config files. The config files have moved in version 8.1.15
  723check_config_files :-
  724    check_config_files(Issues),
  725    maplist(print_message(warning), Issues).
  726
  727check_config_files(Issues) :-
  728    findall(Issue, check_config_file(Issue), Issues).
  729
  730check_config_file(config(Id, move(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       ),
  736    once(new_config(Type, Id, NewFile)).
  737check_config_file(config(Id, different(Type, OldFile, NewFile))) :-
  738    old_config(Type, Id, OldFile),
  739    access_file(OldFile, exist),
  740    new_config(Type, Id, NewFile),
  741    access_file(NewFile, exist),
  742    \+ 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.
  749update_config_files :-
  750    old_config(Type, Id, OldFile),
  751    access_file(OldFile, exist),
  752    \+ ( new_config(Type, Id, NewFile),
  753         access_file(NewFile, exist)
  754       ),
  755    (   new_config(Type, Id, NewFile),
  756        \+ same_file(OldFile, NewFile),
  757        create_parent_dir(NewFile)
  758    ->  catch(rename_file(OldFile, NewFile), E,
  759              print_message(warning, E)),
  760        print_message(informational, config(Id, moved(Type, OldFile, NewFile)))
  761    ),
  762    fail.
  763update_config_files.
  764
  765old_config(file, init, File) :-
  766    current_prolog_flag(windows, true),
  767    win_folder(appdata, Base),
  768    atom_concat(Base, '/SWI-Prolog/swipl.ini', File).
  769old_config(file, init, File) :-
  770    expand_file_name('~/.swiplrc', [File]).
  771old_config(directory, lib, Dir) :-
  772    expand_file_name('~/lib/prolog', [Dir]).
  773old_config(directory, xpce, Dir) :-
  774    expand_file_name('~/.xpce', [Dir]).
  775old_config(directory, history, Dir) :-
  776    expand_file_name('~/.swipl-dir-history', [Dir]).
  777old_config(directory, pack, Dir) :-
  778    (   catch(expand_file_name('~/lib/swipl/pack', [Dir]), _, fail)
  779    ;   absolute_file_name(swi(pack), Dir,
  780                           [ file_type(directory), solutions(all) ])
  781    ).
  782
  783new_config(file, init, File) :-
  784    absolute_file_name(user_app_config('init.pl'), File,
  785                       [ solutions(all) ]).
  786new_config(directory, lib, Dir) :-
  787    config_dir(user_app_config(lib), Dir).
  788new_config(directory, xpce, Dir) :-
  789    config_dir(user_app_config(xpce), Dir).
  790new_config(directory, history, Dir) :-
  791    config_dir(user_app_config('dir-history'), Dir).
  792new_config(directory, pack, Dir) :-
  793    config_dir([app_data(pack), swi(pack)], Dir).
  794
  795config_dir(Aliases, Dir) :-
  796    is_list(Aliases),
  797    !,
  798    (   member(Alias, Aliases),
  799        absolute_file_name(Alias, Dir,
  800                           [ file_type(directory), solutions(all) ])
  801    *-> true
  802    ;   member(Alias, Aliases),
  803        absolute_file_name(Alias, Dir,
  804                           [ solutions(all) ])
  805    ).
  806config_dir(Alias, Dir) :-
  807    (   absolute_file_name(Alias, Dir,
  808                           [ file_type(directory), solutions(all) ])
  809    *-> true
  810    ;   absolute_file_name(Alias, Dir,
  811                           [ solutions(all) ])
  812    ).
  813
  814create_parent_dir(NewFile) :-
  815    file_directory_name(NewFile, Dir),
  816    create_parent_dir_(Dir).
  817
  818create_parent_dir_(Dir) :-
  819    exists_directory(Dir),
  820    '$my_file'(Dir),
  821    !.
  822create_parent_dir_(Dir) :-
  823    file_directory_name(Dir, Parent),
  824    Parent \== Dir,
  825    create_parent_dir_(Parent),
  826    make_directory(Dir).
  827
  828prolog:message(config(Id, Issue)) -->
  829    [ 'Config: '-[] ],
  830    config_description(Id),
  831    config_issue(Issue).
  832
  833config_description(init) -->
  834    [ '(user initialization file) '-[], nl ].
  835config_description(lib) -->
  836    [ '(user library) '-[], nl ].
  837config_description(pack) -->
  838    [ '(add-ons) '-[], nl ].
  839config_description(history) -->
  840    [ '(command line history) '-[], nl ].
  841config_description(xpce) -->
  842    [ '(gui) '-[], nl ].
  843
  844config_issue(move(Type, Old, New)) -->
  845    [ '  found ~w "~w"'-[Type, Old], nl ],
  846    [ '  new location is "~w"'-[New] ].
  847config_issue(moved(Type, Old, New)) -->
  848    [ '  found ~w "~w"'-[Type, Old], nl ],
  849    [ '  moved to new location "~w"'-[New] ].
  850config_issue(different(Type, Old, New)) -->
  851    [ '  found different ~w "~w"'-[Type, Old], nl ],
  852    [ '  new location is "~w"'-[New] ]