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 hash_term/2, 69 checklist/2, 70 sublist/3, 71 sumlist/2, 72 convert_time/2, 73 convert_time/8, 74 'C'/3, 75 current_thread/2, 76 current_mutex/3, 77 message_queue_size/2, 78 lock_predicate/2, 79 unlock_predicate/2, 80 current_module/2, 81 export_list/2, 82 setup_and_call_cleanup/3, 83 setup_and_call_cleanup/4, 84 merge/3, 85 merge_set/3, 86 (index)/1, 87 hash/1, 88 set_base_module/1, 89 eval_license/0,
90 trie_insert_new/3, 91 thread_at_exit/1, 92 read_history/6 93 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).
129'$arch'(Arch, unknown) :-
130 current_prolog_flag(arch, Arch).
136'$version'(Version) :-
137 current_prolog_flag(version, Version).
145'$home'(Home) :-
146 current_prolog_flag(home, Home).
153'$argv'(Argv) :-
154 current_prolog_flag(os_argv, Argv).
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).
182displayq(Term) :-
183 write_term(Term, [ignore_ops(true),quoted(true)]).
184displayq(Stream, Term) :-
185 write_term(Stream, Term, [ignore_ops(true),quoted(true)]).
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).
204concat(A, B, C) :-
205 atom_concat(A, B, C).
214concat_atom([A, B], C) :-
215 !,
216 atom_concat(A, B, C).
217concat_atom(L, Atom) :-
218 atomic_list_concat(L, Atom).
229concat_atom(L, Sep, Atom) :-
230 atomic_list_concat(L, Sep, Atom).
237'$apropos_match'(Needle, Haystack) :-
238 sub_atom_icasechk(Haystack, _, Needle).
244read_clause(Term) :-
245 read_clause(current_input, Term).
251read_clause(Stream, Term) :-
252 read_clause(Stream, Term, [process_comment(false)]).
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)]).
269read_pending_input(Stream, Codes, Tail) :-
270 read_pending_codes(Stream, Codes, Tail).
279feature(Key, Value) :-
280 current_prolog_flag(Key, Value).
281
282set_feature(Key, Value) :-
283 set_prolog_flag(Key, Value).
291substring(String, Offset, Length, Sub) :-
292 Offset0 is Offset - 1,
293 sub_string(String, Offset0, Length, _After, Sub).
302string_to_list(String, Codes) :-
303 string_codes(String, Codes).
312string_to_atom(Atom, String) :-
313 atom_string(String, Atom).
319flush :-
320 flush_output.
326write_ln(X) :-
327 writeln(X).
337proper_list(List) :-
338 is_list(List).
347free_variables(Term, Variables) :-
348 term_variables(Term, Variables).
357hash_term(Term, Hash) :-
358 term_hash(Term, Hash).
365checklist(Goal, List) :-
366 maplist(Goal, List).
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).
391sumlist(List, Sum) :-
392 sum_list(List, Sum).
403:- module_transparent
404 '$strip_module'/3. 405
406'$strip_module'(Term, Module, Plain) :-
407 strip_module(Term, Module, Plain).
411'$module'(OldTypeIn, NewTypeIn) :-
412 '$current_typein_module'(OldTypeIn),
413 '$set_typein_module'(NewTypeIn).
419'$declare_module'(Module, File, Line) :-
420 '$declare_module'(Module, user, user, File, Line, false).
429at_initialization(Goal) :-
430 initialization(Goal, restore).
442convert_time(Stamp, String) :-
443 format_time(string(String), '%+', Stamp).
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).
474'C'([H|T], H, T).
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)).
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).
515message_queue_size(Queue, Size) :-
516 message_queue_property(Queue, size(Size)).
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).
539current_module(Module, File) :-
540 module_property(Module, file(File)).
548export_list(Module, List) :-
549 module_property(Module, exports(List)).
557setup_and_call_cleanup(Setup, Goal, Cleanup) :-
558 setup_call_cleanup(Setup, Goal, Cleanup).
567setup_and_call_cleanup(Setup, Goal, Catcher, Cleanup) :-
568 setup_call_catcher_cleanup(Setup, Goal, Catcher,Cleanup).
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).
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 ).
611index(Head) :-
612 print_message(warning, decl_no_effect(index(Head))).
619hash(PI) :-
620 print_message(warning, decl_no_effect(hash(PI))).
628set_base_module(M:Base) :-
629 set_module(M:base(Base)).
635eval_license :-
636 license.
642trie_insert_new(Trie, Term, Handle) :-
643 trie_insert(Trie, Term, [], Handle).
650thread_at_exit(Goal) :-
651 prolog_listen(this_thread_exit, Goal).
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 ])
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.