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