View source with raw 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 prolog:version_msg/1.   60:- multifile prolog:version_msg/1.
 version is det
Print the Prolog banner message and messages registered using version/1.
   67version :-
   68    print_message(banner, welcome).
 version(+Message) is det
Add message to version/0
   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                *********************************/
 load_init_file(+ScriptMode) is det
Load the user customization file. This can be done using swipl -f file or simply using swipl. In the first case we search the file both directly and over the alias user_app_config. In the latter case we only use the alias.
   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(_).
 loaded_init_file(?Base, ?AbsFile)
Used by prolog_load_context/2 to confirm we are loading a script.
  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).
 initialization :Goal
Runs Goal after loading the file in which this directive appears as well as after restoring a saved state.
See also
- initialization/2
  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'.
 initialize
Run goals registered with :- initialization(Goal, program).. Stop with an exception if a goal fails or raises an exception.
  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.
 thread_initialization :Goal
Run Goal now and everytime a new thread is created.
  270thread_initialization(Goal) :-
  271    assert('$at_thread_initialization'(Goal)),
  272    call(Goal),
  273    !.
 $thread_init
Called by start_thread() from pl-thread.c before the thread's goal.
  279'$thread_init' :-
  280    set_prolog_flag(toplevel_thread, false),
  281    (   '$at_thread_initialization'(Goal),
  282        (   call(Goal)
  283        ->  fail
  284        ;   fail
  285        )
  286    ;   true
  287    ).
  288
  289
  290                 /*******************************
  291                 *     FILE SEARCH PATH (-p)    *
  292                 *******************************/
 $set_file_search_paths is det
Process -p PathSpec options.
  298'$set_file_search_paths' :-
  299    '$cmd_option_val'(search_paths, Paths),
  300    (   '$member'(Path, Paths),
  301        atom_chars(Path, Chars),
  302        (   phrase('$search_path'(Name, Aliases), Chars)
  303        ->  '$reverse'(Aliases, Aliases1),
  304            forall('$member'(Alias, Aliases1),
  305                   asserta(user:file_search_path(Name, Alias)))
  306        ;   print_message(error, commandline_arg_type(p, Path))
  307        ),
  308        fail ; true
  309    ).
  310
  311'$search_path'(Name, Aliases) -->
  312    '$string'(NameChars),
  313    [=],
  314    !,
  315    {atom_chars(Name, NameChars)},
  316    '$search_aliases'(Aliases).
  317
  318'$search_aliases'([Alias|More]) -->
  319    '$string'(AliasChars),
  320    path_sep,
  321    !,
  322    { '$make_alias'(AliasChars, Alias) },
  323    '$search_aliases'(More).
  324'$search_aliases'([Alias]) -->
  325    '$string'(AliasChars),
  326    '$eos',
  327    !,
  328    { '$make_alias'(AliasChars, Alias) }.
  329
  330path_sep -->
  331    { current_prolog_flag(path_sep, Sep) },
  332    [Sep].
  333
  334'$string'([]) --> [].
  335'$string'([H|T]) --> [H], '$string'(T).
  336
  337'$eos'([], []).
  338
  339'$make_alias'(Chars, Alias) :-
  340    catch(term_to_atom(Alias, Chars), _, fail),
  341    (   atom(Alias)
  342    ;   functor(Alias, F, 1),
  343        F \== /
  344    ),
  345    !.
  346'$make_alias'(Chars, Alias) :-
  347    atom_chars(Alias, Chars).
  348
  349
  350                 /*******************************
  351                 *   LOADING ASSIOCIATED FILES  *
  352                 *******************************/
 argv_prolog_files(-Files, -ScriptMode) is det
Update the Prolog flag argv, extracting the leading script files. This is called after the C based parser removed Prolog options such as -q, -f none, etc. These options are available through '$cmd_option_val'/2.

Our task is to update the Prolog flag argv and return a list of the files to be loaded. The rules are:

Arguments:
ScriptMode- is one of
exe
Program is a saved state
prolog
One or more *.pl files on commandline
script
Single existing file on commandline
app
[path:]cli-name on commandline
none
Normal interactive session
  386argv_prolog_files([], exe) :-
  387    current_prolog_flag(saved_program_class, runtime),
  388    !,
  389    clean_argv.
  390argv_prolog_files(Files, ScriptMode) :-
  391    current_prolog_flag(argv, Argv),
  392    no_option_files(Argv, Argv1, Files, ScriptMode),
  393    (   (   nonvar(ScriptMode)
  394        ;   Argv1 == []
  395        )
  396    ->  (   Argv1 \== Argv
  397        ->  set_prolog_flag(argv, Argv1)
  398        ;   true
  399        )
  400    ;   '$usage',
  401        halt(1)
  402    ).
  403
  404no_option_files([--|Argv], Argv, [], ScriptMode) :-
  405    !,
  406    (   ScriptMode = none
  407    ->  true
  408    ;   true
  409    ).
  410no_option_files([Opt|_], _, _, ScriptMode) :-
  411    var(ScriptMode),
  412    sub_atom(Opt, 0, _, _, '-'),
  413    !,
  414    '$usage',
  415    halt(1).
  416no_option_files([OsFile|Argv0], Argv, [File|T], ScriptMode) :-
  417    file_name_extension(_, Ext, OsFile),
  418    user:prolog_file_type(Ext, prolog),
  419    !,
  420    ScriptMode = prolog,
  421    prolog_to_os_filename(File, OsFile),
  422    no_option_files(Argv0, Argv, T, ScriptMode).
  423no_option_files([OsScript|Argv], Argv, [Script], ScriptMode) :-
  424    var(ScriptMode),
  425    !,
  426    prolog_to_os_filename(PlScript, OsScript),
  427    (   exists_file(PlScript)
  428    ->  Script = PlScript,
  429        ScriptMode = script
  430    ;   cli_script(OsScript, Script)
  431    ->  ScriptMode = app,
  432        set_prolog_flag(app_name, OsScript)
  433    ;   '$existence_error'(file, PlScript)
  434    ).
  435no_option_files(Argv, Argv, [], ScriptMode) :-
  436    (   ScriptMode = none
  437    ->  true
  438    ;   true
  439    ).
  440
  441cli_script(CLI, Script) :-
  442    (   sub_atom(CLI, Pre, _, Post, ':')
  443    ->  sub_atom(CLI, 0, Pre, _, SearchPath),
  444        sub_atom(CLI, _, Post, 0, Base),
  445        Spec =.. [SearchPath, Base]
  446    ;   Spec = app(CLI)
  447    ),
  448    absolute_file_name(Spec, Script,
  449                       [ file_type(prolog),
  450                         access(exist),
  451                         file_errors(fail)
  452                       ]).
  453
  454clean_argv :-
  455    (   current_prolog_flag(argv, [--|Argv])
  456    ->  set_prolog_flag(argv, Argv)
  457    ;   true
  458    ).
 win_associated_files(+Files)
If SWI-Prolog is started as <exe> <file>.<ext>, where <ext> is the extension registered for associated files, set the Prolog flag associated_file, switch to the directory holding the file and -if possible- adjust the window title.
  467win_associated_files(Files) :-
  468    (   Files = [File|_]
  469    ->  absolute_file_name(File, AbsFile),
  470        set_prolog_flag(associated_file, AbsFile),
  471        forall(prolog:set_app_file_config(Files), true)
  472    ;   true
  473    ).
  474
  475:- multifile
  476    prolog:set_app_file_config/1.               % +Files
 start_pldoc
If the option --pldoc[=port] is given, load the PlDoc system.
  482start_pldoc :-
  483    '$cmd_option_val'(pldoc_server, Server),
  484    (   Server == ''
  485    ->  call((doc_server(_), doc_browser))
  486    ;   catch(atom_number(Server, Port), _, fail)
  487    ->  call(doc_server(Port))
  488    ;   print_message(error, option_usage(pldoc)),
  489        halt(1)
  490    ).
  491start_pldoc.
 load_associated_files(+Files)
Load Prolog files specified from the commandline.
  498load_associated_files(Files) :-
  499    load_files(user:Files).
  500
  501hkey('HKEY_CURRENT_USER/Software/SWI/Prolog').
  502hkey('HKEY_LOCAL_MACHINE/Software/SWI/Prolog').
  503
  504'$set_prolog_file_extension' :-
  505    current_prolog_flag(windows, true),
  506    hkey(Key),
  507    catch(win_registry_get_value(Key, fileExtension, Ext0),
  508          _, fail),
  509    !,
  510    (   atom_concat('.', Ext, Ext0)
  511    ->  true
  512    ;   Ext = Ext0
  513    ),
  514    (   user:prolog_file_type(Ext, prolog)
  515    ->  true
  516    ;   asserta(user:prolog_file_type(Ext, prolog))
  517    ).
  518'$set_prolog_file_extension'.
  519
  520
  521                /********************************
  522                *        TOPLEVEL GOALS         *
  523                *********************************/
 $initialise is semidet
