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).
177sin(A, V) :- V is sin(A).
178cos(A, V) :- V is cos(A).
179tan(A, V) :- V is tan(A).
180log(A, V) :- V is log(A).
181log10(X, V) :- V is log10(X).
182pow(X,Y,V) :- V is X**Y.
183ceiling(X, V) :- V is ceil(X).
184floor(X, V) :- V is floor(X).
185round(X, V) :- V is round(X).
186sqrt(X, V) :- V is sqrt(X).
187acos(X, V) :- V is acos(X).
188asin(X, V) :- V is asin(X).
189atan(X, V) :- V is atan(X).
190atan2(Y, X, V) :- V is atan(Y, X).
191sign(X, V) :- V is sign(X).
192
193
194
203genarg(N, T, A) :-
204 arg(N, T, A).
205
206
207
217prolog_flag(version, Version) :-
218 !,
219 current_prolog_flag(version_data, swi(Major, Minor, Patch, _)),
220 current_prolog_flag(arch, Arch),
221 current_prolog_flag(compiled_at, Compiled),
222 atomic_list_concat(['SWI-Prolog ',
223 Major, '.', Minor, '.', Patch,
224 ' (', Arch, '): ', Compiled], Version).
225prolog_flag(Flag, Value) :-
226 current_prolog_flag(Flag, Value).
227
228
229 232
236
237
238
246date(Date) :-
247 get_time(T),
248 stamp_date_time(T, DaTime, local),
249 date_time_value(date, DaTime, Date).
250
251
252
263q_style_option(single_var, singleton) :- !.
264q_style_option(Option, Option).
265
266no_style_check(QOption) :-
267 q_style_option(QOption, SWIOption),
268 style_check(-SWIOption).
269
270
271
286mode(_).
287
288
289
297simple(X) :-
298 ( atomic(X)
299 -> true
300 ; var(X)
301 ).
302
303
304
313current_stream(Object, Mode, Stream) :-
314 stream_property(Stream, mode(FullMode)),
315 stream_mode(FullMode, Mode),
316 ( stream_property(Stream, file_name(Object0))
317 -> true
318 ; stream_property(Stream, file_no(Object0))
319 -> true
320 ; Object0 = []
321 ),
322 Object = Object0.
323
324stream_mode(read, read).
325stream_mode(write, write).
326stream_mode(append, write).
327stream_mode(update, write).
337stream_position(Stream, Old, New) :-
338 stream_property(Stream, position(Old)),
339 set_stream_position(Stream, New).
348skip_line :-
349 skip(10).
350skip_line(Stream) :-
351 skip(Stream, 10).
352
353
354
365:- meta_predicate
366 compile(:). 367
368compile(Files) :-
369 consult(Files).
370
371
380atom_char(Char, Code) :-
381 char_code(Char, Code).
391midstring(ABC, B, AC) :-
392 midstring(ABC, B, AC, _, _, _).
393midstring(ABC, B, AC, LenA) :-
394 midstring(ABC, B, AC, LenA, _, _).
395midstring(ABC, B, AC, LenA, LenB) :-
396 midstring(ABC, B, AC, LenA, LenB, _).
397midstring(ABC, B, AC, LenA, LenB, LenC) :- 398 var(ABC),
399 !,
400 atom_length(AC, LenAC),
401 ( nonvar(LenA) ; nonvar(LenC)
402 -> plus(LenA, LenC, LenAC)
403 ; true
404 ),
405 sub_atom(AC, 0, LenA, _, A),
406 LenC is LenAC - LenA,
407 sub_atom(AC, _, LenC, 0, C),
408 atom_length(B, LenB),
409 atomic_list_concat([A,B,C], ABC).
410midstring(ABC, B, AC, LenA, LenB, LenC) :-
411 sub_atom(ABC, LenA, LenB, LenC, B),
412 sub_atom(ABC, 0, LenA, _, A),
413 sub_atom(ABC, _, LenC, 0, C),
414 atom_concat(A, C, AC).
415
416
417
425raise_exception(Term) :-
426 throw(Term).
430:- meta_predicate
431 on_exception(+, 0, 0). 432
433on_exception(Except, Goal, Recover) :-
434 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 ... */