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-2017, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(backward_compatibility,
   37          [ '$arch'/2,
   38            '$version'/1,
   39            '$home'/1,
   40            '$argv'/1,
   41            '$set_prompt'/1,
   42            '$strip_module'/3,
   43            '$declare_module'/3,
   44            '$module'/2,
   45            at_initialization/1,        % :Goal
   46            displayq/1,
   47            displayq/2,
   48            sformat/2,                  % -String, +Fmt
   49            sformat/3,                  % -String, +Fmt, +Args
   50            concat/3,
   51            concat_atom/2,              % +List, -Atom
   52            concat_atom/3,              % +List, +Sep, -Atom
   53            '$apropos_match'/2,         % +Needle, +Hashstack
   54            read_clause/1,              % -Term
   55            read_clause/2,              % +Stream, -Term
   56            read_variables/2,           % -Term, -VariableNames
   57            read_variables/3,           % +Stream, -Term, -VariableNames
   58            read_pending_input/3,       % +Stream, -List, ?Tail
   59            feature/2,
   60            set_feature/2,
   61            substring/4,
   62            string_to_list/2,           % ?String, ?Codes
   63            string_to_atom/2,           % ?String, ?Atom
   64            flush/0,
   65            write_ln/1,                 % +Term
   66            proper_list/1,              % @Term
   67            free_variables/2,           % +Term, -Variables
   68            hash_term/2,                % +Term, -Hash
   69            checklist/2,                % :Goal, +List
   70            sublist/3,                  % :Goal, +List, -Sublist
   71            sumlist/2,                  % +List, -Sum
   72            convert_time/2,             % +Stamp, -String
   73            convert_time/8,             % +String, -YMDmhs.ms
   74            'C'/3,                      % +List, -Head, -Tail
   75            current_thread/2,           % ?Thread, ?Status
   76            current_mutex/3,            % ?Mutex, ?Owner, ?Count
   77            message_queue_size/2,       % +Queue, -TermsWaiting
   78            lock_predicate/2,           % +Name, +Arity
   79            unlock_predicate/2,         % +Name, +Arity
   80            current_module/2,           % ?Module, ?File
   81            export_list/2,              % +Module, -Exports
   82            setup_and_call_cleanup/3,   % :Setup, :Goal, :Cleanup
   83            setup_and_call_cleanup/4,   % :Setup, :Goal, ?Catcher, :Cleanup
   84            merge/3,                    % +List1, +List2, -Union
   85            merge_set/3,                % +Set1, +Set2, -Union
   86            (index)/1,                  % :Head
   87            hash/1,                     % :PI
   88            set_base_module/1,          % :Base
   89            eval_license/0,
   90            trie_insert_new/3,		% +Trie, +Term, -Node
   91            thread_at_exit/1,           % :Goal
   92            read_history/6              % +Show, +Help, +Special, +Prompt,
   93                                        % -Term, -Bindings
   94          ]).   95:- autoload(library(apply),[maplist/3,maplist/2]).   96:- autoload(library(lists),[sum_list/2]).   97:- autoload(library(system),[lock_predicate/1,unlock_predicate/1]).   98
   99
  100:- meta_predicate
  101    at_initialization(0),
  102    setup_and_call_cleanup(0,0,0),
  103    setup_and_call_cleanup(0,0,?,0),
  104    checklist(1, +),
  105    sublist(1, +, ?),
  106    index(:),
  107    hash(:),
  108    set_base_module(:),
  109    thread_at_exit(0).  110
  111/** <module> Backward compatibility
  112
  113This library defines predicates that used to exist in older version of
  114SWI-Prolog, but are considered obsolete as there functionality is neatly
  115covered by new features. Most often, these constructs are superseded by
  116ISO-standard compliant predicates.
  117
  118Please also note the existence of   quintus.pl and edinburgh.pl for more
  119compatibility predicates.
  120
  121@see    gxref/0 can be used to find files that import from
  122        library(backcomp) and thus reply on deprecated features.
  123*/
  124
  125%!  '$arch'(-Architecture, -Version) is det.
  126%
  127%   @deprecated use current_prolog_flag(arch, Architecture)
  128
  129'$arch'(Arch, unknown) :-
  130    current_prolog_flag(arch, Arch).
  131
  132%!  '$version'(Version:integer) is det.
  133%
  134%   @deprecated use current_prolog_flag(version, Version)
  135
  136'$version'(Version) :-
  137    current_prolog_flag(version, Version).
  138
  139%!  '$home'(-SWIPrologDir) is det.
  140%
  141%   @deprecated use current_prolog_flag(home, SWIPrologDir)
  142%   @see file_search_path/2, absolute_file_name/3,  The Prolog home
  143%        directory is available through the alias =swi=.
  144
  145'$home'(Home) :-
  146    current_prolog_flag(home, Home).
  147
  148%!  '$argv'(-Argv:list) is det.
  149%
  150%   @deprecated use current_prolog_flag(os_argv, Argv) or
  151%   current_prolog_flag(argv, Argv)
  152
  153'$argv'(Argv) :-
  154    current_prolog_flag(os_argv, Argv).
  155
  156%!  '$set_prompt'(+Prompt) is det.
  157%
  158%   Set the prompt for the toplevel
  159%
  160%   @deprecated use set_prolog_flag(toplevel_prompt, Prompt).
  161
  162'$set_prompt'(Prompt) :-
  163    (   is_list(Prompt)
  164    ->  Prompt0 = Prompt
  165    ;   atom_codes(Prompt, Prompt0)
  166    ),
  167    maplist(percent_to_tilde, Prompt0, Prompt1),
  168    atom_codes(Atom, Prompt1),
  169    set_prolog_flag(toplevel_prompt, Atom).
  170
  171percent_to_tilde(0'%, 0'~) :- !.
  172percent_to_tilde(X, X).
  173
  174
  175%!  displayq(@Term) is det.
  176%!  displayq(+Stream, @Term) is det.
  177%
  178%   Write term ignoring operators and quote atoms.
  179%
  180%   @deprecated Use write_term/3 or write_canonical/2.
  181
  182displayq(Term) :-
  183    write_term(Term, [ignore_ops(true),quoted(true)]).
  184displayq(Stream, Term) :-
  185    write_term(Stream, Term, [ignore_ops(true),quoted(true)]).
  186
  187
  188%!  sformat(-String, +Format, +Args) is det.
  189%!  sformat(-String, +Format) is det.
  190%
  191%   @deprecated Use format/3 as =|format(string(String), ...)|=
  192
  193:- module_transparent sformat/2, sformat/3.  194
  195sformat(String, Format) :-
  196    format(string(String), Format, []).
  197sformat(String, Format, Arguments) :-
  198    format(string(String), Format, Arguments).
  199
  200%!  concat(+Atom1, +Atom2, -Atom) is det.
  201%
  202%   @deprecated Use ISO atom_concat/3
  203
  204concat(A, B, C) :-
  205    atom_concat(A, B, C).
  206
  207%!  concat_atom(+List, -Atom) is det.
  208%
  209%   Concatenate a list of atomic values to an atom.
  210%
  211%   @deprecated Use atomic_list_concat/2 as proposed by the prolog
  212%               commons initiative.
  213
  214concat_atom([A, B], C) :-
  215    !,
  216    atom_concat(A, B, C).
  217concat_atom(L, Atom) :-
  218    atomic_list_concat(L, Atom).
  219
  220
  221%!  concat_atom(+List, +Separator, -Atom) is det.
  222%
  223%   Concatenate a list of atomic values to an atom, inserting Separator
  224%   between each consecutive elements.
  225%
  226%   @deprecated Use atomic_list_concat/3 as proposed by the prolog
  227%               commons initiative.
  228
  229concat_atom(L, Sep, Atom) :-
  230    atomic_list_concat(L, Sep, Atom).
  231
  232%!  '$apropos_match'(+Needle, +Haystack) is semidet.
  233%
  234%   True if Needle is a sub atom of Haystack.  Ignores the case
  235%   of Haystack.
  236
  237'$apropos_match'(Needle, Haystack) :-
  238    sub_atom_icasechk(Haystack, _, Needle).
  239
  240%!  read_clause(-Term) is det.
  241%
  242%   @deprecated Use read_clause/3 or read_term/3.
  243
  244read_clause(Term) :-
  245    read_clause(current_input, Term).
  246
  247%!  read_clause(+Stream, -Term) is det.
  248%
  249%   @deprecated Use read_clause/3 or read_term/3.
  250
  251read_clause(Stream, Term) :-
  252    read_clause(Stream, Term, [process_comment(false)]).
  253
  254%!  read_variables(-Term, -Bindings) is det.
  255%!  read_variables(+In:stream, -Term, -Bindings) is det.
  256%
  257%   @deprecated Use ISO read_term/2 or read_term/3.
  258
  259read_variables(Term, Vars) :-
  260    read_term(Term, [variable_names(Vars)]).
  261
  262read_variables(Stream, Term, Vars) :-
  263    read_term(Stream, Term, [variable_names(Vars)]).
  264
  265%!  read_pending_input(+Stream, -Codes, ?Tail) is det.
  266%
  267%   @deprecated Use read_pending_codes/3.
  268
  269read_pending_input(Stream, Codes, Tail) :-
  270    read_pending_codes(Stream, Codes, Tail).
  271
  272%!  feature(?Key, ?Value) is nondet.
  273%!  set_feature(+Key, @Term) is det.
  274%
  275%   Control Prolog flags.
  276%
  277%   @deprecated Use ISO current_prolog_flag/2 and set_prolog_flag/2.
  278
  279feature(Key, Value) :-
  280    current_prolog_flag(Key, Value).
  281
  282set_feature(Key, Value) :-
  283    set_prolog_flag(Key, Value).
  284
  285%!  substring(+String, +Offset, +Length, -Sub)
  286%
  287%   Predecessor of sub_string using 1-based Offset.
  288%
  289%   @deprecated Use sub_string/5.
  290
  291substring(String, Offset, Length, Sub) :-
  292    Offset0 is Offset - 1,
  293    sub_string(String, Offset0, Length, _After, Sub).
  294
  295%!  string_to_list(?String, ?Codes) is det.
  296%
  297%   Bi-directional conversion between a string and a list of
  298%   character codes.
  299%
  300%   @deprecated Use string_codes/2.
  301
  302string_to_list(String, Codes) :-
  303    string_codes(String, Codes).
  304
  305%!  string_to_atom(?String, ?Atom) is det.
  306%
  307%   Bi-directional conversion between string and atom.
  308%
  309%   @deprecated     Use atom_string/2. Note that the order of the
  310%                   arguments is reversed.
  311
  312string_to_atom(Atom, String) :-
  313    atom_string(String, Atom).
  314
  315%!  flush is det.
  316%
  317%   @deprecated use ISO flush_output/0.
  318
  319flush :-
  320    flush_output.
  321
  322%!  write_ln(X) is det
  323%
  324%   @deprecated Use writeln(X).
  325
  326write_ln(X) :-
  327    writeln(X).
  328
  329%!  proper_list(+List)
  330%
  331%   Old SWI-Prolog predicate to check for a list that really ends
  332%   in a [].  There is not much use for the quick is_list, as in
  333%   most cases you want to process the list element-by-element anyway.
  334%
  335%   @deprecated Use ISO is_list/1.
  336
  337proper_list(List) :-
  338    is_list(List).
  339
  340%!  free_variables(+Term, -Variables)
  341%
  342%   Return  a  list  of  unbound  variables    in   Term.  The  name
  343%   term_variables/2 is more widely used.
  344%
  345%   @deprecated Use term_variables/2.
  346
  347free_variables(Term, Variables) :-
  348    term_variables(Term, Variables).
  349
  350%!  hash_term(+Term, -Hash) is det.
  351%
  352%   If Term is ground, Hash is unified to an integer representing
  353%   a hash for Term.  Otherwise Hash is left unbound.
  354%
  355%   @deprecated Use term_hash/2.
  356
  357hash_term(Term, Hash) :-
  358    term_hash(Term, Hash).
  359
  360%!  checklist(:Goal, +List)
  361%
  362%   @deprecated Use maplist/2
  363
  364
  365checklist(Goal, List) :-
  366    maplist(Goal, List).
  367
  368%!  sublist(:Goal, +List1, ?List2)
  369%
  370%   Succeeds if List2 unifies with a list holding those terms for which
  371%   call(Goal, Elem) succeeds.
  372%
  373%   @deprecated Use include/3 from library(apply)
  374%   @compat DEC10 library
  375
  376sublist(_, [], []) :- !.
  377sublist(Goal, [H|T], Sub) :-
  378    call(Goal, H),
  379    !,
  380    Sub = [H|R],
  381    sublist(Goal, T, R).
  382sublist(Goal, [_|T], R) :-
  383    sublist(Goal, T, R).
  384
  385%!  sumlist(+List, -Sum) is det.
  386%
  387%   True when Sum is the list of all numbers in List.
  388%
  389%   @deprecated Use sum_list/2
  390
  391sumlist(List, Sum) :-
  392    sum_list(List, Sum).
  393
  394%!  '$strip_module'(+Term, -Module, -Plain)
  395%
  396%   This used to be an internal predicate.  It was added to the XPCE
  397%   compatibility library without $ and  since   then  used  at many
  398%   places. From 5.4.1 onwards strip_module/3 is  built-in and the $
  399%   variation is added here for compatibility.
  400%
  401%   @deprecated Use strip_module/3.
  402
  403:- module_transparent
  404    '$strip_module'/3.  405
  406'$strip_module'(Term, Module, Plain) :-
  407    strip_module(Term, Module, Plain).
  408
  409%!  '$module'(-OldTypeIn, +NewTypeIn)
  410
  411'$module'(OldTypeIn, NewTypeIn) :-
  412    '$current_typein_module'(OldTypeIn),
  413    '$set_typein_module'(NewTypeIn).
  414
  415%!  '$declare_module'(Module, File, Line)
  416%
  417%   Used in triple20 particle library. Should use a public interface
  418
  419'$declare_module'(Module, File, Line) :-
  420    '$declare_module'(Module, user, user, File, Line, false).
  421
  422
  423%!  at_initialization(:Goal) is det.
  424%
  425%   Register goal only to be run if a saved state is restored.
  426%
  427%   @deprecated Use initialization(Goal, restore)
  428
  429at_initialization(Goal) :-
  430    initialization(Goal, restore).
  431
  432%!  convert_time(+Stamp, -String)
  433%
  434%   Convert  a time-stamp as  obtained though get_time/1 into a  textual
  435%   representation  using the C-library function ctime().  The  value is
  436%   returned  as a  SWI-Prolog string object  (see section  4.23).   See
  437%   also convert_time/8.
  438%
  439%   @deprecated Use format_time/3.
  440
  441
  442convert_time(Stamp, String) :-
  443    format_time(string(String), '%+', Stamp).
  444
  445%!  convert_time(+Stamp, -Y, -Mon, -Day, -Hour, -Min, -Sec, -MilliSec)
  446%
  447%   Convert   a  time  stamp,   provided  by   get_time/1,   time_file/2,
  448%   etc.   Year is  unified with the year,  Month with the month  number
  449%   (January  is 1), Day  with the day of  the month (starting with  1),
  450%   Hour  with  the hour  of the  day (0--23),  Minute  with the  minute
  451%   (0--59).   Second with the  second (0--59) and MilliSecond with  the
  452%   milliseconds  (0--999).  Note that the latter might not  be accurate
  453%   or  might always be 0, depending  on the timing capabilities of  the
  454%   system.  See also convert_time/2.
  455%
  456%   @deprecated Use stamp_date_time/3.
  457
  458convert_time(Stamp, Y, Mon, Day, Hour, Min, Sec, MilliSec) :-
  459    stamp_date_time(Stamp,
  460                    date(Y, Mon, Day,
  461                         Hour, Min, FSec,
  462                         _, _, _),
  463                    local),
  464    Sec is integer(float_integer_part(FSec)),
  465    MilliSec is integer(float_fractional_part(FSec)*1000).
  466
  467%!  'C'(?List, ?Head, ?Tail) is det.
  468%
  469%   Used to be generated by DCG.  Some people appear to be using in
  470%   in normal code too.
  471%
  472%   @deprecated Do not use in normal code; DCG no longer generates it.
  473
  474'C'([H|T], H, T).
  475
  476
  477%!  current_thread(?Thread, ?Status) is nondet.
  478%
  479%   @deprecated Replaced by thread_property/2
  480
  481current_thread(Thread, Status) :-
  482    nonvar(Thread),
  483    !,
  484    catch(thread_property(Thread, status(Status)),
  485          error(existence_error(thread, _), _),
  486          fail).
  487current_thread(Thread, Status) :-
  488    thread_property(Thread, status(Status)).
  489
  490%!  current_mutex(?Mutex, ?Owner, ?Count) is nondet.
  491%
  492%   @deprecated Replaced by mutex_property/2
  493
  494current_mutex(Mutex, Owner, Count) :-
  495    nonvar(Mutex),
  496    !,
  497    catch(mutex_property(Mutex, status(Status)),
  498          error(existence_error(mutex, _), _),
  499          fail),
  500    map_mutex_status(Status, Owner, Count).
  501current_mutex(Mutex, Owner, Count) :-
  502    mutex_property(Mutex, status(Status)),
  503    map_mutex_status(Status, Owner, Count).
  504
  505map_mutex_status(unlocked, [], 0).
  506map_mutex_status(locked(Owner, Count), Owner, Count).
  507
  508
  509%!  message_queue_size(+Queue, -Size) is det.
  510%
  511%   True if Queue holds Size terms.
  512%
  513%   @deprecated Please use message_queue_property(Queue, Size)
  514
  515message_queue_size(Queue, Size) :-
  516    message_queue_property(Queue, size(Size)).
  517
  518%!  lock_predicate(+Name, +Arity) is det.
  519%!  unlock_predicate(+Name, +Arity) is det.
  520%
  521%   @deprecated see lock_predicate/1 and unlock_predicate/1.
  522
  523:- module_transparent
  524    lock_predicate/2,
  525    unlock_predicate/2.  526
  527lock_predicate(Name, Arity) :-
  528    lock_predicate(Name/Arity).
  529
  530unlock_predicate(Name, Arity) :-
  531    unlock_predicate(Name/Arity).
  532
  533%!  current_module(?Module, ?File) is nondet.
  534%
  535%   True if Module is a module loaded from File.
  536%
  537%   @deprecated Use module_property(Module, file(File))
  538
  539current_module(Module, File) :-
  540    module_property(Module, file(File)).
  541
  542%!  export_list(+Module, -List) is det.
  543%
  544%   Module exports the predicates of List.
  545%
  546%   @deprecated Use module_property(Module, exports(List))
  547
  548export_list(Module, List) :-
  549    module_property(Module, exports(List)).
  550
  551%!  setup_and_call_cleanup(:Setup, :Goal, :Cleanup).
  552%
  553%   Call Cleanup once after Goal is finished.
  554%
  555%   @deprecated Use setup_call_cleanup/3.
  556
  557setup_and_call_cleanup(Setup, Goal, Cleanup) :-
  558    setup_call_cleanup(Setup, Goal, Cleanup).
  559
  560%!  setup_and_call_cleanup(:Setup, :Goal, Catcher, :Cleanup).
  561%
  562%   Call Cleanup once after Goal is finished, with Catcher
  563%   unified to the reason
  564%
  565%   @deprecated Use setup_call_cleanup/3.
  566
  567setup_and_call_cleanup(Setup, Goal, Catcher, Cleanup) :-
  568    setup_call_catcher_cleanup(Setup, Goal, Catcher,Cleanup).
  569
  570%!  merge_set(+Set1, +Set2, -Set3)
  571%
  572%   Merge the ordered sets Set1 and  Set2   into  a  new ordered set
  573%   without duplicates.
  574%
  575%   @deprecated     New code should use ord_union/3 from
  576%                   library(ordsets)
  577
  578merge_set([], L, L) :- !.
  579merge_set(L, [], L) :- !.
  580merge_set([H1|T1], [H2|T2], [H1|R]) :- H1 @< H2, !, merge_set(T1, [H2|T2], R).
  581merge_set([H1|T1], [H2|T2], [H2|R]) :- H1 @> H2, !, merge_set([H1|T1], T2, R).
  582merge_set([H1|T1], [H2|T2], [H1|R]) :- H1 == H2,    merge_set(T1, T2, R).
  583
  584
  585%!  merge(+List1, +List2, -List3)
  586%
  587%   Merge the ordered sets List1 and List2 into a new ordered  list.
  588%   Duplicates are not removed and their order is maintained.
  589%
  590%   @deprecated     The name of this predicate is far too general for
  591%                   a rather specific function.
  592
  593merge([], L, L) :- !.
  594merge(L, [], L) :- !.
  595merge([H1|T1], [H2|T2], [H|R]) :-
  596    (   H1 @=< H2
  597    ->  H = H1,
  598        merge(T1, [H2|T2], R)
  599    ;   H = H2,
  600        merge([H1|T1], T2, R)
  601    ).
  602
  603%!  index(:Head) is det.
  604%
  605%   Prepare the predicate  indicated  by   Head  for  multi-argument
  606%   indexing.
  607%
  608%   @deprecated     As of version 5.11.29, SWI-Prolog performs
  609%                   just-in-time indexing on all arguments.
  610
  611index(Head) :-
  612    print_message(warning, decl_no_effect(index(Head))).
  613
  614%!  hash(:PredInd) is det.
  615%
  616%   Demands PredInd to be  indexed  using   a  hash-table.  This  is
  617%   handled dynamically.
  618
  619hash(PI) :-
  620    print_message(warning, decl_no_effect(hash(PI))).
  621
  622%!  set_base_module(:Base) is det.
  623%
  624%   Set the default module from which we inherit.
  625%
  626%   @deprecated Equivalent to set_module(base(Base)).
  627
  628set_base_module(M:Base) :-
  629    set_module(M:base(Base)).
  630
  631%!  eval_license is det.
  632%
  633%   @deprecated Equivalent to license/0
  634
  635eval_license :-
  636    license.
  637
  638%!  trie_insert_new(+Trie, +Term, -Handle) is semidet.
  639%
  640%   @deprecated use trie_insert/4.
  641
  642trie_insert_new(Trie, Term, Handle) :-
  643    trie_insert(Trie, Term, [], Handle).
  644
  645%!  thread_at_exit(:Goal) is det.
  646%
  647%   Register Goal to be called when the calling thread exits.
  648%   @deprecated use prolog_listen(this_thread_exit, Goal)
  649
  650thread_at_exit(Goal) :-
  651    prolog_listen(this_thread_exit, Goal).
  652
  653%!  read_history(+Show, +Help, +Special, +Prompt, -Term, -Bindings)
  654%
  655%   @deprecated use read_term_with_history/2.
  656
  657read_history(Show, Help, Special, Prompt, Term, Bindings) :-
  658    read_term_with_history(
  659        Term,
  660        [ show(Show),
  661          help(Help),
  662          no_save(Special),
  663          prompt(Prompt),
  664          variable_names(Bindings)
  665        ])