Skip to content

Commit bfd52f9

Browse files
committed
Adapt original reif.pl
1 parent 62285ea commit bfd52f9

File tree

1 file changed

+38
-31
lines changed

1 file changed

+38
-31
lines changed

src/lib/reif.pl

Lines changed: 38 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111
tfilter/3,
1212
tpartition/4
1313
%
14-
], [hidden(true)]).
14+
]).
1515
%
1616
%
1717
%
@@ -23,16 +23,7 @@
2323
U. Neumerkel and S. Kral. https://arxiv.org/abs/1607.01590 [cs.PL]. July 2016.
2424
*/
2525

26-
27-
:- meta_predicate
28-
if_(1, 0, 0),
29-
cond_t(1, 0, ?),
30-
tfilter(2, ?, ?),
31-
tpartition(2, ?, ?, ?),
32-
','(1, 1, ?),
33-
;(1, 1, ?),
34-
tmember(2, ?),
35-
tmember_t(2, ?, ?).
26+
:- use_module(library(dif)).
3627

3728
:- op(900, fy, [$]).
3829

@@ -102,7 +93,7 @@
10293
*/
10394

10495
%
105-
goal_expansion(if_(If_1, Then_0, Else_0), _L0, _M, G_0, []) :-
96+
user:goal_expansion(if_(If_1, Then_0, Else_0), G_0) :-
10697
ugoal_expansion(if_(If_1, Then_0, Else_0), G_0).
10798

10899
%
@@ -117,10 +108,7 @@
117108
%
118109
%
119110
ugoal_expansion(if_(If_1, Then_0, Else_0), Goal_0) :-
120-
subsumes_term(M:(X=Y), If_1),
121-
M:(X=Y) = If_1,
122-
atom(M),
123-
( M == reif -> true ; predicate_property(M: =(_,_,_),imported_from(reif)) ),
111+
nonvar(If_1), If_1 = (X = Y),
124112
goal_expanded(call(Then_0), Thenx_0),
125113
goal_expanded(call(Else_0), Elsex_0),
126114
!,
@@ -130,20 +118,27 @@
130118
; X = Y, Thenx_0
131119
; dif(X,Y), Elsex_0
132120
).
121+
ugoal_expansion(if_(If_1, Then_0, Else_0), Goal) :-
122+
nonvar(If_1), If_1 = dif(X, Y),
123+
goal_expanded(call(Then_0), Thenx_0),
124+
goal_expanded(call(Else_0), Elsex_0),
125+
!,
126+
Goal =
127+
( X \= Y -> Thenx_0
128+
; X == Y -> Elsex_0
129+
; X = Y, Elsex_0
130+
; dif(X,Y), Thenx_0
131+
).
133132
% if_((A_1;B_1), Then_0, Else_0)
134133
% => if_(A_1, Then_0, if_(B_1, Then_0, Else_0))
135134
ugoal_expansion(if_(If_1, Then_0, Else_0), Goal) :-
136-
subsumes_term(M:(A_1;B_1), If_1),
137-
M:(A_1;B_1) = If_1,
138-
atom(M),
139-
( M == reif -> true ; predicate_property(M:;(_,_,_),imported_from(reif)) ),
135+
subsumes_term((A_1;B_1), If_1),
136+
(A_1;B_1) = If_1,
140137
!,
141138
Goal = if_(A_1, Then_0, if_(B_1, Then_0, Else_0)).
142139
ugoal_expansion(if_(If_1, Then_0, Else_0), Goal_0) :-
143-
subsumes_term(M:(A_1,B_1), If_1),
144-
M:(A_1,B_1) = If_1,
145-
atom(M),
146-
( M == reif -> true ; predicate_property(M:','(_,_,_),imported_from(reif)) ),
140+
subsumes_term((A_1,B_1), If_1),
141+
(A_1,B_1) = If_1,
147142
!,
148143
Goal_0 = if_(A_1, if_(B_1, Then_0, Else_0), Else_0).
149144
ugoal_expansion(if_(If_1, Then_0, Else_0), Goal_0) :-
@@ -154,10 +149,8 @@
154149
( Ifx_0,
155150
( T == true -> Thenx_0
156151
; T == false -> Elsex_0
157-
; nonvar(T) -> throw(error(type_error(boolean,T),
158-
type_error(call(If_1,T),2,boolean,T)))
159-
; throw(error(instantiation_error,
160-
instantiation_error(call(If_1,T),2)))
152+
; nonvar(T) -> throw(error(type_error(boolean,T),_))
153+
; throw(error(instantiation_error,_))
161154
)
162155
).
163156
%
@@ -216,17 +209,19 @@
216209
%
217210
%
218211
%
212+
:- meta_predicate(if_(1, 0, 0)).
219213

220214
if_(If_1, Then_0, Else_0) :-
221215
call(If_1, T),
222216
( T == true -> Then_0
223217
; T == false -> Else_0
224-
; nonvar(T) -> throw(error(type_error(boolean,T),
225-
type_error(call(If_1,T),2,boolean,T)))
226-
; throw(error(instantiation_error,instantiation_error(call(If_1,T),2)))
218+
; nonvar(T) -> throw(error(type_error(boolean,T),_))
219+
; throw(error(instantiation_error,_))
227220
).
228221

229222

223+
:- meta_predicate(tfilter(2, ?, ?)).
224+
230225
tfilter(C_2, Es, Fs) :-
231226
i_tfilter(Es, C_2, Fs).
232227

@@ -235,6 +230,8 @@
235230
if_(call(C_2, E), Fs0 = [E|Fs], Fs0 = Fs),
236231
i_tfilter(Es, C_2, Fs).
237232

233+
:- meta_predicate(tpartition(2, ?, ?, ?)).
234+
238235
tpartition(P_2, Xs, Ts, Fs) :-
239236
i_tpartition(Xs, P_2, Ts, Fs).
240237

@@ -260,12 +257,18 @@
260257
non(true, false).
261258
non(false, true).
262259

260+
:- meta_predicate(','(1, 1, ?)).
261+
263262
','(A_1, B_1, T) :-
264263
if_(A_1, call(B_1, T), T = false).
265264

265+
:- meta_predicate(;(1, 1, ?)).
266+
266267
;(A_1, B_1, T) :-
267268
if_(A_1, T = true, call(B_1, T)).
268269

270+
:- meta_predicate(cond_t(1, 0, ?)).
271+
269272
cond_t(If_1, Then_0, T) :-
270273
if_(If_1, ( Then_0, T = true ), T = false ).
271274

@@ -276,9 +279,13 @@
276279
i_memberd_t([X|Xs], E, T) :-
277280
if_( X = E, T = true, i_memberd_t(Xs, E, T) ).
278281

282+
:- meta_predicate(tmember(2, ?)).
283+
279284
tmember(P_2, [X|Xs]) :-
280285
if_( call(P_2, X), true, tmember(P_2, Xs) ).
281286

287+
:- meta_predicate(tmember_t(2, ?, ?)).
288+
282289
tmember_t(_P_2, [], false).
283290
tmember_t(P_2, [X|Xs], T) :-
284291
if_( call(P_2, X), T = true, tmember_t(P_2, Xs, T) ).

0 commit comments

Comments
 (0)