|
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 | +:- use_module(library(dif)). |
26 | 27 |
|
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, ?, ?). |
| 28 | +:- meta_predicate(if_(1, 0, 0)). |
| 29 | +:- meta_predicate(cond_t(1, 0, ?)). |
| 30 | +:- meta_predicate(tfilter(2, ?, ?)). |
| 31 | +:- meta_predicate(tpartition(2, ?, ?, ?)). |
| 32 | +:- meta_predicate(','(1, 1, ?)). |
| 33 | +:- meta_predicate(;(1, 1, ?)). |
| 34 | +:- meta_predicate(tmember(2, ?)). |
| 35 | +:- meta_predicate(tmember_t(2, ?, ?)). |
36 | 36 |
|
37 | 37 | :- op(900, fy, [$]).
|
38 | 38 |
|
|
102 | 102 | */
|
103 | 103 |
|
104 | 104 | %
|
105 |
| -goal_expansion(if_(If_1, Then_0, Else_0), _L0, _M, G_0, []) :- |
| 105 | +user:goal_expansion(if_(If_1, Then_0, Else_0), G_0) :- |
106 | 106 | ugoal_expansion(if_(If_1, Then_0, Else_0), G_0).
|
107 | 107 |
|
108 | 108 | %
|
|
117 | 117 | %
|
118 | 118 | %
|
119 | 119 | 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)) ), |
| 120 | + nonvar(If_1), If_1 = (X = Y), |
124 | 121 | goal_expanded(call(Then_0), Thenx_0),
|
125 | 122 | goal_expanded(call(Else_0), Elsex_0),
|
126 | 123 | !,
|
|
130 | 127 | ; X = Y, Thenx_0
|
131 | 128 | ; dif(X,Y), Elsex_0
|
132 | 129 | ).
|
| 130 | +ugoal_expansion(if_(If_1, Then_0, Else_0), Goal) :- |
| 131 | + nonvar(If_1), If_1 = dif(X, Y), |
| 132 | + goal_expanded(call(Then_0), Thenx_0), |
| 133 | + goal_expanded(call(Else_0), Elsex_0), |
| 134 | + !, |
| 135 | + Goal = |
| 136 | + ( X \= Y -> Thenx_0 |
| 137 | + ; X == Y -> Elsex_0 |
| 138 | + ; X = Y, Elsex_0 |
| 139 | + ; dif(X,Y), Thenx_0 |
| 140 | + ). |
133 | 141 | % if_((A_1;B_1), Then_0, Else_0)
|
134 | 142 | % => if_(A_1, Then_0, if_(B_1, Then_0, Else_0))
|
135 | 143 | 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)) ), |
| 144 | + subsumes_term((A_1;B_1), If_1), |
| 145 | + (A_1;B_1) = If_1, |
140 | 146 | !,
|
141 | 147 | Goal = if_(A_1, Then_0, if_(B_1, Then_0, Else_0)).
|
142 | 148 | 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)) ), |
| 149 | + subsumes_term((A_1,B_1), If_1), |
| 150 | + (A_1,B_1) = If_1, |
147 | 151 | !,
|
148 | 152 | Goal_0 = if_(A_1, if_(B_1, Then_0, Else_0), Else_0).
|
149 | 153 | ugoal_expansion(if_(If_1, Then_0, Else_0), Goal_0) :-
|
|
0 commit comments