1 % (c) 2009-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(b_interpreter_check,[imply_test_boolean_expression/7,
6 equiv_test_boolean_expression/7,
7 equiv_bidrectional_test_boolean_expression/7,
8 get_priority_of_boolean_expression/2, get_priority_of_boolean_expression2/2,
9 b_check_boolean_expression/5,b_check_boolean_expression/7,
10 b_force_check_boolean_expression/5,
11
12 /* some lower-level propagation predicates */
13 imply/3, imply_true/2,
14 b_check_forall_wf/8, b_check_exists_wf/7,
15
16 reify_closure_with_small_cardinality/5,
17
18 register_predicate/6,
19 norm_pred_check/2, norm_expr_check/2, norm_check/2,
20
21 conjoin/6, disjoin/6,
22 check_less_than_equal/3
23 ]).
24
25 /* A version for checking the truth value of boolean-expressions,
26 the result is instantiated with pred_true/pred_false as soon as the result is known */
27 /* Warning: does not cover all expressions */
28 /* It provides SMT-like performance, for predicates involving arithmetic comparisons (<,...),
29 equality, disequality and membership/not_membership
30 It is not restricted to CNF
31 */
32
33 :- meta_predicate wd_delay(0,-,-,-).
34 :- meta_predicate wd_delay_block(0,-,-,-,-,-).
35 :- meta_predicate wd_delay_until_needed(-,0).
36 :- meta_predicate wd_delay_until_needed_block(-,-,0).
37
38 :- use_module(debug).
39 :- use_module(self_check).
40 :- use_module(error_manager).
41 :- use_module(b_interpreter,[b_compute_expression/5, b_not_test_boolean_expression/6, b_test_boolean_expression/6, b_test_boolean_expression/4]).
42 :- use_module(kernel_waitflags).
43
44
45 :- use_module(kernel_objects,[less_than_direct/2, less_than_equal_direct/2]).
46
47 :- use_module(kernel_equality).
48
49 :- use_module(tools).
50
51 :- use_module(module_information,[module_info/2]).
52 :- module_info(group,interpreter).
53 :- module_info(description,'This module provides a reified interpreter for certain predicates.').
54
55
56
57
58 :- block imply_test_boolean_expression(-, ?,?,?,?,?,?). % TO DO: pass at least Ai to it
59 imply_test_boolean_expression(PredRes1,PredRes2, RHS,LocalState,State,WF,Ai) :-
60 (PredRes1=PredRes2
61 ? -> b_test_boolean_expression(RHS,LocalState,State,WF,Ai,_)
62 ; true
63 ).
64
65 :- block equiv_test_boolean_expression(-, ?,?,?,?,?,?).
66 equiv_test_boolean_expression(PredRes,PredRes, RHS,LocalState,State,WF,Ai) :- !,
67 b_test_boolean_expression(RHS,LocalState,State,WF,Ai,_).
68 equiv_test_boolean_expression(_PredRes,_, RHS,LocalState,State,WF,Ai) :-
69 ? b_not_test_boolean_expression(RHS,LocalState,State,WF,Ai,_).
70
71 equiv_bidrectional_test_boolean_expression(PredResLHS,PredResRHS, _LHS,_RHS,_LocalState,_State,WF) :-
72 PredResLHS=PredResRHS,
73 (var(PredResLHS)
74 -> % create a choice point to enumerate two possible solutions
75 % important, e.g., for not((y > 0 & y * y > 20) <=> (y * y > 25 & y > 0))
76 get_last_wait_flag(equivalence,WF,LWF),
77 enum_bool(PredResLHS,LWF)
78 ; true).
79 :- block enum_bool(-,-).
80 enum_bool(pred_true,_).
81 enum_bool(pred_false,_).
82 /*
83 :- block equiv_bidrectional_test_boolean_expression(-,-, ?,?,?,?,?).
84 equiv_bidrectional_test_boolean_expression(PredResLHS,PredResRHS, LHS,RHS,LocalState,State,WF) :-
85 ( PredResLHS == pred_true -> b_test_boolean_expression(RHS,LocalState,State,WF)
86 ; PredResLHS == pred_false -> b_not_test_boolean_expression(RHS,LocalState,State,WF)
87 ; PredResRHS == pred_true -> b_test_boolean_expression(LHS,LocalState,State,WF)
88 ; PredResRHS == pred_false -> b_not_test_boolean_expression(LHS,LocalState,State,WF)
89 ; add_error_fail(equiv,'Illegal values: ',equiv_bidrectional_test_boolean_expression(PredResLHS,PredResRHS))
90 ).
91 */
92
93 % return starting priority for binary choice points; should be power of 2
94 get_priority_of_boolean_expression(priority(P),Prio) :- !,
95 % case generated for disjoin by contains_fd_element, and not_in_difference_set_wf,not_in_intersection_set_wf,in_union_set_wf
96 Prio=P.
97 get_priority_of_boolean_expression(b(Expr,_,_Infos),Prio) :- !,
98 % try to estimate a priority for performing a case split upon a predicate
99 % i.e., forcing a predicate Expr to be true/false
100 get_priority_of_boolean_expression2(Expr,Prio).
101 get_priority_of_boolean_expression(E,Prio) :-
102 add_internal_error('Boolean expression not properly wrapped: ',get_priority_of_boolean_expression(E,Prio)),
103 get_priority_of_boolean_expression2(E,Prio).
104
105 :- use_module(bsyntaxtree).
106 get_priority_of_boolean_expression2(truth,1) :- !. %, nl,nl,print('TRUTH in disjunct/conjunct'),nl.
107 get_priority_of_boolean_expression2(falsity,1) :- !. %, nl,nl,print('FALSITY in disjunct/conjunct'),nl.
108 get_priority_of_boolean_expression2(_,R) :-
109 preferences:preference(data_validation_mode,true), % in data validation mode we want to drive enumeration from data values only
110 !, R=4096.
111 get_priority_of_boolean_expression2(_,R) :- !, R=4. % force SMT style case-splitting; was 3 before using get_binary_choice_wait_flag_exp_backoff; raising this to 4 makes test 1358, 49 behave better (baload_R07 recognised possible)
112
113
114
115
116 count_number_of_conjuncts(b(Expr,_,_Infos),Prio) :- !,
117 count_number_of_conjuncts2(Expr,Prio).
118 count_number_of_conjuncts(priority(_),Prio) :- !, Prio=1.
119 count_number_of_conjuncts(B,Prio) :-
120 add_internal_error('Expression not wrapped: ',count_number_of_conjuncts(B,Prio)),Prio=1.
121 count_number_of_conjuncts2(conjunct(A,B),Nr) :- !, count_number_of_conjuncts(A,NA),
122 count_number_of_conjuncts(B,NB), Nr is NA+NB.
123 count_number_of_conjuncts2(norm_conjunct(_,RHS),Res) :- length(RHS,Len),!,
124 Res is Len+1.
125 count_number_of_conjuncts2(negation(A),Nr) :- !, count_number_of_disjuncts(A,Nr).
126 count_number_of_conjuncts2(_,1).
127
128 :- public count_number_of_disjuncts/2. %currently commented out above
129 count_number_of_disjuncts(b(Expr,_,_Infos),Prio) :- !,
130 count_number_of_disjuncts2(Expr,Prio).
131 count_number_of_disjuncts(priority(_),Prio) :- !, Prio=1.
132 count_number_of_disjuncts(B,Prio) :-
133 add_internal_error('Expression not wrapped: ',count_number_of_disjuncts(B,Prio)),Prio=1.
134 count_number_of_disjuncts2(disjunct(A,B),Nr) :- !, count_number_of_disjuncts(A,NA),
135 count_number_of_disjuncts(B,NB), Nr is NA+NB.
136 count_number_of_disjuncts2(norm_disjunct(_,RHS),Res) :- length(RHS,Len),!,
137 Res is Len+1.
138 count_number_of_disjuncts2(negation(A),Nr) :- !, count_number_of_conjuncts(A,Nr).
139 count_number_of_disjuncts2(_,1).
140
141
142
143 % we need to ensure that b_check_boolean_expression does not create a choice point on its own
144
145 b_check_boolean_expression(b(Expr,_,Infos),LS,S,WF,Res) :-
146 (composed(Expr) -> empty_avl(Ai)
147 ; Ai = no_avl), % simple expression: no sharing is possible: no need to register expressions
148 create_wfwd_needed(WF,WFD),
149 b_check_boolean_expression2(Expr,Infos,LS,S,WFD,Res,Ai,_).
150
151 composed(negation(_)).
152 composed(conjunct(_,_)).
153 composed(disjunct(_,_)).
154 composed(implication(_,_)).
155 composed(equivalence(_,_)).
156 composed(let_predicate(_,_,_)).
157 composed(lazy_let_pred(_,_,_)).
158
159 b_check_boolean_expression(E,LS,S,WF,Res,Ai,Ao) :-
160 % WFD adds information about WD context: wfwd(WF_store, ExpectedVal, Val,Infos)
161 % when Val becomes nonvar: if Val==ExpectedVal we need the value of E, otherwise it should be discarded
162 create_wfwd_needed(WF,WFD),
163 ? b_check_boolean_expression1(E,LS,S,WFD,Res,Ai,Ao).
164
165 b_check_boolean_expression0(WDE,WDV,Expr,LS,S,WF,Res,Ai,Ao) :-
166 create_wfwd(WF,WDE,WDV,WFD),
167 ? b_check_boolean_expression1(Expr,LS,S,WFD,Res,Ai,Ao).
168
169
170 b_check_boolean_expression1(b(Expr,_,Infos),LS,S,WFD,Res,Ai,Ao) :- get_wd(WFD,WDE,WDV),!,
171 % print('check : '), translate:print_bexpr(b(Expr,pred,Infos)),nl,
172 (nonvar(WDV),WDE \= WDV % the expression is not needed
173 -> Ai=Ao,
174 (var(Res)
175 -> Res=pred_false % set it to false, value does not matter; note: predicate is not reused
176 ; true)
177 ? ; b_check_boolean_expression2(Expr,Infos,LS,S,WFD,Res,Ai,Ao)).
178 b_check_boolean_expression1(E,LS,S,WFD,Res,Ai,Ao) :-
179 add_internal_error('Boolean expression not properly wrapped: ',b_check_boolean_expression1(E,LS,S,WFD,Res,Ai,Ao)),
180 b_check_boolean_expression2(E,[],LS,S,WFD,Res,Ai,Ao).
181
182 % normalise conjunction into flat list of conjuncts
183 normalise_conjunct(b(E,_,Info)) --> normalise_conjunct2(E,Info).
184 normalise_conjunct2(conjunct(A,B),_) --> !,normalise_conjunct(A),normalise_conjunct(B).
185 normalise_conjunct2(F,Info) --> [b(F,pred,Info)].
186
187 construct_norm_conjunct(A,b(B,pred,Info)) :- construct_norm_conjunct2(A,B,Info).
188 construct_norm_conjunct2([],truth,[]).
189 construct_norm_conjunct2([H|T],Res,Info) :-
190 (T==[] -> H=b(Res,pred,Info) ; Res=norm_conjunct(H,T),Info=[]).
191 % TO DO: build up member(contains_wd_condition,Infos)
192
193
194 % normalise disjunction into flat list of disjuncts
195 normalise_disjunct(b(E,_,Info)) --> normalise_disjunct2(E,Info).
196 normalise_disjunct2(disjunct(A,B),_) --> !,normalise_disjunct(A),normalise_disjunct(B).
197 normalise_disjunct2(F,Info) --> [b(F,pred,Info)].
198
199 construct_norm_disjunct(A,b(B,pred,Info)) :- construct_norm_disjunct2(A,B,Info).
200 construct_norm_disjunct2([],falsity,[]).
201 construct_norm_disjunct2([H|T],Res,Info) :-
202 (T==[] -> H=b(Res,pred,Info) ; Res=norm_disjunct(H,T),Info=[]).
203
204 can_negate_expression(b(Expr,pred,I),b(NExpr,pred,I)) :- can_negate2(Expr,NExpr).
205 can_negate2(equal(A,B),not_equal(A,B)).
206 can_negate2(not_equal(A,B),equal(A,B)).
207 can_negate2(member(A,B),not_member(A,B)).
208 can_negate2(not_member(A,B),member(A,B)).
209 can_negate2(subset(A,B),not_subset(A,B)).
210 can_negate2(not_subset(A,B),subset(A,B)).
211 can_negate2(subset_strict(A,B),not_subset_strict(A,B)).
212 can_negate2(not_subset_strict(A,B),subset_strict(A,B)).
213 can_negate2(greater_equal(A,B),less(A,B)).
214 can_negate2(less(A,B),greater_equal(A,B)).
215 can_negate2(less_equal(A,B),greater(A,B)).
216 can_negate2(greater(A,B),less_equal(A,B)).
217 can_negate2(less_real(A,B),less_equal_real(B,A)).
218 can_negate2(less_equal_real(A,B),less_real(B,A)).
219
220 b_check_boolean_expression2(truth,_,_,_,_WFD,Res,Ai,Ao) :- !,Res=pred_true, Ai=Ao.
221 b_check_boolean_expression2(falsity,_,_,_,_WFD,Res,Ai,Ao) :- !,Res=pred_false, Ai=Ao.
222 b_check_boolean_expression2(negation(BExpr),_,LocalState,State,WFD,Res,Ai,Ao) :- !,
223 (can_negate_expression(BExpr,NBExpr)
224 -> /* avoid introducing negate propagator; maybe not necessary */
225 b_check_boolean_expression1(NBExpr,LocalState,State,WFD,Res,Ai,Ao)
226 ; negate(NR,Res),
227 b_check_boolean_expression1(BExpr,LocalState,State,WFD,NR,Ai,Ao)).
228 b_check_boolean_expression2(conjunct(LHS,RHS),CInfo,LocalState,State,WFD,Res,Ai,Ao) :- !,
229 normalise_conjunct2(conjunct(LHS,RHS),CInfo,NormRes,[]),
230 construct_norm_conjunct2(NormRes,NC,Info),
231 ? b_check_boolean_expression2(NC,Info,LocalState,State,WFD,Res,Ai,Ao).
232 b_check_boolean_expression2(norm_conjunct(LHS,RHS),_,LocalState,State,wfwd(WF,WDE,WDV,_),Res,Ai,Ao) :- !,
233 construct_norm_conjunct(RHS,NC),
234 conjoin(LR,RR,Res,LHS,NC,WF),
235 create_wfwd(WF,WDE,WDV,WFD),
236 ? b_check_boolean_expression1(LHS,LocalState,State,WFD,LR,Ai,Aii),
237 propagagate_wfwd(WDE,WDV,GuardFlag,LR,pred_false), % if WDE/=WDV then set GuardFlag to pred_false; indicating to RHS that it is not needed also
238 ? b_check_boolean_expression0(pred_true,GuardFlag,NC,LocalState,State,WF,RR,Aii,Ao).
239 b_check_boolean_expression2(implication(LHS,RHS),_,LocalState,State,wfwd(WF,WDE,WDV,_),Res,Ai,Ao) :- !,
240 imply(LR,RR,Res),
241 create_wfwd(WF,WDE,WDV,WFD),
242 b_check_boolean_expression1(LHS,LocalState,State,WFD,LR,Ai,Aii),
243 propagagate_wfwd(WDE,WDV,GuardFlag,LR,pred_false),
244 ? b_check_boolean_expression0(pred_true,GuardFlag,RHS,LocalState,State,WF,RR,Aii,Ao).
245 b_check_boolean_expression2(equivalence(LHS,RHS),_,LocalState,State,WFD,Res,Ai,Ao) :- !, equiv(LR,RR,Res),
246 b_check_boolean_expression1(LHS,LocalState,State,WFD,LR,Ai,Aii),
247 ? b_check_boolean_expression1(RHS,LocalState,State,WFD,RR,Aii,Ao).
248 b_check_boolean_expression2(disjunct(LHS,RHS),CInfo,LocalState,State,WFD,Res,Ai,Ao) :- !,
249 normalise_disjunct2(disjunct(LHS,RHS),CInfo,NormRes,[]),
250 construct_norm_disjunct2(NormRes,NC,Info),
251 b_check_boolean_expression2(NC,Info,LocalState,State,WFD,Res,Ai,Ao).
252 b_check_boolean_expression2(norm_disjunct(LHS,RHS),_,LocalState,State,wfwd(WF,WDE,WDV,_),Res,Ai,Ao) :- !,
253 construct_norm_disjunct(RHS,NC),
254 disjoin(LR,RR,Res,LHS,NC,WF),
255 create_wfwd(WF,WDE,WDV,WFD),
256 b_check_boolean_expression1(LHS,LocalState,State,WFD,LR,Ai,Aii),
257 propagagate_wfwd(WDE,WDV,GuardFlag,LR,pred_true),
258 b_check_boolean_expression0(pred_false,GuardFlag,NC,LocalState,State,WF,RR,Aii,Ao).
259 b_check_boolean_expression2(let_predicate(Ids,AssignmentExprs,Pred),_Info,LocalState,State,WFD,Res,Ai,Ao) :- !,
260 wd_set_up_localstate_for_let(Ids,AssignmentExprs,LocalState,State,LetState,WFD),
261 Ao=Ai, % anything cached inside the LET may depend on Ids and should not be reused outside of LET, see test 2397
262 empty_avl(InnerAi), % we can only reuse predicates inside if Ids are fresh, see test 2398
263 b_check_boolean_expression1(Pred,LetState,State,WFD,Res,InnerAi,_).
264 b_check_boolean_expression2(lazy_let_pred(Id,AssignmentExpr,Pred),_I,LocalState,State,wfwd(WF,WDE,WDV,_),Res,Ai,Ao) :- !,
265 set_up_localstate([Id],[(Trigger,IdValue)],LocalState,LetState),
266 b_interpreter:lazy_compute_expression(Trigger,AssignmentExpr,LocalState,State,IdValue,WF,Ai),
267 create_wfwd(WF,WDE,WDV,WFD),
268 b_check_boolean_expression1(Pred,LetState,State,WFD,Res,Ai,Ao). % Lazy lets always unique, we can pass Ai
269 b_check_boolean_expression2(lazy_lookup_pred(Id),Info,LocalState,_State,WFD,Res,Ai,Ao) :- !, Ai=Ao,
270 store:lookup_value_for_existing_id(Id,LocalState,(Trigger,Value)), % should normally only occur in LocalState; value introduced by lazy_let
271 wd_delay(((Trigger,Value) = (pred_true,Res)),
272 Res,b(lazy_lookup_pred(Id),pred,Info),WFD).
273 b_check_boolean_expression2(value(V),_Info,_LocalState,_State,_WFD,Res,Ai,Ao) :- !, % this can occur when lazy_lookup_pred gets compiled by b_compiler
274 Res=V,Ai=Ao.
275 b_check_boolean_expression2(not_equal(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao) :- !,
276 (negate_equal_false(LHS,RHS,LHS1,RHS1)
277 -> /* X/=FALSE equivalent to X=TRUE */
278 b_check_boolean_expression3_pos(equal(LHS1,RHS1),Info,LocalState,State,WFD,Res,Ai,Ao)
279 ? ; b_check_boolean_expression3_neg(equal(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao)
280 ).
281 b_check_boolean_expression2(equal(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao) :- !,
282 (negate_equal_false(LHS,RHS,LHS1,RHS1)
283 -> RHS1=b(boolean_true,boolean,[]), /* X/=FALSE equivalent to X=TRUE */
284 b_check_boolean_expression3_neg(equal(LHS1,RHS1),Info,LocalState,State,WFD,Res,Ai,Ao)
285 ? ; b_check_boolean_expression3_pos(equal(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao)
286 ).
287 b_check_boolean_expression2(not_member(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao) :- !,
288 b_check_boolean_expression3_neg(member(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao).
289 b_check_boolean_expression2(not_subset(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao) :- !,
290 b_check_boolean_expression3_neg(subset(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao).
291 b_check_boolean_expression2(not_subset_strict(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao) :- !,
292 b_check_boolean_expression3_neg(subset_strict(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao).
293 b_check_boolean_expression2(greater(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao) :- !,
294 b_check_boolean_expression3_pos(less(RHS,LHS),Info,LocalState,State,WFD,Res,Ai,Ao).
295 b_check_boolean_expression2(greater_equal(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao) :- !,
296 b_check_boolean_expression3_neg(less(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao).
297 b_check_boolean_expression2(less_equal(LHS,RHS),Info,LocalState,State,WFD,Res,Ai,Ao) :- !,
298 b_check_boolean_expression3_neg(less(RHS,LHS),Info,LocalState,State,WFD,Res,Ai,Ao).
299 b_check_boolean_expression2(Pred,Infos,LocalState,State,WFD,Res,Ai,Ao) :-
300 ? b_check_boolean_expression3_pos(Pred,Infos,LocalState,State,WFD,Res,Ai,Ao).
301
302
303 % check whether one of the two arguments is FALSE
304 % translate X/=FALSE -> X=TRUE for normalisation purposes
305 negate_equal_false(b(boolean_false,boolean,_),E,E,b(boolean_true,boolean,[])).
306 negate_equal_false(E,b(boolean_false,boolean,_),E,b(boolean_true,boolean,[])).
307
308 b_check_boolean_expression3_pos(Pred,Infos,LocalState,State,WFD,Res,Ai,Ao) :-
309 %print(register_predicate(WFD)),nl,portray_avl(Ai),nl,
310 register_predicate_wfd(WFD,Pred,Infos,Res,Reused,Ai,Ai2),
311 (Reused=true
312 -> Ao=Ai2 % , print(reused_pred(Res,WFD,Infos)),nl
313 ? ; b_check_boolean_expression4(Pred,Infos,LocalState,State,WFD,Ok,Res),
314 (Ok=ok_to_store -> Ao=Ai2 ; Ao=Ai)
315 ).
316
317 b_check_boolean_expression3_neg(Pred,Infos,LocalState,State,WFD,NegRes,Ai,Ao) :-
318 %print(register_neg_predicate(WFD,Infos,Pred)),nl,
319 register_predicate_wfd(WFD,Pred,Infos,Res,Reused,Ai,Ai2), negate(Res,NegRes),
320 (Reused=true
321 -> Ao=Ai2
322 ? ; b_check_boolean_expression4(Pred,Infos,LocalState,State,WFD,Ok,Res),
323 (Ok=ok_to_store -> Ao=Ai2 ; Ao=Ai)
324 ).
325
326 % Register a new predicate in the AVL tree if either forced or non-WD condition inside
327 register_predicate_wfd(_,_,_,_,false,Ai,Ao) :- Ai = no_avl,!, Ai=Ao.
328 register_predicate_wfd(_,_Pred,_Infos,_,false,Ai,Ao) :-
329 preferences:preference(use_common_subexpression_elimination,true),
330 preferences:preference(use_common_subexpression_also_for_predicates,true),
331 preferences:preference(disprover_mode,false), % there are still a few things detected here that CSE does not detect (=FALSE,=TRUE,...)
332 !, % CSE already statically detects these ( all of the time !?)
333 Ai=Ao.
334 register_predicate_wfd(WFWD,Pred,Infos,PredTruthVar,Reused,Ai,Ao) :-
335 get_wd(WFWD,A,B),
336 (A==B -> register_predicate_aux(Pred,PredTruthVar,Reused,Ai,Ao) % it will be evaluated; we can share it
337 ; nonmember(contains_wd_condition,Infos) -> register_predicate_aux(Pred,PredTruthVar,Reused,Ai,Ao)
338 % Pred is not guaranteed to be evaluated: WD-condition + not in forced WFD context (beware of exists!)
339 ; register_predicate_aux(Pred,PredTruthVar,true,Ai,Ao) -> Reused=true % the predicate is already stored
340 % Note: as predicate is already stored; no problem with WD; relevant for test 1959
341 ; Ai=Ao, Reused=false % not guaranteed to be evaluated: WD-condition + not in forced WFD context
342 % ,print('NOT REGISTERING: '), translate:print_bexpr(Pred),nl
343 ).
344
345 :- assert_must_succeed((E=empty, %avl:empty_avl(E),
346 A=b(value(_VAR),integer,[]),
347 b_interpreter_check:register_predicate(equal(A,A),[],pred_true,Reused,E,A1),
348 Reused==false, A1==empty)). % ensure we do not store non-var expressions
349 :- assert_must_succeed((E=empty, %avl:empty_avl(E),
350 A=b(value(int(1)),integer,[]),
351 b_interpreter_check:register_predicate(equal(A,A),[],pred_true,Reused,E,A1),
352 Reused==false, A1 \= empty, B=b(value(_),integer,[]),
353 b_interpreter_check:register_predicate(equal(B,B),[],pred_true,Reuse2,A1,A2),
354 Reuse2==false, A2==A1)). % ensure we do not look up non-var expressions
355 :- assert_must_succeed((E=empty, %avl:empty_avl(E),
356 A=b(value(int(1)),integer,[]),
357 b_interpreter_check:register_predicate(equal(A,A),[info1],pred_true,Reused,E,A1),
358 Reused==false,
359 b_interpreter_check:register_predicate(equal(A,A),[info2],pred_true,Reuse2,A1,A2),
360 Reuse2==true, A2==A1)). % ensure registering works
361
362 % Register a new predicate in the AVL tree (for outside callers like b_interpreter.pl)
363 register_predicate(Pred,_Infos,NegPredTruthVar,Reused,Ai,Ao) :- negate_pred(Pred,NegPred),!,
364 %print(negating),nl,
365 negate(PredTruthVar,NegPredTruthVar),
366 register_predicate_aux(NegPred,PredTruthVar,Reused,Ai,Ao).
367 register_predicate(Pred,_Infos,PredTruthVar,Reused,Ai,Ao) :-
368 register_predicate_aux(Pred,PredTruthVar,Reused,Ai,Ao).
369
370 negate_typed_pred(b(A,pred,_),NegA) :- negate_pred(A,NegA).
371 negate_pred(equal(A,B),equal(AA,TRUE)) :- negate_equal_false(A,B,AA,TRUE).
372 negate_pred(not_equal(A,B),equal(A,B)). % TO DO: we should check negate_equal_false
373 negate_pred(not_member(A,B),member(A,B)).
374 negate_pred(not_subset(A,B),subset(A,B)).
375 negate_pred(not_subset_strict(A,B),subset_strict(A,B)).
376 negate_pred(greater_equal(A,B),less(A,B)).
377 negate_pred(less_equal(A,B),less(B,A)).
378 negate_pred(negation(b(A,pred,_)),A).
379
380 % to do: detect convert_bool(Pred) = X and register Pred?
381 register_predicate_aux(Pred,_PredTruthVar,Reused,Ai,Ao) :- do_not_store_pred(Pred),
382 !,
383 Ai=Ao, Reused=false.
384 register_predicate_aux(Pred,PredTruthVar,Reused,Ai,Ao) :- check_pred_truth_var(PredTruthVar),
385 norm_pred_check(Pred,NPred), % We could store this information in the info field computed by ast_cleanup ?
386 (%too_simple(NPred) -> Reused=false, Ao=Ai ; %% even for simple equalities it actually pays off !
387 reuse_predicate(NPred,Var,Ai)
388 -> % nl,print(reusing(NPred,Var)),nl, %%
389 PredTruthVar=Var,Ao=Ai, Reused=true
390 ; add_predicate(NPred,PredTruthVar,Ai,Ao), Reused=false
391 %,nl,print(not_reusing(NPred)),nl
392 ).
393
394 check_pred_truth_var(X) :- var(X),!.
395 check_pred_truth_var(pred_true) :- !.
396 check_pred_truth_var(pred_false) :- !.
397 check_pred_truth_var(X) :- add_internal_error('Illegal Predicate Truth Value: ',check_pred_truth_var(X)).
398
399 :- use_module(kernel_tools,[ground_bexpr/1]).
400 do_not_store_pred(external_pred_call(_P,_)) :- !. % expcept maybe LESS, CHOOSE,... we could check performs_io
401 do_not_store_pred(B) :-
402 (ground_bexpr(b(B,pred,[]))
403 % TO DO: improve performance: marking bexpr with potential non-ground value(.) terms inside
404 % maybe avoid registering predicates with very large values inside
405 % avoid registering predicate if it is the only one in a closure
406 -> fail
407 ; true %print('-> Not storing: '),translate:print_bexpr(b(B,pred,[])),nl
408 ).
409
410
411 % Quantifier Expansion
412
413 b_check_forall_wf(Parameters,LHS,RHS,Info,LocalState,State,WF,PredRes) :-
414 create_wfwd_needed(WF,WFD), % we expect it to be in a context where the value will be needed
415 b_check_forall_wfwd(Parameters,LHS,RHS,Info,LocalState,State,WFD,PredRes).
416 b_check_forall_wfwd(_Parameters,LHS,RHS,_Info,_LocalState,_State,_WFD,PredRes) :-
417 (is_falsity(LHS) ; is_truth(RHS)),!, % quantifier always true
418 PredRes = pred_true.
419 b_check_forall_wfwd(Parameters,LHS,RHS,Info,LocalState,State,WFD,PredRes) :-
420 ? small_quantifier_cardinality(Parameters,LHS,LHS1,LHSRest),
421 %print(expand(forall(Parameters))),nl,
422 expand_quantifier(Parameters,LHS1,List,forall,Info), %print(List),nl,
423 Body = b(implication(LHSRest,RHS),pred,Info),% translate:print_bexpr(Body),nl,
424 get_wf(WFD,WF),
425 check_expanded_forall_quantifier(List,Body, LocalState, State,WF,WFD,PredRes).
426 % TO DO: if not small_quantifier_cardinality: b_check_boolean_expression4_delay
427
428
429 b_check_exists_wf(Parameters,Body,Info,LocalState,State,WF,PredRes) :-
430 create_wfwd_needed(WF,WFD), % we expect it to be in a context where the value will be needed
431 b_check_exists_wfwd(Parameters,Body,Info,LocalState,State,WFD,_,PredRes).
432 b_check_exists_wfwd(Parameters,Body,Info,LocalState,State,WFD,ok_to_store,PredRes) :-
433 % could be generalised to take into consideration domain as restricted by Body
434 ? small_quantifier_cardinality(Parameters,Body,LHS,RHS),!,
435 % print(expanding_check_exists(_Card,Parameters)),nl, % portray_waitflags(WF),
436 expand_quantifier(Parameters,LHS,List,exists,Info),
437 % now compute a priority for the disjunction based on the number of case splits
438 % relevant for tests 1358, 1746
439 length(List,Len), % Note: if Len=1: the body must be true; no disjoin will be set up
440 get_pow2_binary_choice_priority(Len,Prio),
441 % if Len=2 -> we actually have just two possibilities T,_ and F,T; but we want Prio to start at 4 ?
442 % if Len=3 -> we have T,_,_ ; F,T,_ ; F,F,T less possibilites if disjoin enumerated from left-to-right; TO DO: should we lower the priority taking this into account ?
443 % TO DO: maybe we could directly set up an n-ary disjoin predicate;
444 % if one disjunct true; remove case-splits on other disjuncts
445 get_wf(WFD,WF),
446 check_expanded_exists_quantifier(List,Prio,RHS, LocalState, State,WF,WFD,PredRes).
447 b_check_exists_wfwd(Parameters,Body,Infos,LocalState,State,wfwd(WF,WDE,WDV,ContextInfo),do_not_store,PredRes) :-
448 % the above reification has not worked; we now "pretend" that reification worked
449 % and introduce a delayed choice point
450 % do_not_store means that the predicate result should not be re-used somewhere else, because
451 % as the predicate evaluation is delayed it may later not be needed and not evaluated, cf test 2404
452 ContextInfo \= outer_wfwd_context, % at the outer-level interpreter expects reification succeeds only if
453 % at least top-level operator was reified deterministically,
454 % important for tests 1074, 1338, 1358, 1915 with this clause enabled
455 % test 305 #x.(x + x = 1000) now works, but not 1739 (timeout)
456 reify_inner_exists_non_deterministically, % hence we currently only use it in data validation mode
457 % here we enumerate reification variables with a much lower priority (data driven enumeration)
458 % (see get_binary_choice_wait_flag_exp_backoff)
459 % this clause relevant for 0323/CCSL/TYPES_AUTORISES_RVF3_GEN__MRGA.mch
460 Pred = exists(Parameters,Body),
461 perfmessage(reify,reifiying_inner_exists_non_deterministically(Parameters),Infos),
462 b_check_boolean_expression4_delay(WDE,WDV,Pred,Infos,LocalState,State,WF,PredRes).
463
464 % true if we allow reification of exists which cannot be expanded
465 % by delayed non-det enumeration (of pred_false, pred_true) if exists is not at top-level
466 reify_inner_exists_non_deterministically :- preferences:preference(data_validation_mode,true).
467
468
469 :- use_module(b_enumerate, [b_tighter_enumerate_values_in_ctxt/3]).
470 expand_quantifier(Parameters,Pred,ListOfNewLocalStates,QuantKind,Span) :-
471 % at the moment LS,State not really needed; only necessary if non-compiled Pred can be used
472 % also: feeding in any non-bound variables in LocalState or State would cause problems in findall !
473 findall(ParLocalState,
474 (b_interpreter:set_up_typed_localstate(Parameters,ParaValues,ParamTypedVals,
475 [],ParLocalState,all_solutions),
476 kernel_waitflags:init_wait_flags_with_call_stack(WF,
477 [quantifier_call(QuantKind,Parameters,ParaValues,Span)]),
478 b_test_boolean_expression(Pred,[],ParLocalState,WF),
479 b_tighter_enumerate_values_in_ctxt(ParamTypedVals,Pred,WF),
480 kernel_waitflags:ground_wait_flags(WF)),
481 ListOfNewLocalStates).
482
483 % a version which ensures that we have unique solutions of the bindings
484 expand_quantifier_normalised(Parameters,Pred,ListOfNewLocalStates,QuantKind,Span) :-
485 expand_quantifier(Parameters,Pred,List,QuantKind,Span),
486 normalise_local_states(List,NList),
487 sort(NList,ListOfNewLocalStates). % will remove duplicates
488
489 normalise_local_states([],[]).
490 normalise_local_states([State|T],[NS|NT]) :-
491 convert_bindings_to_avl(State,NS),
492 normalise_local_states(T,NT).
493
494 :- use_module(custom_explicit_sets,[convert_to_avl/2]).
495 convert_bindings_to_avl([],[]).
496 convert_bindings_to_avl([bind(Var,Val)|T],[bind(Var,NVal)|NT]) :-
497 (convert_to_avl(Val,NVal) -> true ; add_internal_error('Cannot normalise:',Val),fail),
498 convert_bindings_to_avl(T,NT).
499
500 check_expanded_forall_quantifier([], _Body, _LS, _State,_WF,_WFD,Res) :-
501 Res=pred_true.
502 check_expanded_forall_quantifier([LS1|TLS], Body, LS, State,WF,WFD,Res) :-
503 conjoin(Res1,TRes,Res,Body,Body,WF),
504 empty_avl(InnerAi), % TO DO: maybe use no_avl ?
505 append(LS1,LS,InnerLS),
506 % Note: we do not need to guard against wd-definition from other instances inside a quantified expression
507 % either all conjuncts can be evaluated or none
508 % print(expand_forall(WFD)), translate:print_bexpr(Body),nl,
509 b_check_boolean_expression1(Body,InnerLS,State,WFD,Res1,InnerAi,_Aii),
510 %instantiate_wfwd_result(WDE,WDV,Res1),
511 check_expanded_forall_quantifier(TLS,Body,LS,State,WF,WFD,TRes).
512
513 /*
514 :- block instantiate_wfwd_result(?,-,-).
515 % instantiate a boolean variable in case it is no longer needed and not set by something else
516 instantiate_wfwd_result(WDE,WDV,Res) :-
517 (nonvar(Res) -> true
518 ; WDE==WDV -> true
519 ; Res = pred_false). */
520
521 check_expanded_exists_quantifier([], _, _Body, _LS, _State,_WF,_WFD,Res) :-
522 Res=pred_false.
523 check_expanded_exists_quantifier([LS1|TLS], Priority, Body, LS, State,WF,WFD,Res) :-
524 (TLS = [] -> Res=Res1
525 ; disjoin(Res1,TRes,Res,priority(Priority),priority(Priority),WF)), % was using Body instead of priority(Priority)
526 empty_avl(InnerAi), % TO DO: maybe use no_avl ?
527 append(LS1,LS,InnerLS),
528 b_check_boolean_expression1(Body,InnerLS,State,WFD,Res1,InnerAi,_Aii),
529 % Note: we do not need to guard against wd-definition from other instances inside a quantified expression
530 check_expanded_exists_quantifier(TLS,Priority,Body,LS,State,WF,WFD,TRes).
531
532
533 % try and convert a closure into a list of 0/1 variables for each potential element
534 reify_closure_with_small_cardinality(P,T,Body, WF,ReifiedList) :- %print(try(P)),nl,
535 create_typed_ids(P,T,Parameters),
536 small_quantifier_cardinality(Parameters,Body,LHS,RHS,350,25000), % TO DO: how to choose these parameters ?
537 % for card({x|x:1..n & x mod 3=0})=c & n=24000 -> 340 ms with reification; 320 ms without; n=74000 : 1020 ms without, 1160 with reification
538 % but there is a big difference for card({x|x:1..n & x mod 3=0 & x<10}) with n=74000 : 0 ms without reification, 1580 with; n=500: 20 ms with reification; n=250: 10 ms with reification
539 expand_quantifier_normalised(Parameters,LHS,List,comprehension_set,Body),
540 % important to normalise and have unique solutions for cardinality reification,
541 % see tests 639, 640 for card(POW(SS)-{{}}) with SS full set
542 create_wfwd_needed(WF,WFD), % is this ok ??
543 ? reifiy_list(List,RHS,WFD,ReifiedList).
544
545
546
547 reifiy_list([], _Body,_WFD,[]).
548 reifiy_list([LS1|TLS], Body,WFD,[Res_01|TRes]) :-
549 empty_avl(InnerAi),
550 ? b_check_boolean_expression1(Body,LS1,[],WFD,Res1_pred,InnerAi,_Aii),
551 prop_pred_01(Res1_pred,Res_01),
552 %format(' reify ~w : ~w~n',[Res_01,LS1]),
553 % Note: we do not need to guard against wd-definition from other instances inside a quantified expression
554 reifiy_list(TLS,Body,WFD,TRes).
555
556
557
558 :- use_module(library(lists),[select/3]).
559
560 % check if Body produces a small cardinality for the paramters Par
561 % if yes: the predicates constraining Par are put into LHS, the rest into RHS
562 % also: LHS must ensure that ground values are produced for Par and that we can enumerate with a separate WF (in expand_quantifier)
563 small_quantifier_cardinality(Par,Body,LHS,RHS) :-
564 %preferences:preference(solver_strength,SS), NL is 10+SS, SMTL is 40+SS,
565 NL=10,SMTL=40,
566 ? small_quantifier_cardinality(Par,Body,LHS,RHS,NL,SMTL). % was 10,35; raising it to 10,41 makes tests 1441, 1442 fail due to expansion of exists; raising it to 16,50 makes test 1112 fail; TO DO: investigate
567 small_quantifier_cardinality(Par,Body,LHS,RHS,NormalLimit,SMTLimit) :-
568 conjunction_to_list(Body,BodyList),
569 def_get_texpr_ids(Par,AllParas),
570 ? small_quantifier_cardinality_aux(Par,AllParas,BodyList,_UpBoundOnSize,LLHS,LRHS,NormalLimit,SMTLimit),
571 conjunct_predicates_with_pos_info(LLHS,LHS),
572 conjunct_predicates_with_pos_info(LRHS,RHS).
573
574 is_membership_or_eq(b(P,pred,Info),TLHS,RHS,Info) :- is_mem_aux(P,TLHS,RHS).
575 is_mem_aux(member(TLHS,b(RHS,_,_)),TLHS,RHS).
576 %is_mem_aux(subset(SONE,b(RHS,_,_)),TLHS,RHS) :- singleton_set_extension(SONE,TLHS).
577 is_mem_aux(equal(TLHS,b(value(V),_,_)),TLHS,value([V])). % x = V is the same as x:{V}
578 %TODO: use :- use_module(bsyntaxtree,[is_membership_or_equality/3]). % will create set_extension
579
580 % do not rely on size for anything: it is just an upper bound on the size; the actual size could be smaller
581 small_quantifier_cardinality_aux([],_,Body,Size,LHS,RHS,_,_) :- !,
582 LHS=[],RHS=Body,Size=1.
583 small_quantifier_cardinality_aux(Parameters,AllParas,[LHS|TBody],FullSize,FullLHS,FullRHS,NormalLimit,SMTLimit) :-
584 is_membership_or_eq(LHS,SID,MemRHS,Info),
585 ? constrains_ID(SID,AllParas,Parameters,RestParameters,SkelVal,SkelToUnify,BindList), % we could check RestParameters /= Parameters
586 % TO DO: we could also allow parameter to be constrained twice x: 1..100 & x: {...} ?
587 (is_small_set(MemRHS,Size,NormalLimit,SMTLimit,Info) % we have a small set of ground values: we can evaluate LHS to expand the quantifier/set_comprehension for the parameters occuring in LHS
588 -> FullLHS = [LHS|RestLHS],FullRHS = RestRHS
589 ; infer_ground_membership(MemRHS,SID,SkelVal,SkelToUnify,BindList,NormalLimit,SMTLimit, Size,InferredLHS) ->
590 % we have inferred a superset InferredLHS of MemRHS which is small and known
591 FullLHS = [InferredLHS|RestLHS], % we have added an inferred membership constraint
592 FullRHS = [LHS|RestRHS]), % the original membership LHS still needs to be checked later, after expansion of the quantifier
593 !,
594 % we select LHS to be included in FullLHS and mark parameter ID as constrained
595 small_quantifier_cardinality_aux(RestParameters,AllParas,TBody,RestSize,RestLHS,RestRHS,NormalLimit,SMTLimit),
596 FullSize is Size*RestSize,
597 is_small_size(FullSize,NormalLimit,SMTLimit, Parameters).
598 small_quantifier_cardinality_aux(Parameters,AllParas,[H|Rest],FullSize,RestLHS,[H|RestRHS],NormalLimit,SMTLimit) :- !,
599 % skip the conjunct H
600 ? small_quantifier_cardinality_aux(Parameters,AllParas,Rest,FullSize,RestLHS,RestRHS,NormalLimit,SMTLimit).
601 small_quantifier_cardinality_aux(Parameters,_AllParas,Body,ParCard,[],Body,NormalLimit,SMTLimit) :-
602 % if the remaining parameter type cardinality is small: just use "truth" as body; will instantiate parameters
603 ? b_interpreter:parameter_list_cardinality(Parameters,ParCard),
604 is_small_size(ParCard,NormalLimit,SMTLimit, Parameters).
605
606 % try and extract a ground superset (InferredLHS) of the RHS (ID:RHS) which constrains ID
607 infer_ground_membership(value(List),SID,SkelVal,SkelToUnify,BindList,NormalLimit,SMTLimit, Size,InferredLHS) :-
608 !,
609 % the List is probably not ground; let's try and see if we can extract ground matches for the parameters at least; see test 1627 (s=1..20 & x: s-->BOOL & card({t|t|->TRUE:x}):18..19)
610 extract_bind_list(BindList,LHSTerm,RHSValue),
611 has_bounded_ground_matches(List,SkelVal,SkelToUnify,RHSValue,MatchedValues,1,NrMatches), % TO DO: provide SMTLimit as upper limit
612 NrMatches = Size,
613 is_small_size(Size,NormalLimit,SMTLimit, SID),
614 get_texpr_type(LHSTerm,LHSTermType),
615 InferredLHS = b(member(LHSTerm,b(value(MatchedValues),set(LHSTermType),[])),pred,[generated]).
616 infer_ground_membership(Set,SID,SkelVal,SkelToUnify,BindList,NormalLimit,SMTLimit,Size,InferredLHS) :-
617 ? superset(Set,SuperSet),
618 % e.g., if ID: {1} /\ x -> InferredLHS = {1} and we will add ID : {1} to the LHS of the quantifier and keep ID : {1} /\ x as the RHS
619 infer_ground_mem_aux(SuperSet,SID,SkelVal,SkelToUnify,BindList,NormalLimit,SMTLimit,Size,InferredLHS).
620
621
622 superset(intersection(A,B),Set) :- (Set=A ; Set=B). % Set /\ X <: Set
623 superset(set_subtraction(Set,_),Set). % Set \ X <: Set
624 superset(domain_restriction(_,Set),Set). % X <| Set <: Set
625 superset(domain_subtraction(_,Set),Set). % X <<| Set <: Set
626 superset(range_subtraction(Set,_),Set). % Set |> X <: Set
627 superset(range_restriction(Set,_),Set). % Set |>> X <: Set
628
629 infer_ground_mem_aux(b(Set,T,I),SID,SkelVal,SkelToUnify,BindList,NormalLimit,SMTLimit, Size,InferredLHS) :-
630 (is_small_set(Set,Size,NormalLimit,SMTLimit,I)
631 -> InferredLHS = b(member(SID,b(Set,T,I)),pred,[generated])
632 ; infer_ground_membership(Set,SID,SkelVal,SkelToUnify,BindList,NormalLimit,SMTLimit, Size,InferredLHS)).
633
634 :- use_module(bsyntaxtree, [create_couple/3]).
635 % extract result of constrains_ID BindList into an Expression-Tuple for new membership constraint and a value that will be put into a value(List)
636 extract_bind_list([TID/Val],TID,Val) :- !.
637 extract_bind_list([TID/Val|BList],Couple,(Val,RestVal)) :-
638 create_couple(TID,RestExpr,Couple),
639 extract_bind_list(BList,RestExpr,RestVal).
640
641 :- use_module(kernel_tools,[can_match/2]).
642 % check if we can find a bounded / fixed number of ground matches for Skeleton Value in List
643 has_bounded_ground_matches(Var,_,_,_, _,_,_) :- var(Var),!.
644 has_bounded_ground_matches([],_SkelVal,_SkelToUnify,_,[],LenAcc,LenAcc).
645 has_bounded_ground_matches([H|T],SkelVal,SkelToUnify,ValueToStore,Matches,LenAcc,LenRes) :-
646 (can_match(H,SkelVal) -> copy_term((SkelToUnify,ValueToStore),(H,HValueToStore)),
647 ground_value(HValueToStore),
648 Matches = [HValueToStore|MT],
649 A1 is LenAcc+1 ; Matches=MT,A1=LenAcc),
650 has_bounded_ground_matches(T,SkelVal,SkelToUnify,ValueToStore,MT,A1,LenRes).
651
652 % check if the Expr contains ID, i.e., matching Expr with an element of a set will also instantiate and determine TID
653 % TO DO: also accept other patterns: records, sets?,....
654
655 % SkeletonToUnify: a skeleton that can be used to unify with any value and extracts value in BindList
656 constrains_ID(b(E,_,_),AllParas,Parameters,RestParameters,SkeletonValue,SkeletonToUnify,BindList) :-
657 ? constrains_ID_aux(E,AllParas,Parameters,RestParameters,SkeletonValue,SkeletonToUnify,BindList).
658 constrains_ID_aux(couple(A,B),AllParas,Parameters,RestParameters,(V1,V2),(Skel1,Skel2),Bind) :-
659 constrains_ID(A,AllParas,Parameters,Rest1,V1,Skel1,Bind1),
660 constrains_ID(B,AllParas,Rest1,RestParameters,V2,Skel2,Bind2),
661 append(Bind1,Bind2,Bind). % TO DO: use DCGs
662 constrains_ID_aux(rec(F),AllParas,Parameters,RestParameters,record(SkelV),record(SkelU),Bind) :-
663 ? constrains_ID_fields(F,AllParas,Parameters,RestParameters,SkelV,SkelU,Bind).
664 constrains_ID_aux(identifier(ID),AllParas,Parameters,RestParameters,_SkelV,SkelU,Bind) :-
665 % TO DO: allow same id to appear multiple times in expression + allow to re-use parameters in another conjunct
666 ? (select(TID,Parameters,RestParameters), get_texpr_id(TID,ID)
667 -> Bind = [TID/SkelU]
668 ? ; member(ID,AllParas), % we have already used/bound ID; we will use first occurence for skeleton/bind; this one is simply ignored
669 % TO DO: we could try and see whether using the second occurence gives a better result
670 RestParameters=Parameters, Bind=[]
671 ).
672 constrains_ID_aux(value(V),_AllParas,P,P,V,_,[]) :- ground_value(V).% if not ground value we may not be able to compute all possible values for ID
673 constrains_ID_aux(boolean_true,_AllParas,P,P,pred_true,pred_true,[]). % needed ?? everything is compiled anway ?
674 constrains_ID_aux(boolean_false,_AllParas,P,P,pred_false,pred_false,[]). % needed ?? everything is compiled anway ?
675 % Below: allow any other expression as long as it only uses AllParas
676 % e.g. x+1 in : s: 1..20 --> (BOOL*(1..20)) & card({x|x|->(TRUE|->x):s})=10 & card({x|x|->(FALSE|->x+1):s})=10
677 constrains_ID_aux(add(A,B),AllParas,P,P,_,_,[]) :- % basically allow other Parameters or ground values
678 ? constrains_ID(A,AllParas,[],[],_,_,_), constrains_ID(B,AllParas,[],[],_,_,_).
679 constrains_ID_aux(minus(A,B),AllParas,P,P,_,_,[]) :- % TO DO: allow other binary/unary operators ?
680 constrains_ID(A,AllParas,[],[],_,_,_), constrains_ID(B,AllParas,[],[],_,_,_).
681 %constrains_ID_aux(Other,All,P,P,_,_,[]) :- print(other(Other)),nl,fail.
682
683 constrains_ID_fields([],_AllParas,P,P,[],[],[]).
684 constrains_ID_fields([field(Field,Val)|TF],AllParas,Parameters,RestParameters,
685 [field(Field,SkelVal)|TSkelV],[field(Field,SkelUnify)|TSkelU],Bind) :-
686 ? constrains_ID(Val,AllParas,Parameters,Rest1,SkelVal,SkelUnify,Bind1),
687 ? constrains_ID_fields(TF,AllParas,Rest1,RestParameters,TSkelV,TSkelU,Bind2),
688 append(Bind1,Bind2,Bind). % TO DO: use DCGs
689
690 :- use_module(custom_explicit_sets,[efficient_card_for_set/3]).
691
692
693 is_small_set(Val,Size,NormalLimit,SMTLimit,SrcLoc) :-
694 get_small_set_size(Val,Size),
695 is_small_size(Size,NormalLimit,SMTLimit,SrcLoc).
696
697 :- use_module(kernel_card_arithmetic,[safe_mul/3]).
698 :- use_module(kernel_tools,[ground_value/1]).
699 get_small_set_size(value(S),Size) :- !,
700 ground_value(S), % otherwise we could have S=[X] and expand_quantifier will erroneously create multiple solutions for parameter=X
701 efficient_card_for_set(S,Size,C),
702 call(C).
703 get_small_set_size(interval(From,To),Size) :- !,
704 custom_explicit_sets:is_interval_with_integer_bounds(interval(From,To),Low,Up),
705 number(Low), number(Up),
706 (Low > Up -> Size = 1 ; Size is 1+Up-Low).
707 % we provide dom/ran here explicitly as this is often used {i|i:dom(f) ...}
708 get_small_set_size(bool_set,Size) :- !, Size=2.
709 get_small_set_size(domain(b(Val,_,_)),Size) :- !,
710 get_small_domain_set_size(Val,Size). % this is only an upper bound on the size !!
711 get_small_set_size(range(b(Val,_,_)),Size) :- !,
712 get_small_set_size(Val,Size). % this is only an upper bound on the size !!
713 get_small_set_size(cartesian_product(b(A,_,_),b(B,_,_)),Size) :- !,
714 get_small_set_size(A,SizeA), number(SizeA),
715 get_small_set_size(B,SizeB), number(SizeB),
716 safe_mul(SizeA,SizeB,Size), number(Size).
717
718 %get_small_set_size(set_extension(L),Size,_,_,_) :- !, length(L,Size), is_small_size(Size). what if elements itself notknown ?? probably the case as otherwise this would have been compiled into a value
719 %get_small_set_size(sequence_extension(L),Size,_,_,_) :- !, length(L,Size), is_small_size(Size). ditto
720 %get_small_set_size(interval...
721 %get_small_set_size(domain(value([....]))...
722 % for this to work efficiently one should call b_compiler:compile on the predicates before sending them
723 % to b_interpreter_check; otherwise the sets will not yet be in value(_) form
724
725 % TO DO: the same for range or find more principled solution
726 %get_small_domain_set_size(value(S),Size) :- var(S), frozen(S,Frozen), print(var_value(S,Frozen)),nl,fail.
727 get_small_domain_set_size(value(Val),Size) :- nonvar(Val), Val=[H|T],!,
728 efficient_card_for_set([H|T],Size,C),
729 ground_domain([H|T]), % rather than requiring ground of entire list; we only require ground for domain (see test 1272)
730 call(C).
731 get_small_domain_set_size(Val,Size) :-
732 get_small_set_size(Val,Size).
733 ground_domain(V) :- var(V),!,fail.
734 ground_domain([]).
735 ground_domain([H|T]) :-
736 nonvar(H), H=(D,_),
737 ground_value(D), ground_domain(T).
738
739 :- use_module(performance_messages).
740 is_small_size(Size,NormalLimit,SMTLimit,SrcLoc) :- number(Size), %Size \= inf,
741 (Size < NormalLimit -> true
742 ; preferences:preference(use_smt_mode,true)
743 -> preference(solver_strength,SS),
744 (Size < SMTLimit + SS
745 -> true
746 ; perfmessage(reify,'Not reifiying quantifier, try increasing SOLVER_STRENGTH: ','>'(Size,'+'(SMTLimit,SS)),SrcLoc),
747 fail
748 )
749 ; perfmessage(reify,'Not reifiying quantifier, try setting SMT preference: ','>'(Size,limit(NormalLimit)),SrcLoc),
750 fail
751 ).
752
753 % -------------------------------------
754 % EXPRESSIONS
755
756 :- use_module(store,[set_up_localstate/4]).
757
758 wd_set_up_localstate_for_let(Ids,Exprs,LocalState,State,LetState,WFD) :-
759 set_up_localstate(Ids,Vars,LocalState,LetState),
760 wd_compute_let_expressions(Exprs,Vars,LetState,State,WFD).
761 wd_compute_let_expressions([],[],_,_,_).
762 wd_compute_let_expressions([Expr|RestExprs],[Var|RestVars],LocalState,State,WFD) :-
763 b_wd_compute_expression(Expr,LocalState,State,Value,WFD),
764 kernel_objects:equal_object_optimized(Var,Value,compute_let_expressions),
765 wd_compute_let_expressions(RestExprs,RestVars,LocalState,State,WFD).
766
767
768 % compute a Prolog list of expressions:
769 b_wd_compute_expressions([], _, _, [],_WFD).
770 b_wd_compute_expressions([EXPRsHd|EXPRsTl],LocalState,State,[ValHd|ValTl],WFD) :-
771 b_wd_compute_expression(EXPRsHd,LocalState,State,ValHd,WFD),
772 b_wd_compute_expressions(EXPRsTl,LocalState,State,ValTl,WFD).
773
774 % we have to avoid trying to compute certain expressions: evaluation can fail if not well-defined !
775 b_wd_compute_expression(Expr,LocalState,State,Value,wfwd(WF,WDE,WDV,_)) :- !,
776 (nonvar(WDV)
777 -> (WDE==WDV
778 -> % print('REQUIRED: '), translate:print_bexpr(Expr),nl,
779 ? if(b_compute_expression(Expr,LocalState,State,Value,WF), % TO DO: we could use fresh variable for Value
780 true,
781 (kernel_objects:unbound_value(Value), % we have a WD error, if nonvar it could be because we expect a wrong value
782 add_wd_error_span('Well-definedness error evaluating expression: ',Expr,span_predicate(Expr,LocalState,State),WF)
783 %Value = term(undefined),
784 )
785 )
786 ; instantiate_to_any_value(Value,Expr,WF))
787 ; always_wd_no_fail_nor_error(Expr)
788 -> % print('ALWAYS WD: '), translate:print_bexpr(Expr),nl, %
789 ? b_compute_expression(Expr,LocalState,State,Value,WF)
790 ; b_compiler:b_optimize(Expr,[],LocalState,State,CExpr,WF),
791 % try compiling; this will inline values and may make the expression well_defined; relevant for test 2013
792 (always_wd_no_fail_nor_error(CExpr)
793 % it is important that this computation cannot fail and cannot raise any errors
794 % an example showing this is :wde f=[2,4] & xx:1..3 & (xx=1 or f(xx-1)=4) with -p TRY_FIND_ABORT TRUE
795 % even though the whole expression is well-defined, the function call f(xx-1) does lead
796 % to an error with xx=1
797 -> b_compute_expression(CExpr,LocalState,State,Value,WF)
798 ; % print('DELAYING DUE TO WD: '), translate:print_bexpr(CExpr),nl, %%
799 b_compute_expression_delay(WDE,WDV, CExpr,LocalState,State,Value,WF)
800 )
801 ).
802 b_wd_compute_expression(Expr,LocalState,State,Value,WFD) :-
803 add_internal_error('Illegal WFD value: ', b_wd_compute_expression(Expr,LocalState,State,Value,WFD)),fail.
804
805
806 always_wd_no_fail_nor_error(Expr) :-
807 always_well_defined(Expr).
808 % should not use always_well_defined_or_disprover_mode or WD discharged information!
809
810 :- block b_compute_expression_delay(?,-, ?,?,?,?,?).
811 b_compute_expression_delay(WDE,WDV,Expr,LocalState,State,Value,WF) :-
812 (WDE==WDV
813 -> % print('WD Evaluation: '), print(WDE),print(' =?= '), print(WDV), print(' '),translate:print_bexpr(Expr),nl,
814 b_compute_expression(Expr,LocalState,State,Value,WF)
815 ; %print(instantiate_to_any_value(Value,Expr)),nl,
816 instantiate_to_any_value(Value,Expr,WF) % does not matter anyway; but there can be pending co-routines :-(
817 ).
818
819 % WARNING: the variable could be used in another context, where it is relevant !
820
821
822 wd_delay(WDCall,Res, Expr,wfwd(WF,WDExpected,WDV,_)) :-
823 (WDExpected==WDV -> call(WDCall) % WDV truth value on left is ok: we can evaluate
824 ; nonvar(WDV) -> instantiate_to_any_value(Res,Expr,WF) % truth value not ok; we do not need the value
825 ; always_wd_no_fail_nor_error(Expr) -> call(WDCall)
826 ; wd_delay_block(WDCall,Res,Expr,WDExpected,WDV,WF)).
827 :- block wd_delay_block(?,?,?,?,-,?).
828 wd_delay_block(WDCall,Res,Expr,WDExpected,WDV,WF) :-
829 (WDExpected==WDV -> call(WDCall)
830 ; instantiate_to_any_value(Res,Expr,WF)).
831
832
833 :- use_module(typing_tools,[any_value_for_type/2]).
834 :- use_module(kernel_tools,[ground_value_check/2]).
835 %instantiate_to_any_value(V,E,_) :- print(instantiate_to_any_value(V)),nl,translate:print_bexpr(E),nl,nl,fail.
836 instantiate_to_any_value(V,_,_) :- ground_value(V),!.
837 instantiate_to_any_value(V,b(_B,TYPE,_I),WF) :-
838 get_enumeration_finished_wait_flag(WF,EWF),
839 ground_value_check(V,GV),
840 blocking_any_value_for_type(EWF,GV,TYPE,V).
841
842 :- block blocking_any_value_for_type(-,-,?,?).
843 blocking_any_value_for_type(_,_,TYPE,V) :- any_value_for_type(TYPE,V). % , print(inst2(TYPE,V)),translate:print_bexpr(b(_B,TYPE,_I)),nl.
844
845
846 :- block propagagate_wfwd(-,?,?,-,?), propagagate_wfwd(?,-,?,-,?).
847 % propagate expected and actual value guarding left with actual predicate value obtained for left
848 propagagate_wfwd(WDE,WDV,Res,F1,F2) :-
849 (F1==F2 -> Res=F1 % then value of WDE does not matter at all; Res always the same
850 ; propagagate_wfwd2(WDE,WDV,Res,F1,F2)).
851
852 :- block propagagate_wfwd2(-,?,?,?,?), propagagate_wfwd2(?,-,?,?,?).
853 propagagate_wfwd2(WDE,WDV,Res,F1,F2) :- (WDE==WDV -> Res=F1 ; Res=F2).
854
855 :- use_module(external_functions,[external_fun_has_wd_condition/1]).
856 :- use_module(preferences).
857 b_check_boolean_expression4(exists(Parameters,Body),Info,LocalState,State,WFD,OkToStore,Res) :- !,
858 if(b_check_exists_wfwd(Parameters,Body,Info,LocalState,State,WFD,OkToStore,Res),true,
859 (perfmessagecall(reify,cannot_reify_exists(Parameters),translate:print_bexpr(Body),Body),
860 fail)).
861 b_check_boolean_expression4(Pred,Infos,LocalState,State,WFD,ok_to_store,Res) :-
862 ? b_check_boolean_expression4_ok(Pred,Infos,LocalState,State,WFD,Res).
863
864 b_check_boolean_expression4_ok(equal(LHS,RHS),_,LocalState,State,WFD,EqRes) :- !,
865 ? b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
866 b_wd_compute_expression(RHS,LocalState,State,RHValue,WFD),
867 get_texpr_type(LHS,Type), get_wf(WFD,WF),
868 equality_objects_with_type_wf(Type,LHValue,RHValue,EqRes,WF).
869 % we may need to improve not_member for closure to invert symbolic operators
870 b_check_boolean_expression4_ok(member(LHS,RHS),Info,LocalState,State,WFD,Res) :-
871 %member_check_should_be_reified(LHS,RHS), % no longer need this: symbolic operators will be kept as closures if large ?!
872 !,
873 get_texpr_expr(RHS,ERHS),
874 ? b_check_member_expression(ERHS,RHS,LHS,Info,LocalState,State,WFD,Res).
875 % TO DO: compile forall, exists + setup choice point if expansion fails + remove compile calls in b_interpreter
876 b_check_boolean_expression4_ok(forall(Parameters,LHS,RHS),Info,LocalState,State,WFD,Res) :- !,
877 ? if(b_check_forall_wfwd(Parameters,LHS,RHS,Info,LocalState,State,WFD,Res),true,
878 (perfmessagecall(reify,cannot_reify_forall(Parameters),translate:print_bexpr(LHS),LHS),
879 fail)).
880 b_check_boolean_expression4_ok(subset(LHS,RHS),_,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
881 ? b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
882 ? b_wd_compute_expression(RHS,LocalState,State,RHValue,WFD),
883 subset_test(LHValue,RHValue,Res,WF).
884 b_check_boolean_expression4_ok(subset_strict(LHS,RHS),_,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
885 b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
886 b_wd_compute_expression(RHS,LocalState,State,RHValue,WFD),
887 subset_strict_test(LHValue,RHValue,Res,WF).
888 b_check_boolean_expression4_ok(external_pred_call(FunName,Args),Info,LocalState,State,WFD,Res) :-
889 !,
890 (external_fun_has_wd_condition(FunName)
891 -> wd_delay_until_needed(WFD,b_check_external_pred_call(FunName,Args,Info,LocalState,State,WFD,Res))
892 ; b_check_external_pred_call(FunName,Args,Info,LocalState,State,WFD,Res)).
893 b_check_boolean_expression4_ok(freetype_case(FT,IsCase,Expr),_Infos,LocalState,State,WFD,Res) :- !,
894 b_wd_compute_expression(Expr,LocalState,State,freeval(FT,ActualCase,_A),WFD),
895 eq_atomic(IsCase,ActualCase,freeval_case,Res).
896 b_check_boolean_expression4_ok(finite(Expr),_Infos,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
897 b_wd_compute_expression(Expr,LocalState,State,ExprVal,WFD),
898 kernel_objects:test_finite_set_wf(ExprVal,Res,WF).
899 b_check_boolean_expression4_ok(partition(Expr,ListOfSets),_Infos,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
900 b_wd_compute_expression(Expr,LocalState,State,ExprVal,WFD),
901 b_wd_compute_expressions(ListOfSets,LocalState,State,PartitionList,WFD), % arg is a Prolog list, not a set
902 ? kernel_objects:test_partition_wf(ExprVal,PartitionList,Res,WF).
903 b_check_boolean_expression4_ok(Pred,_,LocalState,State,WFD,Res) :-
904 arithmetic_op(Pred,Op,LHS,RHS),!,
905 ? b_wd_compute_expression(LHS,LocalState,State,int(LHValue),WFD),
906 ? b_wd_compute_expression(RHS,LocalState,State,int(RHValue),WFD),
907 check_arithmetic_operator(Op,LHValue,RHValue,Res).
908 b_check_boolean_expression4_ok(Pred,_,LocalState,State,WFD,Res) :-
909 real_arithmetic_op(Pred,Op,LHS,RHS),!,
910 b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
911 b_wd_compute_expression(RHS,LocalState,State,RHValue,WFD),
912 get_wf(WFD,WF),
913 real_comp_wf(Op,LHValue,RHValue,Res,WF).
914 % TO DO ???: use idea of b_artihmetic_expression to avoid intermediate CLPFD variables
915 % TO DO: add other operators, ...
916 /* use_smt_mode = full is never set; at some point we should enable the following clause by default
917 b_check_boolean_expression4_ok(Pred,Infos,LocalState,State,wfwd(WF,WDE,WDV,ContextInfos),Res) :-
918 % preferences:preference(use_smt_mode,full), %% comment out to enable check testing of complicated predicates inside;
919 % caused slowdowns of cbtc/actions_cbtc.mch (test 1751); but no longer the case
920 functor(Pred,F,N),format('~n Cannot reify ~w/~w~n~n',[F,N]),fail,
921 %ContextInfo \= outer_wfwd_context,
922 b_check_boolean_expression4_delay(WDE,WDV,Pred,Infos,LocalState,State,WF,Res).
923 */
924
925 :- use_module(library(lists),[maplist/3]).
926 % TO DO: add member(,pow_subset, fin_subset) --> subset_test
927 % we could distribute RHS=union -> disjunction, LHS=intersection -> conjunction ,... ?
928 %b_check_member_expression(EHRS,_RHS,_LHS,_,_LocalState,_State,_WFD,_Res) :-
929 % print('member : '), print(EHRS),nl,fail.
930 %b_check_member_expression(union(A,B),LHS,_,LocalState,State,WFD,Res) :-
931 b_check_member_expression(pow_subset(RHS),_,LHS,_Info,LocalState,State,WFD,Res) :- !,
932 b_check_boolean_expression4_ok(subset(LHS,RHS),[],LocalState,State,WFD,Res).
933 %b_check_member_expression(NotContainingEmptySet,_TRHS,LHS,LocalState,State,WFD,Res) :-
934 % non_empty_set_version_of(NotContainingEmptySet,RHS_With_EmptySet),
935 % % translate x:seq1(RHS) -> x /= {} & x:seq(RHS), ...
936 % % this improves propagation, in particular in light of WD issues
937 % % TO DO: avoid computing LHS twice !
938 % !,
939 % get_texpr_type(LHS,LType),
940 % EMPTYVERSION = b(member(LHS,b(RHS_With_EmptySet,set(LType),[])),pred,[]),
941 % NOTEMPTYPRED = b(not_equal(LHS,b(empty_set,LType,[])),pred,[]),
942 % print('Translating : '), translate:print_bexpr(EMPTYVERSION), print(' & '), translate:print_bexpr(NOTEMPTYPRED),nl,
943 % empty_avl(Ai), Infos=[], % Infos not important for conjunction
944 % b_check_boolean_expression2(conjunct(EMPTYVERSION,NOTEMPTYPRED),Infos,LocalState,State,WFD,Res,Ai,_).
945 b_check_member_expression(interval(Low,Up),_,LHS,_Info,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
946 % to do: should we also match interval value closure
947 b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
948 b_wd_compute_expression(Low,LocalState,State,LowValue,WFD),
949 b_wd_compute_expression(Up,LocalState,State,UpValue,WFD),
950 kernel_objects:test_in_nat_range_wf(LHValue,LowValue,UpValue,Res,WF).
951 b_check_member_expression(set_extension(SetExt),_RHS,LHS,_Info,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
952 % rewrite x:{a,b,c} into x=a or x=b or x=c (is the opposite of rewrite_disjunct_to_member)
953 % The rewrite_disjunct_to_member is good when we know a membership to be true; the disjunct is better for reification
954 % Note: the problem is in particular when the result of the membership is not needed and an uninstantiated
955 % variable is used in the set extension, example y:dom(f) => (x:{f(y),0} or f(y)=0)
956 % print(mem_check_set_extension),print(' '),translate:print_bexpr(b(member(LHS,_RHS),pred,[])),nl,
957 b_wd_compute_expressions(SetExt,LocalState,State,SetExtValues,WFD),
958 b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
959 get_texpr_type(LHS,Type),
960 NewLHS = b(value(LHValue),Type,[]),
961 (ground_value(SetExtValues)
962 -> % better to use normal treatment, we can compute the entire set and translate it into an AVL tree
963 maplist(construct_value(Type),SetExtValues,Vals),
964 b_wd_compute_expression(b(set_extension(Vals),set(Type),[]),LocalState,State,RHValue,WFD),
965 membership_test_wf(RHValue,LHValue,Res,WF),
966 force_membership_test(Res,LHValue,RHValue,WF)
967 ; maplist(construct_equality(NewLHS,Type),SetExtValues,Disjuncts),
968 construct_norm_disjunct2(Disjuncts,NC,InfoNC),
969 empty_avl(Ai),
970 b_check_boolean_expression2(NC,InfoNC,LocalState,State,WFD,Res,Ai,_)
971 ).
972 b_check_member_expression(closure(Relation),_RHS,LHS,Info,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
973 b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
974 b_wd_compute_expression(Relation,LocalState,State,RelValue,WFD),
975 opt_push_wait_flag_call_stack_info(WF,b_operator_call(member,
976 [LHValue,b_operator(closure,[RelValue])],Info),WF2), % this is closure1
977 bsets_clp:in_closure1_membership_test_wf(LHValue,RelValue,Res,WF2).
978 b_check_member_expression(partial_function(Dom,Range),_RHS,LHS,Info,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
979 b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
980 b_wd_compute_expression(Dom,LocalState,State,DomValue,WFD),
981 b_wd_compute_expression(Range,LocalState,State,RangeValue,WFD),
982 opt_push_wait_flag_call_stack_info(WF,b_operator_call(member,
983 [LHValue,b_operator(partial_function,[DomValue,RangeValue])],Info),WF2),
984 bsets_clp:partial_function_test_wf(LHValue,DomValue,RangeValue,Res,WF2).
985 b_check_member_expression(total_function(Dom,Range),_RHS,LHS,Info,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
986 b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
987 b_wd_compute_expression(Dom,LocalState,State,DomValue,WFD),
988 b_wd_compute_expression(Range,LocalState,State,RangeValue,WFD),
989 opt_push_wait_flag_call_stack_info(WF,b_operator_call(member,
990 [LHValue,b_operator(total_function,[DomValue,RangeValue])],Info),WF2),
991 bsets_clp:total_function_test_wf(LHValue,DomValue,RangeValue,Res,WF2).
992 b_check_member_expression(partial_surjection(Dom,Range),_RHS,LHS,Info,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
993 b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
994 b_wd_compute_expression(Dom,LocalState,State,DomValue,WFD),
995 b_wd_compute_expression(Range,LocalState,State,RangeValue,WFD),
996 opt_push_wait_flag_call_stack_info(WF,b_operator_call(member,
997 [LHValue,b_operator(partial_surjection,[DomValue,RangeValue])],Info),WF2),
998 bsets_clp:partial_surjection_test_wf(LHValue,DomValue,RangeValue,Res,WF2).
999 b_check_member_expression(seq1(SeqType),_RHS,LHS,Info,LocalState,State,WFD,Res) :- !, get_wf(WFD,WF),
1000 b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
1001 b_wd_compute_expression(SeqType,LocalState,State,SeqTValue,WFD),
1002 opt_push_wait_flag_call_stack_info(WF,b_operator_call(member,
1003 [LHValue,b_operator(seq1,[SeqTValue])],Info),WF2),
1004 ? bsets_clp:test_finite_non_empty_sequence(LHValue,SeqTValue,Res,WF2).
1005 % TODO: more sequence checks
1006 b_check_member_expression(_Arg,RHS,LHS,_Info,LocalState,State,WFD,Res) :- get_wf(WFD,WF),
1007 ? b_wd_compute_expression(LHS,LocalState,State,LHValue,WFD),
1008 b_wd_compute_expression(RHS,LocalState,State,RHValue,WFD),
1009 membership_test_wf(RHValue,LHValue,Res,WF),
1010 %(var(Res) -> add_message(reify,member,LHS,_Info) ; true),
1011 force_membership_test(Res,LHValue,RHValue,WF).
1012
1013 % -------------------------
1014
1015 % wfwd/4 add information about WD context to a WF store: wfwd(WF_store, ExpectedVal, Val,Infos)
1016 % when Val becomes nonvar: if Val==ExpectedVal we need the value of E, otherwise it should be discarded
1017
1018 % get WF store from WFD record
1019 get_wf(wfwd(WF,_,_,_),Res) :- !, Res=WF.
1020 get_wf(WFD,WF) :- add_internal_error('Illegal WFD store: ',get_wf(WFD,WF)),
1021 WF = no_wf_available.
1022
1023 % get expected PredicateResult and actual value; if both identical the associated expression is needed
1024 get_wd(wfwd(_,WDExpected,WDVal,_),WDE,WDV) :- !, (WDExpected,WDVal)=(WDE,WDV).
1025 get_wd(WFWD,WDE,WDV) :- add_internal_error('Illegal WFWD info:',get_wd(WFWD,WDE,WDV)), WDE=pred_true,WDV=pred_true.
1026
1027 % create a WFWF construct for an expression that is needed and where reification should only succeed
1028 % if the top-level construct at least can be fully reified (without non-determinism)
1029 create_wfwd_needed(WF,wfwd(WF,pred_true,pred_true,outer_wfwd_context)).
1030
1031 create_wfwd(WF,WDExpected,WDVal,wfwd(WF,WDExpected,WDVal,inner_wfwd_context)).
1032
1033 :- public portray_wfwd/1.
1034 portray_wfwd(wfwd(_,WDExpected,WDVal,Ctxt)) :-
1035 format('Sub-formula required if ~w is expected ~w (ctxt: ~w)~n',[WDVal,WDExpected,Ctxt]).
1036
1037 % ----------------------
1038
1039 construct_value(Type,Val,b(value(Val),Type,[])).
1040
1041 :- use_module(bsyntaxtree, [safe_create_texpr/3]).
1042 construct_equality(NewLHS,Type,ElementV,Equality) :-
1043 Element = b(value(ElementV),Type,[]),
1044 safe_create_texpr(equal(NewLHS,Element),pred,Equality). %, translate:print_bexpr(Equality),nl.
1045
1046 %non_empty_set_version_of(seq1(RHS),seq(RHS)).
1047 %non_empty_set_version_of(iseq1(RHS),iseq(RHS)).
1048 %non_empty_set_version_of(fin1_subset(RHS),fin_subset(RHS)).
1049 %non_empty_set_version_of(pow1_subset(RHS),pow_subset(RHS)).
1050
1051 % check a boolean expression without reification attempt: wait until result is known or waitflag triggered
1052 % can be useful for predicates which we know cannot be reified
1053 b_force_check_boolean_expression(b(Pred,pred,Infos),LocalState,State,WF,Res) :-
1054 b_check_boolean_expression4_delay(pred_true,pred_true,Pred,Infos,LocalState,State,WF,Res).
1055
1056 :- block b_check_boolean_expression4_delay(?,-,?,?,?,?,?,?).
1057 % currently only used for existential quantified predicates in data_validation_mode
1058 b_check_boolean_expression4_delay(WDE,WDV,_Pred,_Infos,_,_,_WF,Res) :- WDE \= WDV,
1059 % no need to check reify_inner_exists_non_deterministically, as we have marked _Pred as do_not_store
1060 % ignoring (not evaluating) predicate
1061 !,
1062 Res=pred_false. % does not matter here (but Res could have been in another context, see above and test 2404)
1063 b_check_boolean_expression4_delay(_WDE,_WDV,Pred,Infos,LocalState,State,WF,Res) :-
1064 % we currently have not yet implemented a way to check the Pred; wait until Result is known
1065 (preferences:preference(use_smt_mode,false)
1066 -> get_last_wait_flag(b_check_test_boolean_expression,WF,WF2)
1067 ; get_binary_choice_wait_flag(b_check_test_boolean_expression,WF,WF2)
1068 ),
1069 (debug:debug_mode(on) -> print(' Check Testing: '),translate:print_bexpr(Pred),nl ; true),
1070 b_check_test_boolean_expression(Res,WF2,b(Pred,pred,Infos),LocalState,State,WF).
1071
1072 :- block b_check_test_boolean_expression(-,-,?,?,?,?).
1073 %b_check_test_boolean_expression(P,LWF,Pred,LocalState,State,WF) :- write(check_test4(P,LWF)),nl,fail.
1074 b_check_test_boolean_expression(pred_true,_,Pred,LocalState,State,WF) :-
1075 b_test_boolean_expression(Pred,LocalState,State,WF).
1076 b_check_test_boolean_expression(pred_false,_,Pred,LocalState,State,WF) :-
1077 ? b_interpreter:b_not_test_boolean_expression(Pred,LocalState,State,WF).
1078
1079
1080 /*
1081 :- use_module(kernel_mappings).
1082 member_check_should_be_reified(_,b(RHS,_,_)) :- functor(RHS,BOP,Arity), print(check(BOP,Arity)),nl,!.
1083 member_check_should_be_reified(_,_) :- \+ preferences:preference(use_smt_mode,false),!.
1084 member_check_should_be_reified(_LHS,b(RHS,_,_)) :- functor(RHS,BOP,Arity),
1085 % check if we have optimized treatments available, for which we do not yet have reified versions
1086 (Arity=1 -> \+ kernel_mappings:unary_in_boolean_type(BOP,_)
1087 ; Arity=2 -> \+ kernel_mappings:binary_in_boolean_type(BOP,_)
1088 ; Arity=0 -> \+ kernel_mappings:cst_in_boolean_type(BOP,_)
1089 ; true).
1090 */
1091
1092
1093 :- block force_membership_test(-,?,?,?).
1094 % currently required for ensuring that following fails:
1095 % kernel_objects:union(closure(['_zzzz_unit_tests'],[integer],b(member(b(identifier('_zzzz_unit_tests'),integer,[generated]),b(value([int(3),int(4)]),set(integer),[])),pred,[])),closure(['_zzzz_unit_tests'],[integer],b(member(b(identifier('_zzzz_unit_tests'),integer,[generated]),b(value([int(2),int(1)]),set(integer),[])),pred,[])),[int(1),int(3),int(2)])
1096 % Reason: membership_test does not on its own enumerate
1097 force_membership_test(pred_true,X,Set,WF) :-
1098 Set \= [],
1099 (ground_value(X) -> true
1100 ; nonvar(Set),no_use_forcing(Set) -> true % no use in forcing membership, will call same element_of_avl_set_wf
1101 ; kernel_objects:check_element_of_wf(X,Set,WF)
1102 ).
1103 force_membership_test(pred_false,_X,_Set,_WF).
1104
1105 % forcing is sometimes useful because we can transmit a WF, currently some of the reification predicates
1106 % do not have a WF-Store and can thus do limited enumeration ! in particular true for CLPFD = FALSE mode
1107 no_use_forcing(avl_set(_)) :- preferences:preference(use_clpfd_solver,true).
1108 no_use_forcing(global_set(_)).
1109 %no_use_forcing(closure(_,_,B)) :- preferences:preference(use_clpfd_solver,true).
1110
1111
1112
1113 :- use_module(external_functions,[call_external_predicate/8, do_not_evaluate_args/1]).
1114 b_check_external_pred_call(FunName,Args,Info,LocalState,State,WFD,Res) :-
1115 get_wf(WFD,WF),
1116 (do_not_evaluate_args(FunName) -> EvaluatedArgs=[]
1117 ; b_wd_compute_expressions(Args, LocalState,State, EvaluatedArgs, WFD)),
1118 push_wait_flag_call_stack_info(WF,external_call(FunName,EvaluatedArgs,Info),WF2),
1119 call_external_predicate(FunName,Args,EvaluatedArgs,LocalState,State,Res,Info,WF2).
1120
1121 wd_delay_until_needed(WFWD,Call) :-
1122 get_wd(WFWD,WDExpected,WDV),
1123 wd_delay_until_needed_block(WDExpected,WDV,Call).
1124 :- block wd_delay_until_needed_block(-,?,?), wd_delay_until_needed_block(?,-,?).
1125 wd_delay_until_needed_block(WDExpected,WDV,Call) :- WDExpected==WDV,!,
1126 call(Call).
1127 wd_delay_until_needed_block(_,_,_). % first call not needed
1128
1129
1130 :- use_module(library(avl)).
1131 reuse_predicate(_,_,no_avl) :- !,fail.
1132 reuse_predicate(Pred,Var,AVL) :-
1133 avl_fetch(Pred,AVL,Var),!. %pred_var(Var)).
1134 reuse_predicate(Pred,Var,AVL) :- %print(check(Pred)),nl, portray_avl(AVL),nl,
1135 preferences:preference(use_smt_mode,true), % it does not seem very expensive; we could always enable it
1136 ? implied_by(Pred,Val,OtherPred,OVal),
1137 avl_fetch(OtherPred,AVL,OVar), OVar==OVal,!,
1138 %print(reused_due_to_implication(Pred)),nl,nl,
1139 Var=Val.
1140
1141 add_predicate(_Pred,_Var,no_avl,NewAVL) :- !, NewAVL=no_avl.
1142 add_predicate(Pred,Var,AVL,NewAVL) :-
1143 % we could compute terms:term_hash(Pred,H) and add pred(H,Pred) to AVL to avoid comparing terms during avl_fetch
1144 (avl_store(Pred,AVL,Var,NewAVL) -> true ; NewAVL=no_avl). %pred_var(Var),NewAVL).
1145
1146 % detect whether predicate implied by some registered predicate
1147 % detects inconsistency in x:INTEGER & x>y & y>x
1148 % very lightweight propagation also achieved by CHR for less
1149 implied_by(less(A,B),pred_false,less(B,A),pred_true). % A>B => not( A<B ) <=> A>=B
1150 implied_by(subset_strict(A,B),pred_false,subset_strict(B,A),pred_true). % B <<: A => not( A<<:B )
1151 implied_by(subset_strict(A,B),pred_false,subset(B,A),pred_true). % B <: A => not( A<<:B )
1152 implied_by(subset(A,B),pred_false,subset_strict(B,A),pred_true). % B <<: A => not( A<:B )
1153 % TO DO: add more rules; e.g., less(x,10) implied by less(x,9)
1154
1155 :- use_module(translate,[print_bexpr/1]).
1156 % normalises a typed predicate by removing position information and ordering commutative operators in a canonical way
1157 norm_pred_check(B,Res) :-
1158 ( norm_pred(B,Res)
1159 -> true
1160 ; bget_functor(B,F,N),
1161 print(norm_pred_failed(F/N)), nl,
1162 print_bexpr(B), nl,
1163 Res=B
1164 ).
1165
1166 bget_functor(b(B,_,_),F,N) :- functor(B,F,N).
1167 bget_functor(B,F,N) :- functor(B,F,N).
1168
1169 %% :-(+List, -UntypedConj).
1170 conjunct_untyped([], Res) :- !, Res=truth.
1171 conjunct_untyped([P|Rest],Result) :- conjunct2(Rest,P,Result).
1172 conjunct2([],P,P).
1173 conjunct2([Q|Rest],P,Result) :- conjunct2(Rest,conjunct(P,Q),Result).
1174
1175 %% disjunct_untyped(+List, -UntypedDisj).
1176 disjunct_untyped([], Res) :- !, Res=falsity.
1177 disjunct_untyped([P|Rest],Result) :- disjunct2(Rest,P,Result).
1178 disjunct2([],P,P).
1179 disjunct2([Q|Rest],P,Result) :- disjunct2(Rest,disjunct(P,Q),Result).
1180
1181 :- assert_must_succeed((I=b(identifier(i),integer,[]),P1=b(greater_equal(I,I),pred,[]),norm_pred(P1,N1),
1182 P2=b(greater_equal(I,I),pred,[info]),norm_pred(P2,N2), N2==N1)). % info ignored
1183 :- assert_must_succeed((I1=b(identifier(i1),integer,[]),I2=b(identifier(i2),integer,[]),
1184 P1=b(equal(I1,I2),pred,[]),norm_pred(P1,N1),
1185 P2=b(equal(I2,I1),pred,[info]),norm_pred(P2,N2), N2==N1)). % equal re-ordered
1186 :- assert_must_succeed((I1=b(identifier(i1),integer,[]),I2=b(identifier(i2),integer,[]),
1187 P1=b(greater_equal(I1,I2),pred,[]),norm_pred(P1,N1),
1188 P2=b(less_equal(I2,I1),pred,[info]),norm_pred(P2,N2), N2==N1)). % <= and >= re-ordered
1189 :- assert_must_succeed((I1=b(identifier(i1),integer,[]),I2=b(identifier(i2),integer,[]),
1190 P1=b(greater(I1,I2),pred,[]),norm_pred(P1,N1),
1191 P2=b(less(I2,I1),pred,[info]),norm_pred(P2,N2), N2==N1)). % < and > re-ordered
1192 :- assert_must_succeed((I1=b(identifier(i1),integer,[]),I2=b(identifier(i2),integer,[]),
1193 P1=b(greater(I1,I2),pred,[]),norm_pred(P1,N1),
1194 P2=b(less_equal(I2,I1),pred,[]),norm_pred(P2,N2), N2 \= N1)). % > and <= not made equal
1195 :- assert_must_succeed((I=b(identifier(i),integer,[]),P1=b(greater_equal(I,I),pred,[was(test1)]),
1196 P2=b(not_equal(I,I),pred,[was(test2)]),
1197 conjunct_predicates_with_pos_info([P1,P2],C1),norm_pred(C1,N1),
1198 conjunct_predicates_with_pos_info([P2,P1],C2),norm_pred(C2,N2), N2==N1)). % conjunct re-ordered
1199 :- assert_must_succeed((I=b(identifier(i),integer,[]),P1=b(greater_equal(I,I),pred,[was(test1)]),
1200 P2=b(not_equal(I,I),pred,[was(test2)]), P3=b(equal(I,I),pred,[was(test3)]),
1201 conjunct_predicates_with_pos_info([P1,P2,P3],C1),norm_pred(C1,N1),
1202 conjunct_predicates_with_pos_info([P2,P3,P1],C2),norm_pred(C2,N2), N2==N1)).
1203
1204 %% norm_pred(+AstOrExpr, -Norm).
1205 norm_pred(X,Res) :- var(X),!,Res=X.
1206 norm_pred(b(B,_,_),Res) :- !, norm_pred(B,Res).
1207 norm_pred(falsity,Res) :- !, Res=falsity.
1208 norm_pred(truth,Res) :- !, Res=truth.
1209 norm_pred(conjunct(A,B),Res) :-
1210 !,
1211 flatten_conjunctions([A,B],CList),
1212 % sort nested conjunctions and disjunctions instead of only single ones
1213 % e.g., difference for '#i.(i : NATURAL & (i > `max`(self) & num′ = num <+ {self |-> i}))' if removing nested parentheses
1214 l_norm_pred(CList, NormedList),
1215 sort(NormedList,SortedList), % better to sort after normalisation
1216 conjunct_untyped(SortedList, Res).
1217 norm_pred(disjunct(A,B),Res) :-
1218 !,
1219 disjunction_to_list(b(disjunct(A,B),pred,[]), CList), % it would be more efficient not to re-construct the b/3 term
1220 l_norm_pred(CList, NormedList),
1221 sort(NormedList,SortedList),
1222 disjunct_untyped(SortedList, Res).
1223 norm_pred(equal(A,B),Res) :- !,norm_expr(A,AA),norm_expr(B,BB),
1224 (BB @< AA -> Res = equal(AA,BB) ; Res= equal(BB,AA)).
1225 norm_pred(equivalence(A,B),Res) :- !, norm_pred(A,AA), norm_pred(B,BB),
1226 (BB @< AA -> Res = equivalence(AA,BB) ; Res= equivalence(BB,AA)).
1227 norm_pred(exists(A,B),Res) :- !, Res=exists(AA,BB),l_norm_expr(A,AA), norm_pred(B,BB).
1228 norm_pred(finite(A),finite(AA)) :- !,norm_expr(A,AA).
1229 norm_pred(forall(A,B,C),Res) :- !, Res=forall(AA,BB,CC),l_norm_expr(A,AA), norm_pred(B,BB), norm_pred(C,CC).
1230 norm_pred(greater(A,B),Less) :- !,norm_expr(A,AA),norm_expr(B,BB), norm_less(BB,AA,Less).
1231 norm_pred(greater_equal(A,B),Leq) :- !,norm_expr(A,AA),norm_expr(B,BB), norm_less_equal(BB,AA,Leq).
1232 norm_pred(implication(A,B),Res) :- !, % we could rewrite this to disjunct(not(A),B); but check ok for WD prover
1233 Res=implication(AA,BB),norm_pred(A,AA), norm_pred(B,BB).
1234 norm_pred(less(A,B),Less) :- !,norm_expr(A,AA),norm_expr(B,BB), norm_less(AA,BB,Less).
1235 norm_pred(less_real(A,B),less_real(AA,BB)) :- !,norm_expr(A,AA),norm_expr(B,BB).
1236 norm_pred(less_equal(A,B),Leq) :- !,norm_expr(A,AA),norm_expr(B,BB), norm_less_equal(AA,BB,Leq).
1237 norm_pred(less_equal_real(A,B),less_equal_real(AA,BB)) :- !,norm_expr(A,AA),norm_expr(B,BB).
1238 norm_pred(let_predicate(A,B,C),Res) :- !,
1239 Res=let_predicate(AA,BB,CC),
1240 l_norm_expr(A,AA), l_norm_expr(B,BB),norm_pred(C,CC).
1241 norm_pred(lazy_let_pred(A,B,C),Res) :- !,
1242 Res = lazy_let_pred(AA,BB,CC),
1243 norm_expr(A,AA),
1244 norm_pred_or_expr(B,BB),norm_pred(C,CC).
1245 norm_pred(lazy_lookup_pred(A),Res) :- !, Res = lazy_lookup_pred(A).
1246 norm_pred(member(A,B),member(AA,BB)) :- !,norm_expr(A,AA),norm_expr(B,BB).
1247 norm_pred(negation(A),Res) :- !,
1248 (negate_typed_pred(A,NegA) -> norm_pred(NegA,Res)
1249 ; Res=negation(AA), norm_pred(A,AA)).
1250 norm_pred(not_equal(A,B),Res) :- !,norm_expr(A,AA),norm_expr(B,BB),
1251 (BB @< AA -> Res = not_equal(AA,BB) ; Res= not_equal(BB,AA)).
1252 norm_pred(not_member(A,B),not_member(AA,BB)) :- !,norm_expr(A,AA),norm_expr(B,BB).
1253 norm_pred(not_subset(A,B),not_subset(AA,BB)) :- !,norm_expr(A,AA),norm_expr(B,BB).
1254 norm_pred(not_subset_strict(A,B),not_subset_strict(AA,BB)) :- !,norm_expr(A,AA),norm_expr(B,BB).
1255 norm_pred(partition(A,L),partition(AA,LL)) :- !,norm_expr(A,AA),l_norm_expr(L,LL).
1256 norm_pred(subset(A,B),subset(AA,BB)) :- !,norm_expr(A,AA),norm_expr(B,BB).
1257 norm_pred(subset_strict(A,B),subset_strict(AA,BB)) :- !,norm_expr(A,AA),norm_expr(B,BB).
1258 norm_pred(freetype_case(Type,Case,A),freetype_case(Type,Case,AA)) :- !,norm_expr(A,AA).
1259 norm_pred(X,X). % :- print(norm_pred(X)),nl.
1260
1261
1262 l_norm_pred([],[]).
1263 l_norm_pred([H|T],[NH|NT]) :- norm_pred(H,NH), l_norm_pred(T,NT).
1264
1265 norm_pred_or_expr(b(B,pred,_),Res) :- norm_pred(B,Res).
1266 norm_pred_or_expr(B,Res) :- norm_expr(B,Res).
1267
1268 norm_less(unary_minus(A),MB,Res) :- apply_unary_minus(MB,B), !,norm_less(B,A,Res). % -A < -B => A > B
1269 % we could also move unary_minus to B if not present
1270 norm_less(MA,unary_minus(B),Res) :- apply_unary_minus(MA,A), !,norm_less(B,A,Res).
1271 norm_less(A,B,less(A,B)).
1272
1273 apply_unary_minus(unary_minus(A),A).
1274 apply_unary_minus(Nr,MNr) :- number(Nr), MNr is -Nr.
1275
1276 norm_less_equal(unary_minus(A),MB,Res) :- apply_unary_minus(MB,B), !,norm_less_equal(B,A,Res). % -A <= -B => A >= B
1277 norm_less_equal(MA,unary_minus(B),Res) :- apply_unary_minus(MA,A), !,norm_less_equal(B,A,Res).
1278 norm_less_equal(A,B,less_equal(A,B)).
1279
1280 % ---------------------
1281
1282 % generic normalisation predicate
1283 norm_check(BExpr,Res) :- BExpr = b(_,pred,_),!, norm_pred_check(BExpr,Res).
1284 norm_check(BExpr,Res) :- norm_expr_check(BExpr,Res).
1285
1286 % normalise expressions and check for failure
1287 norm_expr_check(X,Res) :- var(X),!,Res=X.
1288 norm_expr_check(b(B,_,_),Res) :- !, norm_expr_check2(B,Res).
1289 norm_expr_check(X,X).
1290
1291 norm_expr_check2(B,Res) :-
1292 (norm_expr2(B,Res) -> true
1293 ; functor(B,F,N),print(norm_expr2_failed(F/N)),nl,
1294 Res=B).
1295
1296 norm_expr(X,Res) :- var(X),!,Res=X.
1297 norm_expr(b(B,_,_),Res) :- !, norm_expr2(B,Res).
1298 %norm_expr_check2(B,Res). %% comment in to obtain details about failed normalisation for expressions
1299 norm_expr(X,X). % :- add_internal_error('Expr not wrapped:',norm_expr(X,X)).
1300
1301 norm_expr2(assertion_expression(Cond,E,Expr),assertion_expression(AA,E,BB)) :- norm_pred(Cond,AA),norm_expr(Expr,BB).
1302 norm_expr2(add(A,B),Res) :- norm_expr(A,AA), norm_expr(B,BB), (BB @< AA -> Res = add(AA,BB) ; Res= add(BB,AA)).
1303 norm_expr2(add_real(A,B),add_real(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1304 norm_expr2(bag_items(A),bag_items(AA)) :- norm_expr(A,AA).
1305 norm_expr2(boolean_false,boolean_false).
1306 norm_expr2(boolean_true,boolean_true).
1307 norm_expr2(bool_set,bool_set).
1308 norm_expr2(card(A),card(AA)) :- norm_expr(A,AA).
1309 norm_expr2(cartesian_product(A,B),cartesian_product(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1310 norm_expr2(closure(A),closure(AA)) :- norm_expr(A,AA). % this is closure1
1311 norm_expr2(compaction(A),compaction(AA)) :- norm_expr(A,AA).
1312 norm_expr2(composition(A,B),composition(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1313 norm_expr2(comprehension_set(A,B),comprehension_set(AA,BB)) :- l_norm_expr(A,AA), norm_pred(B,BB).
1314 norm_expr2(concat(A,B),concat(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1315 norm_expr2(convert_bool(A),convert_bool(AA)) :- norm_pred_check(A,AA).
1316 norm_expr2(convert_real(A),convert_real(AA)) :- norm_expr(A,AA).
1317 norm_expr2(convert_int_floor(A),convert_int_floor(AA)) :- norm_expr(A,AA).
1318 norm_expr2(convert_int_ceiling(A),convert_int_ceiling(AA)) :- norm_expr(A,AA).
1319 norm_expr2(couple(A,B),couple(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1320 norm_expr2(direct_product(A,B),direct_product(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1321 norm_expr2(div(A,B),div(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1322 norm_expr2(div_real(A,B),div_real(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1323 norm_expr2(floored_div(A,B),floored_div(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1324 norm_expr2(domain_restriction(A,B),domain_restriction(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1325 norm_expr2(domain_subtraction(A,B),domain_subtraction(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1326 norm_expr2(domain(A),domain(AA)) :- norm_expr(A,AA).
1327 norm_expr2(empty_sequence,empty_sequence).
1328 norm_expr2(empty_set,empty_set).
1329 norm_expr2(event_b_identity,event_b_identity).
1330 norm_expr2(external_function_call(A,B),external_function_call(A,BB)) :- l_norm_expr(B,BB).
1331 norm_expr2(fin_subset(A),fin_subset(AA)) :- norm_expr(A,AA).
1332 norm_expr2(fin1_subset(A),fin1_subset(AA)) :- norm_expr(A,AA).
1333 norm_expr2(first(A),first(AA)) :- norm_expr(A,AA).
1334 norm_expr2(first_of_pair(A),first_of_pair(AA)) :- norm_expr(A,AA).
1335 norm_expr2(first_projection(A,B),first_projection(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1336 norm_expr2(float_set,float_set).
1337 norm_expr2(front(A),front(AA)) :- norm_expr(A,AA).
1338 norm_expr2(function(A,B),function(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1339 norm_expr2(general_concat(A),general_concat(AA)) :- norm_expr(A,AA).
1340 norm_expr2(general_intersection(A),general_intersection(AA)) :- norm_expr(A,AA).
1341 norm_expr2(general_product(A,B,C),Res) :- !,
1342 Res=general_product(AA,BB,CC),l_norm_expr(A,AA), norm_pred(B,BB), norm_expr(C,CC).
1343 norm_expr2(general_sum(A,B,C),Res) :- !,
1344 Res=general_sum(AA,BB,CC),l_norm_expr(A,AA), norm_pred(B,BB), norm_expr(C,CC).
1345 norm_expr2(general_union(A),general_union(AA)) :- norm_expr(A,AA).
1346 norm_expr2(identifier(A),'$'(A)). % need wrapper to avoid confusion with other terms !
1347 norm_expr2(identity(A),identity(AA)) :- norm_expr(A,AA).
1348 norm_expr2(if_then_else(P,A,B),if_then_else(PP,AA,BB)) :- norm_pred(P,PP),norm_expr(A,AA), norm_expr(B,BB).
1349 norm_expr2(image(A,B),image(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1350 norm_expr2(insert_front(A,B),insert_front(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1351 norm_expr2(insert_tail(A,B),insert_tail(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1352 norm_expr2(integer_set(A),A).
1353 norm_expr2(integer(A),A). % integer represented as number
1354 norm_expr2(intersection(A,B),Res) :- norm_expr(A,AA), norm_expr(B,BB),
1355 (BB @< AA -> Res = intersection(AA,BB) ; Res= intersection(BB,AA)).
1356 norm_expr2(interval(A,B),interval(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1357 norm_expr2(iseq(A),iseq(AA)) :- norm_expr(A,AA).
1358 norm_expr2(iseq1(A),iseq1(AA)) :- norm_expr(A,AA).
1359 norm_expr2(iteration(A,B),iteration(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1360 norm_expr2(last(A),last(AA)) :- norm_expr(A,AA).
1361 norm_expr2(lazy_let_expr(A,B,C),lazy_let_expr(AA,BB,CC)) :-
1362 norm_expr(A,AA),norm_pred_or_expr(B,BB),norm_expr(C,CC).
1363 norm_expr2(lazy_lookup_expr(A),lazy_lookup_expr(A)) :- !.
1364 norm_expr2(let_expression(A,B,C),let_expression(AA,BB,CC)) :- l_norm_expr(A,AA), l_norm_expr(B,BB),norm_expr(C,CC).
1365 norm_expr2(let_expression_global(A,B,C),let_expression_global(AA,BB,CC)) :- l_norm_expr(A,AA), l_norm_expr(B,BB),norm_pred(C,CC).
1366 norm_expr2(max(A),max(AA)) :- norm_expr(A,AA).
1367 norm_expr2(max_real(A),max_real(AA)) :- norm_expr(A,AA).
1368 norm_expr2(max_int,max_int).
1369 norm_expr2(min(A),min(AA)) :- norm_expr(A,AA).
1370 norm_expr2(min_real(A),min_real(AA)) :- norm_expr(A,AA).
1371 norm_expr2(min_int,min_int).
1372 norm_expr2(minus(A,B),minus(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1373 norm_expr2(minus_real(A,B),minus_real(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1374 norm_expr2(modulo(A,B),modulo(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1375 norm_expr2(mu(A),mu(AA)) :- norm_expr(A,AA).
1376 norm_expr2(multiplication(A,B),Res) :-
1377 norm_expr(A,AA), norm_expr(B,BB), (BB @< AA -> Res = multiplication(AA,BB) ; Res= multiplication(BB,AA)).
1378 norm_expr2(multiplication_real(A,B),multiplication_real(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1379 norm_expr2(operation_call_in_expr(A,B),operation_call_in_expr(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1380 norm_expr2(overwrite(A,B),overwrite(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1381 norm_expr2(parallel_product(A,B),parallel_product(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1382 norm_expr2(partial_bijection(A,B),partial_bijection(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1383 norm_expr2(partial_function(A,B),partial_function(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1384 norm_expr2(partial_injection(A,B),partial_injection(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1385 norm_expr2(partial_surjection(A,B),partial_surjection(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1386 norm_expr2(perm(A),perm(AA)) :- norm_expr(A,AA).
1387 norm_expr2(power_of(A,B),power_of(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1388 norm_expr2(power_of_real(A,B),power_of_real(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1389 norm_expr2(pow_subset(A),pow_subset(AA)) :- norm_expr(A,AA).
1390 norm_expr2(pow1_subset(A),pow1_subset(AA)) :- norm_expr(A,AA).
1391 norm_expr2(predecessor,predecessor).
1392 % quantified_intersection, quantified_union : should be removed by ast_cleanup
1393 norm_expr2(range_restriction(A,B),range_restriction(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1394 norm_expr2(range_subtraction(A,B),range_subtraction(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1395 norm_expr2(range(A),range(AA)) :- norm_expr(A,AA).
1396 norm_expr2(real(Atom),real(Atom)). % we could use the atom? or convert it to a real number using construct_real
1397 norm_expr2(real_set,real_set).
1398 norm_expr2(rec(A),rec(AA)) :- norm_fields(A,AA).
1399 norm_expr2(record_field(A,Field),record_field(AA,Field)) :- norm_expr(A,AA).
1400 norm_expr2(relations(A,B),relations(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1401 norm_expr2(restrict_front(A,B),restrict_front(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1402 norm_expr2(restrict_tail(A,B),restrict_tail(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1403 norm_expr2(reflexive_closure(A),reflexive_closure(AA)) :- norm_expr(A,AA). % this is rewritten in ast_cleanup
1404 norm_expr2(rev(A),rev(AA)) :- norm_expr(A,AA).
1405 norm_expr2(reverse(A),reverse(AA)) :- norm_expr(A,AA).
1406 norm_expr2(second_of_pair(A),second_of_pair(AA)) :- norm_expr(A,AA).
1407 norm_expr2(second_projection(A,B),second_projection(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1408 norm_expr2(seq(A),seq(AA)) :- norm_expr(A,AA).
1409 norm_expr2(seq1(A),seq1(AA)) :- norm_expr(A,AA).
1410 norm_expr2(sequence_extension(L),sequence_extension(NL)) :- l_norm_expr(L,NL).
1411 norm_expr2(set_extension(L),set_extension(NL)) :- l_norm_expr(L,NL).
1412 norm_expr2(set_subtraction(A,B),set_subtraction(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB). % set difference
1413 norm_expr2(size(A),size(AA)) :- norm_expr(A,AA).
1414 norm_expr2(string(A),string(A)). % need wrapper to avoid confusion with other terms !
1415 norm_expr2(string_set,string_set).
1416 norm_expr2(struct(A),struct(AA)) :- norm_expr(A,AA).
1417 norm_expr2(successor,successor).
1418 norm_expr2(surjection_relation(A,B),surjection_relation(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1419 norm_expr2(tail(A),tail(AA)) :- norm_expr(A,AA).
1420 norm_expr2(total_bijection(A,B),total_bijection(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1421 norm_expr2(total_function(A,B),total_function(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1422 norm_expr2(total_injection(A,B),total_injection(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1423 norm_expr2(total_relation(A,B),total_relation(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1424 norm_expr2(total_surjection(A,B),total_surjection(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1425 norm_expr2(total_surjection_relation(A,B),total_surjection_relation(AA,BB)) :- norm_expr(A,AA), norm_expr(B,BB).
1426 norm_expr2(typeset,typeset).
1427
1428 norm_expr2(unary_minus(A),unary_minus(AA)) :- norm_expr(A,AA).
1429 norm_expr2(unary_minus_real(A),unary_minus_real(AA)) :- norm_expr(A,AA).
1430 norm_expr2(union(A,B),Res) :- norm_expr(A,AA), norm_expr(B,BB), (BB @< AA -> Res = union(AA,BB) ; Res= union(BB,AA)).
1431 norm_expr2(value(A),NA) :- norm_value(A,NA).
1432
1433 norm_expr2(freetype_set(T),freetype_set(T)).
1434 norm_expr2(freetype_constructor(FT,Case,A), freetype_constructor(FT,Case,AA)) :- norm_expr(A,AA).
1435 norm_expr2(freetype_destructor(FT,Case,A),freetype_destructor(FT,Case,AA)) :- norm_expr(A,AA).
1436 norm_expr2(recursive_let(A,B),recursive_let(AA,BB)) :- norm_expr(A,AA),norm_expr(B,BB).
1437
1438
1439 norm_fields([],[]).
1440 norm_fields([field(Name,H)|T],[field(Name,NH)|NT]) :- norm_expr(H,NH), norm_fields(T,NT).
1441
1442 l_norm_expr([],[]).
1443 l_norm_expr([H|T],[NH|NT]) :- norm_expr(H,NH), l_norm_expr(T,NT).
1444
1445 :- use_module(closures,[is_member_closure/5]).
1446 norm_value(V,R) :- var(V),!,R=value(V).
1447 norm_value(int(Nr),R) :- number(Nr),!,R=Nr.
1448 norm_value([],R) :- !, R=empty_set.
1449 norm_value(pred_false,R) :- !, R=boolean_false.
1450 norm_value(pred_true,R) :- !, R=boolean_true.
1451 norm_value(closure(P,T,B),R) :-
1452 (is_member_closure(P,T,B,_,Set) % peel useless member closure wrapper, see test 2483
1453 -> !, norm_expr_check2(Set,R)
1454 ; norm_pred_check(B,NB)
1455 -> !, % normalising relevant for test 1544 with position info added by construct_member_closure
1456 R=value(closure(P,T,NB))
1457 ).
1458 norm_value((A,B),R) :- !, R=(NA,NB), norm_value(A,NA), norm_value(B,NB).
1459 norm_value(rec(Fields),rec(NFields)) :- !, norm_field_values(Fields,NFields).
1460 norm_value(V,value(V)). % we could normalise AVL, or pairs
1461
1462 norm_field_values([],[]).
1463 norm_field_values([field(Name,H)|T],[field(Name,NH)|NT]) :- norm_inner_value(H,NH), norm_field_values(T,NT).
1464
1465 % norm inside values; e.g., getting rid of info fields of closures, see test 2483
1466 norm_inner_value((A,B),R) :- !, R=(NA,NB), norm_inner_value(A,NA), norm_inner_value(B,NB).
1467 norm_inner_value(rec(Fields),rec(NFields)) :- !, norm_field_values(Fields,NFields).
1468 norm_inner_value(closure(P,T,B),R) :- norm_pred_check(B,NB),!,
1469 R=closure(P,T,NB).
1470 % TODO: inside sets ? but AVL sets contain no closures
1471 norm_inner_value(V,V).
1472
1473
1474 arithmetic_op(less(LHS,RHS),'<',LHS,RHS).
1475 arithmetic_op(less_equal(LHS,RHS),'<=',LHS,RHS).
1476 arithmetic_op(greater(LHS,RHS),'<',RHS,LHS).
1477 arithmetic_op(greater_equal(LHS,RHS),'<=',RHS,LHS).
1478
1479 :- use_module(probsrc(kernel_reals),[real_comp_wf/5]).
1480 % these two predicates can be checked by real_comp_wf:
1481 real_arithmetic_op(less_real(LHS,RHS),'<',LHS,RHS).
1482 real_arithmetic_op(less_equal_real(LHS,RHS),'=<',LHS,RHS).
1483
1484 :- use_module(clpfd_interface).
1485 :- use_module(library(clpfd), [(#<=>)/2]).
1486 check_arithmetic_operator('<',X,Y,Res) :- check_less(X,Y,Res),
1487 (nonvar(Res) -> true
1488 ; clpfd_interface:try_post_constraint((X#<Y) #<=> R01), prop_pred_01(Res,R01)).
1489 check_arithmetic_operator('<=',X,Y,Res) :- check_less_than_equal(X,Y,Res),
1490 (nonvar(Res) -> true
1491 ; clpfd_interface:try_post_constraint((X#=<Y) #<=> R01), prop_pred_01(Res,R01)).
1492
1493
1494 :- block prop_pred_01(-,-).
1495 prop_pred_01(A,B) :- B==1,!,A=pred_true. % cut ok: either pred_true or 1 set
1496 prop_pred_01(pred_true,1).
1497 prop_pred_01(pred_false,0).
1498
1499 :- block check_less(-,?,-), check_less(?,-,-).
1500 check_less(X,Y,Res) :- nonvar(Res),!, /* truth value known: enforce it */
1501 (Res=pred_true -> less_than_direct(X,Y) ; less_than_equal_direct(Y,X)).
1502 check_less(X,Y,Res) :-
1503 X < Y,!,/* we could call safe_less_than(X,Y), */
1504 Res=pred_true.
1505 check_less(_,_,pred_false).
1506 :- block check_less_than_equal(-,?,-), check_less_than_equal(?,-,-).
1507 check_less_than_equal(X,Y,Res) :- nonvar(Res),!, /* truth value known: enforce it */
1508 (Res=pred_true -> less_than_equal_direct(X,Y) ; less_than_direct(Y,X)).
1509 check_less_than_equal(X,Y,Res) :- X =< Y,!,Res=pred_true.
1510 check_less_than_equal(_,_,pred_false).
1511
1512
1513
1514 :- use_module(bool_pred).
1515
1516 :- use_module(kernel_objects,[exhaustive_kernel_check_wf/2,
1517 exhaustive_kernel_check/1, exhaustive_kernel_check/2, exhaustive_kernel_fail_check/1]).
1518
1519 :- assert_must_succeed(exhaustive_kernel_check_wf(b_interpreter_check:conjoin(pred_false,pred_false,pred_false,b(truth,pred,[]),b(truth,pred,[]),WF),WF)).
1520 :- assert_must_succeed(exhaustive_kernel_check_wf(b_interpreter_check:conjoin(pred_false,pred_true,pred_false,b(truth,pred,[]),b(truth,pred,[]),WF),WF)).
1521 :- assert_must_succeed(exhaustive_kernel_check_wf(b_interpreter_check:conjoin(pred_true,pred_false,pred_false,b(truth,pred,[]),b(truth,pred,[]),WF),WF)).
1522 :- assert_must_succeed(exhaustive_kernel_check_wf(b_interpreter_check:conjoin(pred_true,pred_true,pred_true,b(truth,pred,[]),b(truth,pred,[]),WF),WF)).
1523 :- assert_must_fail(b_interpreter_check:conjoin(pred_true,pred_false,pred_true,b(truth,pred,[]),b(truth,pred,[]),_WF)).
1524 :- assert_must_fail(b_interpreter_check:conjoin(pred_true,pred_true,pred_false,b(truth,pred,[]),b(truth,pred,[]),_WF)).
1525
1526
1527 % same as and_equality/3 but for pred_false/pred_true rather than eq_obj/pred_false
1528 :- block conjoin(-,-,-,?,?,?).
1529 conjoin(X,Y,Res,LHS,RHS,WF) :- % print(conjoin(X,Y,Res)),nl, translate:print_bexpr(LHS),nl,%
1530 ( Res==pred_true -> X=pred_true,Y=pred_true % on SWI these propagations happen one after the other, see test 2202
1531 ; X==pred_true -> Res=Y
1532 ; X==pred_false -> Res=pred_false
1533 ; Y==pred_true -> Res=X
1534 ; Y==pred_false -> Res=pred_false
1535 ? ; Res==pred_false -> conjoin_false0(X,Y,LHS,RHS,WF)
1536 ; add_error_fail(conjoin,'Illegal values: ', conjoin(X,Y,Res,LHS,RHS,WF))
1537 ).
1538 conjoin_false0(X,Y,_LHS,_RHS,_WF) :- X==Y,!,
1539 %print(conjoin_false_eqeq(X,Y)),nl, translate:print_bexpr(_LHS),nl,
1540 X=pred_false.
1541 conjoin_false0(X,Y,_LHS,_RHS,_WF) :- % X & not(X) -> always false
1542 bool_negate_check(X,Y),!
1543 . %,print(conjoin_false_neqeq(X,Y)),nl,translate:print_bexpr(_LHS),nl.
1544 conjoin_false0(X,Y,LHS,RHS,WF) :-
1545 %%Prio=1, %%
1546 %%(preferences:preference(use_smt_mode,full) -> FullPrio=1.5 ;
1547 get_priority_of_boolean_expression(LHS,Prio),
1548 (preferences:preference(use_clpfd_solver,true) ->
1549 % relevant for tests 349, 362:
1550 count_number_of_conjuncts(RHS,NrC),
1551 FullPrio is Prio+(NrC-1)/10,
1552 get_wait_flag(FullPrio,conjoin,WF,LWF) %%
1553 ; % in non-clpfd mode: much less propagation going on, avoid explosion of choice points
1554 % tests 349, 362 fail with the following for CLPFD: TO DO investigate and use this also in CLPFD mode
1555 get_binary_choice_wait_flag_exp_backoff(Prio,not_conjunct,WF,LWF)
1556 ),
1557 ? conjoin_false(X,Y,LHS,RHS,LWF).
1558 % missing rule: if X==Y -> X=pred_true
1559 :- block conjoin_false(-,-,?,?,-).
1560 conjoin_false(X,Y,LHS,_RHS,_LWF) :-
1561 ( X==pred_true -> pred_false=Y
1562 ; X==pred_false -> true
1563 ; Y==pred_true -> pred_false=X
1564 ; Y==pred_false -> true
1565 ; useless_to_force(LHS) ->
1566 ( % print(forcing_conjoin_rhs_false(X,Y,_LWF)), translate:print_bexpr(_RHS), print(' == FALSE '),nl,
1567 Y=pred_false
1568 ;
1569 (Y,X)=(pred_true,pred_false)
1570 )
1571 ; ( % print(forcing_conjoin_lhs_false(X,Y,_LWF)), translate:print_bexpr(LHS), print(' == FALSE '),nl,
1572 X=pred_false
1573 ; % print(forcing_conjoin_rhs_false(X,Y,_LWF)), translate:print_bexpr(LHS), print(' == TRUE ; '), nl,
1574 (X,Y)=(pred_true,pred_false)
1575 )
1576 ).
1577
1578 % determine when forcing a predicate to true/false does not really help; better choose something else
1579 useless_to_force(b(B,T,I)) :- useless_to_force3(B,T,I).
1580 useless_to_force3(finite(_),_,_). % forcing finite to be false usually not a good idea; we cannot propagate this
1581 % what are other predicates useless to force: some foralls/exists ? some external_pred_call
1582 % in principle a conjunction of useless predicates is also useless: but could be more expensive to check
1583
1584 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:disjoin(pred_false,pred_false,pred_false,_,_,_WF))).
1585 :- assert_must_succeed(exhaustive_kernel_check([commutative],b_interpreter_check:disjoin(pred_false,pred_true,pred_true,_,_,_WF))).
1586 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:disjoin(pred_true,pred_true,pred_true,_,_,_WF))).
1587 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:disjoin(pred_true,pred_true,pred_false,_,_,_WF))).
1588 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:disjoin(pred_true,pred_false,pred_false,_,_,_WF))).
1589 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:disjoin(pred_false,pred_true,pred_false,_,_,_WF))).
1590 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:disjoin(pred_false,pred_false,pred_true,_,_,_WF))).
1591
1592 :- block disjoin(-,-,-,?,?,?).
1593 disjoin(X,Y,Res,LHS,RHS,WF) :-
1594 %print(disjoin(X,Y,Res,WF)),nl, %% translate:print_bexpr(LHS),print(' or '),translate:print_bexpr(RHS),nl,%%
1595 ( Res==pred_false -> X=pred_false,Y=pred_false
1596 ; X==pred_true -> Res=pred_true
1597 ; X==pred_false -> Res=Y
1598 ; Y==pred_true -> Res=pred_true
1599 ; Y==pred_false -> Res=X
1600 ? ; Res==pred_true -> disjoin_true0(X,Y,LHS,RHS,WF)
1601 ; add_error_fail(disjoin,'Illegal values: ',disjoin(X,Y,Res,LHS,RHS,WF))
1602 ).
1603 disjoin_true0(X,Y,_LHS,_RHS,_WF) :- X==Y,!,
1604 X=pred_true.
1605 %disjoin_true0(X,Y,LHS,_,WF) :- !, disjoin_true(X,Y,_).
1606 disjoin_true0(X,Y,_LHS,_RHS,_WF) :- % X or not(X) -> always true
1607 bool_negate_check(X,Y),!.
1608
1609 disjoin_true0(X,Y,LHS,_RHS,WF) :-
1610 %%(preferences:preference(use_smt_mode,full) -> FullPrio=2.5 ;
1611 % poses problem for test 1096:
1612 % count_number_of_disjuncts(RHS,NrC),
1613 %FullPrio is Prio+(NrC-1)/10,
1614 %get_wait_flag(FullPrio,disjoin,WF,LWF), %%
1615 get_priority_of_boolean_expression(LHS,StartPrio),
1616 get_binary_choice_wait_flag_exp_backoff(StartPrio,disjunct,WF,LWF),
1617 % TO DO: extract FD information from LHS and RHS and assert, e.g. x:1..2 or x:4..5
1618 ? disjoin_true(X,Y,LHS,LWF).
1619 % missing rule: if X==Y -> X=pred_true ; if X==~Y -> no need to setup choice point
1620 :- block disjoin_true(-,-,?,-).
1621 disjoin_true(X,Y,LHS,_LWF) :-
1622 ( X==pred_true -> true
1623 ; X==pred_false -> pred_true=Y
1624 ; Y==pred_true -> true
1625 ; Y==pred_false -> pred_true=X
1626 ; useless_to_force(LHS) ->
1627 ( %% print(forcing_disjoin_true(X,Y,_LWF)),nl, %%
1628 Y=pred_true
1629 ;
1630 %%print(forcing_disjoin_false(X,Y,_LWF)),nl,
1631 (Y,X) = (pred_false,pred_true) % these two unifications will happen atomically !
1632 )
1633 ; ( %% print(forcing_disjoin_true(X,Y,_LWF)),nl, %%
1634 X=pred_true
1635 ;
1636 %%print(forcing_disjoin_false(X,Y,_LWF)),nl,
1637 (X,Y) = (pred_false,pred_true) % these two unifications will happen atomically !
1638 )
1639 %add_error_fail(disjoin_true,'Illegal values: ',disjoin_true(X,Y))
1640 ).
1641
1642 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:imply(pred_false,pred_false,pred_true))).
1643 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:imply(pred_false,pred_true,pred_true))).
1644 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:imply(pred_true,pred_false,pred_false))).
1645 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:imply(pred_true,pred_true,pred_true))).
1646 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:imply(pred_false,pred_false,pred_false))).
1647 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:imply(pred_false,pred_true,pred_false))).
1648 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:imply(pred_true,pred_false,pred_true))).
1649 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:imply(pred_true,pred_true,pred_false))).
1650
1651 imply(X,Y,Res) :-
1652 (var(X),var(Y),var(Res) -> bool_equality(X,Y,EqXY) ; true /* impl4 will not block anyway */),
1653 impl4(X,Y,EqXY,Res).
1654 :- block impl4(-,-,-,-).
1655 impl4(X,Y,EqXY,Res) :-
1656 ( Res==pred_false -> X=pred_true,Y=pred_false
1657 ; Res==pred_true -> imply_true3(X,Y,EqXY)
1658 ; X==pred_false -> Res=pred_true
1659 ; X==pred_true -> Res=Y
1660 ; Y==pred_true -> Res=pred_true
1661 ; Y==pred_false -> negate(X,Res)
1662 ; EqXY==pred_true -> Res=pred_true % X => X is always true
1663 ; EqXY==pred_false -> Y=Res % not(Y) => Y is true iff Y is true
1664 ; add_error_fail(impl,'Illegal values: ',imply(X,Y,EqXY,Res))
1665 ).
1666
1667 % assert X=pred_true => Y=pred_true
1668 imply_true(X,Y) :-
1669 (var(X),var(Y) -> bool_equality(X,Y,EqXY) ; true /* imply_true will not block anyway */),
1670 ? imply_true3(X,Y,EqXY).
1671 :- block imply_true3(-,-,-).
1672 imply_true3(X,Y,EqXY) :-
1673 ( X==pred_false -> true
1674 ; X==pred_true -> Y=pred_true
1675 ; Y==pred_true -> true
1676 ; Y==pred_false -> X=pred_false
1677 ; EqXY==pred_true -> true
1678 ; EqXY==pred_false -> X=pred_false % X => not(X) ===> X=pred_false
1679 ; add_error_fail(imply_true,'Illegal values: ',imply_true3(X,Y,EqXY))
1680 ).
1681
1682
1683 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:equiv(pred_false,pred_false,pred_true))).
1684 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:equiv(pred_false,pred_true,pred_false))).
1685 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:equiv(pred_true,pred_false,pred_false))).
1686 :- assert_must_succeed(exhaustive_kernel_check(b_interpreter_check:equiv(pred_true,pred_true,pred_true))).
1687 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:equiv(pred_false,pred_false,pred_false))).
1688 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:equiv(pred_false,pred_true,pred_true))).
1689 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:equiv(pred_true,pred_false,pred_true))).
1690 :- assert_must_succeed(exhaustive_kernel_fail_check(b_interpreter_check:equiv(pred_true,pred_true,pred_false))).
1691
1692 % b_interpreter_check:equiv(X,Y,Res),X=Y, Res==pred_true
1693 equiv(X,Y,Res) :-
1694 bool_equality(X,Y,Res).
1695
1696