1 % (c) 2009-2019 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
6 :- module(custom_explicit_sets,[is_set_value/2,
7 is_custom_explicit_set/1, is_custom_explicit_set/2, is_custom_explicit_set_nonvar/1,
8 %equal_explicit_sets/2,
9 equal_explicit_sets_wf/3,
10 not_equal_explicit_sets/2,
11 equality_explicit_sets/3,
12 is_empty_explicit_set/1, is_empty_explicit_set_wf/2, is_empty_closure_wf/4,
13 is_non_empty_explicit_set/1, is_non_empty_explicit_set_wf/2,
14 test_empty_explicit_set/2,
15 is_definitely_maximal_set/1,
16 explicit_set_cardinality/2, explicit_set_cardinality_wf/3,
17 explicit_set_cardinality_for_wf/2,
18 card_for_specific_custom_set/3, % only succeeds if we can compute it efficiently
19 efficient_card_for_set/3, % same, but also for lists
20 quick_custom_explicit_set_approximate_size/2,
21 avl_approximate_size/2, avl_approximate_size/3,
22 is_infinite_explicit_set/1, is_infinite_closure/3,
23 is_infinite_global_set/2,
24 dont_expand_this_explicit_set/1, dont_expand_this_explicit_set/2,
25 dont_expand_symbolic_explicit_set/1,
26 definitely_expand_this_explicit_set/1,
27 mark_closure_as_symbolic/2, mark_closure_as_recursive/2, mark_closure/3,
28 is_symbolic_closure/1, is_symbolic_closure/3,
29 is_recursive_closure/3,
30 is_infinite_or_very_large_explicit_set/1,
31 is_infinite_or_very_large_explicit_set/2,
32 is_cartesian_product_closure/3,
33 expand_custom_set/2, expand_custom_set_wf/4,
34 try_expand_custom_set/2, try_expand_custom_set_wf/4,
35 expand_custom_set_to_list/2, expand_custom_set_to_list/4,
36 expand_custom_set_to_list_wf/5,
37 expand_custom_set_to_list_gg/4,
38 try_expand_custom_set_to_list/4,
39 expand_interval_closure_to_avl/3,
40 expand_custom_set_to_list_now/2,
41 expand_closure_to_avl_or_list/6,
42 expand_only_custom_closure_global/4, %try_expand_only_custom_closure_global/2,
43 expand_and_convert_to_avl_set/2,
44 ord_list_to_avlset_direct/3, sorted_ground_normalised_list_to_avlset/3,
45 try_expand_and_convert_to_avl/2, convert_to_avl/2,
46 should_be_converted_to_avl_from_lists/1, should_be_converted_to_avl/1,
47 try_expand_and_convert_to_avl_with_check/3,
48 try_expand_and_convert_to_avl_unless_large/2,
49 try_expand_and_convert_to_avl_unless_very_large/2,
50 try_expand_and_convert_to_avl_if_smaller_than/3,
51 is_small_specific_custom_set/2,
52 quick_propagation_element_information/4,
53 element_of_custom_set/2, element_of_custom_set_wf/3,
54 element_of_closure/5,
55 check_element_of_function_closure/6,
56 not_element_of_custom_set_wf/3,
57 membership_custom_set/3, membership_custom_set_wf/4, membership_avl_set_wf/4,
58 quick_test_avl_membership/3,
59
60 is_efficient_custom_set/1,
61 remove_minimum_element_custom_set/3,
62
63 is_maximal_global_set/1, quick_is_definitely_maximal_set/1,
64 is_one_element_custom_set/2, singleton_set/2,
65 construct_one_element_custom_set/2,
66
67 %closure0_for_explicit_set/2,
68 closure1_for_explicit_set/2, closure1_for_explicit_set_from/3,
69 check_in_domain_of_avlset/2,
70 domain_of_explicit_set/2, range_of_explicit_set/2,
71 is_avl_partial_function/1,
72 is_avl_total_function_over_domain/2,
73 quick_definitely_maximal_total_function_avl/1,
74 is_avl_relation/1,
75 is_avl_relation_over_domain/3,
76 is_avl_relation_over_range/3,
77 is_not_avl_relation_over_domain_range/4, is_not_avl_relation_over_range/3,
78 is_avl_sequence/1,
79 is_injective_avl_relation/2,
80 invert_explicit_set/2, union_of_explicit_set/3,
81 union_generalized_explicit_set/3,
82 difference_of_explicit_set_wf/4,
83 intersection_of_explicit_set_wf/4, intersection_with_interval_closure/3,
84 image_for_id_closure/3, image_for_explicit_set/4,
85 rel_composition_for_explicit_set/3,
86 element_can_be_added_or_removed_to_avl/1,
87 add_element_to_explicit_set/3, remove_element_from_explicit_set/3,
88 delete_element_from_explicit_set/3,
89 at_most_one_match_possible/3,
90 apply_to_avl_set/5,
91 min_of_explicit_set/2, max_of_explicit_set/2,
92 sum_or_mul_of_explicit_set/3,
93 %sum_of_range_custom_explicit_set/2, mul_of_range_custom_explicit_set/2,
94 domain_restriction_explicit_set_wf/4,
95 range_restriction_explicit_set_wf/4,
96 domain_subtraction_explicit_set_wf/4,
97 range_subtraction_explicit_set_wf/4,
98 override_pair_explicit_set/4,
99 direct_product_explicit_set/3,
100 override_custom_explicit_set_wf/4,
101
102 subset_of_explicit_set/4, not_subset_of_explicit_set/4,
103 test_subset_of_explicit_set/5,
104
105 conc_custom_explicit_set/2,
106 prefix_of_custom_explicit_set/4, suffix_of_custom_explicit_set/4,
107 concat_custom_explicit_set/4, prepend_custom_explicit_set/3,
108 append_custom_explicit_set/4,
109 tail_sequence_custom_explicit_set/4,
110 last_sequence_explicit_set/2, %first_sequence_explicit_set/2,
111 front_sequence_custom_explicit_set/2,
112 reverse_custom_explicit_set/2,
113 size_of_custom_explicit_set/3,
114
115 get_first_avl_elements/4,
116 construct_avl_from_lists/2, equal_avl_tree/2,
117 is_non_expanded_closure/1, % from closures
118 construct_closure/4, is_closure/4, % from closures
119 construct_member_closure/5, % from closures
120
121 construct_interval_closure/3,
122 is_interval_closure/3, is_interval_closure/5,
123 is_interval_closure_or_integerset/3,
124 is_interval_with_integer_bounds/3,
125
126 is_powerset_closure/3,
127
128 dom_range_for_specific_closure/4,
129 dom_for_specific_closure/3,
130 dom_for_lambda_closure/2,
131 portray_custom_explicit_set/1,
132 closure_occurs_check/4
133 ]).
134
135 :- use_module(error_manager).
136 :- use_module(self_check).
137 :- use_module(library(avl)).
138 :- use_module(kernel_waitflags).
139 :- use_module(kernel_tools).
140 :- use_module(delay).
141 :- use_module(tools).
142 :- use_module(avl_tools).
143
144 :- use_module(module_information,[module_info/2]).
145 :- module_info(group,kernel).
146 :- module_info(description,'This module provides customised operations for the custom explicit set representations of ProB (closures, avl_sets and global_sets).').
147
148 :- use_module(tools_printing,[print_term_summary/1, print_error/1]).
149 :- use_module(preferences,[preference/2]).
150 :- use_module(kernel_objects,[equal_object/2, equal_object/3]).
151 :- use_module(kernel_freetypes,[enumerate_freetype/3,freetype_cardinality/2,
152 is_infinite_freetype/1, is_empty_freetype/1,
153 is_non_empty_freetype/1, test_empty_freetype/2]).
154
155 :- use_module(closures).
156 :- use_module(b_compiler).
157
158 :- load_files(library(system), [when(compile_time), imports([environ/2])]).
159
160 /* These meta_predicate declarations do not seem to have the right effect;
161 the predicates below return code, they do not get passed code
162 :- meta_predicate card_for_specific_custom_set(*,*,0).
163 :- meta_predicate card_for_specific_closure(*,*,0).
164 :- meta_predicate is_a_relation(*,*,*,*,*,*,0).
165 :- meta_predicate subset_of_explicit_set(*,*,0,*).
166 :- meta_predicate not_subset_of_explicit_set(*,*,0,*).
167 */
168
169 construct_avl_from_lists(S,Res) :- (convert_to_avl(S,CS) -> true ; print(convert_to_avl_failed(S,CS)),nl,CS=S),
170 %(CS=S -> true ; (print_term_summary(constructed_avl(S,CS)),nl)),
171 % print(construct_avl_from_lists(S,CS,Res)),nl,
172 Res = CS.
173
174 :- use_module(tools,[safe_sort/3]).
175 :- block normalised_list_to_avl_when_ground(-,?).
176 normalised_list_to_avl_when_ground(S,R) :- % call if you are not sure that S will be ground; e.g. after closure expansion
177 ground_value_check(S,GS),
178 blocking_normalised_list_to_avl(GS,S,R).
179 :- block blocking_normalised_list_to_avl(-,?,?).
180 blocking_normalised_list_to_avl(_,S,R) :- normalised_list_to_avl(S,R).
181
182 normalised_list_to_avl(S,R) :- safe_sort(normalised_list_to_avl,S,SS),
183 ord_list_to_avlset_direct(SS,AVL,normalised_list_to_avl),
184 equal_object(AVL,R). % due to co-routine, R can now be instantiated
185
186 %set_to_avl(List,R) :- empty_avl(A), add_to_avl(List,A,AR), R=avl_set(AR).
187 add_to_avl([],R,R).
188 add_to_avl([H|T],AVL,AVLOUT) :- avl_store(H,AVL,true,AVL1),
189 add_to_avl(T,AVL1,AVLOUT).
190
191
192 % get only the first x elements of an AVL tree
193 get_first_avl_elements(empty,_,R,all) :- !,R=[].
194 get_first_avl_elements(AVL,X,FirstXEls,CutOff) :-
195 avl_min(AVL,Min), get_first_els(X,Min,AVL,FirstXEls,CutOff).
196
197 get_first_els(X,_,_AVL,R,CutOff) :- X<1,!,R=[], CutOff=not_all.
198 get_first_els(X,Cur,AVL,[Cur|T],CutOff) :-
199 (avl_next(Cur,AVL,Nxt) -> X1 is X-1,get_first_els(X1,Nxt,AVL,T,CutOff)
200 ; T=[],CutOff=all).
201
202 %expand_and_try_convert_to_avl(C,R) :- is_closure(C,_,_,_), expand_custom_set(C,EC), expand_and_convert_to_avl
203 %expand_and_convert_to_avl(C,R) :- convert_to_avl(C,R).
204
205 /* convert all list data-values (with all-sub-values) into avl-form */
206 /* assumption: the value is ground when convert_to_avl is called */
207
208 :- load_files(library(system), [when(compile_time), imports([environ/2])]).
209 :- if(environ(prob_safe_mode,true)).
210 convert_to_avl(X,R) :- \+ ground_value(X), !, add_error(convert_to_avl,'Non-ground argument: ',convert_to_avl(X,R)), R=X.
211 :- endif.
212 convert_to_avl(X,R) :- var(X), !, add_error(convert_to_avl,'Variable argument: ',convert_to_avl(X,R)), R=X.
213 convert_to_avl(closure(P,T,B),R) :- !, % print(not_converting_closure(P)),nl, %trace,
214 R=closure(P,T,B).
215 %convert_to_avl(closure_x(_P,_T,_B,E),R) :- !, convert_to_avl(E,R).
216 convert_to_avl(avl_set(A),R) :- !,(A==empty -> add_warning(convert_to_avl,'Emtpy avl_set'), R=[]
217 ; R=avl_set(A)).
218 convert_to_avl([],R) :- !,R=[].
219 convert_to_avl((A,B),(CA,CB)) :- !,convert_to_avl(A,CA), convert_to_avl(B,CB).
220 convert_to_avl(fd(A,T),R) :- !, R=fd(A,T).
221 convert_to_avl(int(X),R) :- !, R=int(X).
222 convert_to_avl(string(X),R) :- !, R=string(X).
223 convert_to_avl(term(X),R) :- !, R=term(X).
224 convert_to_avl(freetype(X),R) :- !, R=freetype(X).
225 convert_to_avl(freeval(ID,Case,Value),R) :- !, R=freeval(ID,Case,CValue),convert_to_avl(Value,CValue).
226 convert_to_avl(pred_false /* bool_false */,R) :- !, R=pred_false /* bool_false */.
227 convert_to_avl(pred_true /* bool_true */,R) :- !, R=pred_true /* bool_true */.
228 convert_to_avl(rec(Fields),R) :- !, convert_fields(Fields,CFields), R=rec(CFields).
229 convert_to_avl(global_set(GS),R) :- !, R=global_set(GS).
230 ?convert_to_avl([H|T],R) :- !, convert_cons_to_avl_inside_set(H,T,R).
231 %convert_to_avl(abort(X),_R) :- print(deprecetated_convert_to_avl(abort(X))),nl,!, fail.
232 convert_to_avl(X,R) :- add_internal_error('Unknown term: ',convert_to_avl(X,R)), R=X.
233
234
235 convert_fields(Var,R) :- var(Var),!,
236 add_internal_error('Var arg: ',convert_fields(Var,R)),fail.
237 convert_fields([],[]).
238 convert_fields([field(FieldName,Value)|T],[field(FieldName,CValue)|CT]) :-
239 convert_to_avl_inside_set(Value,CValue),
240 convert_fields(T,CT).
241
242 l_convert_to_avl([],[]).
243 l_convert_to_avl(avl_set(A),R) :- expand_custom_set(avl_set(A),ES,l_convert_to_avl),
244 l_convert_to_avl(ES,R).
245 l_convert_to_avl(closure(P,T,B),R) :- expand_custom_set(closure(P,T,B),ES,l_convert_to_avl),
246 l_convert_to_avl(ES,R).
247 ?l_convert_to_avl([H|T],[CH-true|CT]) :- convert_to_avl_inside_set(H,CH), l_convert_to_avl(T,CT).
248
249 %add_true([],[]).
250 %add_true([H|T],[H-true|TT]) :- add_true(T,TT).
251
252
253 :- assert_must_succeed((X=(fd(1,'Name'),fd(2,'Name')),
254 custom_explicit_sets:convert_to_avl_inside_set(X,R), R==X)).
255
256 convert_to_avl_inside_set(Var,R) :- var(Var),!,
257 add_internal_error('Var arg: ',convert_to_avl_inside_set(Var,R)),fail.
258 :- if(environ(prob_safe_mode,true)).
259 convert_to_avl_inside_set(fd(A,T),R) :- var(A),!,
260 add_error(convert_to_avl,'Non-ground FD-Term: ',convert_to_avl_inside_set(fd(A,T),R)), R=fd(A,T).
261 convert_to_avl_inside_set(int(X),R) :- var(X),!,
262 add_error(convert_to_avl,'Non-ground integer: ',convert_to_avl_inside_set(int(X),R)), R=int(X).
263 convert_to_avl_inside_set(string(X),R) :- var(X),!,
264 add_error(convert_to_avl,'Non-ground string: ',convert_to_avl_inside_set(string(X),R)), R=string(X).
265 :- endif.
266 ?convert_to_avl_inside_set(closure(P,T,B),R) :- !,
267 ? expand_closure_to_avl(P,T,B,R). % inside a set, the closure needs to be expanded to check against other elements
268 %convert_to_avl_inside_set(closure_x(_P,_T,_B,E),R) :- !, convert_to_avl_inside_set(E,R).
269 convert_to_avl_inside_set(avl_set(A),R) :- !, normalise_avl_set(A,R). %AVL's inside other AVL's need to be normalised !
270 convert_to_avl_inside_set([],R) :- !,R=[].
271 ?convert_to_avl_inside_set((A,B),(CA,CB)) :- !,convert_to_avl_inside_set(A,CA), convert_to_avl_inside_set(B,CB).
272 convert_to_avl_inside_set(fd(A,T),R) :- !, R=fd(A,T).
273 convert_to_avl_inside_set(int(X),R) :- !, R=int(X).
274 convert_to_avl_inside_set(string(X),R) :- !, R=string(X).
275 convert_to_avl_inside_set(term(X),R) :- !, R=term(X).
276 convert_to_avl_inside_set(freetype(X),R) :- !,
277 expand_custom_set(freetype(X),EC,check), convert_to_avl_inside_set(EC,R).
278 convert_to_avl_inside_set(freeval(ID,Case,Value),R) :- !,
279 R=freeval(ID,Case,CValue),convert_to_avl_inside_set(Value,CValue).
280 convert_to_avl_inside_set(rec(Fields),R) :- !, convert_fields(Fields,CFields), R=rec(CFields).
281 convert_to_avl_inside_set(pred_false /* bool_false */,R) :- !, R=pred_false /* bool_false */.
282 convert_to_avl_inside_set(pred_true /* bool_true */,R) :- !, R=pred_true /* bool_true */.
283 convert_to_avl_inside_set(global_set(GS),R) :- !,
284 % first check if GS infinite integer set: in this case do not expand; there can be no confusion with finite avl_sets
285 (is_infinite_global_set(GS,_) -> R = global_set(GS)
286 ; expand_only_custom_closure_global(global_set(GS),EC,check,no_wf_available), convert_to_avl_inside_set(EC,R)).
287 convert_to_avl_inside_set([H|T],R) :- !,convert_cons_to_avl_inside_set(H,T,R).
288 convert_to_avl_inside_set(X,R) :- print(unknown_term_convert_to_avl_inside_set(X)),nl, R=X.
289
290 normalise_avl_set(A,R) :- A=node(_,_,0,empty,empty), !,R=avl_set(A).
291 normalise_avl_set(A,R) :-
292 avl_to_list(A,L),
293 ord_list_to_avlset_direct(L,R,convert_to_avl_inside_set). %AVL's inside other AVL's need to be normalised !
294
295 convert_cons_to_avl_inside_set(H,T,R) :- T==[], !,
296 convert_to_avl_inside_set(H,CH),
297 R = avl_set(node(CH,true,0,empty,empty)).
298 ?convert_cons_to_avl_inside_set(H,T,R) :- l_convert_to_avl([H|T],S),
299 sort(S,SS),
300 ord_list_to_avlset_direct(SS,R,convert_to_avl_inside_set).
301
302 /*
303 a sort that checks that there are no repetitions; throws errors for set_extension findall conversions
304 :- use_module(library(samsort)).
305 %mysort(S,SS) :- !, sort(S,SS).
306 mysort(S,SS2) :- samsort(S,SS),
307 check_repetition(SS),
308 sort(SS,SS2).
309
310 check_repetition([]).
311 check_repetition([H|T]) :- check_repetition_aux(T,H).
312 check_repetition_aux([],_).
313 check_repetition_aux([H|T],Prev) :-
314 (H=Prev -> add_internal_error('Repeated element in list: ',H),trace
315 ; check_repetition_aux(T,H)).
316 */
317
318 is_set_value(X,Origin) :- var(X), !,print(is_set_value(Origin)),nl,fail.
319 is_set_value([],_) :- !.
320 is_set_value([_|_],_) :- !.
321 is_set_value(X,_) :- is_custom_explicit_set(X).
322
323 is_custom_explicit_set(X,Origin) :- var(X), !,print(var_is_custom_explicit_set(Origin)),nl,fail.
324 is_custom_explicit_set(X,_) :- is_custom_explicit_set(X).
325
326 is_custom_explicit_set(X) :- var(X), !,print(var_is_custom_explicit_set),nl,fail.
327 is_custom_explicit_set(global_set(_)).
328 is_custom_explicit_set(freetype(_)).
329 %is_custom_explicit_set(integer_global_set(_)).
330 is_custom_explicit_set(avl_set(_)).
331 %is_custom_explicit_set(closure_x(_Parameters,_PT,_Cond,_Exp)).
332 is_custom_explicit_set(closure(_Parameters,_PT,_Cond)).
333
334 % use if you know the argument to be nonvar
335 is_custom_explicit_set_nonvar(global_set(_)).
336 is_custom_explicit_set_nonvar(freetype(_)).
337 is_custom_explicit_set_nonvar(avl_set(_)).
338 is_custom_explicit_set_nonvar(closure(_Parameters,_PT,_Cond)).
339
340 :- assert_must_succeed(( custom_explicit_sets:portray_custom_explicit_set(avl_set(empty)) )).
341 :- use_module(translate,[translate_bvalue/2]).
342 portray_custom_explicit_set(S) :- translate:translate_bvalue(S,A), format(A,[]),nl.
343
344 /* a predicate to check equality of two custom explicit sets */
345
346 %equal_explicit_sets(A,B) :- equal_explicit_sets_wf(A,B,no_wf_available).
347
348 %equal_explicit_sets(X,Y) :- print_term_summary(equal_explicit_sets(X,Y)),fail.
349 :- block equal_explicit_sets_wf(-,?,?), equal_explicit_sets_wf(?,-,?).
350 equal_explicit_sets_wf(A,B,WF) :- equal_explicit_sets4(A,B,allow_expansion,WF).
351
352 %equal_explicit_sets4(A,B,R,_WF) :- print(eqxs(A,B,R)),nl,fail.
353 equal_explicit_sets4(global_set(X),global_set(Y),_,_WF) :- !,X=Y.
354 equal_explicit_sets4(global_set(B),avl_set(A),E,WF) :- !,equal_explicit_sets4(avl_set(A),global_set(B),E,WF).
355 equal_explicit_sets4(freetype(X),freetype(Y),_,_WF) :- !,X=Y.
356 equal_explicit_sets4(avl_set(A),avl_set(B),_,_WF) :- !,
357 equal_avl_tree(A,B). %, print(equal),nl. % alternatively, we could normalise avl_trees and only store normalised versions
358 equal_explicit_sets4(avl_set(A),I2,_,_WF) :-
359 is_interval_closure_or_integerset(I2,L2,U2),!, % also covers I2=global_set(...)
360 avl_equal_to_interval(A,L2,U2).
361 equal_explicit_sets4(avl_set(A),global_set(B),_,_WF) :- \+ b_global_sets:b_integer_set(B), !, % integersets dealt with above
362 explicit_set_cardinality(global_set(B),Card), %print(check_equal(B,Card)),nl,
363 Card \= inf, %as avl_set must be finite
364 explicit_set_cardinality(avl_set(A),Card). /* the sets must be identical as global_set contains all values */
365 equal_explicit_sets4(closure(P,T,B),avl_set(A),E,WF) :- !, equal_explicit_sets4(avl_set(A),closure(P,T,B),E,WF).
366 equal_explicit_sets4(I1,I2,_,_WF) :- is_interval_closure_or_integerset(I1,L1,U1),
367 is_interval_closure_or_integerset(I2,L2,U2), !, %print(eq_interval(L1,U1,L2,U2)),nl,
368 L1=L2, U1=U2.
369 equal_explicit_sets4(CPA,CPB,_,_WF) :-
370 ? is_cartesian_product_closure(CPA,A1,A2), is_cartesian_product_closure(CPB,B1,B2),!,
371 %print_term_summary(equal_cartesian(A1,A2,B1,B2)),
372 equal_cartesian_product(A1,A2,B1,B2).
373 % what if both subset or relations or functions ... closure: TO DO: add support
374 equal_explicit_sets4(S1,S2,_,WF) :-
375 is_not_member_value_closure_or_integerset(S1,TYPE,MS1),
376 is_not_member_value_closure_or_integerset(S2,TYPE,MS2),
377 !,
378 kernel_objects:equal_object_wf(MS1,MS2,equal_explicit_sets4,WF).
379 equal_explicit_sets4(closure(P,T,B),closure(P,T,B2),_,_WF) :-
380 % nl,print(check_eq),nl,print(B),nl,print(B2),nl, %
381 same_texpr_body(B,B2),!.
382 %equal_explicit_sets4(X,Y) :- X==Y,!.
383 equal_explicit_sets4(Set1,Set2,allow_expansion,WF) :-
384 %kernel_objects:test_finite_set_wf(Set1,F1,WF), kernel_objects:test_finite_set_wf(Set2,F2,WF), equal_expansions(F1,F2,Set1,Set2)
385 card_for_specific_custom_set(Set1,Card1,Code1), % TO DO: do not throw info away if Set2 cannot be determined
386 card_for_specific_custom_set(Set2,Card2,Code2),
387 !,
388 call(Code1), call(Code2),
389 % TO DO: if one of the two sets is infinite, then it would be enough to know that the other is not infinite for failure without expansion
390 equal_expansions(Card1,Card2,Set1,Set2,WF).
391 equal_explicit_sets4(Set1,Set2,allow_expansion,WF) :- equal_expansions(0,0,Set1,Set2,WF).
392
393 :- block equal_expansions(-,?,?,?,?).
394 ?equal_expansions(F1,F2,Set1,Set2,WF) :- (number(F1);number(F2)),!,
395 % NOTE: sometimes we get inf for finite but very large sets
396 F1=F2, % unify; can propagate info back to closure; e.g. prj2(BOOL,NAT) = prj2(BOOL,0..n)
397 equal_expansions2(F1,F2,Set1,Set2,WF).
398 equal_expansions(F1,F2,Set1,Set2,WF) :-
399 equal_expansions2(F1,F2,Set1,Set2,WF).
400
401 :- block equal_expansions2(-,?,?,?,?), equal_expansions2(?,-,?,?,?).
402 %equal_expansions(0,0,avl_set(A),closure(P,T,B)) :- check_subset ?? in both directions ?
403 %equal_expansions2(inf,inf,Set1,Set2,WF) :- WF \= no_wf_available, !, % symbolic treatment
404 equal_expansions2(F,F,Set1,Set2,WF) :-
405 % only expand if both sets have same cardinality
406 % print_term_summary(equal_expansion(F,Set1,Set2)),nl,
407 equal_expansions3(F,Set1,Set2,WF).
408
409 % TO DO: check if this brings something:
410 %equal_expansions3(avl_set(A),closure(P,T,B),_WF) :- !,
411 % expand_closure_to_avl_or_list(P,T,B,E2,check), % in case E2 is avl_set; we can use equal_avl_tree
412 % ((nonvar(E2),E2=avl_set(B2))
413 % -> print(eql_avl),nl, print_term_summary(equal_avl_tree(A,B2)),nl, equal_avl_tree(A,B2)
414 % ; print(eql_non_avl),nl,equal_object(avl_set(A),E2,equal_expansions3)
415 % ).
416 %:- use_module(library(lists),[perm2/4]).
417 %equal_expansions3(F,Set1,Set2,_WF) :- number(F), F>100, % test with: {{},{TRUE},{FALSE},{TRUE,FALSE}} = /*@symbolic */ {x|x<:BOOL} or
418 % {x|x<:POW(BOOL*BOOL) & (x={} or card(x)>0)} = /*@symbolic */ {x|x<:POW(BOOL*BOOL)} 26 sec -> 14 sec
419 % case does not seem to appear very often
420 % perm2(Set1,Set2,avl_set(_),Set),
421 % is_definitely_maximal_set(Set),
422 %Set2 is maximal and has the same cardinality as F, hence Set1 must be identical to Set2
423 % !,
424 % debug_println(9,equal_to_maximal_closure(F)).
425 equal_expansions3(F,Set1,Set2,WF) :- % print(equal_expansions3(F,Set1,Set2,WF)),nl,
426 (F=inf %; is_infinite_explicit_set(Set1) ; is_infinite_explicit_set(Set2)
427 ; Set1 \= avl_set(_),Set2 \= avl_set(_), % if one of the two sets is an AVL Set: better compute the other set explicitly instead of using this symbolic treatment
428 (dont_expand_this_explicit_set(Set1,100000) ;
429 dont_expand_this_explicit_set(Set2,100000)
430 )
431 % avl_test check for test 1081; TO DO: instead of test try to expand set and if this leads to enum warning use symbolic check
432 ),
433 get_identity_as_equivalence(Set1,Set2,EQUIV),
434 % print(checking(F)), translate:print_bexpr(EQUIV),nl,
435 !,
436 b_interpreter:b_test_boolean_expression(EQUIV,[],[],WF).
437 % Alternative could be, if difference were to be fully treated symbolically:
438 % difference_of_explicit_set_wf(Set1,Set2,R12,WF), difference_of_explicit_set_wf(Set2,Set1,R21,WF),
439 % kernel_objects:empty_set_wf(R12,WF), kernel_objects:empty_set_wf(R21,WF).
440 equal_expansions3(_,Set1,Set2,WF) :-
441 expand_custom_set_wf(Set1,E1,equal_expansions1,WF), % print_term_summary(expanded_set1(E1)),nl,
442 expand_custom_set_wf(Set2,E2,equal_expansions2,WF),
443 % print_term_summary(check_equal_exp(E1,E2)),nl,
444 E1=E2. /* ensure that ordering is same for all representations ! */
445
446 get_identity_as_equivalence(Set1,Set2,EQUIV) :-
447 kernel_objects:infer_value_type(Set1,SType),
448 is_set_type(SType,Type),
449 % Construct: !x.(x:Set1 <=> x:Set2) ??
450 TID = b(identifier('_zzzz_unary'),Type,[used_ids([])]),
451 EQUIV = b(forall([TID],b(truth,pred,[]),
452 b(equivalence(
453 b(member(TID,b(value(Set1),SType,[])),pred,[]),
454 b(member(TID,b(value(Set2),SType,[])),pred,[])
455 ) ,pred,[])
456 ),pred,[]).
457
458 :- use_module(kernel_equality,[eq_atomic/4, equality_objects/3]).
459 /* maybe rewrite equal_explicit_sets and not_... to use this to avoid maintaining multiple versions */
460 equality_explicit_sets(global_set(X),global_set(Y),R) :- !, kernel_equality:eq_atomic(X,Y,set,R).
461 equality_explicit_sets(global_set(B),avl_set(A),R) :- !,equality_explicit_sets(avl_set(A),global_set(B),R).
462 equality_explicit_sets(freetype(X),freetype(Y),R) :- !, kernel_equality:eq_atomic(X,Y,set,R).
463 equality_explicit_sets(avl_set(A),avl_set(B),R) :- !,
464 (equal_avl_tree(A,B) -> R=pred_true ; R=pred_false). % alternatively, we could normalise avl_trees and only store normalised versions
465 equality_explicit_sets(avl_set(A),I2,R) :- is_interval_closure_or_integerset(I2,L2,U2),!, % also covers I2=global_set(...)
466 avl_equality_to_interval(A,L2,U2,R).
467 equality_explicit_sets(avl_set(A),global_set(B),R) :- \+ b_global_sets:b_integer_set(B), !,
468 explicit_set_cardinality(global_set(B),Card), %print(check_equal(B,Card)),nl,
469 ((Card \= inf, %as avl_set must be finite
470 explicit_set_cardinality(avl_set(A),Card))
471 -> R=pred_true /* the sets must be identical as global_set contains all values */
472 ; R=pred_false).
473 equality_explicit_sets(closure(P,T,B),avl_set(A),R) :- !, equality_explicit_sets(avl_set(A),closure(P,T,B),R).
474 equality_explicit_sets(I1,I2,R) :- is_interval_closure_or_integerset(I1,L1,U1),
475 is_interval_closure_or_integerset(I2,L2,U2), !, %print(eq_interval(L1,U1,L2,U2)),nl,
476 equality_objects((int(L1),int(U1)),(int(L2),int(U2)),R).
477 equality_explicit_sets(CPA,CPB,R) :-
478 is_cartesian_product_closure(CPA,A1,A2), is_cartesian_product_closure(CPB,B1,B2),!,
479 % print_term_summary(equality_cartesian(A1,A2,B1,B2)),
480 equality_cartesian_product(A1,A2,B1,B2,R).
481 equality_explicit_sets(S1,S2,R) :-
482 is_not_member_value_closure_or_integerset(S1,TYPE,MS1),
483 is_not_member_value_closure_or_integerset(S2,TYPE,MS2),!,
484 kernel_equality:equality_objects_with_type(TYPE,MS1,MS2,R).
485 equality_explicit_sets(closure(P,T,B),closure(P,T,B2),R) :-
486 % print(check_eq),nl,print(B),nl,print(B2),nl,
487 same_texpr_body(B,B2),!,R=pred_true.
488 % TO DO: add complement sets
489
490 /* Cartesian Product Comparison */
491 :- use_module(kernel_equality,[empty_cartesian_product/3]).
492 % A1*A2 = B1*B2 <=> (((A1={} or A2={}) & (B1={} or B2={})) or (A1=B1 & A2=B2))
493 equal_cartesian_product(A1,A2,B1,B2) :- equality_cartesian_product(A1,A2,B1,B2,pred_true).
494 not_equal_cartesian_product(A1,A2,B1,B2) :- equality_cartesian_product(A1,A2,B1,B2,pred_false).
495
496 equality_cartesian_product(A1,A2,B1,B2,R) :- empty_cartesian_product(A1,A2,EmptyA),
497 equality_cart_product2(EmptyA,A1,A2,B1,B2,R).
498 :- block equality_cart_product2(-, ?,?,?,?,?).
499 equality_cart_product2(pred_true,_,_,B1,B2,R) :- empty_cartesian_product(B1,B2,R).
500 equality_cart_product2(pred_false,A1,A2,B1,B2,R) :- equality_objects((A1,A2),(B1,B2),R). % TO DO: call equality_objects_wf
501
502 /* COMPARING AVL-SET with INTERVAL */
503
504 % check if an avl tree is equal to an interval range
505 avl_equal_to_interval(_A,L2,U2) :- %print(equal_interval(L2,U2)),nl,
506 infinite_interval(L2,U2),!,fail. % otherwise infinite & avl_set is finite
507 % we can now assume L2, U2 are numbers (but could not yet be instantiated)
508 avl_equal_to_interval(A,L2,U2) :- %print(check_avl_interval(A,L2,U2)),nl,
509 avl_min(A,int(L2)), avl_max(A,int(U2)),
510 Card is 1+U2-L2, %print(Card),nl,
511 explicit_set_cardinality(avl_set(A),Card). % sets are equal: same size + same lower & upper bound
512
513 avl_not_equal_to_interval(A,L2,U2) :- avl_equality_to_interval(A,L2,U2,pred_false).
514
515 avl_equality_to_interval(_A,L2,U2,R) :-
516 infinite_interval(L2,U2),!,R=pred_false. % interval infinite & avl_set is finite
517 % we can now assume L2, U2 are numbers (but could not yet be instantiated)
518 avl_equality_to_interval(A,L2,U2,R) :- % print(avl_equality_to_interval(L2,U2)),nl,
519 avl_min(A,int(AL)), avl_max(A,int(AU)),
520 Card is 1+AU-AL, %print(Card),nl,
521 explicit_set_cardinality(avl_set(A),ACard),
522 equality_objects((int(ACard),(int(AL),int(AU))),
523 (int(Card),(int(L2),int(U2))),R). % sets are equal if same size + same lower & upper bound
524
525 /* COMPARING TWO CLOSURES */
526
527 % check if two wrapped expressions are equal (modulo associated Info, e.g. source loc info)
528 % and checking inserted values for equality (sometimes storing a closure will convert small inner closures into AVL sets)
529 same_texpr_body(E1,E2) :- empty_avl(E),same_texpr_body(E1,E,E2).
530 same_texpr_body(b(E1,Type,_),AVL,b(E2,Type,_)) :- same_texpr2(E1,AVL,E2).
531
532 :- use_module(bsyntaxtree,[safe_syntaxelement/5, is_set_type/2]).
533 same_texpr2(value(V1),_,value(V2)) :- !,same_value_inside_closure(V1,V2).
534 same_texpr2(lazy_let_expr(ID,LHS,RHS),AVL,lazy_let_expr(ID2,LHS2,RHS2)) :- !,
535 same_texpr_body(LHS,AVL,LHS2),
536 avl_store(ID,AVL,ID2,NewAVL),
537 same_texpr_body(RHS,NewAVL,RHS2).
538 same_texpr2(lazy_let_pred(ID,LHS,RHS),AVL,lazy_let_pred(ID2,LHS2,RHS2)) :- !,
539 same_texpr_body(LHS,AVL,LHS2),
540 avl_store(ID,AVL,ID2,NewAVL),
541 same_texpr_body(RHS,NewAVL,RHS2).
542 same_texpr2(lazy_lookup(ID1), AVL,lazy_lookup(ID2)) :- !, avl_fetch(ID1,AVL,ID2).
543 same_texpr2(E1,AVL,E2) :-
544 functor(E1,F,Arity),
545 functor(E2,F,Arity),
546 safe_syntaxelement(E1,Subs1,_Names1,_List1,Constant1),
547 safe_syntaxelement(E2,Subs2,_Names2,_List2,Constant2), Constant2==Constant1,
548 same_sub_expressions(Subs1,AVL,Subs2).
549
550 allow_expansion(avl_set(_),closure(P,T,B)) :- is_small_specific_custom_set(closure(P,T,B),100).
551 allow_expansion(closure(P,T,B),avl_set(_)) :- is_small_specific_custom_set(closure(P,T,B),100).
552
553 same_sub_expressions([],_,[]).
554 same_sub_expressions([H1|T1],AVL,[H2|T2]) :- same_texpr_body(H1,AVL,H2),
555 same_sub_expressions(T1,AVL,T2).
556
557 same_value_inside_closure(V1,V2) :- var(V1),!, V1==V2.
558 same_value_inside_closure(_,V2) :- var(V2),!,fail.
559 same_value_inside_closure(rec(Fields1),rec(Fields2)) :- !,
560 % sets of records come in this form: struct(b(value(rec(FIELDS)),record(_),_))
561 same_fields_inside_closure(Fields1,Fields2).
562 same_value_inside_closure(V1,V2) :- % print(check_eq(V1,V2)),nl,
563 % we could attempt this only if the outer closure was large/infinite ??
564 is_custom_explicit_set(V1), is_custom_explicit_set(V2),
565 !,
566 (allow_expansion(V1,V2) -> EXP=allow_expansion ; EXP = no_expansion),
567 equal_explicit_sets4(V1,V2,EXP,no_wf_available). % usually only sets compiled differently inside closures
568 same_value_inside_closure(V1,V2) :- V1==V2.
569
570 same_fields_inside_closure(V1,V2) :- var(V1),!, V1==V2.
571 same_fields_inside_closure(_,V2) :- var(V2),!,fail.
572 same_fields_inside_closure([],[]).
573 same_fields_inside_closure([field(Name,V1)|T1],[field(Name,V2)|T2]) :-
574 same_value_inside_closure(V1,V2),
575 same_fields_inside_closure(T1,T2).
576
577 /*
578 same_texpr_body_debug(H1,H2) :-
579 (same_texpr_body(H1,H2) -> true
580 ; print('FAIL: '),nl,
581 translate:print_bexpr(H1),nl, translate:print_bexpr(H2),nl, print(H1),nl, print(H2),nl, fail). */
582
583 %test(Y2,Z2) :- empty_avl(X), avl_store(1,X,2,Y), avl_store(2,X,3,Z),
584 % avl_store(2,Y,3,Y2), avl_store(1,Z,2,Z2), equal_avl_tree(Y2,Z2).
585
586 %equal_avl_tree(A,B) :- avl_min(A,Min), avl_min(B,Min), cmp(Min,A,B).
587 %cmp(El,A,B) :-
588 % (avl_next(El,A,Nxt) -> (avl_next(El,B,Nxt), cmp(Nxt,A,B))
589 % ; \+ avl_next(El,B,Nxt) ).
590
591 % The following is faster than using avl_next
592 equal_avl_tree(A,B) :-
593 % statistics(walltime,[WT1,_]),if(equal_avl_tree2(A,B),true,(statistics(walltime,[_,W]),print(wall(W)),nl)).
594 %equal_avl_tree2(A,B) :-
595 avl_min(A,Min),
596 !,
597 avl_min(B,Min),
598 avl_max(A,Max), avl_max(B,Max),
599 % maybe also check avl_height +/- factor of 1.4405 (page 460, Knuth 3) ? but it seems this would trigger only extremely rarely
600 %avl_height(A,H1), avl_height(A,H2), log(check(Min,Max,H1,H2)),
601 avl_domain(A,L), avl_domain(B,L).
602 equal_avl_tree(empty,_) :- !, format(user_error,'*** Warning: empty AVL tree in equal_avl_tree~n',[]).
603 equal_avl_tree(A,B) :- add_internal_error('Illegal AVL tree: ',equal_avl_tree(A,B)),fail.
604
605 /* a predicate to check equality of two custom explicit sets */
606
607 :- block not_equal_explicit_sets(-,?), not_equal_explicit_sets(?,-).
608 %not_equal_explicit_sets(X,Y) :- print_term_summary(not_equal_explicit_sets(X,Y)),nl,fail.
609 not_equal_explicit_sets(global_set(X),global_set(Y)) :- !,dif(X,Y).
610 not_equal_explicit_sets(global_set(B),avl_set(A)) :- !,
611 \+ equal_explicit_sets4(avl_set(A),global_set(B),allow_expansion,no_wf_available).
612 not_equal_explicit_sets(freetype(X),freetype(Y)) :- !,dif(X,Y).
613 not_equal_explicit_sets(avl_set(A),avl_set(B)) :- !,
614 \+ equal_avl_tree(A,B). %, print(not_equal),nl.
615 %not_equal_explicit_sets(X,Y) :- X==Y,!,fail.
616 not_equal_explicit_sets(avl_set(A),I2) :- is_interval_closure_or_integerset(I2,L2,U2),!, % also covers I2=global_set(...)
617 avl_not_equal_to_interval(A,L2,U2).
618 not_equal_explicit_sets(avl_set(A),global_set(B)) :- !,
619 \+ equal_explicit_sets4(avl_set(A),global_set(B),allow_expansion,no_wf_available).
620 not_equal_explicit_sets(closure(P,T,B),avl_set(A)) :- !,
621 not_equal_explicit_sets(avl_set(A),closure(P,T,B)).
622 not_equal_explicit_sets(I1,I2) :- is_interval_closure_or_integerset(I1,L1,U1),
623 is_interval_closure_or_integerset(I2,L2,U2), !, %print(neq_interval(L1,U1,L2,U2)),nl,
624 dif((L1,U1),(L2,U2)). % maybe we should call not_equal_objects on integers (not on inf values)?
625 not_equal_explicit_sets(CPA,CPB) :-
626 is_cartesian_product_closure(CPA,A1,A2), is_cartesian_product_closure(CPB,B1,B2),!,
627 %print_term_summary(not_equal_cartesian(A1,A2,B1,B2)),
628 not_equal_cartesian_product(A1,A2,B1,B2).
629 not_equal_explicit_sets(S1,S2) :-
630 is_not_member_value_closure_or_integerset(S1,TYPE,MS1),
631 is_not_member_value_closure_or_integerset(S2,TYPE,MS2),!,
632 kernel_objects:not_equal_object(MS1,MS2).
633 not_equal_explicit_sets(closure(P,T,B),closure(P,T,B2)) :-
634 % print(check_eq),nl,print(B),nl,print(B2),nl,
635 same_texpr_body(B,B2),!,fail.
636 % TO DO: maybe support interval & avl_set comparison
637 not_equal_explicit_sets(Set1,Set2) :-
638 card_for_specific_custom_set(Set1,Card1,Code1), card_for_specific_custom_set(Set2,Card2,Code2),
639 call(Code1), call(Code2),!,
640 not_equal_expansions(Card1,Card2,Set1,Set2).
641 not_equal_explicit_sets(Set1,Set2) :- not_equal_expansions(0,0,Set1,Set2).
642
643
644 :- block not_equal_expansions(-,?,?,?), not_equal_expansions(?,-,?,?).
645 not_equal_expansions(F1,F2,_,_) :- F1 \= F2,!. % sets guaranteed to be different
646 %not_equal_expansions(F,F,Set1,Set2) :-
647 % (F=inf ; dont_expand_this_explicit_set(Set1) ; dont_expand_this_explicit_set(Set2)),
648 % get_identity_as_equivalence(Set1,Set2,EQUIV),
649 % !,
650 % b_interpreter:b_not_test_boolean_expression(EQUIV,[],[],WF). %% TODO: WE NEED A WAITFLAG !!
651 not_equal_expansions(F,F,Set1,Set2) :-
652 % only expand if both sets have same cardinality
653 expand_custom_set(Set1,E1,not_equal_expansions1),
654 expand_custom_set(Set2,E2,not_equal_expansions2),
655 % print_term_summary(check_equal_exp(E1,E2)),nl,
656 dif(E1,E2). /* ensure that ordering is same for all representations ! */
657 % for two closures: we could try and solve a constraint instead: that !Paras.(Body1 <=> Body2) ??
658
659 :- use_module(b_global_sets,[b_empty_global_set/1, b_non_empty_global_set/1, b_global_set_cardinality/2]).
660 is_empty_explicit_set_wf(closure(P,T,B),WF) :- !,
661 is_empty_closure_wf(P,T,B,WF).
662 is_empty_explicit_set_wf(S,_WF) :- is_empty_explicit_set(S).
663
664 % with WF we can delay computing Card; see test 1272 / card({x|x:1..10 & x*x<i}) = 0 & i>1
665 % TO DO: ideally we could just write this: is_empty_closure_wf(P,T,B,WF) :- closure_cardinality(P,T,B,0,WF). ; but empty_set / not_exists optimisation not triggered in closure_cardinality (yet); would avoid duplicate code
666 is_empty_closure_wf(P,T,B,WF) :- % translate:print_bvalue(closure(P,T,B)),nl,%trace,
667 is_lambda_value_domain_closure(P,T,B, DomainValue,_Expr),!,
668 kernel_objects:empty_set_wf(DomainValue,WF).
669 is_empty_closure_wf(P,T,B,WF) :- is_cartesian_product_closure_aux(P,T,B,A1,A2),!,
670 very_approximate_cardinality(A1,C1,WF),
671 very_approximate_cardinality(A2,C2,WF), % print(cart_closure_card(C1,C2)),nl,
672 blocking_safe_mul(C1,C2,0).
673 is_empty_closure_wf(P,T,B,_WF) :-
674 card_for_specific_closure2(P,T,B,CC,Code),
675 !,
676 call(Code),CC=0.
677 is_empty_closure_wf(P,T,Body,WF) :-
678 WF \== no_wf_available, % only do this if we have a WF store; see comments for closure_cardinality ; code relevant for test 1272; card({x|x:1..10 & x*x<i}) = 0 & i>1
679 \+ ground_bexpr(Body), % otherwise better to use not_test_exists below (e.g., Bosch v6 Codespeed benchmark)
680 b_interpreter_check:reify_closure_with_small_cardinality(P,T,Body, WF, ReifiedList),
681 !,
682 clpfd:domain(ReifiedList,0,1),
683 clpfd:sum(ReifiedList,'#=',0).
684 is_empty_closure_wf(P,T,B,WF) :- !, % try and check that not(#(P).(B)); i.e., there is no solution for the Body B; solves tests 1542, detecting that {x|x>100 & x mod 102 = 2} = {} is false
685 % print(empty_closure_test(P)),nl, translate:print_bexpr(B),nl,
686 gen_typed_ids(P,T,TypedParas),
687 b_interpreter:b_not_test_exists(TypedParas,B,[used_ids([])],[],[],WF). % used_ids are empty, as all variables already compiled into values
688
689 % very_approximate_cardinality: only required to return 0 for empty set, and number or inf for non-empty set, tested in 1893
690 :- block very_approximate_cardinality(-,?,?).
691 very_approximate_cardinality(avl_set(A),C,_) :- !, (A=empty -> print(empty_avl),nl,C=0 ; C=1).
692 very_approximate_cardinality([],C,_) :- !, C=0.
693 very_approximate_cardinality([_|_],C,_) :- !, C=1.
694 very_approximate_cardinality(Set,C,WF) :- kernel_objects:cardinality_as_int_wf(Set,int(C),WF).
695 % TO DO: maybe call is_empty_closure or similar for closures
696
697 gen_typed_ids([],[],[]).
698 gen_typed_ids([ID|IT],[Type|TT],[b(identifier(ID),Type,[])|TTT]) :- % TO DO: add Info field from outer set comprehension
699 gen_typed_ids(IT,TT,TTT).
700
701
702 is_empty_explicit_set(global_set(GS)) :- !, b_empty_global_set(GS).
703 is_empty_explicit_set(freetype(ID)) :- !, kernel_freetypes:is_empty_freetype(ID).
704 is_empty_explicit_set(avl_set(A)) :- !,
705 (var(A) -> add_warning(is_empty_explicit_set,'Variable avl_set')
706 ; empty_avl(A), add_warning(is_empty_explicit_set,'Empty avl_set')
707 ).
708 is_empty_explicit_set(C) :- card_for_specific_closure(C,CC,Code),!,call(Code),CC=0.
709 is_empty_explicit_set(ES) :- expand_custom_set(ES,[],is_empty_explicit_set).
710 % alternative solution for closures: we could generate an Exists if Expansion not given
711
712 is_non_empty_explicit_set(CS) :- is_non_empty_explicit_set_wf(CS,no_wf_available).
713
714 is_non_empty_explicit_set_wf(global_set(GS),_WF) :- !, b_non_empty_global_set(GS).
715 is_non_empty_explicit_set_wf(freetype(ID),_WF) :- !, kernel_freetypes:is_non_empty_freetype(ID).
716 is_non_empty_explicit_set_wf(avl_set(A),_WF) :- !,
717 (empty_avl(A) -> print('### Warning: empty avl_set (2)'),nl,fail
718 ; true).
719 is_non_empty_explicit_set_wf(closure(P,T,B),WF) :- !, is_non_empty_closure_wf(P,T,B,WF).
720 %is_non_empty_explicit_set_wf(ES,_WF) :- expand_custom_set(ES,[_|_],is_non_empty_explicit_set).
721
722
723 % TO DO: this code is a bit redundant with is_empty_closure_wf
724 is_non_empty_closure_wf(P,T,B,WF) :- %print(closure_card(P,T,B,Card,WF)),trace,
725 is_lambda_value_domain_closure(P,T,B, DomainValue,_Expr),!,
726 kernel_objects:not_empty_set_wf(DomainValue,WF).
727 is_non_empty_closure_wf(P,T,B,WF) :- is_cartesian_product_closure_aux(P,T,B,A1,A2),!,
728 very_approximate_cardinality(A1,C1,WF),
729 very_approximate_cardinality(A2,C2,WF), %print(cart_closure_card(C1,C2)),nl,
730 blocking_safe_mul(C1,C2,CC),gt0(CC).
731 is_non_empty_closure_wf(P,T,B,_WF) :-
732 card_for_specific_closure2(P,T,B,CC,Code),!,call(Code),gt0(CC).
733 % TO DO: reify_closure_with_small_cardinality
734 is_non_empty_closure_wf(P,T,B,WF) :- WF \== no_wf_available, % otherwise enumeration of test_exists will behave strangely; leading to enumeration warnings,... [TO DO: ensure we always have a WF or fix this below ?]
735 !, % try and check that not(#(P).(B)); i.e., there is no solution for the Body B; solves tests 1542; test 1146 also triggers this code
736 (debug_mode(off) -> true ; print(non_empty_closure_test(P)),nl, translate:print_bexpr(B),nl),
737 gen_typed_ids(P,T,TypedParas),
738 b_interpreter:b_test_exists(TypedParas,B,[used_ids([])],[],[],WF). % used_ids are empty, as all variables already compiled into values
739 % some rules for set_subtraction, ... closures ?? if left part infinite and right part finite it must be infinite
740 is_non_empty_closure_wf(P,T,B,_WF) :-
741 expand_custom_set(closure(P,T,B),[_|_],is_non_empty_closure_wf).
742
743 test_empty_explicit_set(V,Res) :- var(V),!,
744 add_internal_error('Illegal call: ',test_empty_explicit_set(V,Res)),fail.
745 test_empty_explicit_set(global_set(GS),Res) :- !,
746 (b_empty_global_set(GS) -> Res=pred_true ; Res=pred_false).
747 test_empty_explicit_set(freetype(ID),Res) :- !, kernel_freetypes:test_empty_freetype(ID,Res).
748 test_empty_explicit_set(avl_set(A),Res) :- !,
749 (var(A) -> add_warning(test_empty_explicit_set,'Variable avl_set'), Res=pred_true
750 ; empty_avl(A), add_warning(test_empty_explicit_set,'Empty avl_set'), Res = pred_true
751 ; Res=pred_false).
752 test_empty_explicit_set(C,Res) :- card_for_specific_closure(C,CC,Code),!,call(Code),
753 check_zero(CC,Res).
754 test_empty_explicit_set(ES,Res) :- expand_custom_set(ES,ExpES,test_empty_explicit_set),
755 kernel_equality:eq_empty_set(ExpES,Res).
756
757 :- block check_zero(-,?).
758 check_zero(0,R) :- !, R=pred_true.
759 check_zero(_,pred_false).
760
761 :- block gt0(-).
762 gt0(CC) :- (CC=inf -> true ; CC>0).
763
764 % a version to compute cardinality for
765 explicit_set_cardinality_for_wf(closure(P,T,B),Card) :-
766 is_symbolic_closure_or_symbolic_mode(P,T,B),!,
767 Card = inf. % assume card is infinite for WF computation; it may be finite!
768 % TO DO: maybe never expand closures here !? -> closure_cardinality can expand closure !!!!!!
769 explicit_set_cardinality_for_wf(CS,Card) :-
770 on_enumeration_warning(
771 explicit_set_cardinality(CS,Card),
772 (debug_println(assuming_inf_card_for_wf), % see test 1519 for relevance
773 Card = inf)). % assume card is infinite for WF computation; it may be finite!
774
775 explicit_set_cardinality(CS,Card) :- explicit_set_cardinality_wf(CS,Card,no_wf_available).
776
777 explicit_set_cardinality_wf(global_set(GS),Card,_) :- !,b_global_set_cardinality(GS,Card).
778 explicit_set_cardinality_wf(freetype(GS),Card,_WF) :- !, freetype_cardinality(GS,Card).
779 explicit_set_cardinality_wf(avl_set(S),Card,_WF) :- !,avl_size(S,Card).
780 explicit_set_cardinality_wf(closure(P,T,B),Card,WF) :- closure_cardinality(P,T,B,Card,WF).
781
782 :- use_module(performance_messages).
783 closure_cardinality(P,T,B,Card,WF) :- %print(closure_card(P,T,B,Card,WF)),trace,
784 is_lambda_value_domain_closure(P,T,B, DomainValue,_Expr),!,
785 % print(lambda_closure_card(DomainValue)),nl,
786 kernel_objects:cardinality_as_int_wf(DomainValue,int(Card),WF). % always compute it; card_for_specific_closure will only compute it if it can be done efficiently
787 closure_cardinality(P,T,B,Card,WF) :- is_cartesian_product_closure_aux(P,T,B,A1,A2),!,
788 kernel_objects:cardinality_as_int_wf(A1,int(C1),WF),
789 kernel_objects:cardinality_as_int_wf(A2,int(C2),WF), %print(cart_closure_card(C1,C2)),nl,
790 blocking_safe_mul(C1,C2,Card).
791 % TO DO: card_for_specific_closure2 calls is_lambda_value_domain_closure and is_cartesian_product_closure_aux again !
792 closure_cardinality(P,T,B,Card,_WF) :-
793 card_for_specific_closure2(P,T,B,CC,Code),
794 !,
795 call(Code),Card=CC.
796 closure_cardinality(P,T,Body,Card,WF) :-
797 (WF == no_wf_available -> CBody=Body
798 ; %print('START COMPILE card: '),translate:print_bexpr(Body),nl,
799 b_compiler:b_compile(Body,P,[],[],CBody)
800 %,print(' COMPILED FOR card: '), translate:print_bexpr(CBody),nl
801 %,nl,print(Body),nl, print(CBody),nl,nl
802 ),
803 % reify will work better if we used b_compiler:compile so that more sets can be detected as small
804 closure_cardinality2(P,T,CBody,Card,WF).
805 closure_cardinality2(P,T,Body,Card,WF) :-
806 % print(try_reify(P,WF)),nl,trace,
807 WF \== no_wf_available, % only do this if we have a WF store
808 if(b_interpreter_check:reify_closure_with_small_cardinality(P,T,Body, WF, ReifiedList),
809 true,
810 (perfmessagecall(reification_of_closure_for_card_failed(P),translate:print_bexpr(Body),Body),fail)),
811 %print(reified_list(ReifiedList)),nl,
812 !,
813 clpfd:domain(ReifiedList,0,1),
814 clpfd:sum(ReifiedList,'#=',Card),
815 % in this case we know card to be finite ! TO DO: ensure that check_finite propagates Card variable
816 debug_println(9,reified_cardinality_sum(ReifiedList,Card)). % clpfd:fd_dom(Card,Dom),print(dom(Card,Dom)),nl.
817 % should we add a special check if Card=0 ? usually Card not instantiated at this point !
818 %closure_cardinality(P,T,B,Card,WF) :- Card==0, %is_symbolic_closure(P,T,B),
819 % !, is_empty_closure_wf(P,T,B,WF).
820 closure_cardinality2(P,T,B,Card,_WF) :-
821 % TO DO: bexpr_variables(ClosureBody,ClosureWaitVars) and wait until those are bound; if Card = 0 -> empty_set; we can try to reifiy again
822 expand_custom_set(closure(P,T,B),Expansion,closure_cardinality),
823 % (var(Expansion)
824 % -> format('Could not reify ~w : ',[Card]), translate:print_bvalue(closure(P,T,B)),nl,
825 % when(nonvar(Card), format('Card bound ~w ~n',[Card]))
826 % ; true),
827 my_length(Expansion,0,Card).
828
829 :- block my_length(-,?,?).
830 my_length([],A,A).
831 my_length([_|T],A,R) :- A1 is A+1, my_length(T,A1,R).
832
833 % compute domain and range for specific relations;
834 % not the closure is total over the domain and surjective over the range
835 % WARNING: this should never enumerate on its own, it is often called with
836 % a cut straight after it; if some enumeration happens then only first solution
837 % will be pursued (e.g., cond_assign_eq_obj)
838 dom_range_for_specific_closure([],[],[],function(bijection)).
839 dom_range_for_specific_closure(closure(P,T,Pred),Domain,Range,Functionality) :-
840 %% print(trying_card_for_specific_closure(P,T,Pred)),nl, trace,%%
841 dom_range_for_specific_closure2(P,T,Pred, Domain,Range,Functionality).
842
843 dom_range_for_specific_closure2(Par,Typ,Body, Domain,Range,Functionality) :-
844 is_member_closure(Par,Typ,Body,TYPE,SET),
845 % print(trying_member(SET,TYPE)),nl, %%
846 dom_range_for_member_closure(SET,TYPE,Domain,Range,Functionality),!.
847 dom_range_for_specific_closure2(Par,Typ,Body, DOMAIN,RANGE,Functionality) :-
848 is_cartesian_product_closure_aux(Par,Typ,Body,SET1,SET2),!,
849 (singleton_set(SET2,_)
850 -> Functionality = function(total) % function if card(SET2)=1
851 ; Functionality=relation),
852 % print(dom_range_cart(Par,SET1,SET2)),nl,
853 kernel_equality:equality_objects(SET1,[],EqRes1), cond_assign_eq_obj(EqRes1,RANGE,[],SET2), % if SET1=[] then Range=[]
854 kernel_equality:equality_objects(SET2,[],EqRes2), cond_assign_eq_obj(EqRes2,DOMAIN,[],SET1). %if SET2=[] then Domain=[]
855 dom_range_for_specific_closure2(Par,Typ,Body, DomainRange,DomainRange,function(bijection)) :-
856 is_id_closure_over(Par,Typ,Body,DomainRange,_).
857
858
859
860 %total_function(closure([_zzzz_unary,_zzzz_binary],[integer,integer],b(equal(b(identifier(_zzzz_unary),integer,[generated]),b(identifier(_zzzz_binary),integer,[generated])),pred,[])),global_set(INTEGER),global_set(INTEGER))
861 %:- use_module(memoization,[expand_memoize_stored_function_reference/2]).
862 dom_range_for_member_closure(identity(b(value(SET1),ST1,_)),_SEQT,SET1,SET1,function(bijection)) :-
863 is_set_type(ST1,_). /* _SEQT=id(T1) */
864 dom_range_for_member_closure(cartesian_product(b(value(SET1),ST1,_), b(value(SET2),ST2,_)),
865 couple(T1,T2), DOMAIN, RANGE,Functionality) :-
866 is_set_type(ST1,T1), is_set_type(ST2,T2),
867 (singleton_set(SET2,_)
868 -> Functionality = function(total) % function if card(SET2)=1
869 ; Functionality=relation),
870 kernel_equality:equality_objects(SET1,[],EqRes1), cond_assign_eq_obj(EqRes1,RANGE,[],SET2), % if SET1=[] then Range=[]
871 kernel_equality:equality_objects(SET2,[],EqRes2), cond_assign_eq_obj(EqRes2,DOMAIN,[],SET1). %if SET2=[] then Domain=[]
872 % not sure if we need this: memoized functions are infinite usually and range can never be computed anyway
873 %dom_range_for_member_closure(Expr,_,Domain,Range,Func) :-
874 % expand_memoize_stored_function_reference(Expr,ExpandedValue),
875 % dom_range_for_specific_closure(ExpandedValue,Domain,Range,Func).
876
877 :- block cond_assign_eq_obj(-,?,?,?).
878 %cond_assign_eq_obj(PTF,R,A,B) :- var(PTF), add_error(cond_assign_eq_obj,'block declaration bug warning: ',cond_assign_eq_obj(PTF,R,A,B)),fail. % comment in to detect if affected by block declaration bug
879 cond_assign_eq_obj(pred_true,Res,A,_) :- equal_object(Res,A,cond_assign_eq_obj_1).
880 cond_assign_eq_obj(pred_false,Res,_,B) :- equal_object(Res,B,cond_assign_eq_obj_2).
881
882 is_cartesian_product_closure(closure(Par,Typ,Body),SET1,SET2) :-
883 ? is_cartesian_product_closure_aux(Par,Typ,Body,SET1,SET2).
884 %is_cartesian_product_closure_aux(Par,Types,Body,_,_) :- print(try_cart(Par,Types,Body)),nl,fail.
885 ?is_cartesian_product_closure_aux(Par,Types,b(truth,pred,Info),SET1,SET2) :- Par=[_,_|_],!,
886 ? append(LPar,[RParID],Par), append(LTypes,[RType],Types),
887 construct_closure_if_necessary(LPar,LTypes,b(truth,pred,Info),SET1),
888 construct_closure_if_necessary([RParID],[RType],b(truth,pred,Info),SET2).
889 %print(cart_closure_truth(LPar,RParID,SET1,SET2)),nl.
890 is_cartesian_product_closure_aux(Par,Types,Body,SET1,SET2) :- Par=[_,_|_],!,
891 ? append(LPar,[RParID],Par), append(LTypes,[RType],Types),!,
892 % print('try split: '), print(LPar), print('<->'), print(RParID), print(' '),translate:print_bexpr(Body),nl, %%
893 split_conjunct(Body,[RParID], RConjL, LPar, LConjL),
894 bsyntaxtree:conjunct_predicates(RConjL,RConj), bsyntaxtree:conjunct_predicates(LConjL,LConj),
895 % print('split : '), print(LPar), print(' : '), translate:print_bexpr(LConj),nl, %%
896 % print(' '), print(RParID), print(' : '), translate:print_bexpr(RConj),nl, %%
897 construct_closure_if_necessary(LPar,LTypes,LConj,SET1),
898 construct_closure_if_necessary([RParID],[RType],RConj,SET2).
899 is_cartesian_product_closure_aux(Par,Typ,Body,SET1,SET2) :-
900 SET = cartesian_product(b(value(SET1),ST1,_), b(value(SET2),ST2,_)),
901 is_member_closure(Par,Typ,Body,couple(T1,T2),SET),
902 is_set_type(ST1,T1), is_set_type(ST2,T2),!.
903 %is_cartesian_product_closure_aux([ID1,ID2],[T1,T2],FBody,SET1,SET2) :- % is this not redundant wrt split ??
904 % % a closure of the form {ID1,ID2|ID1 : SET1 & ID2 : SET2} ;
905 % % can get generated when computing domain symbolically of lambda abstraction
906 % % print(try_cart(ID1,ID2,Body)),nl, trace,
907 % FBody = b(Body,pred,_),
908 % is_cartesian_product_body(Body,ID1,ID2,T1,T2,SET1,SET2). % ,print(cart_res(SET1,SET2)),nl.
909
910 % try and split conjunct into two disjoint parts (for detecting cartesian products)
911 % on the specified variables
912 % fails if it cannot be done
913 split_conjunct(b(PRED,pred,Info),Vars1,C1,Vars2,C2) :-
914 split_conjunct_aux(PRED,Info,Vars1,C1,Vars2,C2).
915 split_conjunct_aux(truth,_Info,_Vars1,C1,_Vars2,C2) :- !,C1=[],C2=[].
916 split_conjunct_aux(conjunct(A,B),_Info,Vars1,C1,Vars2,C2) :- !, % TO DO: use DCG
917 split_conjunct(B,Vars1,CB1,Vars2,CB2), !, % Note: conjunct_predicates will create inner conjunct in A and atomic Expression in B
918 split_conjunct(A,Vars1,CA1,Vars2,CA2),!,
919 append(CA1,CB1,C1), append(CA2,CB2,C2).
920 split_conjunct_aux(E,Info,Vars1,C1,_Vars2,C2) :- unique_id_comparison(E,ID),!,
921 (member(ID,Vars1) -> C1=[b(E,pred,Info)], C2=[] ; C1=[], C2=[b(E,pred,Info)]).
922
923 unique_id_comparison(less(b(L,_,_),b(R,_,_)), ID) :- unique_id_comparison_aux(L,R,ID).
924 unique_id_comparison(less_equal(b(L,_,_),b(R,_,_)), ID) :- unique_id_comparison_aux(L,R,ID).
925 unique_id_comparison(greater(b(L,_,_),b(R,_,_)), ID) :- unique_id_comparison_aux(L,R,ID).
926 unique_id_comparison(greater_equal(b(L,_,_),b(R,_,_)), ID) :- unique_id_comparison_aux(L,R,ID).
927 unique_id_comparison(member(b(identifier(ID),_,_),b(V,_,_)), ID) :- explicit_value(V).
928 unique_id_comparison(subset(b(identifier(ID),_,_),b(V,_,_)), ID) :- explicit_value(V).
929 unique_id_comparison(equal(b(L,_,_),b(R,_,_)), ID) :- unique_id_comparison_aux(L,R,ID). % means we also detect something like %x.(x : INTEGER|0) as cartesian product
930 % what about not_equal
931
932 unique_id_comparison_aux(identifier(ID),V,ID) :- !,explicit_value(V).
933 unique_id_comparison_aux(V,identifier(ID),ID) :- explicit_value(V).
934
935 explicit_value(value(_)) :- !.
936 explicit_value(integer(_)) :- !.
937 explicit_value(unary_minus(TV)) :- !, explicit_tvalue(TV).
938 explicit_value(interval(TV1,TV2)) :- !,
939 explicit_tvalue(TV1), explicit_tvalue(TV2).
940 %explicit_value(seq(B)) :- !, explicit_tvalue(B). % are encoded as values by b_compile
941 %explicit_value(seq1(B)) :- !, explicit_tvalue(B).
942 %explicit_value(iseq(B)) :- !, explicit_tvalue(B).
943 %explicit_value(iseq1(B)) :- !, explicit_tvalue(B).
944 %explicit_value(struct(B)) :- !, explicit_tvalue(B).
945 %explicit_value(rec(Fields)) :- !, explicit_tfields(Fields).
946 explicit_value(total_bijection(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B). % see test 1897 for cases below
947 explicit_value(total_injection(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
948 explicit_value(total_function(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
949 explicit_value(total_surjection(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
950 explicit_value(partial_function(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
951 explicit_value(partial_injection(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
952 explicit_value(partial_surjection(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
953 explicit_value(relations(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
954 explicit_value(total_relation(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
955 explicit_value(surjection_relation(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
956 explicit_value(total_surjection_relation(A,B)) :- !, explicit_tvalue(A),explicit_tvalue(B).
957 explicit_value(string_set) :- !.
958 %explicit_value(X) :- print_term_summary(explicit_check_failed(X)),nl,fail.
959
960 explicit_tvalue(b(B,_,_)) :- !, explicit_value(B).
961
962 %explicit_tfields(V) :- var(V),!,fail.
963 %explicit_tfields([]).
964 %explicit_tfields([field(N,V)|T]) :- ground(N),explicit_tvalue(V),explicit_tfields(T).
965
966 % conjunct_predicates([CA1,CB1],C1),
967 % conjunct_predicates([CA2,CB2],C2).
968
969 /* *********
970 is_cartesian_product_body(conjunct(A,B),ID1,ID2,_T1,_T2,SET1,SET2) :- !,
971 member_pred_value(A,CID1,CSET1),
972 member_pred_value(B,CID2,CSET2),
973 % print(cart(CID1,CT1,CSET1,CID2,CT2,CSET2)),nl,
974 (ID1=CID1,ID2=CID2,SET1=CSET1,SET2=CSET2 ; ID1=CID2,ID2=CID1,SET1=CSET2,SET2=CSET1).
975 is_cartesian_product_body(A,ID1,ID2,T1,T2,SET1,SET2) :-
976 member_pred_value2(A,AID,ASET),
977 ( AID=ID1 -> SET1=ASET, construct_closure_if_necessary([ID2],[T2],b(truth,pred,[]),SET2)
978 ; AID=ID2 -> SET2=ASET, construct_closure_if_necessary([ID1],[T1],b(truth,pred,[]),SET1)).
979
980 member_pred_value(b(B,pred,_), ID,VAL) :- print(member_pred_value2(B,ID,VAL)),nl,
981 member_pred_value2(B,ID,VAL).
982 member_pred_value2(member(b(identifier(ID),_CT1,_),b(value(VAL),_SCT1,_)), ID,VAL). %_SCT1 = set(CT1)
983 */
984
985 % check if we have POW(SET1) or SET1<->SET2 (equiv. to POW(SET1*SET2))
986 is_full_powerset_or_relations_or_struct_closure(closure(Par,Typ,Body),SUBSETS) :-
987 %TYPE = set(T),
988 is_member_closure(Par,Typ,Body,TYPE,SET),
989 is_full_powset_aux(SET,TYPE,SUBSETS).
990
991 :- use_module(library(lists),[maplist/3]).
992 is_full_powset_aux(pow_subset(b(value(SET1),set(T1),_)),set(T1),[SET1]).
993 is_full_powset_aux(relations(S1,S2),set(couple(T1,T2)),[SET1,SET2]) :-
994 S1 = b(value(SET1),set(T1),_), S2 = b(value(SET2),set(T2),_).
995 is_full_powset_aux(struct(b(value(rec(FIELDS)),record(_),_)),record(_),FieldValueSets) :-
996 maplist(get_field_val,FIELDS,FieldValueSets).
997
998 get_field_val(field(_,Val),Val).
999
1000 %[field(duration,global_set('INTEGER')),field(rhythm,global_set('INTEGER')),field(slot,avl_set(...))]
1001
1002 is_powerset_closure(closure(Par,Typ,Body),Type,Subset) :-
1003 ? is_set_type(TYPE,T),
1004 is_member_closure(Par,Typ,Body,TYPE,SET),
1005 nonvar(SET),
1006 is_powset_aux(SET,Type,b(VS,set(T),_)) ,
1007 nonvar(VS), VS = value(Subset). %,print(powerset(Subset)),nl.
1008 is_powset_aux(pow_subset(A),pow,A).
1009 is_powset_aux(pow1_subset(A),pow1,A).
1010 is_powset_aux(fin_subset(A),fin,A).
1011 is_powset_aux(fin1_subset(A),fin1,A).
1012
1013 % group together closures which can be treated like cartesian products in the sense that:
1014 % Closure is empty if either Set1 or Set2 (could also be empty in other conditions though)
1015 % Closure is subset of other Closure if same Constructor and both sets are subsets
1016 /* is_cartesian_product_like_closure(Closure,Constructor,Set1,Set2) :-
1017 is_cartesian_product_closure(Closure,S11,S12),!,
1018 Constructor = cartesian_product,Set1=S11,Set2=S12.
1019 is_cartesian_product_like_closure(closure(Par,Typ,Body),Constructor,Set1,Set2) :-
1020 is_member_closure(Par,Typ,Body,TYPE,SET),
1021 is_cart_like_relation(SET,Constructor,b(value(Set1),set(_T1),_), b(value(Set1),set(_T2),_)).
1022 is_cart_like_relation(relations(A,B),relations,A,B).
1023 is_cart_like_relation(partial_function(A,B),partial_function,A,B).
1024 is_cart_like_relation(partial_injection(A,B),partial_injection,A,B). */
1025
1026 % (closure([_zzzz_unary],[set(couple(integer,string))],b(member(b(identifier(_zzzz_unary),set(couple(integer,string)),[]),b(relations(b(value(global_set(INTEGER)),set(integer),[]),b(value(global_set(STRING)),set(string),[])),set(set(couple(integer,string))),[])),pred,[])))
1027 % 1 1 Fail: custom_explicit_sets:is_powset_aux(relations(b(value(global_set('INTEGER')),set(integer),[]),b(value(global_set('STRING')),set(string),[])),couple(integer,string),_19584) ?
1028
1029 % card_for_specific_custom_set(+Set,-Cardinality,-CodeToComputeCardinality)
1030 % succeeds if card can be computed efficiently
1031 card_for_specific_custom_set(CS,C,Cd) :- var(CS),!,
1032 add_internal_error('Internal error: var ',card_for_specific_custom_set(CS,C,Cd)),fail.
1033 card_for_specific_custom_set(global_set(GS),Card,true) :- !, b_global_set_cardinality(GS,Card).
1034 card_for_specific_custom_set(avl_set(S),Card,true) :- !,avl_size(S,Card).
1035 card_for_specific_custom_set(closure(P,T,B),Card,CodeToComputeCard) :-
1036 card_for_specific_closure2(P,T,B,Card,CodeToComputeCard).
1037
1038 card_for_specific_closure(closure(P,T,Pred),Card,CodeToComputeCard) :-
1039 % print(trying_card_for_specific_closure(P,T,Pred)),nl, trace,%%
1040 card_for_specific_closure2(P,T,Pred,Card,CodeToComputeCard).
1041 % nl, print(calling(CodeToComputeCard)),nl,nl. %%
1042 %card_for_specific_closure(closure_x(P,T,Pred,_Exp),Card,CodeToComputeCard) :-
1043 % card_for_specific_closure2(P,T,Pred,Card,CodeToComputeCard).
1044
1045 :- use_module(btypechecker,[couplise_list/2]).
1046 :- use_module(bsyntaxtree,[is_truth/1]).
1047 card_for_specific_closure2(_,Types,Body,Card,Code) :- is_truth(Body),!,
1048 % TO DO: also treat multiple parameters
1049 couplise_list(Types,Type),
1050 Code=kernel_objects:max_cardinality(Type,Card).
1051 card_for_specific_closure2(Par,Typ,Body, Card,Code) :-
1052 is_special_infinite_closure(Par,Typ,Body),!,Card=inf, Code=true.
1053 card_for_specific_closure2(Par,Typ,Body, Card,Code) :-
1054 is_geq_leq_interval_closure(Par,Typ,Body,Low,Up), !,
1055 card_of_interval_inf(Low,Up,Card),
1056 Code=true. % should we return card_of_interval_inf as code ?
1057 % TO DO: deal with non-infinite not_member_closures, prj1, prj2, id, ...
1058 card_for_specific_closure2(Par,Typ,Body, Card,Code) :-
1059 is_lambda_value_domain_closure(Par,Typ,Body, DomainValue,_Expr),!, nonvar(DomainValue),
1060 efficient_card_for_set(DomainValue,Card,Code).
1061 card_for_specific_closure2(Par,Typ,Body, Card,Code) :-
1062 is_cartesian_product_closure_aux(Par,Typ,Body,A1,A2),!, nonvar(A1), nonvar(A2),
1063 efficient_card_for_set(A1,Card1,Code1),
1064 efficient_card_for_set(A2,Card2,Code2),
1065 Code = (Code1,Code2, custom_explicit_sets:blocking_safe_mul(Card1,Card2,Card)).
1066 card_for_specific_closure2(Par,Typ,Body, Card,Code) :-
1067 is_member_closure(Par,Typ,Body,TYPE,SET),
1068 nonvar(SET),!,
1069 card_for_member_closure(SET,TYPE,Card,Code).
1070 % Note: _ExprInfo could have: contains_wd_condition,
1071 % but if lambda is well-defined we compute the correct card ; if not then card is not well-defined anyway
1072 % maybe we should check contains_wd_condition produce a warning msg ?
1073
1074 % inner values can sometimes be a list, e.g., [pred_true,pred_false] for BOOL
1075 efficient_card_for_set(VAR,_,_) :- var(VAR),!,fail.
1076 efficient_card_for_set([],Card,Code) :- !, Card=0,Code=true.
1077 efficient_card_for_set([_|T],Card,Code) :- known_length(T,1,C), !, Card = C, Code=true.
1078 efficient_card_for_set(CS,Card,Code) :- card_for_specific_custom_set(CS,Card,Code).
1079 known_length(X,_,_) :- var(X),!,fail.
1080 known_length([],A,A).
1081 known_length([_|T],A,R) :- A1 is A+1, known_length(T,A1,R).
1082 known_length(avl_set(S),Acc,Res) :- avl_size(S,Card), %nl,print(known_length_avl(Card)),nl,nl,
1083 Res is Acc+Card.
1084 % TO DO: also support closures
1085
1086 card_for_member_closure(parallel_product(b(value(A1),ST1,_),b(value(A2),ST1,_)),_T,Card,CodeToComputeCard) :- !,
1087 nonvar(A1), nonvar(A2),
1088 efficient_card_for_set(A1,Card1,Code1),
1089 efficient_card_for_set(A2,Card2,Code2),
1090 % cardinality computed like for cartesian_product
1091 CodeToComputeCard = (Code1,Code2, custom_explicit_sets:blocking_safe_mul(Card1,Card2,Card)).
1092 card_for_member_closure(seq(b(value(SET1),ST1,_)),_SEQT,Card,CodeToComputeCard) :- !, /* _SEQT=seq(T1) */
1093 is_set_type(ST1,_T1),
1094 CodeToComputeCard = custom_explicit_sets:seq_card(SET1,Card).
1095 card_for_member_closure(seq1(b(value(SET1),ST1,_)),_SEQT,Card,CodeToComputeCard) :- !, /* _SEQT=seq1(T1) */
1096 is_set_type(ST1,_T1),
1097 CodeToComputeCard = custom_explicit_sets:seq1_card(SET1,Card).
1098 card_for_member_closure(perm(b(value(SET1),ST1,_)),_SEQT,Card,CodeToComputeCard) :- !, /* _SEQT=perm(T1) */
1099 is_set_type(ST1,_T1),
1100 CodeToComputeCard = (kernel_objects:cardinality_as_int(SET1,int(SCard)),
1101 custom_explicit_sets:blocking_factorial(SCard,Card)).
1102 card_for_member_closure(iseq(b(value(SET1),ST1,_)),_SEQT,Card,CodeToComputeCard) :- !, /* _SEQT=iseq(T1) */
1103 is_set_type(ST1,_T1),
1104 CodeToComputeCard = (kernel_objects:cardinality_as_int(SET1,int(SCard)),
1105 custom_explicit_sets:blocking_nr_iseq(SCard,Card)).
1106 card_for_member_closure(iseq1(b(value(SET1),ST1,_)),_SEQT,Card,CodeToComputeCard) :- !, /* _SEQT=iseq1(T1) */
1107 is_set_type(ST1,_T1),
1108 CodeToComputeCard = (kernel_objects:cardinality_as_int(SET1,int(SCard)),
1109 custom_explicit_sets:blocking_nr_iseq1(SCard,Card)).
1110 card_for_member_closure(identity(b(value(SET1),ST1,_)),_SEQT,Card,CodeToComputeCard) :- !, /* _SEQT=id(T1) */
1111 is_set_type(ST1,_T1),
1112 CodeToComputeCard = %(print(computing_card(id(SET1))),nl,
1113 kernel_objects:cardinality_as_int(SET1,int(Card)).
1114 card_for_member_closure(struct(b(value(RECF),record(_FieldSetTypes),_)), record(_FieldTypes),
1115 Card,CodeToComputeCard) :- %print(card_for_member_struct(FIELDS,_FieldTypes)),nl,
1116 nonvar(RECF), RECF=rec(FIELDS),
1117 !,
1118 CodeToComputeCard = custom_explicit_sets:get_field_cardinality(FIELDS,Card).
1119 % now dealt with separately above: card_for_member_closure(cartesian_product(b(value(SET1),set(T1),_), b(value(SET2),set(T2),_)),
1120 % couple(T1,T2), Card,CodeToComputeCard) :- !,
1121 % %% print(trying_cart(SET1,TYPE)),nl, %%
1122 % CodeToComputeCard =
1123 % (kernel_objects:cardinality_as_int(SET1,int(SCard1)),
1124 % kernel_objects:cardinality_as_int(SET2,int(SCard2)),
1125 % custom_explicit_sets:blocking_safe_mul(SCard1,SCard2,Card) ).
1126 card_for_member_closure(POW,TYPE, Card,CodeToComputeCard) :- %print(trying_pow(POW,TYPE)),nl,
1127 ? (POW = pow_subset(b(value(SET),TYPE,_)) ;
1128 POW = fin_subset(b(value(SET),TYPE,_))),!,
1129 CodeToComputeCard =
1130 (kernel_objects:cardinality_as_int(SET,int(SCard)),
1131 custom_explicit_sets:blocking_safe_pow2(SCard,Card)
1132 % ,(when(nonvar(Card),(print(set_res_safe_pow2(SCard,Card)),nl,trace)))
1133 %% ,print(pow_card(SCard,Card)),nl %%
1134 ).
1135 card_for_member_closure(POW,TYPE, Card,CodeToComputeCard) :- %%print(trying_pow1(POW,TYPE)),nl,
1136 (POW = pow1_subset(b(value(SET),TYPE,_)) ;
1137 POW = fin1_subset(b(value(SET),TYPE,_))),!,
1138 CodeToComputeCard =
1139 (kernel_objects:cardinality_as_int(SET,int(SCard)),
1140 custom_explicit_sets:blocking_safe_pow2(SCard,C1),
1141 custom_explicit_sets:safe_dec(C1,Card)
1142 %%,print(pow1_card(SCard,Card)),nl %%
1143 ).
1144 card_for_member_closure(RELEXPR,SType, Card,CodeToComputeCard) :-
1145 is_set_type(SType,couple(T1,T2)),
1146 is_a_relation(RELEXPR, b(value(DOM),set(T1),_),
1147 b(value(RAN),set(T2),_), DCard,RCard,Card,RELCODE),!,
1148 CodeToComputeCard =
1149 ( %%print(card_for_relations(DOM,T1,RAN,T2)),nl,
1150 kernel_objects:cardinality_as_int(DOM,int(DCard)),
1151 kernel_objects:cardinality_as_int(RAN,int(RCard)),
1152 when((ground(DCard),ground(RCard)),
1153 (call(RELCODE) %%, print(rel_card(DCard,RCard,Card)),nl %%
1154 ))).
1155 card_for_member_closure(BODY, integer, Card,CodeToComputeCard) :- % print(try_interval(BODY)),nl,
1156 is_interval_with_integer_bounds(BODY,Low,Up),!,
1157 CodeToComputeCard = custom_explicit_sets:card_of_interval_inf(Low,Up,Card).
1158 card_for_member_closure(value(Value), _Type, Card,CodeToComputeCard) :-
1159 % we have a closure of the type {x|x:S}; equivalent to S
1160 ((nonvar(Value),Value=closure(P,T,B))
1161 -> % cardinality_as_int may expand it ! is bad if e.g. we called this code to check if a closure is infinite
1162 card_for_specific_closure2(P,T,B,Card,CodeToComputeCard) % will not expand, but fail if cannot be computed
1163 % TO DO: provide an argument: precise_or_efficient
1164 ; CodeToComputeCard = kernel_objects:cardinality_as_int(Value,int(Card))
1165 ).
1166 %card_for_member_closure(BODY, Type, Card,CodeToComputeCard) :- print(try_card(BODY,Type)),nl,fail.
1167 % TO DO: add maybe other common closures ? simple value closure
1168 % also: what if subexpressions are not of value() type ?
1169
1170 :- public safe_dec/2. % used in card_for_member_closure
1171 :- block safe_dec(-,?).
1172 safe_dec(inf,R) :- !, R=inf.
1173 safe_dec(X,R) :- R is X-1.
1174
1175 :- public seq_card/2. % used in card_for_member_closure
1176 :- block seq_card(-,?).
1177 %seq_card(A,B) :- print(seq_card(A,B)),nl,fail.
1178 seq_card([],R) :- !,R=1.
1179 seq_card(_,inf).
1180
1181 :- public seq1_card/2. % used in card_for_member_closure
1182 :- block seq1_card(-,?).
1183 seq1_card([],R) :- !,R=0.
1184 seq1_card(_,inf).
1185
1186 :- public get_field_cardinality/2. % used in card_for_member_closure
1187 get_field_cardinality([],1).
1188 get_field_cardinality([field(_Name,Value)|T],ResCard) :-
1189 kernel_objects:cardinality_as_int(Value,int(SCard1)),
1190 get_field_cardinality(T,RestCard), blocking_safe_mul(SCard1,RestCard,ResCard).
1191 % print(field_card(_Name,SCard1,Value,ResCard)),nl.
1192
1193 :- block blocking_safe_mul(-,-,?).
1194 blocking_safe_mul(A,B,R) :-
1195 ( A==0 -> R=0
1196 ; B==0 -> R=0
1197 ; A==1 -> R=B
1198 ; B==1 -> R=A
1199 ; blocking_safe_mul2(A,B,R) ).
1200
1201 :- block blocking_safe_mul2(-,?,?), blocking_safe_mul2(?,-,?).
1202 blocking_safe_mul2(A,B,Res) :-
1203 (safe_mul(A,B,Res) -> true
1204 ; (var(Res), frozen(Res,[])) -> nl,print('*** FAILED: '), print(safe_mul(A,B,Res)),nl, %trace, % could happen for something like prj2(BOOL,NAT) = prj2(BOOL,0..n)
1205 fail).
1206
1207 :- public blocking_safe_pow2/2. % used in card_for_member_closure above
1208 :- block blocking_safe_pow2(-,?).
1209 blocking_safe_pow2(A,Res) :- % print(safe_pow2(A,Res)),nl,
1210 (safe_pow2(A,Res) -> true
1211 ; var(Res) -> nl,print('*** FAILED: '), print(safe_pow2(A,Res)),nl,fail).
1212
1213 :- assert_must_succeed((blocking_factorial(5,R),R==120)).
1214 :- assert_must_succeed((blocking_factorial(0,R),R==1)).
1215 :- assert_must_succeed((blocking_factorial(1,R),R==1)).
1216 :- assert_must_succeed((blocking_factorial(3,R),R==6)).
1217 :- assert_must_succeed((blocking_factorial(inf,R),R==inf)).
1218 :- block blocking_factorial(-,?).
1219 blocking_factorial(inf,R) :- !, R=inf.
1220 blocking_factorial(X,R) :- X<0,!, add_error(blocking_factorial,'Negative arg: ',blocking_factorial(X,R)),R=0.
1221 blocking_factorial(X,R) :- X>1000,!,
1222 % here we overapproximate: throw finite warning in Disprover mode ? or when checking for finite
1223 R=inf.
1224 % Note: blocking_safe_pow2(X,R) reports inf for X>1023; for X=171 blocking_factorial gives a result
1225 % which is greater than 2**1024 :
1226 % X=171,custom_explicit_sets:blocking_factorial(X,R),custom_explicit_sets:blocking_safe_pow2(1023,R2), R>2*R2.
1227 % debug:time(custom_explicit_sets:fact(10000,1,_)) --> 170 ms
1228 % debug:time(custom_explicit_sets:fact(1000,1,_)) --> 0 ms
1229 blocking_factorial(A,Res) :- fact(A,1,Res).
1230
1231 fact(0,Acc,Res) :- !,Res=Acc.
1232 fact(N,Acc,Res) :- (Acc=inf -> Res=inf
1233 ; safe_mul(N,Acc,NAcc), N1 is N-1, fact(N1,NAcc,Res)).
1234
1235
1236 :- assert_must_succeed((custom_explicit_sets:blocking_factorial_k(5,5,R),R==120)).
1237 :- assert_must_succeed((blocking_factorial_k(5,2,R),R==20)).
1238 :- assert_must_succeed((blocking_factorial_k(5,1,R),R==5)).
1239 :- assert_must_succeed((blocking_factorial_k(5,0,R),R==1)).
1240 :- assert_must_succeed((blocking_factorial_k(5,3,R),R==60)).
1241 :- assert_must_succeed((blocking_factorial_k(5,4,R),R==120)).
1242 :- assert_must_succeed((blocking_factorial_k(5,6,R),R==0)).
1243 :- assert_must_succeed((blocking_factorial_k(0,0,R),R==1)).
1244 :- assert_must_succeed((blocking_factorial_k(0,1,R),R==0)).
1245 :- assert_must_succeed((blocking_factorial_k(1,1,R),R==1)).
1246 :- assert_must_succeed((blocking_factorial_k(2,1,R),R==2)).
1247 :- assert_must_succeed((blocking_factorial_k(2,2,R),R==2)).
1248 :- assert_must_succeed((blocking_factorial_k(3,3,R),R==6)).
1249 :- assert_must_succeed((blocking_factorial_k(inf,1,R),R==inf)).
1250 :- assert_must_succeed((blocking_factorial_k(inf,0,R),R==1)).
1251 :- assert_must_succeed((blocking_factorial_k(inf,inf,R),R==inf)).
1252 :- assert_must_succeed((blocking_factorial_k(2,inf,R),R==0)).
1253 % blocking_factorial_k(N,K,Res) :: Res = N*(N-1)*...*(N-K+1)
1254 % Number of ways to choose sequences of K different objects amongst a pool of N objects
1255 :- block blocking_factorial_k(-,?,?),blocking_factorial_k(?,-,?).
1256 blocking_factorial_k(_X,0,R) :- !, R=1.
1257 blocking_factorial_k(inf,_,R) :- !, R=inf.
1258 blocking_factorial_k(_N,K,R) :- K=inf,!, R=0.
1259 blocking_factorial_k(N,K,R) :- K>N,!, R=0.
1260 blocking_factorial_k(A,K,Res) :- fact_k(A,K,1,Res).
1261
1262 fact_k(0,_,Acc,Res) :- !, Res=Acc.
1263 fact_k(_,K,Acc,Res) :- K<1,!,Res=Acc.
1264 fact_k(N,K,Acc,Res) :- (Acc=inf -> Res=inf
1265 ; safe_mul(N,Acc,NAcc), N1 is N-1, K1 is K-1, fact_k(N1,K1,NAcc,Res)).
1266
1267
1268 :- assert_must_succeed((choose_nk(3,3,R),R==1)).
1269 :- assert_must_succeed((choose_nk(3,2,R),R==3)).
1270 :- assert_must_succeed((choose_nk(3,1,R),R==3)).
1271 :- assert_must_succeed((choose_nk(3,0,R),R==1)).
1272 :- block choose_nk(-,?,?), choose_nk(?,-,?).
1273 choose_nk(N,K,Res) :- (K=0;K=N),!,Res=1.
1274 choose_nk(N,K,Res) :- K > N/2,!, KN is N-K, choose_nk2(N,KN,Res).
1275 choose_nk(N,K,Res) :- choose_nk2(N,K,Res).
1276 choose_nk2(N,K,Res) :- blocking_factorial_k(N,K,NK), blocking_factorial(K,KF),
1277 safe_div(NK,KF,Res).
1278
1279 :- assert_must_succeed((safe_div(inf,10,R),R==inf)).
1280 :- assert_must_succeed((safe_div(10,inf,R),R==0)).
1281 :- assert_must_succeed((safe_div(10,5,R),R==2)).
1282 :- assert_must_succeed((safe_div(10,6,R),R==1)).
1283 :- block safe_div(-,?,?), safe_div(?,-,?).
1284 safe_div(X,0,R) :- print(div_by_zero(X,0,R)),nl, !, R=inf.
1285 safe_div(inf,K,R) :-
1286 (number(K) -> true ; print(safe_div(inf,K,R)),nl), !, R=inf.
1287 safe_div(_N,inf,R) :- !, R=0.
1288 safe_div(X,Y,Z) :- Z is X//Y.
1289
1290 :- assert_must_succeed((safe_minus(506,501,R),R==5)).
1291 :- assert_must_succeed((safe_minus(inf,10,R),R==inf)).
1292 :- assert_must_succeed((safe_minus(10,inf,R),R==0)).
1293 :- block safe_minus(-,?,?), safe_minus(?,-,?).
1294 safe_minus(_,inf,R) :- !, print('### Warning: cannot compute X - inf'),nl, R=0.
1295 safe_minus(inf,_,R) :- !, R=inf.
1296 safe_minus(X,Y,R) :- R is X-Y.
1297
1298 :- assert_must_succeed((blocking_nr_iseq(2,R),R==5)).
1299 :- assert_must_succeed((blocking_nr_iseq(0,R),R==1)).
1300 :- assert_must_succeed((blocking_nr_iseq(1,R),R==2)).
1301 :- assert_must_succeed((blocking_nr_iseq(3,R),R==16)).
1302 :- assert_must_succeed((blocking_nr_iseq(inf,R),R==inf)).
1303 :- block blocking_nr_iseq(-,?).
1304 blocking_nr_iseq(inf,R) :- !, R=inf.
1305 blocking_nr_iseq(X,R) :- X<0,!, add_error(blocking_nr_iseq,'Negative arg: ',blocking_nr_iseq(X,R)),R=0.
1306 blocking_nr_iseq(X,R) :- X>500,!, R=inf.
1307 % Note: blocking_safe_pow2(X,R) reports inf for X>1023; for X=171 blocking_nr_iseq gives a result
1308 % which is greater than 2**1024 :
1309 % X=171,custom_explicit_sets:blocking_nr_iseq(X,R),custom_explicit_sets:blocking_safe_pow2(1023,R2), R>2*R2.
1310 % debug:time(custom_explicit_sets:nr_iseq(10000,_)) --> 250 ms
1311 % debug:time(custom_explicit_sets:nr_iseq(1000,_)) --> 10 ms
1312 % debug:time(custom_explicit_sets:nr_iseq(500,_)) --> 0 ms
1313 blocking_nr_iseq(A,Res) :- nr_iseq(A,Res). % , print(nr_iseq(A,Res)),nl.
1314 % number of injective sequences: f(N) = 1+N*(f(N-1))
1315 nr_iseq(0,Res) :- !,Res=1.
1316 nr_iseq(N,Res) :- N1 is N-1, nr_iseq(N1,N1Res),
1317 safe_mul(N,N1Res,NAcc), safe_add(NAcc,1,Res).
1318 :- public blocking_nr_iseq1/2. % used in card_for_member_closure above
1319 :- block blocking_nr_iseq1(-,?).
1320 blocking_nr_iseq1(inf,R) :- !, R=inf.
1321 blocking_nr_iseq1(A,Res1) :- blocking_nr_iseq(A,Res) , safe_add(Res,-1,Res1). %, print(nr_iseq1(A,Res1)),nl.
1322
1323 :- assert_must_succeed((custom_explicit_sets:card_for_specific_closure2(['_zzzz_binary'],[integer],
1324 b(member(b(identifier('_zzzz_binary'),integer,[generated]),
1325 b(interval(b(value(int(1)),integer,[]),b(value(int(10)),integer,[])),set(integer),[])),pred,[]),R,C),
1326 call(C),
1327 R=10)).
1328
1329 is_interval_closure_or_integerset(Var,_,_) :- var(Var),!,fail.
1330 is_interval_closure_or_integerset(global_set(X),Low,Up) :- !, get_integer_set_interval(X,Low,Up).
1331 is_interval_closure_or_integerset(Set,El,El) :- singleton_set(Set,ELX),
1332 nonvar(ELX), ELX=int(El),!. % new, useful??
1333 is_interval_closure_or_integerset(closure(P,T,B),Low,Up) :-
1334 (is_geq_leq_interval_closure(P,T,B,Low,Up) -> true ; is_interval_closure(P,T,B,Low,Up)).
1335
1336
1337 get_integer_set_interval('NAT',0,MAXINT) :- (preferences:preference(maxint,MAXINT)->true).
1338 get_integer_set_interval('NAT1',1,MAXINT) :- (preferences:preference(maxint,MAXINT)->true).
1339 get_integer_set_interval('INT',MININT,MAXINT) :-
1340 ((preferences:preference(maxint,MAXINT),preferences:preference(minint,MININT))->true).
1341 get_integer_set_interval('NATURAL',0,inf).
1342 get_integer_set_interval('NATURAL1',1,inf).
1343 get_integer_set_interval('INTEGER',minus_inf,inf).
1344 % TO DO: add minus_inf to kernel_objects !
1345
1346 :- block geq_inf(-,?), geq_inf(?,-).
1347 geq_inf(inf,_) :- !.
1348 geq_inf(minus_inf,B) :- !, B=minus_inf.
1349 geq_inf(_,minus_inf) :- !.
1350 geq_inf(A,inf) :- !, A=inf.
1351 geq_inf(A,B) :- A >= B.
1352
1353 :- block minimum_with_inf(-,-,?).
1354 % in the first three cases we can determine outcome without knowing both args
1355 minimum_with_inf(A,B,R) :- (A==minus_inf ; B==minus_inf),!,R=minus_inf.
1356 minimum_with_inf(A,B,R) :- A==inf,!,R=B.
1357 minimum_with_inf(A,B,R) :- B==inf,!,R=A.
1358 minimum_with_inf(A,B,R) :- minimum_with_inf1(A,B,R), geq_inf(A,R), geq_inf(B,R).
1359 :- block minimum_with_inf1(-,?,?), minimum_with_inf1(?,-,?).
1360 minimum_with_inf1(minus_inf,_,R) :- !, R=minus_inf.
1361 minimum_with_inf1(_,minus_inf,R) :- !, R=minus_inf.
1362 minimum_with_inf1(inf,B,R) :- !, R=B.
1363 minimum_with_inf1(A,inf,R) :- !, R=A.
1364 minimum_with_inf1(A,B,R) :- (A<B -> R=A ; R=B).
1365
1366 :- block maximum_with_inf(-,-,?).
1367 % in the first three cases we can determine outcome without knowing both args
1368 maximum_with_inf(A,B,R) :- (A==inf ; B==inf),!,R=inf.
1369 maximum_with_inf(A,B,R) :- A==minus_inf,!,R=B.
1370 maximum_with_inf(A,B,R) :- B==minus_inf,!,R=A.
1371 maximum_with_inf(A,B,R) :- maximum_with_inf1(A,B,R), geq_inf(R,A), geq_inf(R,B).
1372 :- block maximum_with_inf1(-,?,?), maximum_with_inf1(?,-,?).
1373 maximum_with_inf1(inf,_,R) :- !, R=inf.
1374 maximum_with_inf1(_,inf,R) :- !, R=inf.
1375 maximum_with_inf1(minus_inf,B,R) :- !, R=B.
1376 maximum_with_inf1(A,minus_inf,R) :- !, R=A.
1377 maximum_with_inf1(A,B,R) :- (A>B -> R=A ; R=B).
1378
1379 /* utilities for detecting interval closures */
1380 construct_interval_closure(Low,Up,Res) :- (Low==inf;Up==minus_inf),!,Res=[].
1381 construct_interval_closure(Low,Up,Res) :- number(Low),number(Up), Low>Up,!,Res=[].
1382 construct_interval_closure(Low,Up,Res) :- Up==inf,!,
1383 ( Low==0 -> Res = global_set('NATURAL')
1384 ; Low==1 -> Res = global_set('NATURAL1')
1385 ; Low==minus_inf -> Res = global_set('INTEGER')
1386 ; Low==inf -> Res = []
1387 ; construct_greater_equal_closure(Low,Res)
1388 ).
1389 construct_interval_closure(Low,Up,Res) :- Low==minus_inf,!,
1390 construct_less_equal_closure(Up,Res).
1391 construct_interval_closure(Low,Up,Res) :- Low==Up,!,
1392 (number(Low) -> construct_one_element_custom_set(int(Low),Res)
1393 ; Res = [Low]).
1394 construct_interval_closure(Low,Up,Res) :-
1395 construct_interval_set(Low,Up,Set),
1396 construct_member_closure('_zzzz_unary',integer,[],Set,Res).
1397
1398 transform_global_sets_into_closure(closure(P,T,B),closure(P,T,B)).
1399 transform_global_sets_into_closure(global_set(X),Res) :-
1400 transform_global_set_into_closure_aux(X,Res).
1401 transform_global_set_into_closure_aux('NATURAL',Res) :-
1402 construct_greater_equal_closure(0,Res).
1403 transform_global_set_into_closure_aux('NATURAL1',Res) :-
1404 construct_greater_equal_closure(1,Res).
1405 % TO DO: add INTEGER
1406
1407 construct_greater_equal_closure(X,Res) :-
1408 construct_closure(['_zzzz_unary'],[integer],
1409 b(greater_equal(b(identifier('_zzzz_unary'),integer,[]),
1410 b(value(int(X)),integer,[])), pred,[]),Res).
1411 construct_less_equal_closure(X,Res) :-
1412 construct_closure(['_zzzz_unary'],[integer],
1413 b(less_equal(b(identifier('_zzzz_unary'),integer,[]),
1414 b(value(int(X)),integer,[])), pred,[]),Res).
1415
1416
1417
1418 is_geq_leq_interval_closure([Par],[integer],b(Body,pred,_),Low,Up) :-
1419 (var(Par) -> add_internal_error('Non-ground closure: ',closure([Par],[integer],b(Body,pred,_))),fail
1420 ; get_geq_leq_bounds(Body,Par,Low,Up)).
1421
1422 infinite_interval(Low,Up) :- (Low==minus_inf -> true ; Up==inf).
1423
1424 :- assert_must_succeed((card_of_interval_inf(1,10,10))).
1425 :- assert_must_succeed((card_of_interval_inf(1,inf,R),R==inf)).
1426 :- assert_must_succeed((card_of_interval_inf(minus_inf,0,R),R==inf)).
1427 :- assert_must_succeed((card_of_interval_inf(2,2,R), R==1)).
1428 :- assert_must_succeed((card_of_interval_inf(12,2,R), R==0)).
1429 :- assert_must_succeed((card_of_interval_inf(2,B,10), B==11)).
1430 :- assert_must_succeed((card_of_interval_inf(A,12,10), A==3)).
1431 :- assert_must_succeed((card_of_interval_inf(A,12,0), A=222)).
1432 :- assert_must_succeed((card_of_interval_inf(12,B,0), B=11)).
1433 :- assert_must_fail((card_of_interval_inf(A,12,0), A=12)).
1434 % compute cardinality of interval; allow bounds to be inf and minus_inf (but if so, they must be bound straightaway)
1435 card_of_interval_inf(A,B,Card) :-
1436 ? at_least_two_vars(A,B,Card), % initially this will usually be true, if only one variable we can compute result
1437 preferences:preference(use_clpfd_solver,true),
1438 !,
1439 clpfd_interface:post_constraint(Card #= max(0,1+B-A),custom_explicit_sets:block_card_of_interval_inf(A,B,Card)).
1440 card_of_interval_inf(A,B,Card) :- block_card_of_interval_inf(A,B,Card).
1441
1442 ?at_least_two_vars(A,B,C) :- var(A),!,(var(B) -> not_infinite_bound(C) ; number(B),var(C)).
1443 at_least_two_vars(A,B,C) :- number(A), var(B),var(C).
1444 ?not_infinite_bound(A) :- (var(A) ; number(A)). % inf can only appear immediately, not for variables
1445
1446 :- block block_card_of_interval_inf(-,?,-),block_card_of_interval_inf(?,-,-).
1447 %block_card_of_interval_inf(A,B,C) :- print(card_int(A,B,C)),nl,fail.
1448 block_card_of_interval_inf(A,_,Card) :- A==minus_inf,!, Card=inf.
1449 block_card_of_interval_inf(_,B,Card) :- B==inf,!, Card=inf.
1450 block_card_of_interval_inf(From,To,Card) :- number(From),number(To),!,
1451 (From>To -> Card=0 ; Card is (To-From)+1).
1452 block_card_of_interval_inf(A,B,C) :- number(C),!, number_card_of_interval_inf_aux(C,A,B).
1453 block_card_of_interval_inf(A,B,C) :- C==inf,!,
1454 % probably this should systematically fail; if A and B are not inf/minus_inf now they will never be
1455 print(infinite_interval_requested(A,B,C)),nl,
1456 when((nonvar(A),nonvar(B)), block_card_of_interval_inf(A,B,C)).
1457 block_card_of_interval_inf(A,B,C) :- add_internal_error('Illegal call: ',card_of_interval_inf(A,B,C)).
1458 :- use_module(inf_arith,[block_inf_greater/2]).
1459 number_card_of_interval_inf_aux(0,A,B) :- !, % empty interval
1460 % if A and B are variables then they will not become inf later ??
1461 % inf can only be set directly for sets such as {x|x>4} or NATURAL1
1462 (((var(A);number(A)),(var(B);number(B)))
1463 % hence we can use ordinary comparison (with CLPFD) here
1464 -> kernel_objects:less_than_direct(B,A)
1465 % TO DO: we could do this even if both A and B are variables !! ex : {n,m|n..m = {} & m..100={} & 103..n={}}
1466 ; block_inf_greater(A,B)).
1467 %number_card_of_interval_inf_aux(Card,From,B) :- number(From),!, B is (From+Card)-1.
1468 %number_card_of_interval_inf_aux(Card,A,To) :- number(To),!, A is 1+To-Card.
1469 number_card_of_interval_inf_aux(Card,A,B) :- %print(card(Card,A,B)),nl,
1470 Card>0, C1 is Card-1,
1471 kernel_objects:int_minus(int(B),int(A),int(C1)).
1472
1473
1474 get_geq_leq_bounds(conjunct(b(LEFT,pred,_),b(RIGHT,pred,_)), Par,Low,Up) :-
1475 % print(conjunct_left(LEFT)),nl,
1476 get_geq_leq_bounds(LEFT,Par,From1,To1),
1477 % print(conjunct_right(RIGHT)),nl,
1478 get_geq_leq_bounds(RIGHT,Par,From2,To2),
1479 % print(intersect_intervals_with_inf(From1,To1,From2,To2)),nl,
1480 intersect_intervals_with_inf(From1,To1,From2,To2,Low,Up).
1481 get_geq_leq_bounds(member(b(identifier(Par),integer,_),
1482 b(Value,set(integer),_)),Par,Low,Up) :-
1483 get_value_bounds(Value,Low,Up).
1484 get_geq_leq_bounds(greater_equal(b(A,_,_),b(B,_,_)),Par,Low,Up) :- get_bounds2(greater_equal,A,B,Par,Low,Up).
1485 get_geq_leq_bounds( less_equal(b(A,_,_),b(B,_,_)),Par,Low,Up) :- get_bounds2(less_equal,A,B,Par,Low,Up).
1486 get_geq_leq_bounds( greater(b(A,_,_),b(B,_,_)),Par,Low,Up) :- get_bounds2(greater,A,B,Par,Low,Up).
1487 get_geq_leq_bounds( less(b(A,_,_),b(B,_,_)),Par,Low,Up) :- get_bounds2(less,A,B,Par,Low,Up).
1488
1489 get_value_bounds(value(GS),Low,Up) :- is_interval_closure_or_integerset(GS,Low,Up). % recursive call
1490 % nonvar(GS), GS=global_set(ISET), get_integer_set_interval(ISET,Low,Up).
1491 get_value_bounds(interval(b(TLow,_,_),b(TUp,_,_)),Low,Up) :-
1492 integer_value(TLow,Low),
1493 integer_value(TUp,Up).
1494
1495 get_bounds2(greater_equal,identifier(Par),V,Par,X,inf) :- integer_value(V,X).
1496 get_bounds2(greater_equal,V,identifier(Par),Par,minus_inf,X) :- integer_value(V,X).
1497 get_bounds2(less_equal,identifier(Par),V,Par,minus_inf,X) :- integer_value(V,X).
1498 get_bounds2(less_equal,V,identifier(Par),Par,X,inf) :- integer_value(V,X).
1499 get_bounds2(greater,identifier(Par),V,Par,X1,inf) :- integer_value(V,X), kernel_objects:int_plus(int(X),int(1),int(X1)). %, X1 is X+1.
1500 get_bounds2(greater,V,identifier(Par),Par,minus_inf,X1) :- integer_value(V,X), kernel_objects:int_minus(int(X),int(1),int(X1)). %X1 is X-1.
1501 get_bounds2(less,V,identifier(Par),Par,X1,inf) :- integer_value(V,X), kernel_objects:int_plus(int(X),int(1),int(X1)). %X1 is X+1.
1502 get_bounds2(less,identifier(Par),V,Par,minus_inf,X1) :- integer_value(V,X),
1503 kernel_objects:int_minus(int(X),int(1),int(X1)). %X1 is X-1.
1504 % to do: add negation thereof ??
1505
1506 integer_value(V,_) :- var(V),!, print(var_integer_value(V)),nl,fail.
1507 integer_value(integer(X),R) :- !, R=X.
1508 integer_value(unary_minus(b(X,_,_)),R) :- !, integer_value(X,RM),
1509 number(RM), % if RM is not a number we could setup CLPFD constraint ?!
1510 R is -(RM).
1511 integer_value(minus(b(X,_,_),b(Y,_,_)),R) :- !, % some AST compilation rules generate X-1, X+1 ...
1512 integer_value(X,RMX),
1513 integer_value(Y,RMY),
1514 kernel_objects:int_minus(int(RMX),int(RMY),int(R)).
1515 integer_value(plus(b(X,_,_),b(Y,_,_)),R) :- !, % some AST compilation rules generate X-1, X+1 ...
1516 integer_value(X,RMX),
1517 integer_value(Y,RMY),
1518 kernel_objects:int_plus(int(RMX),int(RMY),int(R)).
1519 integer_value(value(V),R) :- !, V=int(R).
1520 %integer_value(X,_) :- print(not_integer_value(X)),nl,fail.
1521
1522 is_interval_closure(closure(Par,[integer],Pred),Low,Up) :-
1523 is_interval_closure_aux(Par,Pred,Low,Up).
1524 is_interval_closure(Par,[integer],Pred,Low,Up) :-
1525 is_interval_closure_aux(Par,Pred,Low,Up).
1526 is_interval_closure_aux(Par,Pred,Low,Up) :-
1527 is_member_closure(Par,[integer],Pred,integer,Set),
1528 is_interval_with_integer_bounds(Set,Low,Up).
1529 %is_interval_closure(closure_x(Par,[integer],Pred,_),Low,Up) :-
1530 % is_interval_closure(closure(Par,[integer],Pred),Low,Up).
1531
1532 is_interval_closure_body(Body,ID,Low,Up) :-
1533 is_member_closure([ID],[integer],Body,integer,Set),!,
1534 is_interval_with_integer_bounds(Set,Low,Up).
1535 is_interval_closure_body(Body,ID,Low,Up) :-
1536 is_geq_leq_interval_closure([ID],[integer],Body,Low,Up),
1537 number(Low), number(Up).
1538
1539 :- use_module(bsyntaxtree,[get_texpr_info/2,get_texpr_id/2]).
1540 % do a single check if we have interval, member or not-member closure, avoiding redundant checking
1541 % TO DO: move this and related predicates to closures module ?
1542 is_special_closure(_Ids,_Types,Pred,Result) :-
1543 get_texpr_info(Pred,Info),memberchk(prob_annotation(recursive(RId)),Info),!,
1544 Result = recursive_special_closure(RId).
1545 is_special_closure([ID],[TYPE],b(PRED,_,_), Result) :-
1546 ( closures:is_member_closure_aux(PRED, ID,TYPE,SET) ->
1547 ( (TYPE=integer, is_interval_with_integer_bounds(SET,Low,Up)) ->
1548 Result = interval(Low,Up)
1549 ; Result = member_closure(ID,TYPE,SET))
1550 ; closures:is_not_member_closure_aux(PRED,ID,TYPE,SET) ->
1551 Result = not_member_closure(ID,TYPE,SET)
1552 ; (TYPE=integer,get_geq_leq_bounds(PRED,ID,Low,Up),number(Low), number(Up)) ->
1553 Result = interval(Low,Up)
1554 ).
1555
1556
1557 construct_interval_set(Low,Up,Res) :-
1558 Res = interval(b(value(int(Low)),integer,[]),
1559 b(value(int(Up)), integer,[])).
1560 is_interval_with_integer_bounds(X,L,U) :- var(X),!,
1561 add_internal_error('var arg: ',is_interval_with_integer_bounds(X,L,U)),fail.
1562 is_interval_with_integer_bounds(interval(b(LOW,integer,_),b(UP, integer,_)),Low,Up) :-
1563 integer_value(LOW,Low), integer_value(UP,Up).
1564
1565 :- use_module(kernel_objects,[safe_mul/3, safe_add/3, safe_pow2/2, safe_pown/3]).
1566
1567 is_a_relation(relations(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '<->'
1568 Code = (kernel_objects:safe_mul(DCard,RCard,Exp), kernel_objects:safe_pow2(Exp,Card)).
1569 is_a_relation(partial_function(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '+->'
1570 Code = (kernel_objects:safe_add(RCard,1,R1),kernel_objects:safe_pown(R1,DCard,Card)).
1571 is_a_relation(total_function(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '-->'
1572 Code = (kernel_objects:safe_pown(RCard,DCard,Card)).
1573 is_a_relation(partial_bijection(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '>+>>'
1574 Code = (custom_explicit_sets:partial_bijection_card(DCard,RCard,Card)).
1575 is_a_relation(total_bijection(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '>->>'
1576 Code = (custom_explicit_sets:total_bijection_card(DCard,RCard,Card)).
1577 is_a_relation(total_injection(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '>->'
1578 Code = (custom_explicit_sets:blocking_factorial_k(RCard,DCard,Card)).
1579 is_a_relation(partial_injection(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '>+>'
1580 Code = (custom_explicit_sets:partial_injection_card(DCard,RCard,Card)).
1581 is_a_relation(total_surjection(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '-->>'
1582 Code = (custom_explicit_sets:total_surjection_card(DCard,RCard,Card)).
1583 is_a_relation(partial_surjection(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '+->>'
1584 Code = (custom_explicit_sets:partial_surjection_card(DCard,RCard,Card)).
1585 is_a_relation(total_relation(Domain,Range),Domain,Range,DCard,RCard,Card,Code) :- %% '<<->'
1586 Code = (custom_explicit_sets:total_relation_card(DCard,RCard,Card)).
1587 % TO DO: total_surjective_relation <<->> , surjective_relation <->>
1588
1589
1590 :- assert_must_succeed((custom_explicit_sets:total_relation_card(0,inf,R),R==1)).
1591 :- assert_must_succeed((custom_explicit_sets:total_relation_card(2,inf,R),R==inf)).
1592 :- assert_must_succeed((custom_explicit_sets:total_relation_card(inf,0,R),R==0)).
1593 :- assert_must_succeed((custom_explicit_sets:total_relation_card(inf,1,R),R==1)).
1594 :- assert_must_succeed((custom_explicit_sets:total_relation_card(inf,2,R),R==inf)).
1595 :- assert_must_succeed((custom_explicit_sets:total_relation_card(inf,inf,R),R==inf)).
1596 :- assert_must_succeed((custom_explicit_sets:total_relation_card(2,2,R),R==9)).
1597 :- assert_must_succeed((custom_explicit_sets:total_relation_card(2,3,R),R==49)).
1598
1599 :- block total_relation_card(-,?,?), total_relation_card(?,-,?).
1600 total_relation_card(0,_RanC,Card) :- !, Card=1. % empty set is a solution
1601 total_relation_card(_DomC,0,Card) :- !, Card=0. % no element to choose from in the range
1602 total_relation_card(inf,RanC,Card) :- !, (RanC=1 -> Card=1 ; Card=inf).
1603 total_relation_card(_,inf,Card) :- !, Card=inf.
1604 total_relation_card(DomC,RanC,Card) :- safe_pow2(RanC,SubRan),
1605 safe_minus(SubRan,1,S1), % as we have a total relation we cannot choose empty set
1606 safe_pown(S1,DomC,Card).
1607
1608 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(2,inf,R),R==0)).
1609 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(inf,2,R),R==inf)).
1610 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(inf,inf,R),R==inf)).
1611 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(3,2,R),R==6)).
1612 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(2,2,R),R==2)).
1613 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(1,2,R),R==0)).
1614 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(2,1,R),R==2)).
1615 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(5,3,R),R==60)).
1616 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(6,4,R),R==360)).
1617 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(10,1,R),R==10)).
1618 :- assert_must_succeed((custom_explicit_sets:partial_bijection_card(10,2,R),R==90)).
1619
1620 :- block partial_bijection_card(-,?,?), partial_bijection_card(?,-,?).
1621 partial_bijection_card(_X,0,R) :- !, R=1. % the empty set is a solution
1622 partial_bijection_card(inf,X,R) :- !,
1623 print_inf_warning(X,'>+>>'), % we could have : INTEGER >+>> POW(INTEGER); TO DO: use omega(inf) for POW ?
1624 R=inf. % we know _X>0
1625 partial_bijection_card(_X,inf,R) :- !, R=0. % _X<inf -> no way to cover all elements in range
1626 partial_bijection_card(DomCard,RanCard,Res) :- DomCard<RanCard,!,Res=0.
1627 partial_bijection_card(DomCard,RanCard,XCard) :-
1628 choose_nk(DomCard,RanCard,CNK), % ways to choose domain of size RanCard
1629 blocking_factorial(RanCard,Card), %print(pbij(DomCard,RanCard,CNK,Card)),nl,
1630 safe_mul(CNK,Card,XCard).
1631
1632 print_inf_warning(inf,FUN) :- print('### WARNING: Assuming '),
1633 print(FUN), print(' exists for two infinite sets'),nl.
1634 print_inf_warning(_,_).
1635
1636 :- assert_must_succeed((custom_explicit_sets:partial_surjection_card(0,2,R),R==0)).
1637 :- assert_must_succeed((custom_explicit_sets:partial_surjection_card(0,0,R),R==1)).
1638 :- assert_must_succeed((custom_explicit_sets:partial_surjection_card(2,0,R),R==1)).
1639 :- assert_must_succeed((custom_explicit_sets:partial_surjection_card(1,1,R),R==1)).
1640 :- assert_must_succeed((custom_explicit_sets:partial_surjection_card(inf,2,R),R==inf)).
1641 :- assert_must_succeed((custom_explicit_sets:partial_surjection_card(2,inf,R),R==0)).
1642 :- assert_must_succeed((custom_explicit_sets:partial_surjection_card(inf,inf,R),R==inf)).
1643 :- assert_must_succeed((custom_explicit_sets:partial_surjection_card(3,2,R),R==12)).
1644 :- block partial_surjection_card(-,?,?), partial_surjection_card(?,-,?).
1645 partial_surjection_card(_X,0,R) :- !, R=1. % the empty set is a solution
1646 partial_surjection_card(inf,X,R) :- !,print_inf_warning(X,'+->>'),R=inf. % we know _X>0
1647 partial_surjection_card(_X,inf,R) :- !, R=0. % _X<inf -> no way to cover all elements in range
1648 partial_surjection_card(A,B,Res) :- tsurjcard(A,1,B,Res). % 1 because we can choose to leave the function undefined
1649
1650 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(0,2,R),R==0)).
1651 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(0,0,R),R==1)).
1652 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(2,0,R),R==0)).
1653 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(inf,0,R),R==0)).
1654 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(inf,1,R),R==1)).
1655 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(inf,2,R),R==inf)).
1656 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(2,inf,R),R==0)).
1657 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(0,inf,R),R==0)).
1658 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(inf,inf,R),R==inf)).
1659 :- assert_must_succeed((custom_explicit_sets:total_surjection_card(3,2,R),R==6)).
1660 :- block total_surjection_card(-,?,?), total_surjection_card(?,-,?).
1661 total_surjection_card(0,Range,R) :- !,(Range=0 -> R=1 % the empty set is a solution
1662 ; R=0). % no solution
1663 total_surjection_card(_X,0,R) :- !, R=0. % as _X>0 there is no way to construct a total function
1664 total_surjection_card(_X,1,R) :- !, R=1. % we only have one choice for every element of _X
1665 total_surjection_card(inf,X,R) :- !,print_inf_warning(X,'-->>'),R=inf. % we know _X>0
1666 total_surjection_card(_X,inf,R) :- !, R=0. % _X<inf -> no way to cover all elements in range
1667 total_surjection_card(A,B,Res) :- tsurjcard(A,0,B,Res).
1668
1669 tsurjcard(Rem,_AlreadyUsed,StillToBeUsed,Res) :- Rem<StillToBeUsed,!,Res=0. % no solution
1670 tsurjcard(0,_AlreadyUsed,_StillToBeUsed,Res) :- !, Res=1. % we have finished
1671 tsurjcard(Rem,AlreadyUsed,StillToBeUsed,Res) :-
1672 R1 is Rem-1, A1 is AlreadyUsed+1, S1 is StillToBeUsed-1,
1673 (AlreadyUsed=0 -> ResA=0 ; tsurjcard(R1,AlreadyUsed,StillToBeUsed,ResA)),
1674 (StillToBeUsed=0 -> ResB =0 ; tsurjcard(R1,A1,S1,ResB)),
1675 Res is AlreadyUsed*ResA+StillToBeUsed*ResB.
1676
1677
1678
1679 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(1,1,R),R==2)).
1680 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(1,2,R),R==3)).
1681 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(1,100,R),R==101)).
1682 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(0,100,R),R==1)).
1683 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(1,inf,R),R==inf)).
1684 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(0,inf,R),R==1)).
1685 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(5,0,R),R==1)).
1686 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(inf,0,R),R==1)).
1687 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(inf,1,R),R==inf)).
1688 :- assert_must_succeed((custom_explicit_sets:partial_injection_card(5,1,R),R==6)).
1689
1690 :- block partial_injection_card(-,?,?), partial_injection_card(?,-,?).
1691 partial_injection_card(Dom,Ran,R) :- (Dom=0;Ran=0),!, R=1. % only one solution: empty function
1692 partial_injection_card(Dom,1,R) :- !, (Dom=inf -> R=inf ; R is Dom+1). % empty function + for every domain element one function
1693 partial_injection_card(inf,inf,Card) :- !, print_inf_warning(inf,'>+>'), Card=inf.
1694 partial_injection_card(Dom,Ran,R) :- (Dom=inf;Ran=inf),!, R=inf.
1695 partial_injection_card(Dom,Ran,R) :- Dom>1000,Ran>1000,!, R=inf. % TO DO: refine this
1696 % would give a result larger than blocking_factorial(1000)
1697 partial_injection_card(DCard,RCard,Card) :-
1698 %print(partial_injection_card(DCard,RCard)),nl,
1699 pinj_card(1,DCard,RCard,1,Card). %, print(result(DCard,RCard,Card)),nl.
1700
1701 % TO DO: can we compute this directly rather than using recursion ?
1702 pinj_card(I,M,N,Acc,Res) :- (I>M ; I>N ; Acc=inf),!, Res=Acc.
1703 pinj_card(I,M,N,Acc,Res) :-
1704 %print(pinj_card(I,M,N,Acc,Res)),nl,
1705 choose_nk(M,I,MI), % ways to choose domain of size I
1706 blocking_factorial_k(N,I,NI), % ways to map the domain of size I to N
1707 safe_mul(MI,NI,MINI), safe_add(MINI,Acc,NewAcc),
1708 %print(pinj(I,M,N,MI,NI,MINI,NewAcc)),nl,
1709 I1 is I+1, pinj_card(I1,M,N,NewAcc,Res).
1710
1711 :- public total_bijection_card/3. % exported in is_a_relation above
1712 :- block total_bijection_card(-,?,?), total_bijection_card(?,-,?).
1713 total_bijection_card(inf,inf,Card) :- !, print_inf_warning(inf,'>->>'), Card=inf.
1714 total_bijection_card(DCard,RCard,Card) :- DCard \= RCard,!,Card=0.
1715 total_bijection_card(RCard,RCard,Card) :- blocking_factorial(RCard,Card).
1716
1717
1718
1719
1720 :- block is_infinite_global_set(-,?).
1721 is_infinite_global_set('NATURAL',integer).
1722 is_infinite_global_set('NATURAL1',integer).
1723 is_infinite_global_set('INTEGER',integer).
1724 is_infinite_global_set('STRING',string).
1725
1726 %is_finite_integer_global_set('NAT').
1727 %is_finite_integer_global_set('NAT1').
1728 %is_finite_integer_global_set('INT').
1729
1730 % detects (certain) infinite explict sets
1731 is_infinite_explicit_set(X) :- var(X),!, add_internal_error(is_infinite_explicit_set,var(X)),fail.
1732 is_infinite_explicit_set(global_set(X)) :- is_infinite_global_set(X,_).
1733 is_infinite_explicit_set(freetype(X)) :- is_infinite_freetype(X).
1734 is_infinite_explicit_set(closure(Par,T,Body)) :- is_infinite_closure(Par,T,Body).
1735
1736 % detect some closure that we should definitely expand; even in SYMBOLIC mode or for ABSTRACT_CONSTANTS
1737 definitely_expand_this_explicit_set(closure(P,_T,B)) :-
1738 B = b(Body,_,_), definitely_expand(Body,P).
1739 % some lambda functions have small domain, but are very complicated to compute (test 1078, 1376)
1740 % hence the following is not sufficient:
1741 % ;is_small_specific_custom_set(closure(P,T,B),100), print(exp(T)),nl,translate:print_bexpr(B),nl,fail).
1742
1743 definitely_expand(Body,_) :- avl_mem_construct(Body,_).
1744 definitely_expand(exists(TEIDS,Body),P) :- P = [ID], TEIDS = [TEID], % TO DO: detect multiple ids
1745 % detect {res|#y.(y:AVL & res=Expr(y))} % test 1101
1746 Body = b(conjunct(b(Mem,pred,_),Eq),pred,_),
1747 Eq = b(equal(EqA,EqB),pred,_),
1748 avl_mem_construct(Mem,LHS), get_texpr_id(LHS,EID), get_texpr_id(TEID,EID),
1749 (get_texpr_id(EqA,ID) -> true ; get_texpr_id(EqB,ID)).
1750
1751 avl_mem_construct(member(LHS,RHS),LHS) :- RHS = b(value(V),_,_), nonvar(V), V=avl_set(_).
1752
1753 ?dont_expand_this_explicit_set(closure(P,T,B)) :- !, dont_expand_this_closure(P,T,B).
1754 dont_expand_this_explicit_set(S) :- is_infinite_or_very_large_explicit_set(S).
1755
1756 % true if we have a closure / global_set that should not be expanded
1757 dont_expand_symbolic_explicit_set(closure(P,T,B)) :- !, dont_expand_this_closure(P,T,B).
1758 dont_expand_symbolic_explicit_set(avl_set(_)) :- !, fail. % already expanded
1759 dont_expand_symbolic_explicit_set(S) :- is_infinite_or_very_large_explicit_set(S).
1760
1761
1762 dont_expand_this_explicit_set(closure(P,T,B),Limit) :- !, dont_expand_this_closure(P,T,B,Limit).
1763 dont_expand_this_explicit_set(S,_) :- is_infinite_or_very_large_explicit_set(S).
1764
1765 ?dont_expand_this_closure(P,T,B) :- dont_expand_this_closure(P,T,B,20000).
1766
1767 dont_expand_this_closure(P,T,B,_Limit) :- %print(check_expand(P,T,B)),nl,
1768 is_interval_closure_or_integerset(closure(P,T,B),Low,Up), !,
1769 % interval closures are quite efficient for certain manipulations
1770 (number(Low), number(Up)
1771 -> Size is Up+1-Low, Size>100 % another magic constant ; which value to choose ??
1772 ; true % we have a closure with inf/minus_inf or variables as bounds; in both cases keep the closure
1773 ).
1774 dont_expand_this_closure(_P,_T,b(_,_,INFO),_Limit) :- %print(check_info(INFO)),nl,
1775 ? member(prob_annotation('SYMBOLIC'),INFO). % not yet generated by parser or type checker
1776 dont_expand_this_closure(P,T,B,Limit) :- is_infinite_or_very_large_closure(P,T,B,Limit).
1777
1778 is_recursive_closure(_P,_T,b(_,_,INFO)) :-
1779 ? member(prob_annotation('RECURSIVE'),INFO).
1780 is_symbolic_closure(V) :- nonvar(V), V=closure(P,T,B),
1781 is_symbolic_closure(P,T,B).
1782 is_symbolic_closure(_P,_T,b(_,_,INFO)) :-
1783 member(prob_annotation('SYMBOLIC'),INFO).
1784 is_converted_lambda_closure(_P,_T,b(_,_,INFO)) :-
1785 ? member(prob_annotation('LAMBDA'),INFO).
1786 is_symbolic_closure_or_symbolic_mode(P,T,B) :-
1787 (is_symbolic_closure(P,T,B) -> true
1788 ; preference(convert_comprehension_sets_into_closures,true) % by default suppose closures should be dealt with symbolically
1789 ).
1790 /*
1791 % check both LAMBDA + not RECURSIVE
1792 is_converted_non_recursive_lambda_closure(_,_,b(_,_,INFO)) :- is_conv_lambda_nonrec(INFO).
1793 is_conv_lambda_nonrec([prob_annotation(A)|T]) :- !,
1794 (A='LAMBDA' -> \+ memberchk(prob_annotation('RECURSIVE'),T)
1795 ; A\='RECURSIVE' -> is_conv_lambda_nonrec(T)).
1796 is_conv_lambda_nonrec([_|T]) :- is_conv_lambda_nonrec(T). */
1797
1798 mark_closure_as_symbolic(C,R) :- mark_closure(C,['SYMBOLIC'],R).
1799 mark_closure_as_recursive(C,R) :- mark_closure(C,['SYMBOLIC','RECURSIVE'],R).
1800 :- block mark_closure(-,?,?).
1801 mark_closure(closure(P,T,B),ANN,R) :- !, mark_aux(P,T,B,ANN,R).
1802 mark_closure(A,_,Res) :- equal_object(A,Res). % not a closure
1803 :- block mark_aux(?,?,-,?,?).
1804 mark_aux(P,T,b(Pred,pred,INFO),ANN,Res) :-
1805 (ground(INFO) -> mark_info(ANN,INFO,RINFO) %,print(marked_closure(P,RINFO)),nl
1806 ; add_error(mark_aux,'Info field not set: ',closure(P,T,b(Pred,pred,INFO))),
1807 RINFO=INFO),
1808 Res = closure(P,T,b(Pred,pred,RINFO)).
1809
1810 mark_info([],INFO,INFO).
1811 mark_info([ANN|T],INFO,Res) :-
1812 ? (member(prob_annotation(ANN),INFO) -> Res=TRes ; Res = [prob_annotation(ANN)|TRes]),
1813 mark_info(T,INFO,TRes).
1814
1815
1816 % a set that is so large that expanding it would probably cause problems
1817 is_infinite_or_very_large_explicit_set(S) :- is_infinite_or_very_large_explicit_set(S,20000).
1818
1819 is_infinite_or_very_large_explicit_set(X,_) :- var(X),!,print(var_is_infinite_check(X)),nl,fail.
1820 is_infinite_or_very_large_explicit_set(closure(P,T,B),Limit) :- !,
1821 % treat closure separately here; some special rules
1822 is_infinite_or_very_large_closure(P,T,B,Limit).
1823 is_infinite_or_very_large_explicit_set(avl_set(A),Limit) :- !, % we could compute log and use avl_height_less_than
1824 quick_avl_approximate_size(A,Size), Size >= Limit.
1825 is_infinite_or_very_large_explicit_set(X,Limit) :- % closures are checked above
1826 explicit_set_cardinality(X,Card),
1827 card_gt_limit(Card,Limit).
1828
1829
1830 is_very_large_or_symbolic_closure(P,T,B,Limit) :-
1831 (is_symbolic_closure(P,T,B) -> true ; is_infinite_or_very_large_closure(P,T,B,Limit)).
1832 :- use_module(bsyntaxtree,[is_a_disjunct/3]).
1833 is_infinite_or_very_large_closure(P,T,B,Limit) :-
1834 is_a_disjunct(B,D1,D2), % Assumption: there is no card_for_specific_closure code for disjuncts
1835 !,
1836 (is_infinite_or_very_large_closure(P,T,D1,Limit) -> true
1837 ; is_infinite_or_very_large_closure(P,T,D2,Limit)).
1838 is_infinite_or_very_large_closure(Par,T,Body,Limit) :-
1839 is_closure1_value_closure(Par,T,Body,VAL),!,
1840 % print(check_infinite(VAL,Limit)),nl,
1841 nonvar(VAL), % it could still be large or infinite
1842 (Limit>1 -> NLimit is Limit/2 ; NLimit = Limit), % reduce limit as closure1 usually blows up
1843 is_infinite_or_very_large_explicit_set(VAL,NLimit).
1844 is_infinite_or_very_large_closure(P,T,B,Limit) :-
1845 %print(check),nl,translate:print_bvalue(CS),nl,
1846 %hashing:super_hash(CS,H),print(hash(H)),nl, (H==245697886 -> trace ; true),
1847 card_for_specific_closure2(P,T,B,Card,Code), call(Code),!,
1848 %print(card_of_cs(Card,Limit)),nl,
1849 card_gt_limit(Card,Limit).
1850
1851 card_gt_limit(Card,Limit) :- (Card==inf -> true ; number(Card),Card>Limit).
1852
1853 is_infinite_or_symbolic_closure(P,T,B) :-
1854 (is_symbolic_closure(P,T,B) -> true ; is_infinite_closure(P,T,B)).
1855 is_infinite_closure(P,T,B) :-
1856 is_a_disjunct(B,D1,D2), % Assumption: there is no card_for_specific_closure code for disjuncts
1857 !,
1858 (is_infinite_closure(P,T,D1) -> true ; is_infinite_closure(P,T,D2)).
1859 is_infinite_closure(Par,T,Body) :-
1860 is_closure1_value_closure(Par,T,Body,VAL),!, % TO DO: also check if closure1 is large this way
1861 %print(check_infinite(VAL)),nl,
1862 nonvar(VAL), % if var: it could still be infinite !! TO DO fix
1863 is_infinite_explicit_set(VAL).
1864 is_infinite_closure(Par,T,Body) :- % print(checking_inf_closure(Par,T,Body)),nl,
1865 card_for_specific_closure(closure(Par,T,Body),Card,Code),
1866 call(Code),ground(Card), Card == inf.
1867
1868
1869 :- use_module(memoization,[compute_memo_hash/2, get_stored_memo_expansion/3, store_memo_expansion/3]).
1870 /* transitive closure */
1871 closure1_for_explicit_set(avl_set(A),Res) :-
1872 preferences:preference(use_closure_expansion_memoization,true),!,
1873 compute_memo_hash(closure1_for_explicit_set(A),Hash),
1874 (get_stored_memo_expansion(Hash,closure1_for_explicit_set(A),StoredResult)
1875 -> Res = StoredResult
1876 ; closure1_for_explicit_set_direct(avl_set(A),Result),
1877 store_memo_expansion(Hash,closure1_for_explicit_set(A),Result),
1878 Res = Result
1879 ).
1880 closure1_for_explicit_set(avl_set(A),Res) :- closure1_for_explicit_set_direct(avl_set(A),Res).
1881
1882 % sometimes faster, but can also be considerably slower:
1883 %:- use_module(probsrc(avl_ugraphs),[avl_transitive_closure/2]).
1884 %closure1_for_explicit_set_direct(avl_set(A),Res) :-
1885 % avl_transitive_closure(A,TC),
1886 % construct_avl_set(TC,Res).
1887 closure1_for_explicit_set_direct(avl_set(A),Res) :-
1888 avl_domain(A,AList),
1889 %debug:time(custom_explicit_sets:iterate_closure(AList,A,A,IterationRes)),
1890 iterate_closure(AList,A,A,IterationRes),
1891 construct_avl_set(IterationRes,Res).
1892
1893 /* transitive closure starting from some initial set */
1894 /* not sure if we should do this:
1895 closure1_for_explicit_set_from(avl_set(A),StartFrom,Res) :-
1896 preferences:preference(use_closure_expansion_memoization,true),
1897 compute_memo_hash(closure1_for_explicit_set(A),Hash),
1898 stored_expansion(Hash,closure1_for_explicit_set(A),StoredResult),!,
1899 domain_restriction_explicit_set(StartFrom,StoredResult,Res). */
1900 closure1_for_explicit_set_from(avl_set(A),StartFrom,Res) :-
1901 avl_domain(A,AList),
1902 filter_start_relation(AList,StartFrom,FAList),
1903 (FAList = [] -> Res=[]
1904 ; convert_to_avl(FAList,avl_set(Start)),
1905 %debug:time(custom_explicit_sets:iterate_closure(FAList,A,Start,IterationRes)),
1906 iterate_closure(FAList,A,Start,IterationRes),
1907 construct_avl_set(IterationRes,Res)).
1908 filter_start_relation([],_,[]).
1909 filter_start_relation([(X,Y)|T],StartSet,Res) :-
1910 (element_of_custom_set(X,StartSet) -> Res = [(X,Y)|RT] ; Res=RT),
1911 filter_start_relation(T,StartSet,RT).
1912
1913 iterate_closure([],_,Res,Res).
1914 iterate_closure([(X,Y)|T],InitialRelation,Relation,Res) :- %print(iterate(Key,InitialRelation,Relation,Res)),
1915 %(Key = (X,Y) -> true ; add_error_and_fail(iterate_closure,'Not a relation element: ',Key)),
1916 add_tuples(X,Y,InitialRelation,Relation,NewRelation,AddedTuples),
1917 % better: do added tuples straight away ?
1918 iterate_closure(T,InitialRelation,NewRelation,NewRelation2),
1919 iterate_closure(AddedTuples,InitialRelation,NewRelation2,Res).
1920
1921 add_tuples(X,Y,AVL,AVLClosureSoFar,Res,NewTuples) :-
1922 findall((X,Z), (avl_fetch_pair(Y,AVL,Z), %ok instead of safe_avl_member((Y,Z),AVL),; Y in AVL form, Z var
1923 %Y \= Z, % self-loops are already in initial AVLClosure, this will never add a new pair
1924 % if we use AVLClosureSoFar instead of AVL: considerably slower
1925 \+ avl_fetch((X,Z),AVLClosureSoFar)), NewTuples),
1926 add_to_avl(NewTuples,AVLClosureSoFar,Res).
1927
1928 :- use_module(bsyntaxtree,[create_negation/2]).
1929 % SUBSET_OF <:
1930 % subset_of_explicit_set: returns code to be executed if this subset check can be done in an optimized way
1931 % TO DO: add strict_subset <<: + more cases, e.g., interval & avl_set, ...
1932 % interval & interval already handled in check_subset_of_global_sets
1933 subset_of_explicit_set(AVL,Closure,Code,_WF) :- nonvar(AVL),AVL=avl_set(A),
1934 is_interval_closure_or_integerset(Closure,Low,Up),!,
1935 Code=custom_explicit_sets:check_avl_in_interval(A,Low,Up).
1936 subset_of_explicit_set(Closure,CS,Code,WF) :- nonvar(CS), is_custom_explicit_set(CS),
1937 is_interval_closure_or_integerset(Closure,Low,Up),!,
1938 Code=custom_explicit_sets:check_interval_in_custom_set(Low,Up,CS,WF).
1939 subset_of_explicit_set(AVL1,AVL2,Code,_WF) :- % print_term_summary(try_sub(AVL1,AVL2)), %
1940 nonvar(AVL1),AVL1=avl_set(A1), nonvar(AVL2),AVL2=avl_set(A2),!,
1941 %print_term_summary(subset_avl(AVL1,AVL2)),nl,
1942 Code = custom_explicit_sets:check_avl_subset(A1,A2).
1943 subset_of_explicit_set(C1,AVL2,Code,_WF) :- nonvar(C1), nonvar(AVL2), AVL2=avl_set(_),
1944 simple_infinite_set(C1),!, % infinite set cannot be subset of finite one
1945 Code = fail.
1946 subset_of_explicit_set(C1,C2,Code,WF) :- nonvar(C1),
1947 is_cartesian_product_closure(C1,S11,S12),!,
1948 %print(is_cartesian_product_closure(C1,S11,S12)),
1949 ((S11==[] ; S12==[]) -> Code=true /* we always have a subset */
1950 ; is_definitely_not_empty(S11),
1951 is_definitely_not_empty(S12), % only use optimisation if we know S11, S12 to be non-empty
1952 nonvar(C2), is_cartesian_product_closure(C2,S21,S22),
1953 %print(subset_of_cartesian_products(S11,S12,S21,S22)),nl,
1954 Code = (kernel_objects:check_subset_of_wf(S11,S21,WF),
1955 kernel_objects:check_subset_of_wf(S12,S22,WF) )
1956 ).
1957 subset_of_explicit_set(Set1,Set2,Code,WF) :-
1958 nonvar(Set2),is_cartesian_product_closure(Set2,S21,S22),!,
1959 % TO DO: maybe don't do this if Set1 is avl_set ??
1960 debug_println(9,'Applying C <: S21*S22 <=> C : S21 <-> S22'),
1961 Code = bsets_clp:relation_over_wf(Set1,S21,S22,WF).
1962 subset_of_explicit_set(C1,C2,Code,WF) :- nonvar(C1), nonvar(C2),
1963 is_powerset_closure(C1,Constructor1,Set1),
1964 is_powerset_closure(C2,Constructor2,Set2),
1965 %print(subset(Constructor1,Set1,Constructor2,Set2)),nl,
1966 subset_constructor(Constructor1,Constructor2,R), %print(comparison(R)),nl,
1967 !,
1968 Code = (R=pred_true, kernel_objects:check_subset_of_wf(Set1,Set2,WF)).
1969 subset_of_explicit_set(Set1,Set2,Code,WF) :-
1970 nonvar(Set1), Set1=closure(P1,T1,B1),
1971 get_closure(Set2,P2,T2,B2),
1972 is_symbolic_closure(P1,T1,B1), % we could also do: is_infinite_or_symbolic_closure(P1,T1,B1),
1973 % {x|P1} <: {x|P2} <=> {x|P1 & not(P2)}={}
1974 unify_closure_predicates(P1,T1,B1, P2,T2,B2 , NewP,NewT, NewB1,NewB2),
1975 create_negation(NewB2,NegNewB2),
1976 bsyntaxtree:conjunct_predicates([NewB1,NegNewB2],NewB),
1977 %print(subset_symbolic(P1,P2)),nl,translate:print_bexpr(NewB),nl,
1978 !,
1979 Code = custom_explicit_sets:is_empty_closure_wf(NewP,NewT,NewB,WF).
1980
1981 % get_closure or infinite global set:
1982 get_closure(V,_,_,_) :- var(V),!,fail.
1983 get_closure(closure(P,T,B),P,T,B).
1984 get_closure(global_set(G),P,T,B) :- is_infinite_global_set(G,Type),!,
1985 ID = '_zzzz_unary',
1986 TID = b(identifier(ID),Type,[]),
1987 TSet = b(value(global_set(G)),set(Type),[]),
1988 P = [ID], Type=T, B= b(member(TID,TSet),pred,[]).
1989
1990
1991 subset_constructor(X,X,R) :- !,R=pred_true.
1992 subset_constructor(fin1,_,R) :- !,R=pred_true.
1993 subset_constructor(fin,pow,R) :- !,R=pred_true.
1994 subset_constructor(X,Y,R) :- strict_subset_constructor(X,Y),!,R=pred_true.
1995 subset_constructor(X,Y,R) :- strict_subset_constructor(Y,X),!,R=pred_false.
1996 % pow1,fin1 ; pow,fin ; and pow1,fin only ok if type infinite
1997 strict_subset_constructor(pow1,pow).
1998 strict_subset_constructor(fin1,fin).
1999
2000 % more rules for <->, +->, ...
2001 % what if same closure: then we also know it is a subset
2002
2003 % to be completed:
2004 % code that instantiates R to subset or not_subset, may have to delay
2005 test_subset_of_explicit_set(AVL,Closure,R,_WF,Code) :- nonvar(AVL),AVL=avl_set(A),
2006 is_interval_closure_or_integerset(Closure,Low,Up),!,
2007 Code=custom_explicit_sets:test_avl_in_interval(A,Low,Up,R).
2008 test_subset_of_explicit_set(AVL1,AVL2,R,_WF,Code) :- %print_term_summary(try_sub(AVL1,AVL2)),
2009 nonvar(AVL1),AVL1=avl_set(A1), nonvar(AVL2),AVL2=avl_set(A2),
2010 Code = (custom_explicit_sets:check_avl_subset(A1,A2) -> R=pred_true ; R=pred_false).
2011 % TO DO: add is_cartesian_product_closure case
2012
2013 :- public test_avl_in_interval/4. % used in test_subset_of_explicit_set
2014 test_avl_in_interval(A,Low,Up,R) :-
2015 (check_avl_in_interval(A,Low,Up) -> R=pred_true ; R=pred_false).
2016
2017 is_definitely_not_empty(X) :- nonvar(X),
2018 (X=[_|_] -> true
2019 ; is_custom_explicit_set(X), is_non_empty_explicit_set(X)).
2020
2021 % check if defnitely not empty and provide a witness
2022 is_definitely_not_empty_with_witness(X,El) :- nonvar(X),
2023 get_witness_element(X,El).
2024 get_witness_element([H|_],H).
2025 get_witness_element(avl_set(node(H,_True,_,_,_)),H).
2026 % TO DO: add global_set(GS),...
2027
2028 check_avl_subset(A1,A2) :- avl_max(A1,Max1), avl_max(A2,Max2),
2029 Max1@>Max2,!,
2030 %nl,print(prune_check_avl_subset(Max1,Max2)),nl,nl,
2031 fail.
2032 check_avl_subset(A1,A2) :-
2033 avl_min(A1,Cur1), avl_min(A2,Cur2),
2034 check_avl_subset_loop(Cur1,A1,Cur2,A2).
2035 check_avl_subset_loop(Cur1,AVL1,Cur2,AVL2) :-
2036 (Cur1 @> Cur2 -> avl_next(Cur2,AVL2,NC2), check_avl_subset_loop(Cur1,AVL1,NC2,AVL2)
2037 ; Cur1=Cur2 -> (avl_next(Cur1,AVL1,NC1)
2038 -> avl_next(Cur2,AVL2,NC2),
2039 check_avl_subset_loop(NC1,AVL1,NC2,AVL2)
2040 ; true /* all objects of AVL1 inspected */)
2041 ).
2042
2043 % check A <: Low..Up
2044 check_avl_in_interval(A,Low,Up) :- % does not have to delay: if we have minus_inf & inf they will be known straightaway
2045 (Low==minus_inf -> true
2046 ; avl_min(A,Min), kernel_objects:less_than_equal(int(Low),Min)),
2047 (Up==inf -> true
2048 ; avl_max(A,Max), kernel_objects:less_than_equal(Max,int(Up))).
2049
2050 % some experiments:
2051 % 1..x <: {1,2,3,5} & x>1 & !y.(y>x & y<10 => 1..y /<: {1,2,3,5})
2052 % {ss | ss <: 0..0 & ss /= {} & ss=0..max(ss)}
2053 % {ss | ss <: 0..0 & ss /= {} & ss=min(ss)..max(ss)} // does not work yet
2054 % x..x+1 <: {0,2,3,5}
2055 % x..x+2 <: {0,2,3,5} // does not work yet
2056 % r = {x|x:1..400 & x mod 3/=0} & res={v|v:0..1300 & v..v+1 <: r}
2057 % check Low..Up <: Avl
2058 check_interval_in_custom_set(Low,Up,CS,WF) :-
2059 Low \== minus_inf,
2060 Up \== inf,
2061 b_interpreter_check:check_arithmetic_operator('<=',Low,Up,LeqRes),
2062 %print(check_interval_in_custom_set(LeqRes,Low,Up,CS)),nl,
2063 (var(LeqRes) -> get_binary_choice_wait_flag_exp_backoff(16,check_interval_in_custom_set,WF,WF2) ; true),
2064 check_interval_in_custom_set_aux(LeqRes,Low,Up,CS,WF2).
2065
2066 :- block check_interval_in_custom_set_aux(-,?,?,?,-).
2067 %check_interval_in_custom_set_aux(P,Low,Up,CS,WF2) :- print(check_interval_in_custom_set_aux(P,Low,Up,CS,WF2)),nl,fail.
2068 check_interval_in_custom_set_aux(pred_true,Low,Up,CS,_WF2) :- %print(not_empty),nl,
2069 element_of_custom_set_wf(int(Low),CS,WF),
2070 element_of_custom_set_wf(int(Up),CS,WF),
2071 interval_in_avl_block(Low,Up,CS,WF).
2072 check_interval_in_custom_set_aux(pred_false,_Low,_Up,_CS,_WF2). % Interval is empty; but infinitely many solutions for Low and Up exist in principle
2073
2074 :- block interval_in_avl_block(-,?,?,?), interval_in_avl_block(?,-,?,?).
2075 interval_in_avl_block(Low,Up,CS,WF) :- %print(interval_in_avl_block(Low,Up,CS)),nl,
2076 Low1 is Low+1, interval_in_avl_loop(Low1,Up,CS,WF).
2077 interval_in_avl_loop(Low,Up,_CS,_WF) :- Low>=Up,!. % Lower bound and upper bound already checked
2078 interval_in_avl_loop(Low,Up,CS,WF) :- %print(chck(Low,Up,CS)),nl,
2079 element_of_custom_set_wf(int(Low),CS,WF), L1 is Low+1,
2080 interval_in_avl_loop(L1,Up,CS,WF).
2081
2082
2083 :- public not_check_avl_subset/2. % used in not_subset_of_explicit_set_aux
2084 not_check_avl_subset(A1,A2) :- \+ check_avl_subset(A1,A2).
2085
2086 ?not_subset_of_explicit_set(S1,S2,Code,WF) :- nonvar(S1),
2087 ? not_subset_of_explicit_set_aux(S1,S2,Code,WF).
2088 not_subset_of_explicit_set_aux(avl_set(A),Closure,Code,_WF) :-
2089 is_interval_closure_or_integerset(Closure,Low,Up),!,
2090 Code=custom_explicit_sets:check_avl_not_in_interval(A,Low,Up).
2091 not_subset_of_explicit_set_aux(avl_set(A1),AVL2,Code,_WF) :-
2092 nonvar(AVL2),AVL2=avl_set(A2),
2093 %print(not_subset_avl(Cur1,Cur2)),nl,
2094 Code = custom_explicit_sets:not_check_avl_subset(A1,A2).
2095 not_subset_of_explicit_set_aux(CS,AVL,Code,_WF) :-
2096 simple_infinite_set(CS),
2097 % TO DO: provide code for interval/NAT/INT /<: AVL
2098 nonvar(AVL), AVL=avl_set(_),
2099 !,
2100 Code = true. % G cannot be subset of finite set
2101 not_subset_of_explicit_set_aux(C1,C2,Code,WF) :- is_cartesian_product_closure(C1,S11,S12),
2102 %print(is_cartesian_product_closure(C1,S11,S12)),
2103 ((S11==[] ; S12==[]) -> Code=fail /* we always have a subset */
2104 ; is_definitely_not_empty(S11),
2105 is_definitely_not_empty(S12), % only use optimisation if we know S11, S12 to be non-empty
2106 nonvar(C2), is_cartesian_product_closure(C2,S21,S22),
2107 % print(not_subset_of_cartesian_products(S11,S12,S21,S22)),nl, %
2108 Code = (kernel_objects:not_both_subset_of(S11,S12, S21,S22, WF))).
2109 not_subset_of_explicit_set_aux(C1,C2,Code,WF) :- nonvar(C2),
2110 is_powerset_closure(C1,Constructor1,Set1),
2111 is_powerset_closure(C2,Constructor2,Set2),
2112 %print(not_subset(Constructor1,Set1,Constructor2,Set2)),nl,
2113 subset_constructor(Constructor1,Constructor2,R), %print(comparison(R)),nl,
2114 Code = (R=pred_false -> true ; kernel_objects:not_subset_of_wf(Set1,Set2,WF)).
2115
2116 :- public check_avl_not_in_interval/3. % used in not_subset_of_explicit_set_aux
2117 :- block check_avl_not_in_interval(?,-,?). % TO DO: use non-blocking version, minus_inf, and inf set directly
2118 check_avl_not_in_interval(A,Low,Up) :- avl_min(A,int(Min)),
2119 % print(avl_not_in_interval(Min,Max,Low,Up)),nl,
2120 check_avl_not_in_interval4(Low,Up,A,Min).
2121
2122 check_avl_not_in_interval4(Low,_Up,_A,Min) :- Low \== minus_inf, Min < Low,!.
2123 check_avl_not_in_interval4(_Low,Up,A,_Min) :-
2124 Up \== inf, avl_max(A,Max),
2125 kernel_objects:less_than(int(Up),Max). % Up could still be a variable
2126
2127
2128 % checks for simple infinite sets, without Cartesian Product, ... decomposition
2129 simple_infinite_set(global_set(X)) :- !, is_infinite_global_set(X,_).
2130 simple_infinite_set(CS) :- is_interval_closure_or_integerset(CS,Low,Up), infinite_interval(Low,Up).
2131
2132
2133 % IMAGE [.]
2134 image_for_id_closure(closure(Par,Types,Body),Set,Res) :-
2135 is_full_id_closure(Par,Types,Body),!,
2136 % print(image_of_full_id_closure(Set,Res)),nl, %%
2137 Res=Set.
2138
2139 image_for_explicit_set(closure(Par,Types,Body),Set,Res,WF) :-
2140 ? image_for_closure(Par,Types,Body,Set,Res,WF).
2141 image_for_explicit_set(avl_set(A),Set,Res,WF) :- nonvar(Set),
2142 image_for_explicit_avl_set(A,Set,Res,WF).
2143
2144
2145 image_for_closure([X,Y],[_TX,TY],Pred,Set,Res,WF) :-
2146 singleton_set(Set,SX),
2147 nonvar(SX), % otherwise it may be better to use standard image propagation
2148 % e.g., testcase 1536 sqr = %x.(x>=0|x*x) & (sqr)[{xx,vv}] = {2500}
2149 % TO DO: improve equal_explicit_sets so that 1536 also works without nonvar(SX) test above; do we need this rule for singleton_sets anyway ?
2150 !,
2151 b_compiler:b_compile(Pred,[Y],[],[bind(X,SX)],NewPred,WF),
2152 % compilation avoids introduction of let_predicate
2153 % Res = closure([Y],[TY],NewPred).
2154 construct_closure_if_necessary([Y],[TY],NewPred,Res).
2155 % we could provide optimized code for is_lambda_value_domain_closure([X,Y],[_TX,TY],Pred, DomainValue,Expr)
2156 % if SX in Dom (membership_test_wf(SX,DomainValue,WF,MemRes)) then Res = [Expr/RY]; else Res=[] b_interpreter:b_test_boolean_expression(Pred,[bind(X,SX),bind(Y,RY)],[],WF)
2157 % Res = closure([Y],[TY],b(let_predicate([b(identifier(X),TX,[])],[b(value(SX),TX,[])],Pred),pred,[])).
2158 % ,print(image_for_closure),nl,translate:print_bvalue(Res),nl,print(done),nl.
2159 image_for_closure(Par,Types,Body,Set,Res,_WF) :-
2160 is_id_closure_over(Par,Types,Body,ID_Domain,Full),!,
2161 %print(image_of_id_closure_over(ID_Domain,Full,Set,Res)),nl, %%
2162 (Full=true -> Res=Set ; kernel_objects:intersection(ID_Domain,Set,Res)).
2163 % infinite function case dealt with in image1 in bsets_clp
2164 % TO DO: other closure(); Maybe special case if Set is an interval ?
2165 image_for_closure(Par,Types,Body,Set,Res,WF) :-
2166 ? is_closure1_value_closure(Par,Types,Body,VAL),
2167 %print(image_for_closure_closure1(VAL)),nl,
2168 % compute closure1(VAL)[Set]
2169 ? bsets_clp:image_for_closure1_wf(VAL,Set,Res,WF).
2170
2171 is_closure1_value_closure(Par,Types,Body,VAL) :-
2172 is_member_closure(Par,Types,Body,couple(A,A),MemSET), nonvar(MemSET),
2173 MemSET = closure(V), % this is the closure1 B operator !
2174 nonvar(V), V=b(value(VAL),_,_).
2175
2176 image_for_explicit_avl_set(A,Set,Res,_WF) :- % Set is nonvar
2177 is_interval_closure_or_integerset(Set,From1,To1),!,
2178 % Note: if From1, To1 not yet known we will block and not revert to other image calculation code
2179 % Important e.g. for performance of San Juan (AdaptedBModelPropCheck/acs_as_env_cfg_ipart.mch)
2180 %we used to check for: ground(From1),ground(To1),
2181 interval_image_for_explicit_avl_set(From1,To1,A,Set,Res).
2182 image_for_explicit_avl_set(A,Set,Res,WF) :-
2183 %%(bsets_clp:keep_symbolic(Set) -> print_term_summary(keep_symbolic(Set,A)),nl, fail ; true),
2184 \+ bsets_clp:keep_symbolic(Set), % in this case we fall back to treatment in bsets_clp (image1)
2185 expand_custom_set_to_list_gg(Set,ESet,GG,image_for_explicit_avl_set),
2186 empty_avl(Empty),
2187 % print_term_summary(image_explicit(GG,Set,ESet,A,Empty,Res)),nl,
2188 (GG=guaranteed_ground -> image_explicit_ground(ESet,A,Empty,Res,WF)
2189 ; image_explicit(ESet,A,Empty,Res,WF)).
2190 % print_term_summary(image_explicit_res(ESet,A,Empty,Res)).
2191
2192 :- block interval_image_for_explicit_avl_set(-,?,?,?,?),
2193 interval_image_for_explicit_avl_set(?,-,?,?,?).
2194 interval_image_for_explicit_avl_set(From1,To1,_A,_Set,Res) :-
2195 number(From1), number(To1), From1>To1,!,
2196 kernel_objects:empty_set(Res).
2197 interval_image_for_explicit_avl_set(From1,To1,A,_Set,Res) :-
2198 % print(image_avl_interval(From1,To1)),nl,
2199 ? findall(Image-true, avl_image_interval(From1,To1, A,Image),ImageList),
2200 %print(image_list(ImageList)),nl,
2201 ? normalised_list_to_avl(ImageList,ImageAvl),
2202 ? equal_object(ImageAvl,Res).
2203
2204
2205 singleton_set(X,_) :- var(X),!,fail.
2206 singleton_set([H|T],H) :- !, T==[].
2207 singleton_set(avl_set(node(Y,_,_,empty,empty)),Y). % same as is_one_element_custom_set
2208
2209 is_one_element_custom_set(avl_set(node(Y,_,_,empty,empty)),Y).
2210 is_one_element_avl(node(Y,_,_,empty,empty),Y).
2211
2212 construct_one_element_custom_set(El,avl_set(AVL)) :-
2213 empty_avl(E),avl_store(El,E,true,AVL).
2214
2215 construct_avl_set(Avl,Res) :- empty_avl(Avl) -> Res = [] ; Res = avl_set(Avl).
2216
2217 :- block image_explicit(-,?,?,?,?).
2218 ?image_explicit([],_,Acc,Res,WF) :- !,
2219 ? construct_avl_set(Acc,AVLS),
2220 ? kernel_objects:equal_object_wf(Res,AVLS,image_explicit,WF).
2221 image_explicit([D1|T],AVLRelation,In,Out,WF) :- !, %print_term_summary(image(D1,T,AVLRelation,In,Out)),nl,
2222 ground_value_check(D1,G1),
2223 ? ((var(T);T==[]) % TO DO: see below, make propagation also interesting in other circumstances
2224 -> must_be_in_domain_check(G1,D1,T,AVLRelation,In,Out,WF)
2225 ; true),
2226 image_explicit_aux(G1,D1,AVLRelation,T,In,Out,WF).
2227 image_explicit(Set,_,_,_,_) :- add_error_and_fail(image_explicit,'Unknown set: ',Set).
2228
2229 % a version of image_explicit where the list is guaranteed to be ground
2230 image_explicit_ground([],_,Acc,Res,WF) :- !,
2231 construct_avl_set(Acc,AVLS),
2232 kernel_objects:equal_object_wf(Res,AVLS,image_explicit,WF).
2233 image_explicit_ground([D1|T],AVLRelation,In,Out,WF) :- !, %print_term_summary(image(D1,T,AVLRelation,In,Out)),nl,
2234 image_explicit_aux_ground(D1,AVLRelation,T,In,Out,WF).
2235 image_explicit_ground(Set,_,_,_,_) :- add_error_and_fail(image_explicit_ground,'Unknown set: ',Set).
2236
2237 :- block must_be_in_domain_check(-,?,?,?,?,-,?),
2238 must_be_in_domain_check(-,?,-,?,?,?,?).
2239 % if result requires at least one more element, then D must be in domain of Relation
2240 % ensures that we get a domain for j in x = {1|->2,2|->4, 4|->8} & x[{j}]={8}
2241 % we could even propagate using inverse of AVLRelation ?!
2242 must_be_in_domain_check(GroundD,D,T,AVLRelation,In,Out,WF) :-
2243 T==[], % apart from D, there are no more elements to be added
2244 var(GroundD), % otherwise we already have a value for D
2245 delta_witness(In,Out,Witness), % obtain at least one value that D must map to
2246 !,
2247 % print(in_domain(D,AVLRelation)),nl,
2248 quick_propagation_element_information(avl_set(AVLRelation),(D,Witness),WF,_). % Witness avoids pending co-routines
2249 % TO DO: we could check that *all* elements of Out have this value
2250 % TO DO: below we could check that In is a subset of Out; e.g., for x = %i.(i:1..10|i+i) & x[{5,j,k}]={16,11}; we could also check that Out is subset of range of relation
2251 must_be_in_domain_check(_,_D,_T,_,_In,_Out,_). % :- print(must_be(D,T,In,Out)),nl.
2252
2253 % provide, if possible, a witness element in Out not in In
2254 delta_witness(In,Out,_Witness) :- (var(In) ; var(Out)),!,fail.
2255 %delta_witness(empty,Out,Witness) :- is_definitely_not_empty_with_witness(Out,Witness).
2256 delta_witness(In,Out,Witness) :-
2257 is_custom_explicit_set(Out,delta_witness),
2258 difference_of_explicit_set(Out,avl_set(In),Diff), % could be expensive to compute !? delay ? print(delta(Diff)),nl,
2259 is_definitely_not_empty_with_witness(Diff,Witness). %, print(witness(Witness)),nl.
2260
2261
2262 :- block image_explicit_aux(-,?,?, ?,?,?,?). % we know that D1 is ground
2263 image_explicit_aux(_,D1,AVLRelation,T,In,Out,WF) :-
2264 ? all_images(D1,AVLRelation,NewImages), % compute AVLRelation[{D1}]
2265 ? add_to_avl(NewImages,In,In2),
2266 ? image_explicit(T,AVLRelation,In2,Out,WF).
2267 image_explicit_aux_ground(D1,AVLRelation,T,In,Out,WF) :-
2268 all_images(D1,AVLRelation,NewImages), % compute AVLRelation[{D1}]
2269 add_to_avl(NewImages,In,In2),
2270 image_explicit_ground(T,AVLRelation,In2,Out,WF).
2271
2272 all_images(From,AVLRelation,Images) :-
2273 findall(AY,avl_member_pair_arg1_ground(From,AY,AVLRelation),Images). % we know From ground and AY free variable
2274 % findall(AY,safe_avl_member_pair(From,AY,AVLRelation),Images). %
2275
2276 % compute relational composition ( ; ) if second arg is an AVL set
2277 % TO DO: add support for infinite closures; avoid expanding them [currently handled by symbolic composition in bsets_clp]
2278 rel_composition_for_explicit_set(Rel1,Rel2,Comp) :- nonvar(Rel2),
2279 Rel2=avl_set(A2), % TO DO: see if we can maybe convert Rel2 to AVL ?
2280 % \+ bsets_clp:keep_symbolic(Rel1), check already done in bsets
2281 expand_custom_set_to_list_gg(Rel1,Relation1,GG,rel_composition_for_explicit_set),
2282 % print_term_summary(computing_rel_comp(GG,Rel1,Rel2,Comp)),nl,
2283 empty_avl(In),
2284 (GG=guaranteed_ground -> rel_avl_compose2_ground(Relation1,A2,In,Comp)
2285 ; rel_avl_compose2(Relation1,A2,In,Comp)).
2286
2287 :- block rel_avl_compose2(-,?,?,?).
2288 rel_avl_compose2([],_,In,Res) :- construct_avl_set(In,A),
2289 equal_object(Res,A,rel_avl_compose2). % as we delay; we need to use equal_object at the end
2290 rel_avl_compose2([(X,Y)|T],A2,In,Out) :-
2291 when((ground(X),ground(Y)),
2292 (all_image_pairs(X,Y,A2,ImagePairs), % print(adding_pairs(X,Y,ImagePairs)),nl,
2293 add_to_avl(ImagePairs,In,In2),
2294 rel_avl_compose2(T,A2,In2,Out))).
2295
2296 % a version where argument is guaranteed to be ground:
2297 rel_avl_compose2_ground([],_,In,Res) :- construct_avl_set(In,A),
2298 equal_object(Res,A,rel_avl_compose2). % as we delay; we need to use equal_object at the end
2299 rel_avl_compose2_ground([(X,Y)|T],A2,In,Out) :-
2300 all_image_pairs_ground(X,Y,A2,ImagePairs), % print(adding_pairs(X,Y,ImagePairs)),nl,
2301 add_to_avl(ImagePairs,In,In2),
2302 rel_avl_compose2_ground(T,A2,In2,Out).
2303
2304 all_image_pairs(From,To,AVLRelation,ImagePairs) :-
2305 findall((From,AY),safe_avl_member_pair(To,AY,AVLRelation),ImagePairs).
2306 all_image_pairs_ground(From,To,AVLRelation,ImagePairs) :-
2307 findall((From,AY),avl_member_pair_arg1_ground(To,AY,AVLRelation),ImagePairs).
2308 % To: already in AVL format; AY is variable -> we could use avl_fetch_pair directly : findall((From,AY),avl_fetch_pair(To,AVLRelation,AY),ImagePairs).
2309
2310 /* succeeds if it can compute domain by some clever way */
2311 domain_of_explicit_set(global_set(GS),_R) :- !,
2312 add_error_and_fail(domain_of_explicit_set,'Cannot compute domain of global set: ',GS).
2313 domain_of_explicit_set(freetype(GS),_R) :- !,
2314 add_error_and_fail(domain_of_explicit_set,'Cannot compute domain of freetype: ',GS).
2315 domain_of_explicit_set(avl_set(A),Res) :- !,
2316 avl_domain(A,EC), % -> expand_custom_set(avl_set(A),EC),
2317 % print_term_summary(computing_domain_of_avl(EC,Res)),nl,
2318 domain(EC,R),ord_list_to_avlset(R,Res,domain).
2319 domain_of_explicit_set(C,R) :- dom_for_specific_closure(C,Dom,_),!,
2320 %print(dom_for_specific_closure(C,Dom)),nl,
2321 Dom=R.
2322 domain_of_explicit_set(C,R) :- % print(try_symbolic(C)),nl,
2323 ? dom_symbolic(C,CC),!, % print_term_summary(dom_symbolic(C,CC)),nl,
2324 R=CC.
2325 domain_of_explicit_set(closure(P,T,B),Res) :-
2326 % print_term_summary(domain_of_closure(P,T,B,Res)),nl,
2327 expand_custom_set(closure(P,T,B),EC,domain_of_explicit_set),
2328 domain(EC,R),
2329 normalised_list_to_avl_when_ground(R,Res).
2330
2331 :- use_module(bsyntaxtree,[create_exists/3, create_typed_id/3]).
2332 dom_symbolic(closure(Paras,Types,Pred), Res) :-
2333 expand_pair_closure(Paras,Types,Pred,[X,Y],[TX,TY],NewPred),!,
2334 % simply call code for range ; inverting arguments
2335 ran_symbolic_closure(Y,[X],TY,[TX],NewPred,Res).
2336 dom_symbolic(closure(Paras,Types,Pred), Res) :-
2337 ? append(Xs,[Y],Paras), Xs \= [], % single argument which is a pair
2338 ? append(TXs,[TY],Types),
2339 % simply call code for range ; inverting arguments
2340 ran_symbolic_closure(Y,Xs,TY,TXs,Pred,Res).
2341 % TO DO: allow computation if Paras is a single argument ?
2342
2343 % just computes domain: it can also be successful for lambda closures
2344 dom_for_specific_closure(closure(P,T,Pred),Domain,Functionality) :-
2345 (is_lambda_value_domain_closure(P,T,Pred, DomainValue,Expr),
2346 (preference(find_abort_values,full) -> bsyntaxtree:always_well_defined_or_disprover_mode(Expr)
2347 ; true)
2348 -> % Warning: this will lead to dom(%x.(x:1..3|1/0)) = 1..3 to be true; discarding WD condition
2349 % this is not as bad as {1|->2}(0) = 3 to be silently failing though; hence only done if TRY_FIND_ABORT = full
2350 Domain=DomainValue,
2351 Functionality=function(total)
2352 ; dom_range_for_specific_closure2(P,T,Pred, Domain,_Range,Functionality)).
2353 %dom_for_specific_closure(closure_x(P,T,Pred,_Exp),Card) :- dom_for_specific_closure2(P,T,Pred,Card).
2354
2355 dom_for_lambda_closure(closure(P,T,Pred),Domain) :-
2356 is_lambda_value_domain_closure(P,T,Pred, DomainValue,_Expr),
2357 Domain=DomainValue.
2358
2359 % TO DO: add total functions
2360 %dom_for_specific_closure2([F],[T],
2361 % b(member(b(identifier(F),T,_), b(total_function(value(A),B),set(couple(DOM,RAN)),_)), pred,_) ,
2362 % A).
2363
2364 :- block domain(-,?).
2365 % the list will be sorted according to the term ordering for (_,_); hence it will
2366 % already be sorted for the projection onto the first element
2367 % maybe the speed difference is not worth it ??
2368 domain([],[]).
2369 domain([(A,_B)|T],[A-true|DT]) :- domain(T,A,DT).
2370 :- block domain(-,?,?).
2371 domain([],_,[]).
2372 domain([(A,_B)|T],Prev,Res) :-
2373 (Prev==A
2374 -> domain(T,Prev,Res)
2375 ; Res = [A-true|DT],
2376 (A @< Prev -> add_error_fail(custom_explicit_sets,'Domain list not_sorted: ',(A,Prev)) ; true),
2377 domain(T,A,DT) ).
2378
2379 /* succeeds if it can compute domain by some clever way */
2380 range_of_explicit_set(global_set(GS),_R) :- !,
2381 add_error_and_fail(range_of_explicit_set,'Cannot compute domain of global set: ',GS).
2382 range_of_explicit_set(freetype(GS),_R) :- !,
2383 add_error_and_fail(range_of_explicit_set,'Cannot compute domain of freetype: ',GS).
2384 range_of_explicit_set(avl_set(A),Res) :- !,
2385 avl_domain(A,EC), % -> expand_custom_set(avl_set(A),EC),
2386 range(EC,R), normalised_list_to_avl(R,Res).
2387 range_of_explicit_set(C,R) :- % print(try_ran(C)),nl,
2388 ran_for_specific_closure(C,Ran),!,
2389 %print_term_summary(ran_for_specific_closure(C,Ran)),nl,
2390 Ran=R.
2391 range_of_explicit_set(C,R) :- % print(try_symbolic(C)),nl,
2392 ran_symbolic(C,CC),!, %print(ran_symbolic(C,CC)),nl,
2393 R=CC.
2394 range_of_explicit_set(closure(P,T,B),Res) :-
2395 expand_custom_set(closure(P,T,B),EC,range_of_explicit_set),
2396 % TO DO: it would be more useful here to directly just expand the projection onto the last component of P
2397 range(EC,R), normalised_list_to_avl_when_ground(R,Res).
2398
2399 % TO DO: in future it is maybe better to add an in_range_wf kernel predicate
2400 ran_symbolic(closure(Paras,Types,Pred), Res) :-
2401 expand_pair_closure(Paras,Types,Pred,[Y,X],[TY,TX],NewPred),!,
2402 % following test (1541) works with this: 2 : ran({y|#(x).(y = x |-> x + 2 & x : NATURAL)})
2403 %print('range for pair transformation: '), print(cl(YX,Y,X)),nl,translate:print_bexpr(Pred1),nl,
2404 ran_symbolic_closure(Y,[X],TY,[TX],NewPred,Res). %, print('res: '),translate:print_bvalue(Res),nl.
2405 ran_symbolic(closure([Y,X],[TY,TX],Pred), Res) :-
2406 ran_symbolic_closure(Y,[X],TY,[TX],Pred,Res).
2407 % TO DO: treat closures with more arguments: we need to quantify Y1,...Yn [Y1,...,Yn,X]
2408
2409 % Replace single Identifier YX of type pair by pair (Y,X) where Y,X are (fresh) variables not occuring in Pred
2410 % example: {y| #(x).(y = x |-> x + 2 & x : NATURAL)} --> {y__1,y__2|#(x).(y__1 |-> y__2 = x |-> x + 2 & x : NATURAL)}
2411 expand_pair_closure([YX],[TYX],Pred,[Y,X],[TY,TX],NewPred) :- TYX = couple(TY,TX),
2412 % Replace single ID YX of type pair by pair (Y,X) where Y,X are (fresh) variables not occuring in Pred
2413 % example: {y| #(x).(y = x |-> x + 2 & x : NATURAL)} --> {y__1,y__2|#(x).(y__1 |-> y__2 = x |-> x + 2 & x : NATURAL)}
2414 % following test (1541) works with this: 2 : ran({y|#(x).(y = x |-> x + 2 & x : NATURAL)})
2415 gensym:gensym(YX,Y),gensym:gensym(YX,X),
2416 create_typed_id(Y,TY,YTID), create_typed_id(X,TX,XTID),
2417 Pair = b(couple(YTID,XTID),TYX,[]),
2418 bsyntaxtree:replace_id_by_expr(Pred,YX,Pair,NewPred).
2419
2420 :- use_module(bsyntaxtree,[add_texpr_info_if_new/3]).
2421 ran_symbolic_closure(Y,Xs,TY,TXs,Pred,Res) :-
2422 rename_ran_ids(Xs,Pred,[],XIDs,Pred2),
2423 create_typed_id(Y,TY,YTID),
2424 create_exists([YTID],Pred2,Exists), % use create_and_simplify_exists(Paras,Pred,ResultingPred) ??
2425 %print(ran(Y,XID,TY,TX)),nl,translate:print_bexpr(Exists),nl,
2426 % add_texpr_info_if_new(Exists,allow_to_lift_exists,Exists2), % leads to pending co-routines in self_checks for bsets for apply_to; TO DO: investigate
2427 Res = closure(XIDs,TXs,Exists).
2428
2429
2430
2431 :- use_module(library(lists),[select/3]).
2432
2433 % rename lambda_results :
2434 rename_ran_ids([],Pred,_,[],Pred).
2435 rename_ran_ids([X|TX],Pred,Acc,[XID|TTX],Pred2) :-
2436 % in case X is _lambda_result_ we need to rename it as it then would not get enumerated !
2437 (X == '_lambda_result_' -> get_fresh_id('_was_lambda_result_',TX,Acc,XID), % TO DO: also remove lambda_result info field!
2438 rename_bt(Pred,[rename(X,XID)],Pred2),
2439 TTX=TX
2440 % maybe we should also remove the lambda_result info information inside Pred for the ids and equality !?
2441 % TO DO: also store information about this in info field ?
2442 ; XID = X, rename_ran_ids(TX,Pred,[X|Acc],TTX,Pred2)
2443 ).
2444
2445 :- use_module(b_ast_cleanup,[get_unique_id/2]).
2446 get_fresh_id(ID,List1,List2,Res) :- nonmember(ID,List1), nonmember(ID,List2),!, Res=ID.
2447 get_fresh_id(ID,_,_,FRESHID) :- nl,print('*** VARIABLE_CLASH PREVENTED: '), print(ID),nl,
2448 get_unique_id(ID,FRESHID).
2449
2450 :- block range(-,?).
2451 range([],[]).
2452 range([(_A,B)|T],[B-true|DT]) :- range(T,DT).
2453
2454 ran_for_specific_closure(closure(P,T,Pred),Range) :- dom_range_for_specific_closure2(P,T,Pred, _Domain,Range,_Functionality).
2455 %ran_for_specific_closure(closure_x(P,T,Pred,_Exp),Card) :- ran_for_specific_closure2(P,T,Pred,Card).
2456
2457 :- use_module(bsyntaxtree,[conjunct_predicates/2, disjunct_predicates/2, create_typed_id/3, get_texpr_type/2]).
2458 override_custom_explicit_set_wf(R,S,Res,WF) :- /* R <+ S */
2459 nonvar(R),override_custom_explicit_set_aux(R,S,Res,WF).
2460 override_custom_explicit_set_aux(CL,Rel2,Res,_WF) :-
2461 CL=closure(P0,T,B0), %print(override_custom_explicit_set_aux(CL,Rel2,Res)),nl,
2462 % TO DO: maybe call keep_symbolic in bsets_clp ??
2463 ? ( preferences:get_preference(convert_comprehension_sets_into_closures,true),
2464 (var(Rel2) -> true ; Rel2 \= avl_set(_)) % if Rel2 is avl_set then maybe better to compute explicitly; unless infinite
2465 ? ; quick_size_check_larger_than(Rel2,Size2,133) ->
2466 % if we have a large AVL set anyway; then allow expansion up to a larger limit; cf machine 670_002.mch
2467 % a lot of machines use A*B*C <+ {....} to more compactly define large explicit sets
2468 (Size2=inf -> Limit = 200000
2469 ; Limit is min(200000,Size2*150)), dont_expand_this_closure(P0,T,B0,Limit)
2470 ? ; dont_expand_this_closure(P0,T,B0) % use default limit
2471 ),
2472 !,
2473 rename_ran_ids(P0,B0,[],P,B), % any '_lambda_result_' id is no longer guaranteed to be assigned a value in all cases
2474 % print_term_summary(override_infinite_closure(P,T,B,Rel2,Res) ),nl,
2475 NewClosure=closure(P,T,NewBody),
2476 % B <+ Rel2 ---> NewBody = P:Rel2 or (prj1(P) /: dom(Rel2) & B)
2477 generate_typed_id_pairs(P,T,NestedPairs),
2478 get_texpr_type(NestedPairs,PairsType),
2479 RelPairsType = set(PairsType),
2480 ValS = b(value(Rel2),RelPairsType,[]),
2481 MemS = b(member(NestedPairs,ValS),pred,[]), % P:Rel2
2482 %print(mems(MemS)),nl,
2483 get_prj1(NestedPairs,DomExpr),
2484 %% (NestedPairs=b(couple(DomExpr,_),_,_) -> true ; print('SYMBOLIC <+ : '), translate:print_bvalue(CL),nl, print_term_summary(override_custom_explicit_set_aux(CL,Rel2,Res)),nl),
2485 get_texpr_type(DomExpr,DomType),
2486 Domain = b(domain(ValS),DomType,[]), % TO DO: perform some optimisations like dom(%x.(P|E)) --> {x|P}
2487 %bsets_clp:domain_wf(Rel2,DomainOfRel2,WF), Domain = b(value(DomainOfRel2),DomType,[]), % this DOES NOT work for 1619, 1706 where override is used for infinite functions
2488 NotMemDomS = b(not_member(DomExpr,Domain),pred,[]), % prj1(P) /: dom(Rel2)
2489 conjunct_predicates([NotMemDomS,B],RHS),
2490 %print('RHS: '),translate:print_bexpr(RHS),nl,
2491 disjunct_predicates([MemS,RHS],NewBody),
2492 % NewBody = b(let_predicate([b(identifier(X),RelPairsType,[])],[ValS],Disjunction),pred,[]))
2493 % print('Body: '),translate:print_bexpr(NewBody),nl,
2494 mark_closure_as_symbolic(NewClosure,Res).
2495 % TO DO: add a case where for second set we have: dont_expand_this_closure
2496 override_custom_explicit_set_aux(R,S,Res,_WF) :-
2497 is_custom_explicit_set(R,override_custom_explicit_set),
2498 nonvar(S), is_custom_explicit_set(S,override_custom_explicit_set),
2499 %% hit_profiler:add_profile_hit(override(R,S),3), %%
2500 override_custom_explicit_set2(R,S,Res).
2501
2502 override_custom_explicit_set2(R,S,Res) :- is_one_element_custom_set(S,(X,Y)),
2503 %print(override_pair(X,Y)),nl,
2504 override_pair_explicit_set(R,X,Y,NewR),!,
2505 Res=NewR.
2506 % TO DO: if R is very large and S relatively small : iterate by calling override_pair_explicit_set
2507 override_custom_explicit_set2(R,S,Res) :-
2508 expand_custom_set(R,ER,override_custom_explicit_set_aux1),
2509 expand_custom_set(S,ES,override_custom_explicit_set_aux2),
2510 override_list(ER,ES,LRes,Done),
2511 finish_restriction(Done,LRes,Res).
2512
2513 quick_size_check_larger_than(Set,Size,Limit) :-
2514 quick_custom_explicit_set_approximate_size(Set,Size),
2515 (Size = inf -> true ; Size>Limit).
2516 get_prj1(b(couple(DomExpr,_),_,_),Prj1) :- !, Prj1 = DomExpr.
2517 get_prj1(BE,b(first_of_pair(BE),DT,[])) :- % some closures have a single identifier; we need to apply prj1
2518 BE = b(_E,couple(DT,_RT),_I).
2519
2520 generate_typed_id_pairs([ID|IT],[Type|TT],Res) :- create_typed_id(ID,Type,TypedID),
2521 conv2(IT,TT,TypedID,Res).
2522 conv2([],[],X,X).
2523 conv2([ID|IT],[Type|TT],Acc,Res) :- create_typed_id(ID,Type,TypedID),
2524 get_texpr_type(Acc,AccType),
2525 Couple = b(couple(Acc,TypedID),couple(AccType,Type),[]),
2526 conv2(IT,TT,Couple,Res).
2527
2528 :- block override_list(-,?,?,?), override_list(?,-,?,?).
2529 override_list([],S,Res,Done) :- !, copy_to_true_list(S,Res,Done).
2530 override_list(R,[],Res,Done) :- !, copy_to_true_list(R,Res,Done).
2531 override_list([(From1,To1)|T1],[(From2,To2)|T2],Res,Done) :-
2532 (From1 @< From2
2533 -> Res = [(From1,To1)-true|TR], override_list(T1,[(From2,To2)|T2],TR,Done)
2534 ; From2 @< From1
2535 -> Res = [(From2,To2)-true|TR], override_list([(From1,To1)|T1],T2,TR,Done)
2536 ; override_list(T1,[(From2,To2)|T2],Res,Done)).
2537
2538 :- block copy_to_true_list(-,?,?).
2539 % add -true to get lists that can be converted to avl
2540 copy_to_true_list([],[],true).
2541 copy_to_true_list([H|T],[H-true|CT],Done) :- copy_to_true_list(T,CT,Done).
2542
2543 avl_min_pair(AVLFun,FFrom,FTo) :-
2544 (avl_min(AVLFun,(FFrom,FTo)) -> true
2545 ; add_error_fail(avl_min_pair,'Could not extract minimum pair of AVL set',AVLFun)).
2546 avl_max_pair(AVLFun,FFrom,FTo) :-
2547 (avl_max(AVLFun,(FFrom,FTo)) -> true
2548 ; add_error_fail(avl_max_pair,'Could not extract maximum pair of AVL set',AVLFun)).
2549
2550 % check whether we have a partial function
2551 is_avl_partial_function(empty) :- !.
2552 is_avl_partial_function(node((KeyFrom,_KeyTo),_True,_,L,R)) :- !,
2553 is_avl_partial_function2(L,'$$MIN$$',KeyFrom),
2554 is_avl_partial_function2(R,KeyFrom,'$$MAX$$').
2555 is_avl_partial_function(X) :- add_error_and_fail(is_avl_partial_function,'Not avl_set or relation: ',X).
2556
2557 % we traverse the tree from top to bottom, keeping track of possible upper- and lower-bounds
2558 % if any value matches the upper or lower bound, the we do not have a partial function
2559 is_avl_partial_function2(empty,_,_).
2560 is_avl_partial_function2(node((KeyFrom,_KeyTo),_True,_,L,R),ParentFrom,ParentTo) :-
2561 KeyFrom \= ParentFrom, KeyFrom \= ParentTo,
2562 is_avl_partial_function2(L,ParentFrom,KeyFrom),
2563 is_avl_partial_function2(R,KeyFrom,ParentTo).
2564
2565
2566
2567 % check whether we have a function which is total over a given domain; both as AVL sets
2568 is_avl_total_function_over_domain(empty,empty) :- !.
2569 is_avl_total_function_over_domain(AVLFun,AVLDom) :-
2570 avl_domain(AVLFun,FunList),
2571 avl_domain(AVLDom,DomList),
2572 is_avl_total_fun2(FunList,DomList).
2573
2574 is_avl_total_fun2([],[]).
2575 is_avl_total_fun2([(From,_To)|FT],[From|DomT]) :- is_avl_total_fun2(FT,DomT).
2576
2577
2578 %not_is_avl_partial_function(AVLF) :- \+ is_avl_partial_function(AVLF).
2579
2580 :- use_module(kernel_equality,[membership_test/3,membership_test_wf/4]).
2581 % check whether an AVL Relation is not over a specific domain & range
2582 is_not_avl_relation_over_domain_range(AVLRel,Domain,Range,WF) :- AVLRel \= empty,
2583 avl_min_pair(AVLRel,RFrom,RTo),
2584 kernel_equality:membership_test_wf(Domain,RFrom,MemRes,WF),
2585 is_not_avl_rel_dom1(MemRes,RFrom,RTo,AVLRel,Domain,Range,WF).
2586
2587 :- block is_not_avl_rel_dom1(-, ?,?,?,?,?,?).
2588 is_not_avl_rel_dom1(pred_false,_,_,_,_,_,_WF).
2589 is_not_avl_rel_dom1(pred_true,RFrom,RTo,AVLRel,Domain,Range,WF) :-
2590 kernel_equality:membership_test_wf(Range,RTo,MemRes,WF),
2591 is_not_avl_rel_dom2(MemRes,RFrom,RTo,AVLRel,Domain,Range,WF).
2592
2593 :- block is_not_avl_rel_dom2(-, ?,?,?,?,?,?).
2594 is_not_avl_rel_dom2(pred_false,_,_,_,_,_,_WF).
2595 is_not_avl_rel_dom2(pred_true,RFrom,RTo,AVLRel,Domain,Range,WF) :-
2596 avl_next((RFrom,RTo),AVLRel,(RFrom2,RTo2)),
2597 kernel_equality:membership_test_wf(Domain,RFrom2,MemRes,WF),
2598 is_not_avl_rel_dom1(MemRes,RFrom2,RTo2,AVLRel,Domain,Range,WF).
2599
2600 % check whether an AVL Relation is not over a specific range
2601 is_not_avl_relation_over_range(AVLRel,Range,WF) :- AVLRel \= empty,
2602 avl_min_pair(AVLRel,RFrom,RTo),
2603 kernel_equality:membership_test_wf(Range,RTo,MemRes,WF),
2604 is_not_avl_rel_ran2(MemRes,RFrom,RTo,AVLRel,Range,WF).
2605
2606 :- block is_not_avl_rel_ran2(-, ?,?,?,?,?).
2607 is_not_avl_rel_ran2(pred_false,_,_,_,_,_WF).
2608 is_not_avl_rel_ran2(pred_true,RFrom,RTo,AVLRel,Range,WF) :-
2609 avl_next((RFrom,RTo),AVLRel,(RFrom2,RTo2)),
2610 kernel_equality:membership_test_wf(Range,RTo2,MemRes,WF),
2611 is_not_avl_rel_ran2(MemRes,RFrom2,RTo2,AVLRel,Range,WF).
2612
2613 % check whether we have a relation
2614 is_avl_relation(node((_KeyFrom,_KeyTo),_True,_,_,_)).
2615
2616 % check whether a Relation has all its range elments in a certain Range (not necessarily AVL)
2617 % TO DO: fif Domain is an interval: we could take avl_min and avl_max and rely on lexicographic ordering
2618 is_avl_relation_over_domain(AVL,IntervalClosure,_WF) :-
2619 is_interval_closure_or_integerset(IntervalClosure,Low,Up),!,
2620 ((avl_min(AVL,(int(ALow),_)), avl_max(AVL,(int(AUp),_)))
2621 -> %print(check_avl_over_domain(ALow,AUp,Low,Up)),nl,
2622 cs_greater_than_equal(ALow,Low), cs_greater_than_equal(Up,AUp) %,print(ok),nl
2623 ; (AVL=empty -> true ; add_error_and_fail(is_avl_relation_over_domain,'Not a relation with integer domain: ',AVL))).
2624 is_avl_relation_over_domain(_,Domain,_) :-
2625 quick_is_definitely_maximal_set(Domain),!.
2626 %is_definitely_maximal_set(Domain),!.
2627 is_avl_relation_over_domain(AVL,Domain,WF) :- is_avl_relation_over_domain2(AVL,Domain,WF).
2628 is_avl_relation_over_domain2(empty,_,_).
2629 is_avl_relation_over_domain2(node((KeyFrom,_KeyTo),_,_,L,R), Domain,WF) :-
2630 is_avl_relation_over_domain2(L, Domain,WF),
2631 is_avl_relation_over_domain2(R, Domain,WF),
2632 kernel_objects:check_element_of_wf(KeyFrom,Domain,WF).
2633
2634 % : faster to check than is_definitely_maximal_set
2635 quick_is_definitely_maximal_set(X) :- nonvar(X),
2636 quick_is_definitely_maximal_set_aux(X).
2637 quick_is_definitely_maximal_set_aux(global_set(GS)) :-
2638 nonvar(GS),is_maximal_global_set(GS).
2639 quick_is_definitely_maximal_set_aux(avl_set(AVL)) :-
2640 quick_definitely_maximal_set_avl(AVL).
2641
2642 % check whether a Relation has all its range elments in a certain Range (not necessarily AVL)
2643
2644
2645
2646 is_avl_relation_over_range(empty,_,_) :- !.
2647 is_avl_relation_over_range(_,Range,_) :- % print(chk(Range)),nl,trace,
2648 %quick_is_definitely_maximal_set(Range),
2649 ? is_definitely_maximal_set(Range), % print(maximal),nl,
2650 !.
2651 is_avl_relation_over_range(AVL,Range,WF) :- is_avl_relation_over_range2(AVL,Range,WF).
2652
2653 is_avl_relation_over_range2(empty,_,_).
2654 is_avl_relation_over_range2(node((_KeyFrom,KeyTo),_,_,L,R), Range,WF) :-
2655 is_avl_relation_over_range(L, Range,WF),
2656 %print_term_summary(check_el(KeyTo,Range)),
2657 kernel_objects:check_element_of_wf(KeyTo,Range,WF),
2658 is_avl_relation_over_range2(R, Range,WF).
2659
2660
2661 is_avl_sequence(empty) :- !.
2662 is_avl_sequence(node((int(KeyFrom),_KeyTo),_True,_,L,R)) :- !,
2663 is_avl_sequence2(L,0,KeyFrom),
2664 is_avl_sequence2(R,KeyFrom,'$$MAX$$').
2665 is_avl_sequence(X) :- add_error_and_fail(is_avl_sequence,'Not avl_set or sequence: ',X).
2666
2667 % we traverse the tree from top to bottom, keeping track of possible upper- and lower-bounds
2668 % if any value matches the upper or lower bound, the we do not have a partial function
2669 is_avl_sequence2(empty,X,Y) :- %print(empty(X,Y)),nl,
2670 (Y=='$$MAX$$' -> true ; Y is X+1). % otherwise there is a gap in the sequence
2671 is_avl_sequence2(node((int(KeyFrom),_KeyTo),_,_,L,R),ParentFrom,ParentTo) :-
2672 %print(node(KeyFrom, ParentFrom,ParentTo)),nl,
2673 KeyFrom > ParentFrom, KeyFrom \= ParentTo,
2674 is_avl_sequence2(L,ParentFrom,KeyFrom),
2675 is_avl_sequence2(R,KeyFrom,ParentTo).
2676
2677 % for performance: it is not worthwhile to make a version that checks that
2678 % we have a sequence over a range using a single traversal
2679
2680
2681 % ---------------------------
2682 prefix_of_custom_explicit_set(avl_set(A),MinIndex,Result,WF) :-
2683 size_of_avl_sequence(A,Size,WF),
2684 (MinIndex > Size
2685 -> add_wd_error('index larger than size of sequence in prefix_sequence (/|\\)! ', '>'(MinIndex,Size),WF)
2686 % ; MinIndex = 0 -> Result = [] % case already treated in bsets_clp
2687 ; MinIndex = Size -> Result=avl_set(A)
2688 ; prefix_of_custom_explicit_set2(A,MinIndex,OrdList,[]),
2689 %print(suffix(A,MinIndex,OrdList)),nl,
2690 ord_list_to_avlset(OrdList,Result,prefix_of_custom_explicit_set)
2691 ).
2692 prefix_of_custom_explicit_set2(empty,_MaxIndex) --> {true}.
2693 prefix_of_custom_explicit_set2(node((int(KeyFrom),KeyTo),_True,_,L,R),MaxIndex) -->
2694 ({KeyFrom = MaxIndex}
2695 -> prefix_of_custom_explicit_set2(L,MaxIndex), [((int(KeyFrom),KeyTo)-true)]
2696 ; {KeyFrom > MaxIndex} -> prefix_of_custom_explicit_set2(L,MaxIndex)
2697 ; prefix_of_custom_explicit_set2(L,MaxIndex), [((int(KeyFrom),KeyTo)-true)],
2698 prefix_of_custom_explicit_set2(R,MaxIndex)
2699 ).
2700
2701 % size is only well-defined for sequences:
2702 size_of_custom_explicit_set(avl_set(AVL),int(Size),WF) :- size_of_avl_sequence(AVL,Size,WF).
2703 size_of_custom_explicit_set(closure(P,T,B),Res,WF) :-
2704 is_lambda_value_domain_closure(P,T,B, DomainValue,_Expr),
2705 kernel_objects:finite_cardinality_as_int(DomainValue,Res,WF).
2706 size_of_avl_sequence(AVL,Size,WF) :-
2707 preference(find_abort_values,true),
2708 \+ is_avl_sequence(AVL),!,
2709 avl_max_pair(AVL,int(Sz),_),
2710 add_wd_error('Applying size to a value which is not a sequence',b(value(avl_set(AVL)),seq(any),[]),WF),
2711 Size=Sz. % other calls to size_of_avl_sequence currently expect a value
2712 size_of_avl_sequence(AVL,Size,_WF) :- avl_max_pair(AVL,int(Sz),_), Size=Sz.
2713
2714 suffix_of_custom_explicit_set(avl_set(A),MinIndex,Result,WF) :-
2715 size_of_avl_sequence(A,Size,WF),
2716 (MinIndex > Size
2717 -> add_wd_error('index larger than size of sequence in suffix_sequence (\\|/)! ', '>'(MinIndex,Size),WF)
2718 % ; MinIndex = 0 -> Result = avl_set(A) % case already treated in bsets_clp
2719 ; MinIndex = Size -> Result=[]
2720 ; suffix_of_custom_explicit_set2(A,MinIndex,OrdList,[]),
2721 %print(suffix(A,MinIndex,OrdList)),nl,
2722 ord_list_to_avlset(OrdList,Result,suffix_of_custom_explicit_set)
2723 ).
2724 suffix_of_custom_explicit_set2(empty,_MinIndex) --> {true}.
2725 suffix_of_custom_explicit_set2(node((int(KeyFrom),KeyTo),_True,_,L,R),MinIndex) -->
2726 ({KeyFrom =< MinIndex} -> suffix_of_custom_explicit_set2(R,MinIndex)
2727 ; {ShiftedKeyFrom is KeyFrom-MinIndex},
2728 ({KeyFrom =:= MinIndex+1}
2729 -> {true} ; suffix_of_custom_explicit_set2(L,MinIndex)),
2730 [((int(ShiftedKeyFrom),KeyTo)-true)],
2731 suffix_of_custom_explicit_set2(R,MinIndex)
2732 ).
2733
2734 shift_avl_sequence_to_ord_list(AVL,Offset,ShiftedOrdList) :-
2735 avl_to_list(AVL,List),shift_seq(List,Offset,ShiftedOrdList).
2736 % it does not seem to be worth to use avl_to_list_dcg_offset or a variation thereof
2737 % it is not really slower to do two traversals (avl_to_list and shift_seq)
2738
2739 shift_seq([],_,[]).
2740 shift_seq([(int(I),Val)-true|T],Offset,[(int(NI),Val)-true|ST]) :- NI is I+Offset,
2741 shift_seq(T,Offset,ST).
2742
2743 :- use_module(debug).
2744 concat_custom_explicit_set(avl_set(S1),Seq2,Res,WF) :- nonvar(Seq2), Seq2=avl_set(S2),% print_term_summary(concat(avl_set(S1),avl_set(S2),Res)),
2745 size_of_avl_sequence(S1,Size1,WF),
2746 shift_avl_sequence_to_ord_list(S2,Size1,OL2),
2747 %avl_to_list(S1,OL1),
2748 avl_to_list_dcg(S1,NewOrdList,OL2), % use OL2 rather than [] as tail
2749 %append(OL1,OL2,NewOrdList), % we could avoid traversing OL1 again by doing a custom avl_to_list/3 which specifies tail
2750 ord_list_to_avlset(NewOrdList,Res,concat). % , print_term_summary(res_concat(Res)).
2751
2752 % a DCG version of avl_to_list; allows to call it with something else than [] as tail
2753 avl_to_list_dcg(empty) --> [].
2754 avl_to_list_dcg(node(Key,Val,_,L,R)) -->
2755 avl_to_list_dcg(L), [(Key-Val)],
2756 avl_to_list_dcg(R).
2757
2758 /* conc: concatenation of sequence of sequences */
2759 conc_custom_explicit_set(avl_set(AVL),Res) :-
2760 avl_min_pair(AVL,int(ONE),First),
2761 conc2_cs(First,ONE,AVL,0,NewOrdList),
2762 ord_list_to_avlset(NewOrdList,Res,conc).
2763
2764 conc2_cs(Seq,NrSeq,AVL,Offset,OrdList) :-
2765 %print_term_summary(conc2_cs(Seq,NrSeq,AVL,Offset,OrdList)),
2766 add_seq(Seq,Offset,OrdList,NewOffset,TailOrd),
2767 %print(res(OrdList,NewOffset,TailOrd)),nl,
2768 (avl_next((int(NrSeq),Seq),AVL,(int(N2),Seq2))
2769 -> conc2_cs(Seq2,N2,AVL,NewOffset,TailOrd)
2770 ; TailOrd=[]).
2771
2772 add_seq([],Offset,OrdRes,NewOffset,TailOrdRes) :- NewOffset=Offset, TailOrdRes=OrdRes.
2773 add_seq(avl_set(ASeq),Offset,OrdRes,NewOffset,TailOrd) :-
2774 avl_to_list_dcg_offset(ASeq,Offset,NrEls,OrdRes,TailOrd), NewOffset is Offset+NrEls.
2775
2776 % a version of avl_to_list for sequences which autmatically adds an offset
2777 avl_to_list_dcg_offset(empty,_,0) --> [].
2778 avl_to_list_dcg_offset(node((int(Idx),El),Val,_,L,R),Offset,NrEls) -->
2779 {NIdx is Idx+Offset},
2780 avl_to_list_dcg_offset(L,Offset,N1),
2781 [((int(NIdx),El)-Val)],
2782 avl_to_list_dcg_offset(R,Offset,N2), {NrEls is N1+N2+1}.
2783
2784 prepend_custom_explicit_set(avl_set(S1),ObjectToPrepend,Res) :-
2785 %hit_profiler:add_profile_hit(prepend_custom_explicit_set(avl_set(S1),ObjectToPrepend,Res)),
2786 element_can_be_added_or_removed_to_avl(ObjectToPrepend),
2787 shift_avl_sequence_to_ord_list(S1,1,OL1),
2788 ord_list_to_avlset([(int(1),ObjectToPrepend)-true|OL1],Res).
2789
2790 append_custom_explicit_set(avl_set(S1),ObjectToAppend,Res,WF) :-
2791 element_can_be_added_or_removed_to_avl(ObjectToAppend), % implies that ObjectToAppend is ground
2792 size_of_avl_sequence(S1,Size1,WF), NewSize is Size1+1,
2793 add_ground_element_to_explicit_set(avl_set(S1),(int(NewSize),ObjectToAppend),Res).
2794
2795 tail_sequence_custom_explicit_set(avl_set(S1),Res,Span,WF) :-
2796 shift_avl_sequence_to_ord_list(S1,-1,NewOrdList),
2797 (NewOrdList = [(int(0),_First)-true|TailOL] -> ord_list_to_avlset(TailOL,Res)
2798 ; add_wd_error_span('tail argument is not a sequence!', avl_set(S1),Span,WF)
2799 % add_error_fail(tail_sequence,'tail applied to ', NewOrdList))
2800 ).
2801 last_sequence_explicit_set(avl_set(AVL),Last) :-
2802 avl_max_pair(AVL,int(_Sz),Last).
2803 % TO DO: we could compute height of the path to max H, then check that Sz is in 2**(H-1)+1 .. 2**(H+1)-1 ?
2804 %first_sequence_explicit_set(avl_set(AVL),First) :- % not used anymore; apply_to used instead
2805 % avl_min_pair(AVL,int(_One),First).
2806
2807 front_sequence_custom_explicit_set(avl_set(AVL),Res) :-
2808 avl_max_pair(AVL,int(Size),Last),
2809 direct_remove_element_from_avl(AVL, (int(Size),Last), Res). % we know Last is already in AVL-converted format
2810 %is_avl_sequence_old(AVLSeq) :-
2811 % avl_min_pair(AVLSeq,FFrom,FTo), is_avl_seq(AVLSeq,FFrom,FTo,1).
2812 %is_avl_seq(AVLSeq,int(NextNr),FTo,NextNr) :-
2813 % (avl_next((int(NextNr),FTo),AVLSeq,(FFrom2,FTo2))
2814 % -> N1 is NextNr+1, is_avl_seq(AVLSeq,FFrom2,FTo2,N1)
2815 % ; true).
2816
2817 reverse_custom_explicit_set(avl_set(AVL),Res) :-
2818 avl_to_list_dcg_offset(AVL,0,Size,List,[]),
2819 S1 is Size+1,
2820 reverse_list(List,S1,[],RevList),
2821 ord_list_to_avl(RevList,RevAVL),
2822 Res=avl_set(RevAVL).
2823
2824 reverse_list([],_,Acc,Acc).
2825 reverse_list([(int(Idx),El)-V|T],S1,Acc,Res) :-
2826 NewIdx is S1 - Idx,
2827 reverse_list(T,S1,[(int(NewIdx),El)-V|Acc],Res).
2828
2829 % check if a relation is injective ; compute range at the same time; note AVL can be empty
2830 is_injective_avl_relation(AVL,RangeRes) :-
2831 avl_domain(AVL,ElList),
2832 empty_avl(EmptyAcc),
2833 is_avl_inj_list(ElList,EmptyAcc,Range),
2834 construct_avl_set(Range,RangeRes).
2835
2836 is_avl_inj_list([],Range,Range).
2837 is_avl_inj_list([(_From,To)|T],InRange,OutRange) :-
2838 (avl_fetch(To,InRange) -> fail /* this is not an injection; a range element is repeated */
2839 ; avl_store(To,InRange,true,InRange1),
2840 is_avl_inj_list(T,InRange1,OutRange)
2841 ).
2842
2843 % Example predicates that work with code below:
2844 % card(id((1..1000)*(1..1000))~)=1000*1000
2845 % card(((1..1000)*(1..1000))~)=1000*1000
2846 invert_explicit_set(global_set(GS),_R) :- !,
2847 add_error_and_fail(invert_explicit_set,'Cannot compute inverse of global set: ',GS).
2848 invert_explicit_set(freetype(GS),_R) :- !,
2849 add_error_and_fail(invert_explicit_set,'Cannot compute inverse of freetype: ',GS).
2850 invert_explicit_set(closure([P1,P2],[T1,T2],Clo),R) :- !,
2851 R = closure([P2,P1],[T2,T1],Clo).
2852 invert_explicit_set(closure([P1],[T1],Clo),R) :-
2853 is_member_closure_with_info([P1],[T1],Clo,_Type,Info,MEM),
2854 %print(try_invert_clo(MEM,T1)),nl,
2855 invert_member_predicate(MEM,T1,InvMEM,InvT1),!,
2856 construct_member_closure(P1,InvT1,Info,InvMEM,R). %, print(result(R)),nl.
2857 %invert_explicit_set(closure_x([P1,P2],[T1,T2],Clo,Exp),R) :- !, inv(Exp,IExp,_),
2858 % R = closure_x([P2,P1],[T2,T1],Clo,IExp).
2859 invert_explicit_set(C,AVL) :- expand_custom_set(C,EC,invert_explicit_set), %% convert to AVL ?
2860 inv_and_norm(EC,AVL).
2861
2862 invert_member_predicate(cartesian_product(A,B),couple(TA,TB),
2863 cartesian_product(B,A),couple(TB,TA)).
2864 invert_member_predicate(identity(A),TA,identity(A),TA).
2865
2866
2867 :- block inv_and_norm(-,?).
2868 inv_and_norm(EC,AVL) :- inv(EC,R,Done), norm(Done,R,AVL).
2869
2870 :- block norm(-,?,?).
2871 norm(_,R,AVL) :- normalised_list_to_avl(R,AVL).
2872
2873 :- block inv(-,?,?).
2874 inv([],[],done).
2875 inv([(A,B)|T],[(B,A)-true|DT],Done) :- inv(T,DT,Done).
2876
2877
2878
2879 % checks whether a ground value is in the domain of an AVL relation
2880 check_in_domain_of_avlset(X,AVL) :- convert_to_avl_inside_set(X,AX),!,
2881 ? (avl_fetch_pair(AX,AVL,_) -> true ; fail).
2882 check_in_domain_of_avlset(X,AVL) :-
2883 print('### could not convert arg for check_in_domain_of_avlset'),nl,
2884 print(X),nl,
2885 safe_avl_member_pair(X,_,AVL).
2886
2887
2888
2889 % utility to check if for a value there is at most one matching element in an AVL set
2890 % optimized for function application
2891 at_most_one_match_possible(Element,AVL,Matches) :- nonvar(Element),
2892 Element=(Index,_Rest), % Function Application; TO DO: does this cover all func. appl ?
2893 element_can_be_added_or_removed_to_avl(Index),
2894 convert_to_avl_inside_set(Index,AX), % is ground and normalised ?
2895 % TO DO: check AVL size ? Check other patterns ?
2896 findall((AX,Match),avl_tools:avl_fetch_pair(AX,AVL,Match),Matches),
2897 Matches \= [_,_|_].
2898
2899
2900
2901 apply_to_avl_set(A,X,Y,Span,WF) :- %print(apply(A,X,Y)),nl, %%
2902 ? ground_value_check(X,GroundX),
2903 ? apply_to_avl_set_aux(A,X,Y,GroundX,Span,WF).
2904
2905 ?apply_to_avl_set_aux(A,X,Y,GroundX,Span,WF) :- nonvar(GroundX),!,
2906 ? apply_check_tuple(X,Y,A,Span,WF). % we could call apply_check_tuple_ground to avoid one ground test
2907 % We know that A is a function: we can deterministically apply if X is ground;
2908 % if Y is ground this is only the cases for injective functions
2909 apply_to_avl_set_aux(A,X,Y,GroundX,Span,WF) :-
2910 %(preference(data_validation_mode,true); % we now reduce priority of backpropagation below
2911 preference(find_abort_values,true),
2912 % do not try inverse propagation onto argument X of function application A(X) = Y
2913 !,
2914 avl_approximate_size(A,3,ApproxSizeA),
2915 apply_check_tuple_delay(X,Y,A,ApproxSizeA,Span,WF,GroundX,_,_).
2916 apply_to_avl_set_aux(A,X,Y,GroundX,Span,WF) :-
2917 ground_value_check(Y,GroundY),
2918 avl_approximate_size(A,3,ApproxSizeA), % exact size for height <= 3; approximate size above
2919 (ApproxSizeA < 4 -> SPrio=ApproxSizeA ; SPrio is ApproxSizeA * 10), % magic number; ideally we want X or Y to be known beforehand; if none are known we may miss WD errors and may enumerate useless intermediate variables
2920 get_bounded_wait_flag(SPrio,apply_to_explicit(X,Y),WF,WF1), % this only makes sense if X is a domain variable to be enumerated
2921 %propagate_avl_element_information((X,Y),A,ApproxSizeA,WF), % could be done; but would prevent WD problems from being detected
2922 % this waitflag is used when neither X nor Y are ground;
2923 % quite often not much is gained by enumerating possible values; unless X or Y are constrained or trigger other computations
2924 % WSz is 10*ApproxSizeA, % magic value
2925 %(ApproxSizeA > 100 -> InversePrioSize = 4
2926 % ; avl_range_size_and_propagate_element_info(A,X,Y,RSize), InversePrioSize is ApproxSizeA // RSize), % we could probably compute the exact worst case with the same complexity
2927 % delay_get_wait_flag(GroundY,GroundX,WF1,InversePrioSize,apply_to_explicit_inverse(X,Y),WF,WF2),
2928 %(ApproxSizeA<4000 -> propagate_apply(X,Y,A,ApproxSizeA,WF,GroundX,GroundY) ; true),
2929 apply_check_tuple_delay(X,Y,A,ApproxSizeA,Span,WF,GroundX,WF1,GroundY),
2930 (preference(use_clpfd_solver,false) -> true
2931 % should we also check: preference(find_abort_values,true)?
2932 ; get_wait_flag0(WF,WF0),
2933 propagate_apply(X,Y,A,ApproxSizeA,WF,WF0,GroundX,WF1,GroundY)).
2934
2935 :- block propagate_apply(?,?,?,?,?,-,?,?,?).
2936 propagate_apply(X,Y,AVL,ApproxSizeA,WF,_,GroundX,WF1,GroundY) :-
2937 var(GroundX), var(WF1), var(GroundY),
2938 (preference(disprover_mode,true) -> XX=X % this will also instantiate X and prevent finding WD errors
2939 ; (ApproxSizeA<128 -> true
2940 ; preference(solver_strength,SS), ApproxSizeA < 128+SS*100), % up until 4000 it may make sense to constrain Y
2941 preference(data_validation_mode,false), % note: this can slow down ProB, e.g., test 1105; hence allow disabling it
2942 preference(find_abort_values,false), % TO DO: v = %x.(x:1..20|x+x) & {y,z|y<4 & z=v(y) & (y:{-1,2})} =res: no WD ERROR found
2943 propagate_value(X,XX) % only instantiate X, propagation only makes sense for propagate_avl_element_information_small, as otherwise only X will be bounded
2944 ),
2945 !,
2946 %print_term_summary(propagate_apply2(X,XX,Y,ApproxSizeA)),nl,
2947 propagate_avl_element_information((XX,Y),AVL,ApproxSizeA,WF).
2948 propagate_apply(_,_,_,_,_,_,_,_,_).
2949
2950 :- use_module(library(clpfd),[fd_set/2, in_set/2]).
2951 % only propagate in one direction to allow to find WD errors but also prevent pending co-routines/constraints
2952
2953 :- block propagate_value(-,?).
2954 propagate_value(int(X),R) :- !, fd_set(X,Dom),in_set(RX,Dom), R=int(RX),propagate_atomic_value(X,RX).
2955 propagate_value(fd(X,T),R) :- !, fd_set(X,Dom),in_set(RX,Dom), R=fd(RX,T),propagate_atomic_value(X,RX).
2956 propagate_value((X1,X2),R) :- !, R=(RX1,RX2), propagate_value(X1,RX1), propagate_value(X2,RX2).
2957 propagate_value(pred_true,R) :- !, if(R=pred_true,true,debug_println(9,function_arg_outside_domain(pred_true))).
2958 propagate_value(pred_false,R) :- !, if(R=pred_false,true,debug_println(9,function_arg_outside_domain(pred_false))).
2959 propagate_value(string(X),R) :- !, R=string(RX),propagate_atomic_value(X,RX).
2960 propagate_value(X,RX) :- equal_object(X,RX). % TO DO: get rid of this: this propagates and prevents finding WD errors
2961 :- block propagate_atomic_value(-,?).
2962 propagate_atomic_value(X,Y) :- if(X=Y,true,debug_println(9,function_arg_outside_domain(X))).
2963
2964 /*
2965 :- block propagate_apply(-,?,?,?,?,-,-).
2966 % call propagate as soon as we know something about the function argument and we do not propgagate completely using GroundX/Y anyway
2967 propagate_apply(X,Y,AVL,Size,WF,GroundX,GroundY) :- print(prop_apply(Size,GroundX,GroundY,X,Y)),nl,
2968 (nonvar(GroundX) -> true ; nonvar(GroundY) -> true
2969 ; propagate_avl_element_information((X,Y),AVL,Size,WF)).
2970
2971 % get the waitflag when first WF set and other two not
2972 :- block delay_get_wait_flag(-,-,-,?,?,?,?).
2973 delay_get_wait_flag(_,WF1,WF2, _,_,_,_) :- (nonvar(WF1);nonvar(WF2)),!. % DO NOTHING
2974 delay_get_wait_flag(_,_,_,Prio,Info,WF,WF2) :- get_wait_flag(Prio,Info,WF,WF2).
2975 */
2976
2977 :- block apply_check_tuple_delay(?,?,?, ?,?,?, -,-,-).
2978 apply_check_tuple_delay(X,Y,AVL,_ApproxSizeA,Span,WF,GroundX,WF1,_) :-
2979 ? (nonvar(GroundX);nonvar(WF1)),!,
2980 %(nonvar(WF1) -> print_term_summary(apply_check_tuple_delay(X,Y,AVL,Span,WF,GroundX,WF1,_)) ; true),
2981 ? apply_check_tuple(X,Y,AVL,Span,WF).
2982 apply_check_tuple_delay(X,Y,AVL,ApproxSizeA,_Span,WF,_GroundX,_WF1,_GroundY) :- % Y is ground; do an inverse function lookup
2983 ? inverse_apply_ok(Y,X,AVL,ApproxSizeA),
2984 ? !,
2985 %print(inverse_apply(Y,X,ApproxSizeA)),nl,
2986 ? inverse_get_possible_values(X,Y,AVL,Res),
2987 ? Res=avl_set(InvAVL), % if empty set : we fail
2988 % avl_height(InvAVL,Height), print(height_inv(Height)),nl, %Height<4,
2989 ? (preference(data_validation_mode,true),
2990 avl_approximate_size(InvAVL,10,ApproxSize),
2991 ApproxSize>1
2992 -> A2 is ApproxSize*100, % give lower priority for backwards propagation
2993 % does not call propagate_avl_element_information(X,InvAVL,ApproxSize,WF) or avl_to_table
2994 get_bounded_wait_flag(A2,element_of_avl_inverse_apply_ok(X),WF,WF2),
2995 element_of_avl_set_wf3(X,InvAVL,ApproxSize,WF2,WF)
2996 %apply_check_tuple_delay(X,Y,AVL,ApproxSizeA,Span,WF,GroundX,WF1,_) % now wait on WF1 or GroundX
2997 ? ; element_of_avl_set_wf(InvAVL,X,WF)
2998 ).
2999 apply_check_tuple_delay(X,Y,AVL,ApproxSizeA,Span,WF,GroundX,WF1,_GroundY) :-
3000 apply_check_tuple_delay(X,Y,AVL,ApproxSizeA,Span,WF,GroundX,WF1,_). % now wait on WF1 or GroundX
3001
3002
3003 inverse_get_possible_values(X,Y,AVL,Res) :-
3004 get_template(X,XX,_), copy_term(XX,XX_Copy), % avoid that findall instantiates X
3005 findall(XX_Copy, safe_avl_member_default((XX_Copy,Y),AVL), PossibleValues),
3006 PossibleValues \= [], % fail straightaway
3007 sort(PossibleValues,SPV),
3008 % length(SPV,Len),print(inverse_image(Y,Len)),nl, print_term_summary(apply_check_tuple_delay(X,Y,AVL)),nl,
3009 convert_to_avl(SPV,Res).
3010
3011 % is it ok to compute inverse ? only makes sense if AVL tree not too big and quite functional
3012 inverse_apply_ok(pred_true,_,_AVL,ApproxSizeA) :- !, % only two values possible, probably half of AVL will be returned
3013 ApproxSizeA < 1023. % corresponds to avl_height < 10
3014 inverse_apply_ok(pred_false,_,_AVL,ApproxSizeA) :- !,ApproxSizeA < 1023.
3015 % TO DO: other small types, such as fd(_,_)
3016 inverse_apply_ok(_,_,_AVL,ApproxSizeA) :- ApproxSizeA < 65535. % corresponds Height < 16
3017 %inverse_apply_ok(_,_,_,_).
3018
3019
3020 /*
3021 apply_check_tuple_ground(X,Y,A,Span,WF) :-
3022 convert_to_avl_inside_set(X,AX),!, % we can do optimized lookup + checking in one go
3023 avl_apply(AX,A,XY,Span,WF), kernel_objects:equal_object(XY,Y).
3024 apply_check_tuple_ground(X,Y,A,_Span,_WF) :- preferences:preference(find_abort_values,false), !, safe_avl_member_default((X,Y),A).
3025 apply_check_tuple_ground(X,Y,A,Span,WF) :- !,
3026 if(safe_avl_member_default((X,XY),A), % does not detect abort errors if X unbound
3027 kernel_objects:equal_object(XY,Y),
3028 add_wd_error_span('function applied outside of domain (#4): ','@fun'(X,avl_set(A)),Span,WF)).
3029 */
3030
3031 % apply_check_tuple is allowed to enumerate: either X is ground or Y is ground
3032 %apply_check_tuple(X,Y,A,_Span,_WF) :- preferences:preference(find_abort_values,false),!,safe_avl_member((X,Y),A).
3033 apply_check_tuple(X,Y,A,Span,WF) :-
3034 ? ground_value(X),
3035 ? convert_to_avl_inside_set(X,AX),!, % we can do optimized lookup + checking in one go
3036 ? avl_apply(AX,A,XY,Span,WF),
3037 ? kernel_objects:equal_object_wf(XY,Y,apply_check_tuple,WF).
3038 :- if(environ(no_wd_checking, true)).
3039 apply_check_tuple(X,Y,A,_Span,_WF) :- safe_avl_member_default((X,Y),A).
3040 :- else.
3041 ?apply_check_tuple(X,Y,A,_Span,_WF) :- preferences:preference(find_abort_values,false), !, safe_avl_member_default((X,Y),A).
3042 apply_check_tuple(X,Y,A,Span,WF) :- !,
3043 if(safe_avl_member_default((X,XY),A), % does not detect abort errors if X unbound
3044 kernel_objects:equal_object_wf(XY,Y,apply_check_tuple_avl,WF),
3045 add_wd_error_span('function applied outside of domain (#4): ','@fun'(X,avl_set(A)),Span,WF)).
3046 %apply_check_tuple(X,Y,A,Span,WF) :- % var(Y),!, % we can do the domain checking without penalty, as Y does not help us anyway
3047 % if(safe_avl_member_default((X,XY),A), kernel_objects:equal_object(XY,Y),
3048 % add_wd_error_span('function applied outside of domain (#4): ','@fun'(X,avl_set(A)),Span,WF)).
3049 :- endif.
3050
3051
3052 % ------------------------------------------
3053
3054
3055 :- use_module(b_global_sets,[b_type2_set/2]).
3056 :- use_module(bsyntaxtree,[rename_bt/3]).
3057 union_of_explicit_set(global_set(GS),_,R) :- is_maximal_global_set(GS), !,
3058 R= global_set(GS). /* global_set is already maximal */
3059 union_of_explicit_set(freetype(GS),_,R) :- !, R= freetype(GS). /* freetype is already maximal */
3060 union_of_explicit_set(closure(P,T,B),_,R) :- is_definitely_maximal_closure(P,T,B), !,
3061 R= closure(P,T,B). /* global_set is already maximal */
3062 union_of_explicit_set(_,S2,R) :- is_definitely_maximal_set(S2),!, % will also look at AVL set
3063 R=S2.
3064 union_of_explicit_set(S1,S2,R) :- nonvar(S2), S2 = [], !, R=S1.
3065 union_of_explicit_set(S1,S2,_) :- (var(S1);var(S2)),!,fail. % then we cannot compute it here
3066 union_of_explicit_set(S2,S1,R) :- % print_term_summary(union(S1,S2,R)),nl,
3067 is_not_member_value_closure(S1,TYPE,MS1), nonvar(MS1), is_efficient_custom_set(MS1),
3068 % also works if S2 is complement closure
3069 difference_of_explicit_set(MS1,S2,Diff),!, % print(diff(Diff)),nl,
3070 construct_complement_closure_if_necessary(Diff,TYPE,R).
3071 union_of_explicit_set(avl_set(A1),S2,R) :- !, union_of_avl_set(S2,A1,R).
3072 union_of_explicit_set(S1,S2,R) :-
3073 is_not_member_value_closure(S1,TYPE,MS1), nonvar(MS1), is_efficient_custom_set(MS1),
3074 difference_of_explicit_set(MS1,S2,Diff),!,
3075 construct_complement_closure_if_necessary(Diff,TYPE,R).
3076 union_of_explicit_set(S1,avl_set(A2),R) :- !, union_of_avl_set(S1,A2,R).
3077 union_of_explicit_set(I1,I2,R) :- is_interval_closure_or_integerset(I1,From1,To1), ground(From1), ground(To1),
3078 is_interval_closure_or_integerset(I2,From2,To2), ground(From2), ground(To2),
3079 %print(union(From1,To1,From2,To2)),nl,
3080 !,
3081 (union_of_interval(From1,To1,From2,To2,FromRes,ToRes)
3082 -> construct_interval_closure(FromRes,ToRes,R)
3083 %print(interval_union(From1,To1,From2,To2,FromRes,ToRes)),nl,
3084 ; small_enough_for_expansion(From1,To1),small_enough_for_expansion(From2,To2) ->
3085 % do not attempt union_of_closure below
3086 expand_interval_closure_to_avl(From1,To1,R1), R1=avl_set(A1), % empty interval already dealt with above !?
3087 expand_interval_closure_to_avl(From2,To2,R2), R2=avl_set(A2), % Note: unification after call as expand_interval calls equal_object (which gets confused by partially instantiated avl_set(_))
3088 union_of_avl(A1,A2,ARes),R=avl_set(ARes) /* AVL not normalised */
3089 ; transform_global_sets_into_closure(I1,closure(Par,T,Body)),
3090 union_of_closure(I2,Par,T,Body,R)
3091 ).
3092 union_of_explicit_set(closure(P,T,B),C2,Res) :-
3093 union_of_closure(C2,P,T,B,Res).
3094
3095 small_enough_for_expansion(From1,To1) :- number(To1), number(From1), To1-From1<250.
3096
3097 :- use_module(bsyntaxtree,[extract_info/2,extract_info/3]).
3098 %union_of_closure(X,P,T,B,_Res) :- print(union_with_closure(X,P,T,B)),nl,trace,fail.
3099
3100 union_of_closure(global_set(X),P,T,B,Res) :- !, transform_global_sets_into_closure(global_set(X),C),
3101 union_of_closure(C,P,T,B,Res).
3102 union_of_closure(closure(P2,T2,B2),P,T,B,Res) :- !,
3103 % T2 should be equal to T, module seq(_) <-> set(couple(integer,_))
3104 unify_closure_predicates(P,T,B, P2,T2,B2 , NewP,NewT, NewB1,NewB2),
3105 debug:debug_println(9,union_of_two_closures(P,P2,NewP,NewT)),
3106 extract_info(B,B2,NewInfo),
3107 construct_disjunct(NewB1,NewB2,Disj),
3108 % print('union: '),translate:print_bexpr(Disj),nl,
3109 Res = closure(NewP,NewT,b(Disj,pred,NewInfo)).
3110
3111 % rename predicates of two closures so that they work on common closure parameter ids
3112 % and can then be either joined by conjunction or disjunction
3113 unify_closure_predicates(P,T,B, P2,T2,B2 , NewP,NewT, NewB1,NewB2) :-
3114 length(P,Len1), length(P2,Len2),
3115 (Len1=Len2
3116 -> generate_renaming_list(P,P2,RL),
3117 bsyntaxtree:rename_bt(B2,RL,NewB2),
3118 %translate:print_bexpr(NewB2),nl,
3119 NewP=P, NewT=T, NewB1 = B
3120 ; Len1 < Len2 -> unify_clos_lt(P,T,B, P2,T2,B2 , NewP,NewT, NewB1,NewB2)
3121 ; otherwise -> unify_clos_lt(P2,T2,B2, P,T,B , NewP,NewT, NewB1,NewB2)
3122 ).
3123
3124 % TO DO: generalize: currently only works for single identifier on left
3125 % but works for id(NATURAL) \/ %x.(x<0|-x) or abs = id(NATURAL) \/ %x.(x<0|-x) & abs(2)=a2 & abs(-2)=am2
3126 unify_clos_lt([ID1],[couple(_,_)],B, P2,T2,B2 , NewP,NewT, NewB1,NewB2) :-
3127 rename_lambda_result_id(P2,B2,P3,B3),
3128 create_couple_term(P3,T2,Pair),
3129 % print(replacing_by_pair(ID1,Pair)),nl,
3130 bsyntaxtree:replace_id_by_expr(B,ID1,Pair,NewB1),
3131 NewP=P3, NewT=T2, NewB2=B3.
3132
3133 % _lambda_result_ id is not enumerated, hence we have to avoid inserting such ids into NewB1 as part of the pPair
3134 rename_lambda_result_id(['_lambda_result_',ID2],B2,[FRESHID,ID2],B3) :- !,get_unique_id('_RANGE_',FRESHID),
3135 bsyntaxtree:rename_bt(B2,[rename('_lambda_result_',FRESHID)],B3).
3136 rename_lambda_result_id([ID1,'_lambda_result_'],B2,[ID1,FRESHID],B3) :- !,get_unique_id('_RANGE_',FRESHID),
3137 bsyntaxtree:rename_bt(B2,[rename('_lambda_result_',FRESHID)],B3).
3138 rename_lambda_result_id(P2,B2,P2,B2).
3139
3140 create_couple_term([ID1,ID2],[T1,T2],Res) :-
3141 bsyntaxtree:create_couple(b(identifier(ID1),T1,[]),b(identifier(ID2),T2,[]),Res).
3142
3143 generate_renaming_list([],[],[]).
3144 generate_renaming_list([ID|T],[ID2|T2],RL) :-
3145 (ID==ID2 -> generate_renaming_list(T,T2,RL)
3146 ; RL = [rename(ID2,ID)|RL2],
3147 generate_renaming_list(T,T2,RL2)).
3148
3149
3150 % a more clever way of constructing a disjunct; factor out common prefixes
3151 % (A & B1) or (A1 & B2) <=> A1 & (B1 or B2)
3152 % TO DO: we should try and get the leftmost basic conjunct !
3153 /* construct_disjunct(b(conjunct(A1,A2),pred,IA), b(conjunct(B1,B2),pred,_IB), Res) :-
3154
3155 print('TRY DISJUNCT FACTOR: '), translate:print_bexpr(A1),nl,
3156 translate:print_bexpr(B1),nl,
3157 same_texpr_body(A1,B1),!,
3158 print('DISJUNCT FACTOR: '), translate:print_bexpr(A1),nl,
3159 Res = conjunct(A1,b(Disj,pred,IA)),
3160 construct_disjunct(A2,B2,Disj).
3161 */
3162 construct_disjunct(A,B,disjunct(A,B)).
3163
3164 :- use_module(btypechecker,[couplise_list/2]).
3165 %union_of_avl_set(R,A1,Res) :- print(union_of_avl_set(R,A1,Res)),nl,fail.
3166 % TO DO: quick_check if AVL A1 is maximal ?
3167 union_of_avl_set(avl_set(A2),A1,R) :- !, union_of_avl(A1,A2,ARes), R=avl_set(ARes). /* AVL not normalised */
3168 union_of_avl_set(I2,A1,R) :- is_interval_closure_or_integerset(I2,From2,To2), !,
3169 ground(From2), ground(To2), % we can only compute it if bounds known
3170 (avl_min(A1,int(Min)), low_border(From2,Min,FromRes), avl_max(A1,int(Max)), up_border(To2,Max,ToRes)
3171 -> /* AVL contained (almost) in Interval */ % print(union_interval_avl(From2,To2,Min,Max)),nl,
3172 construct_interval_closure(FromRes,ToRes,R)
3173 ; \+ small_interval(From2,To2) ->
3174 transform_global_sets_into_closure(I2,closure(Par,T,Body)), % we may have something like NATURAL1,...
3175 union_of_avl_set_with_closure(Par,T,Body,A1,R)
3176 ; expand_and_convert_to_avl_set(I2,A2), % can generate ARel=empty; will fail if not possible to convert
3177 union_of_avl(A1,A2,ARes), R=avl_set(ARes)
3178 ).
3179 union_of_avl_set(closure(Par,T,Body),A1,Res) :- is_infinite_or_symbolic_closure(Par,T,Body),!,
3180 % TO DO: what if we are in SYMBOLIC mode and the type of T is infinite; maybe we should also keep the union symbolic ?? (cf Ticket/Georghe1)
3181 union_of_avl_set_with_closure(Par,T,Body,A1,Res).
3182 union_of_avl_set(S2,A1,Res) :-
3183 S2 \= freetype(_),
3184 ground_value(S2), % could be a closure
3185 !,
3186 (try_expand_and_convert_to_avl_set(S2,A2)
3187 -> union_of_avl(A1,A2,ARes), Res=avl_set(ARes) /* AVL not normalised */
3188 ; S2=closure(Par,T,Body),
3189 union_of_avl_set_with_closure(Par,T,Body,A1,Res)).
3190
3191 try_expand_and_convert_to_avl_set(S2,A2) :-
3192 catch_enumeration_warning_exceptions(expand_and_convert_to_avl_set(S2,A2),fail).
3193
3194 % try expanding to list, but catch enumeration warnings and fail if they do occur
3195 % used by override(...)
3196 %try_expand_custom_set_to_list(CS,_,_,_) :- nonvar(CS),CS=global_set(GS),is_infinite_global_set(GS,_),
3197 % !,
3198 % fail.
3199 try_expand_custom_set_to_list(CS,_,_,_) :- nonvar(CS),is_infinite_explicit_set(CS),
3200 !, % we could also check is_symbolic_closure
3201 fail.
3202 try_expand_custom_set_to_list(CS,List,Done,Source) :-
3203 catch_enumeration_warning_exceptions(expand_custom_set_to_list(CS,List,Done,Source),fail).
3204
3205
3206 small_interval(From,To) :- number(From), number(To), To-From < 10000.
3207
3208 union_of_avl_set_with_closure(Par,T,Body,A1,Res) :-
3209 Body = b(_,BodyT,_),
3210 %print(union_of_avl_and_infinite_closure(Par,T,BodyT)),nl,
3211 setup_typed_ids(Par,T,TypedPar), %print(typ(TypedPar)),nl,
3212 btypechecker:couplise_list(TypedPar,TypedCPar),
3213 generate_couple_types(TypedCPar,ParExpr,ParType), %print(partype(ParType)),nl,
3214 debug:debug_println(9,union_of_avl_and_infinite_closure(Par,T,BodyT)),
3215 %translate:print_bexpr(Body),nl,
3216 BodyAvl = b(member(ParExpr,b(value(avl_set(A1)),ParType,[])),pred,[]),
3217 %print('AVL: '),translate:print_bexpr(BodyAvl),nl,
3218 extract_info(Body,NewInfo),
3219 Res = closure(Par,T,b(disjunct(BodyAvl,Body),pred,NewInfo)).
3220 % mark_closure_as_symbolic(closure(Par,T,b(disjunct(BodyAvl,Body),pred,NewInfo)),Res).
3221
3222 low_border(Low,AVLMin,R) :- geq_inf(AVLMin,Low),!,R=Low.
3223 low_border(Low,AVLMin,R) :- number(Low),AVLMin is Low-1,R=AVLMin. % extend lower border by one
3224 up_border(Up,AVLMax,R) :- geq_inf(Up,AVLMax),!,R=Up.
3225 up_border(Up,AVLMax,R) :- number(Up),AVLMax is Up+1,R=AVLMax. % extend upper border by one
3226
3227
3228 setup_typed_ids([],[],[]).
3229 setup_typed_ids([ID|TI],[Type|TT],[b(identifier(ID),Type,[])|BT]) :- setup_typed_ids(TI,TT,BT).
3230
3231 generate_couple_types(couple(A,B),b(couple(TA,TB),Type,[]),Type) :- !, Type = couple(TTA,TTB),
3232 generate_couple_types(A,TA,TTA),
3233 generate_couple_types(B,TB,TTB).
3234 generate_couple_types(b(X,T,I),b(X,T,I),T).
3235
3236
3237 % try to see if two intervals can be unioned into a new interval
3238 union_of_interval(F1,T1,F2,T2,FR,TR) :- %print(union(F1,T1,F2,T2,FR,TR)),nl,trace,
3239 geq_inf(F2,F1), geq_inf(T1,T2),!,FR=F1,TR=T1. % interval [F2,T2] contained in [F1,T1]
3240 union_of_interval(F2,T2,F1,T1,FR,TR) :- geq_inf(F2,F1), geq_inf(T1,T2),!,FR=F1,TR=T1. % see above
3241 union_of_interval(F1,T1,F2,T2,FR,TR) :- number(F2),
3242 geq_inf(F2,F1), number(T1),T11 is T1+1,geq_inf(T11,F2), geq_inf(T2,F2),!,FR=F1,TR=T2. % intervals can be joined
3243 union_of_interval(F2,T2,F1,T1,FR,TR) :- number(F2),
3244 geq_inf(F2,F1), number(T1),T11 is T1+1,geq_inf(T11,F2), geq_inf(T2,F2),!,FR=F1,TR=T2. % see above
3245
3246 :- use_module(library(ordsets),[ord_union/3]).
3247 union_of_avl(A1,A2,ARes) :- avl_height(A1,Sz1), avl_height(A2,Sz2), %print(u(Sz1,Sz2)),nl,
3248 (Sz1<Sz2 -> union_of_avl1(A2,Sz2,A1,Sz1,ARes) ; union_of_avl1(A1,Sz1,A2,Sz2,ARes)).
3249 union_of_avl1(A1,Sz1,A2,Sz2,ARes) :- Sz2>2, Sz1 =< Sz2+3, % difference not too big; Sz2 at least a certain size
3250 !,
3251 %print(union(Sz1,Sz2)),nl,
3252 avl_to_list(A2,List2), % get all members
3253 avl_to_list(A1,List1),
3254 ord_union(List1,List2,L12),
3255 ord_list_to_avl(L12,ARes).
3256 union_of_avl1(A1,_Sz1,A2,_Sz2,ARes) :- % this version is better when A2 is small compared to A1
3257 avl_domain(A2,List2), % get all members
3258 add_to_avl(List2,A1,ARes).
3259
3260 :- use_module(library(lists),[reverse/2]).
3261 % a custom version for union(A) where A is AVL set; avoid converting/expanding accumulators and computing avl_height
3262 % runtime of e.g., UNION(x).(x:1000..1514|0..x) 0.65 sec or UNION(n).(n:10000..10010|UNION(x).(x:n..n+1000|n..x)) 4.8 sec is considerably smaller with this version
3263 union_generalized_explicit_set(avl_set(SetsOfSets),Res,WF) :-
3264 expand_custom_set_to_list_wf(avl_set(SetsOfSets),ESetsOfSets,_,union_generalized_wf,WF),
3265 % length(ESetsOfSets,Len),print(union_gen(Len)),nl,
3266 (ESetsOfSets=[OneSet]
3267 -> Res=OneSet % avoid converting to list and back to Avl
3268 ; reverse(ESetsOfSets,RESetsOfSets), % be sure to insert larger values first, so that ord_union has less work to do below; useful if you have many small singleton sets, for example union(ran(%x.(x : 1 .. 10000|{x * x}))) 2.37 secs --> 0.15 secs
3269 % note: dom({r,x|x:1..50000 & r:{x*x}}) is still 3 times faster
3270 union_of_avls(RESetsOfSets,[],Res)).
3271
3272 % take the union of a list of avl_sets
3273 union_of_avls([],Acc,Res) :- ord_list_to_avl(Acc,ARes), construct_avl_set(ARes,Res).
3274 union_of_avls([H|T],Acc,Res) :-
3275 union_of_avl_with_acc(H,Acc,NewAcc),
3276 union_of_avls(T,NewAcc,Res).
3277
3278 union_of_avl_with_acc(avl_set(H),Acc,NewAcc) :- !,
3279 avl_to_list(H,HList),
3280 ord_union(Acc,HList,NewAcc).
3281 union_of_avl_with_acc([],Acc,Res) :- !,Res=Acc.
3282 % other custom sets should normally not appear, we obtain the list as elements stored in an avl_set
3283 union_of_avl_with_acc(G,_,_) :- add_internal_error('Uncovered element: ',union_of_avl_with_acc(G,_,_)),fail.
3284
3285
3286
3287 % TO DO: there are no rules for is_not_member_value_closure for intersection below
3288 intersection_of_explicit_set_wf(global_set(GS),S2,R,_WF) :- is_maximal_global_set(GS), !, R=S2.
3289 intersection_of_explicit_set_wf(freetype(_GS),S2,R,_WF) :- !, R=S2.
3290 intersection_of_explicit_set_wf(_,S2,_,_WF) :- var(S2),!,fail. % code below may instantiate S2
3291 intersection_of_explicit_set_wf(S1,S2,R,_WF) :- is_definitely_maximal_set(S2), !, R=S1.
3292 intersection_of_explicit_set_wf(_S1,[],R,_WF) :-!, R=[].
3293 intersection_of_explicit_set_wf(avl_set(A1),I2,R,_WF) :-
3294 is_interval_closure_or_integerset(I2,From1,To1),
3295 !,
3296 intersect_avl_interval(A1,From1,To1,R).
3297 intersection_of_explicit_set_wf(I1,I2,R,_WF) :-
3298 intersection_with_interval_closure(I1,I2,R),!.
3299 intersection_of_explicit_set_wf(S1,S2,R,_WF) :-
3300 get_avl_sets(S1,S2,A1,A2),
3301 !, % if too large: better to apply normal intersection code ?
3302 % if one of the args is an interval this is already caught in kernel_objects calling intersection_with_interval_closure; see SetIntersectionBig.mch
3303 %print_term_summary(inter_avl(A1,A2)),nl,
3304 avl_domain(A1,ES), % A1 has the smaller height; important for e.g. SetIntersectionBig2.mch
3305 inter2(ES,A2,IRes),
3306 ord_list_to_avlset(IRes,R,intersection). % we have generated the elements in the right order already
3307 intersection_of_explicit_set_wf(closure(P1,T1,B1),closure(P2,T2,B2),R,WF) :-
3308 % this clause seems no longer used a lot? intersection can be dealt with symbolically
3309 % print(intersect(P1,P2,T1,T2)),nl,
3310 unify_closure_predicates(P1,T1,B1, P2,T2,B2 , NewP,NewT, NewB1,NewB2),
3311 debug:debug_println(9,intersection_of_two_closures(P1,P2,NewP,NewT)),
3312 bsyntaxtree:conjunct_predicates([NewB1,NewB2],BI),
3313 % create a conjunction: can be much more efficient than seperately expanding;
3314 % also works well if one of the closures is infinite
3315 C = closure(NewP,NewT,BI),
3316 expand_custom_set_wf(C,R,intersection_of_explicit_set_wf,WF). % we could also keep it symbolic; maybe use SYMBOLIC pref
3317 % to do: also use above for closure and AVL set with member(P,value(avl_set(A)))
3318 % we could also apply the same principle to difference_of_explicit_set
3319 % currently we enable intersection to be treated symbolically (not_symbolic_binary(intersection) commented out)
3320 % This means the above clause for intersection_of_explicit_set_wf is probably useless !! TO DO INVESTIGATE
3321 % a special case; just for interval closures
3322 intersection_with_interval_closure(I1,I2,R) :-
3323 is_interval_closure_or_integerset(I1,From1,To1), nonvar(I2),
3324 intersection_with_interval_closure_aux(I2,From1,To1,R).
3325 intersection_with_interval_closure(avl_set(A1),I2,R) :-
3326 is_interval_closure_or_integerset(I2,From1,To1),
3327 !,
3328 intersect_avl_interval(A1,From1,To1,R).
3329
3330 % try and get AVL sets from two args; first AVL set is smaller one according to height
3331 get_avl_sets(avl_set(A1),S2,AA1,AA2) :- nonvar(S2), S2=avl_set(A2),
3332 (avl_height_compare(A1,A2,R), R=lt
3333 -> (AA1,AA2)=(A1,A2)
3334 ; (AA1,AA2)=(A2,A1)).
3335 %get_avl_sets(S1,S2,AA1,AA2) :- nonvar(S2),S2=avl_set(A2), get_avl_set_arg(S1,A1),
3336 % (avl_height_compare(A1,A2,R),R=gt -> (AA1,AA2)=(A2,A1) ; (AA1,AA2)=(A1,A2)).
3337
3338
3339 %intersection_with_interval_closure_aux(avl_set(A),...
3340 intersection_with_interval_closure_aux(I2,From1,To1,R) :-
3341 is_interval_closure_or_integerset(I2,From2,To2),!,
3342 intersect_intervals_with_inf(From1,To1,From2,To2,FromRes,ToRes),
3343 %% print(intersect_intervals(From1,To1,From2,To2,FromRes,ToRes)),nl, %%
3344 construct_interval_closure(FromRes,ToRes,R).
3345 % (is_interval_closure_or_integerset(R,F,T) -> print(ok(F,T)),nl ; print(ko),nl).
3346 intersection_with_interval_closure_aux(avl_set(A2),From1,To1,R) :-
3347 intersect_avl_interval(A2,From1,To1,R).
3348
3349 % intersect avl with interval
3350 % TO DO: expand interval if small (or small intersection with AVL) and use avl intersection
3351 intersect_avl_interval(_,From2,To2,_) :- (var(From2) ; var(To2)),!,fail.
3352 intersect_avl_interval(A1,From2,To2,R) :- avl_min(A1,int(Min)),
3353 geq_inf(Min,From2),
3354 geq_inf(To2,Min), avl_max(A1,int(Max)),
3355 geq_inf(To2,Max),
3356 % AVL fully contained in interval; no need to expand to list and back again
3357 !,
3358 %print(full(From2,Min,Max,To2)),nl,
3359 construct_avl_set(A1,R).
3360 intersect_avl_interval(A1,From2,To2,R) :-
3361 %print_term_summary(intersect_avl_interval(A1,From2,To2,R)),nl,
3362 avl_domain(A1,ES),
3363 inter_interval(ES,From2,To2,IRes),
3364 ord_list_to_avlset(IRes,R,intersect_avl_interval).
3365
3366 inter_interval([],_,_, []).
3367 inter_interval([IH|T],From2,To2, Res) :- IH = int(H),
3368 (geq_inf(To2,H) ->
3369 (geq_inf(H,From2) -> Res = [IH-true|Res2] ; Res = Res2),
3370 inter_interval(T,From2,To2,Res2)
3371 ; Res = [] % we have exceeded the upper limit of the interval
3372 ).
3373
3374 intersect_intervals_with_inf(From1,To1,From2,To2,FromRes,ToRes) :-
3375 minimum_with_inf(To1,To2,ToRes),
3376 maximum_with_inf(From1,From2,FromRes).
3377
3378 inter2([],_, []).
3379 inter2([H|T],A1, Res) :-
3380 (avl_fetch(H,A1) -> Res = [H-true|Res2] ; Res = Res2), inter2(T,A1,Res2).
3381
3382 ord_list_to_avlset(OL,R) :- ord_list_to_avlset(OL,R,unknown).
3383 ord_list_to_avlset(OrdList,Res,Origin) :-
3384 % assumes that we have generated the elements in the right order already
3385 (OrdList=[] -> Res=[]
3386 ; check_sorted(OrdList,Origin),
3387 ord_list_to_avl(OrdList,ARes), Res=avl_set(ARes)).
3388
3389 % a version which accepts a list of values without -true
3390 % values have to be ground and already converted for use in avl_set
3391 sorted_ground_normalised_list_to_avlset(List,Res,PP) :-
3392 add_true_to_list(List,LT),
3393 ord_list_to_avlset_direct(LT,Res,PP).
3394
3395 add_true_to_list([],[]).
3396 add_true_to_list([H|T],[H-true|TT]) :- add_true_to_list(T,TT).
3397
3398 % the same, but without checking sorted (only use if you are really sure the list is sorted)
3399 ord_list_to_avlset_direct([],[],_).
3400 ord_list_to_avlset_direct([H|T],Res,_):-
3401 (T==[] -> H=Key-Val, Res = avl_set(node(Key,Val,0,empty,empty)) % slightly faster than calling ord_list_to_avl
3402 ; ord_list_to_avl([H|T],ARes), Res = avl_set(ARes)).
3403
3404 check_sorted([],_) :- !.
3405 check_sorted([H-_|T],Origin) :- !, check_sorted2(T,H,Origin).
3406 check_sorted(X,Origin) :- add_error_and_fail(ord_list_to_avlset,'Not a list of -/2 pairs: ',Origin:X).
3407
3408 check_sorted2([],_,_) :- !.
3409 check_sorted2([H-_|T],PH,Origin) :- PH @< H,!, check_sorted2(T,H,Origin).
3410 check_sorted2(X,Prev,Origin) :-
3411 add_error_and_fail(ord_list_to_avlset,'Not a sorted list of -/2 pairs: ',Origin:(X,Prev)).
3412
3413 % ------------------
3414
3415 :- use_module(kernel_freetypes,[is_maximal_freetype/1]).
3416 ?is_definitely_maximal_set(S) :- nonvar(S), %print(c(S)),nl,
3417 ? is_definitely_maximal_set2(S).
3418 is_definitely_maximal_set2(freetype(ID)) :- is_maximal_freetype(ID).
3419 ?is_definitely_maximal_set2(global_set(GS)) :- is_maximal_global_set(GS).
3420 ?is_definitely_maximal_set2(closure(P,T,B)) :- is_definitely_maximal_closure(P,T,B).
3421 is_definitely_maximal_set2(avl_set(S)) :- quick_definitely_maximal_set_avl(S).
3422 is_definitely_maximal_set2([H|T]) :- nonvar(H), is_definitely_maximal_list(H,T). %, nl,print(maximal(H,T)),nl,nl.
3423 %H==pred_true, T == [pred_false]. % for some reason BOOL is sometimes presented this way
3424 is_definitely_maximal_set2(empty) :- % detect unwrapped AVL sets
3425 add_internal_error('Not a set: ',is_definitely_maximal_set2(empty)),fail.
3426 is_definitely_maximal_set2(node(A,B,C,D,E)) :-
3427 add_internal_error('Not a set: ',is_definitely_maximal_set2(node(A,B,C,D,E))),fail.
3428
3429 is_definitely_maximal_list(pred_true,T) :- nonvar(T), T=[_|_]. %
3430 is_definitely_maximal_list(pred_false,T) :- nonvar(T), T=[_|_].%
3431 is_definitely_maximal_list(fd(_,Type),T) :- nonvar(T),b_global_set_cardinality(Type,Card),
3432 % check if we have the same number of elements as the type: then the set must me maximal
3433 length_at_least(T,Card).
3434 % We could try and and also treat pairs
3435
3436 length_at_least(1,_) :- !. % we have already removed 1 element; T can be nil
3437 length_at_least(N,T) :- nonvar(T), T=[_|TT], N1 is N-1, length_at_least(N1,TT).
3438
3439 is_definitely_maximal_closure(_,_,b(truth,_Pred,_)) :- !.
3440 ?is_definitely_maximal_closure(P,T,B) :- is_cartesian_product_closure_aux(P,T,B,S1,S2),!,
3441 % print(cart(S1,S2)),nl,trace,
3442 ? is_definitely_maximal_set(S1),is_definitely_maximal_set(S2).
3443 is_definitely_maximal_closure(P,T,B) :-
3444 ? is_full_powerset_or_relations_or_struct_closure(closure(P,T,B),Sets),% print(pow(S1)),nl,
3445 ? l_is_definitely_maximal_set(Sets).
3446
3447 l_is_definitely_maximal_set([]).
3448 ?l_is_definitely_maximal_set([H|T]) :- is_definitely_maximal_set(H), l_is_definitely_maximal_set(T).
3449
3450 % check if we have an AVL tree covering all elements of the underlying type
3451 quick_definitely_maximal_set_avl(AVL) :-
3452 AVL=node(El,_True,_,_Left,_Right),
3453 quick_definitely_maximal_set_avl_aux(El,AVL).
3454 quick_definitely_maximal_set_avl_aux(El,AVL) :-
3455 try_get_finite_max_card_from_value(El,Card), % this could fail if El contains empty sets !
3456 (Card < 1000 -> true
3457 ; preferences:preference(solver_strength,SS), Card < 1000+SS*100
3458 ), % otherwise too expensive a check avl_size
3459 quick_avl_approximate_size(AVL,MaxSize),
3460 MaxSize >= Card, % otherwise no sense in computing avl_size, which is linear in size of AVL
3461 avl_size(AVL,Size),
3462 %print(check2(Card,Size,El,MaxSize)),nl,
3463 %(MaxSize>=Size -> print(ok(Size,all(Card))),nl ; print('**** ERROR: '), print(Size),nl,trace),
3464 Size=Card.
3465
3466 % check if we have an AVL function with domain covering all elements of the underlying type
3467 quick_definitely_maximal_total_function_avl(AVL) :-
3468 AVL=node(El,_True,_,_Left,_Right),
3469 El=(DomEl,_),
3470 quick_definitely_maximal_set_avl_aux(DomEl,AVL), % the size is exactly the size of the domain
3471 is_avl_partial_function(AVL).
3472
3473 % ----------------------
3474 difference_of_explicit_set(S1,S2,R) :- difference_of_explicit_set_wf(S1,S2,R,no_wf_available).
3475 % this is called with first argument nonvar (for set_subtraction operator):
3476 difference_of_explicit_set_wf(_S1,S2,R,_) :- % print(diff_expl_set(_S1,S2,R)),nl,
3477 is_definitely_maximal_set(S2), !, R=[].
3478 difference_of_explicit_set_wf(S1,S2,R,_) :- nonvar(S2), S2=[],!, R=S1.
3479 difference_of_explicit_set_wf(S1,S2,R,_) :-
3480 %nonvar(S1),
3481 ? is_very_large_maximal_global_set(S1,Type), !, % TO DO: also for freetype ? cartesian products,...
3482 /* we have a complement-set */
3483 complement_set(S2,Type,R).
3484 difference_of_explicit_set_wf(S1,S2,Result,_) :-
3485 is_not_member_value_closure(S1,Type,MS1),
3486 nonvar(MS1), is_custom_explicit_set(MS1,difference_of_explicit_set_wf),!,
3487 union_complement_set(MS1,S2,Type,Result).
3488 difference_of_explicit_set_wf(_,S2,_,_) :- var(S2), !, fail. % then we cannot do anything below
3489 difference_of_explicit_set_wf(S1,S2,R,WF) :-
3490 is_not_member_value_closure(S2,_Type,MS2), nonvar(MS2),
3491 intersection_of_explicit_set_wf(MS2,S1,R,WF),!.
3492 difference_of_explicit_set_wf(I1,I2,R,_) :-
3493 is_interval_closure_or_integerset(I1,From1,To1),
3494 is_interval_closure_or_integerset(I2,From2,To2), %print(try_diff_interval(From1,To1,From2,To2,FromRes,ToRes)),nl,
3495 difference_interval(From1,To1,From2,To2,FromRes,ToRes),
3496 % TO DO: also treat case when difference yields two disjoint intervals
3497 % i.e., do not fail and forget info about interval bounds in case we cannot compute difference as a an interval, e.g., INT - {0}
3498 !,
3499 %% print(construct_diff_interval(From1,To1,From2,To2,FromRes,ToRes)),nl,
3500 construct_interval_closure(FromRes,ToRes,R).
3501 difference_of_explicit_set_wf(avl_set(A1),S2,R,WF) :-
3502 ? (S2=avl_set(A2) ;
3503 ground_value(S2), expand_and_convert_to_avl_set_unless_very_large(S2,A2)),!,
3504 avl_height(A2,H2),
3505 %avl_min(A1,Min1),avl_max(A1,Max1), avl_min(A2,Min2),avl_max(A2,Max2), avl_height(A1,H1),nl,print(diff(avl(H1,Min1,Max1),avl(H2,Min2,Max2))),nl,
3506 ((H2<2 -> true ; avl_height(A1,H1),H1 > H2+1) % then it is more efficient to expand A2 and remove the A2 elements from A1;
3507 % exact threshold when it is beneficial: difference_of_explicit_set2/3
3508 % for {x|x:1..200000 & x mod 2 = 0} - {y|y:2500..29010 & y mod 2 = 0} -> 150 ms vs 80 ms avl(17,int(2),int(200000)),avl(14,int(2500),int(29010)
3509 % {x|x:1..200000 & x mod 2 = 0} - {y|y:2500..59010 & y mod 2 = 0} -> 180 ms vs 80 ms avl(17,int(2),int(200000)),avl(15,int(2500),int(59010))
3510 % {x|x:1..200000 & x mod 2 = 0} - {y|y:500..159010 & y mod 2 = 0} -> 180 ms vs 250 ms avl(17,int(2),int(200000)),avl(17,int(500),int(159010))
3511 -> expand_custom_set_to_sorted_list(S2,ES,_,difference_of_explicit_set1,WF),
3512 difference_of_explicit_set3(ES,A1,R)
3513 ; expand_custom_set_to_sorted_list(avl_set(A1),ES,Done,difference_of_explicit_set2,WF),
3514 difference_of_explicit_set2(ES,A2,R,Done)).
3515 difference_of_explicit_set_wf(S1,S2,R,WF) :- %print_term_summary(difference_of_explicit_set(S1,S2,R)), statistics,
3516 ? (S2=avl_set(A2) ;
3517 ground_value(S2), expand_and_convert_to_avl_set_unless_very_large(S2,A2)),!,
3518 difference_with_avl(S1,A2,R,WF).
3519
3520 :- use_module(bsyntaxtree,[create_texpr/4, conjunct_predicates/2, mark_bexpr_as_symbolic/2]).
3521 difference_with_avl(S1,A2,R,_) :-
3522 is_closure_or_integer_set(S1,[ID],[T],B),
3523 % check if the first argument is infinite; then do the difference set symbolically
3524 % this could supersed the complement set construction and be generalised to other sets apart from avl_sets as A2
3525 is_very_large_or_symbolic_closure([ID],[T],B,1000000),
3526 !, % TO DO: also allow multiple identifiers
3527 create_texpr(identifier(ID),T,[],TID),
3528 create_texpr(value(avl_set(A2)),set(T),[],A2Value),
3529 create_texpr(not_member(TID,A2Value),pred,[],NotMemA2),
3530 conjunct_predicates([B,NotMemA2],NewBody),
3531 % print(infinite(ID)),nl, translate:print_bexpr(NewBody),nl,
3532 mark_bexpr_as_symbolic(NewBody,NewBodyS),
3533 R = closure([ID],[T],NewBodyS).
3534 difference_with_avl(S1,A2,R,WF) :-
3535 % avl_min(A2,Min2),avl_max(A2,Max2),print(diff2(Min2,Max2)),nl,
3536 expand_custom_set_to_sorted_list(S1,ES,Done,difference_of_explicit_set3,WF),
3537 difference_of_explicit_set2(ES,A2,R,Done).
3538
3539
3540 % construct complement of a set
3541 union_complement_set(S1,S2,Type,Result) :-
3542 ground_value_check(S2,G2),
3543 when(nonvar(G2),union_complement_set2(S1,S2,Type,Result)).
3544 union_complement_set2(S1,S2,Type,Result) :-
3545 union_of_explicit_set(S1,S2,S12),
3546 construct_complement_closure_if_necessary(S12,Type,R),
3547 kernel_objects:equal_object(R,Result,union_complement_set2).
3548
3549 % construct complement of a set
3550 complement_set(S2,Type,Result) :-
3551 ground_value_check(S2,G2),
3552 when(nonvar(G2),complement_set2(S2,Type,Result)).
3553 complement_set2(S2,Type,Result) :-
3554 is_not_member_value_closure(S2,Type,MS2),!, % complement of complement
3555 kernel_objects:equal_object(MS2,Result,complement_set2).
3556 complement_set2(S2,Type,Result) :-
3557 try_expand_and_convert_to_avl_with_check(S2,ExpandedS2,difference_complement_set),
3558 construct_complement_closure_if_necessary(ExpandedS2,Type,R),
3559 kernel_objects:equal_object(R,Result,complement_set2).
3560
3561 :- block construct_complement_closure_if_necessary(-,?,?).
3562 construct_complement_closure_if_necessary(Set,TYPE,R) :-
3563 (Set=[] -> b_type2_set(TYPE,R)
3564 ; is_not_member_value_closure(Set,TYPE,MS) -> R=MS % complement of complement
3565 ; construct_complement_closure(Set,TYPE,R)).
3566
3567 % succeeds if difference of two intervals is also a interval
3568 difference_interval(SourceLow,SourceUp,DiffLow,DiffUp,ResLow,ResUp) :-
3569 (ground(SourceLow),ground(DiffLow),geq_inf(SourceLow,DiffLow)
3570 -> inc(DiffUp,D1),maximum_with_inf(D1,SourceLow,ResLow), ResUp=SourceUp
3571 ; ground(DiffUp),ground(SourceUp),geq_inf(DiffUp,SourceUp)
3572 -> ResLow=SourceLow, dec(DiffLow,D1),minimum_with_inf(SourceUp,D1,ResUp)).
3573
3574 inc(N,R) :- N==inf,!,R=inf.
3575 inc(N,N1) :- N1 is N+1.
3576 dec(N,R) :- N==inf,!,R=inf.
3577 dec(N,N1) :- N1 is N-1.
3578
3579 :- block difference_of_explicit_set2(?,?,?,-).
3580 difference_of_explicit_set2(ES,A2,R,_) :- %print_term_summary(diff2(ES,A2,R)),statistics,
3581 avl_min(A2,Min),
3582 diff1(ES,Min,A2,IRes), %print_term_summary(ord_list_to_avl(IRes)),
3583 ord_list_to_avlset(IRes,AVL,difference), % we have generated the elements in the right order already
3584 equal_object(AVL,R). % due to delays in expansion the result could be instantiated
3585
3586 diff1([],_, _,[]).
3587 diff1([H|T],Min,A1, Res) :-
3588 (H @< Min -> Res = [H-true|Res2],diff1(T,Min,A1,Res2)
3589 ; diff2([H|T],A1,Res)).% TO DO: compute avl_max
3590
3591 diff2([],_, []).
3592 diff2([H|T],A1, Res) :-
3593 (avl_fetch(H,A1) -> Res = Res2 ; Res = [H-true|Res2]), diff2(T,A1,Res2).
3594
3595 % another version to be used when second set small in comparison to first set
3596 difference_of_explicit_set3([],A1,Res) :- construct_avl_set(A1,AVL),
3597 equal_object(AVL,Res). % due to delay in expansion, Res could now be instantiated
3598 difference_of_explicit_set3([H|T],A1,ARes) :-
3599 (avl_delete(H,A1,_True,A2) -> true ; A2=A1),
3600 difference_of_explicit_set3(T,A2,ARes).
3601
3602 % -------------------------
3603
3604 % a version of add_element_to_explicit_set where we have already done the groundness check
3605 add_ground_element_to_explicit_set(avl_set(A),Element,R) :- !,
3606 convert_to_avl_inside_set(Element,AEl),
3607 avl_store(AEl,A,true,A2),!,R=avl_set(A2).
3608 add_ground_element_to_explicit_set(Set,Element,R) :- add_element_to_explicit_set(Set,Element,R).
3609
3610 add_element_to_explicit_set(global_set(GS),_,R) :- is_maximal_global_set(GS), !, R=global_set(GS).
3611 add_element_to_explicit_set(freetype(ID),_,R) :- is_maximal_freetype(ID),!, R=freetype(ID).
3612 add_element_to_explicit_set(avl_set(A),Element,R) :-
3613 ground_value(Element), %% was element_can_be_added_or_removed_to_avl(Element),
3614 convert_to_avl_inside_set(Element,AEl),
3615 avl_store(AEl,A,true,A2),!,R=avl_set(A2). /* AVL not normalised */
3616 /* do we need to add support for (special) closures ??
3617 add_element_to_explicit_set(Clos,Element,R) :- nonvar(Element),Element=int(X), nonvar(X),
3618 is_interval_closure_or_integerset(Clos,Low,Up), ground(Low), ground(Up),
3619 union_of_interval(X,X,Low,Up,FromRes,ToRes),
3620 !,
3621 construct_interval_closure(FromRes,ToRes,R).
3622 % not-member closure not dealt with here
3623 */
3624
3625 element_can_be_added_or_removed_to_avl(Element) :-
3626 ground_value(Element),
3627 does_not_contain_closure(Element).
3628 ground_element_can_be_added_or_removed_to_avl(Element) :- /* use if you know the element to be ground */
3629 does_not_contain_closure(Element).
3630
3631 % does not contain closure or infinite other sets
3632 does_not_contain_closure([]).
3633 does_not_contain_closure([H|T]) :-
3634 (simple_value(H) -> true /* TO DO: check if we could have a closure at the end ?? */
3635 ; does_not_contain_closure(H),list_does_not_contain_closure(T)).
3636 does_not_contain_closure(fd(_,_)).
3637 does_not_contain_closure(pred_true /* bool_true */).
3638 does_not_contain_closure(pred_false /* bool_false */).
3639 does_not_contain_closure(int(_)).
3640 does_not_contain_closure(string(_)).
3641 does_not_contain_closure((X,Y)) :- does_not_contain_closure(X), does_not_contain_closure(Y).
3642 does_not_contain_closure(avl_set(_)).
3643 does_not_contain_closure(global_set(G)) :- \+ is_infinite_global_set(G,_).
3644 %does_not_contain_closure(freetype(_)).
3645 does_not_contain_closure(freeval(_,_,Value)) :- does_not_contain_closure(Value).
3646 does_not_contain_closure(rec(Fields)) :- does_not_contain_closure_fields(Fields).
3647
3648 does_not_contain_closure_fields([]).
3649 does_not_contain_closure_fields([field(_,Val)|T]) :- does_not_contain_closure(Val),
3650 does_not_contain_closure_fields(T).
3651
3652 list_does_not_contain_closure([]).
3653 list_does_not_contain_closure([H|T]) :-
3654 does_not_contain_closure(H),list_does_not_contain_closure(T).
3655 list_does_not_contain_closure(avl_set(_)).
3656 list_does_not_contain_closure(global_set(G)) :- \+ is_infinite_global_set(G,_).
3657
3658 simple_value(fd(_,_)).
3659 simple_value(pred_true /* bool_true */).
3660 simple_value(pred_false /* bool_false */).
3661 simple_value(int(_)).
3662 simple_value((A,B)) :- simple_value(A), simple_value(B).
3663 simple_value(string(_)).
3664
3665 remove_element_from_explicit_set(avl_set(A),Element,R) :-
3666 element_can_be_added_or_removed_to_avl(Element),
3667 convert_to_avl_inside_set(Element,AEl), !,
3668 direct_remove_element_from_avl(A,AEl,R).
3669
3670 direct_remove_element_from_avl(A,AEl,R) :-
3671 avl_delete(AEl,A,_True,A2),
3672 construct_avl_set(A2,R). /* AVL not normalised */
3673
3674 /* same as remove but element can be absent */
3675 delete_element_from_explicit_set(avl_set(A),Element,R) :-
3676 element_can_be_added_or_removed_to_avl(Element),
3677 convert_to_avl_inside_set(Element,AEl), !,
3678 (avl_delete(AEl,A,_True,A2)
3679 -> construct_avl_set(A2,R)
3680 ; R = avl_set(A)
3681 ). /* AVL not normalised */
3682
3683 ?is_maximal_global_set(GS) :- is_maximal_global_set(GS,_Type).
3684 ?is_maximal_global_set(GS,Type) :- nonvar(GS),
3685 ? (GS = 'INTEGER', Type=integer ;
3686 \+ kernel_objects:integer_global_set(GS), Type=global(GS)).
3687
3688 % To do: maybe get rid of all complement set code; add in_difference_set as symbolic binary operator
3689 %is_very_large_maximal_global_set(X,_) :- print(very(X)),nl,fail.
3690 ?is_very_large_maximal_global_set(closure(P,T,B),Type) :- is_definitely_maximal_closure(P,T,B),
3691 couplise_list(T,Type). %, print(max(P,T,Type)),nl.
3692 is_very_large_maximal_global_set(global_set('INTEGER'),integer).
3693 is_very_large_maximal_global_set(global_set('STRING'),string).
3694 is_very_large_maximal_global_set(freetype(ID),freetype(ID)) :- is_infinite_freetype(ID).
3695
3696
3697
3698 remove_minimum_element_custom_set(avl_set(S),X,RES) :- !,
3699 avl_del_min(S,X,_True,Res),
3700 (empty_avl(Res) -> RES=[] ; RES = avl_set(Res)).
3701 %remove_minimum_element_custom_set(closure(P,T,B),X,RES) :-
3702 % is_interval_closure_or_integerset(Clos,Low,Up),!,
3703 % X = Low, TO DO: construct new interval closure
3704 remove_minimum_element_custom_set(CS,X,RES) :-
3705 expand_custom_set_to_list(CS,ECS,Done,remove_minimum_element_custom_set),
3706 remove_minimum_element_custom_set2(ECS,X,RES,Done).
3707
3708 :- block remove_minimum_element_custom_set2(?,?,?,-).
3709 % wait until Done: otherwise the Tail of the list could be instantiated by somebody else; interfering with expand_custom_set_to_list
3710 remove_minimum_element_custom_set2([H|T],X,RES,_) :- equal_object((H,T),(X,RES)).
3711
3712
3713 min_of_explicit_set(avl_set(S),Min) :- !, avl_min(S,Min).
3714 min_of_explicit_set(Clos,Min) :-
3715 is_interval_closure_or_integerset(Clos,Low,Up),
3716 (Low == minus_inf -> add_error_and_fail(min_of_explicit_set,'min of INTEGER undefined !',Clos)
3717 ; cs_greater_than_equal(Up,Low),
3718 Min=int(Low)).
3719
3720 cs_greater_than_equal(X,Y) :-
3721 ? ((X==inf;Y==minus_inf) -> true ; kernel_objects:less_than_equal_direct(Y,X)).
3722
3723
3724 max_of_explicit_set(avl_set(S),Max) :- !,avl_max(S,Max).
3725 max_of_explicit_set(Clos,Max) :-
3726 is_interval_closure_or_integerset(Clos,Low,Up),
3727 (Up==inf -> add_error_and_fail(max_of_explicit_set,'max of NATURAL, NATURAL1 not defined !',Clos)
3728 ; cs_greater_than_equal(Up,Low),
3729 Max=int(Up)).
3730
3731 % ------------- SIGMA/PI --------------
3732
3733 % compute sum or product of an integer set:
3734 sum_or_mul_of_explicit_set(avl_set(S),SUMorMUL,Result) :-
3735 avl_domain(S,Dom),
3736 (SUMorMUL=sum -> simple_sum_list(Dom,0,R) ; simple_mul_list(Dom,1,R)),
3737 Result = int(R).
3738 sum_or_mul_of_explicit_set(CS,SUMorMUL,Result) :- SUMorMUL == sum,
3739 is_interval_closure(CS,Low,Up),
3740 sum_interval(Low,Up,Result),
3741 sum_interval_clpfd_prop(Low,Up,Result).
3742
3743 :- block sum_interval(-,?,?), sum_interval(?,-,?).
3744 sum_interval(Low,Up,_) :- (\+ number(Low) ; \+ number(Up)),!,
3745 add_error(sum_interval,'Cannot compute sum of interval: ',Low:Up),fail.
3746 sum_interval(Low,Up,Result) :- Low>Up,!, Result=int(0).
3747 sum_interval(Low,Up,Result) :-
3748 R is ((1+Up-Low)*(Low+Up)) // 2, % generalisation of Gauss formula k*(k+1)//2
3749 Result = int(R).
3750
3751 sum_interval_clpfd_prop(Low,Up,Result) :-
3752 preferences:preference(use_clpfd_solver,true), Result=int(R),
3753 var(R), % we haven't computed the result yet; the bounds are not known; set up constraint propagation rules
3754 !,
3755 try_post_constraint( clpfd:'#=>'((Low #>= 0) , (R #> 0))), % we could provide better bounds here for negative numbers
3756 try_post_constraint( clpfd:'#=>'(((Low #=< Up) #\/ (R #\= 0)) , (R #= ((1+Up-Low)*(Low+Up))//2))),
3757 try_post_constraint( clpfd:'#=>'((Low #> Up) , (R #= 0) )).
3758 % not working yet: x = SIGMA(i).(i:-3..n|i) & x=0 & n< -1
3759 sum_interval_clpfd_prop(_,_,_).
3760
3761 simple_sum_list([],A,A).
3762 simple_sum_list([int(H)|T],Acc,R) :- NA is Acc+H, simple_sum_list(T,NA,R).
3763 simple_mul_list([],A,A).
3764 simple_mul_list([int(H)|T],Acc,R) :- NA is Acc*H, simple_mul_list(T,NA,R).
3765
3766 %compute the sum of the range elements; was used for SIGMA
3767 %sum_of_range_custom_explicit_set(avl_set(A),R) :- %print(sum_avl(A)),nl, %
3768 % avl_domain(A,Dom), simple_range_sum_list(Dom,0,Sum), %print(avl_sum(Sum)),nl,
3769 % R=int(Sum).
3770 %
3771 %simple_range_sum_list([],A,A).
3772 %simple_range_sum_list([(_,int(H))|T],Acc,R) :- NA is Acc+H, simple_range_sum_list(T,NA,R).
3773 %
3774 %compute the product of the range elements; was used for PI
3775 %mul_of_range_custom_explicit_set(avl_set(A),R) :- %print(sum_avl(A)),nl, %
3776 % avl_domain(A,Dom),
3777 % simple_range_mul_list(Dom,1,Sum), %print(avl_mul(Sum)),nl,
3778 % R=int(Sum).
3779 %
3780 %simple_range_mul_list([],A,A).
3781 %simple_range_mul_list([(_,int(H))|T],Acc,R) :- NA is Acc*H, simple_range_mul_list(T,NA,R).
3782
3783 /*
3784 direct_product_symbolic(S,R,Res) :- % NOT YET FINISHED
3785 nonvar(S), S=closure(PS,[T1,TS2],RS),
3786 nonvar(R), R=closure(PR,[T1,TR1],RR),
3787 is_lambda_value_domain_closure(PS,TS,RS, SDomainValue,SExpr),
3788 is_lambda_value_domain_closure(PR,TR,RR, RDomainValue,RExpr),
3789 construct_closure(['zzz','_lambda_result_'],[T1,couple(TR1,TR2)],
3790 member(zzz,SDomainValue) , member(zzz,RDomainValue), eq(lambda,pair(SExpr,RExpr))).
3791 */
3792
3793 % we assume that try_expand_and_convert_to_avl_unless_very_large already called on arguments
3794 direct_product_explicit_set(S,R,Res) :- %print(direct_product),print_runtime,statistics,
3795 nonvar(R), %is_custom_explicit_set(R,direct_product),
3796 nonvar(S), %is_custom_explicit_set(S,direct_product),
3797 direct_product_explicit_set_aux(S,R,Res).
3798 %direct_product_explicit_set_aux(S,R,Res) :- (S = closure(_,_,_) ; R = closure(_,_,_)),
3799 % print_term_summary(direct_product_explicit_set_aux(S,R,Res)),nl,
3800 % % TO DO: generate closure
3801 % fail.
3802 direct_product_explicit_set_aux(avl_set(AS),avl_set(AR),Res) :-
3803 % the expansion guarantees that we have the lists ES and ER then in sorted order
3804 avl_domain(AS,ES), % -> expand_custom_set(avl_set(AS),ES),
3805 avl_domain(AR,ER), % -> expand_custom_set(avl_set(AR),ER),
3806 % print_term_summary(direct_product3(ES,ER)),print_runtime, %%
3807 direct_product3(ES,ER,DPList),
3808 % print(ord_list_to_avlset),print_runtime, %%
3809 ord_list_to_avlset(DPList,DPAVL,direct_product), % is it really ordered ? findall must also return things ordered!
3810 % statistics,% print(equal_object),print_runtime, %%
3811 equal_object(DPAVL,Res,direct_product_explicit_set).
3812
3813 direct_product3([],_Rel2,[]).
3814 direct_product3([(From,To1)|T1],Rel2,Res) :-
3815 get_next_mapped_to_eq(T1,From,TTo,Tail1), ToList1 = [To1|TTo],
3816 get_next_mapped_to(Rel2,From,ToList2,Tail2),
3817 calc_direct_product(ToList1,From,ToList2,Res,Rest),
3818 (Tail2=[] -> Rest=[] ; direct_product3(Tail1,Tail2,Rest)).
3819
3820 % get all elements which map to From, supposing that the list is sorted & we have already had a match
3821 get_next_mapped_to_eq([],_,[],[]).
3822 get_next_mapped_to_eq([(From2,To2)|T],From,Result,Tail) :-
3823 (From=From2 -> Result = [To2|RR], get_next_mapped_to_eq(T,From,RR,Tail)
3824 ; Result = [], Tail = [(From2,To2)|T]
3825 ).
3826
3827 % get all elements which map to From, supposing the list is sorted
3828 get_next_mapped_to([],_,[],[]).
3829 get_next_mapped_to([(From2,To2)|T],From,Result,Tail) :-
3830 (From=From2 -> Result = [To2|RR], get_next_mapped_to_eq(T,From,RR,Tail)
3831 ; From2 @> From -> Result = [], Tail = [(From2,To2)|T]
3832 ; get_next_mapped_to(T,From,Result,Tail)
3833 ).
3834
3835 calc_direct_product([],_From,_,Tail,Tail).
3836 calc_direct_product([To1|T1],From,To2List,Result,Tail) :-
3837 findall((From,(To1,To2))-true,member(To2,To2List),Result,ResResult),
3838 calc_direct_product(T1,From,To2List,ResResult,Tail).
3839
3840 % TO DO: maybe also add a special rule for infinite R such as event_b_identity ?
3841 domain_restriction_explicit_set_wf(S,R,Res,WF) :- /* S <| R */
3842 nonvar(R),
3843 ((nonvar(S),is_one_element_custom_set(S,El),R \= closure(_,_,_)) ->
3844 domain_restrict_singleton_element(El,R,Res)
3845 ; restriction_explicit_set_wf(S,R,Res,domain,pred_true,WF)).
3846 domain_subtraction_explicit_set_wf(S,R,Res,WF) :- /* S <<| R */
3847 (nonvar(S),is_one_element_custom_set(S,El), nonvar(R), R=avl_set(AVL) ->
3848 avl_domain_subtraction_singleton(AVL,El,ARes),
3849 construct_avl_set(ARes,Res) % TO DO: use this also when S is small and R large
3850 ; restriction_explicit_set_wf(S,R,Res,domain,pred_false,WF)).
3851 range_restriction_explicit_set_wf(R,S,Res,WF) :- /* R |> S */
3852 restriction_explicit_set_wf(S,R,Res,range,pred_true,WF).
3853 range_subtraction_explicit_set_wf(R,S,Res,WF) :- /* R |>> S */
3854 restriction_explicit_set_wf(S,R,Res,range,pred_false,WF).
3855
3856
3857 domain_restrict_singleton_element(El,R,Res) :- /* {El} <| R ; TO DO maybe apply this technique for "small" sets as well */
3858 nonvar(R), is_custom_explicit_set(R,domain_restrict_singleton_element),
3859 expand_and_convert_to_avl_set(R,AR), % can generate ARel=empty; will fail if not possible to convert
3860 findall((El,Z)-true, avl_fetch_pair(El,AR,Z), RTuples),
3861 ord_list_to_avlset(RTuples,Res,domain_restrict_singleton_element).
3862 % print_term_summary(domain_restrict_singleton_element(El,R,Res)).
3863
3864 restriction_explicit_set_wf(_,Rel,_,_,_,_) :- var(Rel),!,fail.
3865 restriction_explicit_set_wf(Set,closure([D,R],[TD,TR],Body),Res,RanOrDom,AddWhen,_WF) :-
3866 %print(symbolic_restrict_closure(D,R,Set)),nl,
3867 !,
3868 (RanOrDom=domain
3869 -> TID = b(identifier(D),TD,[]), TT=TD
3870 ; TID = b(identifier(R),TR,[]), TT=TR),
3871 (AddWhen = pred_true
3872 -> PRED = member(TID,b(value(Set),TT,[]))
3873 ; PRED = not_member(TID,b(value(Set),TT,[]))),
3874 conjunct_predicates([b(PRED,pred,[]),Body],NewBody),
3875 try_expand_and_convert_to_avl_with_catch(closure([D,R],[TD,TR],NewBody),Res). % ,print(res(Res)),nl.
3876 restriction_explicit_set_wf(Set,Rel,Res,RanOrDom,AddWhen,WF) :-
3877 % print_term_summary(try_restriction(Set,Rel,Res,RanOrDom,AddWhen)),
3878 is_custom_explicit_set(Rel,restriction_explicit_set_wf),
3879 % statistics(runtime,[Time1,_]), %%%
3880 expand_and_convert_to_avl_set(Rel,ARel), % can generate ARel=empty; will fail if not possible to convert
3881 avl_domain(ARel,ERel), % -> expand_custom_set(avl_set(ARel),ERel),
3882 %try_expand_and_convert_to_avl_unless_large(Set,ES),
3883 (nonvar(Set),Set=avl_set(AVLS)
3884 -> restrict2_avl(ERel,AVLS,DRes,RanOrDom,AddWhen,Done) %, print_term_summary(restrict2_avl(ERel,AVLS,DRes,RanOrDom,AddWhen))
3885 ; restrict2(ERel,Set,DRes,RanOrDom,AddWhen,Done,WF)
3886 ),
3887 finish_restriction(Done,DRes,Res).
3888 % statistics(runtime,[Time2,_]), Time is Time2-Time1, %%%
3889 % print_message(restriction(Time,RanOrDom,AddWhen)). %%%
3890 :- block finish_restriction(-,?,?).
3891 finish_restriction(_,DRes,Res) :-
3892 ? ord_list_to_avlset(DRes,Restriction,restriction),
3893 ? equal_object(Restriction,Res,finish_restriction). % as we may block below: we need to use equal_object
3894
3895 restrict2([],_,[],_,_,done,_WF).
3896 restrict2([(From,To)|T],S,Res,RanOrDom,AddWhen,Done,WF) :-
3897 ? (RanOrDom==domain -> El=From ; El=To),
3898 ? kernel_equality:membership_test_wf(S,El,MemRes,WF), % TO DO: WF Version !!
3899 /* this only makes sense once we have the full result as argument:
3900 (nonvar(MemRes) -> true % it is already decided
3901 ; AddWhen=pred_true -> kernel_equality:membership_test(Res,(From,To),MemRes)
3902 ; kernel_equality:membership_test(Res,(From,To),InResult), bool_pred:negate(InResult,MemRes)
3903 ), */
3904 ? restrict3(MemRes,From,To,T,S,Res,RanOrDom,AddWhen,Done,WF).
3905 :- block restrict3(-, ?,?, ?,?,?, ?,?,?,?).
3906 restrict3(MemRes, From,To, T,S,Res, RanOrDom,AddWhen,Done,WF) :-
3907 ? (AddWhen=MemRes -> Res = [(From,To)-true|TRes]
3908 ; Res=TRes),
3909 ? restrict2(T,S,TRes,RanOrDom,AddWhen,Done,WF).
3910
3911 % optimised version when second set is also an AVL tree: less blocking,...
3912 restrict2_avl([],_,[],_,_,done).
3913 restrict2_avl([(From,To)|T],AVLS,Res,RanOrDom,AddWhen,Done) :-
3914 fetch(RanOrDom,From,To,AVLS,MemRes),
3915 (AddWhen=MemRes -> Res = [(From,To)-true|TRes]
3916 ; Res=TRes),
3917 restrict2_avl(T,AVLS,TRes,RanOrDom,AddWhen,Done).
3918
3919 fetch(domain,El,_,AVLS,MemRes) :- (avl_fetch(El,AVLS) -> MemRes=pred_true ; MemRes = pred_false).
3920 fetch(range,_,El,AVLS,MemRes) :- (avl_fetch(El,AVLS) -> MemRes=pred_true ; MemRes = pred_false).
3921
3922 % override R(X) := Y
3923 override_pair_explicit_set(avl_set(S),X,Y,avl_set(NewAVL)) :- element_can_be_added_or_removed_to_avl(X),
3924 element_can_be_added_or_removed_to_avl(Y),
3925 convert_to_avl_inside_set(X,AX),
3926 convert_to_avl_inside_set(Y,AY),
3927 % print(override_pair_explicit_set(AX,AY)),nl,
3928 avl_domain_subtraction_singleton(S,AX,AVL2),
3929 avl_store((AX,AY), AVL2, true, NewAVL).
3930
3931 avl_domain_subtraction_singleton(AVL,AX,NewAVL) :-
3932 avl_delete_pair(AX,AVL,_True,AVL2),
3933 !, % recurse, in case we have multiple entries
3934 % this recursion could be avoided if we know AVL to be a function
3935 avl_domain_subtraction_singleton(AVL2,AX,NewAVL).
3936 avl_domain_subtraction_singleton(AVL,_,AVL).
3937
3938
3939 /* --------- */
3940 /* EXPANSION */
3941 /* --------- */
3942
3943 :- use_module(b_global_sets,[all_elements_of_type/2, all_elements_of_type_rand/2]).
3944
3945 %expand_custom_set(CSet,E) :- print_term_summary(start_expanding(CSet,E)),nl,fail.
3946 expand_custom_set(X,R) :- expand_custom_set_wf(X,R,expand_custom_set,no_wf_available).
3947 expand_custom_set(X,R,Src) :- expand_custom_set_wf(X,R,Src,no_wf_available).
3948 expand_custom_set_wf(X,R,Source,WF) :- var(X), !,
3949 add_error_and_fail(expand_custom_set_wf, 'Variable as argument: ',expand_custom_set_wf(X,R,Source,WF)).
3950 expand_custom_set_wf(global_set(GS),ExpandedSet,_,_) :- !,all_elements_of_type(GS,ExpandedSet).
3951 expand_custom_set_wf(freetype(GS),R,_,_) :- !,
3952 expand_freetype(GS,ValueList), convert_to_avl(ValueList,R).
3953 expand_custom_set_wf(avl_set(AVL),ExpandedSet,_,_) :- !,
3954 avl_domain(AVL,ExpandedSet).
3955 expand_custom_set_wf(closure(Parameters,PTypes,Cond),Res,Source,WF) :- !,
3956 expand_closure_to_list(Parameters,PTypes,Cond,Res,_Done,Source,WF).
3957 %wait_try_expand_custom_set(Res1,Res). % could be in AVL form; no longer the case !
3958 expand_custom_set_wf(Set,_,Source,_) :-
3959 add_error_and_fail(expand_custom_set(Source),'Cannot expand custom set: ',Set).
3960
3961
3962
3963 %try_expand_only_custom_closure_global(X,Y) :-
3964 % (var(X) -> X=Y ; expand_only_custom_closure_global(X,Y,check)).
3965
3966 expand_only_custom_closure_global(X,R,C,_WF) :- var(X), !,
3967 add_error_and_fail(expand_only_custom_closure_global, 'Variable as argument: ',expand_only_custom_closure_global(X,R,C)).
3968 expand_only_custom_closure_global(global_set(GS),ExpandedSet,_,_WF) :- !,all_elements_of_type(GS,ExpandedSet).
3969 expand_only_custom_closure_global(freetype(GS),ExpandedSet,_,_WF) :- !,ExpandedSet=freetype(GS).
3970 expand_only_custom_closure_global(avl_set(AVL),ExpandedSet,_,_WF) :- !, ExpandedSet=avl_set(AVL).
3971 expand_only_custom_closure_global(closure(Parameters,PTypes,Cond),Res,CheckTimeOuts,WF) :- !,
3972 (Res==[] -> is_empty_explicit_set(closure(Parameters,PTypes,Cond)) % TO DO: think about other special cases
3973 ; expand_closure_to_avl_or_list(Parameters,PTypes,Cond,Res,CheckTimeOuts,WF)).
3974 expand_only_custom_closure_global(Set,Set,_CheckTimeOuts,_WF).
3975 %:- add_error_and_fail(expand_only_custom_closure_global,'Cannot expand custom set: ',Set).
3976
3977
3978 try_expand_custom_set(CS,Expansion) :-
3979 try_expand_custom_set_wf(CS,Expansion,try_expand_custom_set,no_wf_available).
3980
3981
3982 try_expand_custom_set_wf(CS,Res,_,_) :- var(CS),!,Res=CS.
3983 try_expand_custom_set_wf([],Res,_,_) :- !, Res=[].
3984 try_expand_custom_set_wf([H|T],Res,_,_) :- !, Res=[H|T].
3985 try_expand_custom_set_wf(CS,Res,Src,WF) :-
3986 expand_custom_set_wf(CS,Res,Src,WF). % will generate error message for illegal sets
3987
3988
3989 :- assert_must_succeed((expand_custom_set_to_list(closure(['_zzzz_unit_tests'],
3990 [couple(integer,integer)],
3991 b(member(b(identifier('_zzzz_unit_tests'),couple(integer,integer),[generated]),
3992 b(value([(int(1),int(22))]),set(couple(integer,integer)),[])),pred,[])),R),R==[(int(1),int(22))])).
3993
3994 expand_custom_set_to_list(CS,List) :- expand_custom_set_to_list(CS,List,_Done,unknown).
3995
3996 % a version of expansion which returns guaranteed_ground if the List is guaranteed to be ground
3997 expand_custom_set_to_list_gg(CS,List,GuaranteedGround,_PP) :-
3998 nonvar(CS), CS=avl_set(AVL), var(List),
3999 !,
4000 GuaranteedGround = guaranteed_ground,
4001 avl_domain(AVL,List).
4002 expand_custom_set_to_list_gg(CS,List,not_guaranteed_ground,PP) :-
4003 expand_custom_set_to_list(CS,List,_Done,PP).
4004
4005 % a version where the expansion should happen straightaway and should not block:
4006 expand_custom_set_to_list_now(CS,List) :- expand_custom_set_to_list(CS,List,Done,unknown),
4007 (Done==true -> true ; print_error(expand_custom_set_to_list_not_done(CS,List))).
4008
4009 :- block expand_custom_set_to_sorted_list(-,-,?,?,?).
4010 % sorts the resulting list if needed
4011 % due to random enumeration
4012 expand_custom_set_to_sorted_list(From,To,Done,Source,WF) :-
4013 expand_custom_set_to_list(From,UnsortedTo,Done,Source),
4014 (preferences:get_preference(randomise_enumeration_order,true)
4015 -> sort_when_done(Done,UnsortedTo,To,WF) ; UnsortedTo = To).
4016
4017 :- block sort_when_done(-,?,?,?).
4018 sort_when_done(_,Unsorted,Res,WF) :- sort(Unsorted,Sorted),
4019 equal_object_wf(Sorted,Res,sort_when_done,WF).
4020
4021 expand_custom_set_to_list(From,To,Done,Source) :-
4022 expand_custom_set_to_list_wf(From,To,Done,Source,no_wf_available).
4023
4024 :- use_module(kernel_objects,[equal_object_wf/4]).
4025
4026 :- block expand_custom_set_to_list_wf(-,-,?,?,?).
4027 % ensures that the output is a pure list; the list skeleton should not be instantiated by anybody else
4028 expand_custom_set_to_list_wf(From,To,Done,Source,WF) :-
4029 ? (var(From) ->
4030 (is_list_skeleton(To) -> equal_object_wf(To,From,Source,WF), Done=true
4031 ; expand_custom_set_to_list2(To,From,Done,Source,WF))
4032 ? ; var(To),is_list_skeleton(From) -> To=From, Done=true % equal_object_wf will also to a Prolog unification
4033 ? ; expand_custom_set_to_list2(From,To,Done,Source,WF)).
4034 expand_custom_set_to_list2([],ExpandedSet,Done,_Source,WF) :- !,
4035 equal_object_wf([],ExpandedSet,expand_custom_set_to_list2,WF),Done=true.
4036 ?expand_custom_set_to_list2([H|T],ExpandedSet,Done,Source,WF) :- !,
4037 ? equal_object_wf([H|ET],ExpandedSet,expand_custom_set_to_list2,WF),
4038 expand_custom_set_to_list3(T,ET,Done,Source,WF).
4039 expand_custom_set_to_list2(global_set(GS),ExpandedSet,Done,_Source,WF) :- !,
4040 all_elements_of_type_rand(GS,R),
4041 check_list(R,expand_custom_set_to_list2),
4042 equal_object_wf(R,ExpandedSet,expand_custom_set_to_list2,WF),Done=true.
4043 ?expand_custom_set_to_list2(avl_set(AVL),ExpandedSet,Done,_Source,WF) :- !,
4044 ? avl_domain(AVL,R), %print_term_summary(expanded(avl_set(AVL),R)),nl,
4045 ? equal_object_wf(R,ExpandedSet,expand_custom_set_to_list2,WF), Done=true.
4046 expand_custom_set_to_list2(closure(Parameters,PTypes,Cond),ExpandedSet,Done,Source,WF) :- !,
4047 expand_closure_to_list(Parameters,PTypes,Cond,ExpandedSet,Done,Source,WF).
4048 %assign_expand_result(CDone,Res,ExpandedSet,Done).
4049 expand_custom_set_to_list2(freetype(ID),ExpandedSet,Done,_Source,WF) :- !, %print(expand_freetype(ID)),nl,
4050 expand_freetype(ID,R),
4051 equal_object_wf(R,ExpandedSet,expand_custom_set_to_list2,WF),
4052 Done=true.
4053 % missing avl_set wrapper:
4054 expand_custom_set_to_list2(node(A,B,C,D,E),ExpandedSet,Done,Source,WF) :- !,
4055 add_internal_error('Illegal argument: ',expand_custom_set_to_list2(node(A,B,C,D,E),ExpandedSet,Done,Source)),
4056 expand_custom_set_to_list2(avl_set(node(A,B,C,D,E)),ExpandedSet,Done,Source,WF).
4057 expand_custom_set_to_list2(E,ES,Done,Source,WF) :-
4058 add_internal_error('Illegal argument: ',expand_custom_set_to_list2(E,ES,Done,Source,WF)),fail.
4059
4060 :- block expand_custom_set_to_list3(-,-,?,?,?). % we are no longer sure which was From and which is To
4061 expand_custom_set_to_list3(From,To,Done,Source,WF) :-
4062 ? (var(From) -> expand_custom_set_to_list2(To,From,Done,Source,WF) ;
4063 ? expand_custom_set_to_list2(From,To,Done,Source,WF)).
4064
4065 expand_freetype(ID,Elements) :- var(ID), !,
4066 add_internal_error('Uninstantiated freetype ID: ',expand_freetype(ID,Elements)), fail.
4067 expand_freetype(ID,Elements) :-
4068 findall(FV, enumerate_freetype(basic,FV,freetype(ID)), Elements).
4069
4070 is_list_skeleton(X) :- var(X),!,fail.
4071 is_list_skeleton([]).
4072 is_list_skeleton([_|T]) :- is_list_skeleton(T).
4073
4074 % true if it is more efficient to keep this, rather than expand into list
4075 is_efficient_custom_set(avl_set(_)).
4076 is_efficient_custom_set(closure(P,T,B)) :-
4077 (is_interval_closure(closure(P,T,B),_,_) -> true ; is_infinite_or_symbolic_closure(P,T,B)).
4078 is_efficient_custom_set(global_set(X)) :- is_infinite_global_set(X,_).
4079 is_efficient_custom_set(freetype(_)).
4080
4081 % tries to expand & convert to avl_set; fails if not possible: NOTE: also generates empty AVL
4082 expand_and_convert_to_avl_set(R,AER) :-
4083 try_expand_and_convert_to_avl(R,ER),
4084 nonvar(ER),(ER==[] -> AER=empty ; ER=avl_set(AER)).
4085
4086
4087 expand_and_convert_to_avl_set_unless_very_large(R,AER) :-
4088 try_expand_and_convert_to_avl_unless_very_large(R,ER),
4089 nonvar(ER),(ER==[] -> AER=empty ; ER=avl_set(AER)).
4090 expand_and_convert_to_avl_set_unless_large(R,AER) :-
4091 try_expand_and_convert_to_avl_unless_large(R,ER),
4092 nonvar(ER),(ER==[] -> AER=empty ; ER=avl_set(AER)).
4093
4094 % similar to unless_large version, but will only expand if it is guaranteed to be small
4095
4096 try_expand_and_convert_to_avl_if_smaller_than(freetype(GS),Res,_) :- !, Res = freetype(GS).
4097 try_expand_and_convert_to_avl_if_smaller_than([H|T],Res,_) :- !, try_expand_and_convert_to_avl([H|T],Res).
4098 try_expand_and_convert_to_avl_if_smaller_than(avl_set(A),Res,_) :- !, Res=avl_set(A).
4099 try_expand_and_convert_to_avl_if_smaller_than(CS,Res,Limit) :-
4100 (is_small_specific_custom_set(CS,Limit)
4101 -> % print(expand(Limit)),nl, translate:print_bvalue(CS),nl,
4102 try_expand_and_convert_to_avl(CS,Res)
4103 ; Res = CS % TO DO: maybe look at cardinality of types and determine max. cardinality
4104 ).
4105 is_small_specific_custom_set(CS,Limit) :- card_for_specific_custom_set(CS,Card,Code),
4106 call(Code), ground(Card),Card \= inf, number(Card),Card<Limit.
4107 get_card_for_specific_custom_set(CS,Card) :-
4108 card_for_specific_custom_set(CS,Card,Code),
4109 call(Code), ground(Card).
4110
4111 try_expand_and_convert_to_avl_unless_large(CS,Res) :-
4112 try_expand_and_convert_to_avl_unless_large(CS,Res,2000).
4113 try_expand_and_convert_to_avl_unless_very_large(CS,Res) :-
4114 try_expand_and_convert_to_avl_unless_large(CS,Res,10000).
4115 %try_expand_and_convert_to_avl_unless_very_very_large(CS,Res) :-
4116 % try_expand_and_convert_to_avl_unless_large(CS,Res,100000).
4117
4118 try_expand_and_convert_to_avl_unless_large(CS,Res,_) :- var(CS), !, CS=Res.
4119 try_expand_and_convert_to_avl_unless_large(global_set(GS),Res,_) :- !, Res = global_set(GS).
4120 try_expand_and_convert_to_avl_unless_large(freetype(GS),Res,_) :- !, Res = freetype(GS).
4121 %try_expand_and_convert_to_avl_unless_large(CS,Res) :- is_interval_closure(CS,Low,Up),!,
4122 % ((ground(Low),ground(Up),Size is 1+Up-Low, Size<2000)
4123 %% -> try_expand_and_convert_to_avl(CS,Res)
4124 % ; Res = CS
4125 % ).
4126 try_expand_and_convert_to_avl_unless_large(closure(P,T,B),Res,_Limit) :-
4127 is_symbolic_closure(P,T,B),!, % is explicitly marked as SYMBOLIC
4128 %print('NOT EXPANDING: '),translate:print_bvalue(closure(P,T,B)),nl,
4129 Res=closure(P,T,B).
4130 try_expand_and_convert_to_avl_unless_large(CS,Res,Limit) :-
4131 card_for_specific_closure(CS,Card,Code),
4132 on_enumeration_warning(call(Code),
4133 (debug_println(cannot_expand_specific_closure_for_card(Limit)), % see test 1519 for relevance
4134 Card=inf)), % assume Card is infinite (could be finite; but we cannot expand it anyway)
4135 !,
4136 ((ground(Card),Card \= inf, number(Card),Card<Limit)
4137 -> try_expand_and_convert_to_avl(CS,Res)
4138 ; Res = CS
4139 ).
4140 try_expand_and_convert_to_avl_unless_large(CS,Res,_Limit) :-
4141 % TO DO: check if maybe we cannot determine card explicitly, but have a large lower-bound
4142 % print_term_summary(try_expand(CS)),
4143 try_expand_and_convert_to_avl(CS,Res). % ,print(expanded),nl.
4144
4145
4146 expand_if_small(CS,Res,Limit) :-
4147 card_for_specific_closure(CS,Card,Code),
4148 call(Code), ground(Card),Card \= inf, number(Card),Card<Limit,
4149 try_expand_and_convert_to_avl(CS,Res), nonvar(Res), Res=avl_set(_).
4150
4151 /*
4152 is_definitely_larger_than(closure(P,T,B),Limit) :-
4153 card_for_specific_closure(CS,Card,Code),
4154 call(Code),ground(Card),
4155 (Card == inf -> true ; number(Card),Card>Limit).
4156 is_definitely_larger_than(global_set(GS),Limit) :-
4157 b_global_set_cardinality(GS,Card), Card>Limit.*/
4158
4159
4160
4161 % calls try_expand_and_convert_to_avl and returns original value if enumeration warning occured
4162 try_expand_and_convert_to_avl_with_catch(CS,Res) :-
4163 on_enumeration_warning(try_expand_and_convert_to_avl(CS,Res),
4164 Res=CS).
4165
4166 /* tries to generate an avl-structure, if possible */
4167 try_expand_and_convert_to_avl(CS,Res) :- var(CS), !, CS=Res.
4168 try_expand_and_convert_to_avl(avl_set(A),R) :- !, R=avl_set(A).
4169 try_expand_and_convert_to_avl([],R) :- !, R=[].
4170 try_expand_and_convert_to_avl([H|T],R) :- !, try_convert_to_avl([H|T],R).
4171 try_expand_and_convert_to_avl(closure(P,T,B),Res) :- !,
4172 expand_only_custom_closure_global(closure(P,T,B),Expansion,check(try_expand_and_convert_to_avl1),no_wf_available),
4173 try_convert_to_avl(Expansion,Res).
4174 try_expand_and_convert_to_avl(CS,Res) :-
4175 (\+ is_custom_explicit_set(CS,try_expand_and_convert_to_avl)
4176 -> Expansion = CS
4177 ; expand_only_custom_closure_global(CS,Expansion,check(try_expand_and_convert_to_avl2),no_wf_available)
4178 ),
4179 try_convert_to_avl(Expansion,Res).
4180
4181 try_convert_to_avl(Expansion,Res) :-
4182 (should_be_converted_to_avl_from_lists(Expansion) -> construct_avl_from_lists(Expansion,Res) ; Res=Expansion).
4183
4184 should_be_converted_to_avl_from_lists(Value) :- nonvar(Value),
4185 \+ is_custom_explicit_set(Value,should_be_converted_to_avl_from_lists), % already avl_set, global_set or closure
4186 ground_value(Value).
4187
4188 should_be_converted_to_avl(Value) :- %preference(use_avl_trees_for_sets,true),
4189 ground_value(Value).
4190
4191 try_expand_and_convert_to_avl_with_check(CS,Res,_Origin) :- var(CS),!, Res = CS.
4192 try_expand_and_convert_to_avl_with_check([],Res,_Origin) :- !, Res=[].
4193 try_expand_and_convert_to_avl_with_check(avl_set(A),Res,_Origin) :- !, Res=avl_set(A).
4194 try_expand_and_convert_to_avl_with_check([H|T],Res,_) :- !, try_expand_and_convert_to_avl([H|T],Res).
4195 %try_expand_and_convert_to_avl_with_check(CS,Res,_Origin) :-
4196 % \+ is_custom_explicit_set(CS,try_expand_and_convert_to_avl),!, Res = CS.
4197 try_expand_and_convert_to_avl_with_check(CS,Res,_Origin) :-
4198 is_interval_closure(CS,Low,Up), %print(int(Low,Up)),nl,
4199 (var(Low) ; var(Up)), % better keep this symbolic as we may be able to do constraint propagation
4200 !, % TO DO: see if we should do this check in try_expand_and_convert_to_avl above instead
4201 Res=CS.
4202 try_expand_and_convert_to_avl_with_check(CS,Res,Origin) :-
4203 get_card_for_specific_custom_set(CS,Size), % TO DO: avoid checking for special closures twice (below in try_expand_and_convert_to_avl ?)
4204 !,
4205 try_expand_and_convert_to_avl_with_check_size(Size,CS,Res,Origin).
4206 try_expand_and_convert_to_avl_with_check(CS,Res,_) :-
4207 try_expand_and_convert_to_avl(CS,Res).
4208
4209 try_expand_and_convert_to_avl_with_check_size(inf,CS,Res,Origin) :- !,
4210 debug_format(9,'### Not expanding infinite or very large set~n### ORIGIN: ~w~n',[Origin]),
4211 Res=CS.
4212 try_expand_and_convert_to_avl_with_check_size(Size,CS,Res,Origin) :- Size>=10000000, !,
4213 /* will probably never terminate */
4214 debug_format(9,'### Not expanding very large set with cardinality ~w~n### ORIGIN: ~w~n',[Size,Origin]),
4215 Res=CS.
4216 try_expand_and_convert_to_avl_with_check_size(Size,CS,Res,Origin) :- Size>=50000, !,
4217 print('### WARNING: expanding very large comprehension set, size = '), print(Size),nl,
4218 print('### ORIGIN: '), print(Origin),nl,
4219 try_expand_and_convert_to_avl(CS,Res).
4220 try_expand_and_convert_to_avl_with_check_size(_Size,CS,Res,_Origin) :-
4221 try_expand_and_convert_to_avl(CS,Res).
4222
4223 /* underlying assumption for var case: if G is a global set: we get back the
4224 global_set tag immediately: no need to use when to wait;
4225 better: ensure that b_compute_expression always returns a nonvar term */
4226
4227
4228 :- assert_must_succeed((custom_explicit_sets:try_expand_custom_set(closure([xx],[integer],b(falsity,pred,[])),R),R = [])).
4229 :- assert_must_succeed((custom_explicit_sets:test_closure(X),custom_explicit_sets:expand_custom_set(X,EX),
4230 EX = [(fd(1,'Name'),_),(fd(3,'Name'),_)])).
4231
4232 test_closure(X) :- X = closure(['_zzzz_binary'],[couple(global('Name'),set(global('Name')))],
4233 b(member(b(identifier('_zzzz_binary'),couple(global('Name'),set(global('Name'))),[generated]),
4234 b(cartesian_product(b(value([fd(1,'Name'),fd(3,'Name')]),set(global('Name')),[]),
4235 b(value([[fd(2,'Name'),fd(3,'Name')]]),set(set(global('Name'))),[])),
4236 set(couple(global('Name'),set(global('Name')))),[])),pred,[])).
4237
4238
4239 /* --------- */
4240 /* ELEMENT_OF */
4241 /* --------- */
4242
4243
4244 /* A function that instantiates last argument when membership test can be decided */
4245
4246 membership_custom_set(CS,X,R) :- print(warning_deprecated_non_wf_version(CS,X,R)),nl,
4247 membership_custom_set_wf(CS,X,R,_WF).
4248
4249 % membership_custom_set(CS,X,R) :- print(mem_cs(CS,X,R)),nl,fail.
4250 membership_custom_set_wf(avl_set(A),X,R,WF) :- !, membership_avl_set_wf(A,X,R,WF).
4251 membership_custom_set_wf(freetype(_GS),_X,R,_WF) :- !, R=pred_true. % should be covered by clause above
4252 membership_custom_set_wf(CS,X,R,WF) :- R==pred_true,!, element_of_custom_set_wf(X,CS,WF).
4253 membership_custom_set_wf(CS,X,R,WF) :- R==pred_false,!, not_element_of_custom_set_wf(X,CS,WF).
4254 membership_custom_set_wf(CS,_X,R,_WF) :-
4255 ? is_definitely_maximal_set(CS),!, %print(mem_gs(GS,X)),nl,
4256 R=pred_true.
4257 membership_custom_set_wf(closure(Par,Types,Body),X,R,WF) :- !,
4258 closure_membership_wf(X,Par,Types,Body,R,WF).
4259 %membership_custom_set_wf(CS,X,R,_WF) :- is_one_element_custom_set(CS,Y),!, % only succeeds for AVL
4260 % kernel_equality:equality_objects(X,Y,R).
4261 membership_custom_set_wf(global_set(GS),X,R,WF) :- !,
4262 membership_global_set(GS,X,R,WF).
4263 membership_custom_set_wf(CS,X,R,WF) :-
4264 add_internal_error('Illegal custom set: ',membership_custom_set_wf(CS,X,R,WF)),fail.
4265
4266 membership_avl_set_wf(A,X,R,WF) :- R==pred_true,!, element_of_avl_set_wf(A,X,WF).
4267 membership_avl_set_wf(A,X,R,WF) :- R==pred_false,!, not_element_of_custom_set_wf(X,avl_set(A),WF).
4268 ?membership_avl_set_wf(A,X,R,_WF) :- is_one_element_avl(A,Y),!,
4269 ? kernel_equality:equality_objects(X,Y,R).
4270 membership_avl_set_wf(A,_X,R,_WF) :-
4271 quick_definitely_maximal_set_avl(A),!, %print(mem_gs(GS,X)),nl,
4272 R=pred_true.
4273 ?membership_avl_set_wf(A,X,R,WF) :- reify_avl_membership(A,X,R,_FullReification),
4274 %print(reification(R,FullReification,X,CS)),nl,
4275 %(FullReification=true -> true ; %% THIS Slows down e.g. Bosch Deadlock v9 ! TO DO: investigate why
4276 ? when((ground(X);nonvar(R)),membership_avl_set_wf2(A,X,R,WF)).
4277
4278 membership_avl_set_wf2(A,X,R,WF) :- R==pred_true,!, element_of_avl_set_wf(A,X,WF).
4279 membership_avl_set_wf2(A,X,R,WF) :- R==pred_false,!, not_element_of_custom_set_wf(X,avl_set(A),WF).
4280 membership_avl_set_wf2(AVL,X,R,_WF) :-
4281 ? ground_element_can_be_added_or_removed_to_avl(X), !,
4282 ? (safe_avl_member(X,AVL) %safe_avl_member_ground(X,AVL)
4283 ? -> R=pred_true ; R=pred_false).
4284 membership_avl_set_wf2(AVL,X,Res,WF) :- % X is ground but cannot be added
4285 (Res \== pred_false, element_of_avl_set_wf(AVL,X,WF), Res=pred_true
4286 ;
4287 Res \== pred_true, not_element_of_custom_set_wf(X,avl_set(AVL),WF), Res=pred_false).
4288
4289 membership_global_set(GS,_X,R,_WF) :- is_maximal_global_set(GS),!,
4290 R=pred_true.
4291 membership_global_set(GS,X,R,WF) :- ground(X),!,
4292 (element_of_global_set_wf(X,GS,WF) -> R=pred_true ; R=pred_false).
4293 membership_global_set(GS,X,R,_WF) :- get_integer_set_interval(GS,Low,Up),!,
4294 membership_interval(X,Low,Up,R).
4295 membership_global_set(GS,X,R,WF) :- % this case should probably never apply
4296 print(uncovered_membership(GS,X,R,WF)),nl,
4297 when(ground(X), (element_of_global_set_wf(X,GS,WF) -> R=pred_true ; R=pred_false)).
4298
4299 membership_interval(X,Low,Up,Res) :- nonvar(Up),Up=inf,!,X=int(IX),
4300 b_interpreter_check:check_arithmetic_operator('<=',Low,IX,Res).
4301 membership_interval(X,Low,Up,Res) :- kernel_equality:in_nat_range_test(X,int(Low),int(Up),Res).
4302
4303 :- use_module(bool_pred).
4304 closure_membership_wf(X,[ZZZZ],[integer],CondClosure,Res,_WF) :- %print(closmem(X,Res)),nl,trace,
4305 is_interval_closure_body(CondClosure,ZZZZ,LOW,UP),!, % print(in_interval_closure(X,LOW,UP)),nl,
4306 kernel_equality:in_nat_range_test(X,int(LOW),int(UP),Res). % , print(in_nat_range(X,LOW,UP,Res)),nl.
4307 % TO DO: deal with open intervals 0..inf ...
4308 closure_membership_wf(X,Par,Types,Body,Res,WF) :-
4309 is_member_closure(Par,Types,Body,_Type,VAL),
4310 (VAL=value(_) ; VAL = cartesian_product(b(value(A),_,_),b(value(B),_,_))),!,
4311 (VAL=value(Set)
4312 -> kernel_objects:membership_test_wf(Set,X,Res,WF)
4313 ; kernel_equality:cartesian_pair_test_wf(X,A,B,Res,WF)).
4314 closure_membership_wf(X,Par,Typ,Body,Res,WF) :-
4315 is_not_member_closure(Par,Typ,Body,_Type,value(Set)),!, %print(not_mem(Closure)),nl,
4316 bool_pred:negate(ResXSet,Res), % was kernel_equality:inv_mem_obj(ResXSet,Res),
4317 kernel_objects:membership_test_wf(Set,X,ResXSet,WF).
4318 % TO DO: if closure = POW closure -> translate into subset_test pow_subset
4319 % TO DO: support a few other closures related to symbolic unary/binary operators: closure1, POW(..), ... ?
4320 % TO DO: expand if set is small
4321 closure_membership_wf(X,Par,Types,Body,Res,WF) :- ground_value(X),!,
4322 closure_membership_ground_wf(X,closure(Par,Types,Body),Res,WF).
4323 closure_membership_wf(X,Par,Types,Body,Res,WF) :-
4324 expand_if_small(closure(Par,Types,Body),Expanded,100),!,
4325 %print(expanded(Expanded)),nl,
4326 membership_custom_set_wf(Expanded,X,Res,WF).
4327 closure_membership_wf(X,Par,Types,Body,Res,WF) :-
4328 Body \= b(member(_,_),_,_), % otherwise we may have an infinite loop; b_check_boolean_expression will generate a closure which will call closure_membership_wf again; TO DO: refine to allow certain memberships to go through
4329 get_texpr_info(Body,BodyInfo),
4330 \+ member(prob_annotation(recursive(_RID)),BodyInfo), % otherwise we can get errors as recursive identifier _RID needs to be added to local state ! (test 1151 fails otherwise)
4331 % TO DO: add recursive parameter below in set_up_typed_localstate2; + in which other circumstances do we need to set up recursion identifier !
4332 % Try reifiyng the body
4333 NegationContext=positive,
4334 copy_wf_start(WF,CWF),
4335 b_interpreter:set_up_typed_localstate2(Par,Types,ParValues,TypedVals,[],State,NegationContext),
4336 %couplise_list(Types,XType),
4337 convert_list_into_pairs(ParValues,SingleParValue),
4338 % print(try_reify(X,Par,ParValues,SingleParValue)),nl, translate:print_bexpr(Body),nl,
4339 kernel_objects:equal_object(X,SingleParValue,closure_membership_wf),
4340 b_interpreter_check:b_check_boolean_expression(Body,[],State,CWF,PredRes),
4341 !,
4342 (debug_mode(on) -> print('REIFICATION of closure: '), translate:print_bexpr(Body),nl, print(pred_res(X,PredRes)),nl ; true),
4343 b_enumerate:b_tighter_enumerate_values(TypedVals,WF), % not necessary ?? as X should get enumerated
4344 Res=PredRes,
4345 copy_wf_finish(WF,CWF).
4346 closure_membership_wf(X,Par,Types,Body,Res,WF) :- %print(delay(X,Body,Res)),nl,
4347 when( (ground(X);nonvar(Res)), %%
4348 % used to be ground(X), % with (ground(X);nonvar(Res)), test 292 failed {x,t|t : BOOL & (x : POW(1024 .. 1025) & bool(x : POW(NATURAL1)) = t)} = {{} |-> TRUE,{1024} |-> TRUE,{1024,1025} |-> TRUE,{1025} |-> TRUE} and test 1088 failed
4349 closure_membership_ground_wf(X,closure(Par,Types,Body),Res,WF)).
4350
4351 closure_membership_ground_wf(X,CS,Res,WF) :- nonvar(Res),!,
4352 % this optimization is checked in test 1452
4353 (Res==pred_true -> element_of_custom_set_wf(X,CS,WF) ; not_element_of_custom_set_wf(X,CS,WF)).
4354 closure_membership_ground_wf(X,CS,Res,WF) :-
4355 % print(uncovered_closure(CS,X,Res)),nl,
4356 % to ensure that we leave no choice point behind we have to force full evaluation of element/not_element calls:
4357 % hence we do not call element_of_custom_set_wf or not_element_of_custom_set_wf below !!
4358 kernel_waitflags:get_idle_wait_flag(closure_membership_ground_wf,WF,LWF), % enable other triggered co-routines to fire first; some maybe much more efficient to deal with than closure expansion; important for test 1146
4359 %term_variables(CS,Vars),print(closure_membership_ground_wf_aux(LWF,vars(Vars),CS)),nl,
4360 ground_value_check(CS,CSGr),
4361 %when((nonvar(LWF),(nonvar(CSGr);nonvar(Res))),closure_membership_ground_wf_aux(X,CS,Res)).
4362 block_closure_membership_ground_wf_aux(X,CS,Res,CSGr,LWF). % Note: wrong block in commit 332cb17487017d819e9140427b1017a3045b3685 caused problem for test 1162
4363
4364 :- block block_closure_membership_ground_wf_aux(?,?,?,?,-),
4365 block_closure_membership_ground_wf_aux(?,?,-,-,?).
4366 block_closure_membership_ground_wf_aux(X,CS,Res, _,_) :-
4367 ? closure_membership_ground_wf_aux(X,CS,Res).
4368
4369 % X & CS are ground or Res is known
4370 closure_membership_ground_wf_aux(X,CS,Res) :- Res==pred_true,!,
4371 element_of_custom_set(X,CS).
4372 closure_membership_ground_wf_aux(X,CS,Res) :- Res==pred_false,!,
4373 not_element_of_custom_set(X,CS).
4374 closure_membership_ground_wf_aux(X,CS,Res) :-
4375 % we know that X is a ground value and CS is ground: we can determine completely whether X is element of CS or not
4376 ? if(element_of_custom_set(X,CS),Res=pred_true, Res=pred_false).
4377 /* used to be:
4378 (Res \== pred_false, element_of_custom_set(X,CS), Res=pred_true
4379 ;
4380 Res \== pred_true, not_element_of_custom_set(X,CS), Res=pred_false)).
4381 */
4382
4383 %member_closure_membership(value(Set),X,Res) :- !, kernel_objects:membership_test(Set,X,Res).
4384 %member_closure_membership(cartesian_product(b(value(A),_,_),b(value(B),_,_)),X,Res) :- !,
4385 % kernel_equality:cartesian_pair_test_wf(X,A,B,Res,WF).
4386 %member_closure_membership(pow_subset(b(value(VAL),_,_)),X,Res) :-
4387 % kernel_equality:subset_test(X,VAL,Res,WF). % WE NEED WF
4388
4389 %:- block in_interval_test(?,-,?,?), in_interval_test(?,?,-,?).
4390 %in_interval_test(X,Low,Up,MemRes) :-
4391 % ((X >= Low, X=< Up) /* inf should not appear */
4392 % -> MemRes=pred_true ; MemRes=pred_false).
4393
4394
4395
4396 :- use_module(kernel_objects,[element_of_global_set/2,element_of_global_set_wf/3]).
4397 element_of_custom_set_wf(X,CS,WF) :- %print(element_of_custom_set_wf2(CS,X,WF)),nl,
4398 ? element_of_custom_set_wf2(CS,X,WF). %, print(check_ok(X)),nl.
4399
4400 element_of_custom_set_wf2(node(A,B,C,D,E),X,WF) :-
4401 add_internal_error('Unwrapped avl_set: ',element_of_custom_set_wf2(node(A,B,C,D,E),X,WF)),fail.
4402 element_of_custom_set_wf2(global_set(GS),X,WF) :- element_of_global_set_wf(X,GS,WF).
4403 element_of_custom_set_wf2(freetype(ID),X,WF) :-
4404 (is_maximal_freetype(ID) -> true
4405 ; add_internal_error('Uncovered case: ',element_of_custom_set_wf2(freetype(ID),X,WF))
4406 ). % we assume freetypes to be maximal !
4407 ?element_of_custom_set_wf2(avl_set(AVL),X,WF) :- element_of_avl_set_wf(AVL,X,WF).
4408 element_of_custom_set_wf2(closure(Parameters,PT,Cond),X,WF) :-
4409 ? element_of_closure(X,Parameters,PT,Cond,WF).
4410
4411 ?element_of_avl_set_wf(node(Y,_,_,empty,empty),X,WF) :- !,
4412 ? kernel_objects:equal_object_wf(X,Y,element_of_custom_set_wf2,WF).
4413 element_of_avl_set_wf(AVL,X,_WF) :- ground_value(X),!, safe_avl_member(X,AVL). %safe_avl_member_ground(X,AVL).
4414 element_of_avl_set_wf(AVL,X,WF) :-
4415 avl_approximate_size(AVL,10,ApproxSize),
4416 element_of_avl_set_wf(AVL,ApproxSize,X,WF).
4417
4418 :- use_module(clpfd_tables).
4419
4420 element_of_avl_set_wf(AVL,ApproxSize,X,WF) :- ApproxSize < 100,
4421 preferences:preference(use_clpfd_solver,true),
4422 (var(X) -> true ; X = (X1,_X2) -> (ground_value(X1) -> ApproxSize < 10 ; true) ; X=rec(_)),% check if worthwhile to attempt table treatment
4423 can_translate_avl_to_table(AVL,SkeletonType),
4424 %print(skel_for_table(ApproxSize,SkeletonType)),nl,
4425 !,
4426 check_element_of_avl_with_table(X,SkeletonType,AVL,WF).
4427 element_of_avl_set_wf(AVL,ApproxSize,X,WF) :-
4428 propagate_avl_element_information(X,AVL,ApproxSize,WF), %translate:translate_bvalue(avl_set(AVL),SS),
4429 get_bounded_wait_flag(ApproxSize,element_of_avl(X),WF,WF1),
4430 %print(el_avl(X,Size)),nl,
4431 element_of_avl_set_wf3(X,AVL,ApproxSize,WF1,WF).
4432
4433
4434 % compute an approximate size (small sets are computed exactly)
4435 avl_approximate_size(AVL,Size) :- avl_approximate_size(AVL,10,Size).
4436
4437 avl_approximate_size(AVL,HeightBound,Size) :- var(AVL),!,
4438 add_internal_error('AVL Set is variable: ', avl_approximate_size(AVL,HeightBound,Size)),
4439 Size=1000000.
4440 avl_approximate_size(AVL,HeightBound,Size) :- % when the AVL gets too large; not so important that we have a precise estimation anyway
4441 % so: save some time and just compute height
4442 avl_height(AVL,Height),
4443 (Height>HeightBound -> Size is integer(2**Height-1) %,print(avl_aprox(Height,Size)),nl
4444 ; avl_size(AVL,Size)).
4445
4446 :- block element_of_avl_set_wf3(-,?,?,-,?).
4447 ?element_of_avl_set_wf3(X,AVL,_ApproxSize,WF1,_WF) :- nonvar(WF1), !, safe_avl_member(X,AVL).
4448 % TO DO: if randomise_enumeration_order is true then choose elements in random order
4449 :- if(environ(prob_data_validation_mode,xxxtrue)). % currently disabled due to bug related to 14082013/435_002.mch TO DO: investigate
4450 element_of_avl_set_wf3((X,Y),AVL,ApproxSize,WF1,WF) :- !,
4451 %% ((var(WF1), \+ ground(X)) -> print(avl_relation_check(X,Y)),nl, %%
4452 %% copy_term((X,Y),Copy), findall(Copy,safe_avl_member(Copy,AVL),Cs), print(Cs),nl, Cs \=[] %% check that at least one element exists
4453 %% ; true),
4454 couple_element_of_avl_set_wf(X,Y,AVL,ApproxSize,WF1,WF).
4455 :- else.
4456 element_of_avl_set_wf3((X,Y),AVL,ApproxSize,WF1,WF) :- !,
4457 %print(avl_relation(X,Y)),nl, %%
4458 ground_value_check(X,GrX),
4459 block_couple_element_of_avl_set_grX_wf1(X,Y,AVL,ApproxSize,GrX,WF1,WF).
4460 %when((nonvar(WF1) ; ground(X)), couple_element_of_avl_set(X,Y,AVL,GrX,WF1,WF)).
4461 :- endif.
4462 element_of_avl_set_wf3(X,AVL,_ApproxSize,WF1,_WF) :-
4463 %print(avl_mem(X,Size,WF1)),portray_custom_explicit_set(avl_set(AVL)),
4464 when((nonvar(WF1);ground(X)),
4465 %%( (var(WF1) -> true ; print(selecting(X,Size)), %translate:print_value_variable(X),portray_custom_explicit_set(avl_set(AVL))), %%
4466 safe_avl_member(X,AVL) %(var(WF1) -> safe_avl_member_ground(X,AVL) ; safe_avl_member(X,AVL))
4467 %% ,(var(WF1) -> true ; print(chosen(X,Size)),nl) )%%
4468 ).
4469
4470 :- if(environ(prob_data_validation_mode,true)).
4471 :- public couple_element_of_avl_set_wf/6. % used in conditional if above
4472 :- block couple_element_of_avl_set_wf(-,?,?,?,-,?).
4473 couple_element_of_avl_set_wf(X,Y,AVL,ApproxSize,WF1,WF) :-
4474 ground_value_check(X,GrX),
4475 ((nonvar(WF1);nonvar(GrX)) -> couple_element_of_avl_set(X,Y,AVL,GrX,WF1,WF)
4476 %; true -> when((nonvar(WF1) ; ground(X)), couple_element_of_avl_set(X,Y,AVL,WF1,WF))
4477 ; nonvar(X),X=(X1,X2),ground(X1) -> triple_element_of_avl_set(X1,X2,Y,AVL,WF)
4478 ; nonvar(X),X=(X1,X2) ->
4479 %print_term_summary(avl_member_blocking(X,Y,AVL)),nl,
4480 avl_member_blocking((X,Y),AVL),
4481 (ground(Y),ground(X1) -> safe_avl_member_pair(X,Y,AVL)
4482 ; when(ground(X1),(\+ ground(X2) -> triple_element_of_avl_set(X1,X2,Y,AVL,WF) ; true % avl_member_blocking will have done its work
4483 )),
4484 block_couple_element_of_avl_set(X,Y,AVL,WF1,WF)
4485 )
4486 ; %when((nonvar(WF1) ; ground(X)), couple_element_of_avl_set(X,Y,AVL,WF1,WF))
4487 block_couple_element_of_avl_set_grX_wf1(X,Y,AVL,ApproxSize,GrX,WF1,WF)
4488 /* ; (simple_avl_type(AVL)
4489 -> avl_member_blocking((X,Y),AVL) % TO DO: don't call couple_element_of_avl_set ! avoid double traversal !!
4490 ; true),
4491 block_couple_element_of_avl_set_grX_wf1(X,Y,AVL,GrX,WF1,WF) */
4492 ).
4493
4494 :- block block_couple_element_of_avl_set(?,?,?,-,?).
4495 block_couple_element_of_avl_set(X,Y,_AVL,_WF1,_WF) :- ground(X),ground(Y),!.
4496 block_couple_element_of_avl_set(X,Y,AVL,_WF1,_WF) :- safe_avl_member_pair(X,Y,AVL).
4497
4498 triple_element_of_avl_set(X1,X2,Y,AVLRelation,WF) :- % X1 must be ground
4499 copy_term((X2,Y),(CX2,CY)),
4500 findall((CX2,CY),safe_avl_member_pair((X1,CX2),CY,AVLRelation),Images),
4501 %print(images(X,Y,Images)),nl,
4502 Images \= [],
4503 construct_avl_from_lists(Images,AVL),
4504 %print(AVL),
4505 element_of_custom_set_wf2(AVL,(X2,Y),WF). % will set up waitflag if necessary
4506 :- endif.
4507
4508 % ---------------------------------------------------
4509
4510 test_avl_set(node(((int(2),int(3)),int(6)),true,0,node(((int(1),int(2)),int(2)),true,0,empty,empty),node(((int(3),int(4)),int(12)),true,0,empty,empty))).
4511
4512 %simple_avl_type(node(K,_,_,_,_)) :- simple_value(K). % we can index directly on AVL, without having to normalise inner values
4513 % in particular, we can apply avl_member_blocking
4514
4515 :- assert_must_succeed(( custom_explicit_sets:test_avl_set(A), custom_explicit_sets:avl_member_blocking(((X,Y),Z),A), X=int(2), Y==int(3),Z==int(6) )).
4516 :- assert_must_succeed(( custom_explicit_sets:test_avl_set(A), custom_explicit_sets:avl_member_blocking(((X,Y),Z),A), X=int(3), Y==int(4),Z==int(12) )).
4517 :- assert_must_succeed(( custom_explicit_sets:test_avl_set(A), custom_explicit_sets:avl_member_blocking(((X,Y),Z),A), X=int(1), Y==int(2),Z==int(2) )).
4518 :- assert_must_fail(( custom_explicit_sets:test_avl_set(A), custom_explicit_sets:avl_member_blocking(((X,_Y),_Z),A), X=int(5) )).
4519 % a blocking version of avl_member; will not instantiate the element; just prune
4520
4521 avl_member_blocking(Key, AVL) :- AVL=node(K,_,_,L,R),
4522 %avl_height(AVL,Height),
4523 avl_member_blocking4(Key,K,L,R).
4524
4525 avl_member_blocking4(Key,Kavl,L,R) :- L=empty,R=empty,!,
4526 Key=Kavl. % we could do equal_object
4527 avl_member_blocking4(Key,Kavl,L,R) :-
4528 match_possible(Key,Kavl,MatchPossible), % check if in principle a match could occur
4529 %(MatchPossible==pred_false -> avl_height(L,Height),print('#'(Height)) ; true),
4530 (Kavl=(_,_) ->
4531 (avl_min(R,Knext) -> true ; dif(O,>), Knext=no_match, %print(n(MatchPossible)),
4532 force_comp(MatchPossible,O,'<')),
4533 (avl_max(L,Kprev) -> true ; dif(O,<), Kprev=no_match, %print(p(MatchPossible)),
4534 force_comp(MatchPossible,O,'>'))
4535 ; Knext = no_match, Kprev = no_match
4536 ),
4537 %print(avl_mem(Key,K,O, Kprev,Knext)),nl,
4538 (nonvar(O) -> true
4539 /* ; (MatchPossible==pred_false, avl_height(L,Height), Height < 8,
4540 copy_term(Key,CKey), \+ safe_avl_member(CKey,L), \+ safe_avl_member(CKey,R))
4541 -> print(cannot_match(Key)),nl,fail */
4542 ; compare_blocking(O, Key, Kavl, Kprev,Knext)),
4543 avl_member_blocking_aux(O, Key, Kavl, L, R).
4544
4545 %force_comp(V,_,_) :- var(V),!.
4546 :- block force_comp(-,?,?).
4547 force_comp(pred_true,_,_).
4548 force_comp(pred_false,R,R).
4549
4550 :- block avl_member_blocking_aux(-,?,?,?,?).
4551 %avl_member_blocking_aux(O, Key, K, L, R) :- print(avl_member_blocking_aux(O, Key, K, L, R)),nl,fail.
4552 avl_member_blocking_aux(<, Key, _K, AVL, _) :- avl_member_blocking(Key, AVL).
4553 avl_member_blocking_aux(=, Key, Key, _L, _R). % we could use equal_object
4554 avl_member_blocking_aux(>, Key, _K, _, AVL) :- avl_member_blocking(Key, AVL).
4555
4556 % a blocking version of compare
4557 compare_blocking(Res,A,Kavl, Kprev, Knext) :- block_compare(A,Kavl,Res, Kprev, Knext).
4558
4559 :- block block_compare(-,?,?,?,?), block_compare(?,-,?,?,?).
4560 block_compare((A,B),Kavl,Res, Kprev, Knext) :- !,
4561 (Kavl=(RA,RB) ->
4562 match_key(Kprev,RA,PA,PB),
4563 match_key(Knext,RA,NA,NB),
4564 block_compare(A,RA,ACRes,PA,NA),
4565 block_compare_aux(ACRes,B,RB,Res,PB,NB)
4566 ; add_internal_error('Illegal type: ',block_compare((A,B),Kavl,Res, Kprev, Knext)),fail).
4567 % TO DO: same for records; but currently not used anyway
4568 block_compare(int(A),int(B),Res,_,_) :- !, block_compare_atomic(A,B,Res).
4569 block_compare(pred_false,B,Res,_,_) :- !, block_compare_atomic(pred_false,B,Res).
4570 block_compare(pred_true,B,Res,_,_) :- !, block_compare_atomic(pred_true,B,Res).
4571 block_compare(string(A),string(B),Res,_,_) :- !, block_compare_atomic(A,B,Res).
4572 block_compare(fd(A,T),fd(B,T),Res,_,_) :- !, block_compare_atomic(A,B,Res).
4573 block_compare(avl_set(A),Kavl,Res,_,_) :- !,
4574 convert_to_avl_inside_set(avl_set(A),ConvertedA),compare(Res,ConvertedA,Kavl).
4575 block_compare([],[],Res,_,_) :- !, Res = '='.
4576 block_compare([],_,Res,_,_) :- !, Res = '<'.
4577 block_compare(A,Kavl,Res,_,_) :-
4578 % does deal with various representations of sets !! closure/global_set/...
4579 when(ground(A),
4580 (convert_to_avl_inside_set(A,ConvertedA),compare(Res,ConvertedA,Kavl))).
4581
4582 match_key((KeyA,KeyB),Key,ResA,ResB) :- !, ResA=KeyA,
4583 (Key==KeyA -> ResB=KeyB ; ResB = no_match).
4584 match_key(_,_,no_match,no_match).
4585
4586 :- block block_compare_atomic(-,?,?), block_compare_atomic(?,-,?).
4587 block_compare_atomic(A,B,Res) :- compare(Res,A,B).
4588
4589 :- block block_compare_aux(-,?,?,?, ?,?).
4590 block_compare_aux(ACRes,B,D,Res, Kprev,Knext) :-
4591 (ACRes='<' -> Res = '<'
4592 ; ACRes = '>' -> Res = '>'
4593 ; Kprev=no_match, Knext=no_match -> %print(forcing(B,D)),nl,
4594 Res = '=' % we cannot match neither previous nor next key: force match
4595 ; block_compare(B,D,Res,Kprev,Knext)). % TO DO: check with prev & next value: if no match possible force Res='='
4596
4597 % check if a match is possible between two terms
4598 :- block match_possible(-,?,?), match_possible(?,-,?).
4599 match_possible([],[],Possible) :- !, Possible=pred_true.
4600 match_possible([],avl_set(_),Possible) :- !, Possible=pred_false.
4601 match_possible(avl_set(_),[],Possible) :- !, Possible=pred_false.
4602 match_possible(int(A),int(B),Possible) :- !, match_possible_atomic(A,B,Possible).
4603 match_possible(fd(A,T),fd(B,T),Possible) :- !, match_possible_atomic(A,B,Possible).
4604 match_possible(string(A),string(B),Possible) :- !, match_possible_atomic(A,B,Possible).
4605 match_possible((A1,A2),(B1,B2),Possible) :- !, match_possible(A1,B1,P1),
4606 match_possible(A2,B2,P2), kernel_equality:conjoin_test(P1,P2,Possible,_WF). %% WF <--- TO DO
4607 match_possible(_,_,pred_true).
4608
4609 :- block match_possible_atomic(-,?,?), match_possible_atomic(?,-,?).
4610 match_possible_atomic(A,B,Res) :- (A==B -> Res=pred_true ; Res=pred_false).
4611
4612 % --------------------------------------------
4613
4614 :- block block_couple_element_of_avl_set_grX_wf1(?, - ,?,?,-,-,?).
4615 block_couple_element_of_avl_set_grX_wf1(X,Y,AVL,ApproxSize,GrX,WF1,WF) :- %print(inverse1(ApproxSize,GrX,WF1,Y)),nl,
4616 var(GrX), var(WF1),
4617 !,
4618 %print(inverse(ApproxSize,GrX,WF1,Y)),nl,
4619 % we know the result Y but not yet fully the input value X
4620 (ApproxSize < 129 % TO DO: improve this; unify with inverse_apply_ok(Y,X,AVL,ApproxSize) ?
4621 -> ground_value_check(Y,GrY) % wait until Y is fully known
4622 ; (preference(solver_strength,SS), ApproxSize < 129+SS)
4623 -> ground_value_check(Y,GrY)
4624 % TO DO: we could look at avl_min and avl_max and estimate spread of range keys
4625 ; perfmessage(no_inverse_avl_lookup(ApproxSize,Y)) % do not bind GrY; we wait until GrX or WF1 is bound
4626 ),
4627 block_couple_element_of_avl_set_grX_grY_wf1(X,Y,AVL,ApproxSize,GrX,GrY,WF1,WF).
4628 block_couple_element_of_avl_set_grX_wf1(X,Y,AVL,_ApproxSize,GrX,WF1,WF) :-
4629 ? couple_element_of_avl_set(X,Y,AVL,GrX,WF1,WF).
4630
4631 :- block block_couple_element_of_avl_set_grX_grY_wf1(?,?,?,?, -,-,-,?).
4632 block_couple_element_of_avl_set_grX_grY_wf1(X,Y,AVL,_ApproxSize, GrX,_GrY,WF1,WF) :-
4633 var(GrX), var(WF1), % i.e., Y is known
4634 % we know the result Y but not yet fully the input value X
4635 %inverse_apply_ok(Y,X,AVL,ApproxSize),
4636 % print(try_invert_y(Y,ApproxSize,X,GrX)),nl,
4637 %avl:portray_avl(AVL),nl,
4638 !,
4639 inverse_get_possible_values(X,Y,AVL,Res),
4640 %print(possible_values),nl,translate:print_bvalue(Res),nl,
4641 Res = avl_set(InvAVL),
4642 element_of_avl_set_wf(InvAVL,X,WF).
4643 %couple_element_of_avl_set(X,Y,AVL,GrX,1,WF).
4644 block_couple_element_of_avl_set_grX_grY_wf1(X,Y,AVL,_ApproxSize,GrX,_GrY,WF1,WF) :-
4645 ? couple_element_of_avl_set(X,Y,AVL,GrX,WF1,WF).
4646
4647
4648 % special treatment for relations: if the first component is known: then we can check how many images there are
4649 couple_element_of_avl_set(X,Y,AVL,GrX,WF1,_WF) :-
4650 %print_term_summary(couple_element_of_avl_set(X,Y,AVL,WF1,_WF)),nl,
4651 %hashing:my_term_hash((X,Y,AVL),Hash), %print(hash(Hash)),nl,
4652 %(Hash=797296156541305712 -> trace ; true), %1008421951878593614
4653 ? nonvar(WF1), var(GrX), %\+ground(X),
4654 ? !, %nl,print_term_summary(couple_element_of_avl_set_nonground(X,Y,AVL,WF1,_WF)),nl,
4655 ? safe_avl_member_default((X,Y),AVL).
4656 couple_element_of_avl_set(X,Y,AVLRelation,_GrX,_,WF) :- % X must be ground
4657 copy_term(Y,CY),
4658 findall(CY,avl_member_pair_arg1_ground(X,CY,AVLRelation),Images), % should we use Y instead of CY
4659 %print(images(X,Y,Images)),nl,
4660 Images \= [],
4661 construct_avl_from_lists(Images,AVL),
4662 %print(AVL),
4663 element_of_custom_set_wf2(AVL,Y,WF). % will set up waitflag if necessary
4664
4665
4666 % set Res -> pred_true or pred_false if membership can be decided early
4667 % interval closures already dealt with by closure_membership
4668 % maximal sets are also already dealt with by membership_custom_set
4669 reify_avl_membership(AVL,Element,Res,FullReification) :-
4670 is_avl_simple_set(AVL,Type),
4671 preferences:preference(use_clpfd_solver,true), % to do: require maybe only for integer type !?
4672 \+ ground_value(Element),
4673 !,
4674 reify_avl_mem2(Type,Element,AVL,Res,FullReification).
4675 reify_avl_membership(_,_,_,false).
4676
4677
4678 is_avl_simple_set(node(El,_True,_,_,_),Type) :- simple_type(El,Type).
4679 simple_type(int(_),integer).
4680 simple_type(fd(_,GS),global(GS)).
4681
4682
4683 :- use_module(clpfd_interface,[try_post_constraint/1, clpfd_reify_inlist/3]).
4684 reify_avl_mem2(integer,int(El),AVL,Res,FullReification) :-
4685 avl_min(AVL,int(Min)), avl_max(AVL,int(Max)),
4686 %print(post(El,Min,Max)),nl,
4687 (reify_integer_avl_mem(AVL,Min,Max)
4688 -> clpfd_interface:try_post_constraint(clpfd:'#<=>'( (El in Min..Max) , FDRes)),
4689 propagate_not_membership(FDRes,Res,int(El,Min,Max)),
4690 FullReification=false
4691 ; avl_domain(AVL,R),project_avl_domain_on_fd(R,FDList),
4692 clpfd_interface:clpfd_reify_inlist(El,FDList,FDRes),
4693 %print(clpfd_reify_int_inlist(El,FDList,FDRes)),nl,
4694 propagate_fd_membership(FDRes,Res,inlist(El,FDList)),
4695 FullReification=true
4696 ).
4697 % this could also be enabled with CLPFD = FALSE ?? no overflows are possible
4698 reify_avl_mem2(global(GS),fd(El,GS),AVL,Res,true) :- % print(reify_avl_mem2(global(GS),fd(El,GS),AVL,Res)),nl,nl,
4699 avl_domain(AVL,R),project_avl_domain_on_fd(R,FDList),
4700 b_global_sets:b_get_fd_type_bounds(GS,Low,Up),
4701 (is_full_fdlist(FDList,Low,Up)
4702 -> % print(full_list(FDList,Low,Up)),nl,nl,trace,
4703 Res=pred_true % all the values are in the list; it must be a member
4704 % normally this should also be detected by clpfd_reify_inlist, unless no constraint was set up for El
4705 % it seems to have an effect for test 426: probcli examples/EventBPrologPackages/SSF/Bepi_Soton/M1_mch.eventb -cbc all -strict -p CLPFD TRUE -p SMT TRUE -strict -p STRICT_RAISE_WARNINGS TRUE
4706 ; %print(reify(El,FDList,FDRes)),nl,
4707 clpfd_interface:clpfd_reify_inlist(El,FDList,FDRes),
4708 % print(clpfd_reify_inlist(El,FDList,FDRes)),nl,trace,
4709 propagate_fd_membership(FDRes,Res,inlist(El,FDList))).
4710 %reify_avl_mem2(global(GS),fd(El,GS),AVL,Res) :-
4711 % avl_min(AVL,fd(Min,GS)), avl_max(AVL,fd(Max,GS)),
4712 % clpfd_interface:try_post_constraint(clpfd:'#<=>'( (El in Min..Max) , FDRes)),
4713 % propagate_not_membership(FDRes,Res,fd(El,GS,Min,Max)).
4714
4715 % assumes list is sorted
4716 is_full_fdlist([],Low,Up) :- Low>Up.
4717 is_full_fdlist([Low|T],Low,Up) :- L1 is Low+1, is_full_fdlist(T,L1,Up).
4718
4719 % check if avl small enough to call clpfd_reify_inlist
4720 reify_integer_avl_mem(_AVL,Min,Max) :- MaxSizeM1 is Max-Min, MaxSizeM1 =< 20,!.
4721 reify_integer_avl_mem(AVL,_Min,_Max) :- avl_height_less_than(AVL,5).
4722
4723
4724
4725 project_avl_domain_on_fd([],[]).
4726 project_avl_domain_on_fd([H|T],[PH|PT]) :- project_avl_domain(H,PH), project_avl_domain_on_fd(T,PT).
4727 project_avl_domain(int(X),X).
4728 project_avl_domain(fd(X,_),X).
4729
4730
4731 :- block propagate_fd_membership(-,?,?).
4732 % if we make it propagate_fd_membership(-,-?) Bosch examples becomes much slower ?
4733 % Indeed: membership_custom_set will already force membership or non-membership !
4734 %propagate_fd_membership(X,M,Info) :- var(X),!, print(propagate_fd(X,M,Info)),nl, (M=pred_true ->X=1 ; X=0).
4735 propagate_fd_membership(1,pred_true,_Info).
4736 propagate_fd_membership(0,pred_false,_Info).
4737
4738 :- block propagate_not_membership(-,?,?).
4739 propagate_not_membership(1,_,_). % there could be elements in the interval which are not in the set
4740 propagate_not_membership(0,Res,_Info) :- %print(not_mem(_Info)),nl,
4741 Res=pred_false.
4742
4743 % -----------------
4744
4745 % fails if not possible to quickly compute approximate size
4746 quick_custom_explicit_set_approximate_size(V,_) :- var(V),!,fail.
4747 quick_custom_explicit_set_approximate_size(avl_set(AVL),Size) :- !,
4748 quick_avl_approximate_size(AVL,Size).
4749 quick_custom_explicit_set_approximate_size(CS,Size) :-
4750 card_for_specific_custom_set(CS,Size,Code),
4751 on_enumeration_warning(call(Code),fail).
4752
4753 :- use_module(clpfd_lists,[try_get_fd_value_list/4, get_fd_value/3, in_fd_value_list_wf/4]).
4754 % a membership propagation, but only done if it can be done quickly
4755
4756
4757 % quick_propagation_element_information(Set, Element, WF, PossiblyCompiledSet)
4758 % use last element for next iteration if you call quick_propagation_element_information in a loop
4759 :- block quick_propagation_element_information(-,?,?,?).
4760 quick_propagation_element_information(Set,_El,_,R) :- % print(quick_prop(Set,_El)),nl,
4761 preferences:preference(use_clpfd_solver,false),
4762 !, R=Set.
4763 quick_propagation_element_information(avl_set(AVL),Element,WF,NewSet) :- !,
4764 quick_avl_approximate_size(AVL,Size),
4765 NewSet=avl_set_with_size(AVL,Size),
4766 propagate_avl_element_information(Element,AVL,Size,WF).
4767 quick_propagation_element_information(avl_set_with_size(AVL,Size),Element,WF,NewSet) :- !,
4768 NewSet = avl_set_with_size(AVL,Size),
4769 propagate_avl_element_information(Element,AVL,Size,WF).
4770 quick_propagation_element_information(closure(P,T,B),Element,WF,NewSet) :- !,
4771 NewSet = closure(P,T,B),
4772 element_of_closure(Element,P,T,B,WF).
4773 quick_propagation_element_information(fd_value_list(FDList,GroundList,Type),El,WF,NewSet) :- !,
4774 NewSet = fd_value_list(FDList,GroundList,Type),
4775 get_fd_value(Type,El,ElFD),
4776 in_fd_value_list_wf(GroundList,ElFD,FDList,WF).
4777 quick_propagation_element_information(Set,El,WF,NewSet) :-
4778 try_get_fd_value_list(Set,Type,FDList,GroundList),!,
4779 FDList \= [], % if list is empty membership fails
4780 % print(get_fd_value_list(Type,FDList)),nl,
4781 NewSet = fd_value_list(FDList,GroundList,Type),
4782 % clpfd_inlist requires list of integers as second argument
4783 get_fd_value(Type,El,ElFD),
4784 % We could apply filter_non_matching_elements here
4785 in_fd_value_list_wf(GroundList,ElFD,FDList,WF).
4786 %quick_propagation_element_information(Set,El,_) :- print(cannot_prop(Set,El)),nl,fail.
4787 quick_propagation_element_information(Set,_,_,Set).
4788
4789 % -----------------
4790
4791 % infer information about an element of an AVL set
4792 propagate_avl_element_information(Element,AVL,Size,WF) :- % print(prop_avl(Size)),nl,
4793 (preferences:preference(use_clpfd_solver,true)
4794 -> (Size<100 -> %30 which magic constant to use here; use larger value in SMT mode ?
4795 % print(propagate_avl_element_information_small(Element,AVL,Size)),nl,
4796 propagate_avl_element_information_small(Element,AVL,WF)
4797 ; is_avl_fd_index_set(AVL,Type) ->
4798 %print(avl_simple_type(Type,Size,Element)),
4799 propagate_avl_element_information_large(Type,Element,AVL),
4800 (Size < 4000, nonvar(Element), Element = (_,_) % another magic constant
4801 -> Prio is Size // 60,
4802 get_wait_flag(Prio,propagate_avl_element_information(Element),WF,LWF),
4803 propagate_avl_el_large_block(Element,AVL,WF,LWF) % will do precise propagation
4804 ; true)
4805 ; true)
4806 ; true).
4807 % TO DO: we could call in_nat_range_wf; this way it would also work in non-CLPFD mode
4808
4809 :- block propagate_avl_el_large_block(?,?,?,-).
4810 propagate_avl_el_large_block((A,B),_,_,_) :-
4811 ? (ground(A); ground_value(B)), % in first: case we will apply AVL set ; in second case probably no benefit as propagate_avl_element_information_large already propagated first element
4812 !.
4813 propagate_avl_el_large_block(Element,AVL,WF,_LWF) :-
4814 % print(propagating_large_avl(_LWF,Element)),nl,
4815 % TO DO: maybe look if we should not use clpfd_list, but only upper & lower bound
4816 propagate_avl_element_information_small(Element,AVL,WF). % will do precise propagation
4817
4818 :- use_module(clpfd_lists,[avl_fd_value_check/4]).
4819 propagate_avl_element_information_small(Element,AVL,WF) :- !,
4820 avl_fd_value_check(AVL,Element,WF,_FullyChecked).
4821
4822 propagate_avl_element_information_large(Type,El,AVL) :-
4823 avl_min(AVL,Min), avl_max(AVL,Max),
4824 % if Size small enough and smaller than Max-Min we call clpfd_inlist on domain
4825 %print(couple_prj1_in_range(Type,El,Min,Max)),nl,
4826 couple_prj1_in_range(Type,El,Min,Max).
4827
4828 couple_prj1_in_range(integer,int(El),int(Min),int(Max)) :- clpfd_interface:clpfd_inrange(El,Min,Max).
4829 couple_prj1_in_range(global(GS),fd(El,GS),fd(Min,GS),fd(Max,GS)) :- clpfd_interface:clpfd_inrange(El,Min,Max).
4830 couple_prj1_in_range(couple_prj1(T),(El,_),(Min,_),(Max,_)) :- couple_prj1_in_range(T,El,Min,Max).
4831 couple_prj1_in_range(rec_first_field(Name,T),rec([field(Name,El)|TF]),
4832 rec([field(Name,Min)|TMin]),rec([field(Name,Max)|_])) :-
4833 (var(TF)
4834 -> copy_field_names(TMin,TF) % if Fields not yet instantiated: copy over all fields
4835 ; true),
4836 couple_prj1_in_range(T,El,Min,Max).
4837
4838 copy_field_names([],[]).
4839 copy_field_names([field(N,_)|T],[field(N,_)|CT]) :- copy_field_names(T,CT).
4840
4841 % check if the first component of the AVL elements of a type such that we can propagate FD information
4842 is_avl_fd_index_set(node(El,_True,_,_,_),Type) :-
4843 simple_index_type(El,Type).
4844 simple_index_type((El,_),couple_prj1(T)) :- simple_index_type(El,T).
4845 simple_index_type(int(_),integer).
4846 simple_index_type(fd(_,GS),global(GS)).
4847 simple_index_type(rec(Fields),rec_first_field(Name,T)) :- nonvar(Fields),
4848 Fields = [field(Name,El)|_],
4849 simple_index_type(El,T).
4850 %simple_index_type((int(_),_),couple_integer).
4851 %simple_index_type(((int(_),_),_),couple_couple_integer).
4852 %simple_index_type((fd(_,GS),_),couple_global(GS)).
4853
4854
4855 /* avoid instantiating non-normalised with normalised values leading to failure */
4856 :- assert_must_succeed((X=(fd(1,'Name'),fd(2,'Name')), A=node(X,true,0,empty,empty),
4857 custom_explicit_sets:safe_avl_member(X,A) )).
4858
4859 %safe_avl_member(X,_AVL) :- print(enter_avl_member(X)),nl,fail.
4860 ?safe_avl_member(X,AVL) :- var(X), !, my_avl_member(X,AVL).
4861 safe_avl_member((X,Y),AVL) :- !, safe_avl_member_pair(X,Y,AVL).
4862 % TO DO: treat record -> first field = X
4863 safe_avl_member(X,AVL) :- ground_value(X), convert_to_avl_inside_set(X,AX), !, avl_fetch(AX,AVL).
4864 ?safe_avl_member(X,AVL) :- safe_avl_member_default(X,AVL).
4865 %safe_avl_member(X,_AVL) :- print(exit_avl_member(X)),nl,fail.
4866
4867 % a version of safe_avl_member where the first argument is guaranteed to be ground
4868 % somehow using this seems to slow-down evaluation for vesg_Dec12; Caching ??
4869 %safe_avl_member_ground(X,AVL) :-
4870 % convert_to_avl_inside_set(X,AX), !, avl_fetch(AX,AVL).
4871 %safe_avl_member_ground((X,Y),AVL) :- !, avl_member_pair_arg1_ground(X,Y,AVL).
4872 %safe_avl_member_ground(X,AVL) :- safe_avl_member_default(X,AVL).
4873
4874 safe_avl_member_pair(X,Y,AVL) :- ground_value(X),!,
4875 ((ground_value(Y),
4876 convert_to_avl_inside_set((X,Y),AX))
4877 -> avl_fetch(AX,AVL)
4878 ; avl_member_pair_arg1_ground(X,Y,AVL)).
4879 safe_avl_member_pair(X,Y,AVL) :- safe_avl_member_default((X,Y),AVL).
4880
4881 %safe_avl_member_pair_ground(X,Y,AVL) :- convert_to_avl_inside_set((X,Y),AX),!, avl_fetch(AX,AVL).
4882 %safe_avl_member_pair_ground(X,Y,AVL) :- avl_member_pair_arg1_ground(X,Y,AVL).
4883
4884 ?avl_member_pair_arg1_ground(X,Y,AVL) :- convert_to_avl_inside_set(X,AX), !,
4885 %statistics(runtime,_),
4886 ? get_template(Y,RY,ToUnifyAfter),
4887 %print(fetch_pair(AX,RY)),nl,
4888 ? avl_fetch_pair(AX,AVL,RY),
4889 %debug:watch(10,custom_explicit_sets:avl_member((AX,RY),AVL)),
4890 % statistics(runtime,[_,T2]), print(avl_pair_fetch(X,RY,T2)),nl,
4891 unify_after(ToUnifyAfter). %kernel_objects:equal_object(RY,Y).
4892 avl_member_pair_arg1_ground(X,Y,AVL) :- %print_term_summary(convert_to_avl_inside_set_failed(X,Y,AVL)),nl,
4893 safe_avl_member_default((X,Y),AVL).
4894
4895 %safe_avl_member_default(PP,X,AVL) :-
4896 % debug:timer_call(safe_avl_member_default(PP),custom_explicit_sets:safe_avl_member_default1(X,AVL)).
4897 safe_avl_member_default(X,AVL) :- %statistics(runtime,_),
4898 ? get_template(X,Template,ToUnifyAfter),
4899 ? my_avl_member(Template,AVL), % print_bt_message(avl_member_default(Template)),
4900 % statistics(runtime,[_,T2]), print(avl_member(Template,T2)),nl,
4901 ? unify_after(ToUnifyAfter). % kernel_objects:equal_object(Template,X)).
4902
4903 unify_after([]).
4904 ?unify_after([A/B|T]) :- kernel_objects:equal_object(A,B,unify_after),
4905 ? unify_after(T).
4906
4907
4908
4909 get_template(A,R,ToUnifyAfter) :-
4910 (var(A) -> ToUnifyAfter=[A/R]
4911 ; get_template2(A,R,ToUnifyAfter) -> true
4912 ; add_internal_error('Could_not_get_template: ',get_template(A,R,_))).
4913
4914 get_template2((A,B),(TA,TB),ToUnifyAfter) :- get_template(A,TA,ToUnifyAfter1), get_template(B,TB,ToUnifyAfter2),
4915 append(ToUnifyAfter1,ToUnifyAfter2,ToUnifyAfter). % TO DO: use DifferenceLists / DCG
4916 get_template2(int(X),int(X),[]).
4917 get_template2(fd(A,B),fd(A,B),[]).
4918 get_template2([],[],[]).
4919 get_template2(pred_false /* bool_false */,pred_false /* bool_false */,[]).
4920 get_template2(pred_true /* bool_true */,pred_true /* bool_true */,[]).
4921 get_template2([H|T],R,ToUnifyAfter) :-
4922 ((ground_value(H),ground_value(T))
4923 -> convert_to_avl_inside_set([H|T],R),ToUnifyAfter=[]
4924 ; ToUnifyAfter=[[H|T]/R]).
4925 % ; R=avl_set(A), ToUnifyAfter=[[H|T]/avl_set(A)]).
4926 get_template2(closure(P,T,B),R,[]) :- ground((P,T,B)),expand_closure_to_avl(P,T,B,R),!.
4927 get_template2(closure(P,T,B),AVL_OR_EMPTY_OR_GS,[closure(P,T,B)/AVL_OR_EMPTY_OR_GS]). % closure could be empty or an infinite global set ?
4928 %get_template2(closure_x(_,_,_),_AVL_OR_EMPTY).
4929 get_template2(avl_set(A),avl_set(NA),[]) :- convert_to_avl_inside_set(avl_set(A),avl_set(NA)). % do we need to normalise here ??
4930 get_template2(string(X),string(X),[]).
4931 get_template2(term(X),term(X),[]).
4932 get_template2(freetype(X),R,[]) :- convert_to_avl_inside_set(freetype(X),R).
4933 get_template2(rec(Fields),rec(TFields),ToUnifyAfter) :- get_fields_template(Fields,TFields,ToUnifyAfter).
4934 get_template2(freeval(ID,Case,Value),freeval(ID,Case,TValue),ToUnifyAfter) :- get_template(Value,TValue,ToUnifyAfter).
4935 get_template2(global_set(GS),R,[]) :- convert_to_avl_inside_set(global_set(GS),R).
4936
4937
4938 get_fields_template(A,R,[rec(A)/rec(R)]) :- var(A),!.
4939 get_fields_template([],[],ToUnifyAfter) :- !, ToUnifyAfter=[].
4940 get_fields_template([field(Name,Val)|T],[field(Name,TVal)|TT],ToUnifyAfter) :- nonvar(Name),!,
4941 get_template(Val,TVal,ToUnifyAfter1),
4942 get_fields_template(T,TT,ToUnifyAfter2), append(ToUnifyAfter1,ToUnifyAfter2,ToUnifyAfter).
4943 get_fields_template(A,R,[rec(A)/rec(R)]).
4944
4945
4946 % succeed if we can decide membership of an avl_set on the spot
4947 quick_test_avl_membership(AVL,X,Res) :-
4948 element_can_be_added_or_removed_to_avl(X),
4949 convert_to_avl_inside_set(X,AX),
4950 (avl_fetch(AX,AVL) -> Res=pred_true ; Res=pred_false).
4951
4952 % ---------------------
4953
4954 % a dispatch predicate
4955 my_avl_member(Key,AVL) :-
4956 ? (preferences:preference(randomise_enumeration_order,true)
4957 ? -> random_avl_member(Key,AVL) ; avl_member_opt(Key,AVL)).
4958 :- use_module(library(random),[random/3]).
4959 random_avl_member(Key,AVL) :- avl_height(AVL,Height), H1 is Height+1, random_avl_member(Key,H1,AVL).
4960 % TO DO: make more intelligent; this is not really a very uniform way of randomly enumerating an AVL set (e.g., Key never occurs between L and R)
4961 random_avl_member(Key, H, node(K,_,_,L,R)) :-
4962 random(1,H,1), !, H1 is H-1,
4963 (Key=K ; random_avl_member(Key,H1,L) ; random_avl_member(Key,H1,R)).
4964 random_avl_member(Key, H, node(K,_,_,L,R)) :- random(1,3,1), !, H1 is H-1,
4965 (random_avl_member(Key,H1,L) ; random_avl_member(Key,H1,R) ; Key=K).
4966 random_avl_member(Key, H, node(K,_,_,L,R)) :- H1 is H-1,
4967 (random_avl_member(Key,H1,R) ; random_avl_member(Key,H1,L) ; Key=K).
4968
4969 % a variation of avl_member from library(avl) which tries to avoid leaving choice points behind
4970 avl_member_opt(Key, node(K,_,_,L,R)) :-
4971 ? ( avl_member_opt(Key, L)
4972 ? ; R=empty -> Key = K % avoid trailing choice_point
4973 ? ; (Key=K ; avl_member_opt(Key, R))
4974 ).
4975
4976 % ---------------------
4977
4978 :- use_module(kernel_objects,[check_element_of_wf/3,not_element_of_wf/3]).
4979 element_of_special_closure(interval(LOW,UP),X,WF,_,_,_) :- !,
4980 %hit_profiler:add_profile_hit(in_nat_range(X,LOW,UP,CondClosure)),
4981 kernel_objects:in_nat_range_wf(X,int(LOW),int(UP),WF).
4982 element_of_special_closure(member_closure(_ID,_Type,VAL),X,WF,_,_,_) :-
4983 (VAL=value(_) ; VAL = cartesian_product(b(value(A),_,_),b(value(B),_,_))),!,
4984 %hit_profiler:add_profile_hit(in_member_closure(X,Par,Typ,Body)),
4985 (VAL=value(Set) -> kernel_objects:check_element_of_wf(X,Set,WF)
4986 ; X=(XA,XB),
4987 kernel_objects:check_element_of_wf(XA,A,WF),
4988 kernel_objects:check_element_of_wf(XB,B,WF)).
4989 element_of_special_closure(not_member_closure(_ID,_Type,value(Set)),X,WF,_,_,_) :- !,
4990 %hit_profiler:add_profile_hit(in_not_member_closure(X,Par,Typ,Set)),
4991 % print(closure_not_member_check(X,Set)),nl,
4992 kernel_objects:not_element_of_wf(X,Set,WF).
4993 % we used to have to add enumerator, as not_element_of does not instantiate; e.g. relevant when doing X :: GS - {y}
4994 % This is no longer required
4995 % see test 6 (../prob_examples/public_examples/B/FeatureChecks/NotMemberCheck.mch)
4996 %(ground_value(X) -> true ; (Type=integer, nonvar(Set), Set=avl_set(COMPL_AVL), get_not_member_enum_range(COMPL_AVL,MinFrom,MinTo))
4997 % -> enumerate_integer_with_min_range_wf(X,MinFrom,MinTo,WF)
4998 % ; b_enumerate:b_tighter_enumerate_single_value(X,Type,not_member_check,WF)).
4999 element_of_special_closure(recursive_special_closure(RId),X,WF,Parameters,PT,CondClosure) :- !,
5000 add_recursive_parameter(Parameters,PT,X,RId,CondClosure,NewParameters,NewPT,Value,WF),
5001 element_of_normal_closure(Value,NewParameters,NewPT,CondClosure,WF).
5002 element_of_special_closure(_,X,WF,Parameters,PT,CondClosure) :-
5003 % none of the special cases above apply after all
5004 ? element_of_normal_closure(X,Parameters,PT,CondClosure,WF).
5005
5006 :- block element_of_closure(?,-,?,?,?), element_of_closure(?,?,?,-,?).
5007 % element_of_closure(X,Para,T,Body,_WF): check if X is a member of closure(Para,T,Body)
5008 element_of_closure(X,Parameters,PT,CondClosure,WF) :-
5009 ? is_special_closure(Parameters,PT,CondClosure, SpecialClosure),!,
5010 %print_term_summary(element_of_special_closure(SpecialClosure,X,WF,Parameters,PT,CondClosure)), trace_in_debug_mode,
5011 ? element_of_special_closure(SpecialClosure,X,WF,Parameters,PT,CondClosure).
5012 element_of_closure(X,Parameters,PT,CondClosure,WF) :-
5013 %print_term_summary(element_of_normal_closure(X,Parameters,PT,CondClosure,WF)), trace_in_debug_mode,
5014 ? element_of_normal_closure(X,Parameters,PT,CondClosure,WF).
5015 element_of_normal_closure(X,Parameters,PT,CondClosure,WF) :-
5016 %hit_profiler:add_profile_hit(element_of_closure(X,Parameters,PT,CondClosure)),
5017 ? ~~mnf(lists:same_length(Parameters,ParValues)),
5018 ? ~~mnf(convert_list_into_pairs(ParValues,X)),
5019 ? b_test_closure_wo_enum(Parameters,PT,CondClosure,ParValues,WF).
5020
5021 :- block b_test_closure_wo_enum(?,?,-,?,?).
5022 b_test_closure_wo_enum(Parameters,ParameterTypes,ClosurePred,ParValues,WF) :-
5023 % ~~mnf(lists:same_length(Parameters,ParValues)), % not necessary
5024 ? store:set_up_localstate(Parameters,ParValues,[],LocalState),
5025 ? b_enumerate:b_type_values_in_store(Parameters,ParameterTypes,LocalState),
5026 %print(test_closure(Parameters)),nl, print_term_summary(b_test_boolean_expression(ClosurePred,LocalState,[],WF)),
5027 ? copy_wf_start(WF,InnerWF), % avoid that WF0 actions triggered before we have had a chance to traverse the expression
5028 ? b_interpreter:b_test_boolean_expression(ClosurePred,LocalState,[],InnerWF),
5029 ? copy_wf_finish(WF,InnerWF).
5030
5031 % recursive identifier to list of parameters with body as value
5032 % NewValue is the Value that should be checked for membership in the adapted closure; it has one argument more
5033 add_recursive_parameter(Parameters,Types,Value,TId,CondClosure,NewParameters,NewTypes,NewValue,WF) :-
5034 TId = b(identifier(RId),SetType,_), % unification replaces: get_texpr_id(TId,RId), get_texpr_type(TId,SetType),
5035 append(Parameters,[RId],NewParameters),
5036 append(Types,[SetType],NewTypes),
5037 %tools_printing:print_term_summary(recursion(Value)),nl,
5038 % TO DO check some variant decreases
5039 (kernel_waitflags:pending_abort_error(WF)
5040 -> NewValue = (_,_) % prevent further expansion of recursion, in case WD error in recursive function
5041 % TO DO: detect whether WD error occurs within recursive function,
5042 % indeed, the expansion of the recursive function could be unrelated to WD error and be important to detect inconsistency which prevents WD error: e.g., 1/x=res & recfun(x) \= 0
5043 ,debug_println(19,stopping_recursion_due_to_wd_error)
5044 ; NewValue = (Value,closure(Parameters,Types,CondClosure))
5045 ).
5046
5047
5048 % same as above, but without a waitflag
5049 element_of_custom_set(X,CS) :- element_of_custom_set2(CS,X).
5050
5051 element_of_custom_set2(global_set(GS),X) :- !,element_of_global_set(X,GS).
5052 element_of_custom_set2(freetype(ID),_) :- is_maximal_freetype(ID),!. % freetypes are always maximal at the moment
5053 element_of_custom_set2(avl_set(AVL),X) :- !,
5054 safe_avl_member(X,AVL).
5055 element_of_custom_set2(CS,X) :- init_wait_flags(WF),element_of_custom_set_wf2(CS,X,WF),
5056 ground_wait_flags(WF).
5057
5058 % ---------------
5059
5060 % function application for closure
5061
5062 % same as check_element_of_wf but does not wait on Y:
5063 % should also work for relation ??
5064
5065 check_element_of_function_closure(X,Y,Parameters,PT,CondClosure,WF) :-
5066 is_special_closure(Parameters,PT,CondClosure, SpecialClosure),!, % this covers recursive closures
5067 element_of_special_closure(SpecialClosure,(X,Y),WF,Parameters,PT,CondClosure).
5068 check_element_of_function_closure(X,Y, P,T,ClosureBody, WF) :- % affects test 1312, unless we add s:seq(0..9) before calling num
5069 % a special rule which tries and avoid enumerating solutions to arguments of function application
5070 % usually a function application will either be given all arguments or maybe be used in inverse
5071 ? is_converted_lambda_closure(P,T,ClosureBody), %is_converted_non_recursive_lambda_closure(P,T,ClosureBody), % TO DO: also make this work for recursive closures by adding recursive args (see e.g. test 1302)
5072 ? is_lambda_closure(P,T,ClosureBody, OtherIDs, OtherTypes, DomainPred, EXPR),
5073 ? (debug:debug_level_active_for(4) ->
5074 print('Apply Fun : '), translate:print_bexpr(DomainPred), print(' | '), translate:print_bexpr(EXPR),nl,
5075 get_texpr_info(ClosureBody,I), print(info(I,WF)),nl,
5076 print_term_summary((X,Y)),nl %,trace
5077 ; true),
5078 ? !,
5079 % alternative: annotate X,Y as inner variable ?
5080 ? b_interpreter:set_up_typed_localstate2(OtherIDs,OtherTypes,ParValues,_TypedVals,[],LocalState,positive),
5081 ? convert_list_into_pairs(ParValues,SingleParValue),
5082 ? kernel_objects:equal_object_wf(X,SingleParValue,check_element_of_function_closure,WF),
5083 ? (is_truth(DomainPred) -> true %, print(truth),nl,nl
5084 ; init_wait_flags(InnerWF),
5085 %copy_wf01e_wait_flags(WF,InnerWF), % we could delay copying WF0 until after test_boolean_expression of DomainPred ?
5086 b_interpreter:b_test_boolean_expression(DomainPred,LocalState,[],InnerWF),
5087 get_wait_flag0(WF,WF0), get_wait_flag0(InnerWF,WF0), % was: ground_wait_flag0(InnerWF), but this can result in inner WF0 being set when outer is not yet set; see test 1948
5088 %get_last_wait_flag(check_element_of_function_closure(OtherIDs),WF,LastWF),
5089 get_wait_flag(2000000,check_element_of_function_closure(OtherIDs),WF,LastWF), % we could also multiply priorities ?
5090 ground_value_check(X,GrX), (var(Y) -> ground_value_check(Y,GrY) ; true),
5091 block_copy_waitflag_store(InnerWF,WF,GrX,GrY,LastWF)
5092 ),
5093 ? b_interpreter:b_compute_expression(EXPR,LocalState,[],Y,WF).
5094 check_element_of_function_closure(X,Y, P,T,ClosureBody, WF) :-
5095 ? element_of_normal_closure((X,Y),P,T,ClosureBody,WF).
5096 % we could memoize on X here if /*@symbolic-memo */ pragma used and closure has special ID associated with it
5097
5098 :- block block_copy_waitflag_store(?,?,-,-,-).
5099 block_copy_waitflag_store(InnerWF,WF,_,_,_) :- copy_waitflag_store(InnerWF,WF).
5100
5101 /* -------------- */
5102 /* NOT_ELEMENT_OF */
5103 /* -------------- */
5104
5105 :- use_module(kernel_objects,[not_element_of_global_set/2]).
5106
5107 not_element_of_custom_set(X,CS) :- init_wait_flags(WF),
5108 not_element_of_custom_set_wf(X,CS,WF),
5109 ground_wait_flags(WF).
5110 not_element_of_custom_set_wf(X,CS,WF) :-
5111 not_element_of_custom_set_wf2(CS,X,WF).
5112
5113 not_element_of_custom_set_wf2(global_set(GS),X,_WF) :- not_element_of_global_set(X,GS).
5114 not_element_of_custom_set_wf2(freetype(_),_,_) :- !,fail. % TO DO: what if we have List(1..3) ? can that occur ??
5115 not_element_of_custom_set_wf2(avl_set(node(Y,_,_,empty,empty)),X,WF) :- !,
5116 % X /: {Y} <=> X /= Y
5117 %% print(not_eq(X,Y)),nl,when(nonvar(X),(print(neq(X,Y)),nl)),
5118 kernel_objects:not_equal_object_wf(X,Y,WF). % improve if X is ground
5119 not_element_of_custom_set_wf2(avl_set(AVL),X,_WF) :- !,
5120 ground_value_check(X,GrX),
5121 propagate_avl_not_element_information(X,GrX,AVL),
5122 not_element_of_avl_set_block(GrX,X,AVL).
5123 not_element_of_custom_set_wf2(closure(Parameters,PT,Cond),X,WF) :-
5124 closure_not_member(X,Parameters,PT,Cond,WF).
5125 %not_element_of_custom_set_wf2(closure_x(Parameters,PT,Cond,Expansion),X,WF) :-
5126 % ((ground(Expansion),ground(X))
5127 % -> \+ member(X,Expansion)
5128 % ; closure_not_member(X,Parameters,PT,Cond,WF)
5129 % ).
5130
5131 :- block not_element_of_avl_set_block(-,?,?).
5132 not_element_of_avl_set_block(_,X,AVL) :-
5133 convert_to_avl_inside_set(X,CX), %print(avl_fetch(CX)),nl,
5134 \+ avl_fetch(CX,AVL). %% IMPROVE ??
5135
5136 propagate_avl_not_element_information(_,GrEl,_) :- nonvar(GrEl),!.
5137 propagate_avl_not_element_information(Element,_,AVL) :- preferences:preference(use_clpfd_solver,true),
5138 is_avl_simple_set(AVL,Type), % \+ground(Element) ,
5139 (Type=integer -> avl_height_less_than(AVL,6) % 16-31 elements - was: avl_size(AVL,Size), Size<20
5140 ; true),
5141 !,
5142 propagate_avl_not_element_information3(Type,Element,AVL).
5143 propagate_avl_not_element_information(_Element,_,AVL) :-
5144 quick_definitely_maximal_set_avl(AVL),
5145 !, % we require something not to be an element of the full set; impossible
5146 %print(not_element_of_full_set),nl,
5147 % to do: check if all but one element is in set
5148 fail.
5149 propagate_avl_not_element_information(_,_,_).
5150
5151
5152 % try and compute a small finite cardinality; fail if not possible
5153 try_get_finite_max_card_from_value(pred_true,2).
5154 try_get_finite_max_card_from_value(pred_false,2).
5155 try_get_finite_max_card_from_value(fd(_,Type),Card) :- b_global_sets:b_fd_card(Type,Card).
5156 try_get_finite_max_card_from_value((A,B),Card) :-
5157 try_get_finite_max_card_from_value(A,CA),
5158 try_get_finite_max_card_from_value(B,CB),
5159 Card is CA*CB,
5160 Card < 20000.
5161 % TO DO: add records
5162 try_get_finite_max_card_from_value(avl_set(node(El,_True,_,_,_)),Card) :-
5163 try_get_finite_max_card_from_value(El,CEl),
5164 CEl < 16,
5165 safe_pow2(CEl,Card).
5166
5167
5168 :- use_module(b_global_sets,[get_global_type_value/3]).
5169 propagate_avl_not_element_information3(integer,int(El),AVL) :-
5170 avl_domain(AVL,R),project_avl_domain_on_fd(R,FDList),
5171 % print(posting_not_inlist(integer,El,FDList)),nl,
5172 clpfd_interface:clpfd_not_inlist(El,FDList).
5173 propagate_avl_not_element_information3(global(GS),FD,AVL) :-
5174 get_global_type_value(FD,GS,El), % sets up the FD constraint if var; maybe we can detect inconsistency straightaway below
5175 avl_domain(AVL,R),project_avl_domain_on_fd(R,FDList), % maybe we can compute directly the complement ?
5176 clpfd_interface:clpfd_not_inlist(El,FDList).
5177
5178 :- use_module(library(lists),[same_length/2]).
5179
5180 :- block closure_not_member(?,-,?,?,?).
5181 %, closure_not_member(-,?,?,?,?). /* El is unlikely to be instantiated by not_element_of test , but test 6 requires commenting out block declaration */
5182
5183 closure_not_member(X,Parameters,Types,Body,WF) :-
5184 is_special_closure(Parameters,Types,Body,SpecialClosure),!,
5185 not_element_of_special_closure(SpecialClosure,X,WF,Parameters,Types,Body).
5186 closure_not_member(El,Parameters,PT,Cond,WF) :-
5187 normal_closure_not_member(El,Parameters,PT,Cond,WF).
5188
5189 not_element_of_special_closure(interval(LOW,UP),X,_WF,_Parameters,_Types,_Body) :-
5190 !,kernel_objects:not_in_nat_range(X,int(LOW),int(UP)).
5191 not_element_of_special_closure(member_closure(_ID,_Type,VAL),X,WF,_Parameters,_Types,_Body) :-
5192 ( VAL = value(_)
5193 ; VAL = cartesian_product(b(value(A),_,_),b(value(B),_,_))),!,
5194 %hit_profiler:add_profile_hit(member(X,Par,Typ,Body)),
5195 ( VAL=value(Set) -> kernel_objects:not_element_of_wf(X,Set,WF)
5196 ; kernel_objects:not_is_cartesian_pair(X,A,B,WF)).
5197 not_element_of_special_closure(not_member_closure(_ID,_Type,value(Set)),X,WF,_Parameters,_Types,_Body) :-
5198 !,kernel_objects:check_element_of_wf(X,Set,WF).
5199 not_element_of_special_closure(recursive_special_closure(RId),X,WF,Parameters,Types,Body) :-
5200 !,
5201 add_recursive_parameter(Parameters,Types,X,RId,Body,NewParameters,NewPT,Value,WF),
5202 normal_closure_not_member(Value,NewParameters,NewPT,Body,WF).
5203
5204 not_element_of_special_closure(SC,_X,_WF,Parameters,Types,Body) :-
5205 SC \= interval(_,_),
5206 SC \= not_member_closure(_,_,_),
5207 is_definitely_maximal_closure(Parameters,Types,Body),
5208 !,
5209 fail.
5210 not_element_of_special_closure(_,X,WF,Parameters,Types,Body) :-
5211 % falling back to normal test
5212 normal_closure_not_member(X,Parameters,Types,Body,WF).
5213
5214
5215 normal_closure_not_member(El,Parameters,PT,Cond,WF) :-
5216 %hit_profiler:add_profile_hit(closure_not_member(El,Parameters,PT,Cond,WF)),
5217 lists:same_length(Parameters,ParValues),
5218 convert_list_into_pairs(ParValues,El),
5219 % print(not_test_closure(El,Cond)),nl,
5220 b_not_test_closure_wf(Parameters,PT,Cond,ParValues,WF).
5221
5222
5223
5224
5225 /* -------------------------- */
5226 /* VARIOUS CLOSURE PREDICATES */
5227 /* -------------------------- */
5228
5229
5230 :- use_module(tools,[convert_list_into_pairs/2]).
5231 :- use_module(b_interpreter,[b_test_boolean_expression/4, b_not_test_boolean_expression/4]).
5232 :- use_module(b_enumerate).
5233
5234 :- assert_pre(custom_explicit_sets:expand_closure_to_list(_,_,ClosureBody,_Result,_Done,_,_WF),
5235 (nonvar(ClosureBody),
5236 bsyntaxtree:check_if_typed_predicate(ClosureBody))).
5237 :- assert_post(custom_explicit_sets:expand_closure_to_list(_,_,_,Result,_Done,_,_WF),
5238 b_interpreter:value_type(Result)).
5239
5240 :- block expand_interval_closure_to_avl(-,?,?), expand_interval_closure_to_avl(?,-,?).
5241 expand_interval_closure_to_avl(Low,Up,Result) :-
5242 % print(expand_interval_to_avl(Low,Up)),nl,
5243 Delta is Up-Low,
5244 (Delta>9999 -> perfmessage(expanding_interval(Low,Up)) ; true),
5245 construct_interval_ord_list(Low,Up,OL),
5246 ord_list_to_avlset_direct(OL,ARes,expand_interval),
5247 equal_object(ARes,Result,expand_interval_closure_to_avl).
5248 construct_interval_ord_list(Low,Up,Res) :-
5249 (Low>Up -> Res = []
5250 ; Res = [int(Low)-true|T], L1 is Low+1, construct_interval_ord_list(L1,Up,T)
5251 ).
5252
5253 :- block expand_interval_closure_to_list(-,?,?,?), expand_interval_closure_to_list(?,-,?,?).
5254 expand_interval_closure_to_list(Low,Up,Result,Done) :- %print(expand_interval_to_list(Low,Up)),nl,
5255 construct_interval_list(Low,Up,OL), %print(done_epxand_interval(Low,Up)),nl,
5256 equal_object(OL,Result,expand_interval_closure_to_list),
5257 Done=true.
5258 construct_interval_list(Low,Up,Res) :-
5259 (Low>Up -> Res = []
5260 ; Res = [int(Low)|T], L1 is Low+1, construct_interval_list(L1,Up,T)
5261 ).
5262
5263 expand_closure_to_list([X],[integer],Body,Result,Done,_,_) :-
5264 is_interval_closure_body(Body,X,Low,Up),!,
5265 % print(expanding_interval_closure_to_list(Low,Up)),nl,
5266 expand_interval_closure_to_list(Low,Up,Result,Done).
5267 expand_closure_to_list(Par,Types,Body,Result,Done,Source,WF) :- %print(exp_to_list),nl,
5268 expand_normal_closure(Par,Types,Body,CResult,CDone,expand_closure_to_list(Source),WF),
5269 %% print_term_summary(expanded_normal_closure(Par,Types,CResult,CDone)),nl,
5270 expand_if_avl(CResult,Result,CDone,Done,Source),
5271 (WF==no_wf_available -> true ;
5272 % print(lazy_check(Result,CDone,Par)),nl, translate:print_bexpr(Body),nl,
5273 lazy_check_elements(Result,CDone, Par,Types,Body,WF)).
5274 %% print_term_summary(expanded(CResult,Result,CDone,Done)).
5275
5276 % Note: does slow down test 1306
5277 :- block lazy_check_elements(-,-, ?,?,?,?).
5278 lazy_check_elements(Result,CDone, _Par,_Types,_Body,_WF) :- (var(Result) ; nonvar(CDone)),!.
5279 lazy_check_elements([H|T],CDone, Par,Types,Body,WF) :- !,
5280 %nl,print(check_el(H,Par)),nl,
5281 element_of_closure(H,Par,Types,Body,WF),
5282 lazy_check_elements(T,CDone, Par,Types,Body,WF).
5283 lazy_check_elements(avl_set(A),_CDone, Par,Types,Body,WF) :- !,
5284 avl_max(A,X),
5285 %nl,print(check_el_avl_max(X,Par)),nl,
5286 element_of_closure(X,Par,Types,Body,WF).
5287 % TO DO: also check avl_min or even all elements ?
5288 lazy_check_elements(_,_,_,_,_,_).
5289
5290 check_valid_avl(AVL,Origin) :-
5291 (nonvar(AVL) -> true
5292 ; add_internal_error('Var avl_set: ', check_valid_avl(AVL,Origin)),fail).
5293
5294 :- block expand_if_avl(?,?,-,?,?).
5295 ?expand_if_avl(avl_set(S),Result,_,Done,Source) :- !, % we could transmit a flag to expand_normal_closure so that transform_result_into_set does not expand to avl
5296 ? expand_custom_set_to_list2(avl_set(S),Result,Done,expand_if_avl(Source),no_wf_available).
5297 ?expand_if_avl(Res,Result,_,Done,Source) :- check_list(Res,expand_if_avl(Source)),
5298 ? equal_object(Res,Result), Done=true.
5299
5300 check_list(Res,_) :- nonvar(Res), is_list(Res),!.
5301 check_list(Res,Src) :- add_error(Src,'Could not expand to list: ',Res).
5302 is_list([]). is_list([_|_]).
5303
5304 expand_closure_to_avl_or_list([X],[integer],Body,Result,_CheckTimeouts,_WF) :-
5305 is_interval_closure_body(Body,X,Low,Up),!,
5306 %print(expanding_interval_closure_to_avl(Low,Up)),nl,
5307 expand_interval_closure_to_avl(Low,Up,Result).
5308 %expand_closure_to_avl_or_list(P,T,Body,Result,_WF) :- is_member_closure(P,T,Body,TS,Set),
5309 % print(expand_member_closure(P,T,Body,TS,Set)),nl,fail.
5310 expand_closure_to_avl_or_list(Par,Types,Body,Result,CheckTimeouts,WF) :-
5311 expand_normal_closure(Par,Types,Body,CResult,_Done,CheckTimeouts,WF), % print(expanded(CResult)),nl, %
5312 kernel_objects:equal_object(Result,CResult,expand_closure_to_avl_or_list). % may convert to AVL, should we wait for _Done?
5313
5314
5315 expand_closure_to_avl([X],[integer],Body,Result) :-
5316 is_interval_closure_body(Body,X,Low,Up),!,
5317 %print(expanding_interval_closure_to_avl(Low,Up)),nl,
5318 expand_interval_closure_to_avl(Low,Up,Result).
5319 expand_closure_to_avl(Par,Types,Body,Result) :-
5320 ? expand_normal_closure(Par,Types,Body,S,_Done,check(expand_closure_to_avl),no_wf_available),
5321 (ground_value(S) -> convert_to_avl_inside_set(S,R),equal_object(R,Result,expand_closure_to_avl)
5322 ; print(cannot_convert_closure_value_to_avl(closure(Par,Types,Body))),nl,fail).
5323
5324
5325 % possible values for CheckTimeouts: check, check_no_inf, no_check, ...
5326 % Note: we no longer check is_infinite_explicit_set(closure(Parameters,ParameterTypes,ClosureBody))
5327 % and no longer raise add_closure_warning(Source,Parameters,ParameterTypes,ClosureBody,'### WARNING: expanding infinite comprehension set: ')
5328 % and no longer use preference warn_when_expanding_infinite_closures
5329 % this is relevant for e.g., test 1291
5330 expand_normal_closure(Parameters,ParameterTypes,ClosureBody,Result,Done,CheckTimeouts,WF) :-
5331 ? expand_normal_closure_memo(CheckTimeouts,Parameters,ParameterTypes,ClosureBody,Result,Done,WF).
5332
5333 add_closure_warning(Source,Parameters,_ParameterTypes,_ClosureBody,_MSG) :-
5334 preference(provide_trace_information,false),preference(strict_raise_warnings,false),!,
5335 format('### TIME-OUT raised during closure expansion (~w,~w).~n### set TRACE_INFO preference to TRUE for more details.~n',[Parameters,Source]).
5336 add_closure_warning(Source,Parameters,ParameterTypes,ClosureBody,MSG) :-
5337 (debug_mode(on) -> Limit = 2500, AvlLim=10 ; Limit = 500, AvlLim=5),
5338 preferences:temporary_set_preference(expand_avl_upto,AvlLim,CHNG),
5339 call_cleanup(translate:translate_bvalue_with_limit(closure(Parameters,ParameterTypes,ClosureBody),Limit,CT),
5340 preferences:reset_temporary_preference(expand_avl_upto,CHNG)),
5341 bsyntaxtree:get_texpr_info(ClosureBody,Infos),
5342 add_warning(Source,MSG,CT,Infos), debug_print(19,'! infos: '), debug_println(Infos). %,trace.
5343
5344
5345 % a version of closure expansion which memoizes its results; stored_expansion needs to be cleared when new machine loaded
5346 expand_normal_closure_memo(CHECK,Parameters,ParameterTypes,ClosureBody,FullResult,Done,WF) :-
5347 ? preferences:preference(use_closure_expansion_memoization,false),!,
5348 %% print(expand(Parameters,ClosureBody)),nl, %%
5349 ? expand_normal_closure2(CHECK,Parameters,ParameterTypes,ClosureBody,FullResult,Done,WF).
5350 expand_normal_closure_memo(CHECK,Parameters,ParameterTypes,ClosureBody,FullResult,Done,WF) :-
5351 % maybe we should only memo when ClosureWaitVars are ground ?
5352 MemoLookupTerm = closure(Parameters,ParameterTypes,ClosureBody),
5353 compute_memo_hash(MemoLookupTerm,Hash),
5354 % idea: maybe store expansion only on second hit ?
5355 (get_stored_memo_expansion(Hash,MemoLookupTerm,StoredResult)
5356 -> %print_term_summary(reusing_expansion(Hash,Parameters,ParameterTypes,ClosureBody,StoredResult)),nl,
5357 UPV=StoredResult, %state_packing:unpack_value(StoredResult,UPV),
5358 FullResult = UPV, Done=true
5359 ; %statistics(runtime,[T1,_]), %%
5360 expand_normal_closure2(CHECK,Parameters,ParameterTypes,ClosureBody,FullResult,Done,WF),
5361 %statistics(runtime,[T2,_]), Time is T2-T1, store_memo_computation_time(Hash,Time),
5362 (Done==true/* ,T2-T1>0*/
5363 -> PackedValue=FullResult, %state_packing:pack_value(FullResult,PackedValue),
5364 store_memo_expansion(Hash,MemoLookupTerm,PackedValue)
5365 ; true)
5366 ).
5367
5368
5369 %spycl([iti0|_]).
5370
5371 expand_normal_closure2(_CHECK,Parameters,ParameterTypes,ClosureBody,FullResult,Done,WF) :-
5372 % TO DO: add more symbolic member closures who have expression computation code
5373 ? is_closure1_value_closure(Parameters,ParameterTypes,ClosureBody,VAL),!,
5374 %print_term_summary(closure1_expand(VAL)),nl,
5375 ? bsets_clp:relational_trans_closure_wf(VAL,FullResult,WF), % TO DO: pass WF
5376 ground_value_check(FullResult,FRGr),
5377 when(nonvar(FRGr),Done=true).
5378 %print(compute(closure1(VAL))),nl,
5379 %when(ground(VAL), (bsets_clp:relational_trans_closure(VAL,Result),
5380 % equal_object(Result,FullResult),Done=true)).
5381 expand_normal_closure2(CHECK,Parameters,ParameterTypes,ClosureBody,FullResult,Done,WF) :-
5382 % special treatment for lambda closures: Advantage: we don't have to wait for variables in EXPR body of closure
5383 % Disadvantage: EXPR only gets evaluated after a solution has been found for args: can mean repeated computations !
5384 % (cf pas_as_env_inv_cv_sui, negated version of !(cv_i).(cv_i : t_cv_pas => closure(%cv_o2.((...|>> {cv_i} : t_cv_pas <-> t_cv_pas) ASSERTION
5385 % Advantage: it can solve constraints such as f = %x.(x:1..10|x+y) & f(5)=1005 (finding y without enumeration); see test 1168
5386 \+ preferences:preference(use_smt_mode,false),
5387 is_lambda_closure(Parameters,ParameterTypes,ClosureBody, OtherIDs,OtherTypes, DomainPred, EXPR),
5388 \+ ground_bexpr(EXPR), % if EXPR is ground, there is nothing to be gained by special treatment here
5389 WF \= no_wf_available, % otherwise we may have to enumerate EXPR result leading to choice points, e.g. in phase 0
5390 !,
5391 % print(lambda(DomainPred,EXPR)),nl,
5392 bexpr_variables(DomainPred,ClosureWaitVars),
5393 % statistics(runtime,[Start,_]),
5394 % print(expanding_lambda_closure(ClosureWaitVars,Start)),nl,
5395 (CHECK=no_check -> TIMEOUTCODE = true ;
5396 TIMEOUTCODE = add_closure_warning(CHECK,Parameters,ParameterTypes,ClosureBody,'TIME-OUT occurred while ProB was expanding: ')),
5397 (CHECK=check_no_inf -> VIRTUALTIMEOUTCODE=true ; VIRTUALTIMEOUTCODE=TIMEOUTCODE),
5398 delay_setof_check_wf( ParTuple,
5399 (custom_explicit_sets:b_test_closure(OtherIDs,OtherTypes,DomainPred,OtherValues,all_solutions,WF),
5400 ~~mnf(convert_list_into_pairs(OtherValues,ParTuple))
5401 % TO DO: compile EXPR when we start expanding the closure: to avoid repeated re-computation of expressions for every instance
5402 ),
5403 Result, ClosureWaitVars, __Done,
5404 TIMEOUTCODE,VIRTUALTIMEOUTCODE,WF,DomainPred),
5405 % statistics(runtime,[ResT,_]), T1 is ResT-Start, print(result_time(T1)),nl,
5406 (WF = no_wf_available -> init_wait_flags(WF1) ; WF1=WF),
5407 evaluate_result_expr(Result,EXPR,OtherIDs,EvResult,EvDone,WF1),
5408 when(nonvar(EvDone),(%print(finished(Parameters)),nl, print_term_summary(eq(EvResult,FullResult)),nl,
5409 (WF = no_wf_available -> ground_wait_flags(WF1) ; true),
5410 kernel_objects:equal_object(EvResult,FullResult,expand_normal_closure2),Done=true)).
5411 expand_normal_closure2(no_check,Parameters,ParameterTypes,ClosureBody,Result,Done,WF) :- !,
5412 expand_normal_closure_direct(Parameters,ParameterTypes,ClosureBody,Result,Done,WF).
5413 expand_normal_closure2(CHECK,Parameters,ParameterTypes,ClosureBody,Result,Done,WF) :-
5414 bexpr_variables(ClosureBody,ClosureWaitVars),
5415 TIMEOUTCODE = add_closure_warning(CHECK,Parameters,ParameterTypes,ClosureBody,'TIME-OUT occurred while ProB was expanding: '),
5416 (CHECK=check_no_inf -> VIRTUALTIMEOUTCODE=true ; VIRTUALTIMEOUTCODE=TIMEOUTCODE),
5417 delay_setof_check_wf( ParTuple,
5418 custom_explicit_sets:test_closure_and_convert(Parameters,ParameterTypes,ClosureBody, ParTuple,WF),
5419 Result, ClosureWaitVars, Done, TIMEOUTCODE, VIRTUALTIMEOUTCODE,WF,ClosureBody).
5420
5421 expand_normal_closure_direct(Parameters,ParameterTypes,ClosureBody,Result,Done,WF) :-
5422 bexpr_variables(ClosureBody,ClosureWaitVars),
5423 Span = ClosureBody,
5424 delay_setof_wf( ParTuple,
5425 % TO DO: refresh waitflag in out waitflag store to let all pending code run to completion and avoid spurious WD errors ?
5426 custom_explicit_sets:test_closure_and_convert(Parameters,ParameterTypes,ClosureBody, ParTuple,WF),
5427 Result, ClosureWaitVars, Done,WF, Span).
5428
5429
5430
5431 :- block evaluate_result_expr(-,?,?,?,?,?).
5432 evaluate_result_expr(avl_set(AVL),EXPR,OtherIDs,Res,Done,WF) :-
5433 avl_domain(AVL,R),
5434 evaluate_result_expr(R,EXPR,OtherIDs,Res,Done,WF).
5435 evaluate_result_expr([],_EXPR,_OtherIDs,[],Done,_WF) :- %translate:print_bexpr(_EXPR),nl,print(done_evaluate_result_expr(_OtherIDs)),nl,
5436 %ground_wait_flags(WF),
5437 Done=true.
5438 evaluate_result_expr([ParTuple|T],EXPR,OtherIDs,[FullTuple|ET],Done,WF) :-
5439 % print(evaluate(ParTuple)),nl,
5440 %~~mnf(lists:same_length(OtherIDs,ParValues)), % not necessary
5441 ~~pp_mnf(store:set_up_localstate(OtherIDs,ParValues,[],LocalState)),
5442 ~~mnf(convert_list_into_pairs(ParValues,ParTuple)), % bind values in ParTuple to LocalState
5443 % print(setup_localstate(LocalState)),nl,
5444 b_interpreter:b_compute_expression(EXPR,LocalState,[],EXPRVALUE,WF),
5445 % print(expr_value(EXPRVALUE)),nl,
5446 append(ParValues,[EXPRVALUE],FullValues),
5447 ~~mnf(convert_list_into_pairs(FullValues,FullTuple)),
5448 %print(full_tuple(FullTuple)),nl,
5449 evaluate_result_expr(T,EXPR,OtherIDs,ET,Done,WF).
5450
5451 %:- use_module(library(lists),[prefix_length/3, suffix_length/3]).
5452 % test a closure and convert into pairs; assume we want all solutions
5453 test_closure_and_convert(Parameters,ParameterTypes,b(exists(EParAndTypes,ClosureBody),pred,Info), ParTuple, WF) :-
5454 % Motivation: enumerating Parameters can be quite inefficient if for example we have something like {x|#y.(y:SmallSet & x=f(y))}
5455 % Problem: the existential quantifier will be delayed until the Parameters are instantiated !
5456 % maybe only do this in special circumstances ? domain of EPar much smaller than of Parameters, exists constructed by ran_symbolic ?
5457 ? (Parameters == ['_was_lambda_result_'] % at the moment only accept this ; here we are quite sure that we gain by this optimisation
5458 ? ; member(allow_to_lift_exists,Info) % parameters were originally from a set comprehension, see test 306: in this case existential quantifier is lifted in b_interpreter anyway;
5459 %Note we counter the rewrite ran({x1,...xn|P}) ---> {xn| #(x1,...).(P)}
5460 ? ; ClosureBody = b(member(_,_),_,_) % we have a simple projection closure % TO DO: maybe support other ones as well
5461 ; %print(check_card(Parameters)),nl,
5462 basic_type_list_cardinality(ParameterTypes,Card), %print(card(Card)),nl,
5463 (Card=inf -> true ; Card>10000)
5464 % if here are only a few parameter values: do not lift existential quantified variables
5465 ),
5466 ? b_interpreter:split_names_and_types(EParAndTypes,EPar,ETypes),
5467 ? !,
5468 % print(' Lifting existential quantifier: '), print(EPar),nl, %translate:print_bexpr(ClosureBody),nl,
5469 % append Parameters at end; in case we have a lambda function
5470 ? append(EPar,Parameters,FullPar), length(Parameters,NrParas),
5471 ? append(ETypes,ParameterTypes,FullTypes),
5472 ? length(EPar,NrExistsParas),
5473 ? length(IrrelevantParas,NrExistsParas), length(Suffix,NrParas),
5474 ? append(IrrelevantParas,Suffix,FullParList),
5475 %(EPar=['LV_ma',speedLimitAreasInMA] -> print(par(Parameters)),nl,translate:print_bexpr(ClosureBody),nl
5476 %, trace, is_lambda_closure(FullPar,FullTypes,ClosureBody, OtherIDs,OtherTypes, DomainPred, EXPR)
5477 % ; true),
5478 % print(fullpar(FullPar)),nl,
5479 ? b_test_closure(FullPar,FullTypes,ClosureBody, FullParList,all_solutions,WF),
5480 convert_list_into_pairs(Suffix,ParTuple). % , print(converted(Prefix,ParTuple)),nl.
5481 test_closure_and_convert(Parameters,ParameterTypes,ClosureBody, ParTuple, WF) :-
5482 %print(test),nl, translate:print_bexpr(ClosureBody),nl,
5483 ? length(Parameters,Len), length(ParValues,Len),
5484 ? b_test_closure(Parameters,ParameterTypes,ClosureBody,ParValues,all_solutions,WF),
5485 convert_list_into_pairs(ParValues,ParTuple). % ,print(solution(ParTuple)),nl,nl.
5486
5487 % compute cardinality of a list of basic types
5488 basic_type_list_cardinality([],1).
5489 basic_type_list_cardinality([BasicType|T],Res) :-
5490 basic_type_list_cardinality(T,TCard),
5491 (TCard=inf -> Res=inf
5492 ; kernel_objects:max_cardinality(BasicType,Card),
5493 kernel_objects:safe_mul(Card,TCard,Res)
5494 ).
5495
5496 % for lambda closures we can set up a second waitflag for the expression and only ground it when body enumeration finished
5497 % idea is to avoid perturbation of constraint solving of main closure predicate by lambda expression, see test 1737
5498 % something like %(x,y).(x:1..200 & y:1..100 & y+x<259 & y*x>10|(y+x*x+y) mod 100) is faster
5499 % this is slower : %(x,y).(x:1..200 & y:1..100 |(y+x*x+y))
5500 % currently this slows down test 1336
5501 :- block b_test_closure(?,?,-,?,?,?).
5502 b_test_closure(Parameters,ParameterTypes,ClosureBody, FullParValues, NegationContext, _OuterWF) :-
5503 \+ preferences:preference(use_smt_mode,false), % TO DO: enable in normal mode when performance of 1336 fixed
5504 % print(test_closure(Parameters,FullParValues)),nl,
5505 is_lambda_closure(Parameters,ParameterTypes,ClosureBody, OtherIDs,OtherTypes, DomainPred, EXPR),
5506 % TO DO: detect not only equalities at end, but any equality which is irrelevant for the rest
5507 % nl,print(lambda_closure(OtherIDs)),nl, translate:print_bexpr(EXPR),nl,
5508 append(ParValues,[LambdaResult],FullParValues),
5509 !,
5510 b_interpreter:set_up_typed_localstate2(OtherIDs,OtherTypes,ParValues,TypedVals,[],LocalState,NegationContext),
5511 init_wait_flags(WF),
5512 b_interpreter:b_test_boolean_expression(DomainPred,LocalState,[],WF),
5513 %print('PRED: '),translate:print_bexpr(ClosureBody),nl,
5514 (project_away_useless_enumeration_values(DomainPred,TypedVals,EnumVals) -> true ; EnumVals=TypedVals),
5515 b_enumerate:b_tighter_enumerate_values(EnumVals,WF),
5516 init_wait_flags(WF2),
5517 b_compiler:b_optimize(EXPR,[],LocalState,[],CEXPR,WF), % already pre-compile lookup, without constraint processing; is not sufficient for test 1336
5518 %print(compiled), translate:print_bexpr(CEXPR),nl,
5519 %ground_wait_flag0(WF),
5520 ground_wait_flags(WF),
5521 b_interpreter:b_compute_expression(CEXPR,LocalState,[],LambdaResult,WF2),
5522 ground_wait_flags(WF2).
5523 b_test_closure(Parameters,ParameterTypes,Closure,ParValues,NegationContext, _OuterWF) :-
5524 % tools:print_bt_message(b_test_closure_testing_closure(Parameters,ParValues)), %%
5525 % ~~mnf(lists:same_length(Parameters,ParValues)), % not necessary
5526 %~~pp_mnf(store:set_up_localstate(Parameters,ParValues,[],LocalState)),
5527 ? b_interpreter:set_up_typed_localstate2(Parameters,ParameterTypes,ParValues,TypedVals,[],LocalState,NegationContext),
5528 % print_message(b_interpreter:b_test_boolean_expression(Closure,LocalState,[],WF)),
5529 ? init_wait_flags(WF),
5530 % print(init_wf(WF)),nl,
5531 %external_functions:observe_parameters(Parameters,LocalState), %%
5532 ? ~~pp_cll(b_interpreter:b_test_boolean_expression(Closure,LocalState,[],WF)),
5533 % tools:print_bt_message(tested_bool_expr), translate:print_bexpr(Closure),nl,
5534 % TO DO: detect useless Values to enumerate; e.g., SLOT-PERFORMANCE2 : if Closure is member predicate for AVL value which already binds Value
5535 ? (project_away_useless_enumeration_values(Closure,TypedVals,EnumVals) -> true ; EnumVals=TypedVals),
5536 ? b_enumerate:b_tighter_enumerate_values(EnumVals,WF),
5537 % tools:print_bt_message(grounding_closure_constraint_prop_wait_flags(Parameters,WF)), ground_wait_flag0(WF),portray_waitflags(WF), %%
5538 ? ground_wait_flags(WF). %% Do not generate spurious error messages
5539 %% error if it persists will be a pending co-routine ?!
5540 % TO DO: use create_inner_wait_flags when using test_closure and then not ground_enumeration_finished; to avoid spurious error messages inside
5541
5542 % TO DO: try and generalize this treatment (applicable for SLOT-PERFORMANCE2 at the moment)
5543 % i.e. also treat (x,y):AVL & OTHERPRED
5544 project_away_useless_enumeration_values(b(member(A,b(value(V),_,_)),_,_),TypedVals,EnumVals) :-
5545 nonvar(V), V=avl_set(_),
5546 %print(projecting_away(TypedVals)),nl,
5547 project(A,TypedVals,EnumVals).
5548
5549 project(b(couple(A,B),_,_),TypedVals,EnumVals) :- !,
5550 project(A,TypedVals,TV1),
5551 project(B,TV1,EnumVals).
5552 project(b(identifier(ID),T,_),TypedVals,EnumVals) :- % the identifier is bound by the member test; we do not need to enumerate it
5553 ? select(typedval(_,T,ID,_),TypedVals,Rest),
5554 debug_println(9,not_enumerating_inside_closure(ID)),
5555 !,
5556 EnumVals = Rest.
5557 project(_,TV,TV).
5558
5559
5560 :- block b_not_test_closure_wf(?,?,?,-,?).
5561 b_not_test_closure_wf(Parameters,ParameterTypes,Closure,ParValues,WF) :-
5562 % ~~mnf(lists:same_length(Parameters,ParValues)), % not necessary
5563 ~~pp_mnf(store:set_up_localstate(Parameters,ParValues,[],LocalState)),
5564 ~~pp_mnf(b_enumerate:b_type_values_in_store(Parameters,ParameterTypes,LocalState)),
5565 %%init_wait_flags(WF),
5566 % print_message(b_interpreter:b_not_test_boolean_expression(Closure,LocalState,[],WF)),
5567 ~~pp_cll(b_interpreter:b_not_test_boolean_expression(Closure,LocalState,[],WF)),
5568 %%%ground_constraintprop_wait_flags(WF),
5569 get_last_wait_flag(b_not_test_closure_wf(Parameters),WF,WF2),
5570 b_not_test_closure_enum(Parameters,ParameterTypes,LocalState,WF,WF2).
5571 %% ,ground_enumeration_finished_flag(WF).
5572
5573 :- block b_not_test_closure_enum(-,?,?,?,?).
5574 b_not_test_closure_enum(Parameters,ParameterTypes,LocalState,WF,WF2) :-
5575 ~~mnf(b_enumerate:b_extract_typedvalc(Parameters,ParameterTypes,LocalState,TypedVals)),
5576 (var(WF2) -> ground_typedvals_check(TypedVals,GrVals) ; true),
5577 b_not_test_closure_enum_aux(GrVals,WF2,TypedVals,WF).
5578
5579 :- block b_not_test_closure_enum_aux(-,-,?,?).
5580 b_not_test_closure_enum_aux(_,_,TypedVals,WF) :-
5581 b_enumerate:b_tighter_enumerate_values(TypedVals,WF).
5582 % , print(finished_enum(Parameters)),nl.
5583
5584
5585 :- use_module(library(terms)).
5586 % check whether a VARIABLE occurs inside a closure
5587 closure_occurs_check(VARIABLE,_Par,_ParTypes,ClosureBody) :- expression_contains_setvar(ClosureBody,VARIABLE).
5588 % /* occurs check; x = closure1(x) ; for other closures this cannot happen ???!!! TO DO: Check */
5589 % custom_explicit_sets:is_closure1_value_closure(Par,ParTypes,ClosureBody,Val),
5590 % contains_var(VARIABLE,Val).
5591
5592 expression_contains_setvar(b(E,_,_),Variable) :- !,
5593 expression_contains_setvar_aux(E,Variable).
5594 expression_contains_setvar(E,V) :- add_internal_error('Illegal Expression: ', expression_contains_setvar(E,V)),
5595 contains_var(V,E).
5596
5597 expression_contains_setvar_aux(value(Val),Variable) :- !,value_contains_setvar(Val,Variable).
5598 % a few very common cases for performance; currently this predicate is often called for recursive functions
5599 expression_contains_setvar_aux(identifier(_),_) :- !,fail.
5600 expression_contains_setvar_aux(equal(A,B),Variable) :- !,
5601 (expression_contains_setvar(A,Variable) -> true ; expression_contains_setvar(B,Variable)).
5602 expression_contains_setvar_aux(conjunct(A,B),Variable) :- !,
5603 (expression_contains_setvar(A,Variable) -> true ; expression_contains_setvar(B,Variable)).
5604 expression_contains_setvar_aux(function(A,B),Variable) :- !,
5605 (expression_contains_setvar(A,Variable) -> true ; expression_contains_setvar(B,Variable)).
5606 expression_contains_setvar_aux(union(A,B),Variable) :- !,
5607 (expression_contains_setvar(A,Variable) -> true ; expression_contains_setvar(B,Variable)).
5608 expression_contains_setvar_aux(couple(A,B),Variable) :- !,
5609 (expression_contains_setvar(A,Variable) -> true ; expression_contains_setvar(B,Variable)).
5610 % the rest via safe_syntaxelement:
5611 expression_contains_setvar_aux(Expr,V) :- bsyntaxtree:safe_syntaxelement(Expr,Subs,_Names,_,_),!,
5612 ? member(Sub,Subs), expression_contains_setvar(Sub,V),!.
5613 expression_contains_setvar_aux(E,V) :- add_internal_error('Illegal Expression: ', expression_contains_setvar_aux(E,V)),
5614 contains_var(V,E).
5615
5616 value_contains_setvar(Val,V) :- var(Val),!,Val==V.
5617 value_contains_setvar(avl_set(_),_V) :- !, fail. % assume avl_set always properly grounded; avoid looking inside
5618 value_contains_setvar(closure(_,_,Body),V) :- !,
5619 expression_contains_setvar(Body,V).
5620 value_contains_setvar(int(_),_) :- !,fail. % we check for set variables
5621 value_contains_setvar(global_set(_),_) :- !,fail. % we check for set variables
5622 value_contains_setvar(freetype(_),_) :- !,fail. % we check for set variables
5623 value_contains_setvar(freeval(_ID,_Case,Val),V) :- !, value_contains_setvar(Val,V).
5624 value_contains_setvar(string(_),_) :- !,fail. % we check for set variables
5625 value_contains_setvar(fd(_,_),_) :- !,fail. % we check for set variables
5626 value_contains_setvar((A,B),V) :- !, (value_contains_setvar(A,V) ; value_contains_setvar(B,V)).
5627 value_contains_setvar([A|B],V) :- !, (value_contains_setvar(A,V) ; value_contains_setvar(B,V)).
5628 value_contains_setvar(Val,V) :- %print(check(Val,V)),nl,
5629 contains_var(V,Val).
5630
5631 % ------------------