View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  1985-2025, University of Amsterdam
    7                              VU University 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('$toplevel',
   38          [ '$initialise'/0,            % start Prolog
   39            '$toplevel'/0,              % Prolog top-level (re-entrant)
   40            '$compile'/0,               % `-c' toplevel
   41            '$config'/0,                % --dump-runtime-variables toplevel
   42            initialize/0,               % Run program initialization
   43            version/0,                  % Write initial banner
   44            version/1,                  % Add message to the banner
   45            prolog/0,                   % user toplevel predicate
   46            '$query_loop'/0,            % toplevel predicate
   47            '$execute_query'/3,         % +Query, +Bindings, -Truth
   48            residual_goals/1,           % +Callable
   49            (initialization)/1,         % initialization goal (directive)
   50            '$thread_init'/0,           % initialise thread
   51            (thread_initialization)/1   % thread initialization goal
   52            ]).   53
   54
   55                 /*******************************
   56                 *         VERSION BANNER       *
   57                 *******************************/
   58
   59:- dynamic
   60    prolog:version_msg/1.   61
   62%!  version is det.
   63%
   64%   Print the Prolog banner message and messages registered using
   65%   version/1.
   66
   67version :-
   68    print_message(banner, welcome).
   69
   70%!  version(+Message) is det.
   71%
   72%   Add message to version/0
   73
   74:- multifile
   75    system:term_expansion/2.   76
   77system:term_expansion((:- version(Message)),
   78                      prolog:version_msg(Message)).
   79
   80version(Message) :-
   81    (   prolog:version_msg(Message)
   82    ->  true
   83    ;   assertz(prolog:version_msg(Message))
   84    ).
   85
   86
   87                /********************************
   88                *         INITIALISATION        *
   89                *********************************/
   90
   91%!  load_init_file(+ScriptMode) is det.
   92%
   93%   Load the user customization file. This can  be done using ``swipl -f
   94%   file`` or simply using ``swipl``. In the   first  case we search the
   95%   file both directly and over  the   alias  `user_app_config`.  In the
   96%   latter case we only use the alias.
   97
   98load_init_file(_) :-
   99    '$cmd_option_val'(init_file, OsFile),
  100    !,
  101    prolog_to_os_filename(File, OsFile),
  102    load_init_file(File, explicit).
  103load_init_file(prolog) :-
  104    !,
  105    load_init_file('init.pl', implicit).
  106load_init_file(none) :-
  107    !,
  108    load_init_file('init.pl', implicit).
  109load_init_file(_).
  110
  111%!  loaded_init_file(?Base, ?AbsFile)
  112%
  113%   Used by prolog_load_context/2 to confirm we are loading a script.
  114
  115:- dynamic
  116    loaded_init_file/2.             % already loaded init files
  117
  118load_init_file(none, _) :- !.
  119load_init_file(Base, _) :-
  120    loaded_init_file(Base, _),
  121    !.
  122load_init_file(InitFile, explicit) :-
  123    exists_file(InitFile),
  124    !,
  125    ensure_loaded(user:InitFile).
  126load_init_file(Base, _) :-
  127    absolute_file_name(user_app_config(Base), InitFile,
  128                       [ access(read),
  129                         file_errors(fail)
  130                       ]),
  131    !,
  132    asserta(loaded_init_file(Base, InitFile)),
  133    load_files(user:InitFile,
  134               [ scope_settings(false)
  135               ]).
  136load_init_file('init.pl', implicit) :-
  137    (   current_prolog_flag(windows, true),
  138        absolute_file_name(user_profile('swipl.ini'), InitFile,
  139                           [ access(read),
  140                             file_errors(fail)
  141                           ])
  142    ;   expand_file_name('~/.swiplrc', [InitFile]),
  143        exists_file(InitFile)
  144    ),
  145    !,
  146    print_message(warning, backcomp(init_file_moved(InitFile))).
  147load_init_file(_, _).
  148
  149'$load_system_init_file' :-
  150    loaded_init_file(system, _),
  151    !.
  152'$load_system_init_file' :-
  153    '$cmd_option_val'(system_init_file, Base),
  154    Base \== none,
  155    current_prolog_flag(home, Home),
  156    file_name_extension(Base, rc, Name),
  157    atomic_list_concat([Home, '/', Name], File),
  158    absolute_file_name(File, Path,
  159                       [ file_type(prolog),
  160                         access(read),
  161                         file_errors(fail)
  162                       ]),
  163    asserta(loaded_init_file(system, Path)),
  164    load_files(user:Path,
  165               [ silent(true),
  166                 scope_settings(false)
  167               ]),
  168    !.
  169'$load_system_init_file'.
  170
  171'$load_script_file' :-
  172    loaded_init_file(script, _),
  173    !.
  174'$load_script_file' :-
  175    '$cmd_option_val'(script_file, OsFiles),
  176    load_script_files(OsFiles).
  177
  178load_script_files([]).
  179load_script_files([OsFile|More]) :-
  180    prolog_to_os_filename(File, OsFile),
  181    (   absolute_file_name(File, Path,
  182                           [ file_type(prolog),
  183                             access(read),
  184                             file_errors(fail)
  185                           ])
  186    ->  asserta(loaded_init_file(script, Path)),
  187        load_files(user:Path),
  188        load_files(user:More)
  189    ;   throw(error(existence_error(script_file, File), _))
  190    ).
  191
  192
  193                 /*******************************
  194                 *       AT_INITIALISATION      *
  195                 *******************************/
  196
  197:- meta_predicate
  198    initialization(0).  199
  200:- '$iso'((initialization)/1).  201
  202%!  initialization(:Goal)
  203%
  204%   Runs Goal after loading the file in which this directive
  205%   appears as well as after restoring a saved state.
  206%
  207%   @see initialization/2
  208
  209initialization(Goal) :-
  210    Goal = _:G,
  211    prolog:initialize_now(G, Use),
  212    !,
  213    print_message(warning, initialize_now(G, Use)),
  214    initialization(Goal, now).
  215initialization(Goal) :-
  216    initialization(Goal, after_load).
  217
  218:- multifile
  219    prolog:initialize_now/2,
  220    prolog:message//1.  221
  222prolog:initialize_now(load_foreign_library(_),
  223                      'use :- use_foreign_library/1 instead').
  224prolog:initialize_now(load_foreign_library(_,_),
  225                      'use :- use_foreign_library/2 instead').
  226
  227prolog:message(initialize_now(Goal, Use)) -->
  228    [ 'Initialization goal ~p will be executed'-[Goal],nl,
  229      'immediately for backward compatibility reasons', nl,
  230      '~w'-[Use]
  231    ].
  232
  233'$run_initialization' :-
  234    '$set_prolog_file_extension',
  235    '$run_initialization'(_, []),
  236    '$thread_init'.
  237
  238%!  initialize
  239%
  240%   Run goals registered with `:-  initialization(Goal, program).`. Stop
  241%   with an exception if a goal fails or raises an exception.
  242
  243initialize :-
  244    forall('$init_goal'(when(program), Goal, Ctx),
  245           run_initialize(Goal, Ctx)).
  246
  247run_initialize(Goal, Ctx) :-
  248    (   catch(Goal, E, true),
  249        (   var(E)
  250        ->  true
  251        ;   throw(error(initialization_error(E, Goal, Ctx), _))
  252        )
  253    ;   throw(error(initialization_error(failed, Goal, Ctx), _))
  254    ).
  255
  256
  257                 /*******************************
  258                 *     THREAD INITIALIZATION    *
  259                 *******************************/
  260
  261:- meta_predicate
  262    thread_initialization(0).  263:- dynamic
  264    '$at_thread_initialization'/1.  265
  266%!  thread_initialization(:Goal)
  267%
  268%   Run Goal now and everytime a new thread is created.
  269
  270thread_initialization(Goal) :-
  271    assert('$at_thread_initialization'(Goal)),
  272    call(Goal),
  273    !.
  274
  275'$thread_init' :-
  276    (   '$at_thread_initialization'(Goal),
  277        (   call(Goal)
  278        ->  fail
  279        ;   fail
  280        )
  281    ;   true
  282    ).
  283
  284
  285                 /*******************************
  286                 *     FILE SEARCH PATH (-p)    *
  287                 *******************************/
  288
  289%!  '$set_file_search_paths' is det.
  290%
  291%   Process -p PathSpec options.
  292
  293'$set_file_search_paths' :-
  294    '$cmd_option_val'(search_paths, Paths),
  295    (   '$member'(Path, Paths),
  296        atom_chars(Path, Chars),
  297        (   phrase('$search_path'(Name, Aliases), Chars)
  298        ->  '$reverse'(Aliases, Aliases1),
  299            forall('$member'(Alias, Aliases1),
  300                   asserta(user:file_search_path(Name, Alias)))
  301        ;   print_message(error, commandline_arg_type(p, Path))
  302        ),
  303        fail ; true
  304    ).
  305
  306'$search_path'(Name, Aliases) -->
  307    '$string'(NameChars),
  308    [=],
  309    !,
  310    {atom_chars(Name, NameChars)},
  311    '$search_aliases'(Aliases).
  312
  313'$search_aliases'([Alias|More]) -->
  314    '$string'(AliasChars),
  315    path_sep,
  316    !,
  317    { '$make_alias'(AliasChars, Alias) },
  318    '$search_aliases'(More).
  319'$search_aliases'([Alias]) -->
  320    '$string'(AliasChars),
  321    '$eos',
  322    !,
  323    { '$make_alias'(AliasChars, Alias) }.
  324
  325path_sep -->
  326    { current_prolog_flag(path_sep, Sep) },
  327    [Sep].
  328
  329'$string'([]) --> [].
  330'$string'([H|T]) --> [H], '$string'(T).
  331
  332'$eos'([], []).
  333
  334'$make_alias'(Chars, Alias) :-
  335    catch(term_to_atom(Alias, Chars), _, fail),
  336    (   atom(Alias)
  337    ;   functor(Alias, F, 1),
  338        F \== /
  339    ),
  340    !.
  341'$make_alias'(Chars, Alias) :-
  342    atom_chars(Alias, Chars).
  343
  344
  345                 /*******************************
  346                 *   LOADING ASSIOCIATED FILES  *
  347                 *******************************/
  348
  349%!  argv_prolog_files(-Files, -ScriptMode) is det.
  350%
  351%   Update the Prolog flag `argv`, extracting  the leading script files.
  352%   This is called after the C based  parser removed Prolog options such
  353%   as ``-q``, ``-f none``, etc.  These   options  are available through
  354%   '$cmd_option_val'/2.
  355%
  356%   Our task is to update the Prolog flag   `argv`  and return a list of
  357%   the files to be loaded.   The rules are:
  358%
  359%     - If we find ``--`` all remaining options must go to `argv`
  360%     - If we find *.pl files, these are added to Files and possibly
  361%       remaining arguments are "script" arguments.
  362%     - If we find an existing file, this is Files and possibly
  363%       remaining arguments are "script" arguments.
  364%     - File we find [search:]name, find search(name) as Prolog file,
  365%       make this the content of `Files` and pass the remainder as
  366%       options to `argv`.
  367%
  368%   @arg ScriptMode is one of
  369%
  370%     - exe
  371%       Program is a saved state
  372%     - prolog
  373%       One or more *.pl files on commandline
  374%     - script
  375%       Single existing file on commandline
  376%     - app
  377%       [path:]cli-name on commandline
  378%     - none
  379%       Normal interactive session
  380
  381argv_prolog_files([], exe) :-
  382    current_prolog_flag(saved_program_class, runtime),
  383    !,
  384    clean_argv.
  385argv_prolog_files(Files, ScriptMode) :-
  386    current_prolog_flag(argv, Argv),
  387    no_option_files(Argv, Argv1, Files, ScriptMode),
  388    (   (   nonvar(ScriptMode)
  389        ;   Argv1 == []
  390        )
  391    ->  (   Argv1 \== Argv
  392        ->  set_prolog_flag(argv, Argv1)
  393        ;   true
  394        )
  395    ;   '$usage',
  396        halt(1)
  397    ).
  398
  399no_option_files([--|Argv], Argv, [], ScriptMode) :-
  400    !,
  401    (   ScriptMode = none
  402    ->  true
  403    ;   true
  404    ).
  405no_option_files([Opt|_], _, _, ScriptMode) :-
  406    var(ScriptMode),
  407    sub_atom(Opt, 0, _, _, '-'),
  408    !,
  409    '$usage',
  410    halt(1).
  411no_option_files([OsFile|Argv0], Argv, [File|T], ScriptMode) :-
  412    file_name_extension(_, Ext, OsFile),
  413    user:prolog_file_type(Ext, prolog),
  414    !,
  415    ScriptMode = prolog,
  416    prolog_to_os_filename(File, OsFile),
  417    no_option_files(Argv0, Argv, T, ScriptMode).
  418no_option_files([OsScript|Argv], Argv, [Script], ScriptMode) :-
  419    var(ScriptMode),
  420    !,
  421    prolog_to_os_filename(PlScript, OsScript),
  422    (   exists_file(PlScript)
  423    ->  Script = PlScript,
  424        ScriptMode = script
  425    ;   cli_script(OsScript, Script)
  426    ->  ScriptMode = app,
  427        set_prolog_flag(app_name, OsScript)
  428    ;   '$existence_error'(file, PlScript)
  429    ).
  430no_option_files(Argv, Argv, [], ScriptMode) :-
  431    (   ScriptMode = none
  432    ->  true
  433    ;   true
  434    ).
  435
  436cli_script(CLI, Script) :-
  437    (   sub_atom(CLI, Pre, _, Post, ':')
  438    ->  sub_atom(CLI, 0, Pre, _, SearchPath),
  439        sub_atom(CLI, _, Post, 0, Base),
  440        Spec =.. [SearchPath, Base]
  441    ;   Spec = app(CLI)
  442    ),
  443    absolute_file_name(Spec, Script,
  444                       [ file_type(prolog),
  445                         access(exist),
  446                         file_errors(fail)
  447                       ]).
  448
  449clean_argv :-
  450    (   current_prolog_flag(argv, [--|Argv])
  451    ->  set_prolog_flag(argv, Argv)
  452    ;   true
  453    ).
  454
  455%!  win_associated_files(+Files)
  456%
  457%   If SWI-Prolog is started as <exe> <file>.<ext>, where <ext> is
  458%   the extension registered for associated files, set the Prolog
  459%   flag associated_file, switch to the directory holding the file
  460%   and -if possible- adjust the window title.
  461
  462win_associated_files(Files) :-
  463    (   Files = [File|_]
  464    ->  absolute_file_name(File, AbsFile),
  465        set_prolog_flag(associated_file, AbsFile),
  466        set_working_directory(File),
  467        set_window_title(Files)
  468    ;   true
  469    ).
  470
  471%!  set_working_directory(+File)
  472%
  473%   When opening as a GUI application, e.g.,  by opening a file from
  474%   the Finder/Explorer/..., we typically  want   to  change working
  475%   directory to the location of  the   primary  file.  We currently
  476%   detect that we are a GUI app  by the Prolog flag `console_menu`,
  477%   which is set by swipl-win[.exe].
  478
  479set_working_directory(File) :-
  480    current_prolog_flag(console_menu, true),
  481    access_file(File, read),
  482    !,
  483    file_directory_name(File, Dir),
  484    working_directory(_, Dir).
  485set_working_directory(_).
  486
  487set_window_title([File|More]) :-
  488    current_predicate(system:window_title/2),
  489    !,
  490    (   More == []
  491    ->  Extra = []
  492    ;   Extra = ['...']
  493    ),
  494    atomic_list_concat(['SWI-Prolog --', File | Extra], ' ', Title),
  495    system:window_title(_, Title).
  496set_window_title(_).
  497
  498
  499%!  start_pldoc
  500%
  501%   If the option ``--pldoc[=port]`` is given, load the PlDoc system.
  502
  503start_pldoc :-
  504    '$cmd_option_val'(pldoc_server, Server),
  505    (   Server == ''
  506    ->  call((doc_server(_), doc_browser))
  507    ;   catch(atom_number(Server, Port), _, fail)
  508    ->  call(doc_server(Port))
  509    ;   print_message(error, option_usage(pldoc)),
  510        halt(1)
  511    ).
  512start_pldoc.
  513
  514
  515%!  load_associated_files(+Files)
  516%
  517%   Load Prolog files specified from the commandline.
  518
  519load_associated_files(Files) :-
  520    load_files(user:Files).
  521
  522hkey('HKEY_CURRENT_USER/Software/SWI/Prolog').
  523hkey('HKEY_LOCAL_MACHINE/Software/SWI/Prolog').
  524
  525'$set_prolog_file_extension' :-
  526    current_prolog_flag(windows, true),
  527    hkey(Key),
  528    catch(win_registry_get_value(Key, fileExtension, Ext0),
  529          _, fail),
  530    !,
  531    (   atom_concat('.', Ext, Ext0)
  532    ->  true
  533    ;   Ext = Ext0
  534    ),
  535    (   user:prolog_file_type(Ext, prolog)
  536    ->  true
  537    ;   asserta(user:prolog_file_type(Ext, prolog))
  538    ).
  539'$set_prolog_file_extension'.
  540
  541
  542                /********************************
  543                *        TOPLEVEL GOALS         *
  544                *********************************/
  545
  546%!  '$initialise' is semidet.
  547%
  548%   Called from PL_initialise()  to  do  the   Prolog  part  of  the
  549%   initialization. If an exception  occurs,   this  is  printed and
  550%   '$initialise' fails.
  551
  552'$initialise' :-
  553    catch(initialise_prolog, E, initialise_error(E)).
  554
  555initialise_error(unwind(abort)) :- !.
  556initialise_error(unwind(halt(_))) :- !.
  557initialise_error(E) :-
  558    print_message(error, initialization_exception(E)),
  559    fail.
  560
  561initialise_prolog :-
  562    '$clean_history',
  563    apply_defines,
  564    apple_setup_app,                            % MacOS cwd/locale setup for swipl-win
  565    init_optimise,
  566    '$run_initialization',
  567    '$load_system_init_file',                   % -F file
  568    set_toplevel,                               % set `toplevel_goal` flag from -t
  569    '$set_file_search_paths',                   % handle -p alias=dir[:dir]*
  570    init_debug_flags,
  571    start_pldoc,                                % handle --pldoc[=port]
  572    opt_attach_packs,
  573    argv_prolog_files(Files, ScriptMode),
  574    load_init_file(ScriptMode),                 % -f file
  575    catch(setup_colors, E, print_message(warning, E)),
  576    win_associated_files(Files),                % swipl-win: cd and update title
  577    '$load_script_file',                        % -s file (may be repeated)
  578    load_associated_files(Files),
  579    '$cmd_option_val'(goals, Goals),            % -g goal (may be repeated)
  580    (   ScriptMode == app
  581    ->  run_program_init,                       % initialization(Goal, program)
  582        run_main_init(true)
  583    ;   Goals == [],
  584        \+ '$init_goal'(when(_), _, _)          % no -g or -t or initialization(program)
  585    ->  version                                 % default interactive run
  586    ;   run_init_goals(Goals),                  % run -g goals
  587        (   load_only                           % used -l to load
  588        ->  version
  589        ;   run_program_init,                   % initialization(Goal, program)
  590            run_main_init(false)                % initialization(Goal, main)
  591        )
  592    ).
  593
  594apply_defines :-
  595    '$cmd_option_val'(defines, Defs),
  596    apply_defines(Defs).
  597
  598apply_defines([]).
  599apply_defines([H|T]) :-
  600    apply_define(H),
  601    apply_defines(T).
  602
  603apply_define(Def) :-
  604    sub_atom(Def, B, _, A, '='),
  605    !,
  606    sub_atom(Def, 0, B, _, Flag),
  607    sub_atom(Def, _, A, 0, Value0),
  608    (   '$current_prolog_flag'(Flag, Value0, _Scope, Access, Type)
  609    ->  (   Access \== write
  610        ->  '$permission_error'(set, prolog_flag, Flag)
  611        ;   text_flag_value(Type, Value0, Value)
  612        ),
  613	set_prolog_flag(Flag, Value)
  614    ;   (   atom_number(Value0, Value)
  615	->  true
  616	;   Value = Value0
  617	),
  618	create_prolog_flag(Flag, Value, [warn_not_accessed(true)])
  619    ).
  620apply_define(Def) :-
  621    atom_concat('no-', Flag, Def),
  622    !,
  623    set_user_boolean_flag(Flag, false).
  624apply_define(Def) :-
  625    set_user_boolean_flag(Def, true).
  626
  627set_user_boolean_flag(Flag, Value) :-
  628    current_prolog_flag(Flag, Old),
  629    !,
  630    (   Old == Value
  631    ->  true
  632    ;   set_prolog_flag(Flag, Value)
  633    ).
  634set_user_boolean_flag(Flag, Value) :-
  635    create_prolog_flag(Flag, Value, [warn_not_accessed(true)]).
  636
  637text_flag_value(integer, Text, Int) :-
  638    atom_number(Text, Int),
  639    !.
  640text_flag_value(float, Text, Float) :-
  641    atom_number(Text, Float),
  642    !.
  643text_flag_value(term, Text, Term) :-
  644    term_string(Term, Text, []),
  645    !.
  646text_flag_value(_, Value, Value).
  647
  648:- if(current_prolog_flag(apple,true)).  649apple_set_working_directory :-
  650    (   expand_file_name('~', [Dir]),
  651	exists_directory(Dir)
  652    ->  working_directory(_, Dir)
  653    ;   true
  654    ).
  655
  656apple_set_locale :-
  657    (   getenv('LC_CTYPE', 'UTF-8'),
  658	apple_current_locale_identifier(LocaleID),
  659	atom_concat(LocaleID, '.UTF-8', Locale),
  660	catch(setlocale(ctype, _Old, Locale), _, fail)
  661    ->  setenv('LANG', Locale),
  662        unsetenv('LC_CTYPE')
  663    ;   true
  664    ).
  665
  666apple_setup_app :-
  667    current_prolog_flag(apple, true),
  668    current_prolog_flag(console_menu, true),	% SWI-Prolog.app on MacOS
  669    apple_set_working_directory,
  670    apple_set_locale.
  671:- endif.  672apple_setup_app.
  673
  674init_optimise :-
  675    current_prolog_flag(optimise, true),
  676    !,
  677    use_module(user:library(apply_macros)).
  678init_optimise.
  679
  680opt_attach_packs :-
  681    current_prolog_flag(packs, true),
  682    !,
  683    attach_packs.
  684opt_attach_packs.
  685
  686set_toplevel :-
  687    '$cmd_option_val'(toplevel, TopLevelAtom),
  688    catch(term_to_atom(TopLevel, TopLevelAtom), E,
  689          (print_message(error, E),
  690           halt(1))),
  691    create_prolog_flag(toplevel_goal, TopLevel, [type(term)]).
  692
  693load_only :-
  694    current_prolog_flag(os_argv, OSArgv),
  695    memberchk('-l', OSArgv),
  696    current_prolog_flag(argv, Argv),
  697    \+ memberchk('-l', Argv).
  698
  699%!  run_init_goals(+Goals) is det.
  700%
  701%   Run registered initialization goals  on  order.   If  a  goal fails,
  702%   execution is halted.
  703
  704run_init_goals([]).
  705run_init_goals([H|T]) :-
  706    run_init_goal(H),
  707    run_init_goals(T).
  708
  709run_init_goal(Text) :-
  710    catch(term_to_atom(Goal, Text), E,
  711          (   print_message(error, init_goal_syntax(E, Text)),
  712              halt(2)
  713          )),
  714    run_init_goal(Goal, Text).
  715
  716%!  run_program_init is det.
  717%
  718%   Run goals registered using
  719
  720run_program_init :-
  721    forall('$init_goal'(when(program), Goal, Ctx),
  722           run_init_goal(Goal, @(Goal,Ctx))).
  723
  724run_main_init(_) :-
  725    findall(Goal-Ctx, '$init_goal'(when(main), Goal, Ctx), Pairs),
  726    '$last'(Pairs, Goal-Ctx),
  727    !,
  728    (   current_prolog_flag(toplevel_goal, default)
  729    ->  set_prolog_flag(toplevel_goal, halt)
  730    ;   true
  731    ),
  732    run_init_goal(Goal, @(Goal,Ctx)).
  733run_main_init(true) :-
  734    '$existence_error'(initialization, main).
  735run_main_init(_).
  736
  737run_init_goal(Goal, Ctx) :-
  738    (   catch_with_backtrace(user:Goal, E, true)
  739    ->  (   var(E)
  740        ->  true
  741        ;   print_message(error, init_goal_failed(E, Ctx)),
  742            halt(2)
  743        )
  744    ;   (   current_prolog_flag(verbose, silent)
  745        ->  Level = silent
  746        ;   Level = error
  747        ),
  748        print_message(Level, init_goal_failed(failed, Ctx)),
  749        halt(1)
  750    ).
  751
  752%!  init_debug_flags is det.
  753%
  754%   Initialize the various Prolog flags that   control  the debugger and
  755%   toplevel.
  756
  757init_debug_flags :-
  758    Keep = [keep(true)],
  759    create_prolog_flag(answer_write_options,
  760                       [ quoted(true), portray(true), max_depth(10),
  761                         spacing(next_argument)], Keep),
  762    create_prolog_flag(prompt_alternatives_on, determinism, Keep),
  763    create_prolog_flag(toplevel_extra_white_line, true, Keep),
  764    create_prolog_flag(toplevel_print_factorized, false, Keep),
  765    create_prolog_flag(print_write_options,
  766                       [ portray(true), quoted(true), numbervars(true) ],
  767                       Keep),
  768    create_prolog_flag(toplevel_residue_vars, false, Keep),
  769    create_prolog_flag(toplevel_list_wfs_residual_program, true, Keep),
  770    '$set_debugger_write_options'(print).
  771
  772%!  setup_backtrace
  773%
  774%   Initialise printing a backtrace.
  775
  776setup_backtrace :-
  777    (   \+ current_prolog_flag(backtrace, false),
  778        load_setup_file(library(prolog_stack))
  779    ->  true
  780    ;   true
  781    ).
  782
  783%!  setup_colors is det.
  784%
  785%   Setup  interactive  usage  by  enabling    colored   output.
  786
  787setup_colors :-
  788    (   \+ current_prolog_flag(color_term, false),
  789        stream_property(user_input, tty(true)),
  790        stream_property(user_error, tty(true)),
  791        stream_property(user_output, tty(true)),
  792        \+ getenv('TERM', dumb),
  793        load_setup_file(user:library(ansi_term))
  794    ->  true
  795    ;   true
  796    ).
  797
  798%!  setup_history
  799%
  800%   Enable per-directory persistent history.
  801
  802setup_history :-
  803    (   \+ current_prolog_flag(save_history, false),
  804        stream_property(user_input, tty(true)),
  805        \+ current_prolog_flag(readline, false),
  806        load_setup_file(library(prolog_history))
  807    ->  prolog_history(enable)
  808    ;   true
  809    ),
  810    set_default_history,
  811    '$load_history'.
  812
  813%!  setup_readline
  814%
  815%   Setup line editing.
  816
  817setup_readline :-
  818    (   current_prolog_flag(readline, swipl_win)
  819    ->  true
  820    ;   stream_property(user_input, tty(true)),
  821        current_prolog_flag(tty_control, true),
  822        \+ getenv('TERM', dumb),
  823        (   current_prolog_flag(readline, ReadLine)
  824        ->  true
  825        ;   ReadLine = true
  826        ),
  827        readline_library(ReadLine, Library),
  828        load_setup_file(library(Library))
  829    ->  set_prolog_flag(readline, Library)
  830    ;   set_prolog_flag(readline, false)
  831    ).
  832
  833readline_library(true, Library) :-
  834    !,
  835    preferred_readline(Library).
  836readline_library(false, _) :-
  837    !,
  838    fail.
  839readline_library(Library, Library).
  840
  841preferred_readline(editline).
  842preferred_readline(readline).
  843
  844%!  load_setup_file(+File) is semidet.
  845%
  846%   Load a file and fail silently if the file does not exist.
  847
  848load_setup_file(File) :-
  849    catch(load_files(File,
  850                     [ silent(true),
  851                       if(not_loaded)
  852                     ]), _, fail).
  853
  854
  855:- '$hide'('$toplevel'/0).              % avoid in the GUI stacktrace
  856
  857%!  '$toplevel'
  858%
  859%   Called from PL_toplevel()
  860
  861'$toplevel' :-
  862    '$runtoplevel',
  863    print_message(informational, halt).
  864
  865%!  '$runtoplevel'
  866%
  867%   Actually run the toplevel. The values   `default`  and `prolog` both
  868%   start the interactive toplevel, where `prolog` implies the user gave
  869%   =|-t prolog|=.
  870%
  871%   @see prolog/0 is the default interactive toplevel
  872
  873'$runtoplevel' :-
  874    current_prolog_flag(toplevel_goal, TopLevel0),
  875    toplevel_goal(TopLevel0, TopLevel),
  876    user:TopLevel.
  877
  878:- dynamic  setup_done/0.  879:- volatile setup_done/0.  880
  881toplevel_goal(default, '$query_loop') :-
  882    !,
  883    setup_interactive.
  884toplevel_goal(prolog, '$query_loop') :-
  885    !,
  886    setup_interactive.
  887toplevel_goal(Goal, Goal).
  888
  889setup_interactive :-
  890    setup_done,
  891    !.
  892setup_interactive :-
  893    asserta(setup_done),
  894    catch(setup_backtrace, E, print_message(warning, E)),
  895    catch(setup_readline,  E, print_message(warning, E)),
  896    catch(setup_history,   E, print_message(warning, E)).
  897
  898%!  '$compile'
  899%
  900%   Toplevel called when invoked with -c option.
  901
  902'$compile' :-
  903    (   catch('$compile_', E, (print_message(error, E), halt(1)))
  904    ->  true
  905    ;   print_message(error, error(goal_failed('$compile'), _)),
  906        halt(1)
  907    ),
  908    halt.                               % set exit code
  909
  910'$compile_' :-
  911    '$load_system_init_file',
  912    catch(setup_colors, _, true),
  913    '$set_file_search_paths',
  914    init_debug_flags,
  915    '$run_initialization',
  916    opt_attach_packs,
  917    use_module(library(qsave)),
  918    qsave:qsave_toplevel.
  919
  920%!  '$config'
  921%
  922%   Toplevel when invoked with --dump-runtime-variables
  923
  924'$config' :-
  925    '$load_system_init_file',
  926    '$set_file_search_paths',
  927    init_debug_flags,
  928    '$run_initialization',
  929    load_files(library(prolog_config)),
  930    (   catch(prolog_dump_runtime_variables, E,
  931              (print_message(error, E), halt(1)))
  932    ->  true
  933    ;   print_message(error, error(goal_failed(prolog_dump_runtime_variables),_))
  934    ).
  935
  936
  937                /********************************
  938                *    USER INTERACTIVE LOOP      *
  939                *********************************/
  940
  941%!  prolog:repl_loop_hook(+BeginEnd, +BreakLevel) is nondet.
  942%
  943%   Multifile  hook  that  allows  acting    on   starting/stopping  the
  944%   interactive REPL loop. Called as
  945%
  946%       forall(prolog:repl_loop_hook(BeginEnd, BreakLevel), true)
  947%
  948%   @arg BeginEnd is one of `begin` or `end`
  949%   @arg BreakLevel is 0 for the normal toplevel, -1 when
  950%   non-interactive and >0 for _break environments_.
  951
  952:- multifile
  953    prolog:repl_loop_hook/2.  954
  955%!  prolog
  956%
  957%   Run the Prolog toplevel. This is now  the same as break/0, which
  958%   pretends  to  be  in  a  break-level    if  there  is  a  parent
  959%   environment.
  960
  961prolog :-
  962    break.
  963
  964:- create_prolog_flag(toplevel_mode, backtracking, []).  965
  966%!  '$query_loop'
  967%
  968%   Run the normal Prolog query loop.  Note   that  the query is not
  969%   protected by catch/3. Dealing with  unhandled exceptions is done
  970%   by the C-function query_loop().  This   ensures  that  unhandled
  971%   exceptions are really unhandled (in Prolog).
  972
  973'$query_loop' :-
  974    break_level(BreakLev),
  975    setup_call_cleanup(
  976        notrace(call_repl_loop_hook(begin, BreakLev)),
  977        '$query_loop'(BreakLev),
  978        notrace(call_repl_loop_hook(end, BreakLev))).
  979
  980call_repl_loop_hook(BeginEnd, BreakLev) :-
  981    forall(prolog:repl_loop_hook(BeginEnd, BreakLev), true).
  982
  983
  984'$query_loop'(BreakLev) :-
  985    current_prolog_flag(toplevel_mode, recursive),
  986    !,
  987    read_expanded_query(BreakLev, Query, Bindings),
  988    (   Query == end_of_file
  989    ->  print_message(query, query(eof))
  990    ;   '$call_no_catch'('$execute_query'(Query, Bindings, _)),
  991        (   current_prolog_flag(toplevel_mode, recursive)
  992        ->  '$query_loop'(BreakLev)
  993        ;   '$switch_toplevel_mode'(backtracking),
  994            '$query_loop'(BreakLev)     % Maybe throw('$switch_toplevel_mode')?
  995        )
  996    ).
  997'$query_loop'(BreakLev) :-
  998    repeat,
  999        read_expanded_query(BreakLev, Query, Bindings),
 1000        (   Query == end_of_file
 1001        ->  !, print_message(query, query(eof))
 1002        ;   '$execute_query'(Query, Bindings, _),
 1003            (   current_prolog_flag(toplevel_mode, recursive)
 1004            ->  !,
 1005                '$switch_toplevel_mode'(recursive),
 1006                '$query_loop'(BreakLev)
 1007            ;   fail
 1008            )
 1009        ).
 1010
 1011break_level(BreakLev) :-
 1012    (   current_prolog_flag(break_level, BreakLev)
 1013    ->  true
 1014    ;   BreakLev = -1
 1015    ).
 1016
 1017read_expanded_query(BreakLev, ExpandedQuery, ExpandedBindings) :-
 1018    '$current_typein_module'(TypeIn),
 1019    (   stream_property(user_input, tty(true))
 1020    ->  '$system_prompt'(TypeIn, BreakLev, Prompt),
 1021        prompt(Old, '|    ')
 1022    ;   Prompt = '',
 1023        prompt(Old, '')
 1024    ),
 1025    trim_stacks,
 1026    trim_heap,
 1027    repeat,
 1028      read_query(Prompt, Query, Bindings),
 1029      prompt(_, Old),
 1030      catch(call_expand_query(Query, ExpandedQuery,
 1031                              Bindings, ExpandedBindings),
 1032            Error,
 1033            (print_message(error, Error), fail)),
 1034    !.
 1035
 1036
 1037%!  read_query(+Prompt, -Goal, -Bindings) is det.
 1038%
 1039%   Read the next query. The first  clause   deals  with  the case where
 1040%   !-based history is enabled. The second is   used  if we have command
 1041%   line editing.
 1042
 1043:- if(current_prolog_flag(emscripten, true)). 1044read_query(_Prompt, Goal, Bindings) :-
 1045    '$can_yield',
 1046    !,
 1047    await(query, GoalString),
 1048    term_string(Goal, GoalString, [variable_names(Bindings)]).
 1049:- endif. 1050read_query(Prompt, Goal, Bindings) :-
 1051    current_prolog_flag(history, N),
 1052    integer(N), N > 0,
 1053    !,
 1054    read_term_with_history(
 1055        Goal,
 1056        [ show(h),
 1057          help('!h'),
 1058          no_save([trace, end_of_file]),
 1059          prompt(Prompt),
 1060          variable_names(Bindings)
 1061        ]).
 1062read_query(Prompt, Goal, Bindings) :-
 1063    remove_history_prompt(Prompt, Prompt1),
 1064    repeat,                                 % over syntax errors
 1065    prompt1(Prompt1),
 1066    read_query_line(user_input, Line),
 1067    '$save_history_line'(Line),             % save raw line (edit syntax errors)
 1068    '$current_typein_module'(TypeIn),
 1069    catch(read_term_from_atom(Line, Goal,
 1070                              [ variable_names(Bindings),
 1071                                module(TypeIn)
 1072                              ]), E,
 1073          (   print_message(error, E),
 1074              fail
 1075          )),
 1076    !,
 1077    '$save_history_event'(Line).            % save event (no syntax errors)
 1078
 1079%!  read_query_line(+Input, -Line) is det.
 1080
 1081read_query_line(Input, Line) :-
 1082    stream_property(Input, error(true)),
 1083    !,
 1084    Line = end_of_file.
 1085read_query_line(Input, Line) :-
 1086    catch(read_term_as_atom(Input, Line), Error, true),
 1087    save_debug_after_read,
 1088    (   var(Error)
 1089    ->  true
 1090    ;   catch(print_message(error, Error), _, true),
 1091        (   Error = error(syntax_error(_),_)
 1092        ->  fail
 1093        ;   throw(Error)
 1094        )
 1095    ).
 1096
 1097%!  read_term_as_atom(+Input, -Line)
 1098%
 1099%   Read the next term as an  atom  and   skip  to  the newline or a
 1100%   non-space character.
 1101
 1102read_term_as_atom(In, Line) :-
 1103    '$raw_read'(In, Line),
 1104    (   Line == end_of_file
 1105    ->  true
 1106    ;   skip_to_nl(In)
 1107    ).
 1108
 1109%!  skip_to_nl(+Input) is det.
 1110%
 1111%   Read input after the term. Skips   white  space and %... comment
 1112%   until the end of the line or a non-blank character.
 1113
 1114skip_to_nl(In) :-
 1115    repeat,
 1116    peek_char(In, C),
 1117    (   C == '%'
 1118    ->  skip(In, '\n')
 1119    ;   char_type(C, space)
 1120    ->  get_char(In, _),
 1121        C == '\n'
 1122    ;   true
 1123    ),
 1124    !.
 1125
 1126remove_history_prompt('', '') :- !.
 1127remove_history_prompt(Prompt0, Prompt) :-
 1128    atom_chars(Prompt0, Chars0),
 1129    clean_history_prompt_chars(Chars0, Chars1),
 1130    delete_leading_blanks(Chars1, Chars),
 1131    atom_chars(Prompt, Chars).
 1132
 1133clean_history_prompt_chars([], []).
 1134clean_history_prompt_chars(['~', !|T], T) :- !.
 1135clean_history_prompt_chars([H|T0], [H|T]) :-
 1136    clean_history_prompt_chars(T0, T).
 1137
 1138delete_leading_blanks([' '|T0], T) :-
 1139    !,
 1140    delete_leading_blanks(T0, T).
 1141delete_leading_blanks(L, L).
 1142
 1143
 1144%!  set_default_history
 1145%
 1146%   Enable !-based numbered command history. This  is enabled by default
 1147%   if we are not running under GNU-emacs  and   we  do not have our own
 1148%   line editing.
 1149
 1150set_default_history :-
 1151    current_prolog_flag(history, _),
 1152    !.
 1153set_default_history :-
 1154    (   (   \+ current_prolog_flag(readline, false)
 1155        ;   current_prolog_flag(emacs_inferior_process, true)
 1156        )
 1157    ->  create_prolog_flag(history, 0, [])
 1158    ;   create_prolog_flag(history, 25, [])
 1159    ).
 1160
 1161
 1162                 /*******************************
 1163                 *        TOPLEVEL DEBUG        *
 1164                 *******************************/
 1165
 1166%!  save_debug_after_read
 1167%
 1168%   Called right after the toplevel read to save the debug status if
 1169%   it was modified from the GUI thread using e.g.
 1170%
 1171%     ==
 1172%     thread_signal(main, gdebug)
 1173%     ==
 1174%
 1175%   @bug Ideally, the prompt would change if debug mode is enabled.
 1176%        That is hard to realise with all the different console
 1177%        interfaces supported by SWI-Prolog.
 1178
 1179save_debug_after_read :-
 1180    current_prolog_flag(debug, true),
 1181    !,
 1182    save_debug.
 1183save_debug_after_read.
 1184
 1185save_debug :-
 1186    (   tracing,
 1187        notrace
 1188    ->  Tracing = true
 1189    ;   Tracing = false
 1190    ),
 1191    current_prolog_flag(debug, Debugging),
 1192    set_prolog_flag(debug, false),
 1193    create_prolog_flag(query_debug_settings,
 1194                       debug(Debugging, Tracing), []).
 1195
 1196restore_debug :-
 1197    current_prolog_flag(query_debug_settings, debug(Debugging, Tracing)),
 1198    set_prolog_flag(debug, Debugging),
 1199    (   Tracing == true
 1200    ->  trace
 1201    ;   true
 1202    ).
 1203
 1204:- initialization
 1205    create_prolog_flag(query_debug_settings, debug(false, false), []). 1206
 1207
 1208                /********************************
 1209                *            PROMPTING          *
 1210                ********************************/
 1211
 1212'$system_prompt'(Module, BrekLev, Prompt) :-
 1213    current_prolog_flag(toplevel_prompt, PAtom),
 1214    atom_codes(PAtom, P0),
 1215    (    Module \== user
 1216    ->   '$substitute'('~m', [Module, ': '], P0, P1)
 1217    ;    '$substitute'('~m', [], P0, P1)
 1218    ),
 1219    (    BrekLev > 0
 1220    ->   '$substitute'('~l', ['[', BrekLev, '] '], P1, P2)
 1221    ;    '$substitute'('~l', [], P1, P2)
 1222    ),
 1223    current_prolog_flag(query_debug_settings, debug(Debugging, Tracing)),
 1224    (    Tracing == true
 1225    ->   '$substitute'('~d', ['[trace] '], P2, P3)
 1226    ;    Debugging == true
 1227    ->   '$substitute'('~d', ['[debug] '], P2, P3)
 1228    ;    '$substitute'('~d', [], P2, P3)
 1229    ),
 1230    atom_chars(Prompt, P3).
 1231
 1232'$substitute'(From, T, Old, New) :-
 1233    atom_codes(From, FromCodes),
 1234    phrase(subst_chars(T), T0),
 1235    '$append'(Pre, S0, Old),
 1236    '$append'(FromCodes, Post, S0) ->
 1237    '$append'(Pre, T0, S1),
 1238    '$append'(S1, Post, New),
 1239    !.
 1240'$substitute'(_, _, Old, Old).
 1241
 1242subst_chars([]) -->
 1243    [].
 1244subst_chars([H|T]) -->
 1245    { atomic(H),
 1246      !,
 1247      atom_codes(H, Codes)
 1248    },
 1249    Codes,
 1250    subst_chars(T).
 1251subst_chars([H|T]) -->
 1252    H,
 1253    subst_chars(T).
 1254
 1255
 1256                /********************************
 1257                *           EXECUTION           *
 1258                ********************************/
 1259
 1260%!  '$execute_query'(Goal, Bindings, -Truth) is det.
 1261%
 1262%   Execute Goal using Bindings.
 1263
 1264'$execute_query'(Var, _, true) :-
 1265    var(Var),
 1266    !,
 1267    print_message(informational, var_query(Var)).
 1268'$execute_query'(Goal, Bindings, Truth) :-
 1269    '$current_typein_module'(TypeIn),
 1270    '$dwim_correct_goal'(TypeIn:Goal, Bindings, Corrected),
 1271    !,
 1272    setup_call_cleanup(
 1273        '$set_source_module'(M0, TypeIn),
 1274        expand_goal(Corrected, Expanded),
 1275        '$set_source_module'(M0)),
 1276    print_message(silent, toplevel_goal(Expanded, Bindings)),
 1277    '$execute_goal2'(Expanded, Bindings, Truth).
 1278'$execute_query'(_, _, false) :-
 1279    notrace,
 1280    print_message(query, query(no)).
 1281
 1282'$execute_goal2'(Goal, Bindings, true) :-
 1283    restore_debug,
 1284    '$current_typein_module'(TypeIn),
 1285    residue_vars(TypeIn:Goal, Vars, TypeIn:Delays, Chp),
 1286    deterministic(Det),
 1287    (   save_debug
 1288    ;   restore_debug, fail
 1289    ),
 1290    flush_output(user_output),
 1291    (   Det == true
 1292    ->  DetOrChp = true
 1293    ;   DetOrChp = Chp
 1294    ),
 1295    call_expand_answer(Goal, Bindings, NewBindings),
 1296    (    \+ \+ write_bindings(NewBindings, Vars, Delays, DetOrChp)
 1297    ->   !
 1298    ).
 1299'$execute_goal2'(_, _, false) :-
 1300    save_debug,
 1301    print_message(query, query(no)).
 1302
 1303residue_vars(Goal, Vars, Delays, Chp) :-
 1304    current_prolog_flag(toplevel_residue_vars, true),
 1305    !,
 1306    '$wfs_call'(call_residue_vars(stop_backtrace(Goal, Chp), Vars), Delays).
 1307residue_vars(Goal, [], Delays, Chp) :-
 1308    '$wfs_call'(stop_backtrace(Goal, Chp), Delays).
 1309
 1310stop_backtrace(Goal, Chp) :-
 1311    toplevel_call(Goal),
 1312    prolog_current_choice(Chp).
 1313
 1314toplevel_call(Goal) :-
 1315    call(Goal),
 1316    no_lco.
 1317
 1318no_lco.
 1319
 1320%!  write_bindings(+Bindings, +ResidueVars, +Delays, +DetOrChp)
 1321%!	is semidet.
 1322%
 1323%   Write   bindings   resulting   from   a     query.    The   flag
 1324%   prompt_alternatives_on determines whether the   user is prompted
 1325%   for alternatives. =groundness= gives   the  classical behaviour,
 1326%   =determinism= is considered more adequate and informative.
 1327%
 1328%   Succeeds if the user accepts the answer and fails otherwise.
 1329%
 1330%   @arg ResidueVars are the residual constraints and provided if
 1331%        the prolog flag `toplevel_residue_vars` is set to
 1332%        `project`.
 1333
 1334write_bindings(Bindings, ResidueVars, Delays, DetOrChp) :-
 1335    '$current_typein_module'(TypeIn),
 1336    translate_bindings(Bindings, Bindings1, ResidueVars, TypeIn:Residuals),
 1337    omit_qualifier(Delays, TypeIn, Delays1),
 1338    write_bindings2(Bindings1, Residuals, Delays1, DetOrChp).
 1339
 1340write_bindings2([], Residuals, Delays, _) :-
 1341    current_prolog_flag(prompt_alternatives_on, groundness),
 1342    !,
 1343    name_vars([], t(Residuals, Delays)),
 1344    print_message(query, query(yes(Delays, Residuals))).
 1345write_bindings2(Bindings, Residuals, Delays, true) :-
 1346    current_prolog_flag(prompt_alternatives_on, determinism),
 1347    !,
 1348    name_vars(Bindings, t(Residuals, Delays)),
 1349    print_message(query, query(yes(Bindings, Delays, Residuals))).
 1350write_bindings2(Bindings, Residuals, Delays, Chp) :-
 1351    repeat,
 1352        name_vars(Bindings, t(Residuals, Delays)),
 1353        print_message(query, query(more(Bindings, Delays, Residuals))),
 1354        get_respons(Action, Chp),
 1355    (   Action == redo
 1356    ->  !, fail
 1357    ;   Action == show_again
 1358    ->  fail
 1359    ;   !,
 1360        print_message(query, query(done))
 1361    ).
 1362
 1363%!  name_vars(+Bindings, +Term) is det.
 1364%
 1365%   Give a name ``_[A-Z][0-9]*`` to all variables   in Term, that do not
 1366%   have a name due to Bindings. Singleton   variables in Term are named
 1367%   `_`. The behavior depends on these Prolog flags:
 1368%
 1369%     - toplevel_name_variables
 1370%       Only act when `true`, else name_vars/2 is a no-op.
 1371%     - toplevel_print_anon
 1372%
 1373%   Variables are named by unifying them to `'$VAR'(Name)`
 1374%
 1375%   @arg Bindings is a list Name=Value
 1376
 1377name_vars(Bindings, Term) :-
 1378    current_prolog_flag(toplevel_name_variables, true),
 1379    answer_flags_imply_numbervars,
 1380    !,
 1381    '$term_multitons'(t(Bindings,Term), Vars),
 1382    name_vars_(Vars, Bindings, 0),
 1383    term_variables(t(Bindings,Term), SVars),
 1384    anon_vars(SVars).
 1385name_vars(_Bindings, _Term).
 1386
 1387name_vars_([], _, _).
 1388name_vars_([H|T], Bindings, N) :-
 1389    name_var(Bindings, Name, N, N1),
 1390    H = '$VAR'(Name),
 1391    name_vars_(T, Bindings, N1).
 1392
 1393anon_vars([]).
 1394anon_vars(['$VAR'('_')|T]) :-
 1395    anon_vars(T).
 1396
 1397%!  name_var(+Bindings, -Name, +N0, -N) is det.
 1398%
 1399%   True when Name is a valid name for   a new variable where the search
 1400%   is guided by the number N0. Name may not appear in Bindings.
 1401
 1402name_var(Bindings, Name, N0, N) :-
 1403    between(N0, infinite, N1),
 1404    I is N1//26,
 1405    J is 0'A + N1 mod 26,
 1406    (   I == 0
 1407    ->  format(atom(Name), '_~c', [J])
 1408    ;   format(atom(Name), '_~c~d', [J, I])
 1409    ),
 1410    (   current_prolog_flag(toplevel_print_anon, false)
 1411    ->  true
 1412    ;   \+ is_bound(Bindings, Name)
 1413    ),
 1414    !,
 1415    N is N1+1.
 1416
 1417is_bound([binding(Vars,_Value,_Subst)|T], Name) :-
 1418    (   in_vars(Vars, Name)
 1419    ->  true
 1420    ;   is_bound(T, Name)
 1421    ).
 1422
 1423in_vars(Name, Name) :- !.
 1424in_vars(Names, Name) :-
 1425    '$member'(Name, Names).
 1426
 1427%!  answer_flags_imply_numbervars
 1428%
 1429%   True when the answer will be  written recognising '$VAR'(N). If this
 1430%   is not the case we should not try to name the variables.
 1431
 1432answer_flags_imply_numbervars :-
 1433    current_prolog_flag(answer_write_options, Options),
 1434    numbervars_option(Opt),
 1435    memberchk(Opt, Options),
 1436    !.
 1437
 1438numbervars_option(portray(true)).
 1439numbervars_option(portrayed(true)).
 1440numbervars_option(numbervars(true)).
 1441
 1442%!  residual_goals(:NonTerminal)
 1443%
 1444%   Directive that registers NonTerminal as a collector for residual
 1445%   goals.
 1446
 1447:- multifile
 1448    residual_goal_collector/1. 1449
 1450:- meta_predicate
 1451    residual_goals(2). 1452
 1453residual_goals(NonTerminal) :-
 1454    throw(error(context_error(nodirective, residual_goals(NonTerminal)), _)).
 1455
 1456system:term_expansion((:- residual_goals(NonTerminal)),
 1457                      '$toplevel':residual_goal_collector(M2:Head)) :-
 1458    \+ current_prolog_flag(xref, true),
 1459    prolog_load_context(module, M),
 1460    strip_module(M:NonTerminal, M2, Head),
 1461    '$must_be'(callable, Head).
 1462
 1463%!  prolog:residual_goals// is det.
 1464%
 1465%   DCG that collects residual goals that   are  not associated with
 1466%   the answer through attributed variables.
 1467
 1468:- public prolog:residual_goals//0. 1469
 1470prolog:residual_goals -->
 1471    { findall(NT, residual_goal_collector(NT), NTL) },
 1472    collect_residual_goals(NTL).
 1473
 1474collect_residual_goals([]) --> [].
 1475collect_residual_goals([H|T]) -->
 1476    ( call(H) -> [] ; [] ),
 1477    collect_residual_goals(T).
 1478
 1479
 1480
 1481%!  prolog:translate_bindings(+Bindings0, -Bindings, +ResidueVars,
 1482%!                            +ResidualGoals, -Residuals) is det.
 1483%
 1484%   Translate the raw variable bindings  resulting from successfully
 1485%   completing a query into a  binding   list  and  list of residual
 1486%   goals suitable for human consumption.
 1487%
 1488%   @arg    Bindings is a list of binding(Vars,Value,Substitutions),
 1489%           where Vars is a list of variable names. E.g.
 1490%           binding(['A','B'],42,[])` means that both the variable
 1491%           A and B have the value 42. Values may contain terms
 1492%           '$VAR'(Name) to indicate sharing with a given variable.
 1493%           Value is always an acyclic term. If cycles appear in the
 1494%           answer, Substitutions contains a list of substitutions
 1495%           that restore the original term.
 1496%
 1497%   @arg    Residuals is a pair of two lists representing residual
 1498%           goals. The first element of the pair are residuals
 1499%           related to the query variables and the second are
 1500%           related that are disconnected from the query.
 1501
 1502:- public
 1503    prolog:translate_bindings/5. 1504:- meta_predicate
 1505    prolog:translate_bindings(+, -, +, +, :). 1506
 1507prolog:translate_bindings(Bindings0, Bindings, ResVars, ResGoals, Residuals) :-
 1508    translate_bindings(Bindings0, Bindings, ResVars, ResGoals, Residuals),
 1509    name_vars(Bindings, t(ResVars, ResGoals, Residuals)).
 1510
 1511% should not be required.
 1512prolog:name_vars(Bindings, Term) :- name_vars(Bindings, Term).
 1513
 1514translate_bindings(Bindings0, Bindings, ResidueVars, Residuals) :-
 1515    prolog:residual_goals(ResidueGoals, []),
 1516    translate_bindings(Bindings0, Bindings, ResidueVars, ResidueGoals,
 1517                       Residuals).
 1518
 1519translate_bindings(Bindings0, Bindings, [], [], _:[]-[]) :-
 1520    term_attvars(Bindings0, []),
 1521    !,
 1522    join_same_bindings(Bindings0, Bindings1),
 1523    factorize_bindings(Bindings1, Bindings2),
 1524    bind_vars(Bindings2, Bindings3),
 1525    filter_bindings(Bindings3, Bindings).
 1526translate_bindings(Bindings0, Bindings, ResidueVars, ResGoals0,
 1527                   TypeIn:Residuals-HiddenResiduals) :-
 1528    project_constraints(Bindings0, ResidueVars),
 1529    hidden_residuals(ResidueVars, Bindings0, HiddenResiduals0),
 1530    omit_qualifiers(HiddenResiduals0, TypeIn, HiddenResiduals),
 1531    copy_term(Bindings0+ResGoals0, Bindings1+ResGoals1, Residuals0),
 1532    '$append'(ResGoals1, Residuals0, Residuals1),
 1533    omit_qualifiers(Residuals1, TypeIn, Residuals),
 1534    join_same_bindings(Bindings1, Bindings2),
 1535    factorize_bindings(Bindings2, Bindings3),
 1536    bind_vars(Bindings3, Bindings4),
 1537    filter_bindings(Bindings4, Bindings).
 1538
 1539hidden_residuals(ResidueVars, Bindings, Goal) :-
 1540    term_attvars(ResidueVars, Remaining),
 1541    term_attvars(Bindings, QueryVars),
 1542    subtract_vars(Remaining, QueryVars, HiddenVars),
 1543    copy_term(HiddenVars, _, Goal).
 1544
 1545subtract_vars(All, Subtract, Remaining) :-
 1546    sort(All, AllSorted),
 1547    sort(Subtract, SubtractSorted),
 1548    ord_subtract(AllSorted, SubtractSorted, Remaining).
 1549
 1550ord_subtract([], _Not, []).
 1551ord_subtract([H1|T1], L2, Diff) :-
 1552    diff21(L2, H1, T1, Diff).
 1553
 1554diff21([], H1, T1, [H1|T1]).
 1555diff21([H2|T2], H1, T1, Diff) :-
 1556    compare(Order, H1, H2),
 1557    diff3(Order, H1, T1, H2, T2, Diff).
 1558
 1559diff12([], _H2, _T2, []).
 1560diff12([H1|T1], H2, T2, Diff) :-
 1561    compare(Order, H1, H2),
 1562    diff3(Order, H1, T1, H2, T2, Diff).
 1563
 1564diff3(<,  H1, T1,  H2, T2, [H1|Diff]) :-
 1565    diff12(T1, H2, T2, Diff).
 1566diff3(=, _H1, T1, _H2, T2, Diff) :-
 1567    ord_subtract(T1, T2, Diff).
 1568diff3(>,  H1, T1, _H2, T2, Diff) :-
 1569    diff21(T2, H1, T1, Diff).
 1570
 1571
 1572%!  project_constraints(+Bindings, +ResidueVars) is det.
 1573%
 1574%   Call   <module>:project_attributes/2   if   the    Prolog   flag
 1575%   `toplevel_residue_vars` is set to `project`.
 1576
 1577project_constraints(Bindings, ResidueVars) :-
 1578    !,
 1579    term_attvars(Bindings, AttVars),
 1580    phrase(attribute_modules(AttVars), Modules0),
 1581    sort(Modules0, Modules),
 1582    term_variables(Bindings, QueryVars),
 1583    project_attributes(Modules, QueryVars, ResidueVars).
 1584project_constraints(_, _).
 1585
 1586project_attributes([], _, _).
 1587project_attributes([M|T], QueryVars, ResidueVars) :-
 1588    (   current_predicate(M:project_attributes/2),
 1589        catch(M:project_attributes(QueryVars, ResidueVars), E,
 1590              print_message(error, E))
 1591    ->  true
 1592    ;   true
 1593    ),
 1594    project_attributes(T, QueryVars, ResidueVars).
 1595
 1596attribute_modules([]) --> [].
 1597attribute_modules([H|T]) -->
 1598    { get_attrs(H, Attrs) },
 1599    attrs_modules(Attrs),
 1600    attribute_modules(T).
 1601
 1602attrs_modules([]) --> [].
 1603attrs_modules(att(Module, _, More)) -->
 1604    [Module],
 1605    attrs_modules(More).
 1606
 1607
 1608%!  join_same_bindings(Bindings0, Bindings)
 1609%
 1610%   Join variables that are bound to the   same  value. Note that we
 1611%   return the _last_ value. This is   because the factorization may
 1612%   be different and ultimately the names will   be  printed as V1 =
 1613%   V2, ... VN = Value. Using the  last, Value has the factorization
 1614%   of VN.
 1615
 1616join_same_bindings([], []).
 1617join_same_bindings([Name=V0|T0], [[Name|Names]=V|T]) :-
 1618    take_same_bindings(T0, V0, V, Names, T1),
 1619    join_same_bindings(T1, T).
 1620
 1621take_same_bindings([], Val, Val, [], []).
 1622take_same_bindings([Name=V1|T0], V0, V, [Name|Names], T) :-
 1623    V0 == V1,
 1624    !,
 1625    take_same_bindings(T0, V1, V, Names, T).
 1626take_same_bindings([Pair|T0], V0, V, Names, [Pair|T]) :-
 1627    take_same_bindings(T0, V0, V, Names, T).
 1628
 1629
 1630%!  omit_qualifiers(+QGoals, +TypeIn, -Goals) is det.
 1631%
 1632%   Omit unneeded module qualifiers  from   QGoals  relative  to the
 1633%   given module TypeIn.
 1634
 1635
 1636omit_qualifiers([], _, []).
 1637omit_qualifiers([Goal0|Goals0], TypeIn, [Goal|Goals]) :-
 1638    omit_qualifier(Goal0, TypeIn, Goal),
 1639    omit_qualifiers(Goals0, TypeIn, Goals).
 1640
 1641omit_qualifier(M:G0, TypeIn, G) :-
 1642    M == TypeIn,
 1643    !,
 1644    omit_meta_qualifiers(G0, TypeIn, G).
 1645omit_qualifier(M:G0, TypeIn, G) :-
 1646    predicate_property(TypeIn:G0, imported_from(M)),
 1647    \+ predicate_property(G0, transparent),
 1648    !,
 1649    G0 = G.
 1650omit_qualifier(_:G0, _, G) :-
 1651    predicate_property(G0, built_in),
 1652    \+ predicate_property(G0, transparent),
 1653    !,
 1654    G0 = G.
 1655omit_qualifier(M:G0, _, M:G) :-
 1656    atom(M),
 1657    !,
 1658    omit_meta_qualifiers(G0, M, G).
 1659omit_qualifier(G0, TypeIn, G) :-
 1660    omit_meta_qualifiers(G0, TypeIn, G).
 1661
 1662omit_meta_qualifiers(V, _, V) :-
 1663    var(V),
 1664    !.
 1665omit_meta_qualifiers((QA,QB), TypeIn, (A,B)) :-
 1666    !,
 1667    omit_qualifier(QA, TypeIn, A),
 1668    omit_qualifier(QB, TypeIn, B).
 1669omit_meta_qualifiers(tnot(QA), TypeIn, tnot(A)) :-
 1670    !,
 1671    omit_qualifier(QA, TypeIn, A).
 1672omit_meta_qualifiers(freeze(V, QGoal), TypeIn, freeze(V, Goal)) :-
 1673    callable(QGoal),
 1674    !,
 1675    omit_qualifier(QGoal, TypeIn, Goal).
 1676omit_meta_qualifiers(when(Cond, QGoal), TypeIn, when(Cond, Goal)) :-
 1677    callable(QGoal),
 1678    !,
 1679    omit_qualifier(QGoal, TypeIn, Goal).
 1680omit_meta_qualifiers(G, _, G).
 1681
 1682
 1683%!  bind_vars(+BindingsIn, -Bindings)
 1684%
 1685%   Bind variables to '$VAR'(Name), so they are printed by the names
 1686%   used in the query. Note that by   binding  in the reverse order,
 1687%   variables bound to one another come out in the natural order.
 1688
 1689bind_vars(Bindings0, Bindings) :-
 1690    bind_query_vars(Bindings0, Bindings, SNames),
 1691    bind_skel_vars(Bindings, Bindings, SNames, 1, _).
 1692
 1693bind_query_vars([], [], []).
 1694bind_query_vars([binding(Names,Var,[Var2=Cycle])|T0],
 1695                [binding(Names,Cycle,[])|T], [Name|SNames]) :-
 1696    Var == Var2,                   % also implies var(Var)
 1697    !,
 1698    '$last'(Names, Name),
 1699    Var = '$VAR'(Name),
 1700    bind_query_vars(T0, T, SNames).
 1701bind_query_vars([B|T0], [B|T], AllNames) :-
 1702    B = binding(Names,Var,Skel),
 1703    bind_query_vars(T0, T, SNames),
 1704    (   var(Var), \+ attvar(Var), Skel == []
 1705    ->  AllNames = [Name|SNames],
 1706        '$last'(Names, Name),
 1707        Var = '$VAR'(Name)
 1708    ;   AllNames = SNames
 1709    ).
 1710
 1711
 1712
 1713bind_skel_vars([], _, _, N, N).
 1714bind_skel_vars([binding(_,_,Skel)|T], Bindings, SNames, N0, N) :-
 1715    bind_one_skel_vars(Skel, Bindings, SNames, N0, N1),
 1716    bind_skel_vars(T, Bindings, SNames, N1, N).
 1717
 1718%!  bind_one_skel_vars(+Subst, +Bindings, +VarName, +N0, -N)
 1719%
 1720%   Give names to the factorized variables that   do not have a name
 1721%   yet. This introduces names  _S<N>,   avoiding  duplicates.  If a
 1722%   factorized variable shares with another binding, use the name of
 1723%   that variable.
 1724%
 1725%   @tbd    Consider the call below. We could remove either of the
 1726%           A = x(1).  Which is best?
 1727%
 1728%           ==
 1729%           ?- A = x(1), B = a(A,A).
 1730%           A = x(1),
 1731%           B = a(A, A), % where
 1732%               A = x(1).
 1733%           ==
 1734
 1735bind_one_skel_vars([], _, _, N, N).
 1736bind_one_skel_vars([Var=Value|T], Bindings, Names, N0, N) :-
 1737    (   var(Var)
 1738    ->  (   '$member'(binding(Names, VVal, []), Bindings),
 1739            same_term(Value, VVal)
 1740        ->  '$last'(Names, VName),
 1741            Var = '$VAR'(VName),
 1742            N2 = N0
 1743        ;   between(N0, infinite, N1),
 1744            atom_concat('_S', N1, Name),
 1745            \+ memberchk(Name, Names),
 1746            !,
 1747            Var = '$VAR'(Name),
 1748            N2 is N1 + 1
 1749        )
 1750    ;   N2 = N0
 1751    ),
 1752    bind_one_skel_vars(T, Bindings, Names, N2, N).
 1753
 1754
 1755%!  factorize_bindings(+Bindings0, -Factorized)
 1756%
 1757%   Factorize cycles and sharing in the bindings.
 1758
 1759factorize_bindings([], []).
 1760factorize_bindings([Name=Value|T0], [binding(Name, Skel, Subst)|T]) :-
 1761    '$factorize_term'(Value, Skel, Subst0),
 1762    (   current_prolog_flag(toplevel_print_factorized, true)
 1763    ->  Subst = Subst0
 1764    ;   only_cycles(Subst0, Subst)
 1765    ),
 1766    factorize_bindings(T0, T).
 1767
 1768
 1769only_cycles([], []).
 1770only_cycles([B|T0], List) :-
 1771    (   B = (Var=Value),
 1772        Var = Value,
 1773        acyclic_term(Var)
 1774    ->  only_cycles(T0, List)
 1775    ;   List = [B|T],
 1776        only_cycles(T0, T)
 1777    ).
 1778
 1779
 1780%!  filter_bindings(+Bindings0, -Bindings)
 1781%
 1782%   Remove bindings that must not be printed. There are two of them:
 1783%   Variables whose name start with '_'  and variables that are only
 1784%   bound to themselves (or, unbound).
 1785
 1786filter_bindings([], []).
 1787filter_bindings([H0|T0], T) :-
 1788    hide_vars(H0, H),
 1789    (   (   arg(1, H, [])
 1790        ;   self_bounded(H)
 1791        )
 1792    ->  filter_bindings(T0, T)
 1793    ;   T = [H|T1],
 1794        filter_bindings(T0, T1)
 1795    ).
 1796
 1797hide_vars(binding(Names0, Skel, Subst), binding(Names, Skel, Subst)) :-
 1798    hide_names(Names0, Skel, Subst, Names).
 1799
 1800hide_names([], _, _, []).
 1801hide_names([Name|T0], Skel, Subst, T) :-
 1802    (   sub_atom(Name, 0, _, _, '_'),
 1803        current_prolog_flag(toplevel_print_anon, false),
 1804        sub_atom(Name, 1, 1, _, Next),
 1805        char_type(Next, prolog_var_start)
 1806    ->  true
 1807    ;   Subst == [],
 1808        Skel == '$VAR'(Name)
 1809    ),
 1810    !,
 1811    hide_names(T0, Skel, Subst, T).
 1812hide_names([Name|T0], Skel, Subst, [Name|T]) :-
 1813    hide_names(T0, Skel, Subst, T).
 1814
 1815self_bounded(binding([Name], Value, [])) :-
 1816    Value == '$VAR'(Name).
 1817
 1818%!  get_respons(-Action, +Chp)
 1819%
 1820%   Read the continuation entered by the user.
 1821
 1822:- if(current_prolog_flag(emscripten, true)). 1823get_respons(Action, _Chp) :-
 1824    '$can_yield',
 1825    !,
 1826    await(more, ActionS),
 1827    atom_string(Action, ActionS).
 1828:- endif. 1829get_respons(Action, Chp) :-
 1830    repeat,
 1831        flush_output(user_output),
 1832        get_single_char(Char),
 1833        answer_respons(Char, Chp, Action),
 1834        (   Action == again
 1835        ->  print_message(query, query(action)),
 1836            fail
 1837        ;   !
 1838        ).
 1839
 1840answer_respons(Char, _, again) :-
 1841    '$in_reply'(Char, '?h'),
 1842    !,
 1843    print_message(help, query(help)).
 1844answer_respons(Char, _, redo) :-
 1845    '$in_reply'(Char, ';nrNR \t'),
 1846    !,
 1847    print_message(query, if_tty([ansi(bold, ';', [])])).
 1848answer_respons(Char, _, redo) :-
 1849    '$in_reply'(Char, 'tT'),
 1850    !,
 1851    trace,
 1852    save_debug,
 1853    print_message(query, if_tty([ansi(bold, '; [trace]', [])])).
 1854answer_respons(Char, _, continue) :-
 1855    '$in_reply'(Char, 'ca\n\ryY.'),
 1856    !,
 1857    print_message(query, if_tty([ansi(bold, '.', [])])).
 1858answer_respons(0'b, _, show_again) :-
 1859    !,
 1860    break.
 1861answer_respons(0'*, Chp, show_again) :-
 1862    !,
 1863    print_last_chpoint(Chp).
 1864answer_respons(Char, _, show_again) :-
 1865    current_prolog_flag(answer_write_options, Options0),
 1866    print_predicate(Char, Pred, Options0, Options),
 1867    !,
 1868    print_message(query, if_tty(['~w'-[Pred]])),
 1869    set_prolog_flag(answer_write_options, Options).
 1870answer_respons(-1, _, show_again) :-
 1871    !,
 1872    print_message(query, halt('EOF')),
 1873    halt(0).
 1874answer_respons(Char, _, again) :-
 1875    print_message(query, no_action(Char)).
 1876
 1877%!  print_predicate(+Code, -Change, +Options0, -Options) is semidet.
 1878%
 1879%   Modify  the  `answer_write_options`  value  according  to  the  user
 1880%   command.
 1881
 1882print_predicate(0'w, [write], Options0, Options) :-
 1883    edit_options([-portrayed(true),-portray(true)],
 1884                 Options0, Options).
 1885print_predicate(0'p, [print], Options0, Options) :-
 1886    edit_options([+portrayed(true)],
 1887                 Options0, Options).
 1888print_predicate(0'+, [Change], Options0, Options) :-
 1889    (   '$select'(max_depth(D0), Options0, Options1)
 1890    ->  D is D0*10,
 1891        format(string(Change), 'max_depth(~D)', [D]),
 1892        Options = [max_depth(D)|Options1]
 1893    ;   Options = Options0,
 1894        Change = 'no max_depth'
 1895    ).
 1896print_predicate(0'-, [Change], Options0, Options) :-
 1897    (   '$select'(max_depth(D0), Options0, Options1)
 1898    ->  D is max(1, D0//10),
 1899        Options = [max_depth(D)|Options1]
 1900    ;   D = 10,
 1901        Options = [max_depth(D)|Options0]
 1902    ),
 1903    format(string(Change), 'max_depth(~D)', [D]).
 1904
 1905edit_options([], Options, Options).
 1906edit_options([H|T], Options0, Options) :-
 1907    edit_option(H, Options0, Options1),
 1908    edit_options(T, Options1, Options).
 1909
 1910edit_option(-Term, Options0, Options) =>
 1911    (   '$select'(Term, Options0, Options)
 1912    ->  true
 1913    ;   Options = Options0
 1914    ).
 1915edit_option(+Term, Options0, Options) =>
 1916    functor(Term, Name, 1),
 1917    functor(Var, Name, 1),
 1918    (   '$select'(Var, Options0, Options1)
 1919    ->  Options = [Term|Options1]
 1920    ;   Options = [Term|Options0]
 1921    ).
 1922
 1923%!  print_last_chpoint(+Chp) is det.
 1924%
 1925%   Print the last choicepoint when an answer is nondeterministic.
 1926
 1927print_last_chpoint(Chp) :-
 1928    current_predicate(print_last_choice_point/0),
 1929    !,
 1930    print_last_chpoint_(Chp).
 1931print_last_chpoint(Chp) :-
 1932    use_module(library(prolog_stack), [print_last_choicepoint/2]),
 1933    print_last_chpoint_(Chp).
 1934
 1935print_last_chpoint_(Chp) :-
 1936    print_last_choicepoint(Chp, [message_level(information)]).
 1937
 1938
 1939                 /*******************************
 1940                 *          EXPANSION           *
 1941                 *******************************/
 1942
 1943:- user:dynamic(expand_query/4). 1944:- user:multifile(expand_query/4). 1945
 1946call_expand_query(Goal, Expanded, Bindings, ExpandedBindings) :-
 1947    (   '$replace_toplevel_vars'(Goal, Expanded0, Bindings, ExpandedBindings0)
 1948    ->  true
 1949    ;   Expanded0 = Goal, ExpandedBindings0 = Bindings
 1950    ),
 1951    (   user:expand_query(Expanded0, Expanded, ExpandedBindings0, ExpandedBindings)
 1952    ->  true
 1953    ;   Expanded = Expanded0, ExpandedBindings = ExpandedBindings0
 1954    ).
 1955
 1956
 1957:- dynamic
 1958    user:expand_answer/2,
 1959    prolog:expand_answer/3. 1960:- multifile
 1961    user:expand_answer/2,
 1962    prolog:expand_answer/3. 1963
 1964call_expand_answer(Goal, BindingsIn, BindingsOut) :-
 1965    (   prolog:expand_answer(Goal, BindingsIn, BindingsOut)
 1966    ->  true
 1967    ;   user:expand_answer(BindingsIn, BindingsOut)
 1968    ->  true
 1969    ;   BindingsOut = BindingsIn
 1970    ),
 1971    '$save_toplevel_vars'(BindingsOut),
 1972    !.
 1973call_expand_answer(_, Bindings, Bindings)