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, 46 displayq/1,
47 displayq/2,
48 sformat/2, 49 sformat/3, 50 concat/3,
51 concat_atom/2, 52 concat_atom/3, 53 '$apropos_match'/2, 54 read_clause/1, 55 read_clause/2, 56 read_variables/2, 57 read_variables/3, 58 read_pending_input/3, 59 feature/2,
60 set_feature/2,
61 substring/4,
62 string_to_list/2, 63 string_to_atom/2, 64 flush/0,
65 write_ln/1, 66 proper_list/1, 67 free_variables/2, 68 subsumes_chk/2, 69 subsumes/2, 70 hash_term/2, 71 checklist/2, 72 sublist/3, 73 sumlist/2, 74 convert_time/2, 75 convert_time/8, 76 'C'/3, 77 current_thread/2, 78 current_mutex/3, 79 message_queue_size/2, 80 lock_predicate/2, 81 unlock_predicate/2, 82 current_module/2, 83 export_list/2, 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 ]). 94:- use_module(apply, [maplist/2]). 95:- use_module(system, [lock_predicate/1, unlock_predicate/1]). 96:- use_module(lists, [sum_list/2]). 97
98:- meta_predicate
99 at_initialization(0),
100 setup_and_call_cleanup(0,0,0),
101 setup_and_call_cleanup(0,0,?,0),
102 checklist(1, +),
103 sublist(1, +, ?),
104 index(:),
105 hash(:),
106 set_base_module(:).
126'$arch'(Arch, unknown) :-
127 current_prolog_flag(arch, Arch).
133'$version'(Version) :-
134 current_prolog_flag(version, Version).
142'$home'(Home) :-
143 current_prolog_flag(home, Home).
150'$argv'(Argv) :-
151 current_prolog_flag(os_argv, Argv).
159'$set_prompt'(Prompt) :-
160 ( is_list(Prompt)
161 -> Prompt0 = Prompt
162 ; atom_codes(Prompt, Prompt0)
163 ),
164 maplist(percent_to_tilde, Prompt0, Prompt1),
165 atom_codes(Atom, Prompt1),
166 set_prolog_flag(toplevel_prompt, Atom).
167
168percent_to_tilde(0'%, 0'~) :- !.
169percent_to_tilde(X, X).
179displayq(Term) :-
180 write_term(Term, [ignore_ops(true),quoted(true)]).
181displayq(Stream, Term) :-
182 write_term(Stream, Term, [ignore_ops(true),quoted(true)]).
190:- module_transparent sformat/2, sformat/3. 191
192sformat(String, Format) :-
193 format(string(String), Format, []).
194sformat(String, Format, Arguments) :-
195 format(string(String), Format, Arguments).
201concat(A, B, C) :-
202 atom_concat(A, B, C).
211concat_atom([A, B], C) :-
212 !,
213 atom_concat(A, B, C).
214concat_atom(L, Atom) :-
215 atomic_list_concat(L, Atom).
226concat_atom(L, Sep, Atom) :-
227 atomic_list_concat(L, Sep, Atom).
234'$apropos_match'(Needle, Haystack) :-
235 sub_atom_icasechk(Haystack, _, Needle).
241read_clause(Term) :-
242 read_clause(current_input, Term).
248read_clause(Stream, Term) :-
249 read_clause(Stream, Term, [process_comment(false)]).
256read_variables(Term, Vars) :-
257 read_term(Term, [variable_names(Vars)]).
258
259read_variables(Stream, Term, Vars) :-
260 read_term(Stream, Term, [variable_names(Vars)]).
266read_pending_input(Stream, Codes, Tail) :-
267 read_pending_codes(Stream, Codes, Tail).
276feature(Key, Value) :-
277 current_prolog_flag(Key, Value).
278
279set_feature(Key, Value) :-
280 set_prolog_flag(Key, Value).
288substring(String, Offset, Length, Sub) :-
289 Offset0 is Offset - 1,
290 sub_string(String, Offset0, Length, _After, Sub).
299string_to_list(String, Codes) :-
300 string_codes(String, Codes).
309string_to_atom(Atom, String) :-
310 atom_string(String, Atom).
316flush :-
317 flush_output.
323write_ln(X) :-
324 writeln(X).
334proper_list(List) :-
335 is_list(List).
344free_variables(Term, Variables) :-
345 term_variables(Term, Variables).
354subsumes_chk(Generic, Specific) :-
355 subsumes_term(Generic, Specific).
367subsumes(Generic, Specific) :-
368 subsumes_term(Generic, Specific),
369 Generic = Specific.
378hash_term(Term, Hash) :-
379 term_hash(Term, Hash).
386checklist(Goal, List) :-
387 maplist(Goal, List).
397sublist(_, [], []) :- !.
398sublist(Goal, [H|T], Sub) :-
399 call(Goal, H),
400 !,
401 Sub = [H|R],
402 sublist(Goal, T, R).
403sublist(Goal, [_|T], R) :-
404 sublist(Goal, T, R).
412sumlist(List, Sum) :-
413 sum_list(List, Sum).
424:- module_transparent
425 '$strip_module'/3. 426
427'$strip_module'(Term, Module, Plain) :-
428 strip_module(Term, Module, Plain).
432'$module'(OldTypeIn, NewTypeIn) :-
433 '$current_typein_module'(OldTypeIn),
434 '$set_typein_module'(NewTypeIn).
440'$declare_module'(Module, File, Line) :-
441 '$declare_module'(Module, user, user, File, Line, false).
450at_initialization(Goal) :-
451 initialization(Goal, restore).
463convert_time(Stamp, String) :-
464 format_time(string(String), '%+', Stamp).
479convert_time(Stamp, Y, Mon, Day, Hour, Min, Sec, MilliSec) :-
480 stamp_date_time(Stamp,
481 date(Y, Mon, Day,
482 Hour, Min, FSec,
483 _, _, _),
484 local),
485 Sec is integer(float_integer_part(FSec)),
486 MilliSec is integer(float_fractional_part(FSec)*1000).
495'C'([H|T], H, T).
502current_thread(Thread, Status) :-
503 nonvar(Thread),
504 !,
505 catch(thread_property(Thread, status(Status)),
506 error(existence_error(thread, _), _),
507 fail).
508current_thread(Thread, Status) :-
509 thread_property(Thread, status(Status)).
515current_mutex(Mutex, Owner, Count) :-
516 nonvar(Mutex),
517 !,
518 catch(mutex_property(Mutex, status(Status)),
519 error(existence_error(mutex, _), _),
520 fail),
521 map_mutex_status(Status, Owner, Count).
522current_mutex(Mutex, Owner, Count) :-
523 mutex_property(Mutex, status(Status)),
524 map_mutex_status(Status, Owner, Count).
525
526map_mutex_status(unlocked, [], 0).
527map_mutex_status(locked(Owner, Count), Owner, Count).
536message_queue_size(Queue, Size) :-
537 message_queue_property(Queue, size(Size)).
544:- module_transparent
545 lock_predicate/2,
546 unlock_predicate/2. 547
548lock_predicate(Name, Arity) :-
549 lock_predicate(Name/Arity).
550
551unlock_predicate(Name, Arity) :-
552 unlock_predicate(Name/Arity).
560current_module(Module, File) :-
561 module_property(Module, file(File)).
569export_list(Module, List) :-
570 module_property(Module, exports(List)).
578setup_and_call_cleanup(Setup, Goal, Cleanup) :-
579 setup_call_cleanup(Setup, Goal, Cleanup).
588setup_and_call_cleanup(Setup, Goal, Catcher, Cleanup) :-
589 setup_call_catcher_cleanup(Setup, Goal, Catcher,Cleanup).
599merge_set([], L, L) :- !.
600merge_set(L, [], L) :- !.
601merge_set([H1|T1], [H2|T2], [H1|R]) :- H1 @< H2, !, merge_set(T1, [H2|T2], R).
602merge_set([H1|T1], [H2|T2], [H2|R]) :- H1 @> H2, !, merge_set([H1|T1], T2, R).
603merge_set([H1|T1], [H2|T2], [H1|R]) :- H1 == H2, merge_set(T1, T2, R).
614merge([], L, L) :- !.
615merge(L, [], L) :- !.
616merge([H1|T1], [H2|T2], [H|R]) :-
617 ( H1 @=< H2
618 -> H = H1,
619 merge(T1, [H2|T2], R)
620 ; H = H2,
621 merge([H1|T1], T2, R)
622 ).
632index(Head) :-
633 print_message(warning, decl_no_effect(index(Head))).
640hash(PI) :-
641 print_message(warning, decl_no_effect(hash(PI))).
649set_base_module(M:Base) :-
650 set_module(M:base(Base)).
656eval_license :-
657 license.
663trie_insert_new(Trie, Term, Handle) :-
664 trie_insert(Trie, Term, [], Handle)
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 superceeded by ISO-standard compliant predicates.
Please also note the existence of
quintus.pl
andedinburgh.pl
for more compatibility predicates.