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