samer@0
|
1 % Some general utilities
|
samer@0
|
2
|
samer@0
|
3 :- module(utils,[
|
samer@0
|
4
|
samer@0
|
5 % type testing and enumeration
|
samer@0
|
6 natural/1 % test or enumerate natural numbers
|
samer@0
|
7 , isfinite/1 % check number is non NaN or Inf
|
samer@0
|
8 , int/1 % test or enumerate integers
|
samer@0
|
9 , in/2
|
samer@0
|
10
|
samer@0
|
11 % mathematical utilities
|
samer@0
|
12 , max/3
|
samer@0
|
13 , min/3
|
samer@0
|
14
|
samer@0
|
15 % list utilities
|
samer@0
|
16 , list_idx1_member/3 % like nth1 but more useful argument order
|
samer@0
|
17 , apply_to_nth1/4
|
samer@0
|
18 , measure/3 % match list lengths
|
samer@0
|
19 , equal_length/2 % match 2 list lengths
|
samer@0
|
20 , getopts/2
|
samer@0
|
21 , rep/3 % make a list of repeats of the same term
|
samer@0
|
22 , cons/3 % list constructror
|
samer@0
|
23 , decons/3 % list deconstructor
|
samer@0
|
24
|
samer@0
|
25 % comma lists
|
samer@0
|
26 , cl_list/2
|
samer@0
|
27 , cl_list_vt/2
|
samer@0
|
28 , cl_length/2
|
samer@0
|
29 , cl_length_vt/2
|
samer@0
|
30 , cl_member/2
|
samer@0
|
31
|
samer@0
|
32
|
samer@0
|
33 % term manipulation
|
samer@0
|
34 , copy_head/2 % check terms for same head and arity
|
samer@0
|
35 , unify_args/5
|
samer@0
|
36 , reinstatevars/3
|
samer@0
|
37 , reinstatevars/4
|
samer@0
|
38
|
samer@0
|
39 % formatting and parsing
|
samer@0
|
40 , aphrase/2 % like phrase but makes an atom instead of a string
|
samer@0
|
41 , aphrase/3 % like aphrase but takes code list
|
samer@0
|
42 , print_list/1 % writes each element on a new line
|
samer@0
|
43 , printq_list/1 % as print_list but quotes atom as necessary
|
samer@0
|
44 , print_numbered_list/1
|
samer@0
|
45
|
samer@0
|
46 % database management
|
samer@0
|
47 , extensible/1 % declare dynamic multifile predicate
|
samer@0
|
48 , bt_assert/1
|
samer@0
|
49 , bt_retract/1
|
samer@0
|
50 , strict_assert/1
|
samer@0
|
51 , strict_retract/1
|
samer@0
|
52 , browse/2 % browse predicate with unknown arity
|
samer@0
|
53 , current_state/2
|
samer@0
|
54 , set_state/2
|
samer@0
|
55
|
samer@0
|
56 % file system utilities
|
samer@0
|
57 , dir/2 % directory listing
|
samer@0
|
58 , path_atom/2 % expand paths
|
samer@0
|
59 , expand_path/2 % expand paths
|
samer@0
|
60
|
samer@0
|
61 % operating system
|
samer@0
|
62 , open_with/2 % apply shell command to a file (SIDE EFFECTS)
|
samer@0
|
63 , open_with/3 % apply shell command to a file with options (SIDE EFFECTS)
|
samer@0
|
64 , shellcmd/2 % apply shell command to arguments
|
samer@0
|
65 , open_/1 % open with 'open' command (Mac OS X).
|
samer@0
|
66 , fmt_shellcmd/3 % format a shell command with switches and args
|
samer@0
|
67 , hostname/1
|
samer@0
|
68
|
samer@0
|
69 % user interaction
|
samer@0
|
70 , read_char_echo/1 % read one character and echo it immediately
|
samer@0
|
71 , get_key/2 % read and validate keypress
|
samer@0
|
72 , userchk/1 % unary predicate which allows user to force failure
|
samer@0
|
73 , prompt_for_key/3
|
samer@0
|
74
|
samer@0
|
75 % ---- high order stuff ----
|
samer@0
|
76
|
samer@0
|
77 % modes of computation
|
samer@0
|
78 , retry/1 % keep trying until success
|
samer@0
|
79 , parallel/1 % parallel computation using threads
|
samer@0
|
80 , bt_call/2 % Construct backtrackable operation
|
samer@0
|
81 , on_backtracking/1
|
samer@0
|
82
|
samer@0
|
83 % iteration
|
samer@0
|
84 , exhaust/1 % trigger all solutions to a goal (SIDE EFFECTS)
|
samer@0
|
85 , iterate/3 % apply predicate recursively till failure
|
samer@0
|
86
|
samer@0
|
87 % mapping
|
samer@0
|
88 , for_naturals/2 % call predicate with natural numbers N down to 1
|
samer@0
|
89 , mapints/2 % call predicate with integers
|
samer@0
|
90 , mapints/3
|
samer@0
|
91 , mapargs/2, mapargs/3, mapargs/4
|
samer@0
|
92 , mapargs_x/4, mapargs_x/5, mapargs_x/6
|
samer@0
|
93 , mapargs_xx/6
|
samer@0
|
94 , sfold/4 % structural fold for lists
|
samer@0
|
95 , take/3
|
samer@0
|
96 , drop/3
|
samer@0
|
97 , drop_while/3
|
samer@0
|
98 , take_while/3
|
samer@0
|
99
|
samer@0
|
100 % lambda expressions
|
samer@0
|
101 , mcall/2, mcall/3, mcall/4
|
samer@0
|
102
|
samer@0
|
103 ]).
|
samer@0
|
104
|
samer@0
|
105 /** <module> General utilities
|
samer@0
|
106
|
samer@0
|
107 The predicates in this module can be divided into several groups as listed
|
samer@0
|
108 below.
|
samer@0
|
109
|
samer@0
|
110 ---+++ Type testing and enumeration
|
samer@0
|
111 * natural/1 - test or enumerate natural numbers
|
samer@0
|
112 * isfinite/1 - check number is non NaN or Inf
|
samer@0
|
113 * int/1 - test or enumerate integers
|
samer@0
|
114 * in/2
|
samer@0
|
115
|
samer@0
|
116 ---+++ mathematical utilities
|
samer@0
|
117 * max/3
|
samer@0
|
118 * min/3
|
samer@0
|
119
|
samer@0
|
120 ---+++ list utilities
|
samer@0
|
121 * list_idx1_member/3 % like nth1 but more useful argument order
|
samer@0
|
122 * measure/3 - match list lengths
|
samer@0
|
123 * equal_length/2 - match two list lenghts
|
samer@0
|
124 * getopts/2
|
samer@0
|
125 * rep/3 - make a list of repeats of the same term
|
samer@0
|
126 * cons/3 - make list from head and tail
|
samer@0
|
127 * decons/3 - get head and tail from list
|
samer@0
|
128
|
samer@0
|
129 ---+++ term manipulation
|
samer@0
|
130 * copy_head/2 - check terms for same head and arity
|
samer@0
|
131 * unify_args/5
|
samer@0
|
132 * reinstatevars/3
|
samer@0
|
133 * reinstatevars/4
|
samer@0
|
134
|
samer@0
|
135 ---+++ formatting and parsing
|
samer@0
|
136 * aphrase/2 - like phrase but makes an atom instead of a string
|
samer@0
|
137 * aphrase/3 - like aphrase but takes code list
|
samer@0
|
138 * print_list/1 - write/1 each element, one per line
|
samer@0
|
139 * printq_list/1 - as print_list but quotes atom as with writeq/1
|
samer@0
|
140 * print_numbered_list/1 - as print_list/1 but with line numbers
|
samer@0
|
141
|
samer@0
|
142 ---+++ database management
|
samer@0
|
143 * extensible/1 - declare dynamic multifile predicate
|
samer@0
|
144 * bt_assert/1
|
samer@0
|
145 * bt_retract/1
|
samer@0
|
146 * strict_assert/1
|
samer@0
|
147 * strict_retract/1
|
samer@0
|
148 * browse/2 - browse predicate with unknown arity
|
samer@0
|
149 * current_state/2
|
samer@0
|
150 * set_state/2
|
samer@0
|
151
|
samer@0
|
152 ---+++ file system utilities
|
samer@0
|
153 * dir/2 - directory listing
|
samer@0
|
154 * path_atom/2 - expand paths
|
samer@0
|
155 * expand_path/2 - expand paths
|
samer@0
|
156
|
samer@0
|
157 ---+++ operating system
|
samer@0
|
158 * open_with/2 - apply shell command to a file (SIDE EFFECTS)
|
samer@0
|
159 * open_with/3 - apply shell command to a file with options (SIDE EFFECTS)
|
samer@0
|
160 * shellcmd/2 - apply shell command to arguments
|
samer@0
|
161 * open_/1 - open with 'open' command (Mac OS X).
|
samer@0
|
162 * fmt_shellcmd/3 - format a shell command with switches and args
|
samer@0
|
163 * hostname/1
|
samer@0
|
164
|
samer@0
|
165 ---+++ user interaction
|
samer@0
|
166 * read_char_echo/1 - read one character and echo it immediately
|
samer@0
|
167 * get_key/2 - read and validate keypress
|
samer@0
|
168 * userchk/1 - unary predicate which allows user to force failure
|
samer@0
|
169 * prompt_for_key/3 - print message and get keypress from user
|
samer@0
|
170
|
samer@0
|
171 ---+++ High order stuff
|
samer@0
|
172
|
samer@0
|
173 ---++++ modes of computation
|
samer@0
|
174 * retry/1 - keep trying until success
|
samer@0
|
175 * parallel/1 - parallel computation using threads
|
samer@0
|
176 * bt_call/2 - Construct backtrackable operation
|
samer@0
|
177 , on_backtracking/1
|
samer@0
|
178
|
samer@0
|
179 ---++++ iteration
|
samer@0
|
180 * exhaust/1 - trigger all solutions to a goal (SIDE EFFECTS)
|
samer@0
|
181 * iterate/3 - apply predicate recursively till failure
|
samer@0
|
182
|
samer@0
|
183 ---++++ mapping
|
samer@0
|
184 * for_naturals/2 - call predicate with natural numbers N down to 1
|
samer@0
|
185 * mapints/2 - call predicate with integers
|
samer@0
|
186 * mapints/3
|
samer@0
|
187 * mapargs/2, mapargs/3, mapargs/4
|
samer@0
|
188 * mapargs_xx/6
|
samer@0
|
189 * sfold/4 - structural fold for lists
|
samer@0
|
190 * take/3
|
samer@0
|
191 * drop/3
|
samer@0
|
192 * drop_while/3
|
samer@0
|
193 * take_while/3
|
samer@0
|
194
|
samer@0
|
195 ---++++ lambda expressions
|
samer@0
|
196 * mcall/2, mcall/3, mcall/4
|
samer@0
|
197 */
|
samer@0
|
198
|
samer@0
|
199 :- use_module(library(ops)).
|
samer@0
|
200
|
samer@0
|
201 :- meta_predicate
|
samer@0
|
202 exhaust(0)
|
samer@0
|
203 , retry(0)
|
samer@0
|
204 , iterate(2,?,?)
|
samer@0
|
205 , drop_while(1,?,?)
|
samer@0
|
206 , take_while(1,?,?)
|
samer@0
|
207 , apply_to_nth1(?,2,?,?)
|
samer@0
|
208 , for_naturals(+,1)
|
samer@0
|
209 , for_ints(+,+,1)
|
samer@0
|
210 , mapints(1,?)
|
samer@0
|
211 , mapints(2,?,?)
|
samer@0
|
212 , mapargs(1,?)
|
samer@0
|
213 , mapargs(2,?,?)
|
samer@0
|
214 , mapargs(3,?,?,?)
|
samer@0
|
215 , mapargs_x(+,+,1,?)
|
samer@0
|
216 , mapargs_x(+,+,2,?,?)
|
samer@0
|
217 , mapargs_x(+,+,3,?,?,?)
|
samer@0
|
218 , mapargs_xx(2,?,?,?,?,?)
|
samer@0
|
219 , on_backtracking(0)
|
samer@0
|
220 , bt_call(0,0)
|
samer@0
|
221 , bt_assert(:)
|
samer@0
|
222 , bt_retract(:)
|
samer@0
|
223 , strict_assert(:)
|
samer@0
|
224 , strict_retract(:)
|
samer@0
|
225 , extensible(:)
|
samer@0
|
226 , aphrase(2,?)
|
samer@0
|
227 , aphrase(2,?,?)
|
samer@0
|
228 .
|
samer@0
|
229
|
samer@0
|
230 :- multifile user:path/2.
|
samer@0
|
231 :- multifile user:demo/1.
|
samer@0
|
232 :- dynamic current_state/2.
|
samer@0
|
233
|
samer@0
|
234
|
samer@0
|
235 %% extensible(+P) is det.
|
samer@0
|
236 % declares 'extensible' predicates, ie ones that can have new clauses
|
samer@0
|
237 % added in other files. Equivalent to dynamic(P), multifile(P).
|
samer@0
|
238 extensible(P) :- dynamic(P), multifile(P).
|
samer@0
|
239
|
samer@0
|
240
|
samer@0
|
241 %% natural(+N) is semidet.
|
samer@0
|
242 %% natural(-N:natural) is multi.
|
samer@0
|
243 %
|
samer@0
|
244 % Means N is a natural number (includes 0). If N is
|
samer@0
|
245 % a variable, succeeds an infinite number of times on backtracking,
|
samer@0
|
246 % returning all natural numbers.
|
samer@0
|
247 natural(N) :- (var(N) -> between(0,inf,N); integer(N), N>=0).
|
samer@0
|
248
|
samer@0
|
249
|
samer@0
|
250 %% int(+N) is semidet.
|
samer@0
|
251 %% int(-N:integer) is multi.
|
samer@0
|
252 %
|
samer@0
|
253 % Means N is an integer. If N is
|
samer@0
|
254 % a variable, succeeds an infinite number of times on backtracking,
|
samer@0
|
255 % returning all integers starting at zero and interleaving positive
|
samer@0
|
256 % and negative values.
|
samer@0
|
257 int(N) :- nonvar(N), integer(N).
|
samer@0
|
258 int(N) :- var(N), (N=0; (between(1,inf,M), (N=M; N is -M))).
|
samer@0
|
259
|
samer@0
|
260
|
samer@0
|
261 %% isfinite(+N:number) is semidet.
|
samer@0
|
262 %
|
samer@0
|
263 % Succeeds when N is a finite number.
|
samer@0
|
264 isfinite(N):- catch(_ is N+0,error(_,_),fail). % !! workable hack
|
samer@0
|
265
|
samer@0
|
266
|
samer@0
|
267 %% in(+X,Set) is semidet.
|
samer@0
|
268 %% in(-X,Set) is nondet.
|
samer@0
|
269 %
|
samer@0
|
270 % Simple testing and enumration of values in some sets.
|
samer@0
|
271 % Set can be
|
samer@0
|
272 % * {A,B,_}
|
samer@0
|
273 % Explicit list of values.
|
samer@0
|
274 % * natural
|
samer@0
|
275 % Natural numbers starting from 0.
|
samer@0
|
276 % * integer
|
samer@0
|
277 % Natural numbers.
|
samer@0
|
278 % * real
|
samer@0
|
279 % Real (floating point) numbers.
|
samer@0
|
280 % * A..B
|
samer@0
|
281 % Integer range from A to B inclusive.
|
samer@0
|
282 % * A--B
|
samer@0
|
283 % Closed interval [A,B].
|
samer@0
|
284 X in A--\B :- X in A--(\B).
|
samer@0
|
285 X in \A--(\B):- !, ch(A<X), ch(X<B).
|
samer@0
|
286 X in \A--B :- !, ch(A<X), ch(X=<B).
|
samer@0
|
287 X in A--(\B) :- !, ch(A=<X), ch(X<B).
|
samer@0
|
288 X in A--B :- !, ch(A=<X), ch(X=<B).
|
samer@0
|
289 X in A..B :- integer(A), integer(B), between(A,B,X).
|
samer@0
|
290 X in {CList} :- member_clist(X,CList).
|
samer@0
|
291 X in natural :- natural(X). % enumerate!
|
samer@0
|
292 X in integer :- int(X). % enumerates!
|
samer@0
|
293 X in real :- number(X). % same as X :: real
|
samer@0
|
294
|
samer@0
|
295
|
samer@0
|
296 ch(_ =<inf) :- !.
|
samer@0
|
297 ch(inf=< _ ) :- !, fail.
|
samer@0
|
298 ch(-inf=< _) :- !.
|
samer@0
|
299 ch(_ =<(-inf)) :- !, fail.
|
samer@0
|
300 ch(A=<B) :- !, A=<B.
|
samer@0
|
301
|
samer@0
|
302 ch(inf<_ ) :- !, fail.
|
samer@0
|
303 ch(_ <inf) :- !.
|
samer@0
|
304 ch(_ <(-inf)) :- !, fail.
|
samer@0
|
305 ch(-inf<_ ) :- !.
|
samer@0
|
306 ch(A<B) :- !, A<B.
|
samer@0
|
307
|
samer@0
|
308
|
samer@0
|
309
|
samer@0
|
310 %% exhaust(:Goal) is det.
|
samer@0
|
311 %
|
samer@0
|
312 % Repeat Goal until failure, then succeed.
|
samer@0
|
313 exhaust(Q) :- call(Q), fail; true.
|
samer@0
|
314
|
samer@0
|
315 %% iterate(+P:pred(A,A), X:A, Y:A) is semidet.
|
samer@0
|
316 % apply P recursively to X until failure, then return final value Y.
|
samer@0
|
317 iterate(P,X,Y) :- call(P,X,Z) -> iterate(P,Z,Y); Y=X.
|
samer@0
|
318
|
samer@0
|
319 %% sfold(Functor,Initial,L:list,Final) is semidet.
|
samer@0
|
320 % *Structural* fold applied to a term,
|
samer@0
|
321 % rather than a relational fold using a predicate name.
|
samer@0
|
322 sfold(_,E,[],E).
|
samer@0
|
323 sfold(O,E,[X|XX],R) :- R=..[O,X,YY], sfold(O,E,XX,YY).
|
samer@0
|
324
|
samer@0
|
325
|
samer@0
|
326 %% dir( +Pattern, -File) is nondet.
|
samer@0
|
327 %
|
samer@0
|
328 % Directory listing for directory matching Pattern. File
|
samer@0
|
329 % names are returned one by one on backtracking.
|
samer@0
|
330 dir(Pattern,File) :-
|
samer@0
|
331 expand_file_name(Pattern,List),
|
samer@0
|
332 member(File,List).
|
samer@0
|
333
|
samer@0
|
334
|
samer@0
|
335 %% path_atom( +Spec:path_expr, -Path:atom) is nondet.
|
samer@0
|
336 %
|
samer@0
|
337 % Expand a 'path expression' into a flat path (an atom).
|
samer@0
|
338 % A path expression is defined by:
|
samer@0
|
339 % ==
|
samer@0
|
340 % path_expr ---> atom % literal path component name
|
samer@0
|
341 % ; path_expr/atom % child of path_expr
|
samer@0
|
342 % ; path_macro % a previously defined abbr for a path.
|
samer@0
|
343 % ==
|
samer@0
|
344 % A path_macro is defined using path/2.
|
samer@0
|
345
|
samer@0
|
346 path_atom(P,C) :- path(P,C), atom(C).
|
samer@0
|
347
|
samer@0
|
348 path_atom(PA/B,C) :-
|
samer@0
|
349 once((nonvar(C); nonvar(B); nonvar(PA))),
|
samer@0
|
350 path_atom(PA,A),
|
samer@0
|
351 concat3atoms(A,'/',B,C).
|
samer@0
|
352
|
samer@0
|
353
|
samer@0
|
354 path_atom(Path,Atom) :- path(Path, Def), \+atom(Def), path_atom(Def,Atom).
|
samer@0
|
355 path_atom(Path,Atom) :-
|
samer@0
|
356 nonvar(Path),
|
samer@0
|
357 \+path(Path,_),
|
samer@0
|
358 Path\=_/_,
|
samer@0
|
359 Atom=Path.
|
samer@0
|
360
|
samer@0
|
361 concat3atoms(A,B,C,ABC) :-
|
samer@0
|
362 nonvar(A), nonvar(B), nonvar(C), !, concat_atom([A,B,C],ABC).
|
samer@0
|
363
|
samer@0
|
364 concat3atoms(_,_,_,ABC) :- var(ABC), !, fail.
|
samer@0
|
365 concat3atoms(A,B,C,ABC) :- nonvar(C), !, atom_concat(AB,C,ABC), atom_concat(A,B,AB).
|
samer@0
|
366 concat3atoms(A,B,C,ABC) :- nonvar(A), !, atom_concat(A,BC,ABC), atom_concat(B,C,BC).
|
samer@0
|
367 concat3atoms(A,B,C,ABC) :-
|
samer@0
|
368 maplist(atom_codes,[B,ABC],[BX,ABCX]),
|
samer@0
|
369 append(ABX,CX,ABCX),
|
samer@0
|
370 append(AX,BX,ABX),
|
samer@0
|
371 maplist(atom_codes,[A,C],[AX,CX]).
|
samer@0
|
372
|
samer@0
|
373 %% expand_path( +P:path_expr, -FP:atom) is semidet.
|
samer@0
|
374 %
|
samer@0
|
375 % Expand path_exp including wildcards to fully qualified path
|
samer@0
|
376 expand_path(P,FP) :- path_atom(P,PP), expand_file_name(PP,[FP]).
|
samer@0
|
377
|
samer@0
|
378
|
samer@0
|
379 %% open_with( +Program:atom, +Thing:path_expr, +Options:list) is semidet.
|
samer@0
|
380 %% open_with( +Program:atom, +Thing:path_expr) is semidet.
|
samer@0
|
381 %
|
samer@0
|
382 % The only option is bg, which adds "&" to make command execute in background.
|
samer@0
|
383 open_with(Q,P) :- open_with(Q,P,[]).
|
samer@0
|
384 open_with(Q,P,Opts) :-
|
samer@0
|
385 expand_path(P,FP),
|
samer@0
|
386 (member(bg,Opts) -> OO=' &'; OO=''),
|
samer@0
|
387 sformat(S,'~w ~q~w',[Q,FP,OO]),
|
samer@0
|
388 shell(S).
|
samer@0
|
389
|
samer@0
|
390 %% open_( +Thing:path_expr) is semidet.
|
samer@0
|
391 % Equivalent to open_with(open,Thing).
|
samer@0
|
392 open_(P) :- open_with(open,P).
|
samer@0
|
393
|
samer@0
|
394 %% shellcmd( +Head:atom, +Args:list(atom)) is det.
|
samer@0
|
395 %
|
samer@0
|
396 % Execute a shell command on a given list of arguments
|
samer@0
|
397 shellcmd(Head,Args) :-
|
samer@0
|
398 concat_atom([Head|Args],' ',Cmd),
|
samer@0
|
399 shell(Cmd,_Status).
|
samer@0
|
400
|
samer@0
|
401 %% fmt_shellcmd( +Prog:atom, +Args:list(shellarg), -Cmd) is det.
|
samer@0
|
402 % make a shell command string.
|
samer@0
|
403 fmt_shellcmd(Prog,Args,Cmd) :-
|
samer@0
|
404 phrase(utils:shellcmd(l_(Args)),FArgs),
|
samer@0
|
405 concat_atom([Prog|FArgs],' ',Cmd).
|
samer@0
|
406
|
samer@0
|
407 shellcmd(l_([])) --> !, [].
|
samer@0
|
408 shellcmd(l_([H|T])) --> !, shellcmd(H), shellcmd(l_(T)).
|
samer@0
|
409 shellcmd(s(N,V)) --> !, shellcmd(s(N)), shellcmd(V).
|
samer@0
|
410 shellcmd(q(X)) --> !, { concat_atom(['"',X,'"'],A) }, [A].
|
samer@0
|
411 shellcmd(s(N)) --> !, {
|
samer@0
|
412 (atom_codes(N,[_]) -> F='-' ; F='--'),
|
samer@0
|
413 atom_concat(F,N,A) }, [A].
|
samer@0
|
414 shellcmd(l(X)) --> [X].
|
samer@0
|
415
|
samer@0
|
416
|
samer@0
|
417
|
samer@0
|
418 %% read_char_echo( -C:atom) is det.
|
samer@0
|
419 %
|
samer@0
|
420 % Read a single character from the current input,
|
samer@0
|
421 % echo it to the output.
|
samer@0
|
422 read_char_echo(C) :-
|
samer@0
|
423 get_single_char(Code),
|
samer@0
|
424 put_code(Code), flush_output,
|
samer@0
|
425 char_code(C,Code).
|
samer@0
|
426
|
samer@0
|
427
|
samer@0
|
428
|
samer@0
|
429 %% set_state( +Key, +Value) is det.
|
samer@0
|
430 %
|
samer@0
|
431 % Maintains a mutable global set of Key-Value pairs, sets the value
|
samer@0
|
432 % associated with Key to Value.
|
samer@0
|
433 set_state(Flag,Value) :-
|
samer@0
|
434 ground(Flag),
|
samer@0
|
435 retractall(current_state(Flag,_)),
|
samer@0
|
436 assert(current_state(Flag,Value)).
|
samer@0
|
437
|
samer@0
|
438
|
samer@0
|
439 %% current_state( -Key, -Value) is nondet.
|
samer@0
|
440 %% current_state( +Key, -Value) is semidet.
|
samer@0
|
441 %
|
samer@0
|
442 % Lookup the value associated with Key, or enumerate all the
|
samer@0
|
443 % key value pairs.
|
samer@0
|
444
|
samer@0
|
445
|
samer@0
|
446
|
samer@0
|
447 %% parallel( +List:list(query)) is semidet.
|
samer@0
|
448 %
|
samer@0
|
449 % Use this by giving a list of queries of the form
|
samer@0
|
450 % [Vars2:Goal, Vars2:Goal2, ...]
|
samer@0
|
451 % where Vars is the term that each thread must return
|
samer@0
|
452 % when it has finished computing its Goal. The
|
samer@0
|
453 % parallel predicate finishes when all the threads
|
samer@0
|
454 % have finished, and should result in all the Vars
|
samer@0
|
455 % being bound appropriately.
|
samer@0
|
456
|
samer@0
|
457 parallel(Queries) :-
|
samer@0
|
458 maplist(async,Queries,Collecters),
|
samer@0
|
459 maplist(call,Collecters).
|
samer@0
|
460
|
samer@0
|
461 % these are used to initiate and wait for each
|
samer@0
|
462 % computation thread.
|
samer@0
|
463 async_collect(Id,X:_) :- thread_join(Id,exited(X)).
|
samer@0
|
464 async(X:Goal,utils:async_collect(Id,X:_)) :-
|
samer@0
|
465 thread_create((Goal,thread_exit(X)),Id,[]).
|
samer@0
|
466
|
samer@0
|
467 %% browse( +PredSpec, -Goal) is nondet.
|
samer@0
|
468 %
|
samer@0
|
469 % PredSpec is a term like (PredicateName/Arity). Goal
|
samer@0
|
470 % is unified with solutions of PredicateName/Arity.
|
samer@0
|
471 browse(P/A,Goal) :-
|
samer@0
|
472 current_predicate(P/A),
|
samer@0
|
473 length(L,A),
|
samer@0
|
474 Goal=..[P|L],
|
samer@0
|
475 call(Goal).
|
samer@0
|
476
|
samer@0
|
477
|
samer@0
|
478
|
samer@0
|
479 %% aphrase(P:phrase(code), -A:atom, +S:list(code)) is nondet.
|
samer@0
|
480 %% aphrase(P:phrase(code), +A:atom, -S:list(code)) is nondet.
|
samer@0
|
481 %% aphrase(P:phrase(code), -A:atom, -S:list(code)) is nondet.
|
samer@0
|
482 %% aphrase(P:phrase(code), -A:atom) is nondet.
|
samer@0
|
483 %
|
samer@0
|
484 % Generate or parse an atom using given DCG phrase P.
|
samer@0
|
485 % aphrase(P,A) is equivalent to aphrase(P,A,_).
|
samer@0
|
486 aphrase(X,A) :- aphrase(X,A,_).
|
samer@0
|
487 aphrase(X,A,S) :-
|
samer@0
|
488 ( ground(A)
|
samer@0
|
489 -> atom_codes(A,S), phrase(X,S)
|
samer@0
|
490 ; phrase(X,S), atom_codes(A,S)).
|
samer@0
|
491
|
samer@0
|
492
|
samer@0
|
493 %% print_list( +L:list) is det.
|
samer@0
|
494 %
|
samer@0
|
495 % Print a list, one item per line.
|
samer@0
|
496 print_list([]) :- writeln('~'), nl.
|
samer@0
|
497 print_list([H|T]) :- print(H), nl, print_list(T).
|
samer@0
|
498
|
samer@0
|
499 %% printq_list( +L:list) is det.
|
samer@0
|
500 %
|
samer@0
|
501 % Print a list, one item per line, as with writeq/1.
|
samer@0
|
502 printq_list([]) :- writeln('~'), nl.
|
samer@0
|
503 printq_list([H|T]) :- writeq(H), nl, printq_list(T).
|
samer@0
|
504
|
samer@0
|
505 %% print_numbered_list( +L:list) is det.
|
samer@0
|
506 %
|
samer@0
|
507 % Print a list with numbered lines.
|
samer@0
|
508 print_numbered_list(L) :-
|
samer@0
|
509 length(L,Max),
|
samer@0
|
510 number_codes(Max,MC),
|
samer@0
|
511 length(MC,Width),
|
samer@0
|
512 print_num_list(Width,1,L).
|
samer@0
|
513
|
samer@0
|
514 print_num_list(_,_,[]) :- nl.
|
samer@0
|
515 print_num_list(Width,N,[H|T]) :- succ(N,M),
|
samer@0
|
516 copy_term(H,H1),
|
samer@0
|
517 numbervars(H1,0,_),
|
samer@0
|
518 number_codes(N,NC), " "=[Pad],
|
samer@0
|
519 padleft(Pad,Width,NC,PNC),
|
samer@0
|
520 format('~s. ~q\n',[PNC,H1]),
|
samer@0
|
521 print_num_list(Width,M,T).
|
samer@0
|
522
|
samer@0
|
523 padleft(_,W,In,In) :- length(In,W).
|
samer@0
|
524 padleft(P,W,In,[P|Out]) :- succ(V,W), padleft(P,V,In,Out).
|
samer@0
|
525
|
samer@0
|
526
|
samer@0
|
527
|
samer@0
|
528
|
samer@0
|
529 %% get_key( +Valid:list(char), -C:char) is det.
|
samer@0
|
530 %
|
samer@0
|
531 % Get and validate a key press from the user. The character
|
samer@0
|
532 % must be one of the ones listed in Valid, otherwise, an
|
samer@0
|
533 % error message is printed and the user prompted again.
|
samer@0
|
534 get_key(Valid,C) :-
|
samer@0
|
535 read_char_echo(D), nl,
|
samer@0
|
536 ( member(D,Valid) -> C=D
|
samer@0
|
537 ; D='\n' -> get_key(Valid,C) % this improves interaction with acme
|
samer@0
|
538 ; format('Unknown command "~q"; valid keys are ~q.\n', [D,Valid]),
|
samer@0
|
539 write('Command? '),
|
samer@0
|
540 get_key(Valid,C)).
|
samer@0
|
541
|
samer@0
|
542
|
samer@0
|
543 %% userchk(T) is semidet.
|
samer@0
|
544 %
|
samer@0
|
545 % Write T and ask this user if it is ok. User presses y or n.
|
samer@0
|
546 % userchk succeeds if if the keypress was y and fails if it was n.
|
samer@0
|
547 userchk(T) :- prompt_for_key(T,[y,n],y).
|
samer@0
|
548
|
samer@0
|
549
|
samer@0
|
550 %% prompt_for_key( +Msg:atom, +Keys:list(char), -Key:char) is semidet.
|
samer@0
|
551 %
|
samer@0
|
552 % Prompt user for a keypress. Prompt message is Msg, and valid keys are
|
samer@0
|
553 % listed in Keys.
|
samer@0
|
554 prompt_for_key(Msg,Keys,Key) :- format('~p ~q? ',[Msg,Keys]), get_key(Keys,Key).
|
samer@0
|
555
|
samer@0
|
556 % ------------------- TERM MANIPULATION ------------------------------
|
samer@0
|
557
|
samer@0
|
558
|
samer@0
|
559 %% copy_head(+T1,-T2) is det.
|
samer@0
|
560 %% copy_head(+T1,+T2) is semidet.
|
samer@0
|
561 %
|
samer@0
|
562 % true if T1 and T2 have the same head and arity
|
samer@0
|
563 copy_head(T1,T2) :- functor(T1,N,A), functor(T2,N,A).
|
samer@0
|
564
|
samer@0
|
565
|
samer@0
|
566
|
samer@0
|
567 %% reinstatevars( F:atom, V:list, Eh, What) is nondet.
|
samer@0
|
568 %% reinstatevars( V:list, Eh, What) is nondet.
|
samer@0
|
569 %
|
samer@0
|
570 % Reverse of numbervars. Each '$VAR'(N) subterm of X is replaced
|
samer@0
|
571 % with the Nth element of V, which can be uninstantiated on entry
|
samer@0
|
572 % reinstatevars/4 uses an arbitrary functor F instead of $VAR.
|
samer@0
|
573
|
samer@0
|
574 reinstatevars(V,'$VAR'(N),Y) :- !, nth0(N,V,Y).
|
samer@0
|
575 reinstatevars(_,X,Y) :- atomic(X), !, Y=X.
|
samer@0
|
576 reinstatevars(V,X,Y) :- mapargs(reinstatevars(V),X,Y).
|
samer@0
|
577
|
samer@0
|
578 reinstatevars(F,V,T,Y) :- functor(T,F,1), !, arg(1,T,N), nth0(N,V,Y).
|
samer@0
|
579 reinstatevars(_,_,X,Y) :- atomic(X), !, Y=X.
|
samer@0
|
580 reinstatevars(F,V,X,Y) :- mapargs(reinstatevars(F,V),X,Y).
|
samer@0
|
581
|
samer@0
|
582
|
samer@0
|
583 %% unify_args( Src, SrcIndex, Dest, DestIndex, Num) is det.
|
samer@0
|
584 %
|
samer@0
|
585 % this unifies N consecutive arguments of Src and Dest starting
|
samer@0
|
586 % from SI and DI in each term respectively
|
samer@0
|
587 unify_args(_,_,_,_,0).
|
samer@0
|
588 unify_args(Src,SI,Dest,DI,N) :-
|
samer@0
|
589 arg(SI,Src,X), arg(DI,Dest,X), !,
|
samer@0
|
590 succ(SI,SI2), succ(DI,DI2), succ(N2,N),
|
samer@0
|
591 unify_args(Src,SI2,Dest,DI2,N2).
|
samer@0
|
592
|
samer@0
|
593
|
samer@0
|
594 % ---------------------- LIST UTILITIES -----------------------------
|
samer@0
|
595
|
samer@0
|
596
|
samer@0
|
597 %member_clist(_,Z) :- var(Z), !, fail.
|
samer@0
|
598 member_clist(A,A) :- A\=(_,_).
|
samer@0
|
599 member_clist(A,(A,_)).
|
samer@0
|
600 member_clist(A,(_,B)) :- member_clist(A,B).
|
samer@0
|
601
|
samer@0
|
602
|
samer@0
|
603
|
samer@0
|
604 %% measure(Ruler,In,Out) is det.
|
samer@0
|
605 % true if Out is the same length as Ruler but matches In as far as possible
|
samer@0
|
606 measure([],_I,[]).
|
samer@0
|
607 measure([_|R],[],[_|O]) :- measure(R,[],O).
|
samer@0
|
608 measure([_|R],[X|I],[X|O]) :- measure(R,I,O).
|
samer@0
|
609
|
samer@0
|
610 %% equal_length( ?In, ?Out) is nondet.
|
samer@0
|
611 % equal_length( +L1:list, -L2:list) is det.
|
samer@0
|
612 % equal_length( -L1:list, +L2:list) is det.
|
samer@0
|
613 %
|
samer@0
|
614 % True if L1 and L2 are the same length.
|
samer@0
|
615 equal_length([],[]).
|
samer@0
|
616 equal_length([_|T1],[_|T2]) :- equal_length(T1,T2).
|
samer@0
|
617
|
samer@0
|
618 %split_at(0,T,I-I,T).
|
samer@0
|
619 %split_at(N,[H|T],[H|I1]-Z,T1) :- succ(M,N), split_at(M,T,I1-Z,T1).
|
samer@0
|
620
|
samer@0
|
621 %split_at2(0,T,I-I,T).
|
samer@0
|
622 %split_at2(N,[H|T],[H|I1]-Z,T1) :- split_at2(M,T,I1-Z,T1), succ(M,N).
|
samer@0
|
623
|
samer@0
|
624 %% max(+X:number, +Y:number, -Z:number) is det.
|
samer@0
|
625 %
|
samer@0
|
626 % Unify Z with the larger of X and Y. Legal values are
|
samer@0
|
627 % any numerical value or inf or -inf.
|
samer@0
|
628 max(_,inf,inf) :- !.
|
samer@0
|
629 max(inf,_,inf) :- !.
|
samer@0
|
630 max(X,-inf,X) :- !.
|
samer@0
|
631 max(-inf,X,X) :- !.
|
samer@0
|
632 max(X,Y,Z) :- X<Y -> Z=Y; Z=X.
|
samer@0
|
633
|
samer@0
|
634 %% max(+X:number, +Y:number, -Z:number) is det.
|
samer@0
|
635 %
|
samer@0
|
636 % Unify Z with the larger of X and Y. Legal values are
|
samer@0
|
637 % any numerical value or inf or -inf.
|
samer@0
|
638 min(_,-inf,-inf) :- !.
|
samer@0
|
639 min(-inf,_,-inf) :- !.
|
samer@0
|
640 min(X,inf,X) :- !.
|
samer@0
|
641 min(inf,X,X) :- !.
|
samer@0
|
642 min(X,Y,Z) :- X<Y -> Z=X; Z=Y.
|
samer@0
|
643
|
samer@0
|
644 %% list_idx1_member( +L:list(A), +N:natural, ?X:A) is semidet.
|
samer@0
|
645 %% list_idx1_member( ?L:list(A), ?N:natural, ?X:A) is nondet.
|
samer@0
|
646 %
|
samer@0
|
647 % Equivalent to nth1(N,L,X).
|
samer@0
|
648 list_idx1_member(L,I,X) :- nth1(I,L,X).
|
samer@0
|
649
|
samer@0
|
650
|
samer@0
|
651 %% getopts( +Opts:list(option), ?Spec:list(optspec)) is det.
|
samer@0
|
652 %
|
samer@0
|
653 % Get value from option list.
|
samer@0
|
654 % ==
|
samer@0
|
655 % option(A) ---> term(A).
|
samer@0
|
656 % optspec ---> option(A)/A.
|
samer@0
|
657 % ==
|
samer@0
|
658 getopts(OptsIn,Spec) :- maplist(getopt(OptsIn),Spec).
|
samer@0
|
659 getopt(OptsIn,Option/Default) :- option(Option,OptsIn,Default).
|
samer@0
|
660
|
samer@0
|
661 %% cons( ?Head:A, ?Tail:list(A), ?List:list(A)) is det.
|
samer@0
|
662 %
|
samer@0
|
663 % List constructor.
|
samer@0
|
664 cons(H,T,[H|T]).
|
samer@0
|
665
|
samer@0
|
666 %% decons( ?Head:A, ?List:list(A), ?Tail:list(A)) is det.
|
samer@0
|
667 %
|
samer@0
|
668 % List deconstructor.
|
samer@0
|
669 decons(H,[H|T],T).
|
samer@0
|
670
|
samer@0
|
671 % ---------------------- MAPPING, HIGH ORDER STUFF ---------------------
|
samer@0
|
672
|
samer@0
|
673 %% for_naturals(+N:natural, P:pred(natural)) is nondet.
|
samer@0
|
674 % apply predicate to each natural number from 1 to N (backwards)
|
samer@0
|
675 for_naturals(0,_).
|
samer@0
|
676 for_naturals(N,P) :- succ(M,N), call(P,N), for_naturals(M,P).
|
samer@0
|
677
|
samer@0
|
678 %% mapints( +P:pred(integer,A), +R:intrange, -X:list) is nondet.
|
samer@0
|
679 %% mapints( +P:pred(integer), +R:intrange) is nondet.
|
samer@0
|
680 %
|
samer@0
|
681 % Mapping predicates over lists of integers. Range is like M..N.
|
samer@0
|
682 % mapints/3 maps 2 argument predicate over implicit list of
|
samer@0
|
683 % integers M..N and explicit list of values X.
|
samer@0
|
684 mapints(_,M..N) :- N<M, !.
|
samer@0
|
685 mapints(P,M..N) :- call(P,M), plus(M,1,L), mapints(P,L..N).
|
samer@0
|
686
|
samer@0
|
687 mapints(_,M..N,[]) :- N<M, !.
|
samer@0
|
688 mapints(P,M..N,[X|T]) :- call(P,M,X), plus(M,1,L), mapints(P,L..N,T).
|
samer@0
|
689
|
samer@0
|
690 %% rep( +N:natural, ?X:A, -L:list(A)) is det.
|
samer@0
|
691 %% rep( -N:natural, ?X:A, -L:list(A)) is multi.
|
samer@0
|
692 % Make a list consisting of N repeats of the same term. If called
|
samer@0
|
693 % with N unbount, creates progressively longer and longer lists
|
samer@0
|
694 % on backtracking.
|
samer@0
|
695 rep(0,_,[]).
|
samer@0
|
696 rep(N,A,[A|X]) :-
|
samer@0
|
697 ( nonvar(N)
|
samer@0
|
698 -> succ(M,N), rep(M,A,X)
|
samer@0
|
699 ; rep(M,A,X), succ(M,N)
|
samer@0
|
700 ).
|
samer@0
|
701
|
samer@0
|
702 %% mapargs( P:pred(A,B,C), T1:tuple(F,A), T2:tuple(F,B), T3:tuple(F,C)) is nondet.
|
samer@0
|
703 %% mapargs( P:pred(A,B), T1:tuple(F,A), T2:tuple(F,B)) is nondet.
|
samer@0
|
704 %% mapargs( P:pred(A), T1:term) is nondet.
|
samer@0
|
705 %
|
samer@0
|
706 % Map predicate over to args of a term preserving head.
|
samer@0
|
707 % A tuple(F,A) is a term with head functor F and any number of arguments
|
samer@0
|
708 % of type A, ie
|
samer@0
|
709 % ==
|
samer@0
|
710 % tuple(F,A) ---> F ; F(A) ; F(A,A) ; F(A,A,A) ; .. .
|
samer@0
|
711 % ==
|
samer@0
|
712
|
samer@0
|
713 mapargs(P,T1) :-
|
samer@0
|
714 functor(T1,_,N),
|
samer@0
|
715 mapargs_x(1,N,P,T1).
|
samer@0
|
716
|
samer@0
|
717 mapargs(P,T1,T2) :-
|
samer@0
|
718 ( nonvar(T1)
|
samer@0
|
719 -> functor(T1,F,N), functor(T2,F,N)
|
samer@0
|
720 ; functor(T2,F,N), functor(T1,F,N)),
|
samer@0
|
721 mapargs_x(1,N,P,T1,T2).
|
samer@0
|
722
|
samer@0
|
723 mapargs(P,T1,T2,T3) :-
|
samer@0
|
724 functor(T1,F,N),
|
samer@0
|
725 functor(T2,F,N),
|
samer@0
|
726 functor(T3,F,N),
|
samer@0
|
727 mapargs_x(1,N,P,T1,T2,T3).
|
samer@0
|
728
|
samer@0
|
729 mapargs_x(I,N,P,T1) :-
|
samer@0
|
730 ( I>N -> true
|
samer@0
|
731 ; arg(I,T1,X1),
|
samer@0
|
732 call(P,X1),
|
samer@0
|
733 succ(I,J), mapargs_x(J,N,P,T1)).
|
samer@0
|
734
|
samer@0
|
735 mapargs_x(I,N,P,T1,T2) :-
|
samer@0
|
736 ( I>N -> true
|
samer@0
|
737 ; arg(I,T1,X1),
|
samer@0
|
738 arg(I,T2,X2),
|
samer@0
|
739 call(P,X1,X2),
|
samer@0
|
740 succ(I,J), mapargs_x(J,N,P,T1,T2)).
|
samer@0
|
741
|
samer@0
|
742 mapargs_x(I,N,P,T1,T2,T3) :-
|
samer@0
|
743 ( I>N -> true
|
samer@0
|
744 ; arg(I,T1,X1),
|
samer@0
|
745 arg(I,T2,X2),
|
samer@0
|
746 arg(I,T3,X3),
|
samer@0
|
747 call(P,X1,X2,X3),
|
samer@0
|
748 succ(I,J), mapargs_x(J,N,P,T1,T2,T3)).
|
samer@0
|
749
|
samer@0
|
750 %% drop( +N:natural, +In:list(A), -Out:list(A)) is det.
|
samer@0
|
751 drop(0,T,T).
|
samer@0
|
752 drop(N,[_|T],V) :- succ(M,N), drop(M,T,V).
|
samer@0
|
753
|
samer@0
|
754
|
samer@0
|
755 %% take( +N:natural, +In:list(A), -Out:list(A)) is det.
|
samer@0
|
756 take(N,T,X) :- length(X,N), append(X,_,T).
|
samer@0
|
757
|
samer@0
|
758
|
samer@0
|
759 %% drop_while( +P:pred(A), +In:list(A), -Out:list(A)) is det.
|
samer@0
|
760 %
|
samer@0
|
761 % Remove all elements from head of In that are accepted by P
|
samer@0
|
762 % and return the remained in Out.
|
samer@0
|
763 drop_while(P,[X|T],V) :- call(P,X) -> drop_while(P,T,V); V=[X|T].
|
samer@0
|
764
|
samer@0
|
765
|
samer@0
|
766 %% take_while( +P:pred(A), +In:list(A), -Out:list(A)) is det.
|
samer@0
|
767 %
|
samer@0
|
768 % Remove all elements from head of In that are accepted by P
|
samer@0
|
769 % and return them in Out.
|
samer@0
|
770 take_while(P,[X|T],O) :- call(P,X) -> O=[X|V], take_while(P,T,V); O=[].
|
samer@0
|
771
|
samer@0
|
772
|
samer@0
|
773
|
samer@0
|
774 %% retry( :Goal) is det.
|
samer@0
|
775 %
|
samer@0
|
776 % Keep retrying Goal until it succeeds. Only makes sense if Goal
|
samer@0
|
777 % has side effects. Might be nonterminating.
|
samer@0
|
778 retry(G) :- once((repeat,G)).
|
samer@0
|
779
|
samer@0
|
780 %% apply_to_nth1( N:natural, Op:pred(A,A), +In:list(A), +Out:list(A)) is nondet.
|
samer@0
|
781 %
|
samer@0
|
782 % Apply predicate Op to the N th element of list In and unify Out with the result.
|
samer@0
|
783 %apply_to_nth1(N,Op,Old,Init) :-
|
samer@0
|
784 % ( nonvar(N)
|
samer@0
|
785 % -> succ(M,N), split_at(M,Old,Init-[Y|Tail],[X|Tail])
|
samer@0
|
786 % ; split_at2(M,Old,Init-[Y|Tail],[X|Tail]), succ(M,N)
|
samer@0
|
787 % ),
|
samer@0
|
788 % call(Op,X,Y).
|
samer@0
|
789
|
samer@0
|
790 apply_to_nth1(1,P,[X|XX],[Y|XX]) :- call(P,X,Y).
|
samer@0
|
791 apply_to_nth1(N,P,[X|X1],[X|Y1]) :- nonvar(N), !, N>1, succ(M,N), apply_to_nth1(M,P,X1,Y1).
|
samer@0
|
792 apply_to_nth1(N,P,[X|X1],[X|Y1]) :- var(N), !, apply_to_nth1(M,P,X1,Y1), succ(M,N).
|
samer@0
|
793
|
samer@0
|
794
|
samer@0
|
795 %% mapargs_xx( +P:pred(A,B), +Src:term(_,A), +SrcIndex:natural, +Dest:term(_,B), +DestIndex:natural, +N:natural) is nondet.
|
samer@0
|
796 %
|
samer@0
|
797 % Maps predicate P over N consecutive arguments of Src and Dest. Starts
|
samer@0
|
798 % at SrcIndex th argument of Src and DestIndex th argument of Dest.
|
samer@0
|
799 mapargs_xx(_,_,_,_,_,0).
|
samer@0
|
800 mapargs_xx(Pred,Src,SI,Dest,DI,N) :-
|
samer@0
|
801 arg(SI,Src,SX), arg(DI,Dest,DX), call(Pred,SX,DX), !,
|
samer@0
|
802 succ(SI,SI2), succ(DI,DI2), succ(N2,N),
|
samer@0
|
803 mapargs_xx(Pred,Src,SI2,Dest,DI2,N2).
|
samer@0
|
804
|
samer@0
|
805
|
samer@0
|
806 %% mcall(P:pred(A), X:A) is nondet.
|
samer@0
|
807 %% mcall(P:pred(A,B), X:A, Y:B) is nondet.
|
samer@0
|
808 %% mcall(P:pred(A,B,C), X:A, Y:B, Z:C) is nondet.
|
samer@0
|
809 %% mcall(P:pred(A,B,C,D), X:A, Y:B, Z:C, W:D) is nondet.
|
samer@0
|
810 %
|
samer@0
|
811 % Like call/N but P can additionally be a lambda expression in one of several
|
samer@0
|
812 % forms:
|
samer@0
|
813 % * Tuple :- Body
|
samer@0
|
814 % If functor(Tuple,\,N), Body is executed after unifying tuple arguments
|
samer@0
|
815 % with arguments to mcall, eg =mcall(\(X):-member(X,[a,b,c]),Y)= is equivalent
|
samer@0
|
816 % to member(Y,[a,b,c]), or =mcall(\(X,Y):-nth1(X,[a,b,c],Y),2,c)=.
|
samer@0
|
817 % * Tuple
|
samer@0
|
818 % Equivalent to Tuple:-true.
|
samer@0
|
819
|
samer@0
|
820 mcall(P,A) :- mc(P,\(A),Q), Q.
|
samer@0
|
821 mcall(P,A,B) :- mc(P,\(A,B),Q), Q.
|
samer@0
|
822 mcall(P,A,B,C) :- mc(P,\(A,B,C),Q), Q.
|
samer@0
|
823 mcall(P,A,B,C,D) :- mc(P,\(A,B,C,D),Q), Q.
|
samer@0
|
824
|
samer@0
|
825 mc(Tuple:-Body,Params,Goal) :- !, copy_term(Tuple/Body,Params/Goal).
|
samer@0
|
826 mc(Tuple,Params,true) :- functor(Tuple,\,_), !, copy_term(Tuple,Params).
|
samer@0
|
827 mc(P,Params,apply(P,Args)) :- Params=..[\|Args].
|
samer@0
|
828
|
samer@0
|
829
|
samer@0
|
830 %% on_backtracking( :Goal) is det.
|
samer@0
|
831 %
|
samer@0
|
832 % The first time this is called, it succeeds and does nothing.
|
samer@0
|
833 % On backtracking, Goal is called and then a failure is generated.
|
samer@0
|
834
|
samer@0
|
835 on_backtracking(_).
|
samer@0
|
836 on_backtracking(P) :- P, !, fail.
|
samer@0
|
837
|
samer@0
|
838
|
samer@0
|
839 %% bt_call( :Do, :Undo) is nondet.
|
samer@0
|
840 %
|
samer@0
|
841 % Creates a backtrackable operation from a non-backtrackable Do
|
samer@0
|
842 % operation and a corresponding operation to undo it. Do can
|
samer@0
|
843 % be non-deterministic, in which case bt_call(Do,Undo) will also
|
samer@0
|
844 % have multiple solutions. Undo is called inside once/1.
|
samer@0
|
845 %
|
samer@0
|
846 % bt_call/2 is implemented both as a predicate and as a goal
|
samer@0
|
847 % expansion (see goal_expansion/2).
|
samer@0
|
848 bt_call(Do,Undo) :- Do, (true; once(Undo), fail).
|
samer@0
|
849
|
samer@0
|
850 user:goal_expansion( bt_call(Do,Undo), (Do, (true; once(Undo), fail))).
|
samer@0
|
851
|
samer@0
|
852
|
samer@0
|
853
|
samer@0
|
854 /* Might include these at some point
|
samer@0
|
855
|
samer@0
|
856 % apply lambda term to another term
|
samer@0
|
857 app(X\\F,Y,G) :- !, copy_term(X\\F,Y\\G).
|
samer@0
|
858 app(T,A,Z) :- addargs(T,[A],Z).
|
samer@0
|
859 app(T,A,B,Z) :- addargs(T,[A,B],Z).
|
samer@0
|
860 app(T,A,B,C,Z) :- addargs(T,[A,B,C],Z).
|
samer@0
|
861
|
samer@0
|
862 applist(F,N,A,Z) :- length(Z,N), maplist(app(F),A,Z).
|
samer@0
|
863 applist(F,N,A,B,Z) :- length(Z,N), maplist(app(F),A,B,Z).
|
samer@0
|
864 applist(F,N,A,B,C,Z) :- length(Z,N), maplist(app(F),A,B,C,Z).
|
samer@0
|
865
|
samer@0
|
866 */
|
samer@0
|
867
|
samer@0
|
868
|
samer@0
|
869 % ------------------ DATABASE ------------------------------
|
samer@0
|
870
|
samer@0
|
871 %% bt_assert(Clause) is det.
|
samer@0
|
872 % Backtrackable assert.
|
samer@0
|
873 bt_assert(H) :- bt_call(assert(H),retract(H)).
|
samer@0
|
874
|
samer@0
|
875 %% bt_retract(Clause) is det.
|
samer@0
|
876 % Backtrackable retract.
|
samer@0
|
877 bt_retract(H) :- bt_call(retract(H), assert(H)).
|
samer@0
|
878
|
samer@0
|
879 %% strict_assert(Fact) is semidet.
|
samer@0
|
880 %
|
samer@0
|
881 % Asserts fact only if it is not already true. Fails
|
samer@0
|
882 % if fact is already provable. Retracts fact on backtracking.
|
samer@0
|
883 strict_assert(H) :- \+call(H), bt_call(assert(H),retract(H)).
|
samer@0
|
884
|
samer@0
|
885
|
samer@0
|
886 %% strict_retract(Fact) is semidet.
|
samer@0
|
887 %
|
samer@0
|
888 % Retracts fact only if it is currently in the database. Fails
|
samer@0
|
889 % if fact is not provable. Reasserts fact on backtracking.
|
samer@0
|
890 strict_retract(H) :- call(H), bt_call(retract(H), assert(H)).
|
samer@0
|
891
|
samer@0
|
892
|
samer@0
|
893 % when loaded, this sets the hostname/1 predicate.
|
samer@0
|
894 :- dynamic hostname/1.
|
samer@0
|
895
|
samer@0
|
896 %% hostname( -A:atom) is det.
|
samer@0
|
897 %
|
samer@0
|
898 % Unifies A with the computer's hostname. This is set when the
|
samer@0
|
899 % module is loaded by calling the system command 'hostname -s'.
|
samer@0
|
900
|
samer@0
|
901 % init_hostname is det - read hostname from UNIX command hostname.
|
samer@0
|
902 init_hostname :-
|
samer@0
|
903 setup_call_cleanup(
|
samer@0
|
904 open(pipe('hostname -s'),read,SID),
|
samer@0
|
905 (read_line_to_codes(SID,C), atom_codes(H,C), retractall(hostname(_)), assert(hostname(H))),
|
samer@0
|
906 close(SID)).
|
samer@0
|
907
|
samer@0
|
908 :- ( hostname(H)
|
samer@0
|
909 -> format('% hostname already set to ~w\n',[H])
|
samer@0
|
910 ; init_hostname, hostname(H), format('% hostname set to ~w\n',[H])
|
samer@0
|
911 ).
|
samer@0
|
912
|
samer@0
|
913 % Comma lists
|
samer@0
|
914 % ie, lists built up using (,) as a pairing functor
|
samer@0
|
915 % Note, these functor lists do NOT have a nil element - the
|
samer@0
|
916 % last item in the list is the 2nd argument to the final
|
samer@0
|
917 % functor term, which can therefore be a term headed by any
|
samer@0
|
918 % other functor. Eg:
|
samer@0
|
919 % (1,(2,3)) <-> [1,2,3]
|
samer@0
|
920 % (1,(2,(3+4)) <-> [1,2,(3+4)]
|
samer@0
|
921
|
samer@0
|
922 %% cl_list( +CL:clist(A), -L:list(A)) is det.
|
samer@0
|
923 %% cl_list( -CL:clist(A), +L:list(A)) is det.
|
samer@0
|
924 %
|
samer@0
|
925 % Convert between comma lists and ordinary lists
|
samer@0
|
926 cl_list((A,B),[A|BL]) :- cl_list(B,BL).
|
samer@0
|
927 cl_list(A,[A]) :- A\=(_,_).
|
samer@0
|
928
|
samer@0
|
929 %% cl_length( +L:clist, -N:natural) is det.
|
samer@0
|
930 %% cl_length( -L:clist, +N:natural) is det.
|
samer@0
|
931 %
|
samer@0
|
932 % Length of a comma-list.
|
samer@0
|
933 cl_length((_,B),N) :- cl_length(B,M), succ(M,N).
|
samer@0
|
934 cl_length(X,1) :- X\=(_,_).
|
samer@0
|
935
|
samer@0
|
936
|
samer@0
|
937 %% cl_list_vt( +CL:clist(A), -L:list(A)) is det.
|
samer@0
|
938 %% cl_list_vt( -CL:clist(A), +L:list(A)) is det.
|
samer@0
|
939 %
|
samer@0
|
940 % Convert between comma lists (with open tails) and ordinary lists.
|
samer@0
|
941 cl_list_vt(FL,[FL]) :- var(FL), !.
|
samer@0
|
942 cl_list_vt(FL,[A|BL]) :- FL = (A,B), cl_list_vt(B,BL).
|
samer@0
|
943 cl_list_vt(A,[A]) :- A\=(_,_).
|
samer@0
|
944
|
samer@0
|
945
|
samer@0
|
946 %% cl_length_vt( +L:clist, -N:natural) is det.
|
samer@0
|
947 %% cl_length_vt( -L:clist, +N:natural) is det.
|
samer@0
|
948 %
|
samer@0
|
949 % Length of a comma-list with possible variable tail.
|
samer@0
|
950 % This version handles lists where the last element is variable (counts as 1)
|
samer@0
|
951 cl_length_vt(FL,1) :- var(FL), !.
|
samer@0
|
952 cl_length_vt(FL,N) :- FL=(_,B), cl_length_vt(B,M), succ(M,N).
|
samer@0
|
953 cl_length_vt(FL,1) :- FL\=(_,_).
|
samer@0
|
954
|
samer@0
|
955 %% cl_member(-X, +L:clist) is nondet.
|
samer@0
|
956 % List membership for comma lists.
|
samer@0
|
957 cl_member(X,(X,_)).
|
samer@0
|
958 cl_member(X,(_,T)) :- cl_member(X,T).
|
samer@0
|
959 cl_member(X,X) :- X\=(_,_).
|
samer@0
|
960
|