|
11 | 11 | tfilter/3,
|
12 | 12 | tpartition/4
|
13 | 13 | %
|
14 |
| - ], [hidden(true)]). |
| 14 | + ]). |
15 | 15 | %
|
16 | 16 | %
|
17 | 17 | %
|
|
23 | 23 | U. Neumerkel and S. Kral. https://arxiv.org/abs/1607.01590 [cs.PL]. July 2016.
|
24 | 24 | */
|
25 | 25 |
|
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)). |
36 | 27 |
|
37 | 28 | :- op(900, fy, [$]).
|
38 | 29 |
|
|
102 | 93 | */
|
103 | 94 |
|
104 | 95 | %
|
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) :- |
106 | 97 | ugoal_expansion(if_(If_1, Then_0, Else_0), G_0).
|
107 | 98 |
|
108 | 99 | %
|
|
117 | 108 | %
|
118 | 109 | %
|
119 | 110 | 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), |
124 | 112 | goal_expanded(call(Then_0), Thenx_0),
|
125 | 113 | goal_expanded(call(Else_0), Elsex_0),
|
126 | 114 | !,
|
|
130 | 118 | ; X = Y, Thenx_0
|
131 | 119 | ; dif(X,Y), Elsex_0
|
132 | 120 | ).
|
| 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 | + ). |
133 | 132 | % if_((A_1;B_1), Then_0, Else_0)
|
134 | 133 | % => if_(A_1, Then_0, if_(B_1, Then_0, Else_0))
|
135 | 134 | 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, |
140 | 137 | !,
|
141 | 138 | Goal = if_(A_1, Then_0, if_(B_1, Then_0, Else_0)).
|
142 | 139 | 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, |
147 | 142 | !,
|
148 | 143 | Goal_0 = if_(A_1, if_(B_1, Then_0, Else_0), Else_0).
|
149 | 144 | ugoal_expansion(if_(If_1, Then_0, Else_0), Goal_0) :-
|
|
154 | 149 | ( Ifx_0,
|
155 | 150 | ( T == true -> Thenx_0
|
156 | 151 | ; 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,_)) |
161 | 154 | )
|
162 | 155 | ).
|
163 | 156 | %
|
|
216 | 209 | %
|
217 | 210 | %
|
218 | 211 | %
|
| 212 | +:- meta_predicate(if_(1, 0, 0)). |
219 | 213 |
|
220 | 214 | if_(If_1, Then_0, Else_0) :-
|
221 | 215 | call(If_1, T),
|
222 | 216 | ( T == true -> Then_0
|
223 | 217 | ; 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,_)) |
227 | 220 | ).
|
228 | 221 |
|
229 | 222 |
|
| 223 | +:- meta_predicate(tfilter(2, ?, ?)). |
| 224 | + |
230 | 225 | tfilter(C_2, Es, Fs) :-
|
231 | 226 | i_tfilter(Es, C_2, Fs).
|
232 | 227 |
|
|
235 | 230 | if_(call(C_2, E), Fs0 = [E|Fs], Fs0 = Fs),
|
236 | 231 | i_tfilter(Es, C_2, Fs).
|
237 | 232 |
|
| 233 | +:- meta_predicate(tpartition(2, ?, ?, ?)). |
| 234 | + |
238 | 235 | tpartition(P_2, Xs, Ts, Fs) :-
|
239 | 236 | i_tpartition(Xs, P_2, Ts, Fs).
|
240 | 237 |
|
|
260 | 257 | non(true, false).
|
261 | 258 | non(false, true).
|
262 | 259 |
|
| 260 | +:- meta_predicate(','(1, 1, ?)). |
| 261 | + |
263 | 262 | ','(A_1, B_1, T) :-
|
264 | 263 | if_(A_1, call(B_1, T), T = false).
|
265 | 264 |
|
| 265 | +:- meta_predicate(;(1, 1, ?)). |
| 266 | + |
266 | 267 | ;(A_1, B_1, T) :-
|
267 | 268 | if_(A_1, T = true, call(B_1, T)).
|
268 | 269 |
|
| 270 | +:- meta_predicate(cond_t(1, 0, ?)). |
| 271 | + |
269 | 272 | cond_t(If_1, Then_0, T) :-
|
270 | 273 | if_(If_1, ( Then_0, T = true ), T = false ).
|
271 | 274 |
|
|
276 | 279 | i_memberd_t([X|Xs], E, T) :-
|
277 | 280 | if_( X = E, T = true, i_memberd_t(Xs, E, T) ).
|
278 | 281 |
|
| 282 | +:- meta_predicate(tmember(2, ?)). |
| 283 | + |
279 | 284 | tmember(P_2, [X|Xs]) :-
|
280 | 285 | if_( call(P_2, X), true, tmember(P_2, Xs) ).
|
281 | 286 |
|
| 287 | +:- meta_predicate(tmember_t(2, ?, ?)). |
| 288 | + |
282 | 289 | tmember_t(_P_2, [], false).
|
283 | 290 | tmember_t(P_2, [X|Xs], T) :-
|
284 | 291 | if_( call(P_2, X), T = true, tmember_t(P_2, Xs, T) ).
|
0 commit comments