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