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, 47 displayq/1,
48 displayq/2,
49 sformat/2, 50 sformat/3, 51 concat/3,
52 concat_atom/2, 53 concat_atom/3, 54 '$apropos_match'/2, 55 read_clause/1, 56 read_clause/2, 57 read_variables/2, 58 read_variables/3, 59 read_pending_input/3, 60 feature/2,
61 set_feature/2,
62 substring/4,
63 string_to_list/2, 64 string_to_atom/2, 65 flush/0,
66 write_ln/1, 67 proper_list/1, 68 free_variables/2, 69 hash_term/2, 70 checklist/2, 71 sublist/3, 72 sumlist/2, 73 convert_time/2, 74 convert_time/8, 75 'C'/3, 76 current_thread/2, 77 current_mutex/3, 78 message_queue_size/2, 79 lock_predicate/2, 80 unlock_predicate/2, 81 current_module/2, 82 export_list/2, 83 call_cleanup/3, 84 setup_and_call_cleanup/3, 85 setup_and_call_cleanup/4, 86 merge/3, 87 merge_set/3, 88 (index)/1, 89 hash/1, 90 set_base_module/1, 91 eval_license/0,
92 trie_insert_new/3, 93 thread_at_exit/1, 94 read_history/6, 95 96 '$sig_atomic'/1 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(0),
105 call_cleanup(0,?,0),
106 setup_and_call_cleanup(0,0,0),
107 setup_and_call_cleanup(0,0,?,0),
108 checklist(1, +),
109 sublist(1, +, ?),
110 index(:),
111 hash(:),
112 set_base_module(:),
113 thread_at_exit(0),
114 '$sig_atomic'(0).
134'$arch'(Arch, unknown) :-
135 current_prolog_flag(arch, Arch).
141'$version'(Version) :-
142 current_prolog_flag(version, Version).
150'$home'(Home) :-
151 current_prolog_flag(home, Home).
158'$argv'(Argv) :-
159 current_prolog_flag(os_argv, Argv).
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).
187displayq(Term) :-
188 write_term(Term, [ignore_ops(true),quoted(true)]).
189displayq(Stream, Term) :-
190 write_term(Stream, Term, [ignore_ops(true),quoted(true)]).
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).
209concat(A, B, C) :-
210 atom_concat(A, B, C).
219concat_atom([A, B], C) :-
220 !,
221 atom_concat(A, B, C).
222concat_atom(L, Atom) :-
223 atomic_list_concat(L, Atom).
234concat_atom(L, Sep, Atom) :-
235 atomic_list_concat(L, Sep, Atom).
242'$apropos_match'(Needle, Haystack) :-
243 sub_atom_icasechk(Haystack, _, Needle).
249read_clause(Term) :-
250 read_clause(current_input, Term).
256read_clause(Stream, Term) :-
257 read_clause(Stream, Term, [process_comment(false)]).
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)]).
274read_pending_input(Stream, Codes, Tail) :-
275 read_pending_codes(Stream, Codes, Tail).
284feature(Key, Value) :-
285 current_prolog_flag(Key, Value).
286
287set_feature(Key, Value) :-
288 set_prolog_flag(Key, Value).
296substring(String, Offset, Length, Sub) :-
297 Offset0 is Offset - 1,
298 sub_string(String, Offset0, Length, _After, Sub).
307string_to_list(String, Codes) :-
308 string_codes(String, Codes).
317string_to_atom(Atom, String) :-
318 atom_string(String, Atom).
324flush :-
325 flush_output.
331write_ln(X) :-
332 writeln(X).
342proper_list(List) :-
343 is_list(List).
352free_variables(Term, Variables) :-
353 term_variables(Term, Variables).
362hash_term(Term, Hash) :-
363 term_hash(Term, Hash).
370checklist(Goal, List) :-
371 maplist(Goal, List).
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).
396sumlist(List, Sum) :-
397 sum_list(List, Sum).
408:- module_transparent
409 '$strip_module'/3. 410
411'$strip_module'(Term, Module, Plain) :-
412 strip_module(Term, Module, Plain).
416'$module'(OldTypeIn, NewTypeIn) :-
417 '$current_typein_module'(OldTypeIn),
418 '$set_typein_module'(NewTypeIn).
424'$declare_module'(Module, File, Line) :-
425 '$declare_module'(Module, user, user, File, Line, false).
434at_initialization(Goal) :-
435 initialization(Goal, restore).
447convert_time(Stamp, String) :-
448 format_time(string(String), '%+', Stamp).
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).
479'C'([H|T], H, T).
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)).
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).
520message_queue_size(Queue, Size) :-
521 message_queue_property(Queue, size(Size)).
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).
544current_module(Module, File) :-
545 module_property(Module, file(File)).
553export_list(Module, List) :-
554 module_property(Module, exports(List)).
562call_cleanup(Goal, Catcher, Cleanup) :-
563 setup_call_catcher_cleanup(true, Goal, Catcher, Cleanup).
571setup_and_call_cleanup(Setup, Goal, Cleanup) :-
572 setup_call_cleanup(Setup, Goal, Cleanup).
581setup_and_call_cleanup(Setup, Goal, Catcher, Cleanup) :-
582 setup_call_catcher_cleanup(Setup, Goal, Catcher,Cleanup).
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).
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 ).
625index(Head) :-
626 print_message(warning, decl_no_effect(index(Head))).
633hash(PI) :-
634 print_message(warning, decl_no_effect(hash(PI))).
642set_base_module(M:Base) :-
643 set_module(M:base(Base)).
649eval_license :-
650 license.
656trie_insert_new(Trie, Term, Handle) :-
657 trie_insert(Trie, Term, [], Handle).
664thread_at_exit(Goal) :-
665 prolog_listen(this_thread_exit, Goal).
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 ]).
687'$sig_atomic'(Goal) :-
688 sig_atomic(Goal)
Backward compatibility
This library defines predicates that used to exist in older version of SWI-Prolog, but are considered obsolete as there functionality is neatly covered by new features. Most often, these constructs are superseded by ISO-standard compliant predicates.
Please also note the existence of
quintus.pl
andedinburgh.pl
for more compatibility predicates.