35
36:- module(quintus,
37 [ unix/1,
39
40 abs/2,
41 sin/2,
42 cos/2,
43 tan/2,
44 log/2,
45 log10/2,
46 pow/3,
47 ceiling/2,
48 floor/2,
49 round/2,
50 acos/2,
51 asin/2,
52 atan/2,
53 atan2/3,
54 sign/2,
55 sqrt/2,
56
57 genarg/3,
58
59 (mode)/1,
60 no_style_check/1,
61 otherwise/0,
62 simple/1,
64 prolog_flag/2,
65
66 date/1, 67
68 current_stream/3, 69 stream_position/3, 70 skip_line/0,
71 skip_line/1, 72
73 compile/1, 74
75 atom_char/2,
76 midstring/3, 77 midstring/4, 78 midstring/5, 79 midstring/6, 80
81 raise_exception/1, 82 on_exception/3 83 ]). 84:- use_module(library(lists), [member/2]).
102
109unix(system(Command)) :-
110 shell(Command).
111unix(shell(Command)) :-
112 shell(Command).
113unix(shell) :-
114 shell.
115unix(access(File, 0)) :-
116 access_file(File, read).
117unix(cd) :-
118 expand_file_name(~, [Home]),
119 working_directory(_, Home).
120unix(cd(Dir)) :-
121 working_directory(_, Dir).
122unix(args(L)) :-
123 current_prolog_flag(os_argv, L).
124unix(argv(L)) :-
125 current_prolog_flag(os_argv, S),
126 maplist(to_prolog, S, L).
127
128to_prolog(S, A) :-
129 name(S, L),
130 name(A, L).
131
132
133
141otherwise.
142
143
144
151abs(Number, Absolute) :-
152 Absolute is abs(Number).
163sin(A, V) :- V is sin(A).
164cos(A, V) :- V is cos(A).
165tan(A, V) :- V is tan(A).
166log(A, V) :- V is log(A).
167log10(X, V) :- V is log10(X).
168pow(X,Y,V) :- V is X**Y.
169ceiling(X, V) :- V is ceil(X).
170floor(X, V) :- V is floor(X).
171round(X, V) :- V is round(X).
172sqrt(X, V) :- V is sqrt(X).
173acos(X, V) :- V is acos(X).
174asin(X, V) :- V is asin(X).
175atan(X, V) :- V is atan(X).
176atan2(Y, X, V) :- V is atan(Y, X).
177sign(X, V) :- V is sign(X).
178
179
180
189genarg(N, T, A) :-
190 arg(N, T, A).
191
192
193
203prolog_flag(version, Version) :-
204 !,
205 current_prolog_flag(version_data, swi(Major, Minor, Patch, _)),
206 current_prolog_flag(arch, Arch),
207 current_prolog_flag(compiled_at, Compiled),
208 atomic_list_concat(['SWI-Prolog ',
209 Major, '.', Minor, '.', Patch,
210 ' (', Arch, '): ', Compiled], Version).
211prolog_flag(Flag, Value) :-
212 current_prolog_flag(Flag, Value).
213
214
215 218
222
223
224
232date(Date) :-
233 get_time(T),
234 stamp_date_time(T, DaTime, local),
235 date_time_value(date, DaTime, Date).
236
237
238
249q_style_option(single_var, singleton) :- !.
250q_style_option(Option, Option).
251
252no_style_check(QOption) :-
253 q_style_option(QOption, SWIOption),
254 style_check(-SWIOption).
255
256
257
272mode(_).
273
274
275
283simple(X) :-
284 ( atomic(X)
285 -> true
286 ; var(X)
287 ).
288
289
290
299current_stream(Object, Mode, Stream) :-
300 stream_property(Stream, mode(FullMode)),
301 stream_mode(FullMode, Mode),
302 ( stream_property(Stream, file_name(Object0))
303 -> true
304 ; stream_property(Stream, file_no(Object0))
305 -> true
306 ; Object0 = []
307 ),
308 Object = Object0.
309
310stream_mode(read, read).
311stream_mode(write, write).
312stream_mode(append, write).
313stream_mode(update, write).
323stream_position(Stream, Old, New) :-
324 stream_property(Stream, position(Old)),
325 set_stream_position(Stream, New).
334skip_line :-
335 skip(10).
336skip_line(Stream) :-
337 skip(Stream, 10).
338
339
340
351:- meta_predicate
352 compile(:). 353
354compile(Files) :-
355 consult(Files).
356
357
366atom_char(Char, Code) :-
367 char_code(Char, Code).
377midstring(ABC, B, AC) :-
378 midstring(ABC, B, AC, _, _, _).
379midstring(ABC, B, AC, LenA) :-
380 midstring(ABC, B, AC, LenA, _, _).
381midstring(ABC, B, AC, LenA, LenB) :-
382 midstring(ABC, B, AC, LenA, LenB, _).
383midstring(ABC, B, AC, LenA, LenB, LenC) :- 384 var(ABC),
385 !,
386 atom_length(AC, LenAC),
387 ( nonvar(LenA) ; nonvar(LenC)
388 -> plus(LenA, LenC, LenAC)
389 ; true
390 ),
391 sub_atom(AC, 0, LenA, _, A),
392 LenC is LenAC - LenA,
393 sub_atom(AC, _, LenC, 0, C),
394 atom_length(B, LenB),
395 atomic_list_concat([A,B,C], ABC).
396midstring(ABC, B, AC, LenA, LenB, LenC) :-
397 sub_atom(ABC, LenA, LenB, LenC, B),
398 sub_atom(ABC, 0, LenA, _, A),
399 sub_atom(ABC, _, LenC, 0, C),
400 atom_concat(A, C, AC).
401
402
403
411raise_exception(Term) :-
412 throw(Term).
416:- meta_predicate
417 on_exception(+, 0, 0). 418
419on_exception(Except, Goal, Recover) :-
420 catch(Goal, Except, Recover)
Quintus compatibility
This module defines several predicates from the Quintus Prolog libraries. Note that our library structure is totally different. If this library were complete, Prolog code could be ported by removing the use_module/1 declarations, relying on the SWI-Prolog autoloader.
Bluffers guide to porting:
use_module(library(...))
?- list_undefined.
Of course, this library is incomplete ... */