Called from PL_initialise() to do the Prolog part of the initialization. If an exception occurs, this is printed and '$initialise' fails.
  531'$initialise' :-
  532    catch(initialise_prolog, E, initialise_error(E)).
  533
  534initialise_error(unwind(abort)) :- !.
  535initialise_error(unwind(halt(_))) :- !.
  536initialise_error(E) :-
  537    print_message(error, initialization_exception(E)),
  538    fail.
  539
  540initialise_prolog :-
  541    '$clean_history',
  542    apply_defines,
  543    init_optimise,
  544    '$run_initialization',
  545    '$load_system_init_file',                   % -F file
  546    set_toplevel,                               % set `toplevel_goal` flag from -t
  547    '$set_file_search_paths',                   % handle -p alias=dir[:dir]*
  548    init_debug_flags,
  549    setup_app,
  550    start_pldoc,                                % handle --pldoc[=port]
  551    main_thread_init.
 main_thread_init
Deal with the Epilog toplevel. If the flag epilog is set and xpce is around, create an epilog window and complete the user part of the initialization in the epilog thread.
  559main_thread_init :-
  560    current_prolog_flag(epilog, true),
  561    thread_self(main),
  562    current_prolog_flag(xpce, true),
  563    exists_source(library(epilog)),
  564    !,
  565    setup_theme,
  566    catch(setup_backtrace, E, print_message(warning, E)),
  567    use_module(library(epilog)),
  568    call(epilog([ init(user_thread_init),
  569                  main(true)
  570                ])).
  571main_thread_init :-
  572    setup_theme,
  573    user_thread_init.
 user_thread_init
Complete the toplevel startup. This may run in a separate thread.
  579user_thread_init :-
  580    opt_attach_packs,
  581    argv_prolog_files(Files, ScriptMode),
  582    load_init_file(ScriptMode),                 % -f file
  583    catch(setup_colors, E, print_message(warning, E)),
  584    '$load_history',
  585    win_associated_files(Files),                % swipl-win: cd and update title
  586    '$load_script_file',                        % -s file (may be repeated)
  587    load_associated_files(Files),
  588    '$cmd_option_val'(goals, Goals),            % -g goal (may be repeated)
  589    (   ScriptMode == app
  590    ->  run_program_init,                       % initialization(Goal, program)
  591        run_main_init(true)
  592    ;   Goals == [],
  593        \+ '$init_goal'(when(_), _, _)          % no -g or -t or initialization(program)
  594    ->  version                                 % default interactive run
  595    ;   run_init_goals(Goals),                  % run -g goals
  596        (   load_only                           % used -l to load
  597        ->  version
  598        ;   run_program_init,                   % initialization(Goal, program)
  599            run_main_init(false)                % initialization(Goal, main)
  600        )
  601    ).
 setup_theme
  605setup_theme :-
  606    current_prolog_flag(theme, Theme),
  607    exists_source(library(theme/Theme)),
  608    !,
  609    use_module(library(theme/Theme)).
  610setup_theme.
 apply_defines
Handle -Dflag[=value] options
  616apply_defines :-
  617    '$cmd_option_val'(defines, Defs),
  618    apply_defines(Defs).
  619
  620apply_defines([]).
  621apply_defines([H|T]) :-
  622    apply_define(H),
  623    apply_defines(T).
  624
  625apply_define(Def) :-
  626    sub_atom(Def, B, _, A, '='),
  627    !,
  628    sub_atom(Def, 0, B, _, Flag),
  629    sub_atom(Def, _, A, 0, Value0),
  630    (   '$current_prolog_flag'(Flag, Value0, _Scope, Access, Type)
  631    ->  (   Access \== write
  632        ->  '$permission_error'(set, prolog_flag, Flag)
  633        ;   text_flag_value(Type, Value0, Value)
  634        ),
  635	set_prolog_flag(Flag, Value)
  636    ;   (   atom_number(Value0, Value)
  637	->  true
  638	;   Value = Value0
  639	),
  640	set_defined(Flag, Value)
  641    ).
  642apply_define(Def) :-
  643    atom_concat('no-', Flag, Def),
  644    !,
  645    set_user_boolean_flag(Flag, false).
  646apply_define(Def) :-
  647    set_user_boolean_flag(Def, true).
  648
  649set_user_boolean_flag(Flag, Value) :-
  650    current_prolog_flag(Flag, Old),
  651    !,
  652    (   Old == Value
  653    ->  true
  654    ;   set_prolog_flag(Flag, Value)
  655    ).
  656set_user_boolean_flag(Flag, Value) :-
  657    set_defined(Flag, Value).
  658
  659text_flag_value(integer, Text, Int) :-
  660    atom_number(Text, Int),
  661    !.
  662text_flag_value(float, Text, Float) :-
  663    atom_number(Text, Float),
  664    !.
  665text_flag_value(term, Text, Term) :-
  666    term_string(Term, Text, []),
  667    !.
  668text_flag_value(_, Value, Value).
  669
  670set_defined(Flag, Value) :-
  671    define_options(Flag, Options), !,
  672    create_prolog_flag(Flag, Value, Options).
 define_options(+Flag, -Options)
Define the options with which to create Flag. This can be used for known flags to control -for example- their type.
  679define_options('SDL_VIDEODRIVER', []).
  680define_options(_, [warn_not_accessed(true)]).
 init_optimise
Load library(apply_macros) if -O is effective.
  686init_optimise :-
  687    current_prolog_flag(optimise, true),
  688    !,
  689    use_module(user:library(apply_macros)).
  690init_optimise.
  691
  692opt_attach_packs :-
  693    current_prolog_flag(packs, true),
  694    !,
  695    attach_packs.
  696opt_attach_packs.
  697
  698set_toplevel :-
  699    '$cmd_option_val'(toplevel, TopLevelAtom),
  700    catch(term_to_atom(TopLevel, TopLevelAtom), E,
  701          (print_message(error, E),
  702           halt(1))),
  703    create_prolog_flag(toplevel_goal, TopLevel, [type(term)]).
  704
  705load_only :-
  706    current_prolog_flag(os_argv, OSArgv),
  707    memberchk('-l', OSArgv),
  708    current_prolog_flag(argv, Argv),
  709    \+ memberchk('-l', Argv).
 run_init_goals(+Goals) is det
Run registered initialization goals on order. If a goal fails, execution is halted.
  716run_init_goals([]).
  717run_init_goals([H|T]) :-
  718    run_init_goal(H),
  719    run_init_goals(T).
  720
  721run_init_goal(Text) :-
  722    catch(term_to_atom(Goal, Text), E,
  723          (   print_message(error, init_goal_syntax(E, Text)),
  724              halt(2)
  725          )),
  726    run_init_goal(Goal, Text).
 run_program_init is det
Run goals registered using
  732run_program_init :-
  733    forall('$init_goal'(when(program), Goal, Ctx),
  734           run_init_goal(Goal, @(Goal,Ctx))).
  735
  736run_main_init(_) :-
  737    findall(Goal-Ctx, '$init_goal'(when(main), Goal, Ctx), Pairs),
  738    '$last'(Pairs, Goal-Ctx),
  739    !,
  740    (   current_prolog_flag(toplevel_goal, default)
  741    ->  set_prolog_flag(toplevel_goal, halt)
  742    ;   true
  743    ),
  744    run_init_goal(Goal, @(Goal,Ctx)).
  745run_main_init(true) :-
  746    '$existence_error'(initialization, main).
  747run_main_init(_).
  748
  749run_init_goal(Goal, Ctx) :-
  750    (   catch_with_backtrace(user:Goal, E, true)
  751    ->  (   var(E)
  752        ->  true
  753        ;   print_message(error, init_goal_failed(E, Ctx)),
  754            halt(2)
  755        )
  756    ;   (   current_prolog_flag(verbose, silent)
  757        ->  Level = silent
  758        ;   Level = error
  759        ),
  760        print_message(Level, init_goal_failed(failed, Ctx)),
  761        halt(1)
  762    ).
 init_debug_flags is det
Initialize the various Prolog flags that control the debugger and toplevel.
  769init_debug_flags :-
  770    Keep = [keep(true)],
  771    create_prolog_flag(answer_write_options,
  772                       [ quoted(true), portray(true), max_depth(10),
  773                         spacing(next_argument)], Keep),
  774    create_prolog_flag(prompt_alternatives_on, determinism, Keep),
  775    create_prolog_flag(toplevel_extra_white_line, true, Keep),
  776    create_prolog_flag(toplevel_print_factorized, false, Keep),
  777    create_prolog_flag(print_write_options,
  778                       [ portray(true), quoted(true), numbervars(true) ],
  779                       Keep),
  780    create_prolog_flag(toplevel_residue_vars, false, Keep),
  781    create_prolog_flag(toplevel_list_wfs_residual_program, true, Keep),
  782    '$set_debugger_write_options'(print).
 setup_backtrace
