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:- 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
307mode(_).
308
309
310
318simple(X) :-
319 ( atomic(X)
320 -> true
321 ; var(X)
322 ).
323
324
325
334current_stream(Object, Mode, Stream) :-
335 stream_property(Stream, mode(FullMode)),
336 stream_mode(FullMode, Mode),
337 ( stream_property(Stream, file_name(Object0))
338 -> true
339 ; stream_property(Stream, file_no(Object0))
340 -> true
341 ; Object0 = []
342 ),
343 Object = Object0.
344
345stream_mode(read, read).
346stream_mode(write, write).
347stream_mode(append, write).
348stream_mode(update, write).
358stream_position(Stream, Old, New) :-
359 stream_property(Stream, position(Old)),
360 set_stream_position(Stream, New).
369skip_line :-
370 skip(10).
371skip_line(Stream) :-
372 skip(Stream, 10).
373
374
375
386:- meta_predicate
387 compile(:). 388
389compile(Files) :-
390 consult(Files).
391
392
401atom_char(Char, Code) :-
402 char_code(Char, Code).
412midstring(ABC, B, AC) :-
413 midstring(ABC, B, AC, _, _, _).
414midstring(ABC, B, AC, LenA) :-
415 midstring(ABC, B, AC, LenA, _, _).
416midstring(ABC, B, AC, LenA, LenB) :-
417 midstring(ABC, B, AC, LenA, LenB, _).
418midstring(ABC, B, AC, LenA, LenB, LenC) :- 419 var(ABC),
420 !,
421 atom_length(AC, LenAC),
422 ( nonvar(LenA) ; nonvar(LenC)
423 -> plus(LenA, LenC, LenAC)
424 ; true
425 ),
426 sub_atom(AC, 0, LenA, _, A),
427 LenC is LenAC - LenA,
428 sub_atom(AC, _, LenC, 0, C),
429 atom_length(B, LenB),
430 atomic_list_concat([A,B,C], ABC).
431midstring(ABC, B, AC, LenA, LenB, LenC) :-
432 sub_atom(ABC, LenA, LenB, LenC, B),
433 sub_atom(ABC, 0, LenA, _, A),
434 sub_atom(ABC, _, LenC, 0, C),
435 atom_concat(A, C, AC).
436
437
438
446raise_exception(Term) :-
447 throw(Term).
451:- meta_predicate
452 on_exception(+, 0, 0). 453
454on_exception(Except, Goal, Recover) :-
455 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 ... */