36
37:- module(quintus,
38 [ unix/1,
40
41 abs/2,
42 sin/2,
43 cos/2,
44 tan/2,
45 log/2,
46 log10/2,
47 pow/3,
48 ceiling/2,
49 floor/2,
50 round/2,
51 acos/2,
52 asin/2,
53 atan/2,
54 atan2/3,
55 sign/2,
56 sqrt/2,
57
58 genarg/3,
59
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:- autoload(library(apply),[maplist/3]). 85:- autoload(library(date),[date_time_value/3]). 86:- autoload(library(shell),[shell/0]).
105
130unix(system(Command)) :-
131 shell(Command).
132unix(shell(Command)) :-
133 shell(Command).
134unix(shell) :-
135 shell.
136unix(access(File, 0)) :-
137 access_file(File, read).
138unix(cd) :-
139 expand_file_name(~, [Home]),
140 working_directory(_, Home).
141unix(cd(Dir)) :-
142 working_directory(_, Dir).
143unix(args(L)) :-
144 current_prolog_flag(os_argv, L).
145unix(argv(L)) :-
146 current_prolog_flag(os_argv, S),
147 maplist(to_prolog, S, L).
148
149to_prolog(S, A) :-
150 name(S, L),
151 name(A, L).
152
153
154
162otherwise.
163
164
165
172abs(Number, Absolute) :-
173 Absolute is abs(Number).
198sin(A, V) :- V is sin(A).
199cos(A, V) :- V is cos(A).
200tan(A, V) :- V is tan(A).
201log(A, V) :- V is log(A).
202log10(X, V) :- V is log10(X).
203pow(X,Y,V) :- V is X**Y.
204ceiling(X, V) :- V is ceil(X).
205floor(X, V) :- V is floor(X).
206round(X, V) :- V is round(X).
207sqrt(X, V) :- V is sqrt(X).
208acos(X, V) :- V is acos(X).
209asin(X, V) :- V is asin(X).
210atan(X, V) :- V is atan(X).
211atan2(Y, X, V) :- V is atan(Y, X).
212sign(X, V) :- V is sign(X).
213
214
215
224genarg(N, T, A) :-
225 arg(N, T, A).
226
227
228
238prolog_flag(version, Version) :-
239 !,
240 current_prolog_flag(version_data, swi(Major, Minor, Patch, _)),
241 current_prolog_flag(arch, Arch),
242 current_prolog_flag(compiled_at, Compiled),
243 atomic_list_concat(['SWI-Prolog ',
244 Major, '.', Minor, '.', Patch,
245 ' (', Arch, '): ', Compiled], Version).
246prolog_flag(Flag, Value) :-
247 current_prolog_flag(Flag, Value).
248
249
250 253
257
258
259
267date(Date) :-
268 get_time(T),
269 stamp_date_time(T, DaTime, local),
270 date_time_value(date, DaTime, Date).
271
272
273
284q_style_option(single_var, singleton) :- !.
285q_style_option(Option, Option).
286
287no_style_check(QOption) :-
288 q_style_option(QOption, SWIOption),
289 style_check(-SWIOption).
290
291
292
300simple(X) :-
301 ( atomic(X)
302 -> true
303 ; var(X)
304 ).
305
306
307
316current_stream(Object, Mode, Stream) :-
317 stream_property(Stream, mode(FullMode)),
318 stream_mode(FullMode, Mode),
319 ( stream_property(Stream, file_name(Object0))
320 -> true
321 ; stream_property(Stream, file_no(Object0))
322 -> true
323 ; Object0 = []
324 ),
325 Object = Object0.
326
327stream_mode(read, read).
328stream_mode(write, write).
329stream_mode(append, write).
330stream_mode(update, write).
340stream_position(Stream, Old, New) :-
341 stream_property(Stream, position(Old)),
342 set_stream_position(Stream, New).
351skip_line :-
352 skip(10).
353skip_line(Stream) :-
354 skip(Stream, 10).
355
356
357
368:- meta_predicate
369 compile(:). 370
371compile(Files) :-
372 consult(Files).
373
374
383atom_char(Char, Code) :-
384 char_code(Char, Code).
394midstring(ABC, B, AC) :-
395 midstring(ABC, B, AC, _, _, _).
396midstring(ABC, B, AC, LenA) :-
397 midstring(ABC, B, AC, LenA, _, _).
398midstring(ABC, B, AC, LenA, LenB) :-
399 midstring(ABC, B, AC, LenA, LenB, _).
400midstring(ABC, B, AC, LenA, LenB, LenC) :- 401 var(ABC),
402 !,
403 atom_length(AC, LenAC),
404 ( nonvar(LenA) ; nonvar(LenC)
405 -> plus(LenA, LenC, LenAC)
406 ; true
407 ),
408 sub_atom(AC, 0, LenA, _, A),
409 LenC is LenAC - LenA,
410 sub_atom(AC, _, LenC, 0, C),
411 atom_length(B, LenB),
412 atomic_list_concat([A,B,C], ABC).
413midstring(ABC, B, AC, LenA, LenB, LenC) :-
414 sub_atom(ABC, LenA, LenB, LenC, B),
415 sub_atom(ABC, 0, LenA, _, A),
416 sub_atom(ABC, _, LenC, 0, C),
417 atom_concat(A, C, AC).
418
419
420
428raise_exception(Term) :-
429 throw(Term).
433:- meta_predicate
434 on_exception(+, 0, 0). 435
436on_exception(Except, Goal, Recover) :-
437 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 ... */