Initialise printing a backtrace.
  788setup_backtrace :-
  789    (   \+ current_prolog_flag(backtrace, false),
  790        load_setup_file(library(prolog_stack))
  791    ->  true
  792    ;   true
  793    ).
 setup_colors is det
Setup interactive usage by enabling colored output.
  799setup_colors :-
  800    (   \+ current_prolog_flag(color_term, false),
  801        stream_property(user_input, tty(true)),
  802        stream_property(user_error, tty(true)),
  803        stream_property(user_output, tty(true)),
  804        \+ getenv('TERM', dumb),
  805        load_setup_file(user:library(ansi_term))
  806    ->  true
  807    ;   true
  808    ).
 setup_history
Enable per-directory persistent history.
  814setup_history :-
  815    (   \+ current_prolog_flag(save_history, false),
  816        stream_property(user_input, tty(true)),
  817        \+ current_prolog_flag(readline, false),
  818        load_setup_file(library(prolog_history))
  819    ->  prolog_history(enable)
  820    ;   true
  821    ),
  822    set_default_history,
  823    '$load_history'.
 setup_readline
Setup line editing.
  829setup_readline :-
  830    (   current_prolog_flag(readline, swipl_win)
  831    ->  true
  832    ;   stream_property(user_input, tty(true)),
  833        current_prolog_flag(tty_control, true),
  834        \+ getenv('TERM', dumb),
  835        (   current_prolog_flag(readline, ReadLine)
  836        ->  true
  837        ;   ReadLine = true
  838        ),
  839        readline_library(ReadLine, Library),
  840        load_setup_file(library(Library))
  841    ->  set_prolog_flag(readline, Library)
  842    ;   set_prolog_flag(readline, false)
  843    ).
  844
  845readline_library(true, Library) :-
  846    !,
  847    preferred_readline(Library).
  848readline_library(false, _) :-
  849    !,
  850    fail.
  851readline_library(Library, Library).
  852
  853preferred_readline(editline).
  854preferred_readline(readline).
 load_setup_file(+File) is semidet
Load a file and fail silently if the file does not exist.
  860load_setup_file(File) :-
  861    catch(load_files(File,
  862                     [ silent(true),
  863                       if(not_loaded)
  864                     ]), _, fail).
 setup_app is det
When running as an "app", behave as such. The behaviour depends on the platform.
Windows
If Prolog is started using --win_app, try to change directory to <My Documents>\Prolog.
  876:- if(current_prolog_flag(windows,true)).  877
  878setup_app :-
  879    current_prolog_flag(associated_file, _),
  880    !.
  881setup_app :-
  882    '$cmd_option_val'(win_app, true),
  883    !,
  884    catch(my_prolog, E, print_message(warning, E)).
  885setup_app.
  886
  887my_prolog :-
  888    win_folder(personal, MyDocs),
  889    atom_concat(MyDocs, '/Prolog', PrologDir),
  890    (   ensure_dir(PrologDir)
  891    ->  working_directory(_, PrologDir)
  892    ;   working_directory(_, MyDocs)
  893    ).
  894
  895ensure_dir(Dir) :-
  896    exists_directory(Dir),
  897    !.
  898ensure_dir(Dir) :-
  899    catch(make_directory(Dir), E, (print_message(warning, E), fail)).
  900
  901:- elif(current_prolog_flag(apple, true)).  902use_app_settings(true).                        % Indicate we need app settings
  903
  904setup_app :-
  905    apple_set_locale,
  906    current_prolog_flag(associated_file, _),
  907    !.
  908setup_app :-
  909    current_prolog_flag(bundle, true),
  910    current_prolog_flag(executable, Exe),
  911    file_base_name(Exe, 'SWI-Prolog'),
  912    !,
  913    setup_macos_app.
  914setup_app.
  915
  916apple_set_locale :-
  917    (   getenv('LC_CTYPE', 'UTF-8'),
  918        apple_current_locale_identifier(LocaleID),
  919        atom_concat(LocaleID, '.UTF-8', Locale),
  920        catch(setlocale(ctype, _Old, Locale), _, fail)
  921    ->  setenv('LANG', Locale),
  922        unsetenv('LC_CTYPE')
  923    ;   true
  924    ).
  925
  926setup_macos_app :-
  927    restore_working_directory,
  928    !.
  929setup_macos_app :-
  930    expand_file_name('~/Documents/Prolog', [PrologDir]),
  931    (   exists_directory(PrologDir)
  932    ->  true
  933    ;   catch(make_directory(PrologDir), MkDirError,
  934              print_message(warning, MkDirError))
  935    ),
  936    catch(working_directory(_, PrologDir), CdError,
  937          print_message(warning, CdError)),
  938    !.
  939setup_macos_app.
  940
  941:- elif(current_prolog_flag(emscripten, true)).  942setup_app.
  943:- else.  944use_app_settings(true).                        % Indicate we need app settings
  945
  946% Other (Unix-like) platforms.
  947setup_app :-
  948    running_as_app,
  949    restore_working_directory,
  950    !.
  951setup_app.
 running_as_app is semidet
True if we were started from the dock.
  957running_as_app :-
  958%   getenv('FLATPAK_SANDBOX_DIR', _),
  959    current_prolog_flag(epilog, true),
  960    stream_property(In, file_no(0)),
  961    \+ stream_property(In, tty(true)),
  962    !.
  963
  964:- endif.  965
  966
  967:- if((current_predicate(use_app_settings/1),
  968       use_app_settings(true))).  969
  970
  971                /*******************************
  972                *    APP WORKING DIRECTORY     *
  973                *******************************/
  974
  975save_working_directory :-
  976    working_directory(WD, WD),
  977    app_settings(Settings),
  978    (   Settings.get(working_directory) == WD
  979    ->  true
  980    ;   app_save_settings(Settings.put(working_directory, WD))
  981    ).
  982
  983restore_working_directory :-
  984    at_halt(save_working_directory),
  985    app_settings(Settings),
  986    WD = Settings.get(working_directory),
  987    catch(working_directory(_, WD), _, fail),
  988    !.
  989
  990                /*******************************
  991                *           SETTINGS           *
  992                *******************************/
 app_settings(-Settings:dict) is det
