1:- module(callutils, [ (*)/4, (*)//4, (*:)//3
2 , const/3 , constf//3
3 , pairf//3
4 , mr/5
5 , op(600,yfx,*:)
6 , flip/3
7 , true2/2, true1/1
8 , fail2/2, fail1/1
9 , call_with_time_limit//2
10 , timeout/3, timeout//3
11 , timeout_retry//3
12 , bt_call/2
13 ]).
22:- meta_predicate *(2,2,?,?)
23 , *(4,4,?,?,?,?)
24 , constf(3,?,?,?,?)
25 , pairf(3,3,?,?,?)
26 , mr(2,3,?,?,?)
27 , flip(2,?,?)
.
32flip(P,X,Y) :- call(P,Y,X).
38*(P,Q,X,Z) --> call(Q,X,Y), call(P,Y,Z).
39*(P,Q,X,Z) :- call(Q,X,Y), call(P,Y,Z).
43*:(P,G,Y) --> call(G,X), call(P,X,Y).
47const(X,_,X).
51pairf(F,G,X-Y) --> call(F,X), call(G,Y).
55constf(F,_,X) --> call(F,X).
59mr(M,R,X,S1,S2) :- call(M,X,Y), call(R,Y,S1,S2).
60
61user:goal_expansion(*(P,Q,X,Z), (call(Q,X,Y), call(P,Y,Z))) :-
62 nonvar(P), nonvar(Q).
63
64user:goal_expansion(G1, G2) :-
65 G1 =.. [call, Closure |Args],
66 nonvar(Closure), expand_call(Closure, Args, G2).
67
68expand_call(Mod:Head, Args, Mod:G) :- !,
69 nonvar(Head), expand_call(Head, Args, G).
70expand_call(Head, Args, G) :-
71 Head =.. [Pred|Bound],
72 append(Bound, Args, AllArgs),
73 G =.. [Pred | AllArgs].
74
75true1(_).
76true2(_,_).
77fail1(_) :- fail.
78fail2(_,_) :- fail.
79
80:- meta_predicate call_with_time_limit(+,//,?,?). 81call_with_time_limit(T,G,S1,S2) :-
82 call_with_time_limit(T,call_dcg(G,S1,S2)).
83
84:- meta_predicate timeout(+,0,0). 85timeout(T,G,R) :-
86 catch(call_with_time_limit(T,G),
87 time_limit_exceeded, R).
88
89:- meta_predicate timeout(+,//,//,?,?). 90timeout(T,G,R,S1,S2) :-
91 timeout(T, call_dcg(G,S1,S2), call_dcg(R,S1,S2)).
92
93:- meta_predicate timeout_retry(+,//,//,?,?). 94timeout_retry(T,G,R) -->
95 timeout(T,G,(R, timeout_retry(T,G,R))).
105:- meta_predicate bt_call(0,0). 106bt_call(Do,Undo) :-
107 debug(bt_call,'doing: ~p.\n',[Do]),
108 Do,
109 ( true
110 ; debug(bt_call,'undoing: ~p.\n',[Undo]),
111 once(Undo), fail
112 )
High-order utility predicates
Some high-order predicates to enable high-order 'point-free' and lambda free composition of predicates. Also provides a goal expansion for call/N when the target predicate is already known. */