Get a dict holding the persistent application settings.
  998app_settings(Settings) :-
  999    app_settings_file(File),
 1000    access_file(File, read),
 1001    catch(setup_call_cleanup(
 1002              open(File, read, In, [encoding(utf8)]),
 1003              read_term(In, Settings, []),
 1004              close(In)),
 1005          Error,
 1006          (print_message(warning, Error), fail)),
 1007    !.
 1008app_settings(#{}).
 app_save_settings(+Settings:dict) is det
Save the given application settings dict.
 1014app_save_settings(Settings) :-
 1015    app_settings_file(File),
 1016    catch(setup_call_cleanup(
 1017              open(File, write, Out, [encoding(utf8)]),
 1018              write_term(Out, Settings,
 1019                         [ quoted(true),
 1020                           module(system), % default operators
 1021                           fullstop(true),
 1022                           nl(true)
 1023                         ]),
 1024              close(Out)),
 1025          Error,
 1026          (print_message(warning, Error), fail)).
 1027
 1028
 1029app_settings_file(File) :-
 1030    absolute_file_name(user_app_config('app_settings.pl'), File,
 1031                       [ access(write),
 1032                         file_errors(fail)
 1033                       ]).
 1034:- endif.% app_settings
 1035
 1036                /*******************************
 1037                *           TOPLEVEL           *
 1038                *******************************/
 1039
 1040:- '$hide'('$toplevel'/0).              % avoid in the GUI stacktrace
 $toplevel
Called from PL_toplevel()
 1046'$toplevel' :-
 1047    '$runtoplevel',
 1048    print_message(informational, halt).
 $runtoplevel
Actually run the toplevel. The values default and prolog both start the interactive toplevel, where prolog implies the user gave -t prolog.
See also
- prolog/0 is the default interactive toplevel
 1058'$runtoplevel' :-
 1059    current_prolog_flag(toplevel_goal, TopLevel0),
 1060    toplevel_goal(TopLevel0, TopLevel),
 1061    user:TopLevel.
 1062
 1063:- dynamic  setup_done/0. 1064:- volatile setup_done/0. 1065
 1066toplevel_goal(default, '$query_loop') :-
 1067    !,
 1068    setup_interactive.
 1069toplevel_goal(prolog, '$query_loop') :-
 1070    !,
 1071    setup_interactive.
 1072toplevel_goal(Goal, Goal).
 1073
 1074setup_interactive :-
 1075    setup_done,
 1076    !.
 1077setup_interactive :-
 1078    asserta(setup_done),
 1079    catch(setup_backtrace, E, print_message(warning, E)),
 1080    catch(setup_readline,  E, print_message(warning, E)),
 1081    catch(setup_history,   E, print_message(warning, E)).
 $compile
Toplevel called when invoked with -c option.
 1087'$compile' :-
 1088    (   catch('$compile_', E, (print_message(error, E), halt(1)))
 1089    ->  true
 1090    ;   print_message(error, error(goal_failed('$compile'), _)),
 1091        halt(1)
 1092    ),
 1093    halt.                               % set exit code
 1094
 1095'$compile_' :-
 1096    '$load_system_init_file',
 1097    catch(setup_colors, _, true),
 1098    '$set_file_search_paths',
 1099    init_debug_flags,
 1100    '$run_initialization',
 1101    opt_attach_packs,
 1102    use_module(library(qsave)),
 1103    qsave:qsave_toplevel.
 $config
Toplevel when invoked with --dump-runtime-variables
 1109'$config' :-
 1110    '$load_system_init_file',
 1111    '$set_file_search_paths',
 1112    init_debug_flags,
 1113    '$run_initialization',
 1114    load_files(library(prolog_config)),
 1115    (   catch(prolog_dump_runtime_variables, E,
 1116              (print_message(error, E), halt(1)))
 1117    ->  true
 1118    ;   print_message(error, error(goal_failed(prolog_dump_runtime_variables),_))
 1119    ).
 1120
 1121
 1122                /********************************
 1123                *    USER INTERACTIVE LOOP      *
 1124                *********************************/
 prolog:repl_loop_hook(+BeginEnd, +BreakLevel) is nondet
Multifile hook that allows acting on starting/stopping the interactive REPL loop. Called as
forall(prolog:repl_loop_hook(BeginEnd, BreakLevel), true)
Arguments:
BeginEnd- is one of begin or end
BreakLevel- is 0 for the normal toplevel, -1 when non-interactive and >0 for break environments.
 1137:- multifile
 1138    prolog:repl_loop_hook/2.
 prolog
Run the Prolog toplevel. This is now the same as break/0, which pretends to be in a break-level if there is a parent environment.
 1146prolog :-
 1147    break.
 1148
 1149:- create_prolog_flag(toplevel_mode, backtracking, []).
 $query_loop
Run the normal Prolog query loop. Note that the query is not protected by catch/3. Dealing with unhandled exceptions is done by the C-function query_loop(). This ensures that unhandled exceptions are really unhandled (in Prolog).
 1158'$query_loop' :-
 1159    break_level(BreakLev),
 1160    setup_call_cleanup(
 1161        notrace(call_repl_loop_hook(begin, BreakLev, IsToplevel)),
 1162        '$query_loop'(BreakLev),
 1163        notrace(call_repl_loop_hook(end, BreakLev, IsToplevel))).
 1164
 1165call_repl_loop_hook(begin, BreakLev, IsToplevel) =>
 1166    (   current_prolog_flag(toplevel_thread, IsToplevel)
 1167    ->  true
 1168    ;   IsToplevel = false
 1169    ),
 1170    set_prolog_flag(toplevel_thread, true),
 1171    call_repl_loop_hook_(begin, BreakLev).
 1172call_repl_loop_hook(end, BreakLev, IsToplevel) =>
 1173    set_prolog_flag(toplevel_thread, IsToplevel),
 1174    call_repl_loop_hook_(end, BreakLev).
 1175
 1176call_repl_loop_hook_(BeginEnd, BreakLev) :-
 1177    forall(prolog:repl_loop_hook(BeginEnd, BreakLev), true).
 1178
 1179
 1180'$query_loop'(BreakLev) :-
 1181    current_prolog_flag(toplevel_mode, recursive),
 1182    !,
 1183    read_expanded_query(BreakLev, Query, Bindings),
 1184    (   Query == end_of_file
 1185    ->  print_message(query, query(eof))
 1186    ;   '$call_no_catch'('$execute_query'(Query, Bindings, _)),
 1187        (   current_prolog_flag(toplevel_mode, recursive)
 1188        ->  '$query_loop'(BreakLev)
 1189        ;   '$switch_toplevel_mode'(backtracking),
 1190            '$query_loop'(BreakLev)     % Maybe throw('$switch_toplevel_mode')?
 1191        )
 1192    ).
 1193'$query_loop'(BreakLev) :-
 1194    repeat,
 1195        read_expanded_query(BreakLev, Query, Bindings),
 1196        (   Query == end_of_file
 1197        ->  !, print_message(query, query(eof))
 1198        ;   '$execute_query'(Query, Bindings, _),
 1199            (   current_prolog_flag(toplevel_mode, recursive)
 1200            ->  !,
 1201                '$switch_toplevel_mode'(recursive),
 1202                '$query_loop'(BreakLev)
 1203            ;   fail
 1204            )
 1205        ).
 1206
 1207break_level(BreakLev) :-
 1208    (   current_prolog_flag(break_level, BreakLev)
 1209    ->  true
 1210    ;   BreakLev = -1
 1211    ).
 1212
 1213read_expanded_query(BreakLev, ExpandedQuery, ExpandedBindings) :-
 1214    '$current_typein_module'(TypeIn),
 1215    (   stream_property(user_input, tty(true))
 1216    ->  '$system_prompt'(TypeIn, BreakLev, Prompt),
 1217        prompt(Old, '|    ')
 1218    ;   Prompt = '',
 1219        prompt(Old, '')
 1220    ),
 1221    trim_stacks,
 1222    trim_heap,
 1223    repeat,
 1224      (   catch(read_query(Prompt, Query, Bindings),
 1225                error(io_error(_,_),_), fail)
 1226      ->  prompt(_, Old),
 1227          catch(call_expand_query(Query, ExpandedQuery,
 1228                                  Bindings, ExpandedBindings),
 1229                Error,
 1230                (print_message(error, Error), fail))
 1231      ;   set_prolog_flag(debug_on_error, false),
 1232          thread_exit(io_error)
 1233      ),
 1234    !.
 read_query(+Prompt, -Goal, -Bindings) is det
Read the next query. The first clause deals with the case where !-based history is enabled. The second is used if we have command line editing.
 1243:- if(current_prolog_flag(emscripten, true)). 1244read_query(_Prompt, Goal, Bindings) :-
 1245    '$can_yield',
 1246    !,
 1247    await(query, GoalString),
 1248    term_string(Goal, GoalString, [variable_names(Bindings)]).
 1249:- endif. 1250read_query(Prompt, Goal, Bindings) :-
 1251    current_prolog_flag(history, N),
 1252    integer(N), N > 0,
 1253    !,
 1254    read_term_with_history(
 1255        Goal,
 1256        [ show(h),
 1257          help('!h'),
 1258          no_save([trace, end_of_file]),
 1259          prompt(Prompt),
 1260          variable_names(Bindings)
 1261        ]).
 1262read_query(Prompt, Goal, Bindings) :-
 1263    remove_history_prompt(Prompt, Prompt1),
 1264    repeat,                                 % over syntax errors
 1265    prompt1(Prompt1),
 1266    read_query_line(user_input, Line),
 1267    '$save_history_line'(Line),             % save raw line (edit syntax errors)
 1268    '$current_typein_module'(TypeIn),
 1269    catch(read_term_from_atom(Line, Goal,
 1270                              [ variable_names(Bindings),
 1271                                module(TypeIn)
 1272                              ]), E,
 1273          (   print_message(error, E),
 1274              fail
 1275          )),
 1276    !,
 1277    '$save_history_event'(Line).            % save event (no syntax errors)
 read_query_line(+Input, -Line) is det
 1281read_query_line(Input, Line) :-
 1282    stream_property(Input, error(true)),
 1283    !,
 1284    Line = end_of_file.
 1285read_query_line(Input, Line) :-
 1286    catch(read_term_as_atom(Input, Line), Error, true),
 1287    save_debug_after_read,
 1288    (   var(Error)
 1289    ->  true
 1290    ;   catch(print_message(error, Error), _, true),
 1291        (   Error = error(syntax_error(_),_)
 1292        ->  fail
 1293        ;   throw(Error)
 1294        )
 1295    ).
 read_term_as_atom(+Input, -Line)
Read the next term as an atom and skip to the newline or a non-space character.
 1302read_term_as_atom(In, Line) :-
 1303    '$raw_read'(In, Line),
 1304    (   Line == end_of_file
 1305    ->  true
 1306    ;   skip_to_nl(In)
 1307    ).
 skip_to_nl(+Input) is det
Read input after the term. Skips white space and %... comment until the end of the line or a non-blank character.
 1314skip_to_nl(In) :-
 1315    repeat,
 1316    peek_char(In, C),
 1317    (   C == '%'
 1318    ->  skip(In, '\n')
 1319    ;   char_type(C, space)
 1320    ->  get_char(In, _),
 1321        C == '\n'
 1322    ;   true
 1323    ),
 1324    !.
 1325
 1326remove_history_prompt('', '') :- !.
 1327remove_history_prompt(Prompt0, Prompt) :-
 1328    atom_chars(Prompt0, Chars0),
 1329    clean_history_prompt_chars(Chars0, Chars1),
 1330    delete_leading_blanks(Chars1, Chars),
 1331    atom_chars(Prompt, Chars).
 1332
 1333clean_history_prompt_chars([], []).
 1334clean_history_prompt_chars(['~', !|T], T) :- !.
 1335clean_history_prompt_chars([H|T0], [H|T]) :-
 1336    clean_history_prompt_chars(T0, T).
 1337
 1338delete_leading_blanks([' '|T0], T) :-
 1339    !,
 1340    delete_leading_blanks(T0, T).
 1341delete_leading_blanks(L, L).
 set_default_history
Enable !-based numbered command history. This is enabled by default if we are not running under GNU-emacs and we do not have our own line editing.
 1350set_default_history :-
 1351    current_prolog_flag(history, _),
 1352    !.
 1353set_default_history :-
 1354    (   (   \+ current_prolog_flag(readline, false)
 1355        ;   current_prolog_flag(emacs_inferior_process, true)
 1356        )
 1357    ->  create_prolog_flag(history, 0, [])
 1358    ;   create_prolog_flag(history, 25, [])
 1359    ).
 1360
 1361
 1362                 /*******************************
 1363                 *        TOPLEVEL DEBUG        *
 1364                 *******************************/
 save_debug_after_read
Called right after the toplevel read to save the debug status if it was modified from the GUI thread using e.g.
thread_signal(main, gdebug)
bug
- Ideally, the prompt would change if debug mode is enabled. That is hard to realise with all the different console interfaces supported by SWI-Prolog.
 1379save_debug_after_read :-
 1380    current_prolog_flag(debug, true),
 1381    !,
 1382    save_debug.
 1383save_debug_after_read.
 1384
 1385save_debug :-
 1386    (   tracing,
 1387        notrace
 1388    ->  Tracing = true
 1389    ;   Tracing = false
 1390    ),
 1391    current_prolog_flag(debug, Debugging),
 1392    set_prolog_flag(debug, false),
 1393    create_prolog_flag(query_debug_settings,
 1394                       debug(Debugging, Tracing), []).
 1395
 1396restore_debug :-
 1397    current_prolog_flag(query_debug_settings, debug(Debugging, Tracing)),
 1398    set_prolog_flag(debug, Debugging),
 1399    (   Tracing == true
 1400    ->  trace
 1401    ;   true
 1402    ).
 1403
 1404:- initialization
 1405    create_prolog_flag(query_debug_settings, debug(false, false), []). 1406
 1407
 1408                /********************************
 1409                *            PROMPTING          *
 1410                ********************************/
 1411
 1412'$system_prompt'(Module, BrekLev, Prompt) :-
 1413    current_prolog_flag(toplevel_prompt, PAtom),
 1414    atom_codes(PAtom, P0),
 1415    (    Module \== user
 1416    ->   '$substitute'('~m', [Module, ': '], P0, P1)
 1417    ;    '$substitute'('~m', [], P0, P1)
 1418    ),
 1419    (    BrekLev > 0
 1420    ->   '$substitute'('~l', ['[', BrekLev, '] '], P1, P2)
 1421    ;    '$substitute'('~l', [], P1, P2)
 1422    ),
 1423    current_prolog_flag(query_debug_settings, debug(Debugging, Tracing)),
 1424    (    Tracing == true
 1425    ->   '$substitute'('~d', ['[trace] '], P2, P3)
 1426    ;    Debugging == true
 1427    ->   '$substitute'('~d', ['[debug] '], P2, P3)
 1428    ;    '$substitute'('~d', [], P2, P3)
 1429    ),
 1430    atom_chars(Prompt, P3).
 1431
 1432'$substitute'(From, T, Old, New) :-
 1433    atom_codes(From, FromCodes),
 1434    phrase(subst_chars(T), T0),
 1435    '$append'(Pre, S0, Old),
 1436    '$append'(FromCodes, Post, S0) ->
 1437    '$append'(Pre, T0, S1),
 1438    '$append'(S1, Post, New),
 1439    !.
 1440'$substitute'(_, _, Old, Old).
 1441
 1442subst_chars([]) -->
 1443    [].
 1444subst_chars([H|T]) -->
 1445    { atomic(H),
 1446      !,
 1447      atom_codes(H, Codes)
 1448    },
 1449    Codes,
 1450    subst_chars(T).
 1451subst_chars([H|T]) -->
 1452    H,
 1453    subst_chars(T).
 1454
 1455
 1456                /********************************
 1457                *           EXECUTION           *
 1458                ********************************/
 $execute_query(Goal, Bindings, -Truth) is det
Execute Goal using Bindings.
 1464'$execute_query'(Var, _, true) :-
 1465    var(Var),
 1466    !,
 1467    print_message(informational, var_query(Var)).
 1468'$execute_query'(Goal, Bindings, Truth) :-
 1469    '$current_typein_module'(TypeIn),
 1470    '$dwim_correct_goal'(TypeIn:Goal, Bindings, Corrected),
 1471    !,
 1472    setup_call_cleanup(
 1473        '$set_source_module'(M0, TypeIn),
 1474        expand_goal(Corrected, Expanded),
 1475        '$set_source_module'(M0)),
 1476    print_message(silent, toplevel_goal(Expanded, Bindings)),
 1477    '$execute_goal2'(Expanded, Bindings, Truth).
 1478'$execute_query'(_, _, false) :-
 1479    notrace,
 1480    print_message(query, query(no)).
 1481
 1482'$execute_goal2'(Goal, Bindings, true) :-
 1483    restore_debug,
 1484    '$current_typein_module'(TypeIn),
 1485    residue_vars(TypeIn:Goal, Vars, TypeIn:Delays, Chp),
 1486    deterministic(Det),
 1487    (   save_debug
 1488    ;   restore_debug, fail
 1489    ),
 1490    flush_output(user_output),
 1491    (   Det == true
 1492    ->  DetOrChp = true
 1493    ;   DetOrChp = Chp
 1494    ),
 1495    call_expand_answer(Goal, Bindings, NewBindings),
 1496    (    \+ \+ write_bindings(NewBindings, Vars, Delays, DetOrChp)
 1497    ->   !
 1498    ).
 1499'$execute_goal2'(_, _, false) :-
 1500    save_debug,
 1501    print_message(query, query(no)).
 1502
 1503residue_vars(Goal, Vars, Delays, Chp) :-
 1504    current_prolog_flag(toplevel_residue_vars, true),
 1505    !,
 1506    '$wfs_call'(call_residue_vars(stop_backtrace(Goal, Chp), Vars), Delays).
 1507residue_vars(Goal, [], Delays, Chp) :-
 1508    '$wfs_call'(stop_backtrace(Goal, Chp), Delays).
 1509
 1510stop_backtrace(Goal, Chp) :-
 1511    toplevel_call(Goal),
 1512    prolog_current_choice(Chp).
 1513
 1514toplevel_call(Goal) :-
 1515    call(Goal),
 1516    no_lco.
 1517
 1518no_lco.
 write_bindings(+Bindings, +ResidueVars, +Delays, +DetOrChp) is semidet
Write bindings resulting from a query. The flag prompt_alternatives_on determines whether the user is prompted for alternatives. groundness gives the classical behaviour, determinism is considered more adequate and informative.

Succeeds if the user accepts the answer and fails otherwise.

Arguments:
ResidueVars- are the residual constraints and provided if the prolog flag toplevel_residue_vars is set to project.
 1534write_bindings(Bindings, ResidueVars, Delays, DetOrChp) :-
 1535    '$current_typein_module'(TypeIn),
 1536    translate_bindings(Bindings, Bindings1, ResidueVars, TypeIn:Residuals),
 1537    omit_qualifier(Delays, TypeIn, Delays1),
 1538    write_bindings2(Bindings, Bindings1, Residuals, Delays1, DetOrChp).
 1539
 1540write_bindings2(OrgBindings, [], Residuals, Delays, _) :-
 1541    current_prolog_flag(prompt_alternatives_on, groundness),
 1542    !,
 1543    name_vars(OrgBindings, [], t(Residuals, Delays)),
 1544    print_message(query, query(yes(Delays, Residuals))).
 1545write_bindings2(OrgBindings, Bindings, Residuals, Delays, true) :-
 1546    current_prolog_flag(prompt_alternatives_on, determinism),
 1547    !,
 1548    name_vars(OrgBindings, Bindings, t(Residuals, Delays)),
 1549    print_message(query, query(yes(Bindings, Delays, Residuals))).
 1550write_bindings2(OrgBindings, Bindings, Residuals, Delays, Chp) :-
 1551    repeat,
 1552        name_vars(OrgBindings, Bindings, t(Residuals, Delays)),
 1553        print_message(query, query(more(Bindings, Delays, Residuals))),
 1554        get_respons(Action, Chp),
 1555    (   Action == redo
 1556    ->  !, fail
 1557    ;   Action == show_again
 1558    ->  fail
 1559    ;   !,
 1560        print_message(query, query(done))
 1561    ).
 name_vars(+OrgBinding, +Bindings, +Term) is det
Give a name _[A-Z][0-9]* to all variables in Term, that do not have a name due to Bindings. Singleton variables in Term are named _. The behavior depends on these Prolog flags:
toplevel_name_variables
Only act when true, else name_vars/3 is a no-op.
toplevel_print_anon

Variables are named by unifying them to '$VAR'(Name)

Arguments:
Bindings- is a list Name=Value
 1577name_vars(OrgBindings, Bindings, Term) :-
 1578    current_prolog_flag(toplevel_name_variables, true),
 1579    answer_flags_imply_numbervars,
 1580    !,
 1581    '$term_multitons'(t(Bindings,Term), Vars),
 1582    bindings_var_names(OrgBindings, Bindings, VarNames),
 1583    name_vars_(Vars, VarNames, 0),
 1584    term_variables(t(Bindings,Term), SVars),
 1585    anon_vars(SVars).
 1586name_vars(_OrgBindings, _Bindings, _Term).
 1587
 1588name_vars_([], _, _).
 1589name_vars_([H|T], Bindings, N) :-
 1590    name_var(Bindings, Name, N, N1),
 1591    H = '$VAR'(Name),
 1592    name_vars_(T, Bindings, N1).
 1593
 1594anon_vars([]).
 1595anon_vars(['$VAR'('_')|T]) :-
 1596    anon_vars(T).
 name_var(+Reserved, -Name, +N0, -N) is det
True when Name is a valid name for a new variable where the search is guided by the number N0. Name may not appear in Reserved.
 1603name_var(Reserved, Name, N0, N) :-
 1604    between(N0, infinite, N1),
 1605    I is N1//26,
 1606    J is 0'A + N1 mod 26,
 1607    (   I == 0
 1608    ->  format(atom(Name), '_~c', [J])
 1609    ;   format(atom(Name), '_~c~d', [J, I])
 1610    ),
 1611    \+ memberchk(Name, Reserved),
 1612    !,
 1613    N is N1+1.
 bindings_var_names(+OrgBindings, +TransBindings, -VarNames) is det
Find the joined set of variable names in the original bindings and translated bindings. When generating new names, we better also omit names that appear in the original bindings (but not in the translated bindigns).
 1622bindings_var_names(OrgBindings, TransBindings, VarNames) :-
 1623    phrase(bindings_var_names_(OrgBindings), VarNames0, Tail),
 1624    phrase(bindings_var_names_(TransBindings), Tail, []),
 1625    sort(VarNames0, VarNames).
 bindings_var_names_(+Bindings)// is det
Produce a list of variable names that appear in Bindings. This deals both with the single and joined representation of bindings.
 1632bindings_var_names_([]) --> [].
 1633bindings_var_names_([H|T]) -->
 1634    binding_var_names(H),
 1635    bindings_var_names_(T).
 1636
 1637binding_var_names(binding(Vars,_Value,_Subst)) ==>
 1638    var_names(Vars).
 1639binding_var_names(Name=_Value) ==>
 1640    [Name].
 1641
 1642var_names([]) --> [].
 1643var_names([H|T]) --> [H], var_names(T).
 answer_flags_imply_numbervars
True when the answer will be written recognising '$VAR'(N). If this is not the case we should not try to name the variables.
 1651answer_flags_imply_numbervars :-
 1652    current_prolog_flag(answer_write_options, Options),
 1653    numbervars_option(Opt),
 1654    memberchk(Opt, Options),
 1655    !.
 1656
 1657numbervars_option(portray(true)).
 1658numbervars_option(portrayed(true)).
 1659numbervars_option(numbervars(true)).
 residual_goals(:NonTerminal)
Directive that registers NonTerminal as a collector for residual goals.
 1666:- multifile
 1667    residual_goal_collector/1. 1668
 1669:- meta_predicate
 1670    residual_goals(2). 1671
 1672residual_goals(NonTerminal) :-
 1673    throw(error(context_error(nodirective, residual_goals(NonTerminal)), _)).
 1674
 1675system:term_expansion((:- residual_goals(NonTerminal)),
 1676                      '$toplevel':residual_goal_collector(M2:Head)) :-
 1677    \+ current_prolog_flag(xref, true),
 1678    prolog_load_context(module, M),
 1679    strip_module(M:NonTerminal, M2, Head),
 1680    '$must_be'(callable, Head).
 prolog:residual_goals// is det
DCG that collects residual goals that are not associated with the answer through attributed variables.
 1687:- public prolog:residual_goals//0. 1688
 1689prolog:residual_goals -->
 1690    { findall(NT, residual_goal_collector(NT), NTL) },
 1691    collect_residual_goals(NTL).
 1692
 1693collect_residual_goals([]) --> [].
 1694collect_residual_goals([H|T]) -->
 1695    ( call(H) -> [] ; [] ),
 1696    collect_residual_goals(T).
 prolog:translate_bindings(+Bindings0, -Bindings, +ResidueVars, +ResidualGoals, -Residuals) is det
Translate the raw variable bindings resulting from successfully completing a query into a binding list and list of residual goals suitable for human consumption.
Arguments:
Bindings- is a list of binding(Vars,Value,Substitutions), where Vars is a list of variable names. E.g. binding(['A','B'],42,[])` means that both the variable A and B have the value 42. Values may contain terms '$VAR'(Name) to indicate sharing with a given variable. Value is always an acyclic term. If cycles appear in the answer, Substitutions contains a list of substitutions that restore the original term.
Residuals- is a pair of two lists representing residual goals. The first element of the pair are residuals related to the query variables and the second are related that are disconnected from the query.
 1721:- public
 1722    prolog:translate_bindings/5. 1723:- meta_predicate
 1724    prolog:translate_bindings(+, -, +, +, :). 1725
 1726prolog:translate_bindings(Bindings0, Bindings, ResVars, ResGoals, Residuals) :-
 1727    translate_bindings(Bindings0, Bindings, ResVars, ResGoals, Residuals),
 1728    name_vars(Bindings0, Bindings, t(ResVars, ResGoals, Residuals)).
 1729
 1730% should not be required.
 1731prolog:name_vars(Bindings, Term) :- name_vars([], Bindings, Term).
 1732prolog:name_vars(Bindings0, Bindings, Term) :- name_vars(Bindings0, Bindings, Term).
 1733
 1734translate_bindings(Bindings0, Bindings, ResidueVars, Residuals) :-
 1735    prolog:residual_goals(ResidueGoals, []),
 1736    translate_bindings(Bindings0, Bindings, ResidueVars, ResidueGoals,
 1737                       Residuals).
 1738
 1739translate_bindings(Bindings0, Bindings, [], [], _:[]-[]) :-
 1740    term_attvars(Bindings0, []),
 1741    !,
 1742    join_same_bindings(Bindings0, Bindings1),
 1743    factorize_bindings(Bindings1, Bindings2),
 1744    bind_vars(Bindings2, Bindings3),
 1745    filter_bindings(Bindings3, Bindings).
 1746translate_bindings(Bindings0, Bindings, ResidueVars, ResGoals0,
 1747                   TypeIn:Residuals-HiddenResiduals) :-
 1748    project_constraints(Bindings0, ResidueVars),
 1749    hidden_residuals(ResidueVars, Bindings0, HiddenResiduals0),
 1750    omit_qualifiers(HiddenResiduals0, TypeIn, HiddenResiduals),
 1751    copy_term(Bindings0+ResGoals0, Bindings1+ResGoals1, Residuals0),
 1752    '$append'(ResGoals1, Residuals0, Residuals1),
 1753    omit_qualifiers(Residuals1, TypeIn, Residuals),
 1754    join_same_bindings(Bindings1, Bindings2),
 1755    factorize_bindings(Bindings2, Bindings3),
 1756    bind_vars(Bindings3, Bindings4),
 1757    filter_bindings(Bindings4, Bindings).
 1758
 1759hidden_residuals(ResidueVars, Bindings, Goal) :-
 1760    term_attvars(ResidueVars, Remaining),
 1761    term_attvars(Bindings, QueryVars),
 1762    subtract_vars(Remaining, QueryVars, HiddenVars),
 1763    copy_term(HiddenVars, _, Goal).
 1764
 1765subtract_vars(All, Subtract, Remaining) :-
 1766    sort(All, AllSorted),
 1767    sort(Subtract, SubtractSorted),
 1768    ord_subtract(AllSorted, SubtractSorted, Remaining).
 1769
 1770ord_subtract([], _Not, []).
 1771ord_subtract([H1|T1], L2, Diff) :-
 1772    diff21(L2, H1, T1, Diff).
 1773
 1774diff21([], H1, T1, [H1|T1]).
 1775diff21([H2|T2], H1, T1, Diff) :-
 1776    compare(Order, H1, H2),
 1777    diff3(Order, H1, T1, H2, T2, Diff).
 1778
 1779diff12([], _H2, _T2, []).
 1780diff12([H1|T1], H2, T2, Diff) :-
 1781    compare(Order, H1, H2),
 1782    diff3(Order, H1, T1, H2, T2, Diff).
 1783
 1784diff3(<,  H1, T1,  H2, T2, [H1|Diff]) :-
 1785    diff12(T1, H2, T2, Diff).
 1786diff3(=, _H1, T1, _H2, T2, Diff) :-
 1787    ord_subtract(T1, T2, Diff).
 1788diff3(>,  H1, T1, _H2, T2, Diff) :-
 1789    diff21(T2, H1, T1, Diff).
 project_constraints(+Bindings, +ResidueVars) is det
Call <module>:project_attributes/2 if the Prolog flag toplevel_residue_vars is set to project.
 1797project_constraints(Bindings, ResidueVars) :-
 1798    !,
 1799    term_attvars(Bindings, AttVars),
 1800    phrase(attribute_modules(AttVars), Modules0),
 1801    sort(Modules0, Modules),
 1802    term_variables(Bindings, QueryVars),
 1803    project_attributes(Modules, QueryVars, ResidueVars).
 1804project_constraints(_, _).
 1805
 1806project_attributes([], _, _).
 1807project_attributes([M|T], QueryVars, ResidueVars) :-
 1808    (   current_predicate(M:project_attributes/2),
 1809        catch(M:project_attributes(QueryVars, ResidueVars), E,
 1810              print_message(error, E))
 1811    ->  true
 1812    ;   true
 1813    ),
 1814    project_attributes(T, QueryVars, ResidueVars).
 1815
 1816attribute_modules([]) --> [].
 1817attribute_modules([H|T]) -->
 1818    { get_attrs(H, Attrs) },
 1819    attrs_modules(Attrs),
 1820    attribute_modules(T).
 1821
 1822attrs_modules([]) --> [].
 1823attrs_modules(att(Module, _, More)) -->
 1824    [Module],
 1825    attrs_modules(More).
 join_same_bindings(Bindings0, Bindings)
Join variables that are bound to the same value. Note that we return the last value. This is because the factorization may be different and ultimately the names will be printed as V1 = V2, ... VN = Value. Using the last, Value has the factorization of VN.
 1836join_same_bindings([], []).
 1837join_same_bindings([Name=V0|T0], [[Name|Names]=V|T]) :-
 1838    take_same_bindings(T0, V0, V, Names, T1),
 1839    join_same_bindings(T1, T).
 1840
 1841take_same_bindings([], Val, Val, [], []).
 1842take_same_bindings([Name=V1|T0], V0, V, [Name|Names], T) :-
 1843    V0 == V1,
 1844    !,
 1845    take_same_bindings(T0, V1, V, Names, T).
 1846take_same_bindings([Pair|T0], V0, V, Names, [Pair|T]) :-
 1847    take_same_bindings(T0, V0, V, Names, T).
 omit_qualifiers(+QGoals, +TypeIn, -Goals) is det
Omit unneeded module qualifiers from QGoals relative to the given module TypeIn.
 1856omit_qualifiers([], _, []).
 1857omit_qualifiers([Goal0|Goals0], TypeIn, [Goal|Goals]) :-
 1858    omit_qualifier(Goal0, TypeIn, Goal),
 1859    omit_qualifiers(Goals0, TypeIn, Goals).
 1860
 1861omit_qualifier(M:G0, TypeIn, G) :-
 1862    M == TypeIn,
 1863    !,
 1864    omit_meta_qualifiers(G0, TypeIn, G).
 1865omit_qualifier(M:G0, TypeIn, G) :-
 1866    predicate_property(TypeIn:G0, imported_from(M)),
 1867    \+ predicate_property(G0, transparent),
 1868    !,
 1869    G0 = G.
 1870omit_qualifier(_:G0, _, G) :-
 1871    predicate_property(G0, built_in),
 1872    \+ predicate_property(G0, transparent),
 1873    !,
 1874    G0 = G.
 1875omit_qualifier(M:G0, _, M:G) :-
 1876    atom(M),
 1877    !,
 1878    omit_meta_qualifiers(G0, M, G).
 1879omit_qualifier(G0, TypeIn, G) :-
 1880    omit_meta_qualifiers(G0, TypeIn, G).
 1881
 1882omit_meta_qualifiers(V, _, V) :-
 1883    var(V),
 1884    !.
 1885omit_meta_qualifiers((QA,QB), TypeIn, (A,B)) :-
 1886    !,
 1887    omit_qualifier(QA, TypeIn, A),
 1888    omit_qualifier(QB, TypeIn, B).
 1889omit_meta_qualifiers(tnot(QA), TypeIn, tnot(A)) :-
 1890    !,
 1891    omit_qualifier(QA, TypeIn, A).
 1892omit_meta_qualifiers(freeze(V, QGoal), TypeIn, freeze(V, Goal)) :-
 1893    callable(QGoal),
 1894    !,
 1895    omit_qualifier(QGoal, TypeIn, Goal).
 1896omit_meta_qualifiers(when(Cond, QGoal), TypeIn, when(Cond, Goal)) :-
 1897    callable(QGoal),
 1898    !,
 1899    omit_qualifier(QGoal, TypeIn, Goal).
 1900omit_meta_qualifiers(G, _, G).
 bind_vars(+BindingsIn, -Bindings)
Bind variables to '$VAR'(Name), so they are printed by the names used in the query. Note that by binding in the reverse order, variables bound to one another come out in the natural order.
 1909bind_vars(Bindings0, Bindings) :-
 1910    bind_query_vars(Bindings0, Bindings, SNames),
 1911    bind_skel_vars(Bindings, Bindings, SNames, 1, _).
 1912
 1913bind_query_vars([], [], []).
 1914bind_query_vars([binding(Names,Var,[Var2=Cycle])|T0],
 1915                [binding(Names,Cycle,[])|T], [Name|SNames]) :-
 1916    Var == Var2,                   % also implies var(Var)
 1917    !,
 1918    '$last'(Names, Name),
 1919    Var = '$VAR'(Name),
 1920    bind_query_vars(T0, T, SNames).
 1921bind_query_vars([B|T0], [B|T], AllNames) :-
 1922    B = binding(Names,Var,Skel),
 1923    bind_query_vars(T0, T, SNames),
 1924    (   var(Var), \+ attvar(Var), Skel == []
 1925    ->  AllNames = [Name|SNames],
 1926        '$last'(Names, Name),
 1927        Var = '$VAR'(Name)
 1928    ;   AllNames = SNames
 1929    ).
 1930
 1931
 1932
 1933bind_skel_vars([], _, _, N, N).
 1934bind_skel_vars([binding(_,_,Skel)|T], Bindings, SNames, N0, N) :-
 1935    bind_one_skel_vars(Skel, Bindings, SNames, N0, N1),
 1936    bind_skel_vars(T, Bindings, SNames, N1, N).
 bind_one_skel_vars(+Subst, +Bindings, +VarName, +N0, -N)
Give names to the factorized variables that do not have a name yet. This introduces names _S<N>, avoiding duplicates. If a factorized variable shares with another binding, use the name of that variable.
To be done
- Consider the call below. We could remove either of the A = x(1). Which is best?
?- A = x(1), B = a(A,A).
A = x(1),
B = a(A, A), % where
    A = x(1).
 1955bind_one_skel_vars([], _, _, N, N).
 1956bind_one_skel_vars([Var=Value|T], Bindings, Names, N0, N) :-
 1957    (   var(Var)
 1958    ->  (   '$member'(binding(Names, VVal, []), Bindings),
 1959            same_term(Value, VVal)
 1960        ->  '$last'(Names, VName),
 1961            Var = '$VAR'(VName),
 1962            N2 = N0
 1963        ;   between(N0, infinite, N1),
 1964            atom_concat('_S', N1, Name),
 1965            \+ memberchk(Name, Names),
 1966            !,
 1967            Var = '$VAR'(Name),
 1968            N2 is N1 + 1
 1969        )
 1970    ;   N2 = N0
 1971    ),
 1972    bind_one_skel_vars(T, Bindings, Names, N2, N).
 factorize_bindings(+Bindings0, -Factorized)
Factorize cycles and sharing in the bindings.
 1979factorize_bindings([], []).
 1980factorize_bindings([Name=Value|T0], [binding(Name, Skel, Subst)|T]) :-
 1981    '$factorize_term'(Value, Skel, Subst0),
 1982    (   current_prolog_flag(toplevel_print_factorized, true)
 1983    ->  Subst = Subst0
 1984    ;   only_cycles(Subst0, Subst)
 1985    ),
 1986    factorize_bindings(T0, T).
 1987
 1988
 1989only_cycles([], []).
 1990only_cycles([B|T0], List) :-
 1991    (   B = (Var=Value),
 1992        Var = Value,
 1993        acyclic_term(Var)
 1994    ->  only_cycles(T0, List)
 1995    ;   List = [B|T],
 1996        only_cycles(T0, T)
 1997    ).
 filter_bindings(+Bindings0, -Bindings)
Remove bindings that must not be printed. There are two of them: Variables whose name start with '_' and variables that are only bound to themselves (or, unbound).
 2006filter_bindings([], []).
 2007filter_bindings([H0|T0], T) :-
 2008    hide_vars(H0, H),
 2009    (   (   arg(1, H, [])
 2010        ;   self_bounded(H)
 2011        )
 2012    ->  filter_bindings(T0, T)
 2013    ;   T = [H|T1],
 2014        filter_bindings(T0, T1)
 2015    ).
 2016
 2017hide_vars(binding(Names0, Skel, Subst), binding(Names, Skel, Subst)) :-
 2018    hide_names(Names0, Skel, Subst, Names).
 2019
 2020hide_names([], _, _, []).
 2021hide_names([Name|T0], Skel, Subst, T) :-
 2022    (   sub_atom(Name, 0, _, _, '_'),
 2023        current_prolog_flag(toplevel_print_anon, false),
 2024        sub_atom(Name, 1, 1, _, Next),
 2025        char_type(Next, prolog_var_start)
 2026    ->  true
 2027    ;   Subst == [],
 2028        Skel == '$VAR'(Name)
 2029    ),
 2030    !,
 2031    hide_names(T0, Skel, Subst, T).
 2032hide_names([Name|T0], Skel, Subst, [Name|T]) :-
 2033    hide_names(T0, Skel, Subst, T).
 2034
 2035self_bounded(binding([Name], Value, [])) :-
 2036    Value == '$VAR'(Name).
 get_respons(-Action, +Chp)
Read the continuation entered by the user.
 2042:- if(current_prolog_flag(emscripten, true)). 2043get_respons(Action, Chp) :-
 2044    '$can_yield',
 2045    !,
 2046    repeat,
 2047        await(more, CommandS),
 2048        atom_string(Command, CommandS),
 2049        more_action(Command, Chp, Action),
 2050        (   Action == again
 2051        ->  print_message(query, query(action)),
 2052            fail
 2053        ;   !
 2054        ).
 2055:- endif. 2056get_respons(Action, Chp) :-
 2057    repeat,
 2058        flush_output(user_output),
 2059        get_single_char(Code),
 2060        find_more_command(Code, Command, Feedback, Style),
 2061        (   Style \== '-'
 2062        ->  print_message(query, if_tty([ansi(Style, '~w', [Feedback])]))
 2063        ;   true
 2064        ),
 2065        more_action(Command, Chp, Action),
 2066        (   Action == again
 2067        ->  print_message(query, query(action)),
 2068            fail
 2069        ;   !
 2070        ).
 2071
 2072find_more_command(-1, end_of_file, 'EOF', warning) :-
 2073    !.
 2074find_more_command(Code, Command, Feedback, Style) :-
 2075    more_command(Command, Atom, Feedback, Style),
 2076    '$in_reply'(Code, Atom),
 2077    !.
 2078find_more_command(Code, again, '', -) :-
 2079    print_message(query, no_action(Code)).
 2080
 2081more_command(help,        '?h',        '',          -).
 2082more_command(redo,        ';nrNR \t',  ';',         bold).
 2083more_command(trace,       'tT',        '; [trace]', comment).
 2084more_command(continue,    'ca\n\ryY.', '.',         bold).
 2085more_command(break,       'b',         '',          -).
 2086more_command(choicepoint, '*',         '',          -).
 2087more_command(write,       'w',         '[write]',   comment).
 2088more_command(print,       'p',         '[print]',   comment).
 2089more_command(depth_inc,   '+',         Change,      comment) :-
 2090    (   print_depth(Depth0)
 2091    ->  depth_step(Step),
 2092        NewDepth is Depth0*Step,
 2093        format(atom(Change), '[max_depth(~D)]', [NewDepth])
 2094    ;   Change = 'no max_depth'
 2095    ).
 2096more_command(depth_dec,   '-',         Change,      comment) :-
 2097    (   print_depth(Depth0)
 2098    ->  depth_step(Step),
 2099        NewDepth is max(1, Depth0//Step),
 2100        format(atom(Change), '[max_depth(~D)]', [NewDepth])
 2101    ;   Change = '[max_depth(10)]'
 2102    ).
 2103
 2104more_action(help, _, Action) =>
 2105    Action = again,
 2106    print_message(help, query(help)).
 2107more_action(redo, _, Action) =>			% Next
 2108    Action = redo.
 2109more_action(trace, _, Action) =>
 2110    Action = redo,
 2111    trace,
 2112    save_debug.
 2113more_action(continue, _, Action) =>             % Stop
 2114    Action = continue.
 2115more_action(break, _, Action) =>
 2116    Action = show_again,
 2117    break.
 2118more_action(choicepoint, Chp, Action) =>
 2119    Action = show_again,
 2120    print_last_chpoint(Chp).
 2121more_action(end_of_file, _, Action) =>
 2122    Action = show_again,
 2123    halt(0).
 2124more_action(again, _, Action) =>
 2125    Action = again.
 2126more_action(Command, _, Action),
 2127    current_prolog_flag(answer_write_options, Options0),
 2128    print_predicate(Command, Options0, Options) =>
 2129    Action = show_again,
 2130    set_prolog_flag(answer_write_options, Options).
 2131
 2132print_depth(Depth) :-
 2133    current_prolog_flag(answer_write_options, Options),
 2134    memberchk(max_depth(Depth), Options),
 2135    !.
 print_predicate(+Action, +Options0, -Options) is semidet
Modify the answer_write_options value according to the user command.
 2142print_predicate(write, Options0, Options) :-
 2143    edit_options([-portrayed(true),-portray(true)],
 2144                 Options0, Options).
 2145print_predicate(print, Options0, Options) :-
 2146    edit_options([+portrayed(true)],
 2147                 Options0, Options).
 2148print_predicate(depth_inc, Options0, Options) :-
 2149    (   '$select'(max_depth(D0), Options0, Options1)
 2150    ->  depth_step(Step),
 2151        D is D0*Step,
 2152        Options = [max_depth(D)|Options1]
 2153    ;   Options = Options0
 2154    ).
 2155print_predicate(depth_dec, Options0, Options) :-
 2156    (   '$select'(max_depth(D0), Options0, Options1)
 2157    ->  depth_step(Step),
 2158        D is max(1, D0//Step),
 2159        Options = [max_depth(D)|Options1]
 2160    ;   D = 10,
 2161        Options = [max_depth(D)|Options0]
 2162    ).
 2163
 2164depth_step(5).
 2165
 2166edit_options([], Options, Options).
 2167edit_options([H|T], Options0, Options) :-
 2168    edit_option(H, Options0, Options1),
 2169    edit_options(T, Options1, Options).
 2170
 2171edit_option(-Term, Options0, Options) =>
 2172    (   '$select'(Term, Options0, Options)
 2173    ->  true
 2174    ;   Options = Options0
 2175    ).
 2176edit_option(+Term, Options0, Options) =>
 2177    functor(Term, Name, 1),
 2178    functor(Var, Name, 1),
 2179    (   '$select'(Var, Options0, Options1)
 2180    ->  Options = [Term|Options1]
 2181    ;   Options = [Term|Options0]
 2182    ).
 print_last_chpoint(+Chp) is det
Print the last choicepoint when an answer is nondeterministic.
 2188print_last_chpoint(Chp) :-
 2189    current_predicate(print_last_choice_point/0),
 2190    !,
 2191    print_last_chpoint_(Chp).
 2192print_last_chpoint(Chp) :-
 2193    use_module(library(prolog_stack), [print_last_choicepoint/2]),
 2194    print_last_chpoint_(Chp).
 2195
 2196print_last_chpoint_(Chp) :-
 2197    print_last_choicepoint(Chp, [message_level(information)]).
 2198
 2199
 2200                 /*******************************
 2201                 *          EXPANSION           *
 2202                 *******************************/
 2203
 2204:- user:dynamic(expand_query/4). 2205:- user:multifile(expand_query/4). 2206
 2207call_expand_query(Goal, Expanded, Bindings, ExpandedBindings) :-
 2208    (   '$replace_toplevel_vars'(Goal, Expanded0, Bindings, ExpandedBindings0)
 2209    ->  true
 2210    ;   Expanded0 = Goal, ExpandedBindings0 = Bindings
 2211    ),
 2212    (   user:expand_query(Expanded0, Expanded, ExpandedBindings0, ExpandedBindings)
 2213    ->  true
 2214    ;   Expanded = Expanded0, ExpandedBindings = ExpandedBindings0
 2215    ).
 2216
 2217
 2218:- dynamic
 2219    user:expand_answer/2,
 2220    prolog:expand_answer/3. 2221:- multifile
 2222    user:expand_answer/2,
 2223    prolog:expand_answer/3. 2224
 2225call_expand_answer(Goal, BindingsIn, BindingsOut) :-
 2226    (   prolog:expand_answer(Goal, BindingsIn, BindingsOut)
 2227    ->  true
 2228    ;   user:expand_answer(BindingsIn, BindingsOut)
 2229    ->  true
 2230    ;   BindingsOut = BindingsIn
 2231    ),
 2232    '$save_toplevel_vars'(BindingsOut),
 2233    !.
 2234call_expand_answer(_, Bindings, Bindings)