1 % (c) 2009-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html
4
5 :- module(b_ast_cleanup, [clean_up/3, clean_up_pred/3,
6 clean_up_pred_or_expr/3,
7 clean_up_pred_or_expr_with_path/4, % provide initial path, used for eventb context infos
8 clean_up_l_wo_optimizations/4,
9 clean_up_l_with_optimizations/4,
10 check_used_ids_info/4, recompute_used_ids_info/2,
11 definitely_not_empty_and_finite/1, definitely_infinite/1, % TO DO: move to another module
12 get_unique_id/2,
13 predicate_level_optimizations/2,
14 perform_do_not_enumerate_analysis/5,
15 has_top_level_wd_condition/1]).
16
17 :- use_module(module_information,[module_info/2]).
18 :- module_info(group,typechecker).
19 :- module_info(description,'This module implements transformations/simplifications on the AST.').
20
21 :- set_prolog_flag(double_quotes, codes). % relevant for detecting prob-ignore, test 2151 on SWI
22
23 :- use_module(tools, [safe_atom_chars/3,exact_member/2,foldl/4,filter/4]).
24 :- use_module(tools_lists, [length_less/2]).
25 :- use_module(error_manager).
26 :- use_module(debug).
27 :- use_module(self_check).
28 :- use_module(bsyntaxtree).
29 :- use_module(translate,[print_bexpr/1, translate_span/2, get_definition_context_from_span/2]).
30 :- use_module(btypechecker, [unify_types_strict/2]).
31 :- use_module(preferences,[get_preference/2]).
32 :- use_module(custom_explicit_sets,[convert_to_avl/2]).
33 :- use_module(prob_rewrite_rules(b_ast_cleanup_rewrite_rules),[rewrite_rule_with_rename/7]).
34 :- use_module(b_enumeration_order_analysis, [find_do_not_enumerate_variables/4]).
35 :- use_module(performance_messages,[perfmessage/2]).
36 :- use_module(b_operation_guards,[get_operation_propositional_guards/6]).
37
38 :- use_module(library(lists)).
39 :- use_module(library(ordsets)).
40 :- use_module(library(system), [environ/2]).
41
42 % entry point for cleaning up predicates; ensures that global, predicate-level optimizations also applied
43 clean_up_pred(Expr,NonGroundExceptions,CleanedUpExpr) :-
44 ? clean_up(Expr,NonGroundExceptions,CExpr),
45 (get_texpr_type(CExpr,pred)
46 -> predicate_level_optimizations(CExpr,CleanedUpExpr)
47 ; add_internal_error('Not predicate: ',clean_up_pred(Expr,NonGroundExceptions,CleanedUpExpr)),
48 CleanedUpExpr = CExpr).
49
50 % Warning: arguments swapped with clean_up for maplist !
51 clean_up_pred_or_expr(NonGroundExceptions,Expr,CleanedUpExpr) :-
52 ? clean_up_pred_or_expr_with_path(NonGroundExceptions,Expr,CleanedUpExpr,[]).
53 clean_up_pred_or_expr_with_path(NonGroundExceptions,Expr,CleanedUpExpr,Path) :-
54 clean_up_init(NonGroundExceptions,Expr,Expr1),
55 ? clean_up_aux(Expr1,NonGroundExceptions,CExpr,Path),
56 (get_texpr_type(CExpr,pred)
57 -> predicate_level_optimizations(CExpr,CleanedUpExpr,Path)
58 ; CleanedUpExpr = CExpr).
59
60 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
61
62 % clean up some code afterwards
63 clean_up(Expr,NonGroundExceptions,CExpr) :- % clean-up with init
64 clean_up_init(NonGroundExceptions,Expr,Expr1),
65 ? clean_up_aux(Expr1,NonGroundExceptions,CExpr,[]).
66 clean_up_aux(Expr1,NonGroundExceptions,CExpr,Path) :- % performs no init
67 (preferences:get_preference(normalize_ast,true)
68 -> cleanups(normalize,Expr1,[],Expr2,Path)
69 ; Expr2=Expr1),
70 cleanups(pre,Expr2,[],TPExpr,Path),
71 remove_bt(TPExpr,PExpr,LExpr,TLExpr),
72 ? syntaxtransformation(PExpr,Subs,_,NewSubs,LExpr),
73 functor(PExpr,F,N),
74 % recursively clean up sub-expressions
75 ? clean_up_l(Subs,NonGroundExceptions,NewSubs,F/N,1,Path),
76 cleanups(post,TLExpr,[],CExpr,Path).
77 %, tools_printing:print_term_summary(cleaned_up(CExpr)),nl.
78
79 % just run post-phase
80 %cleanups_post(Expr,CleanedupExpr) :- cleanups(post,Expr,[],CleanedupExpr,[]).
81
82 clean_up_init(NonGroundExceptions,Expr,Expr2) :-
83 % ensure that WD info is available also for pre phase
84 % also pre-transform large set_extensions; they are only later transformed using eval_set_extension
85 ? (transform_bexpr_td_with_scoping(b_ast_cleanup:try_evaluate_set_extension,Expr,Expr1),
86 ? transform_bexpr(b_ast_cleanup:compute_wd_info_and_norm_record_types(NonGroundExceptions),Expr1,Expr2) -> true
87 ; add_internal_error('Call failed:',clean_up_init(NonGroundExceptions,Expr,_)), Expr2=Expr).
88
89
90 :- use_module(kernel_records,[normalise_record_types/4]).
91 :- use_module(bsyntaxtree,[transform_bexpr/3]).
92 compute_wd_info_and_norm_record_types(NonGroundExceptions,b(E,Type0,I),b(E,Type2,NInfo)) :-
93 ? (member(contains_wd_condition,I) -> NInfo=I
94 ? ; is_possibly_undefined(E)
95 -> NInfo = [contains_wd_condition|I]
96 ; NInfo = I
97 ),
98 (NonGroundExceptions = do_not_ground_types -> Type2=Type0
99 ; ground_type_to_any(Type0,NonGroundExceptions),
100 normalise_record_types(Type0,NonGroundExceptions,Type1,HasRecords),
101 % difference between Type1/0 in test 1906
102 (HasRecords == true,Type1 \= Type0 -> Type2=Type1 ; Type2=Type0)
103 ).
104
105 try_evaluate_set_extension(set_extension(List),Res,LocalIds) :-
106 (extension_should_be_evaluated(List),
107 evaluate_set_extension(List,EvaluatedList,LocalIds),
108 convert_to_avl(EvaluatedList,AVL)
109 % evaluate simple explicit set extensions: avoid storing & traversing position info & AST
110 -> (debug_mode(on) -> format('EVAL SET EXTENSION: ',[]), translate:print_bvalue(AVL),nl ; true),
111 Res=value(AVL)
112 ;
113 Res=set_extension(List) % avoid traversing inside set_extension, can be very large
114 ).
115 try_evaluate_set_extension(set_extension(List),Res,LocalIds) :-
116 (extension_should_be_evaluated(List),
117 evaluate_seq_extension_to_avl(List,AVL,LocalIds)
118 -> (debug_mode(on) -> format('EVAL SEQUENCE EXTENSION: ',[]), translate:print_bvalue(AVL),nl ; true),
119 Res=value(AVL)
120 ; Res=sequence_extension(List) % avoid traversing inside set_extension, can be very large
121 ).
122
123
124 :- use_module(library(ordsets),[ord_nonmember/2, ord_add_element/3]).
125 % apply the clean-up rules to an expression until all
126 % applicable rules are processed
127 % cleanups(Phase,Expr,AppliedRules,Result,Path):
128 % Phase: pre or post or normalize
129 % Expr: the expression to clean up
130 % AppliedRules: a sorted list of clean up rules that have been already applied
131 % and must only be apply once ("single" mode)
132 % Result: the cleaned-up expression
133 % Path: list of outer functors leading to this expression; can be used to decide about applicability of rules
134 cleanups(Phase,Expr,AppliedRules,Result,Path) :-
135 %% print(cleanups(Phase,Expr,AppliedRules,Result,Path)),nl,
136 % set up co-routines that ensure that "Rule" is not applied if
137 % is in the list AppliedRules
138 start_profile_rule(RuleInfos),
139 assure_single_rules(AppliedRules,Mode,Rule),
140 ? ( cleanup_phase(Phase,Expr,NExpr,Mode/Rule,Path) -> % try to apply a rule (matching the current phase)
141 ( Mode==single -> ord_add_element(AppliedRules,Rule,AppRules) % if the rule is marked as "single", we add to the list of already applied rules
142 ; Mode==multi -> AppRules = AppliedRules % if "multi", we do not add it to the list, the rule might be applied more than once
143 ; add_error_fail(b_ast_cleanup,'Unexpected rule mode ',Mode)
144 ),
145 stop_profile_rule(Rule,Mode,Phase,Expr,NExpr,RuleInfos),
146 %(NExpr=b(_,_,I),bsyntaxtree:check_infos(I,Rule) -> true ; true),
147 cleanups(Phase,NExpr,AppRules,Result,Path) % continue recursively with the new expression
148 ; % if no rule matches anymore,
149 Result = Expr, % we leave the expression unmodified
150 Mode=multi, Rule=none). % and unblock the co-routine (see assure_single_rules/3)
151
152
153 :- if(environ(prob_safe_mode,true)).
154 start_profile_rule([R1,W1]) :- statistics(runtime,[R1,_]),statistics(walltime,[W1,_]).
155 stop_profile_rule(Rule,Mode,Phase,Expr,_NExpr,[R1,W1]) :-
156 statistics(runtime,[R2,_]),statistics(walltime,[W2,_]), DeltaW is W2-W1, DeltaR is R2-R1,
157 (DeltaW < 20 -> true ; format('Firing AST cleanup rule ~w (mode:~w) in phase ~w took ~w ms (~w ms walltime)~n',[Rule,Mode,Phase,DeltaR,DeltaW]), translate:print_span(Expr),nl),
158 runtime_profiler:register_profiler_runtime(Rule,ast_cleanup,unknown,DeltaR,DeltaW).
159 % print(fired_rule(Rule,Mode,Phase)),nl, translate:print_bexpr_or_subst(Expr), print(' ===> '),nl, translate:print_bexpr_or_subst(NExpr),nl, print_ast(_NExpr),nl. %% COMMENT IN TO SEE applied RULES <---------------
160 %(map_over_typed_bexpr(b_ast_cleanup:check_valid_result,NExpr) -> true ; true), % comment in to check output after every firing of a rule
161 :- else.
162 start_profile_rule(_).
163 stop_profile_rule(_,_,_,_,_,_).
164 :- endif.
165
166 %check_valid_result(b(xexists([b(identifier(msgXX),integer,_)|_],_),pred,Infos)) :- nonmember(allow_to_lift_exists,Infos),print(missing_info),nl,trace,fail.
167
168 assure_single_rules([],_Mode,_Rule) :- !.
169 assure_single_rules(AppliedRules,Mode,Rule) :-
170 assure_single_rules2(AppliedRules,Mode,Rule).
171 :- block assure_single_rules2(?,-,?),assure_single_rules2(?,?,-).
172 assure_single_rules2(_AppliedRules,_,none) :- !.
173 assure_single_rules2(_AppliedRules,multi,_) :- !.
174 assure_single_rules2(AppliedRules,_,Rule) :-
175 % typically AppliedRules not very long; would also do: \+ member(Rule, AppliedRules).
176 ord_nonmember(Rule,AppliedRules).
177
178 cleanup_phase(Phase,OTExpr,NTExpr,Mode/Rule,Path) :-
179 create_texpr(OExpr,OType,OInfo,OTExpr),
180 check_generated_info(OInfo,entry,Path),
181 create_texpr(NExpr,NType,NInfo,NTExpr),
182 ? cleanup_phase2(Phase,OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule,Path),
183 check_generated_info(NInfo,Rule,Path).
184 cleanup_phase2(normalize,OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule,_Path) :-
185 decompose_rule(Mode_Rule,Mode,Rule),
186 cleanup_normalize(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode_Rule),
187 (debug_mode(off) -> true
188 ; print('Rewritten: '), print_bexpr(b(OExpr,OType,OInfo)),nl,
189 print(' Into: '), print_bexpr(b(NExpr,NType,NInfo)),nl
190 ).
191 cleanup_phase2(pre,OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule,Path) :-
192 decompose_rule(Mode_Rule,Mode,Rule),
193 ? cleanup_pre_with_path(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode_Rule,Path).
194 cleanup_phase2(post,OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule,Path) :-
195 decompose_rule(Mode_Rule,Mode,Rule),
196 ? cleanup_post_with_path(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode_Rule,Path).
197 % check_ast(b(NExpr,NType,NInfo)),nl.
198
199 :- block decompose_rule(-,?,?).
200 decompose_rule(Mode_Rule,Mode,Rule) :-
201 (functor(Mode_Rule,'/',2)
202 -> Mode_Rule = Mode/Rule
203 ; add_internal_error('Illegal cleanup rule, missing mode: ',Mode_Rule),fail).
204
205 check_generated_info(Info,Rule,Path) :-
206 get_preference(prob_safe_mode,true),
207 (select(used_ids(_),Info,I1) -> member(used_ids(_),I1)),!,
208 format('Illegal used ids generated by ~w within ~w~n Infos=~w~n',[Rule,Path,Info]),
209 add_internal_error('Illegal Info generated by rule: ',Rule),
210 fail.
211 check_generated_info(_,_,_).
212
213 clean_up_l_wo_optimizations(Rest,NonGroundExceptions,CRest,SectionName) :-
214 maplist(clean_up_init(NonGroundExceptions),Rest,Rest1),
215 clean_up_l(Rest1,NonGroundExceptions,CRest,top_level(SectionName),1,[]).
216 clean_up_l([],_,[],_Functor,_Nr,_Path).
217 clean_up_l([Expr|Rest],NonGroundExceptions,[CExpr|CRest],Functor,ArgNr,Path) :-
218 ? clean_up_aux(Expr,NonGroundExceptions,CExpr,[path_arg(Functor,ArgNr)|Path]),
219 A1 is ArgNr+1,
220 ? clean_up_l(Rest,NonGroundExceptions,CRest,Functor,A1,Path).
221
222
223 % MAIN ENTRY POINT for b_machine_construction, bmachine_eventb, proz
224 % same as clean_up_l but also applies predicate_level_optimizations
225 % Context is just the name of the section/context in which the optimizations are run
226 clean_up_l_with_optimizations(Rest,NonGroundExceptions,CRest,Context) :-
227 %clean_up_l(Rest,NonGroundExceptions,CRest,top_level,1,[]).
228 ? (clean_up_l_with_opt(Rest,NonGroundExceptions,CleanedUpRest,top_level(Context),1,[]) -> CRest=CleanedUpRest
229 ; add_internal_error('Call failed:',clean_up_l_with_optimizations(Rest,NonGroundExceptions,CRest,Context)),
230 CRest=Rest
231 ).
232 clean_up_l_with_opt([],_,[],_Functor,_Nr,_Path).
233 clean_up_l_with_opt([Expr|Rest],NonGroundExceptions,[CExpr|CRest],Functor,ArgNr,Path) :-
234 %print('Cleaning up: '),translate:print_bexpr_or_subst(Expr),nl,
235 clean_up_init(NonGroundExceptions,Expr,Expr1),
236 ? clean_up_pred_or_expr_with_path(NonGroundExceptions,Expr1,CExpr,[path_arg(Functor,ArgNr)|Path]),
237 A1 is ArgNr+1,
238 ? clean_up_l_with_opt(Rest,NonGroundExceptions,CRest,Functor,A1,Path).
239
240 :- use_module(specfile,[animation_mode/1, animation_minor_mode/1]).
241 % cleanup_pre(OldExpr,OldType,OldInfo,NewExpr,NewType,NewInfo,Mode/Rule)
242
243 % optional normalization rules
244 % These rules are now generated using the prob_rule_compiler
245 %cleanup_normalize(empty_sequence,Type,Info,empty_set,Type,Info, multi/apply_normalization_rule(empty_sequence)). % rule probably not useful as empty_sequence converted to value([])?
246 cleanup_normalize(Expr,Type,Info,NewExpr,NewType,NewInfo, multi/apply_normalization_rule(Rule)) :-
247 b_ast_cleanup_rewrite_rules:normalization_rule_with_rename(Expr,Type,Info,NewExpr,NewType,NewInfo,Rule),
248 (debug_mode(off) -> true
249 ; format('Use rewrite_rule_normalize ~w~n',[Rule]),
250 print_bexpr(b(NewExpr,NewType,NewInfo)),nl
251 ),
252 (ground(NewExpr) -> true
253 ; print(not_ground_rewrite(Rule,Type,Info)),nl,
254 write(Expr),nl, write(' --> '),nl, write(NewExpr),nl,
255 fail).
256
257 never_transform_or_optimise(boolean_false).
258 never_transform_or_optimise(boolean_true).
259 %never_transform_or_optimise(bool_set).
260 never_transform_or_optimise(empty_set).
261 never_transform_or_optimise(empty_sequence). % except for normalization (cf above)
262 never_transform_or_optimise(falsity).
263 %never_transform_or_optimise(max_int).
264 %never_transform_or_optimise(min_int).
265 never_transform_or_optimise(truth).
266 never_transform_or_optimise(identifier(_)).
267 never_transform_or_optimise(integer(_)).
268 never_transform_or_optimise(real(_)).
269 never_transform_or_optimise(string(_)).
270 never_transform_or_optimise(value(_)) :- preferences:preference(normalize_ast, false).
271
272
273 % first check for a few expressions that never need to be optimised, rewritten:
274 cleanup_pre_with_path(E,_,_,_,_,_,_,_) :- never_transform_or_optimise(E),!,fail.
275 % TO DO: think about enabling the following clause
276 cleanup_pre_with_path(exists(AllIds,P),pred,I,exists(AllIds,P),pred,NewI,single/annotate_toplevel_exists,Path) :-
277 % mark the exists inside {paras| #(AllIds).(P)} as allowed to be lifted; relevant for test 1945 (although delayed semi_lifting in b_test_exists_wo_expansion also solves performance issue)
278 Path = [H|_], % TODO: also deal with lambda and other quantifications
279 H=path_arg(comprehension_set/2,1),
280 % % TO DO: add some conditions under which we allow to lift
281 get_preference(data_validation_mode,true), % TODO: check if we cannot enable this more generally
282 (debug_mode(off) -> true ; add_message(b_ast_cleanup,'Marking exists for lifting: ',AllIds,I)),
283 add_info_if_new(I,allow_to_lift_exists,NewI).
284 % mark existential quantifier as outermost: no need to delay it in b_interpreter:b_test_exists_wo_expansion
285 cleanup_pre_with_path(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode_Rule,_) :-
286 ? cleanup_pre(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode_Rule).
287
288 % Now cleanup_pre rules that do not require path:
289
290 cleanup_pre(block(TS),subst,_,Subst,subst,Info,multi/remove_block) :-
291 !,get_texpr_expr(TS,Subst),get_texpr_info(TS,Info).
292 % replace finite by truth
293 cleanup_pre(finite(S),pred,I,truth,pred,[was(finite(S))|I],multi/remove_finite) :-
294 % preferences:get_preference(disprover_mode,false), % keep finite in disprover goals
295 get_texpr_type(S,Type),
296 (typing_tools:is_provably_finite_type(Type) -> true
297 % ; is_infinite_ground_type(Type) -> fail
298 % ; print(no_longer_assuming_finite(Type)),nl,b_global_sets:portray_global_sets,nl,fail
299 ),!. % add_message(ast,'Removed : ',b(finite(S),pred,I),I).
300 /*
301 cleanup_pre(domain(SETC),Type,I,
302 comprehension_set(DomainIds,NewPred),Type,I,multi/dom_let_pred) :-
303 get_texpr_expr(SETC,comprehension_set(CompIds,CompPred)),
304 get_domain_range_ids(CompIds,DomainIds,[RangeId]),
305 get_texpr_ids(CompIds,UnsortedIds), sort(UnsortedIds,Blacklist),
306 conjunction_to_list(CompPred,Preds),
307 select_equality(TId,Preds,Blacklist,Expr,Rest,_UsedIds,check_well_definedness),
308 same_id(TId,RangeId,_),
309 !,
310 LetIds = [RangeId], Exprs = [Expr],
311 conjunct_predicates(Rest,RestPred),
312 NewPred = b(let_predicate(LetIds,Exprs,RestPred),pred,[generated(domain)]),
313 print('Translated dom({...,x|x=E&...}) into: '),
314 print_bexpr(b(comprehension_set(DomainIds,NewPred),Type,[])),nl.
315 */
316 /* strangely enough: this does not seem to buy anything:
317 cleanup_pre(domain(SETC),Type,I,
318 let_expression(LetIds,Exprs,NewExpr),Type,[generated(domain)|I],multi/dom_let_expr) :-
319 get_texpr_expr(SETC,comprehension_set(CompIds,CompPred)),
320 get_domain_range_ids(CompIds,DomainIds,[RangeId]),
321 get_texpr_ids(CompIds,UnsortedIds), sort(UnsortedIds,Blacklist),
322 conjunction_to_list(CompPred,Preds),
323 select_equality(TId,Preds,Blacklist,Expr,Rest,_UsedIds,check_well_definedness),
324 same_id(TId,RangeId,_),
325 !,
326 LetIds = [RangeId], Exprs = [Expr],
327 conjunct_predicates(Rest,RestPred),
328 get_texpr_info(SETC,CInfo),
329 NewExpr = b(comprehension_set(DomainIds,RestPred),Type,CInfo),
330 print('Translated dom({...,x|x=E&...}) into: '), print_bexpr(b(let_expression(LetIds,Exprs,NewExpr),Type,[])),nl.
331 */
332 % exchange quantified union by generalized union
333 cleanup_pre(QUANT,Type,I,
334 let_expression(LetIds,Exprs,NewExpr),Type,[generated(QuantOP)|I],multi/quant_union_inter_let) :-
335 get_preference(optimize_ast,true),
336 quantified_set_operator(QUANT,QuantOP,AllIds,Pred,Expr),
337 conjunction_to_nontyping_list(Pred,Preds),
338 % The ids are needed to build a "black list"
339 get_sorted_ids(AllIds,Ids),
340 find_one_point_rules(AllIds,Preds,Ids,LetIds,Exprs,RestIds,NewPreds),
341 % only succeed if we found at least one id which can be rewritten as let
342 LetIds = [_ID1|_],
343 !,
344 (RestIds=[],NewPreds=[] -> NewExpr=Expr
345 % UNION(x).(x=E|Expr) --> LET x BE x=E in Expr END
346 ; RestIds = [] -> conjunct_predicates_with_pos_info(NewPreds,NewPred),
347 % UNION(x).(x=E & NewPred|Expr) --> LET x BE x=E in IF NewPRED THEN Expr ELSE {} END END
348 NewExpr = b(if_then_else(NewPred,Expr,b(empty_set,Type,[])),Type,I)
349 ; conjunct_predicates_with_pos_info(NewPreds,NewPred),
350 ? quantified_set_operator(NewQUANT,QuantOP,RestIds,NewPred,Expr),
351 NewExpr = b(NewQUANT,Type,I)
352 ),
353 (debug_mode(off) -> true
354 ; print('Translated UNION/INTER into: '), print_bexpr(b(let_expression(LetIds,Exprs,NewExpr),Type,[])),nl).
355 cleanup_pre(quantified_union(Ids,Pred,Expr),Type,I,DomCOMPSET,Type,I,multi/quant_union_into_comprehension) :-
356 singleton_set_extension(Expr,CoupleExpr),
357 nested_couple_to_list(CoupleExpr,List), % we have UNION(..).(...| { A |-> B }) --> List = [A,B]
358 match_ids(List,Ids,AllIds,RestIds),
359 (RestIds = []
360 -> true % UNION(x,y).(x:INTEGER & y=x+1|{x|->y}) --> {x,y| x:INTEGER & y=x+1} = %x.(...).
361 ; % UNION(y,x,z).(x:INTEGER & y=x+1|{x|->y}) --> dom({x,y,z| x:INTEGER & y=x+1})
362 % used to fail test 1101; check on List relevant for test 2359
363 List = [_,_|_] % at least two ids, otherwise use quant_union translation below: ran( %(Ids).(Pred|One) )
364 ),
365 COMPSET = comprehension_set(AllIds,Pred),
366 generate_dom_for_ids(RestIds,COMPSET,Type,I,TDomCOMPSET), % add one dom(.) construct per ID that is projected away
367 (debug_mode(off) -> true
368 ; print('Translated UNION over identifier couples into: '), print_bexpr(TDomCOMPSET),nl),
369 % check_ast(TDomCOMPSET), will complain about redundant typing as we are still in pre phase
370 TDomCOMPSET = b(DomCOMPSET,Type,_).
371 cleanup_pre(quantified_union(Ids,Pred,Expr),Type,I,Res,Type,[was(quantified_union)|I],multi/quant_union_symbolic) :-
372 memberchk(prob_annotation('SYMBOLIC'),I),
373 % UNION(Ids).(Pred|Expr) --> {u| #Ids.(Pred & u:Expr)}
374 get_texpr_set_type(Expr,IdType),
375 !,
376 get_unique_id_inside('__UNION__',Pred,Expr,FRESHID),
377 NewTID = b(identifier(FRESHID),IdType,[]),
378 safe_create_texpr(member(NewTID,Expr),pred,Member),
379 create_exists_opt(Ids,[Pred,Member],Exists),
380 Res = comprehension_set([NewTID],Exists),
381 (debug_mode(off) -> true ; print('UNION @symbolic: '), print_bexpr(b(Res,Type,I)),nl).
382 % exchange quantified union by generalized union
383 cleanup_pre(quantified_union(Ids,Pred,Expr),Type,I,Res,Type,I,multi/quant_union) :-
384 !,
385 ((get_preference(convert_comprehension_sets_into_closures,false), % for test 1101: UNION is a form of let and forces computation at the moment; translating it into a construct without union means that it may be kept symbolic
386 singleton_set_extension(Expr,One) %, debug:bisect(Expr,[1,1,1,1,1,1,1])) % [1,1,1,1,1,1,1] slow; 1,1,0 1,1,1,0 fast
387 )
388 % UNION(Ids).(Pred|{One}) --> ran( %(Ids).(Pred|One) )
389 -> quantified_set_op(Ids,Pred,One,quantified_union,I,TRes),
390 get_texpr_expr(TRes,Res),
391 (debug_mode(off) -> true ; print('UNION - SINGLETON: '), print_bexpr(TRes),nl)
392 ;
393 % UNION(Ids).(Pred|Expr) --> union( ran( %(Ids).(Pred|Expr) ) )
394 quantified_set_op(Ids,Pred,Expr,quantified_union,I,Set),
395 Res = general_union(Set)
396 ).
397 %alternate encoding:
398 %cleanup_pre(quantified_union(Ids,Pred,Expr),Type,I,Set,Type,I,multi/quant_union) :-
399 %poses problem to test 614, 1101
400 % !,quantified_union_op(Ids,Pred,Expr,Type,Set).
401 % exchange quantified intersection by generalized intersection
402 cleanup_pre(quantified_intersection(Ids,Pred,Expr),Type,I,general_intersection(Set),Type,I,multi/quant_inter) :-
403 !,quantified_set_op(Ids,Pred,Expr,quantified_intersection,I,Set).
404 cleanup_pre(function(FUN,Argument),Type,I,Result,Type,I2,RULE) :-
405 ? cleanup_pre_function(FUN,Argument,Type,I,Result,I2,RULE).
406 cleanup_pre(first_projection(A,B),Type,I,Set,Type,[was(prj1),prob_annotation('SYMBOLIC')|I],multi/first_projection) :-
407 !,create_projection_set(A,B,first,Set).
408 cleanup_pre(second_projection(A,B),Type,I,Set,Type,[was(prj2),prob_annotation('SYMBOLIC')|I],multi/second_projection) :-
409 !,create_projection_set(A,B,second,Set).
410 cleanup_pre(event_b_first_projection(Rel),Type,I,Set,Type,[prob_annotation('SYMBOLIC')|I],multi/ev_first_projection) :-
411 !,create_event_b_projection_set(Rel,first,Set).
412 cleanup_pre(event_b_second_projection(Rel),Type,I,Set,Type,[prob_annotation('SYMBOLIC')|I],multi/ev_second_projection) :-
413 !,create_event_b_projection_set(Rel,second,Set).
414 cleanup_pre(event_b_first_projection_v2,Type,I,Set,Type,[prob_annotation('SYMBOLIC')|I],multi/ev2_first_projection) :-
415 !,create_event_b_projection_set_v2(Type,first,Set).
416 cleanup_pre(event_b_second_projection_v2,Type,I,Set,Type,[prob_annotation('SYMBOLIC')|I],multi/ev2_second_projection) :-
417 !,create_event_b_projection_set_v2(Type,second,Set).
418 cleanup_pre(image(Fun,SONE),T,I,Res,T,I,multi/succ_pred_image_optimisation) :-
419 singleton_set_extension(SONE,One), % succ[{h}] --> {h+1} and pred[{h}] --> {h-1} ; useful for alloy2b
420 precompute_pred_succ_function_call(Fun,One,FunOneRes),
421 !,
422 Res = set_extension([b(FunOneRes,integer,I)]).
423 cleanup_pre(union(Lambda1,Lambda2),T,I,lambda(TIDs1,TPred,TVal),T,I,multi/combine_lambdas_if_then_else) :-
424 Lambda1 = b(lambda(TIDs1,TPred1,TValue1),_,_), get_texpr_ids(TIDs1,Ids),
425 Lambda2 = b(lambda(TIDs2,TPred2,TValue2),_,_), get_texpr_ids(TIDs2,Ids),
426 % %x.(P & Cond1 | Val1) \/ %x.(P & not(Cond1) | Val2) ==> %x.(P| IF Cond1 THEN Val1 ELSE Val2 END)
427 conjunction_to_list(TPred1,L1),
428 conjunction_to_list(TPred2,L2),
429 append(Front1,[Last1],L1),
430 append(Front2,[Last2],L2),
431 maplist(same_texpr,Front1,Front2),
432 ? is_negation_of(Last1,Last2),
433 conjunct_predicates_with_pos_info(Front1,TPred),
434 get_texpr_type(TValue1,TV),
435 safe_create_texpr(if_then_else(Last1,TValue1,TValue2),TV,[],TVal),
436 (debug_mode(off) -> true
437 ; format('Union of lambdas converted to if-then-else: ',[]),
438 translate:print_bexpr(b(lambda(TIDs1,TPred,TVal),T,I)),nl
439 ).
440 cleanup_pre(event_b_comprehension_set(Ids,Expr,Pred),T,I,NewExpression,T,
441 [was(event_b_comprehension_set)|I],multi/ev_compset) :-
442 rewrite_event_b_comprehension_set(Ids,Expr,Pred, T, NewExpression).
443 cleanup_pre(domain_restriction(A,B),T,I,identity(A),T,I,multi/event_b_to_normal_identity1) :-
444 /* translate S <| id into id(S) */
445 is_event_b_identity(B).
446 cleanup_pre(range_restriction(B,A),T,I,identity(A),T,I,multi/event_b_to_normal_identity2) :-
447 /* translate id |> S into id(S) */
448 is_event_b_identity(B).
449 % what about translating id(TOTAL TYPE) into event_b_identity ??
450 cleanup_pre(ring(A,B),T,I,composition(B,A),T,I,multi/ring_composition). % replace backward composition by forward compositoin
451 cleanup_pre(less_equal(A,B),pred,I,less_equal_real(A,B),pred,I,multi/remove_ambiguous_leq_real) :-
452 get_texpr_type(A,real).
453 cleanup_pre(greater_equal(A,B),pred,I,less_equal_real(B,A),pred,I,multi/remove_ambiguous_geq_real) :-
454 get_texpr_type(A,real).
455 cleanup_pre(less(A,B),pred,I,less_real(A,B),pred,I,multi/remove_ambiguous_lt_real) :-
456 get_texpr_type(A,real).
457 cleanup_pre(greater(A,B),pred,I,less_real(B,A),pred,I,multi/remove_ambiguous_gt_real) :-
458 get_texpr_type(A,real).
459 cleanup_pre(unary_minus(A),real,I,unary_minus_real(A),real,I,multi/remove_ambiguous_unary_minus_real).
460 cleanup_pre(power_of(A,B),real,I,power_of_real(A,TB),real,I,multi/remove_ambiguous_unary_minus_real) :-
461 get_texpr_type(A,real),
462 safe_create_texpr(convert_real(B),real,[],TB). % TO DO: add pos
463 cleanup_pre(max(A),real,I,max_real(A),real,I,multi/remove_ambiguous_unary_max_real).
464 cleanup_pre(min(A),real,I,min_real(A),real,I,multi/remove_ambiguous_unary_min_real).
465 cleanup_pre(add(A,B),real,I,add_real(A,B),real,I,multi/remove_ambiguous_add_real).
466 cleanup_pre(div(A,B),real,I,div_real(A,B),real,I,multi/remove_ambiguous_div_real).
467
468 cleanup_pre(minus_or_set_subtract(A,B),integer,I,minus(A,B),integer,I,multi/remove_ambiguous_minus_int).
469 cleanup_pre(minus_or_set_subtract(A,B),real,I,minus_real(A,B),real,I,multi/remove_ambiguous_minus_real).
470 cleanup_pre(minus_or_set_subtract(A,B),Type,I,set_subtraction(A,B),Type,I,multi/remove_abiguous_minus_set) :-
471 is_set_type(Type,_).
472 cleanup_pre(mult_or_cart(A,B),integer,I,multiplication(A,B),integer,I,multi/remove_ambiguous_times_int).
473 cleanup_pre(mult_or_cart(A,B),real,I,multiplication_real(A,B),real,I,multi/remove_ambiguous_times_real).
474 cleanup_pre(mult_or_cart(A,B),Type,I,cartesian_product(A,B),Type,I,multi/remove_ambiguous_times_set) :-
475 is_set_type(Type,_).
476 cleanup_pre(E,T,Iin,E,T,Iout,multi/remove_rodinpos) :- % we use multi but can per construction only be applied once
477 selectchk(nodeid(rodinpos(_,[],_)),Iin,Iout). % remove rodinpos information with Name=[]
478 cleanup_pre(partition(X,[Set]),pred,I,equal(X,Set),pred,I,multi/remove_partition_one_element) :-
479 !,
480 % partition(X,Set) <=> X=Set
481 (debug_mode(off) -> true ;
482 print('Introducing equality for partition: '),
483 print_bexpr(X), print(' = '), print_bexpr(Set),nl).
484 cleanup_pre(case(Expression,CASES,Else),subst,I,NewSubst,subst,I,single/rewrite_case_to_if_then_else) :-
485 % translate CASE E OF EITHER e1 THEN ... ---> LET case_expr BE case_expr=E IN IF case_expr=e1 THEN ...
486 get_texpr_type(Expression,EType), get_texpr_info(Expression,EInfo),
487 ExprID = b(identifier(EID),EType,EInfo),
488 (get_texpr_id(Expression,EID)
489 -> NewSubst = if(IFLISTE) % no LET necessary
490 ; NewSubst = let([ExprID],Equal,b(if(IFLISTE),subst,I)),
491 get_unique_id_inside('case_expr',b(case(Expression,CASES,Else),subst,I),EID),
492 safe_create_texpr(equal(ExprID,Expression),pred,Equal)
493 ),
494 (maplist(gen_if_elsif(ExprID),CASES,IFLIST)
495 -> (get_texpr_expr(Else,skip) -> IFLISTE = IFLIST
496 ; TRUTH = b(truth,pred,[]), get_texpr_info(Else,EI),
497 append(IFLIST,[b(if_elsif(TRUTH,Else),subst,EI)],IFLISTE)
498 ),
499 (debug_mode(off) -> true
500 ; print('Translating CASE to IF-THEN-ELSE: '), print_bexpr(Expression),nl
501 %,translate:print_subst(b(NewSubst,subst,[])),nl
502 )
503 ; add_internal_error('Translation of CASE to IF-THEN-ELSE failed: ',CASES),fail
504 ).
505 cleanup_pre(exists(AllIds,Body),pred,I,exists(AllIds,Body),pred,I,single/check_implication_inside_exists) :-
506 is_an_implication(Body,LHS,_RHS),
507 % #x.(P => Q) is true if for some x P is false; usually one intends to write #x.(P & Q)
508 % see tests 1452, 1453 and 1493; Note: typing is always added by Rodin anyway
509 not_generated_exists_paras(AllIds),
510 Ex = b(exists(AllIds,Body),pred,I),
511 ( is_typing_predicate(LHS) % a typing predicate is equivalent to btrue; btrue => RHS is not problematic
512 -> true
513 ; animation_minor_mode(X),(X=eventb ; X=tla)
514 -> add_warning(bmachine_static_checks,'Body of existential quantifier is an implication: ',Ex,I)
515 ? ; member(removed_typing,I) % we have #x.(TYPE & (LHS => RHS)) and exists_body_warning has not triggered
516 -> add_warning(bmachine_static_checks,
517 'Body of existential quantifier corresponds to an implication (after removing typing predicates): ',Ex,I)
518 ; true % bmachine_construction:exists_body_warning already triggered and generated a warning already
519 ).
520 cleanup_pre(exists(AllIds,Body),pred,I0,NewP1,pred,NewI,single/components_partition_exists) :-
521 get_preference(optimize_ast,true),
522 nonmember(partitioned_exists,I0), % avoid re-computing components on something that is already partitioned
523 Simplify=no_cleanup_and_simplify, % avoid loops
524 % Warning: the next call may make use of existing used_ids infos; if they are wrong we may have a problem!
525 b_interpreter_components:construct_optimized_exists(AllIds,Body,NewPred,Simplify,NrC),
526 (NrC = 1 % just one component; perform no change to avoid re-ordering ids, ... ; see test 510
527 -> NewP1=exists(AllIds,Body), NewI=I0
528 ; get_texpr_ids(AllIds,Ids), sort(Ids,SortedIds),
529 add_important_infos_to_exists_conjuncts(NewPred,I0,SortedIds, b(NewP1,pred,NewI)),
530 % important e.g. for test 1945; in particular allow_to_lift_exists
531 % Note: construct_optimized_exists can lift unrelated inner exists out (/ClearSy/2023/perf_0704/rule_genz.mch)
532 (debug_mode(on), NewP1 \= exists(_,_)
533 -> format('PARTITIONED EXISTS:~n ',[]), translate:nested_print_bexpr(b(NewP1,pred,NewI)),nl ; true)
534 ).
535 cleanup_pre(exists(AllIds,P),pred,I,NewP1,pred,I,single/factor_out) :- % REDUNDANT with rule above ??
536 conjunction_to_nontyping_list(P,Preds),
537 % move things which do not depend on AllIds outside
538 % transform, e.g., #(x).(y>2 & x=y) --> y>2 & #(x).(x=y)
539 get_preference(optimize_ast,true),
540 create_exists_opt(AllIds,Preds,b(NewP1,pred,_I),Modified),
541 %(Modified = true -> print(exists(AllIds)),nl,print_bexpr(b(NewP1,pred,_I)),nl),
542 % the rule will fire again on the newly generated sub predicate ! -> fix ?
543 Modified=true.% check if anything modified; otherwise don't fire rule
544
545 cleanup_pre(exists(AllIds,P),pred,Info0,NewP,pred,INew,multi/remove_single_use_equality) :-
546 % remove existentially quantified variables which are defined by an equation and are used only once
547 % e.g., Z1...Z4 in not(#(X,Y,Z,Z1,Z2,Z3,Z4).(X:INTEGER & X*Y=Z1 & Z1*Z = Z2 & Z*X = Z3 & Z3*Y = Z4 & Z2 /= Z4))
548 get_preference(optimize_ast,true),
549 (length_less(AllIds,100) -> true % otherwise the code becomes quite inefficient at the moment
550 ; perfmessage('Large existential quantifier, performing limited optimizations',Info0),
551 fail),
552 conjunction_to_list(P,Preds),
553 CheckWellDef=no_check,
554 ? select_equality(TId,Preds,[],_,IDEXPR,RestPreds,_,CheckWellDef),
555 get_texpr_id(TId,ID),
556 ? select(TIdE,AllIds,RestIds), get_texpr_id(TIdE,ID),
557 can_be_optimized_away(TIdE),
558 \+ occurs_in_expr(ID,IDEXPR), % we cannot inline #x.(x=y+x & ...)
559 always_defined_full_check_or_disprover_mode(IDEXPR), % otherwise we may remove WD issue by removing ID if Count=0 or move earlier/later if count=1
560 single_usage_identifier(ID,RestPreds,Count), % we could also remove if Expr is simple
561 (Count=0 -> debug_println(19,unused_equality_id(ID)),
562 PL=RestPreds
563 ; % Count should be 1
564 conjunct_predicates_with_pos_info(RestPreds,RestPred),
565 ? replace_id_by_expr(RestPred,ID,IDEXPR,E2),
566 conjunction_to_list(E2,PL)
567 ),
568 create_exists_opt(RestIds,PL,TNewP), % no need to computed used ids yet; we could do this:
569 %conjunct_predicates_with_pos_info(PL,PP), safe_create_texpr(exists(RestIds,PP),pred,TNewP),
570 (debug_mode(off) -> true
571 ; format('Remove existentially quantified identifier with single usage: ~w (count: ~w)~n',[ID,Count]), print_bexpr(IDEXPR),nl),
572 TNewP = b(NewP,pred,INew),!.
573 cleanup_pre(exists(AllIds,P),pred,I,let_predicate(LetIds,Exprs,NewP),pred,INew,multi/exists_to_let) :-
574 % rewrite predicates of the form #x.(x=E & P(x)) into (LET x==E IN P(x))
575 % side condition for #(ids).(id=E & P(ids)): no identifiers of ids occur in E
576 get_preference(optimize_ast,true),
577 conjunction_to_nontyping_list(P,Preds), % TO DO: avoid recomputing again (see line in clause above)
578 % The ids are needed to build a "black list"
579 get_sorted_ids(AllIds,Ids),
580 find_one_point_rules(AllIds,Preds,Ids,LetIds,Exprs,RestIds,NewPreds),
581 % no_check is not ok in the context of existential quantification and reification:
582 % #x.(1:dom(f) & x=f(1) & P) --> LET x=f(1) IN 1:dom(f) & P END
583 % it is not ok if the whole predicate gets reified in b_intepreter_check !! Hence we use always_defined_full_check_or_disprover_mode; see Well_def_1.9.0_b5 in private_examples
584 % only succeed if we found at least one id which can be rewritten as let
585 LetIds = [ID1|_],
586 !,
587 (atomic(ID1) -> add_internal_error(cleanup_pre,unwrapped_let_identifier(ID1)), INew=I
588 ; get_texpr_ids(LetIds,AtomicIDs),
589 remove_used_ids_from_info(AtomicIDs,I,INew)
590 ), % probably not necessary ?!
591 % see also the annotate_toplevel_exists rule above which adds allow_to_lift_exists; relevant, e.g., for test 1945
592 ? (member(allow_to_lift_exists,I) -> AddInfos=[allow_to_lift_exists] ; AddInfos=[]),
593 create_exists_opt(RestIds,NewPreds,AddInfos,NewP,_Modified),
594 (debug_mode(off) -> true
595 ; format('Extracted LET over ~w from exists (rest: ~w):~n ',[AtomicIDs,RestIds]),
596 translate:print_bexpr(b(let_predicate(LetIds,Exprs,NewP),pred,I)),nl
597 ).
598 % now the same LET extraction but for universal quantification:
599 cleanup_pre(forall(AllIds,P,Rhs),pred,I,let_predicate(LetIds,Exprs,NewP),pred,I,multi/forall_to_let) :-
600 get_preference(optimize_ast,true),
601 conjunction_to_nontyping_list(P,Preds),
602 % The ids are needed to build a "black list"
603 get_sorted_ids(AllIds,Ids),
604 check_forall_lhs_rhs(P,Rhs,I,Ids),
605 find_one_point_rules(AllIds,Preds,Ids,LetIds,Exprs,RestIds,NewPreds),
606 % only succeed if we found at least one id which can be rewritten as let
607 LetIds = [ID1|_],!,
608 (atomic(ID1) -> add_internal_error(cleanup_pre,unwrapped_let_identifier(ID1)) ; true),
609 conjunct_predicates_with_pos_info(NewPreds,NewLhs),
610 create_implication(NewLhs,Rhs,NewForallBody),
611 create_forall(RestIds,NewForallBody,NewP),
612 (debug_mode(on) -> print('Introduced let in forall: '), print(LetIds),nl ; true).
613 % warning: used_identifier information not yet computed; translate may generate warnings
614 cleanup_pre(exists(AllIds,P),pred,I0,NewPE,pred,NewI,multi/exists_remove_typing) :-
615 (is_a_conjunct(P,Typing,Q) ; is_an_implication(P,Typing,Q)),
616 % TRUE & Q == TRUE => Q == Q
617 is_typing_predicate(Typing),
618 % remove typing so that other exists rules can fire
619 % we run as cleanup_pre: the other simplifications which remove typing have not run yet
620 % such typing conjuncts typicially come from Rodin translations
621 create_exists_opt(AllIds,[Q],b(NewPE,_,I1)),
622 add_important_info_from_super_expression(I0,I1,I2), % we could also copy node_id(_) from I0 ?
623 add_removed_typing_info(I2,NewI).
624 cleanup_pre(exists(AllIds,P),pred,I,disjunct(NewP1,NewP2),pred,I,single/partition_exists_implication) :-
625 is_a_disjunct_or_implication(P,_Type,Q,R),
626 /* note that even if R is only well-defined in case Q is false; it is ok to seperate this out
627 into two existential quantifiers: #x.(x=0 or 1/x=10) is ok to transform into #x.(x=0) or #x.(1/x=10) */
628 % this slows down test 1452, Cylinders, 'inv3/WD'; TO DO:investigate
629 create_exists_opt(AllIds,[Q],NewP1), % print('Q: '),print_bexpr(NewP1),nl,
630 create_exists_opt(AllIds,[R],NewP2). %, print('R: '),print_bexpr(NewP2),nl.
631 cleanup_pre(exists([B],P),pred,I,truth,pred,I,single/tautology_exists_min_max) :-
632 % ∃b·∀x0·(x0 ∈ FINITE ⇒ b ≤ x0) == TRUE : WD condition from Rodin for max; similar for min (TODO: check min)
633 B = b(identifier(ID1),integer,_),
634 get_texpr_expr(P,forall([X0],Left,Right)),
635 X0 = b(identifier(ID2),integer,_),
636 get_texpr_expr(Left,member(X1,FiniteSet)),
637 get_texpr_id(X1,ID2),
638 Right = b(COMP,pred,_),
639 (COMP = less_equal(B2,X2) ; COMP = greater_equal(B2,X2)),
640 get_texpr_id(B2,ID1), get_texpr_id(X2,ID2),
641 definitely_finite(FiniteSet),
642 (debug_mode(off) -> true ; format('Removing WD condition for min/max exists over ~w :',[ID1]), translate:print_bexpr(P),nl).
643 cleanup_pre(forall(AllIds,P,Rhs),pred,I,NewPred,pred,I,multi/forall_to_post_let) :-
644 % translate something like !(x,y).(y:1..100 & x=y*y => x<=y) into !(y).(y : 1 .. 100 => (#(x).( (x)=(y * y) & x <= y)))
645 post_let_forall(AllIds,P,Rhs,NewPred,modification),
646 !,
647 (debug_mode(on) -> print('POST LET INTRODUCTION: '), print_bexpr(b(NewPred,pred,[])),nl ; true).
648 cleanup_pre(set_extension(List),Type,I, set_extension(NList),Type,I, single/remove_pos) :-
649 remove_position_info_from_list(List,I,NList),!.
650 cleanup_pre(sequence_extension(List),Type,I, sequence_extension(NList),Type,I, single/remove_pos) :-
651 remove_position_info_from_list(List,I,NList),!.
652 cleanup_pre(if(List),Type,I, if(NList),Type,I, single/remove_if_elsif_pos) :-
653 % the pos info is not used for individual if_elsif entries; some models contain very large if-then-else constructs
654 maplist(remove_top_levelposition_info,List,NList),!.
655 %cleanup_pre(concat(A,B),string,I,Res,string,I,multi/concat_assoc_reorder) :-
656 % A = b(concat(A1,A2),string,I1),
657 % !, % reorder STRING concats for better efficiency, can only occur when allow_sequence_operators_on_strings is true
658 % % TO DO: extract information I2B from A2 and B
659 % Res = concat(A1,b(concat(A2,B),string,I2B)).
660 cleanup_pre(typeset,SType,I,Expr,SType,I,multi/remove_typeset) :- !,
661 % used, e.g., in test 1205 for recursive Event-B operator definition
662 ( ground(SType) ->
663 (is_set_type(SType,Type),
664 create_maximal_type_set(Type,b(MaxExpr,_,_)) -> Expr=MaxExpr
665 ; is_set_type(SType,Type) ->
666 add_error_and_fail(b_ast_cleanup,'Creating type expression for typeset failed: ',Type)
667 ;
668 add_error_and_fail(b_ast_cleanup,'Creating type expression for typeset failed, type is not a set: ',SType)
669 )
670 ; add_error_and_fail(b_ast_cleanup,'Non-ground type for typeset expression: ',SType)).
671 cleanup_pre(integer_set(S),Type,I,Expr,Type,[was(integer_set(S))|I],multi/remove_integer_set) :- !,
672 translate_integer_set(S,I,Expr),
673 (debug_mode(off) -> true
674 ; format('Rewrite ~w to: ',[S]),
675 print_bexpr(b(Expr,integer,I)),nl).
676 % should we move the rewrite_rules to normalize ??
677 cleanup_pre(Expr,Type,Info,NewExpr,NewType,NewInfo, multi/apply_rewrite_rule(Rule)) :-
678 ? rewrite_rule_with_rename(Expr,Type,Info,NewExpr,NewType,NewInfo,Rule), % from b_ast_cleanup_rewrite_rules
679 (debug_mode(off) -> true
680 ; format('Use rewrite_rule ~w~n',[Rule]),
681 print_bexpr(b(NewExpr,NewType,NewInfo)),nl),
682 (ground(NewExpr) -> true ; print(not_ground_rewrite(NewExpr)),nl,fail).
683 % 'x > y' to 'y < x'
684 cleanup_pre(greater(Lhs,Rhs), pred, I, less(Rhs,Lhs), pred, [was(greater(Lhs,Rhs))|I], single/normalize_greater) :-
685 preferences:get_preference(normalize_ast, true).
686 % 'x >= y' to 'y <= x'
687 cleanup_pre(greater_equal(Lhs,Rhs), pred, I, less_equal(Rhs,Lhs), pred, [was(greater_equal(Lhs,Rhs))|I], single/normalize_greater_equal) :-
688 preferences:get_preference(normalize_ast, true).
689 % 'x - y' to 'x + -y'
690 cleanup_pre(minus(Lhs,Rhs), integer, I, add(Lhs,b(unary_minus(Rhs),integer,[])), integer, [was(minus(Lhs,Rhs))|I], single/normalize_minus) :-
691 preferences:get_preference(normalize_ast, true).
692 cleanup_pre(value(CLOSURE), Type, I, comprehension_set(TIDs,B), Type, I, single/normalize_value_closure) :-
693 nonvar(CLOSURE), CLOSURE=closure(P,T,B),
694 preferences:get_preference(normalize_ast, true),
695 create_typed_ids(P,T,TIDs).
696 cleanup_pre(comprehension_set(TIDs,Body), Type, I, union(Set1,Set2), Type,I, single/extract_union) :-
697 preferences:get_preference(normalize_ast, true),
698 is_a_disjunct(Body,B1,B2), % should we also detect set difference, should we detect common prefix typing
699 % {x| P or Q} ==> {x|P} \/ {x|Q}
700 % such closure values are created by symbolic union, relevant for JSON trace replay for test 281
701 safe_create_texpr(comprehension_set(TIDs,B1),Type,I,Set1),
702 safe_create_texpr(comprehension_set(TIDs,B2),Type,I,Set2).
703 cleanup_pre(external_function_call('ASSERT_EXPR',[BOOL,MSG,EXPR]), Type, I,
704 assertion_expression(Pred,MsgStr,EXPR), Type,I, single/detect_assertion_expression) :-
705 % translate ASSERT_EXPR back to assertion_expression; dual to way it is printed in pretty printer
706 get_pred_from_bool(BOOL,Pred),
707 ? get_string(MSG,MsgStr).
708 cleanup_pre(external_pred_call(PRED,ARGS), pred, I,
709 EQ, pred,I, single/rewrite_external_pred_to_bool_function) :-
710 preferences:get_preference(normalize_ast,true),
711 synonym_for_external_predicate(PRED,FUNC),
712 % replace PRED(ARGS) by bool(FUNC(ARGS)=TRUE) as external functions can always be used wo DEFINITIONS
713 safe_create_texpr(external_function_call(FUNC,ARGS),boolean,[],FUNCALL),
714 EQ = equal(FUNCALL,b(boolean_true,boolean,[])),
715 (debug_mode(off) -> true ; print('REWRITTEN external predicate call to '), print_bexpr(FUNCALL),nl).
716
717
718 % Cleanup PRE for function calls:
719 % In reply to PROB-240: Check if arguments of Prj1/2 are types only using is_just_type:
720 cleanup_pre_function(TProjection,Argument,_Type,I,Result,I,multi/projection_call) :-
721 get_texpr_expr(TProjection,Projection),
722 cleanup_function_projection(Projection,Argument,I,Result),
723 !.
724 cleanup_pre_function(Lambda,Argument,Type,I,NewContextExpr,I,multi/lambda_guard1) :-
725 get_preference(optimize_ast,true),
726 get_texpr_expr(Lambda,LambdaExpr),
727 is_lambda_in_context(LambdaExpr,Type,TIds,TPre,TVal,NewContextExpr,NewExpr,LocalIds),
728 (is_just_typing_pred(TPre)
729 -> TPre1 = b(truth,pred,[]), % relevant for replace count below
730 get_texpr_expr(TVal,AssertionExpr)
731 ; TPre1=TPre,
732 AssertionExpr = assertion_expression(TPre1,ErrMsg,TVal)
733 ),
734 get_texpr_ids(TIds,Ids),
735 nested_couple_to_list(Argument,ArgList),
736 % translate %x.(TPre|TVal)(arg) -> LET x BE x=arg IN ASSERT_EXPR(TPre,Msg,TVal) END
737 same_length(ArgList,TIds),
738 \+ some_id_occurs_in_expr(LocalIds,Argument), % would trigger here LET x BE x=1+1 IN %y.(y:0..x|y+x+x) END (x) = res & x=0
739 ( same_ids_and_types(ArgList,TIds)
740 -> % lambda argument names and provided arguments are identical
741 NewExpr = AssertionExpr % no LET has to be introduced; relevant e.g. for rule_sgc335.mch
742 ; \+ ( sort(Ids,SIds),
743 some_id_occurs_in_expr(SIds,Argument)
744 %,format('Not inlining lambda, parameter id ~w occurs in : ',[Id]), print_bexpr(Argument),nl
745 %, add_message(ast_cleanup,'Not inlining parameter: ',Id,I)
746 ), % otherwise name clash and we would need a LET that can treat LET x BE x=x+1
747 TAssertionExpr = b(AssertionExpr,Type,I),
748 NewExpr = let_expression(TIds,ArgList,TAssertionExpr)
749 ; Ids = [Id1], ArgList = [Arg1] ->
750 %TODO: safely treat multiple args and things like (%(x,v).(x:INTEGER|x*v)(v|->v))=100
751 % In this case we need to substitute all args in one go
752 replace_id_by_expr_with_count(TPre1,Id1,Arg1,TPre2,Count1),
753 replace_id_by_expr_with_count(TVal,Id1,Arg1,TVal2,Count2),
754 Count is Count1+Count2,
755 ? is_replace_id_by_expr_ok(Arg1,Id1,Count,lambda_guard1),
756 NewExpr = assertion_expression(TPre2,ErrMsg,TVal2)
757 ),
758 % simplify_let will remove simple let expressions and vars used only once
759 % we used to call replace_ids_by_args in all cases, but this can duplicate arguments
760 % not replacing did lead to test 1284 taking very long, 191 seconds instead of 0.3 for 192 states
761 !,
762 ajoin_with_sep(Ids,',',IdsAtom),
763 get_texpr_info(Lambda,LambdaInfo), translate_span(LambdaInfo,LSpan),
764 (get_definition_context_from_span(LambdaInfo,LSpan2)
765 -> ajoin(['lambda function %(',IdsAtom,') ',LSpan,' (', LSpan2,
766 ') called outside of domain, condition false: '],ErrMsg)
767 ; ajoin(['lambda function %(',IdsAtom,') ',LSpan,
768 ' called outside of domain, condition false: '],ErrMsg)),
769 (debug_mode(off) -> true
770 ; add_message(ast_cleanup,'INLINED function application for: ',Ids,I),
771 translate:nested_print_bexpr(b(NewExpr,Type,I)),nl
772 ).
773 cleanup_pre_function(Fun,Arg,integer,I,ArithOp,NewI,multi/succ_pred_optimisation) :-
774 precompute_pred_succ_function_call(Fun,Arg,ArithOp),
775 delete(I,contains_wd_condition,NewI). % we no longer have a WD condition; succ/pred are totally defined
776 /* cleanup_pre(event_b_comprehension_set([ID],ID,Pred),T,I,comprehension_set([Result],NewPred),T,
777 [was(event_b_comprehension_set)|I],multi/ev_compset_single_id) :-
778 % Event_B_Comprehension with a single ID which is also the expression
779 % TO DO: expand for multiple IDs
780 !,
781 Result = ID, NewPred=Pred. */
782 % Detect if_then_else; also done in cleanup_post (in pre we may be able to detect IF-THEN-ELSE before CSE has inserted lazy_lets
783 cleanup_pre_function(IFT,DUMMYARG,_Type,Info,if_then_else(IFPRED,THEN,ELSE),Info,multi/function_if_then_else) :-
784 is_if_then_else(IFT,pre,DUMMYARG,IFPRED,THEN,ELSE),
785 (debug_mode(off) -> true
786 ; print('% Recognised if-then-else expression (pre): IF '), print_bexpr(IFPRED),
787 print(' THEN '),print_bexpr(THEN), print(' ELSE '), print_bexpr(ELSE),nl
788 ).
789
790 % check if we detect a lambda or a lambda wrapped inside let_expressions
791 % e.g., LET one BE one=1 IN LET two BE two=2 IN %(x).(x:INTEGER|x+one+one+two+two)END END(y) = 7
792 % NewType: by moving the function application into the LETs the type of the LETs need to be adapted
793 is_lambda_in_context(let_expression(LetIds,Exprs,b(Lambda,_OldType,Info)),NewType,TIds,TPred,TValue,
794 let_expression(LetIds,Exprs,b(InnerCtxt,NewType,Info)),Hole,NewLocalIds) :- !,
795 is_lambda_in_context(Lambda,NewType,TIds,TPred,TValue,InnerCtxt,Hole,LocalIds),
796 get_texpr_ids(LetIds,Ids),
797 sort(Ids,SIds),
798 ord_union(SIds,LocalIds,NewLocalIds).
799 is_lambda_in_context(Lambda,_NewType,TIds,TPred,TValue,Context,ReplacementHole,[]) :-
800 Context=ReplacementHole,
801 is_lambda(Lambda, TIds, TPred,TValue).
802
803 :- use_module(closures,[is_lambda_closure/7, is_lambda_comprehension_set/4]).
804 is_lambda(lambda(TIds,TPred,TValue), TIds, TPred,TValue) :- !.
805 is_lambda(event_b_comprehension_set([TId],Expr,TPred), [TId], TPred, TValue) :- !,
806 % rewrite_event_b_comprehension_set does not seem to get called before the function/lambda rule is applied
807 % {ID.ID|->Val | PRed}
808 Expr = b(couple(LHS,RHS),_,_),
809 same_texpr(LHS,TId),
810 TValue=RHS.
811 is_lambda(value(Closure),[TId],TPred,TValue) :- !, nonvar(Closure), Closure = closure(Args,Types,Body),
812 is_lambda_closure(Args,Types,Body, [OtherID], [OtherType], TPred, TValue),
813 create_typed_id(OtherID,OtherType,TId). % TODO: accept lambdas with more than one argument TId
814 is_lambda(CompSet,TIds,Pred,Val) :- CompSet=comprehension_set(_,_),
815 is_lambda_comprehension_set(b(CompSet,any,[]),TIds,Pred,Val).
816
817 is_just_typing_pred(b(E,_,_)) :- is_just_typing_pred2(E).
818 is_just_typing_pred2(truth).
819 is_just_typing_pred2(conjunct(A,B)) :- is_just_typing_pred(A), is_just_typing_pred(B).
820 is_just_typing_pred2(member(_,B)) :- is_just_type(B). % would be removed by remove_type_member rule
821
822
823 :- use_module(external_function_declarations,[synonym_for_external_predicate/2]).
824
825 get_string(b(string(S),_,_),S).
826 get_string(b(value(V),_,_),S) :- nonvar(V), V=string(Str), atom(Str), S=Str.
827 % translate a boolean value into a predicate:
828 get_pred_from_bool(b(convert_bool(P),_,_),Pred) :- !, Pred=P.
829 get_pred_from_bool(BOOL,b(equal(BOOL,BTRUE),pred,[])) :- BTRUE = b(boolean_true,boolean,[]).
830
831 translate_integer_set('NAT',I,interval(b(integer(0),integer,I),b(max_int,integer,I))).
832 translate_integer_set('NAT1',I,interval(b(integer(1),integer,I),b(max_int,integer,I))).
833 translate_integer_set('INT',I,interval(b(min_int,integer,I),b(max_int,integer,I))).
834 %translate_integer_set('INTEGER',I,comprehension_set([b(identifier('_zzzz_unary'),integer,I)],
835 % b(truth,pred,[prob_annotation('SYMBOLIC')|I]))).
836 %translate_integer_set('NATURAL',I,comprehension_set([b(identifier('_zzzz_unary'),integer,I)],
837 % b(greater_equal(b(identifier('_zzzz_unary'),integer,I),
838 % b(integer(0),integer,I)),pred,[prob_annotation('SYMBOLIC')|I]))).
839 %translate_integer_set('NATURAL1',I,comprehension_set([b(identifier('_zzzz_unary'),integer,I)],
840 % b(greater_equal(b(identifier('_zzzz_unary'),integer,I),
841 % b(integer(1),integer,I)),pred,[prob_annotation('SYMBOLIC')|I]))).
842
843 % detect if an expression is equivalent to an integer set, does not check for interval yet
844 is_integer_set(integer_set(S),S).
845 is_integer_set(comprehension_set([b(identifier(ID),integer,_)],b(B,_,_)),S) :-
846 ? is_integer_set_constraint_pred(B,ID,S).
847 is_integer_set_constraint_pred(truth,_,'INTEGER').
848 is_integer_set_constraint_pred(Expr,ID,Set) :-
849 is_greater_equal(Expr,b(identifier(ID),integer,_),TNr),
850 get_integer(TNr,Nr),
851 (Nr=0 -> Set='NATURAL' ; Nr=1 -> Set='NATURAL1').
852 is_integer_set_constraint_pred(Expr,ID,Set) :-
853 is_greater(Expr,b(identifier(ID),integer,_),TNr),
854 get_integer(TNr,Nr),
855 (Nr = -1 -> Set='NATURAL' ; Nr=0 -> Set='NATURAL1').
856
857 is_greater_equal(greater_equal(A,B),A,B).
858 is_greater_equal(less_equal(B,A),A,B).
859 is_greater(greater(A,B),A,B).
860 is_greater(less(B,A),A,B).
861
862 is_inf_integer_set_with_lower_bound(b(X,_,_),Bound) :- is_integer_set(X,N),
863 (N='NATURAL' -> Bound=0 ; N='NATURAL1' -> Bound=1).
864
865
866
867 is_subset(subset(A,B),A,B).
868 is_subset(member(A,b(pow_subset(B),_,_)),A,B). % x : POW(T) <=> x <: T
869
870 % tool to translate CASE values to Test predicates for IF-THEN-ELSE
871 gen_if_elsif(CaseID,b(case_or(ListOfValues, Body),_,I),
872 b(if_elsif(Test,Body),subst,I)) :-
873 get_texpr_type(CaseID,T),
874 SEXT = b(set_extension(ListOfValues),set(T),I),
875 Test = b(member(CaseID,SEXT),pred,I).
876
877 % the case below happens frequently in data validation:
878 remove_position_info_from_list(List,I,NList) :-
879 member(nodeid(pos(C,FilePos,Line,From,Line,To)),I),
880 To-From > 1000, % the entire set/sequence extension is on one large line
881 length(List,Len), Len>100, % it has many elements
882 % we replace all position infos by the same top-level position info (enabling sharing)
883 maplist(remove_position_info(nodeid(pos(C,FilePos,Line,From,Line,To))),List,NList),
884 (debug_mode(off) -> true
885 ; format('SIMPLIFY POSITION INFO IN SET/SEQUENCE EXTENSION: line # ~w, length ~w~n',[Line,Len])).
886 remove_position_info(NI,b(Expr,Type,Infos),b(NExpr,Type,NewInfos)) :-
887 syntaxtransformation(Expr,Subs,_Names,NSubs,NExpr),
888 (select(nodeid(pos(_,_FilePos,_,_,_,_)),Infos,NT) -> NewInfos=[NI|NT] ; NewInfos=Infos),
889 maplist(remove_position_info(NI),Subs,NSubs).
890
891 :- use_module(bsyntaxtree,[delete_pos_info/2]).
892 % just remove position infos from top-lefel
893 remove_top_levelposition_info(b(Expr,Type,Infos),b(Expr,Type,NewInfos)) :-
894 delete_pos_info(Infos,NewInfos). % TODO: maybe remove other useless infos
895
896 % rules for function application of various projection functions
897 cleanup_function_projection(first_projection(A,B),Argument,I,Result) :-
898 gen_assertion_expression(A,B,Argument,first_of_pair(Argument),first,I,Result).
899 cleanup_function_projection(second_projection(A,B),Argument,I,Result) :-
900 gen_assertion_expression(A,B,Argument,second_of_pair(Argument),second,I,Result).
901 cleanup_function_projection(event_b_second_projection(A),Argument,_I,Result) :- % old style Rodin projection
902 check_is_just_type(A),Result = first_of_pair(Argument).
903 cleanup_function_projection(event_b_second_projection(A),Argument,_I,Result) :- % old style Rodin projection
904 check_is_just_type(A),Result = second_of_pair(Argument).
905 cleanup_function_projection(event_b_first_projection_v2,Argument,_I,Result) :- Result = first_of_pair(Argument).
906 cleanup_function_projection(event_b_second_projection_v2,Argument,_I,Result) :- Result = second_of_pair(Argument).
907
908 check_is_just_type(_A) :- preferences:get_preference(ignore_prj_types,true),!.
909 check_is_just_type(A) :- (is_just_type(A) -> true ; debug_println(9,not_type_for_prj(A)),fail).
910
911 :- use_module(bsyntaxtree,[get_texpr_set_type/2, create_cartesian_product/3]).
912 gen_assertion_expression(A,B,_Argument,ProjExpr,_ProjType,_I,Result) :-
913 check_is_just_type(A),check_is_just_type(B),
914 !,
915 Result = ProjExpr.
916 % TO DO: add simplification rule for couple(x,y) : A*B with A or B being just types
917 gen_assertion_expression(A,B,Argument,ProjExpr,ProjType,Info,Result) :-
918 create_cartesian_product(A,B,CartAB),
919 safe_create_texpr(member(Argument,CartAB),pred,MemCheck),
920 ErrMsg = 'projection function called outside of domain: ', % TO DO: provide better user message with Argument result
921 perfmessage('Projection function has WD condition which needs to be checked at runtime (use prj1/prj2 without arguments or set IGNORE_PRJ_TYPES preference to TRUE)',Info),
922 (ProjType == first -> get_texpr_set_type(A,TT) ; get_texpr_set_type(B,TT)), %%
923 %get_texpr_pos_infos(Argument,Info), % add position infos
924 extract_pos_infos(Info,PosInfo),
925 safe_create_texpr(ProjExpr,TT,PosInfo,TProjExpr),
926 Result = assertion_expression(MemCheck,ErrMsg,TProjExpr).
927
928
929
930 % rewriting Event-B comprehension sets into classical B style ones
931 rewrite_event_b_comprehension_set(IDs,CoupleExpr,Pred, _T, NewExpression) :-
932 % detect lambda expressions in classical B style
933 nested_couple_to_list(CoupleExpr,List),
934 check_ids(IDs,List,Expr),!,
935 NewExpression = lambda(IDs,Pred,Expr).
936 rewrite_event_b_comprehension_set(IDList,CoupleExpr,Pred, _T, NewExpression) :-
937 % Event_B_Comprehension with a several IDs which are also used as the couple expression
938 nested_couple_to_list(CoupleExpr,List),
939 List = IDList,
940 !,
941 NewExpression = comprehension_set(IDList,Pred).
942 rewrite_event_b_comprehension_set(Ids,Expr,Pred, T, NewExpression) :-
943 NewExpression = comprehension_set([Result],NewPred),
944 unify_types_strict(T,set(Type)),
945 % print(event_b_comprehension_set(Ids,Expr,Pred)),nl,
946 ? (select(Expr,Ids,RestIds)
947 -> % the Expr is an identifier which is part of Ids: we can avoid complicated translation below
948 % example {f,n•n:INT & f:1..n-->Digit|f} --translated-> {f|#(n).(n:INT & f:1..n-->Digit)}
949 % print(remove(Expr,RestIds)),nl,
950 ExPred=Pred, Result=Expr
951 ; get_unique_id_inside('__comp_result__',Pred,Expr,ResultId),
952 create_texpr(identifier(ResultId),Type,[],Result),
953 safe_create_texpr(equal(Result,Expr),pred,Equal),
954 conjunct_predicates_with_pos_info(Pred,Equal,ExPred), % put Equal after Pred for WD; used to be other order!
955 RestIds=Ids
956 ),
957 create_exists(RestIds,ExPred,NewPred). %, print(done_rewrite_event_b_comprehension_set),nl, print_bexpr(NewPred),nl.
958
959 check_ids([],[CoupleExpr],CoupleExpr). % we terminate with a single expression
960 check_ids([ID|T],[CoupleExprID|CT],Rest) :-
961 same_id(ID,CoupleExprID,_),
962 check_ids(T,CT,Rest).
963
964
965 evaluate_seq_extension_to_avl(List,AVL,LocalIds) :-
966 evaluate_set_extension(List,EvaluatedList,LocalIds),
967 convert_set_to_seq(EvaluatedList,1,ESeq),
968 convert_to_avl(ESeq,AVL).
969
970 evaluate_set_extension([],[],_).
971 evaluate_set_extension([H|List],[EH|EvaluatedList],LocalIds) :-
972 eval_set_extension_element(H,EH,LocalIds),
973 evaluate_set_extension(List,EvaluatedList,LocalIds).
974
975 extension_should_be_evaluated(List) :-
976 %preferences:has_default_value(use_solver_on_load), % Kodkod could not translate booleans back; now it can; check if we still need this
977 preferences:get_preference(optimize_ast,true),
978 List \= [],
979 List = [_|ListT], ListT \= []. % do not do this for singleton sets so as not to prevent triggering of other rules
980
981 :- use_module(kernel_reals,[construct_real/2, construct_negative_real/2]).
982 % construct a value term for a simple AST element:
983 eval_set_extension_element(b(E,T,_I),EE,LocalIds) :-
984 (eval_set_extension_aux(E,EE,LocalIds) -> true
985 ; eval_set_extension_typed_aux(E,T,EE,LocalIds)
986 % ; print('eval_set_extension failed: '),tools_printing:print_term_summary(E),nl,translate:print_span(_I),nl,fail
987 ).
988 eval_set_extension_aux(boolean_false,pred_false,_).
989 eval_set_extension_aux(boolean_true,pred_true,_).
990 eval_set_extension_aux(couple(A,B),(EA,EB),LocalIds) :-
991 eval_set_extension_element(A,EA,LocalIds), eval_set_extension_element(B,EB,LocalIds).
992 eval_set_extension_aux(integer(I),int(I),_).
993 eval_set_extension_aux(real(Atom),Real,_) :- construct_real(Atom,Real).
994 eval_set_extension_aux(unary_minus(b(Val,_,_)),Res,_) :- eval_set_ext_minus(Val,Res).
995 eval_set_extension_aux(string(S),string(S),_).
996 eval_set_extension_aux(empty_set,[],_).
997 eval_set_extension_aux(empty_sequence,[],_).
998 eval_set_extension_aux(value(V),V,_).
999 eval_set_extension_aux(rec(Fields),rec(EF),LocalIds) :- eval_set_extension_fields(Fields,EF,LocalIds).
1000 %eval_set_extension_aux(interval(A,B),...) :- ...
1001 eval_set_extension_aux(set_extension(List),AVL,LocalIds) :-
1002 evaluate_set_extension(List,EvaluatedList,LocalIds),
1003 convert_to_avl(EvaluatedList,AVL).
1004 eval_set_extension_aux(sequence_extension(List),AVL,LocalIds) :-
1005 evaluate_seq_extension_to_avl(List,AVL,LocalIds).
1006
1007
1008 :- use_module(probsrc(kernel_freetypes),[registered_freetype_case_value/3, freetype_case_db/3]).
1009 eval_set_extension_typed_aux(identifier(ID),TYPE,FDVal,LocalIds) :- LocalIds \= not_available,
1010 (TYPE = global(GType)
1011 -> b_global_sets:lookup_global_constant(ID,FDVal),
1012 ord_nonmember(ID,LocalIds),
1013 % we could check if enumerated_set_element entry in infos, cf is_just_type3 with given_set info
1014 % may not yet be fully precompiled, hence we rely on pre_register_enumerated_set_with_elems
1015 FDVal = fd(_,GType) % just check that the type matches, in case ID is a local name with different type
1016 ; TYPE = freetype(FType)
1017 -> % see b_global_set_or_free_type; we could also accept global sets and freetype sets
1018 registered_freetype_case_value(ID,TYPE,FDVal),
1019 ord_nonmember(ID,LocalIds),
1020 FDVal = freeval(FType,_,_) % check type matches
1021 ).
1022 eval_set_extension_typed_aux(function(TID,Args),freetype(FreetypeId),V,LocalIds) :- LocalIds \= not_available,
1023 ground(FreetypeId),
1024 get_texpr_id(TID,CaseId),
1025 freetype_case_db(CaseId,FreetypeId,_CaseType),
1026 ord_nonmember(CaseId,LocalIds),
1027 %write(case(CaseId,FreetypeId,CaseType)),nl,
1028 eval_set_extension_element(Args,EArgs,LocalIds),
1029 V = freeval(FreetypeId,CaseId,EArgs).
1030 %eval_set_extension_typed_aux(E,T,_,_) :- print(uncov(E,T)),nl,nl,fail.
1031
1032
1033 eval_set_ext_minus(integer(I),int(R)) :- R is -I.
1034 eval_set_ext_minus(real(Atom),Real) :- construct_negative_real(Atom,Real).
1035
1036 eval_set_extension_fields([],[],_LocalIds).
1037 eval_set_extension_fields([field(Name,V)|T],[field(Name,EV)|ET],LocalIds) :- eval_set_extension_element(V,EV,LocalIds),
1038 eval_set_extension_fields(T,ET,LocalIds).
1039
1040 convert_set_to_seq([],_,[]).
1041 convert_set_to_seq([H|T],N,[(int(N),H)|CT]) :- N1 is N+1, convert_set_to_seq(T,N1,CT).
1042
1043
1044 post_let_forall(AllIds,P,Rhs,NewPred,modification) :-
1045 conjunction_to_list(P,Preds), reverse(Preds,RPreds),
1046 ? select_equality(TId,RPreds,[],_,Expr,RRest,UsedIds,no_check),
1047 ? select(TId,AllIds,RestIds),
1048 get_texpr_id(TId,Id),
1049 \+ member(Id,UsedIds), % not a recursive equality
1050 reverse(RRest,Rest),
1051 conjunct_predicates_with_pos_info(Rest,RestPred),
1052 \+ occurs_in_expr(Id,RestPred),
1053 !,
1054 NewRhs = b(let_predicate([TId],[Expr],Rhs),pred,[]),
1055 post_let_forall(RestIds,RestPred,NewRhs,NewPred,_).
1056 post_let_forall(AllIds,P,Rhs,NewPred, no_modification) :-
1057 create_implication(P,Rhs,NewForallBody),
1058 create_forall(AllIds,NewForallBody,NewP),
1059 get_texpr_expr(NewP,NewPred).
1060
1061
1062 is_interval(b(interval(A,B),_,_),A,B).
1063 is_interval(b(value(V),set(_),_),A,B) :- nonvar(V), V=closure(P,T,B),
1064 custom_explicit_sets:is_interval_closure(P,T,B,LOW,UP), integer(LOW),integer(UP),
1065 A=b(integer(LOW),integer,[]),
1066 B=b(integer(UP),integer,[]).
1067
1068 % a more flexible version, also detecting singleton set extension
1069 ?is_interval_or_singleton(I,A,B) :- is_interval(I,A,B),!.
1070 is_interval_or_singleton(b(set_extension([A]),set(integer),_),A,A).
1071
1072
1073
1074 % create a lambda expression for a projection
1075 create_projection_set(A,B,_Switch,Res) :-
1076 (definitely_empty_set(A) ; definitely_empty_set(B)),!,
1077 Res = empty_set.
1078 create_projection_set(A,B,Switch,lambda(Ids,SPred,Expr)) :- % generate lambda to be able to use function(lambda) rule
1079 Ids = [TArg1,TArg2],
1080 ( Switch==first -> Expr = TArg1
1081 ; Switch==second -> Expr = TArg2),
1082 get_texpr_type(A,TA1), unify_types_strict(TA1,set(Type1)),
1083 get_texpr_type(B,TB2), unify_types_strict(TB2,set(Type2)),
1084 ? (contains_no_ids(A,B) -> Arg1 = '_zzzz_unary', Arg2 = '_zzzz_binary' % avoid generating fresh ids; relevant for test 1313 and ticket PROB-346
1085 % TO DO: check whether _zzzz_unary/binary are actually used; we should avoid generating fresh ids whenever possible (otherwise syntactically identical formulas become different)
1086 ; get_unique_id_inside('_prj_arg1__',A,B,Arg1),
1087 get_unique_id_inside('_prj_arg2__',A,B,Arg2)),
1088 create_texpr(identifier(Arg1),Type1,[generated(Switch)],TArg1),
1089 create_texpr(identifier(Arg2),Type2,[generated(Switch)],TArg2),
1090 safe_create_texpr(member(TArg1,A),pred,MembA),
1091 safe_create_texpr(member(TArg2,B),pred,MembB),
1092 conjunct_predicates([MembA,MembB],Pred), SPred=Pred.
1093 % bsyntaxtree:mark_bexpr_as_symbolic(Pred,SPred). % TO DO: put mark code into another module; maybe only mark as symbolic if types large enough ??
1094
1095 ?contains_no_ids(A,B) :- contains_no_ids(A), contains_no_ids(B).
1096 ?contains_no_ids(b(E,_,_)) :- contains_no_ids_aux(E).
1097 contains_no_ids_aux(bool_set).
1098 contains_no_ids_aux(X) :- is_integer_set(X,_). % comprehension set may contain ids, but not visible to outside
1099 contains_no_ids_aux(mult_or_cart(A,B)) :- contains_no_ids(A),contains_no_ids(B).
1100 contains_no_ids_aux(relations(A,B)) :- contains_no_ids(A),contains_no_ids(B).
1101 contains_no_ids_aux(pow_subset(A)) :- contains_no_ids(A).
1102 contains_no_ids_aux(pow1_subset(A)) :- contains_no_ids(A).
1103 contains_no_ids_aux(real_set).
1104 contains_no_ids_aux(string_set).
1105 contains_no_ids_aux(interval(A,B)) :- contains_no_ids(A),contains_no_ids(B).
1106 % TO DO: add more
1107
1108 create_event_b_projection_set(Rel,Switch,lambda(Ids,SPred,Expr)) :-
1109 Ids = [TArg1,TArg2],
1110 ( Switch==first -> Expr = TArg1
1111 ; Switch==second -> Expr = TArg2),
1112 get_texpr_type(Rel,RT),unify_types_strict(RT,set(couple(Type1,Type2))),
1113 get_unique_id_inside('_prj_arg1__',Rel,Arg1),
1114 get_unique_id_inside('_prj_arg2__',Rel,Arg2),
1115 create_texpr(identifier(Arg1),Type1,[generated(Switch)],TArg1),
1116 create_texpr(identifier(Arg2),Type2,[generated(Switch)],TArg2),
1117 create_texpr(couple(TArg1,TArg2),couple(Type1,Type2),[],Couple),
1118 safe_create_texpr(member(Couple,Rel),pred,Member),
1119 SPred=Member.
1120 %bsyntaxtree:mark_bexpr_as_symbolic(Pred,SPred).
1121
1122 create_event_b_projection_set_v2(RelType,Switch,comprehension_set(Ids,SPred)) :-
1123 % we are generating {p1,p2,lambda | lambda=p1/p2}
1124 Ids = [TArg1,TArg2,TArg3],
1125 ( Switch==first -> ResultExpr = TArg1, Type1 = Type3
1126 ; Switch==second -> ResultExpr = TArg2, Type2 = Type3),
1127 unify_types_strict(RelType,set(couple(couple(Type1,Type2),T3))),
1128 (T3==Type3 -> true ; add_error(create_event_b_projection_set,'Unexpected return type: ',T3)),
1129 Arg1 = '_zzzz_unary',
1130 Arg2 = '_zzzz_binary',
1131 Arg3 = '_lambda_result_', % the comprehension set contains no other expressions: no clash possible
1132 create_texpr(identifier(Arg1),Type1,[generated(Switch)],TArg1),
1133 create_texpr(identifier(Arg2),Type2,[generated(Switch)],TArg2),
1134 create_texpr(identifier(Arg3),Type3,[lambda_result(Arg3),generated(Switch)],TArg3),
1135 safe_create_texpr(equal(TArg3,ResultExpr),pred,[prob_annotation('LAMBDA-EQUALITY')],Equal),
1136 SPred=Equal.
1137 % bsyntaxtree:mark_bexpr_as_symbolic(Pred,SPred).
1138 %,print(Pred),nl.
1139
1140 :- use_module(btypechecker,[couplise_list/2,prime_identifiers/2,prime_identifiers0/2, prime_atom0/2]).
1141 % create a comprehension set for quantified union or intersection UNION(x).(P|E) = ran(%x.(P|E))
1142 % TO DO: translate UNION into UNION(x).(P|E) = dom({r,x|P & r:E}) = ran({x,r|P & r:E}) which is considerably faster
1143 % also works for e.g., UNION(x).(x:1..2|{x+y}) = 12..13
1144 %quantified_union_op(Ids,Pred,Expr,SetType,Res) :- is_set_type(SetType,Type),
1145 % !,
1146 % Info = [generated(quantified_union)],
1147 % get_unique_id_inside('_zzzz_unary',Pred,Expr,FRESHID), % also include Expr !
1148 % NewID = b(identifier(FRESHID),Type,[]), %fresh
1149 % append(Ids,[NewID],NewIds),
1150 % safe_create_texpr(member(NewID,Expr),pred,[],Member),
1151 % conjunct_predicates([Pred,Member],Body),
1152 % get_texpr_types(NewIds,Types),couplise_list(Types,TupleType),
1153 % safe_create_texpr(comprehension_set(NewIds,Body),set(TupleType),Info,ComprSet),
1154 % Res = range(ComprSet).
1155 % %safe_create_texpr(range(ComprSet),set(set(Type)),Info,Set), print_bexpr(Set),nl.
1156 %quantified_union_op(Ids,Pred,Expr,SetType,Set) :-
1157 % add_internal_error('Could not translate quantified UNION operator: ',quantified_union_op(Ids,Pred,Expr,SetType,Set)),
1158 % fail.
1159
1160 % create a comprehension set for quantified union or intersection INTER(x).(P|E) = inter(ran(%x.(P|E)))
1161 % UNION could be treated by quantified_union_op above
1162 quantified_set_op(Ids,Pred,Expr,Loc,OuterInfos,Set) :-
1163 create_range_lambda(Ids,Pred,Expr,Loc,OuterInfos,Set),
1164 !. % , print(quantified),nl,print_bexpr(Set),nl.
1165 quantified_set_op(Ids,Pred,Expr,Loc,OuterInfos,Set) :-
1166 add_internal_error('Could not translate quantified set operator: ',
1167 quantified_set_op(Ids,Pred,Expr,Loc,OuterInfos,Set)),
1168 fail.
1169
1170 create_range_lambda(Ids,Pred,Expr,Loc,OuterInfos,Set) :-
1171 Info = [generated(Loc)|OuterInfos],
1172 get_texpr_types(Ids,Types),couplise_list(Types,ArgType),
1173 get_texpr_type(Expr,ExprType),
1174 safe_create_texpr(lambda(Ids,Pred,Expr),set(couple(ArgType,ExprType)),Info,Lambda),
1175 safe_create_texpr(range(Lambda),set(ExprType),Info,Set).
1176
1177
1178 quantified_set_operator(quantified_union(AllIds,Pred,Expr),quantified_union,AllIds,Pred,Expr).
1179 quantified_set_operator(quantified_intersection(AllIds,Pred,Expr),quantified_intersection,AllIds,Pred,Expr).
1180
1181 % match_ids(List1,List2, AllIds,Rest) find all ids in List1 in List2; ids in List2 not in List1 are put in Rest
1182 match_ids([],List,List,List).
1183 ?match_ids([TID|T],List,[TID2|T2],Rest) :- select(TID2,List,L2),
1184 same_id(TID,TID2,_),!,
1185 match_ids(T,L2,T2,Rest).
1186
1187 % generate dom(.) operators for TypedIds which have to be projected away
1188 generate_dom_for_ids([],E,T,I,b(E,T,I)).
1189 generate_dom_for_ids([TID|Ts],E,T,I,Res) :- T = set(T1),
1190 get_texpr_type(TID,TIDType),
1191 generate_dom_for_ids(Ts,E,set(couple(T1,TIDType)),I,DE),
1192 safe_create_texpr(domain(DE),T,Res).
1193
1194 :- use_module(tools_strings,[ajoin/2,ajoin_with_sep/3]).
1195 % we ensure that this check is only done once, for user machines,... not for generated formulas
1196 check_forall_lhs_rhs(_,_,_,_) :- preferences:get_preference(perform_stricter_static_checks,false),!.
1197 check_forall_lhs_rhs(_,_,_,_) :- preferences:get_preference(disprover_mode,true),!.
1198 check_forall_lhs_rhs(_,_,_,_) :- animation_minor_mode(eventb),!. % typing predicates get removed it seems
1199 ?check_forall_lhs_rhs(_,_,I,_) :- member(removed_typing,I),!. % means that typing was possibly removed
1200 ?check_forall_lhs_rhs(Lhs,_,_,_) :- member_in_conjunction(PC,Lhs),
1201 ? get_texpr_info(PC,PI),member(II,PI),
1202 removed_typing(II),!. % it was something else; does not seem to detect all removed conjunctions, hence we also check I above
1203 check_forall_lhs_rhs(P,_,I,Ids) :- find_identifier_uses_if_necessary(P,[],LhsUsed),
1204 ord_subtract(Ids,LhsUsed,NotDefined),
1205 NotDefined=[_|_],
1206 ajoin_with_sep(NotDefined,',',S),
1207 translate:translate_bexpression(P,PS),
1208 ajoin(['Left-hand side "', PS, '" of forall does not define identifier(s): '],Msg),
1209 add_warning(bmachine_static_checks,Msg,S,I),
1210 fail.
1211 check_forall_lhs_rhs(_,Rhs,I,Ids) :-
1212 find_identifier_uses_if_necessary(Rhs,[],RhsUsed),
1213 (ord_intersect(Ids,RhsUsed) -> true
1214 ; ajoin_with_sep(Ids,',',S),
1215 add_warning(bmachine_static_checks,'Right-hand side of forall does not use identifiers: ',S,I)
1216 ).
1217 removed_typing(removed_typing). removed_typing(was(_)).
1218
1219 :- use_module(kernel_records,[normalise_record_type/2]).
1220 :- use_module(library(lists),[last/2]).
1221
1222 % first the rules that require the path:
1223 cleanup_post_with_path(assign([b(identifier(ID),TYPE,INFO)],[EXPR]),subst,I,
1224 assign_single_id(b(identifier(ID),TYPE,INFO),EXPR),subst,I,single/assign_single_id,Path) :-
1225 \+ animation_minor_mode(eventb), % there is no support in the Event-B interpreter for assign_single_id yet
1226 ? (simple_expression(EXPR) % the assign_single_id is not guarded by a waitflag; EXPR should not be too expensive too calculate
1227 -> true
1228 ; % if we are in an unguarded context; then we do not need to guard EXPR by waitflag anyway
1229 ? maplist(unguarded,Path)
1230 ),
1231 !,
1232 (debug_level_active_for(4) -> format('Single Assignment to ~w~n',[ID])
1233 %translate:print_subst(b(assign([b(identifier(ID),TYPE,INFO)],[EXPR]),subst,I)),nl
1234 ; true).
1235 cleanup_post_with_path(any(Ids,Pred,Subst),subst,Info,any(Ids,Pred,NewSubst),subst,NewInfo,multi/remove_useless_assign,_Path) :-
1236 get_preference(optimize_ast,true),
1237 ? member_in_conjunction(b(equal(TID1,TID2),pred,_),Pred),
1238 get_texpr_id(TID1,ID1),
1239 get_texpr_id(TID2,ID2), % we have an equality of the form x=x' (as generated by TLA2B)
1240 ? delete_assignment(Subst,TID3,TID4,NewSubst),
1241 get_texpr_id(TID4,ID4), get_texpr_id(TID3,ID3),
1242 ( c(ID1,ID2) = c(ID3,ID4) ; c(ID1,ID2) = c(ID4,ID3)), % we have an assignment x:=x' or x':=x
1243 % the cleanup rule recompute_accessed_vars below recomputes the info fields for enclosing operations! get_accessed_vars is currently called before ast_cleanup
1244 ajoin([ID3,' := ',ID4],Assign),
1245 add_hint_message(remove_useless_assign,'Removing useless assignment: ',Assign,Info),
1246 ? (member(removed_useless_assign,Info) -> NewInfo=Info ; NewInfo=[removed_useless_assign|Info]).
1247 cleanup_post_with_path(operation(TName,Res,Params,TBody),Type,Info,
1248 operation(TName,Res,Params,NewTBody),Type,NewInfos,single/recompute_accessed_vars,_Path) :-
1249 TBody=b(Body,subst,BInfos),
1250 ? select(removed_useless_assign,BInfos,NewBInfos),
1251 btypechecker:compute_accessed_vars_infos_for_operation(TName,Res,Params,TBody,Modifies,_,_,_,NewRWInfos),
1252 debug_format(19,'Recomputing read/write infos for ~w (~w)~n',[TName,Modifies]),
1253 update_infos(NewRWInfos,Info,NewInfos),
1254 NewTBody=b(Body,subst,NewBInfos).
1255 cleanup_post_with_path(any(Ids,Pred,Subst),subst,I,Result,subst,[generated|I],single/transform_any_into_let,Path) :-
1256 (last(Path,path_arg(top_level(_),_))
1257 /* do not remove top-level ANY if show_eventb_any_arguments is true; see, e.g., test 1271 */
1258 -> preferences:preference(show_eventb_any_arguments,false) ; true),
1259 conjunction_to_list(Pred,Preds),
1260 get_sorted_ids(Ids,BlacklistIds),
1261 find_one_point_rules(Ids,Preds,BlacklistIds,LetIDs,Exprs,RestIds,RestPreds),
1262 LetIDs \= [],
1263 maplist(create_equality,LetIDs,Exprs,LetDefs),
1264 % print(found_lets(LetIDs,RestIds,RestPred)),nl,print(Path),nl,
1265 conjunct_predicates_with_pos_info(LetDefs,LetDefPred),
1266 (RestIds = [], RestPreds=[] % complete ANY can be translated to LET
1267 -> Result = let(LetIDs,LetDefPred,Body), Body = Subst
1268 ? ; split_predicates(RestPreds,Ids,RestUsingIds,RestNotUsingIds),
1269 conjunct_predicates_with_pos_info(RestPreds,RestPred),
1270 % print('USING: '), print_bexpr(RestUsingIds),nl, print('NOT USING: '), print_bexpr(RestNotUsingIds),nl,
1271 (RestIds = []
1272 -> (is_truth(RestUsingIds)
1273 % RestPred does not use the LET identifiers; move outside of the LET !
1274 -> Result = select([b(select_when(RestPred,SelectBody),subst,[generated|I])]),
1275 SelectBody = b(let(LetIDs,LetDefPred,Subst),subst,[generated|I])
1276 ; is_truth(RestNotUsingIds)
1277 % RestPred uses LET identifiers in all conjuncts; move inside LET
1278 -> Result = let(LetIDs,LetDefPred,LetBody),
1279 LetBody = b(select([b(select_when(RestPred,Subst),subst,[])]),subst,[generated|I])
1280 ;
1281 % we would need to generate an outer and inner select; transformation probably not worth it
1282 fail
1283 )
1284 ; is_truth(RestUsingIds)
1285 % RestPred does not use LET identifiers move outside of LET
1286 -> Result = any(RestIds,RestPred,SelectBody),
1287 SelectBody = b(let(LetIDs,LetDefPred,Subst),subst,[generated|I])
1288 ; is_truth(RestNotUsingIds)
1289 % RestPred uses LET identifiers in all conjuncts; move inside LET
1290 -> Result = let(LetIDs,LetDefPred,LetBody),
1291 LetBody = b(any(RestIds,RestPred,Subst),subst,I)
1292 ;
1293 % we would need to generate an outer and inner any; transformation probably not worth it
1294 fail
1295 )
1296 ),
1297 !. %,translate:print_subst(b(Result,subst,[])),nl.
1298 cleanup_post_with_path(operation(TName,Res,Params,Body),Type,Info,
1299 operation(TName,Res,Params,NewBody),Type,Info,single/lts_min_guard_splitting,Path) :-
1300 get_preference(ltsmin_guard_splitting,true), % used also to checkpge_algo:is_pge_opt_on,
1301 Path = [path_arg(top_level(operation_bodies),_)], % only apply at top-level and TO DO: only for top-most machine !!
1302 % TO DO: also apply for Event-B models
1303 get_texpr_id(TName,Name),
1304 (get_operation_propositional_guards(Name,Res,Params,Body,Guards,RestBody)
1305 -> true
1306 ; add_warning(ltsmin_guard_splitting,'Cannot extract guard for:',Name),fail),
1307 Guards \= [],
1308 conjunct_predicates_with_pos_info(Guards,G),
1309 get_texpr_info(Body,BInfo),
1310 NewBody = b(precondition(G,RestBody),subst,[prob_annotation('LTSMIN-GUARD')|BInfo]), % a SELECT would be more appropriate
1311 (debug_mode(off) -> true
1312 ; format('Extracting LTS Min guard for ~w~n',[Name]),translate:print_subst(NewBody),nl).
1313 cleanup_post_with_path(exists(Ids,B),Type,OInfo,exists(Ids,B),Type,NInfo,single/invalidate_used_ids,_Path) :-
1314 delete(OInfo,used_ids(_),NInfo). % the changes done by cleanups, e.g, removing unused predicates can affect used_ids
1315 cleanup_post_with_path(forall(Ids,LHS,RHS),Type,OInfo,forall(Ids,LHS,RHS),Type,NInfo,single/invalidate_used_ids,_Path) :-
1316 delete(OInfo,used_ids(_),NInfo). % ditto
1317 cleanup_post_with_path(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule,Path) :-
1318 get_preference(optimize_ast,true),
1319 cleanup_post_ne_with_path(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule,Path).
1320 cleanup_post_with_path(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule,_Path) :-
1321 ? cleanup_post_essential(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule).
1322
1323 % delete an assignment from a substitution
1324 delete_assignment(b(assign(LHS,RHS),subst,Info),ID,IDRHS,b(RES,subst,Info)) :-
1325 ? nth1(Pos,LHS,ID,RestLHS),
1326 nth1(Pos,RHS,IDRHS,RestRHS),
1327 (RestLHS = [] -> RES = skip ; RES = assign(RestLHS,RestRHS)).
1328 % TO DO: also deal with parallel and possibly other constructs assign_single_id,...
1329
1330 %unguarded(path_arg(sequence/1,1)). % first argument of sequence is not guarded
1331 ?unguarded(path_arg(X,_)) :- unguarded_aux(X).
1332 unguarded_aux(top_level(_)).
1333 unguarded_aux(operation/4).
1334 unguarded_aux(parallel/1).
1335 unguarded_aux(var/2).
1336 unguarded_aux(let/3).
1337 % what about choice/2 ??
1338
1339 :- load_files(library(system), [when(compile_time), imports([environ/2])]).
1340
1341
1342 % ---------------------
1343
1344 % now the rules which do not need the Path
1345
1346 % first check for a few expressions that never need to be optimised, rewritten:
1347 cleanup_post_essential(E,_,_,_,_,_,_) :- never_transform_or_optimise(E),!,fail.
1348
1349 cleanup_post_essential(Expr,Type,I,Expr,Type,I2,single/remove_erroneous_info_field) :-
1350 \+ ground(I),!,
1351 functor(Expr,F,_N),
1352 add_internal_error('Information field not ground: ',I:F),
1353 I2=[].
1354 cleanup_post_essential(comprehension_set(Ids,E),Type,I,comprehension_set(Ids,E),Type,I,single/sanity_check) :-
1355 get_preference(prob_safe_mode,true),
1356 get_texpr_ids(Ids,UnsortedIds),sort(UnsortedIds,SIds),
1357 \+ same_length(UnsortedIds,SIds),
1358 add_error(cleanup_post,'Identifier clash in comprehension set: ',UnsortedIds),
1359 print(E),nl,
1360 fail.
1361
1362
1363 cleanup_post_essential(lambda(Ids,Pred,Expr),Type,I,
1364 comprehension_set(CompIds,CompPred),Type,NewInfo,multi/remove_lambda) :- !,
1365 unify_types_strict(Type,set(couple(_ArgType,ResType))),
1366 get_unique_id_inside('_lambda_result_',Pred,Expr,ResultId),
1367 def_get_texpr_id(Result,ResultId),
1368 get_texpr_type(Result,ResType),
1369 get_texpr_info(Result,[lambda_result(ResultId)]),
1370 append(Ids,[Result],CompIds),
1371 Equal = b(equal(Result,Expr),pred,[prob_annotation('LAMBDA-EQUALITY')|EqInfo]),
1372 extract_important_info_from_subexpression(Expr,EqInfo), % mark equality with wd condition if Expr has wd condition
1373 ? (member(prob_annotation('SYMBOLIC'),EqInfo)
1374 -> % something like %p.(p : BOOL|%t.(t : NATURAL|t .. t + 7))
1375 (debug_mode(off) -> true
1376 ; write('Marking lambda as symbolic because result is symbolic: '),print_bexpr(Expr),nl),
1377 add_info_if_new(I,prob_annotation('SYMBOLIC'),NewInfo)
1378 ? ; infinite_or_symbolic_domain_for_lambda(Ids,Pred,Kind)
1379 -> % something like %t.(t : NATURAL|t .. t + 7)
1380 (debug_mode(off) -> true
1381 ; get_texpr_ids(Ids,AIds),
1382 format('Marking lambda over ~w as symbolic because the domain is ~w: ',[AIds,Kind]),
1383 print_bexpr(Pred),nl),
1384 add_info_if_new(I,prob_annotation('SYMBOLIC'),NewInfo)
1385 ; NewInfo = I),
1386 conjunct_predicates_with_pos_info(Pred,Equal,CompPred0),
1387 add_texpr_infos(CompPred0,[prob_annotation('LAMBDA')],CompPred). % checked e.g. in is_converted_lambda_closure
1388 %print_bexpr(b(comprehension_set(CompIds,CompPred),Type,NewInfo)),nl.
1389
1390 cleanup_post_essential(reflexive_closure(Rel),Type,I, UNION,Type,NewInfo,multi/remove_reflexive_closure) :- !,
1391 NewInfo = [was(reflexive_closure)|I],
1392 safe_create_texpr(closure(Rel),Type,I,CL),
1393 UNION = union(b(event_b_identity,Type,IdInfo), CL), % closure(R) = id \/ closure1(R)
1394 (is_infinite_ground_type(Type) -> IdInfo = [prob_annotation('SYMBOLIC')|I] ; IdInfo =I),
1395 (debug_mode(on) -> print('Rewriting closure to: '), print_bexpr(b(UNION,Type,[])),nl ; true).
1396 cleanup_post_essential(evb2_becomes_such(Ids,Pred),subst,I,becomes_such(Ids,Pred2),subst,I,multi/ev2_becomes_such) :-
1397 % we translate a Classical-B becomes_such with id -> id$0, id' -> id
1398 % classical B: Dec = BEGIN level : (level>=0 & level> level$0-5 & level < level$0) END
1399 % Event-B: level'>= 0, level' > level-5 ...
1400 !,
1401 prime_identifiers(Ids,PIds),
1402 maplist(gen_rename,PIds,Ids,RenameList1), % id' -> id
1403 prime_identifiers0(Ids,PIds0),
1404 maplist(gen_rename,Ids,PIds0,RenameList2), % id -> id$0
1405 append(RenameList1,RenameList2,RenameList),
1406 rename_bt(Pred,RenameList,Pred2),
1407 (debug_mode(off) -> true
1408 ; format('Converting Event-B becomes_such: ',[]), print_bexpr(Pred2),nl).
1409 cleanup_post_essential(successor,Type,I,Compset,Type,[was(successor)|I],multi/successor) :- !,
1410 % translation of succ
1411 pred_succ_compset(add,Compset).
1412 cleanup_post_essential(rev(A),string,I,ExtFunCall,string,[was(rev)|I],multi/rev_for_string) :- !,
1413 % translation of rev for STRINGs, this can only occur when allow_sequence_operators_on_strings is true
1414 ExtFunCall = external_function_call('STRING_REV',[A]).
1415 cleanup_post_essential(concat(A,B),string,I,ExtFunCall,string,[was(concat)|I],multi/concat_for_string) :- !,
1416 % translation of concat (^) for STRINGs, can only occur when allow_sequence_operators_on_strings is true
1417 construct_string_append(A,B,ExtFunCall).
1418 cleanup_post_essential(general_concat(A),string,I,ExtFunCall,string,[was(general_concat)|I],multi/concat_for_string) :-
1419 !, % translation of conc for seq(STRING) --> STRING, can only occur when allow_sequence_operators_on_strings is true
1420 ExtFunCall = external_function_call('STRING_CONC',[A]).
1421 cleanup_post_essential(size(A),integer,I,ExtFunCall,integer,[was(A)|I],multi/concat_for_string) :-
1422 get_texpr_type(A,string),!,
1423 % translation of size for STRING, this can only occur when allow_sequence_operators_on_strings is true
1424 ExtFunCall = external_function_call('STRING_LENGTH',[A]).
1425 cleanup_post_essential(predecessor,Type,I,Compset,Type,[was(predecessor)|I],multi/predecessor) :- !,
1426 % translation of pred
1427 pred_succ_compset(minus,Compset).
1428 cleanup_post_essential(becomes_such(Ids1,Pred),subst,I,becomes_such(Ids2,Pred),subst,I,single/becomes_such) :- !,
1429 annotate_becomes_such_vars(Ids1,Pred,Ids2).
1430 cleanup_post_essential(Expr,Type,I,Expr,Type,[contains_wd_condition|I],multi/possibly_undefined) :-
1431 % multi: rule can only be applied once anyway, no need to check
1432 nonmember(contains_wd_condition,I),
1433 % print(' - CHECK WD: '), print_bexpr(Expr),nl, %%
1434 is_possibly_undefined(Expr),!,
1435 %% print('CONTAINS WD: '), print_bexpr(Expr),nl, %%
1436 %(translate:translate_bexpression(Expr,'{min(xunits)}') -> trace ; true),
1437 true.
1438 % if a substitution has a sub-expression that is a substitution with that refers to the original
1439 % value of a variable, we mark this substitution, too.
1440
1441 % If the substitution of an operation contains a while whose invariant contains references x$0
1442 % to the original value of a variable x, we must insert a LET substitution to preserve the original value.
1443 cleanup_post_essential(operation(Id,Results,Args,Body),Type,I,operation(Id,Results,Args,NewBody),Type,I,single/refers_to_old_state_let) :-
1444 get_texpr_info(Body,BodyInfo),
1445 memberchk(refers_to_old_state(References),BodyInfo),!,
1446 create_equalities_for_let(References,Ids,Equalities),
1447 conjunct_predicates_with_pos_info(Equalities,P),
1448 insert_let(Body,Ids,P,NewBody).
1449 cleanup_post_essential(Subst,subst,I,Subst,subst,NI,single/refers_to_old_state) :-
1450 safe_syntaxelement_det(Subst,Subs,_,_,_),
1451 % check if a child contains the refers_to_old_state flag
1452 findall(Reference, (member(Sub,Subs),
1453 get_texpr_info(Sub,SubInfo),
1454 memberchk(refers_to_old_state(References),SubInfo),
1455 member(Reference,References)), ReferedIds),
1456 ReferedIds \= [],
1457 !,
1458 sort(ReferedIds,SortedIds),
1459 NI = [refers_to_old_state(SortedIds)|I].
1460
1461 cleanup_post_essential(let_predicate([],[],TExpr),Type,Iin,Expr,Type,Iout,multi/remove_let_predicate) :- !,
1462 % same as above, just for predicates
1463 get_texpr_expr(TExpr,Expr),
1464 get_texpr_info(TExpr,I),
1465 % The next is done to prevent removing position information (in case of Event-B invariants, theorems,...)
1466 propagate_pos_info_if_useful(I,Iin,Iout).
1467
1468 cleanup_post_essential(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule) :-
1469 get_preference(optimize_ast,true),
1470 ? cleanup_post(OExpr,OType,OInfo,NExpr,NType,NInfo,Mode/Rule).
1471
1472 % moved these rule below the simplifciation rules above to avoid re-computing used_id infos
1473 cleanup_post_essential(forall(Ids,Lhs,Rhs),pred,IOld,Res,pred,INew,single/forall_used_identifier) :-
1474 reconstruct_forall(Ids,Lhs,Rhs,IOld, b(Res,pred,INew)).
1475 cleanup_post_essential(exists(Ids,P),pred,IOld,exists(Ids,NP),pred,ResInfo,single/exists_used_identifier) :-
1476 inner_predicate_level_optimizations(P,NP),
1477 add_used_identifier_info(Ids,NP,IOld,INew0),
1478 add_used_ids_defined_by_equality(Ids,NP,INew0,INew),
1479 %print('* POST => '),print_bexpr(b(exists(Ids,NP),pred,INew)),nl,
1480 %print(' INFO=> '),print(INew),nl,
1481 % TO DO: also compute which identifiers are worth waiting for; do not wait for res in #x.(x:E & ... & res=min(f(x)))
1482 add_removed_typing_info(INew,ResInfo).
1483 cleanup_post_essential(Construct,Type,I,NewConstruct,Type,I,single/detect_partitions) :-
1484 contains_predicate(Construct,Type,Pred,NewConstruct,NewPred),!, % something like a select or other substitution
1485 predicate_level_optimizations(Pred,NewPred).
1486 cleanup_post_essential(Construct,Type,I,NewConstruct,Type,I,single/detect_partitions2) :-
1487 contains_predicates(Construct,Type,Preds,NewConstruct,NewPreds),!,
1488 maplist(predicate_level_optimizations,Preds,NewPreds) % TO DO: do CSE together (in some cases) !
1489 . %, (Preds=NewPreds -> true ; print('Found partitions: '), translate:print_subst(b(NewConstruct,Type,I)),nl).
1490
1491 construct_inner_forall(Ids,LHS,RHS,OldInfo,Res) :-
1492 delete(OldInfo,used_ids(_),I1), % we construct a changed forall construct; old used_ids info possibly incorrect
1493 reconstruct_forall(Ids,LHS,RHS,I1,Res).
1494 % use when in cleanup_post you construct a forall which will not be at the top-level
1495 % (meaning that the above essential rules will not run)
1496 reconstruct_forall(Ids,LHS,RHS,OldInfo, b(Res,pred,NewInfo)) :-
1497 inner_predicate_level_optimizations(LHS,NLhs),
1498 inner_predicate_level_optimizations(RHS,NRhs),
1499 construct_forall_opt(Ids,NLhs,NRhs,OldInfo, Res,NewInfo).
1500
1501 construct_forall_opt(IDs,NLhs,NRhs,Info, Res,NewInfo) :-
1502 (is_truth(NRhs) ; is_falsity(NLhs)),!,
1503 add_hint_message(remove_useless_assign,'Removing useless universal quantification','',Info),
1504 Res= truth, NewInfo = [was(forall(IDs,NLhs,NRhs))|Info].
1505 % TO DO: is the following rule useful ?: will require adapting test 510 output file
1506 % triggers e.g. for test 1447
1507 %construct_forall_opt([TID],LHS,RHS,Info, Res,NewInfo) :- % !x. (x:SetA => x:SetB) ---> SetA <: SetB
1508 % is_valid_id_member_check(LHS,TID,SetA), is_valid_id_member_check(RHS,TID,SetB),
1509 % !,
1510 % (debug_mode(off) -> true
1511 % ; format('Replacing forall ~w by subset: ',[TID]), print_bexpr(b(subset(SetA,SetB),pred,Info)),nl
1512 % ),
1513 % Res = subset(SetA,SetB), NewInfo = [was(forall)|Info].
1514 construct_forall_opt(Ids,NLhs,NRhs,OldInfo, forall(Ids,NLhs,NRhs),ResInfo) :-
1515 conjunct_predicates([NLhs,NRhs],P),
1516 add_used_identifier_info(Ids,P,OldInfo,Info),
1517 add_removed_typing_info(Info,ResInfo).
1518
1519 add_removed_typing_info(Info,ResInfo) :-
1520 (memberchk(removed_typing,Info) -> ResInfo = Info ; ResInfo = [removed_typing|Info]).
1521
1522 disjoint_ids(Ids1,Ids2) :-
1523 get_texpr_ids(Ids1,I1), sort(I1,SI1),
1524 get_texpr_ids(Ids2,I2), sort(I2,SI2),
1525 ord_disjoint(SI1,SI2).
1526
1527
1528 % translate concat(^) of strings:
1529 construct_string_append(A,B,ExtCall) :-
1530 is_string_conc_or_append(A,List,InfoA), !, % nested concat -> translate to STRING_CONC to enable optimisations
1531 append(List,[B],NewList),
1532 ExtCall = external_function_call('STRING_CONC',[S]),
1533 get_texpr_info(B,IB),merge_info(InfoA,IB,Info),
1534 S = b(sequence_extension(NewList),seq(string),Info).
1535 construct_string_append(A,B,external_function_call('STRING_APPEND',[A,B])).
1536
1537 is_string_conc_or_append(b(external_function_call(F,FArgs),_,Info),Args,Info) :-
1538 (F='STRING_APPEND' -> Args = FArgs
1539 ; F='STRING_CONC',
1540 FArgs = b(sequence_extension(SArgs),_,_)
1541 -> Args = SArgs).
1542
1543 % ---------------------
1544
1545 % non-essential post cleanup rules; only applied when optimize_ast is TRUE
1546
1547 % WITH PATH:
1548
1549 cleanup_post_ne_with_path(member(E,b(image(Rel,SONE),TypeImg,InfoImg)),pred,I,member(Couple,Rel),pred,I,multi/replace_image_by_member,Path) :-
1550 % x : Rel[{One}] => One|->x : Rel
1551 Path \= [path_arg(forall/3,1)|_], % not LHS of a forall
1552 %% do not do this if it is the LHS of a forall: !(aus2).( aus2 : helper[{mm}] => RHS) (as we no longer can apply the optimized set treatment for forall
1553 singleton_set_extension(SONE,One),
1554 %% Rel \= b(reverse(_),_,_), %% TO DO: maybe exclude this; here user maybe wants to explicitly compute image ?
1555 !,
1556 create_couple(One,E,Couple),
1557 (debug_mode(off) -> true
1558 ; print('Member of Image: '),print_bexpr(b(member(E,b(image(Rel,SONE),TypeImg,InfoImg)),pred,I)),nl,
1559 print(' replaced by: '),print_bexpr(b(member(Couple,Rel),pred,I)),nl
1560 ).
1561
1562
1563 % WITHOUT PATH:
1564
1565 cleanup_post(conjunct(b(truth,pred,I1),b(B,pred,I2)),pred,I0,B,pred,NewI,multi/remove_truth_conj1) :- !,
1566 include_important_info_from_removed_pred(I1,I2,I3), % ensure was,... information propagated
1567 add_important_info_from_super_expression(I0,I3,NewI).
1568 cleanup_post(conjunct(b(A,pred,I2),b(truth,pred,I1)),pred,I0,A,pred,NewI,multi/remove_truth_conj2) :- !,
1569 include_important_info_from_removed_pred(I1,I2,I3),
1570 add_important_info_from_super_expression(I0,I3,NewI).
1571 cleanup_post(conjunct(b(falsity,pred,I1),b(_,_,I2)),pred,I0,falsity,pred,NewI,multi/simplify_falsity_conj1) :- !,
1572 include_important_info_from_removed_pred(I2,I1,I3),
1573 add_important_info_from_super_expression(I0,I3,NewI).
1574 cleanup_post(conjunct(LHS,b(falsity,pred,I2)),pred,I0,falsity,pred,NewI,multi/simplify_falsity_conj2) :-
1575 always_well_defined_or_wd_reorderings_allowed(LHS), % we can only improve WD here,
1576 % also checks allow_improving_wd_mode preference
1577 !, % Note: ProB would treat falsity first anyway; so in principle this could be done always for solving
1578 get_texpr_info(LHS,I1),
1579 include_important_info_from_removed_pred(I1,I2,I3),
1580 add_important_info_from_super_expression(I0,I3,NewI).
1581 % we use FInfo: in case it has a was(.) field, e.g., for pretty printing and unsat core generation and unsatCore.groovy test
1582 cleanup_post(conjunct(AA,BB),pred,I,Res,pred,I,multi/modus_ponens) :-
1583 Impl = b(implication(A,B),pred,_),
1584 ((AA,BB) = (Impl,A2) ; (BB,AA) = (Impl,A2)),
1585 same_texpr(A,A2),
1586 % arises e.g., for predicates such as IF x:0..3 THEN y=2 ELSE 1=0 END ; works with simplify_falsity_impl3 rule
1587 % rewrite (A=>B) & A into (A&B)
1588 !,
1589 (debug_mode(off) -> true ; print('Modus Ponens: '),print_bexpr(A), print(' => '), print_bexpr(B),nl),
1590 Res = conjunct(A,B).
1591 %cleanup_post(conjunct(TLHS,P1),pred,_,LHS,pred,Info,multi/duplicate_pred) :-
1592 % % TO DO: implement an efficient version of this; currently very slow e.g. for test 293
1593 % b_interpreter:member_conjunct(P2,TLHS,_),
1594 % same_texpr(P1,P2),
1595 % TLHS = b(LHS,pred,Info),
1596 % print('remove_duplicate: '), print_bexpr(P1),nl.
1597 cleanup_post(conjunct(LHS,b(Comparison1,pred,_)),pred,I0,Result,pred,RInfo,multi/detect_interval1) :-
1598 % X <= UpBound & X >= LowBound <=> X : UpBound .. LowBound (particularly useful when CLPFD FALSE, causes problem with test 1771)
1599 % Note: x>18 & y<1024 & x<20 & y>1020 now works, it is bracketed ((()) & y>1020)
1600 get_preference(use_clpfd_solver,false),
1601 \+ data_validation_mode, % this rule may lead to additional enumerations
1602 get_leq_comparison(Comparison1,X,UpBound),
1603 ? select_conjunct(b(Comparison2,_,_),LHS,Prefix,Suffix),
1604 get_geq_comparison(Comparison2,X2,LowBound),
1605 same_texpr(X,X2),
1606 (always_well_defined_or_disprover_mode(UpBound)
1607 -> true
1608 ; % as we may move valuation earlier, we have to be careful
1609 % we check if Comparison2 is last conjunct; x=7 & x:8..(1/0) raises no WD error in ProB
1610 Suffix=[]
1611 ),
1612 !,
1613 create_interval_member(X,LowBound,UpBound,Member),
1614 append(Prefix,[Member|Suffix],ResultList),
1615 conjunct_predicates(ResultList,TResult),
1616 TResult = b(Result,pred,I1),
1617 add_important_info_from_super_expression(I0,I1,RInfo),
1618 (debug_mode(off) -> true ; print(' Detected interval membership (1): '),print_bexpr(b(Result,pred,RInfo)),nl).
1619 cleanup_post(conjunct(LHS,b(Comparison1,pred,_)),pred,I0,Result,pred,RInfo,multi/detect_interval2) :-
1620 % X >= LowBound & X <= UpBound <=> X : UpBound .. LowBound
1621 get_preference(use_clpfd_solver,false),
1622 \+ data_validation_mode, % this rule may lead to additional enumerations
1623 get_geq_comparison(Comparison1,X,LowBound),
1624 ? select_conjunct(b(Comparison2,_,_),LHS,Prefix,Suffix),
1625 get_leq_comparison(Comparison2,X2,UpBound),
1626 same_texpr(X,X2),
1627 (always_well_defined_or_disprover_mode(LowBound)
1628 -> true
1629 ; % as we may move valuation earlier, we have to be careful
1630 % we check if Comparison2 is last conjunct; x=7 & x:8..(1/0) raises no WD error in ProB
1631 Suffix=[]
1632 ),
1633 !,
1634 create_interval_member(X,LowBound,UpBound,Member),
1635 append(Prefix,[Member|Suffix],ResultList),
1636 conjunct_predicates(ResultList,TResult),
1637 TResult = b(Result,pred,I1),
1638 add_important_info_from_super_expression(I0,I1,RInfo),
1639 (debug_mode(off) -> true ; print(' Detected interval membership (2): '),print_bexpr(b(Result,pred,RInfo)),nl).
1640
1641 cleanup_post(disjunct(b(truth,pred,I1),_),pred,I0,truth,pred,I,multi/simplify_truth_disj1) :- !,
1642 add_important_info_from_super_expression(I0,I1,I).
1643 cleanup_post(disjunct(b(A,pred,I1),b(falsity,pred,_)),pred,I0,A,pred,I,multi/remove_falsity_disj1) :- !,
1644 add_important_info_from_super_expression(I0,I1,I).
1645 cleanup_post(disjunct(b(falsity,pred,_),b(B,pred,I1)),pred,I0,B,pred,I,multi/remove_falsity_disj2) :- !,
1646 add_important_info_from_super_expression(I0,I1,I).
1647 cleanup_post(disjunct(Expr1,b(truth,pred,I1)),pred,I0,truth,pred,I,multi/simplify_truth_disj2) :-
1648 always_well_defined_or_wd_reorderings_allowed(Expr1), !, % we can only improve WD here
1649 add_important_info_from_super_expression(I0,I1,I).
1650 cleanup_post(disjunct(P1,NegP1),pred,Info,truth,pred,Info,multi/tautology_disjunction) :-
1651 % P1 or not(P1) == truth (was created by Rodin for WD)
1652 ? is_negation_of(P1,NegP1),
1653 always_well_defined_or_disprover_mode(P1),
1654 (debug_mode(off) -> true
1655 ; format('Detected useless disjunction (tautology): ',[]),print_bexpr(b(disjunct(P1,NegP1),pred,Info)),nl).
1656 cleanup_post(disjunct(Equality1,Equality2),pred,I,New,pred,I,multi/rewrite_disjunct_to_member1) :-
1657 ? identifier_equality(Equality2,ID,_,Expr2),
1658 always_well_defined_or_disprover_mode(Expr2),
1659 get_texpr_type(Expr2,Type2),
1660 type_contains_no_sets(Type2), % we do not want to generate sets of sets, or worse sets with infinite sets (x=NATURAL1 or ...) which cannot be converted to AVL
1661 ? identifier_equality(Equality1,ID,TID,Expr1),
1662 % Rewrite (ID = Expr1 or ID = Expr2) into ID: {Expr1,Expr2} ; good if FD information can be extracted for ID
1663 % But: can be bad for reification, in particular when set extension cannot be computed fully
1664 % TO DO: also deal with ID : {Values} and more general extraction of more complicated disjuncts
1665 % TO DO: also apply for implication (e.g., ID /= E1 => ID=E2)
1666 !,
1667 construct_set_extension(Expr1,Expr2,SetX), % TODO: check if fulltype? BOOL already treated in tautology_disjunction
1668 New=member(TID,SetX),
1669 (debug_mode(off) -> true
1670 ; format('Rewrite disjunct (1) ~w: ',[ID]),print_bexpr(SetX),nl).
1671 cleanup_post(disjunct(LHS1,LHS2),pred,I,New,pred,I,multi/rewrite_disjunct_to_member2) :-
1672 ? id_member_of_set_extension(LHS2,ID,TID1,LExpr2), % also detects equalities
1673 get_texpr_type(TID1,Type),
1674 get_preference(use_clpfd_solver,true),type_contains_fd_index(Type), % merging is potentially useful
1675 maplist(always_well_defined_or_disprover_mode,LExpr2), % TODO: check that merging makes sense, e.g., definite FD values or simple identfiiers
1676 ? id_member_of_set_extension(LHS1,ID,TID,LExpr1),
1677 % Rewrite (ID : {Expr1,...} or ID : {Expr2,...} into ID: {Expr1,Expr2}
1678 l_construct_set_extension(LExpr1,LExpr2,SetX),
1679 New=member(TID,SetX),
1680 (debug_mode(off) -> true
1681 ; format('Rewrite disjunct (2) ~w: ',[ID]),print_bexpr(SetX),nl).
1682 cleanup_post(disjunct(CEquality1,CEquality2),pred,IOld,New,pred,INew,multi/factor_common_pred_in_disjunction) :-
1683 % (x=2 & y=3) or (x=2 & y=4) -> x=2 & (y=3 or y=4) to improve constraint propagation
1684 ? factor_disjunct(CEquality1,CEquality2,IOld,New,INew),
1685 (debug_mode(off) -> true
1686 ; format('Factor disjunct: ',[]),print_bexpr(b(New,pred,INew)),nl).
1687 cleanup_post(implication(b(truth,pred,_),b(B,pred,I1)),pred,I0,B,pred,I,multi/remove_truth_impl1) :- !,
1688 add_important_info_from_super_expression(I0,I1,I).
1689 cleanup_post(implication(b(falsity,pred,I1),_),pred,I0,truth,pred,I,multi/simplify_falsity_impl1) :- !,
1690 add_important_info_from_super_expression(I0,I1,I).
1691 cleanup_post(implication(_,b(truth,pred,I1)),pred,I0,truth,pred,I,multi/simplify_truth_impl2) :- !,
1692 add_important_info_from_super_expression(I0,I1,I).
1693 cleanup_post(implication(P,b(falsity,pred,_)),pred,I,NotP,pred,[was(implication)|I],multi/simplify_falsity_impl3) :- !,
1694 create_negation(P,TNotP),
1695 (debug_mode(off) -> true ; print_bexpr(P), print(' => FALSE simplified'),nl),
1696 get_texpr_expr(TNotP,NotP).
1697 % TO DO: is the following rule useful ?:
1698 %cleanup_post(implication(A,b(implication(B,C),pred,_)),pred,IOld,
1699 % implication(AB,C),pred,IOld,single/replace_implication_by_and) :-
1700 % % (A => B => C <==> (A & B) => C
1701 % conjunct_predicates([A,B],AB),
1702 % (debug_mode(off) -> true ; print('Simplifying double implication: '), print_bexpr(b(implication(AB,C),pred,IOld)),nl).
1703 cleanup_post(equivalence(TA,b(B,pred,I1)),pred,I0,B,pred,I,multi/remove_truth_equiv1) :-
1704 is_truth(TA), !,
1705 add_important_info_from_super_expression(I0,I1,I).
1706 cleanup_post(equivalence(b(A,pred,I1),TB),pred,I0,A,pred,I,multi/remove_truth_equiv2) :-
1707 is_truth(TB), !,
1708 add_important_info_from_super_expression(I0,I1,I).
1709 % TO DO: more rules for implication/equivalence to introduce negations (A <=> FALSITY ---> not(A)) ?
1710 % detect certain tautologies/inconsistencies
1711 cleanup_post(lazy_let_pred(_ID,_,b(Sub,pred,I1)),pred,I0,Sub,pred,I,multi/remove_lazy_let_pred) :-
1712 (Sub=truth ; Sub=falsity), !,
1713 add_important_info_from_super_expression(I0,I1,I).
1714 cleanup_post(IFTHENELSE,T,_,Res,T,[was(ifthenelse)|NI],single/remove_if_then_else) :-
1715 explicit_if_then_else(IFTHENELSE,IF,THEN,ELSE),
1716 (is_falsity(IF) -> b(Res,_,NI)=ELSE
1717 ; is_truth(IF) -> b(Res,_,NI)=THEN
1718 ),
1719 (debug_mode(off) -> true
1720 ; print('Simplified IF-THEN-ELSE: '), print_bexpr(IF),nl).
1721 cleanup_post(member(X,B),pred,I,truth,pred,[was(member(X,B))|I],multi/remove_type_member) :-
1722 is_just_type(B),
1723 nonmember(label(_),I), % the user has explicitly labeled this conjunct
1724 !. % print('REMOVE: '),print_bexpr(b(member(X,B),pred,[])),nl, print(I),nl.
1725 %cleanup_post(member(X,SET),pred,I,greater_equal(X,TBound),pred,[was(member(X,SET))|I],multi/remove_type_member) :-
1726 % disabled at the moment: we need to adapt test 1383, 767, 1703, 1003
1727 % is_inf_integer_set_with_lower_bound(SET,Bound),
1728 % Replace x:NATURAL by x>=0 and x:NATURAL1 by x>=1 ; is usually much more efficient
1729 % note : removes virtual timeout in test 290
1730 % !,
1731 % TBound = b(integer(Bound),integer,[]), print('REPLACE: '),print_bexpr(b(member(X,SET),pred,I)),nl, print_bexpr(b(greater_equal(X,TBound),pred,I)),nl.
1732 cleanup_post(not_member(X,B),pred,I,falsity,pred,[was(not_member(X,B))|I],multi/remove_type_not_member) :-
1733 is_just_type(B),
1734 nonmember(label(_),I), % the user has explicitly labeled this conjunct
1735 !.
1736 cleanup_post(member(X,TSet),pred,I,equal(X,One),pred,I,multi/remove_member_one_element_set) :-
1737 singleton_set_extension(TSet,One),
1738 !,
1739 % X:{One} <=> X=One
1740 true. %,print('Introducing equality: '),print_bexpr(X), print(' = '), print_bexpr(One),nl.
1741 cleanup_post(member(X,b(Set,_,_)),pred,I,not_equal(X,One),pred,I,multi/remove_member_setdiff) :-
1742 Set = set_subtraction(MaximalSet,SONE),
1743 singleton_set_extension(SONE,One),
1744 definitely_maximal_set(MaximalSet),
1745 !, % x : INTEGER-{One} <=> x/=One
1746 (debug_mode(off) -> true
1747 ; print('Replacing member of set_subtraction: '), print_bexpr(MaximalSet), print(' - '), print_bexpr(SONE),nl).
1748 cleanup_post(not_member(X,TSet),pred,I,not_equal(X,One),pred,I,multi/remove_member_one_element_set) :-
1749 singleton_set_extension(TSet,One),
1750 !,
1751 % X/:{One} <=> X/=One
1752 true.
1753 cleanup_post(member(E,b(fin_subset(E2),_,_)),pred,I,finite(E),pred,I,multi/introduce_finite) :-
1754 (same_texpr(E,E2); is_just_type(E2)),!. % print(introduce(finite(E))),nl.
1755 cleanup_post(not_member(E,b(fin_subset(E2),_,_)),pred,I,NotFinite,pred,I,multi/introduce_not_finite) :-
1756 (same_texpr(E,E2); is_just_type(E2)),!,
1757 create_negation(b(finite(E),pred,I),TNotP), get_texpr_expr(TNotP,NotFinite).
1758 /* do we want need this rule ?:
1759 clenaup_post(member(b(couple(A,B),couple(TA,TB),IC),ID),pred,I,equal(A,B),pred,I,multi/replace_member_id) :-
1760 is_is_event_b_identity(ID), !.
1761 */
1762 cleanup_post(member(b(couple(A,B),couple(TA,TB),IC),b(reverse(Rel),_,_)),pred,I,member(ICouple,Rel),pred,I,multi/remove_reverse) :- !,
1763 % (A,B) : Rel~ ===> (B,A) : Rel
1764 % can be detrimental for performance when A is known and B is not and Rel is large
1765 \+ data_validation_mode,
1766 (debug_mode(off) -> true ; print('Removed inverse (~): '),print_bexpr(Rel),nl),
1767 ICouple = b(couple(B,A),couple(TB,TA),IC).
1768 cleanup_post(member(LHS,ITE),pred,I,Result,pred,I,multi/member_if_then_else) :-
1769 get_texpr_expr(ITE,if_then_else(IFPRED,THEN,ELSE)),
1770 (definitely_empty_set(ELSE)
1771 -> A=THEN, P = IFPRED
1772 ; definitely_empty_set(THEN)
1773 -> A=ELSE, create_negation(IFPRED,P)
1774 ),
1775 % x: IF P THEN A ELSE {} END --> P & x:A
1776 % x: IF P THEN {} ELSE A END --> not(P) & x:A
1777 % appears in some generated Caval machines
1778 % x: IF a=TRUE THEN {11} ELSE {} END & x>11 can now be solved deterministically
1779 MEM = b(member(LHS,A),pred,I),
1780 conjunct_predicates([P,MEM],TR),
1781 (debug_mode(off) -> true ; print('Replace member of if-then-else by: '),print_bexpr(TR),nl),
1782 get_texpr_expr(TR,Result).
1783 cleanup_post(member(LHS,Comprehension),pred,I,Result,pred,NewInfo,multi/remove_member_comprehension) :-
1784 Comprehension = b(ComprSet,_,_),
1785 is_comprehension_set(ComprSet,[TID],Body),
1786 get_texpr_id(TID,ID),
1787 % LHS:{x|P(x)} ==> P(LHS)
1788 ? replace_id_by_expr_with_count(Body,ID,LHS,TResult,Count),
1789 % rewrite could duplicate LHS: not an issue in CSE mode; optimization relevant in normalize_ast mode
1790 ? is_replace_id_by_expr_ok(LHS,ID,Count,remove_member_comprehension),
1791 !,
1792 % could introduce LET if necessary because ID occurs multiple times (Count>1)
1793 get_texpr_expr(TResult,Result),
1794 get_texpr_info(TResult,I1),
1795 add_important_info_from_super_expression(I,I1,NewInfo),
1796 (debug_mode(off) -> true ; print('Remove element of comprehension_set: '),print_bexpr(Comprehension),nl,
1797 format(' rewriting to (~w): ',[Count]),print_bexpr(TResult),nl).
1798 cleanup_post(not_member(LHS,Comprehension),pred,I,Result,pred,I,multi/remove_not_member_comprehension) :-
1799 Comprehension = b(ComprSet,_,_),
1800 is_comprehension_set(ComprSet,[TID],Body),
1801 get_texpr_id(TID,ID),
1802 % LHS/:{x|P(x)} ==> not(P(LHS))
1803 replace_id_by_expr_with_count(Body,ID,LHS,TResult,Count),
1804 % rewrite could duplicate LHS: not an issue in CSE mode; optimization relevant in normalize_ast mode
1805 ? is_replace_id_by_expr_ok(LHS,ID,Count,remove_not_member_comprehension),
1806 !,
1807 Result = negation(TResult),
1808 (debug_mode(off) -> true ; print('Remove not element of comprehension_set: '),print_bexpr(Comprehension),nl,
1809 format(' rewriting to (~w): not(',[Count]),print_bexpr(TResult),print(')'),nl).
1810 cleanup_post(comprehension_set(Ids,Body),Type,I,NewExpr,Type,I2,Rule) :-
1811 ? cleanup_comprehension_set(Ids,Body,Type,I,NewExpr,I2,Rule),
1812 !.
1813 cleanup_post(subset(A,B),pred,I,truth,pred,[was(subset(A,B))|I],multi/remove_type_subset) :-
1814 is_just_type(B),
1815 nonmember(label(_),I), % the user has explicitly labeled this conjunct
1816 !.
1817 cleanup_post(not_subset(A,B),pred,I,falsity,pred,[was(not_subset(A,B))|I],multi/remove_type_not_subset) :-
1818 is_just_type(B),
1819 nonmember(label(_),I), % the user has explicitly labeled this conjunct
1820 !.
1821 cleanup_post(SUB,pred,I,NewPred,pred,[generated_conjunct|I],multi/replace_subset_by_element) :-
1822 is_subset(SUB,A,B),
1823 is_set_extension(A,List),
1824 !, % for sequence extension we don't need this as the interpreter knows exactly the cardinality of a sequence_extension ?
1825 % applying rule {x1,x2,...} <: B <=> x1:B & x2:B & ...
1826 maplist(gen_member_predicates(B),List,Conjuncts),
1827 conjunct_predicates(Conjuncts,TNewPred),
1828 % print('detected subset-member rule: '),print_bexpr(TNewPred),nl,
1829 get_texpr_expr(TNewPred,NewPred).
1830 cleanup_post(SUB,pred,I,NewPred,pred,[generated_conjunct|I],multi/replace_union_subset) :-
1831 is_subset(SUB,A,B),
1832 % mark conjunct as generated: used e.g. by flatten_conjunct in predicate_evaluator
1833 get_texpr_expr(A,union(_,_)),!,
1834 % applying rule A1 \/ A2 <: B <=> A1 <: B & A2 <: B
1835 % could be detrimental if checking that something is an element of B is expensive
1836 extract_unions(A,As),
1837 findall(Subi,(member(Ai,As),safe_create_texpr(subset(Ai,B),pred,I,Subi)),Conj), % we could try and re-run clean-up ? safe_create_texpr will ensure WD info set
1838 conjunct_predicates(Conj,TNewPred),
1839 get_texpr_expr(TNewPred,NewPred).
1840 cleanup_post(Comp,pred,I,SComp,pred,I,multi/simplify_cse_comparison) :-
1841 % simplify comparison operations; can result in improved constraint propagation
1842 % e.g., ia + CSE1 * 2 > ia + fa <=> CSE1 * 2 > fa for Setlog/prob-ttf/qsee-TransmitMemoryDumpOk21_SP_3.prob
1843 comparison(Comp,A,B,SComp,SA,SB),
1844 simplify_comparison_terms(A,B,SA,SB),!,
1845 (debug_mode(off) -> true
1846 ; print('Simplified: '),print_bexpr(b(Comp,pred,I)),
1847 print(' <=> '),print_bexpr(b(SComp,pred,I)),nl).
1848 cleanup_post(EMPTYSET,T,I,empty_set,T,[was(EMPTYSET)|I],multi/detect_emptyset) :- EMPTYSET \= empty_set,
1849 definitely_empty_set(b(EMPTYSET,T,I)),
1850 (debug_mode(off) -> true
1851 ; print('Detected empty set: '), print_bexpr(b(EMPTYSET,T,I)),nl).
1852 cleanup_post(equal(A,B),pred,I,truth,pred,[was(equal(A,B))|I],multi/remove_equality) :-
1853 same_texpr(A,B),always_well_defined_or_disprover_mode(A),!. % ,print(removed_equal(A,B)),nl.
1854 cleanup_post(equal(A,B),pred,I,equal(A2,B2),pred,I,multi/simplify_equality) :-
1855 simplify_equality(A,B,A2,B2).
1856 cleanup_post(not_equal(A,B),pred,I,not_equal(A2,B2),pred,I,multi/simplify_inequality) :-
1857 simplify_equality(A,B,A2,B2).
1858 cleanup_post(equal(A,B),pred,I,falsity,pred,[was(equal(A,B))|I],multi/remove_equality_false) :-
1859 different_texpr_values(A,B),!. %,print(removed_equal_false(A,B)),nl.
1860 cleanup_post(equal(A,B),pred,I,greater(Low,Up),pred,I,multi/remove_equality) :-
1861 % Low..Up = {} <=> Low>Up % is also handled by constraint solver; but other simplifications can apply here
1862 ? (definitely_empty_set(B), is_interval(A,Low,Up) ;
1863 ? definitely_empty_set(A), is_interval(B,Low,Up)),!,
1864 (debug_mode(off) -> true
1865 ; print('Simplified: '), print_bexpr(b(equal(A,B),pred,I)), print(' <=> '),
1866 print_bexpr(b(greater(Low,Up),pred,I)),nl).
1867 cleanup_post(CardGt0Expr,pred,I,not_equal(X,EmptySet),pred,I,multi/remove_cardgt0) :-
1868 get_geq_comparison(CardGt0Expr,Card,One),
1869 % card(P) > 0 -> P\={} if wd guaranteed; also rewrites card(P) >= 1
1870 Card = b(card(X),integer,_), get_integer(One,1),
1871 finite_set_or_disprover_mode(X), % as we keep X, it is sufficient for X to be finite for the rule to be ok
1872 get_texpr_type(X,TX), get_texpr_info(One,I0),
1873 EmptySet = b(empty_set,TX,I0),!,
1874 (debug_mode(off) -> true ; print('Removed card(.) > 0 for set: '), print_bexpr(X), nl).
1875 cleanup_post(CardEq0Expr,pred,I,equal(X,EmptySet),pred,I,multi/remove_cardeq0) :-
1876 is_equality(b(CardEq0Expr,pred,I),Card,Zero),
1877 % card(P) = 0 -> P={} if wd guaranteed
1878 Card = b(card(X),integer,_), get_integer(Zero,0),
1879 finite_set_or_disprover_mode(X),
1880 get_texpr_type(X,TX), get_texpr_info(Zero,I0),
1881 EmptySet = b(empty_set,TX,I0),!,
1882 (debug_mode(off) -> true ; print('Removed card(.) = 0 for set: '), print_bexpr(X), nl).
1883 cleanup_post(CardLt1Expr,pred,I,equal(X,EmptySet),pred,I,multi/remove_cardlt1) :-
1884 get_leq_comparison(CardLt1Expr,Card,Zero),
1885 % card(P) <= 0 -> P={} if wd guaranteed; TODO: also detect card(P) < 1
1886 Card = b(card(X),integer,_), get_integer(Zero,0),
1887 finite_set_or_disprover_mode(X),
1888 get_texpr_type(X,TX), get_texpr_info(Zero,I0),
1889 EmptySet = b(empty_set,TX,I0),!,
1890 (debug_mode(off) -> true ; print('Removed card(.) <= 0 for set: '), print_bexpr(X), nl).
1891 cleanup_post(member(Card,Natural),pred,I,truth,pred,I,multi/remove_card_natural) :-
1892 % card(P) : NATURAL -> truth if wd guaranteed
1893 Card = b(card(X),integer,_),
1894 is_integer_set(Natural,'NATURAL'),
1895 always_well_defined_or_disprover_mode(Card),
1896 !,
1897 (debug_mode(off) -> true ; print('Removed card(.):NATURAL for set: '), print_bexpr(X), nl).
1898 cleanup_post(not_equal(A,B),pred,I,less_equal(Low,Up),pred,I,multi/remove_equality) :-
1899 % Low..Up \= {} <=> Low<=Up % is also handled by constraint solver; but other simplifications can apply here
1900 ? (definitely_empty_set(B), is_interval(A,Low,Up) ;
1901 definitely_empty_set(A), is_interval(B,Low,Up)),!,
1902 (debug_mode(off) -> true
1903 ; print('Simplified: '), print_bexpr(b(equal(A,B),pred,I)), print(' <=> '),
1904 print_bexpr(b(less_equal(Low,Up),pred,I)),nl).
1905 cleanup_post(equal(A,B),pred,I,equal(A,RLet),pred,I,single/detect_recursion) :-
1906 % "A" should be an identifier
1907 get_texpr_id(A,ID),
1908 % check if some side conditions are fulfilled where the recursion detection can be enabled
1909 recursion_detection_enabled(A,B,I),
1910 % A must be recursively used in B:
1911 ? find_recursive_usage(B,ID),
1912 % TO DO: also find mutual recursion !
1913 debug_println(9,recursion_detected(ID)),
1914 !, % create an recursive_let where the body is annotated to be symbolic
1915 get_texpr_type(B,Type), add_texpr_infos(B,[prob_annotation('SYMBOLIC')],B2),
1916 mark_recursion(B2,ID,B3),
1917 %print(marked_recursion(ID)),nl,
1918 safe_create_texpr(recursive_let(A,B3),Type,RLet).
1919 cleanup_post(recursive_let(TID,TBody),T,_,Body,T,I2,single/remove_recursive_let) :- get_texpr_id(TID,ID),
1920 \+ occurs_in_expr(ID,TBody),
1921 debug_println(19,removing_recursive_let(ID)), % required for test 1225
1922 TBody = b(Body,_,I2).
1923 cleanup_post(equal(A,B),pred,Info1,ResultExpr,pred,Info3,multi/simplify_bool_true_false) :-
1924 % simplify bool(X)=TRUE -> X and bool(X)=FALSE -> not(X)
1925 ( get_texpr_expr(A,convert_bool(X)), get_texpr_boolean(B,BOOLVAL)
1926 ;
1927 get_texpr_boolean(A,BOOLVAL),get_texpr_expr(B,convert_bool(X))
1928 ),
1929 get_texpr_info(X,Info2),
1930 add_important_info_from_super_expression(Info1,Info2,Info3),
1931 (BOOLVAL = boolean_true -> get_texpr_expr(X,ResultExpr) ;
1932 BOOLVAL = boolean_false -> create_negation(X,TNX), get_texpr_expr(TNX,ResultExpr)),
1933 !,
1934 (debug_mode(off) -> true
1935 ; format('Simplifying bool(.)=~w to ',[BOOLVAL]),translate:print_bexpr(b(ResultExpr,pred,Info3)),nl).
1936 %cleanup_post(equal(A,B),pred,Info1,equal(REL,CartProd),pred,Info1,multi/simplify_image) :-
1937 % cannot be applied yet; SETS not precompiled yet !
1938 % A = b(image(REL,SetExt),_,_),
1939 % % REL[{OneEl}] = B ----> REL = {OneEl}*B if OneEl is the only possible value
1940 % % such signature appear in Alloy generated code
1941 % SetExt = b(set_extension([_]),set(global(GlobalSetName)),_),
1942 % %bmachine:b_get_named_machine_set_calc(GlobalSetName,_,[_]),
1943 % b_global_set_cardinality(Type,1), % cannot be called yet; global sets not precompiled
1944 % !,
1945 % get_texpr_type(REL,RelType),
1946 % safe_create_texpr(cartesian_product(SetExt,B),RelType,CartProd),
1947 % format('Translating image for singleton set'), print_bexpr(b(equal(REL,CartProd),pred,[])),nl.
1948 cleanup_post(not_equal(A,B),pred,I,falsity,pred,[was(not_equal(A,B))|I],multi/remove_disequality) :-
1949 same_texpr(A,B),always_well_defined_or_disprover_mode(A),!. % ,print(removed_not_equal(A,B)),nl.
1950 % sometimes one uses & TRUE=TRUE to finish off guards, invariants, ...
1951 % exchange lambda expressions by a comprehension set
1952 % TO DO: also add rule for bool(X)=FALSE -> not(X)
1953 cleanup_post(not_equal(A,B),pred,I,truth,pred,[was(not_equal(A,B))|I],multi/remove_disequality_false) :-
1954 different_texpr_values(A,B),!. % ,print(removed_not_equal_false(A,B)),nl.
1955 cleanup_post(not_equal(A,B),pred,I,NewP,pred,[was(not_equal(A,B))|I],multi/not_disjoint_disequality) :-
1956 /* Set1 /\ Set2 /= {} <===> #(zz).(zz:Set1 & zz:Set2) */
1957 preferences:preference(use_smt_mode,true), /* currently this rewriting makes test 1112 fail; TO DO: investigate */
1958 definitely_empty_set(B),
1959 get_texpr_expr(A,intersection(Set1,Set2)),!,
1960 get_texpr_type(Set1,Set1Type), unify_types_strict(Set1Type,set(T)),
1961 ID = b(identifier('_zzzz_unary'),T,[generated]),
1962 ESet1 = b(member(ID,Set1),pred,[]),
1963 ESet2 = b(member(ID,Set2),pred,[]),
1964 create_exists_opt([ID],[ESet1,ESet2],NewPredicate),
1965 (debug_mode(off) -> true
1966 ; print('Transformed not disjoint disequality: '),print_bexpr(NewPredicate),nl),
1967 get_texpr_expr(NewPredicate,NewP).
1968 cleanup_post(equal(b(intersection(A,B),_,_),Empty),pred,I,not_equal(El1,El2),pred,[was(intersection)|I],multi/detect_not_equal) :-
1969 % {El1} /\ {El2} = {} --> El1 \= El2 (disjoint sets)
1970 singleton_set_extension(A,El1),
1971 singleton_set_extension(B,El2),
1972 definitely_empty_set(Empty).
1973 cleanup_post(equal(b(intersection(A,B),_,_),Empty),pred,I,NewDisequality,pred,[was(intersection)|I],multi/detect_disjoint_set_extensions) :-
1974 % {El1,...} /\ {El2,...} = {} --> El1 \= El2 & .... (disjoint sets)
1975 get_texpr_expr(A,set_extension(Els1)), length(Els1,Len1), Len1 < 20,
1976 get_texpr_expr(B,set_extension(Els2)), length(Els2,Len2), Len2 < 20,
1977 Len1 * Len2 < 100,
1978 definitely_empty_set(Empty),
1979 ? maplist(simple_expression,Els1), % avoid duplication of computation
1980 ? maplist(simple_expression,Els2), % ditto
1981 findall(NotEqual, (member(A1,Els1),member(B1,Els2),safe_create_texpr(not_equal(A1,B1),pred,NotEqual)),
1982 NotEquals),
1983 conjunct_predicates(NotEquals,TRes),
1984 (debug_mode(off) -> true
1985 ; write('Expanding disjoint set constraint: '),translate:print_bexpr(TRes),nl
1986 ),
1987 get_texpr_expr(TRes,NewDisequality).
1988 cleanup_post(greater(A,B),pred,I,Res,pred,[was(greater(A,B))|I],multi/eval_greater) :-
1989 get_integer(A,IA), get_integer(B,IB),
1990 (IA>IB -> Res = truth ; Res=falsity).
1991 cleanup_post(less(A,B),pred,I,Res,pred,[was(less(A,B))|I],multi/eval_less) :-
1992 get_integer(A,IA), get_integer(B,IB),
1993 (IA<IB -> Res = truth ; Res=falsity).
1994 cleanup_post(greater_equal(A,B),pred,I,Res,pred,[was(greater_equal(A,B))|I],multi/eval_greater_equal) :-
1995 get_integer(A,IA), get_integer(B,IB),
1996 (IA >= IB -> Res = truth ; Res=falsity).
1997 cleanup_post(less_equal(A,B),pred,I,Res,pred,[was(less_equal(A,B))|I],multi/eval_less_equal) :-
1998 get_integer(A,IA), get_integer(B,IB),
1999 (IA =< IB -> Res = truth ; Res=falsity).
2000 % TODO: similar things for less_real ?
2001 cleanup_post(CHOOSE,real,I,div_real(A,B),real,I,multi/replace_tla_real_division) :-
2002 is_tla_real_division(CHOOSE,A,B),
2003 % Detect TLA real division defined by Div_1(a, b) == CHOOSE({m|m:REAL & m*b=a})
2004 add_debug_message(ast_cleanup,'Translated TLA+ division to real division: ',b(div_real(A,B),real,I),I).
2005 cleanup_post(negation(A),pred,I,falsity,pred,[was(negation(A))|I],multi/remove_negation_truth) :-
2006 is_truth(A),!. % ,print(negation(A)),nl.
2007 cleanup_post(negation(A),pred,I,truth,pred,[was(negation(A))|I],multi/remove_negation_falsity) :-
2008 is_falsity(A),!. % ,print(negation(A)),nl.
2009 cleanup_post(convert_bool(A),boolean,I,Res,boolean,I,multi/remove_convert_bool) :-
2010 (is_truth(A) -> Res = boolean_true
2011 ; is_falsity(A) -> Res = boolean_false
2012 ; is_equality(A,LHS,BoolTRUE), get_texpr_boolean(BoolTRUE,boolean_true) % bool(LHS=TRUE) --> LHS
2013 -> get_texpr_expr(LHS,Res)
2014 ; A=not_equal(LHS,BoolFALSE), get_texpr_boolean(BoolFALSE,boolean_false) % bool(LHS/=FALSE) --> LHS
2015 -> get_texpr_expr(LHS,Res)
2016 ),!.
2017 cleanup_post(assertion_expression(Cond,_ErrMsg,Expr),_T,I0,BE,TE,IE,multi/remove_assertion_expression) :-
2018 is_truth(Cond),!,
2019 Expr = b(BE,TE,I1),
2020 add_important_info_from_super_expression(I0,I1,IE).
2021 cleanup_post(card(INTERVAL), T, I, Res, T, I, single/card_of_interval) :-
2022 % e.g., card(1..4) -> 4
2023 ? is_interval(INTERVAL, LowerBound, UpperBound),
2024 get_integer(LowerBound, L),
2025 number(L),
2026 get_integer(UpperBound, U),
2027 number(U),
2028 (L > U -> Card = 0 ; Card is 1+(U - L)),
2029 !,
2030 Res = integer(Card).
2031 cleanup_post(member(Empty,TPow),T,I,Res,T,I,single/empty_set_in_pow_subset) :-
2032 definitely_empty_set(Empty), % useful for z3 integration to prevent powerset constraint
2033 TPow = b(POW,_,_),
2034 (POW=pow_subset(_) -> RT=truth
2035 ; POW=fin_subset(_) -> RT=truth
2036 ; POW=pow1_subset(_) -> RT=falsity
2037 ; POW=fin1_subset(_) -> RT=falsity),
2038 always_well_defined_or_disprover_mode(TPow),
2039 !,
2040 Res = RT.
2041 cleanup_post(card(Empty),T,I,Res,T,I,single/card_singleton_set) :-
2042 Empty = b(empty_set,_,_), % useful for z3 integration to prevent cardinality constraint
2043 !,
2044 Res = integer(0).
2045 cleanup_post(card(SONE),T,I,Res,T,I,single/card_singleton_set) :-
2046 singleton_set_extension(SONE,One), % card({One}) = 1 ; useful for alloy2b
2047 always_well_defined_or_disprover_mode(One),
2048 !,
2049 Res = integer(1).
2050 cleanup_post(cartesian_product(A,B),T,I,Res,T,I,single/cartesian_product_to_pair) :-
2051 singleton_set_extension(A,El1),
2052 singleton_set_extension(B,El2), % {A}*{B} -> {A|->B} ; happens in Alloy translations a lot
2053 !,
2054 get_texpr_type(El1,T1), get_texpr_type(El2,T2),
2055 safe_create_texpr(couple(El1,El2),couple(T1,T2),Pair),
2056 Res = set_extension([Pair]).
2057 cleanup_post(image(Fun,Empty),T,I,empty_set,T,I,multi/image_empty_optimisation) :-
2058 definitely_empty_set(Empty),
2059 always_well_defined_or_wd_improvements_allowed(Fun),
2060 !,
2061 (debug_mode(off) -> true
2062 ; add_message(ast_cleanup,'Removing unnecessary image of empty set: ',Fun,I)).
2063 cleanup_post(union(A,B),T,I,Res,T,[add_element_to_set|I],multi/add_element_to_set) :- % multi: cycle check done in info field
2064 ? \+ member(add_element_to_set,I),
2065 ( singleton_set_extension(B,_El) -> Res = union(A,B)
2066 ; singleton_set_extension(A,_El) -> Res = union(B,A)),
2067 !. %,print(detected_add_singleton_element(_El)),nl.
2068 cleanup_post(union(A,B),T,I,Res,T,I,multi/union_empty_set) :-
2069 ( definitely_empty_set(A) -> get_texpr_expr(B,Res) % {} \/ B = B
2070 ; definitely_empty_set(B) -> get_texpr_expr(A,Res) % A \/ {} = A
2071 ),
2072 !.
2073 cleanup_post(intersection(A,B),T,I,empty_set,T,I,multi/intersection_empty_set) :-
2074 ( definitely_empty_set(A) -> true % A /\ {} = {}
2075 ; definitely_empty_set(B) -> true % {} /\ B = {}
2076 ),
2077 !.
2078 cleanup_post(set_subtraction(A,B),T,I,Res,T,I,multi/intersection_empty_set) :-
2079 ( definitely_empty_set(A) -> Res=empty_set % {} - B = {}
2080 ; definitely_empty_set(B) -> get_texpr_expr(A,Res) % A - {} = A
2081 ),
2082 !.
2083 cleanup_post(general_union(SetExt),Type,I0,Res,Type,Info,multi/general_union_set_extension) :- % union_generalized
2084 % union({a,b,c,...}) = a \/ b \/ c ...
2085 SetExt = b(set_extension(LIST),_,I1),
2086 add_important_info_from_super_expression(I0,I1,Info),
2087 % no need to apply rule if already transformed into avl in cleanup_pre, hence we do not call is_set_extension
2088 construct_union_from_list(LIST,Type,Info,TRes),
2089 !,
2090 (debug_mode(on) -> print('translated_general_union: '), print_bexpr(TRes),nl ; true),
2091 get_texpr_expr(TRes,Res).
2092 cleanup_post(general_intersection(SetExt),Type,I0,Res,Type,Info,multi/general_inter_set_extension) :- % inter_generalized
2093 % inter({a,b,c,...}) = a /\ b /\ c ...
2094 SetExt = b(set_extension(LIST),_,I1),
2095 add_important_info_from_super_expression(I0,I1,Info),
2096 % no need to apply rule if already transformed into avl in cleanup_pre, hence we do not call is_set_extension
2097 construct_inter_from_list(LIST,Type,Info,TRes),
2098 !,
2099 (debug_mode(on) -> print('translated_general_intersection: '), print_bexpr(TRes),nl ; true),
2100 get_texpr_expr(TRes,Res).
2101 cleanup_post(SUB,pred,I0,FORALL,pred,FInfo,multi/general_union_subset) :-
2102 is_subset(SUB,UNION,T),
2103 % union(S) <: T ===> !x.(x:S => x <: T)
2104 % currently: subsets of T may be generated, but it does not propagate well to S
2105 UNION = b(general_union(S),_,_),
2106 !,
2107 get_unique_id_inside('_zzzz_unary',S,T,ID),
2108 get_texpr_type(S,SType), is_set_type(SType,IDType),
2109 TID = b(identifier(ID),IDType,[generated]),
2110 safe_create_texpr(member(TID,S),pred,LHS),
2111 safe_create_texpr(subset(TID,T),pred,RHS),
2112 create_implication(LHS,RHS,NewForallBody),
2113 create_forall([TID],NewForallBody,TFORALL),
2114 TFORALL = b(FORALL,pred,I1),
2115 add_important_info_from_super_expression(I0,I1,FInfo),
2116 % see test 1854, and ProZ ROZ/model.tex
2117 (debug_mode(on) -> print('translated_general_union subset: '), print_bexpr(TFORALL),nl ; true).
2118 cleanup_post(size(Seq),integer,Info,Res,integer,Info,multi/size_append) :-
2119 get_texpr_expr(Seq,concat(A,B)),
2120 % size(A^B) = size(A)+size(B) useful e.g. for test 1306
2121 !,
2122 Res = add(b(size(A),integer,Info),b(size(B),integer,Info)).
2123 cleanup_post(concat(A,B),Type,I0,Seq,Type,[was(concat)|NewInfo],multi/concat_empty) :-
2124 ( definitely_empty_set(A) -> b(Seq,_,I1)=B
2125 ; definitely_empty_set(B) -> b(Seq,_,I1)=A
2126 ),!,
2127 add_important_info_from_super_expression(I0,I1,NewInfo).
2128 cleanup_post(concat(A,B),Type,I0,Seq,Type,[was(concat)|I0],multi/concat_singleton_seq) :-
2129 ( is_singleton_sequence(B,Element) -> Seq = insert_tail(A,Element)
2130 ; is_singleton_sequence(A,Element) -> Seq = insert_front(Element,B)
2131 ),!,
2132 debug_format(19,'Concat with singleton sequence detected~n',[]).
2133 cleanup_post(E,integer,I,Res,integer,[was(Operator)|I],multi/constant_expression) :-
2134 pre_compute_static_int_expression(E,Result),!,
2135 functor(E,Operator,_),
2136 % format('Precomputed: ~w for ',[Result]), translate:print_bexpr(b(E,integer,[])),nl,
2137 Res = integer(Result).
2138 cleanup_post(min(Interval),integer,I0,Res,integer,Info,multi/eval_min_interval) :-
2139 is_interval_or_singleton(Interval,Low,Up),
2140 get_integer(Low,L), number(L),
2141 get_integer(Up,U), number(U), L =< U, % non-empty interval
2142 debug_println(5,simplified_min_interval(L,U,L)),
2143 Res = integer(L), get_texpr_info(Low,I1),
2144 add_important_info_from_super_expression(I0,I1,Info).
2145 cleanup_post(max(Interval),integer,I0,Res,integer,Info,multi/eval_max_interval) :-
2146 is_interval_or_singleton(Interval,Low,Up),
2147 get_integer(Low,L), number(L),
2148 get_integer(Up,U), number(U), L =< U, % non-empty interval
2149 debug_println(5,simplified_max_interval(L,U,U)),
2150 Res = integer(U), get_texpr_info(Low,I1),
2151 add_important_info_from_super_expression(I0,I1,Info).
2152 cleanup_post(first(Seq),Type,I0,Res,Type,Info,multi/first_seq_extension) :-
2153 is_sequence_extension(Seq,List), List = [First|Rest],
2154 (Rest == [] -> true ; preferences:get_preference(disprover_mode,true)), % we may remove WD issue otherwise (TO DO: check if Rest contains any problematic elements)
2155 !,
2156 First = b(Res,Type,I1),
2157 add_important_info_from_super_expression(I0,I1,Info).
2158 cleanup_post(last(Seq),Type,I0,Res,Type,Info,multi/first_seq_extension) :-
2159 is_sequence_extension(Seq,List), List = [First|Rest],
2160 (Rest == [] -> true ; preferences:get_preference(disprover_mode,true)), % we may remove WD issue otherwise (TO DO: check if list contains any problematic elements)
2161 !,
2162 last([First|Rest],b(Res,Type,I1)),
2163 add_important_info_from_super_expression(I0,I1,Info).
2164 cleanup_post(function(Fun,Arg),Type,Info,New,Type,NewInfo,Rule) :-
2165 ? cleanup_post_function(Fun,Arg,Type,Info,New,NewInfo,Rule).
2166 cleanup_post(range(SETC),Type,I, comprehension_set(RangeIds2,NewCompPred),Type,I,single/range_setcompr) :-
2167 % translate ran({x1,...xn|P}) into {xn| #(x1,...).(P)} ; particularly interesting if x1... contains large datavalues (e.g., C_02_001.mch from test 1131)
2168 get_texpr_expr(SETC,comprehension_set(CompIds,CompPred)),
2169 get_domain_range_ids(CompIds,DomainIds,RangeIds), % print(range(CompIds,DomainIds,RangeIds)),nl,
2170 %\+((member(ID,RangeIds),get_texpr_id(ID,'_lambda_result_'))), % for test 612; maybe disable optimisation if memory consumption of variables small
2171 !, % TO DO: also detect patterns such as dom(dom( or ran(ran( ... [Done ??]
2172 ? rename_lambda_result_id(RangeIds,CompPred,RangeIds2,CompPred1),
2173 rename_lambda_result_id(DomainIds,CompPred1,DomainIds2,CompPred2),
2174 create_outer_exists_for_dom_range(DomainIds2,CompPred2,NewCompPred), % will mark the exists; so that during expansion we will treat it differently for enumeration
2175 (debug_mode(off) -> true
2176 ; print('Encode range as existential quantification: '), print_bexpr(NewCompPred),nl).
2177 cleanup_post(domain(SETC),Type,I, comprehension_set(DomainIds2,NewCompPred),Type,I,single/domain_setcompr) :-
2178 % translate dom({x1,...xn|P}) into {x1,..| #(xn).(P)} ; particularly interesting if xn contains large datavalues
2179 % used to fail test 306 ; fixed by allow_to_lift_exists annotation
2180 \+ data_validation_mode, % sometimes this optimisation is counter-productive for data_validation, problem: test 1945
2181 get_texpr_expr(SETC,comprehension_set(CompIds,CompPred)),
2182 get_domain_range_ids(CompIds,DomainIds,RangeIds), % print(domain(CompIds,DomainIds,RangeIds)),nl,
2183 % \+ (member(ID,CompIds),get_texpr_id(ID,'_lambda_result_')),
2184 % WE HAVE TO BE CAREFUL if xn = LAMBDA_RESULT ; TO DO rename like above for range
2185 % example from test 292: rel(fnc({x,y|x:1..10 & y:1..x})) = {x,y|x:1..10 & y:1..x}
2186 %\+ data_validation_mode, % test 1945 fails with WD errors if we disable this rule
2187 !,
2188 % TO DO: detect when closure is lambda; e.g., for e.g. dom(pred) = INTEGER in test 292 : split(CompIds,Args,Types), closures:is_lambda_value_domain_closure(Args,Types,B, DomainValue, _),; currently create_exists_opt deals with most of this
2189 rename_lambda_result_id(DomainIds,CompPred,DomainIds2,CompPred1),
2190 rename_lambda_result_id(RangeIds,CompPred1,RangeIds2,CompPred2),
2191 create_outer_exists_for_dom_range(RangeIds2,CompPred2,NewCompPred),
2192 (debug_mode(off) -> true
2193 ; get_texpr_ids(DomainIds,DIS), get_texpr_ids(RangeIds,RIS),
2194 ajoin(['Encode domain over ',DIS,' as existential quantification over ',RIS,' : '],Msg),
2195 add_message(ast_cleanup,Msg,NewCompPred,I)).
2196 cleanup_post(domain(SETC),Type,I, comprehension_set(DomainIds,RestPred),Type,I,single/domain_setcompr) :-
2197 % translate dom({x1,...xn|P & xn=E}) into {x1,..| P} ; particularly interesting if xn contains large datavalues
2198 get_texpr_expr(SETC,comprehension_set(CompIds,CompPred)),
2199 get_domain_range_ids(CompIds,DomainIds,RangeIds), % print(domain(CompIds,DomainIds,RangeIds)),nl,
2200 ? \+ (member(ID,CompIds),get_texpr_id(ID,'_lambda_result_')),
2201 conjunction_to_list(CompPred,Preds),
2202 RangeIds = [TId],
2203 get_sorted_ids(RangeIds,Blacklist),
2204 select_equality(TId,Preds,Blacklist,_Eq,_Expr,RestPreds,_,check_well_definedness), % We could do check_well_definedness only if preference set
2205 conjunct_predicates_with_pos_info(RestPreds,RestPred),
2206 not_occurs_in_predicate(Blacklist,RestPred),
2207 !,
2208 % TO DO: use create_optimized exists; also treat inner existential quantification and merge
2209 (debug_mode(off) -> true
2210 ; write('Encode domain of lambda abstraction: '),print_bexpr(RestPred),nl).
2211 cleanup_post(precondition(TP,TS),subst,I0,S,subst,Info,multi/remove_triv_precondition) :-
2212 % remove trivial preconditions
2213 get_texpr_expr(TP,truth),!,
2214 get_texpr_expr(TS,S),get_texpr_info(TS,I1),
2215 add_important_info_from_super_expression(I0,I1,Info).
2216 cleanup_post(external_function_call('ENUM',[TA]),T,I,A,T,[prob_annotation('ENUM')|I],single/process_ENUM) :-
2217 (debug_mode(on) -> format(' Processing ENUM (~w): ',[T]),translate:print_bexpr(TA),nl ; true),
2218 % TO DO: do not process in DEFINITION of ENUM in LibraryProB.def
2219 get_texpr_expr(TA,A).
2220 cleanup_post(external_function_call('FORCE',[TA]),T,I,external_function_call('FORCE',[TA2]),T,I,single/process_FORCE) :-
2221 mark_comprehension_set_with(TA,'FORCE',TA2), % could be sufficient on its own if TA is a comprehension set
2222 % but we keep the call to FORCE, in case TA is re-written or more complex
2223 (debug_mode(off) -> true
2224 ; format(' Processing FORCE: ',[]),translate:print_bexpr(TA2),nl).
2225 cleanup_post(comprehension_set(TIds,Body),T,I1,comprehension_set(TIds,Body2),T,I1,single/detect_lambda_result_auto) :-
2226 get_texpr_info(Body,BI),
2227 (TIds=[_,_,_|_] % check if at least three ids
2228 -> true % for example useful here: {x,y,v| x:INTEGER & y:INTEGER & #z.(z=x+1 & x = y*y & v=z*z & y:1..10)} it could be useful to detect x as DO_NOT_ENUMERATE; currently we only enable this analysis for four ids at least
2229 ; nonmember(prob_annotation('LAMBDA'),BI) % it is a lambda with one argument, no use to do analysis
2230 ),
2231 perform_do_not_enumerate_analysis(TIds,Body,'SET COMPREHENSION',I1,Body2).
2232 cleanup_post(comprehension_set(Ids1,E1),T,I,comprehension_set(Ids2,E2),T,I,multi/detect_lambda_result_user_ann) :-
2233 get_texpr_expr(DNE,external_pred_call('DO_NOT_ENUMERATE',[TID])),
2234 get_texpr_id(TID,ID),
2235 ? member_in_conjunction(DNE,E1),
2236 NewInfo = prob_annotation('DO_NOT_ENUMERATE'(ID)), % similar to lambda_result
2237 E1 = b(PRED,pred,I1),
2238 nonmember(NewInfo,I1),
2239 get_texpr_id(TID,ID),
2240 ? nth1(Pos,Ids1,TID1,Rest),
2241 add_texpr_infos(TID1,[NewInfo],TID2),
2242 nth1(Pos,Ids2,TID2,Rest),
2243 add_message(detect_lambda_result,'Annotating comprehension set identifier with DO_NOT_ENUMERATE: ',ID,I1),
2244 E2 = b(PRED,pred,[NewInfo|I1]).
2245 cleanup_post(record_field(b(rec(Fields),TR,IR),Field),T,I,FieldVal,T,I, single/remove_field_access) :-
2246 always_well_defined_or_disprover_mode(b(rec(Fields),TR,IR)),
2247 ? member(field(Field,TFieldVal),Fields),!,
2248 (debug_mode(off) -> true ; add_message(remove_field_access,'Remove static field access: ',Field,I)), % cf test 1294
2249 get_texpr_expr(TFieldVal,FieldVal).
2250 cleanup_post(sequence([S1,b(sequence(S2),subst,_)]),subst,I,sequence([S1|S2]),subst,I, single/flatten_sequence2) :-
2251 debug_println(9,flatten_sequence2). % do we need something for longer sequences?
2252 cleanup_post(sequence([b(sequence(S1),subst,_)|S2]),subst,I,sequence(NewSeq),subst,I, single/flatten_sequence1) :-
2253 append(S1,S2,NewSeq),
2254 % avoid maybe calling filter_useless_subst_in_sequence again
2255 debug_println(9,flatten_sequence1).
2256 cleanup_post(sequence(S1),subst,I,sequence(S2),subst,I, single/remove_useless_subst_in_seuence) :-
2257 get_preference(useless_code_elimination,true),
2258 filter_useless_subst_in_sequence(S1,Change,S2), debug_println(filter_sequence(9,Change)).
2259 cleanup_post(sequence(Statements),subst,I,Result,subst,I, single/sequence_to_multi_assign) :-
2260 % merge sequence of assignments if possible
2261 merge_assignments(Statements,Merge,New), Merge==merged,
2262 construct_sequence(New,Result).
2263 % nl,print('Merged: '),translate:print_subst(b(Result,subst,I)),nl,nl.
2264 cleanup_post(parallel(Statements),subst,I,Result,subst,I, single/parallel_to_multi_assign) :-
2265 % this merges multiple assignments into a single one: advantage: only one waitflag set up
2266 % should probably not be done in INITIALISATION
2267 % print(parallel(Statements)),nl,trace,
2268 extract_assignments(Statements,LHS,RHS,Rest,Nr), % print(extracted(Nr,LHS)),nl,
2269 Nr>1,!,
2270 (debug_mode(on) ->
2271 print('Parallel to Assignment: '), translate:print_subst(b(parallel(Statements),subst,I)),nl
2272 ; true),
2273 (Rest == [] -> Result = assign(LHS,RHS)
2274 ; Result = parallel([b(assign(LHS,RHS),subst,[])|Rest])).
2275 %translate:print_subst(b(Result,subst,I)),nl.
2276 cleanup_post(select([CHOICE|Rest]),subst,I0,S,subst,Info,single/remove_select) :-
2277 Rest = [], % SELECT can have multiple true branches
2278 CHOICE=b(select_when(TRUTH,Subst),subst,_),
2279 is_truth(TRUTH),!,
2280 debug_println(19,'Removing useless SELECT'),
2281 get_texpr_expr(Subst,S),get_texpr_info(Subst,I1),
2282 add_hint_message(remove_select,'Removing useless SELECT','',I1),
2283 add_important_info_from_super_expression(I0,I1,Info).
2284 cleanup_post(select([CHOICE|Rest],_ELSE),subst,OldInfo,Res,subst,I,single/remove_select_else) :-
2285 CHOICE=b(select_when(TRUTH,Subst),subst,_),
2286 is_truth(TRUTH),!,
2287 (Rest = [] % completely useless SELECT
2288 -> add_hint_message(remove_select_else,'Removing useless SELECT','',OldInfo),
2289 get_texpr_expr(Subst,Res),get_texpr_info(Subst,I1),
2290 add_important_info_from_super_expression(OldInfo,I1,I)
2291 ; add_hint_message(remove_select_else,'Removing useless SELECT ELSE branch','',OldInfo),
2292 Res = select([CHOICE|Rest]), I=OldInfo).
2293 cleanup_post(let_expression([],[],TExpr),Type,I0,Expr,Type,I,multi/remove_let_expression) :- !,
2294 % remove trivial let expressions without any introduced identifiers
2295 % this rule makes only sense in combination with the next rule which removes
2296 % simple let identifiers
2297 get_texpr_expr(TExpr,Expr),
2298 get_texpr_info(TExpr,I1),
2299 add_important_info_from_super_expression(I0,I1,I).
2300 cleanup_post(let([],Pred,TExpr),Type,I0,Expr,Type,I,multi/remove_let) :- is_truth(Pred),!,
2301 % remove trivial let expressions without any introduced identifiers
2302 % this rule makes only sense in combination with the next rule which removes
2303 % simple let identifiers
2304 get_texpr_expr(TExpr,Expr),
2305 get_texpr_info(TExpr,I1),
2306 add_important_info_from_super_expression(I0,I1,I).
2307 cleanup_post(let_expression(TIds,Exprs,Expr),Type,I,
2308 let_expression(NIds,NExprs,NExpr),Type,I,multi/remove_let_expression2) :-
2309 ? simplify_let(TIds,Exprs,Expr,NIds,NExprs,NExpr),!,
2310 %format('~n Simplified Let ~w --> ~w~n',[TIds,NIds]),
2311 true.
2312 cleanup_post(let_predicate(TIds,Exprs,Body),Type,I,
2313 let_predicate(NIds,NExprs,NBody),Type,I,multi/remove_let_predicate2) :-
2314 ? simplify_let(TIds,Exprs,Body,NIds,NExprs,NBody),!,
2315 %format('~n Simplified Let ~w --> ~w~n',[TIds,NIds]),
2316 (is_truth(NBody), NIds \=[]
2317 -> add_debug_message(b_ast_cleanup,'Useless LET predicate: ',Body,I) % not removed due to WD ?
2318 ; true). % if NIds = [] then we will remove it in cleanup_post_essential
2319 cleanup_post(let_predicate(TIds,Exprs,Body),Type,I,
2320 NewExpr,Type,NewI,single/useless_let_message_or_removal) :-
2321 is_truth(Body),
2322 nonmember(useless_let,I),
2323 get_texpr_ids(TIds,Ids),
2324 TE=b(let_predicate(TIds,Exprs,Body),Type,I),
2325 (always_well_defined_or_wd_improvements_allowed(TE)
2326 -> NewExpr = truth, delete(I,contains_wd_condition,NewI),
2327 (always_well_defined_or_disprover_mode(TE)
2328 -> true
2329 ; TIds=[TID1|_],
2330 add_message(b_ast_cleanup,'Removing useless existentially quantified variables: ',Ids,TID1)
2331 )
2332 ; NewExpr = let_predicate(TIds,Exprs,Body), NewI=[useless_let|I],
2333 not_generated_exists_paras(TIds),
2334 % otherwise this was generated programmatically, e.g., in get_operation_enabling_condition, see test 625
2335 (nonmember(allow_to_lift_exists,I) -> true % ditto, e.g., by create_outer_exists_for_dom_range, see test 1945
2336 ; get_preference(data_validation_mode,true)),
2337 add_message(b_ast_cleanup,'Useless existentially quantified variables: ',Ids,TIds)
2338 ).
2339 % was disabled because simplify_let_subst also replaced in RHS of assignments
2340 % but now we check that a LET/ANY variable cannot be assigned to statically
2341 % so it should be safe now to replace simple equalities:
2342 cleanup_post(let(Ids,Pred,Subst),Type,I,
2343 let(NIds,NPred,NSubst),Type,I,multi/remove_let_subst2) :-
2344 simplify_let_subst(Ids,Pred,Subst,NIds,NPred,NSubst),! ,
2345 true. % translate:print_subst(b(let(NIds,NPred,NSubst),subst,[])),nl.
2346
2347
2348 cleanup_post(forall([ID],LHS,RHS),pred,IOld,Res,pred,IOld,single/expand_forall_set_extension) :-
2349 % expand !x.(x:{a,b,...} => RHS) into conjunction
2350 % can be useful e.g. for KODKOD when we pick an element from a set of sets
2351 \+ preferences:has_default_value(use_solver_on_load), % prob, used to be only enabled in Kodkod mode
2352 % TO DO: enable always; but maybe check that set_extension can be computed (which eval_set_extension will do) to avoid duplicating checks (!y.(y:{v,w} => expensive_pred) + what if v=w
2353 nonmember(do_not_optimize_away,IOld),
2354 get_texpr_expr(LHS,member(ID2,Set)),
2355 same_texpr(ID,ID2),
2356 is_set_extension(Set,SList),
2357 get_texpr_id(ID,AID),
2358 debug_format(19,'Expanding forall ~w ',[AID]),
2359 findall(C, (member(SEL,SList),replace_id_by_expr(RHS,AID,SEL,C)),Conjuncts),
2360 conjunct_predicates_with_pos_info(Conjuncts,ExpandedForAll),
2361 (silent_mode(on) -> true ; print_bexpr(ExpandedForAll),nl),
2362 get_texpr_expr(ExpandedForAll,Res).
2363 cleanup_post(forall(Ids1,LHS,RHS),pred,IOld,
2364 forall(Ids,NewLHS,NewRHS),pred,INew,multi/merge_forall) :-
2365 is_truth(LHS),
2366 RHS = b(forall(Ids2,NewLHS,NewRHS),pred,_),
2367 %((member(b(identifier(_),Type,_),Ids1), is_infinite_ground_type(Type)) -> true), % could be useful for tests 1441, 1447 ??
2368 (disjoint_ids(Ids1,Ids2)
2369 -> append(Ids1,Ids2,Ids),
2370 % !x.(truth => !y.(P=>Q) <==> !(x,y).(P=>Q)
2371 (debug_mode(off) -> true ; format('Merging forall ~w: ',[Ids]), print_bexpr(NewLHS),nl),
2372 add_removed_typing_info(IOld,INew)
2373 ; \+ preferences:get_preference(disprover_mode,true),
2374 translate:translate_bexpression(b(forall(Ids1,LHS,RHS),pred,IOld),PS),
2375 add_warning(b_ast_cleanup,'Variable clash in nested universal quantification: ',PS,IOld),
2376 fail
2377 ).
2378 cleanup_post(forall(Ids,LHS,RHS),pred,IOld,
2379 implication(Outer,FORALL),pred,IOld,single/detect_global_preds_forall1) :-
2380 % !x.(P(x) & Q => R(x) <==> Q => !x.(P(x) => R(x))
2381 % TO DO: maybe we should not lift things like printf, ... ?
2382 bsyntaxtree:detect_global_predicates(Ids,LHS,Outer,Inner),
2383 (debug_mode(off) -> true ; format('Lifting predicate (lhs) of forall ~w: ',[Ids]), print_bexpr(Outer),nl),
2384 construct_inner_forall(Ids,Inner,RHS,IOld,FORALL).
2385 % TO DO: implement similar lifting rules for exists(Ids,P)
2386 cleanup_post(forall(Ids,LHS,RHS),pred,IOld,
2387 conjunct(Outer,FORALL),pred,IOld,single/detect_global_preds_forall2) :-
2388 is_truth(LHS),
2389 % !x.(truth => Q & R(x) <==> Q & !x.(truth => R(x))
2390 bsyntaxtree:detect_global_predicates(Ids,RHS,Outer,Inner),
2391 (debug_mode(off) -> true ; format('Lifting predicate (rhs &) of forall ~w: ',[Ids]), print_bexpr(Outer),nl),
2392 construct_inner_forall(Ids,LHS,Inner,IOld, FORALL). % print_bexpr(FORALL),nl,nl.
2393 cleanup_post(forall(Ids,LHS,RHS),pred,IOld,
2394 implication(Outer,FORALL),pred,IOld,single/detect_global_preds_forall3) :-
2395 is_truth(LHS),
2396 RHS = b(implication(RHS1,RHS2),pred,_),
2397 % !x.(truth => (Q & R(x) => S(x)) <==> Q => !x.(truth => R(x) => S(x))
2398 bsyntaxtree:detect_global_predicates(Ids,RHS1,Outer,Inner),
2399 create_implication(Inner,RHS2,NewRHS),
2400 (debug_mode(off) -> true ; format('Lifting predicate (rhs =>) of forall ~w: ',[Ids]), print_bexpr(Outer),nl),
2401 construct_inner_forall(Ids,LHS,NewRHS,IOld, FORALL).
2402 cleanup_post(forall([TID1,TID2|OTHER],LHS,RHS),pred,IOld,
2403 forall([TID1,TID2|OTHER],NewLHS,RHS),pred,[prob_symmetry(ID1,ID2)|IOld],single/symmetry_detection) :-
2404 % DETECT Symmetries such as !(x,y).(x /= y => x=TRUE or y=TRUE)
2405 % !(x2,y).(x2 /= y & x2:s & y:s => x2=aa or y=aa)
2406 % f:1..n --> 1..(n-1) & !(x,y).(x/=y &x:dom(f) & y:1..n => f(x) /= f(y)) & n=9 (runtime 1 sec -> 0.78 sec)
2407 get_texpr_type(TID1,T), get_texpr_type(TID2,T),
2408 \+ preferences:get_preference(use_solver_on_load,kodkod), % e.g., Kodkod cannot properly deal with LEQ_SYM_BREAK, treats it like truth
2409 preferences:get_preference(use_static_symmetry_detection,true),
2410 sym_break_supported_type(T), % LEQ_SYM_BREAK not yet fully functional with SET types; TO DO: fix
2411 get_texpr_id(TID1,ID1), get_texpr_id(TID2,ID2),
2412 nonmember(prob_symmetry(ID1,ID2),IOld),
2413 ? rename_bt(LHS,[rename(ID1,ID2),rename(ID2,ID1)],LHS2),
2414 same_norm_texpr(LHS,LHS2),
2415 rename_bt(RHS,[rename(ID1,ID2),rename(ID2,ID1)],RHS2),
2416 same_norm_texpr(RHS,RHS2),
2417 construct_sym_break(T,TID1,TID2,LHS,SYMBREAK),
2418 conjunct_predicates_with_pos_info(LHS,SYMBREAK,NewLHS),
2419 (debug_mode(off) -> true
2420 ; format('SYMMETRY BREAKING FORALL: !(~w,~w).(',[ID1,ID2]),print_bexpr(NewLHS),
2421 print(' => '), print_bexpr(RHS),print(')'),nl).
2422 cleanup_post(forall(AllIds,P,Rhs),pred,I,NewPred,pred,INew,multi/forall_splitting) :-
2423 AllIds = [_TID1|TRestIDs0], TRestIDs0 = [_|_],
2424 get_preference(use_clpfd_solver,true), % with CLPFD false: maybe more likely to reduce performance
2425 % NOTE: we could destroy symmetry reduction detection if TRestIDs = [TID2], but we run after symmetry detection
2426 % !(x,y,...).(x:SET & RestPred => Rhs) == !x.(x:SET => !(y,..).(RestPred => Rhs))
2427 conjunction_to_list(P,[MEM|RestPreds]),
2428 is_membership(MEM,LHS,Set),
2429 ? is_forall_membership_pattern_match(LHS,AllIds,PatMatchIds,TRestIDs),
2430 TRestIDs \= [],
2431 %same_id(TID1,TID,ID),
2432 ? \+ definitely_infinite(Set), % prevent !(x,y).(x:NATURAL & x<10 & y :1..x => x+y<20)
2433 %\+ known_set(Set), % rewriting makes sense if Set is not fully known and will be instantiated during solving
2434 % used to prevent known sets, but rewriting also useful for known sets (QueensWithEvents_ForallTest2b)
2435 get_sorted_ids(TRestIDs,RestIDs),
2436 not_occurs_in_predicate(RestIDs,Set),
2437 NewPred = forall(PatMatchIds,MEM,InnerForall),
2438 conjunct_predicates_with_pos_info(RestPreds,InnerForallLhs),
2439 construct_inner_forall(TRestIDs,InnerForallLhs,Rhs,I,InnerForall),
2440 !,
2441 delete(I,used_ids(_),I1), % should in principle still be ok at outer level; but just be sure
2442 add_removed_typing_info(I1,INew),
2443 (debug_mode(on) -> get_sorted_ids(PatMatchIds,PatIds),
2444 format('FORALL SPLITTING ~w (from ~w) for better propagation: ',[PatIds,RestIDs]),
2445 print_bexpr(b(NewPred,pred,INew)),nl
2446 ; true).
2447 cleanup_post(exists([TID],MemPred),pred,IOld,
2448 Res,pred,IOld, single/replace_exists_by_not_empty) :-
2449 % simplify #ID.(ID:E) <=> E /= {}
2450 % simplify #ID.(ID:E1 & ID:E2) <=> E1 /\ E2 /= {} , etc...
2451 % important e.g. for y:20..30000000000 & not(#x.(x:1..10 & x:8..y))
2452 ? is_valid_id_member_check(MemPred,TID,E),
2453 !,
2454 (definitely_not_empty_set(E) -> Res= truth
2455 ; get_texpr_type(E,Type), EmptySet=b(empty_set,Type,[]),
2456 Res = not_equal(E,EmptySet)),
2457 (debug_mode(off) -> true
2458 ; get_texpr_id(TID,ID),
2459 format('Removing existential quantifier: ~w~n',[ID]),
2460 print_bexpr(b(Res,pred,IOld)),nl).
2461 cleanup_post(exists([TID],b(NotMemPred,_,_)),pred,IOld,
2462 not_equal(E,TypeExpr),pred,IOld, single/replace_exists_by_not_full) :-
2463 % simplify #ID.(ID/:E) <=> E /= FullType
2464 % important e.g. for y:7..30000000000 & not(#x.(x /: 1..y))
2465 is_not_member(NotMemPred,MID,E),
2466 same_id(TID,MID,SID),
2467 % + check that MID does not occur in E
2468 \+ occurs_in_expr(SID,E),
2469 get_texpr_type(E,SType),
2470 is_set_type(SType,Type),
2471 create_maximal_type_set(Type,TypeExpr), % Note: no longer introduces identifiers but value(.) results
2472 !,
2473 (debug_mode(off) -> true
2474 ; format('Removing existential quantifier: ~w~n',[SID]),
2475 print_bexpr(b(not_equal(E,TypeExpr),pred,IOld)),nl).
2476 cleanup_post(exists([TID],b(Pred,_,_)),pred,IOld,
2477 truth,pred,IOld, single/replace_exists_by_truth) :-
2478 b_interpreter_check:arithmetic_op(Pred,_Op,X,Y),
2479 ( (same_id(TID,X,SID), \+ occurs_in_expr(SID,Y), always_well_defined_or_disprover_mode(Y)) ;
2480 (same_id(TID,Y,SID), \+ occurs_in_expr(SID,X), always_well_defined_or_disprover_mode(X))
2481 ),
2482 !, % we have a formula of the form #SID.(SID > Expr); provided Expr is well-defined, this is always true
2483 (debug_mode(off) -> true
2484 ; format('Removing existential quantifier: ~w~n',[SID]),
2485 print_bexpr(b(Pred,pred,[])),nl).
2486 cleanup_post(exists([TID1,TID2|OTHER],RHS),pred,IOld,
2487 exists([TID1,TID2|OTHER],NewRHS),pred,[prob_symmetry(ID1,ID2)|IOld],single/symmetry_detection) :-
2488 % DETECT Symmetries such as #(x,y).(x /= y & (x=TRUE or y=TRUE))
2489 % #(x2,y).(x2 /= y & x2:s & y:s & x2=aa or y=aa)
2490 get_texpr_type(TID1,T), get_texpr_type(TID2,T),
2491 \+ preferences:get_preference(use_solver_on_load,kodkod),
2492 preferences:get_preference(use_static_symmetry_detection,true),
2493 sym_break_supported_type(T), % LESS not yet fully functional with SET types; TO DO: fix
2494 get_texpr_id(TID1,ID1), get_texpr_id(TID2,ID2),
2495 nonmember(prob_symmetry(ID1,ID2),IOld),
2496 ? \+(contains_equality(TID1,TID2,RHS)), % IDs are already equal; no use in sym breaking
2497 ? rename_bt(RHS,[rename(ID1,ID2),rename(ID2,ID1)],RHS2),
2498 same_norm_texpr(RHS,RHS2),
2499 construct_sym_break(T,TID1,TID2,RHS,SYMBREAK),
2500 conjunct_predicates_with_pos_info(RHS,SYMBREAK,NewRHS),
2501 (debug_mode(off) -> true
2502 ; format('SYMMETRY BREAKING EXISTS: #(~w,~w).(',[ID1,ID2]),print_bexpr(NewRHS),print(')'),nl).
2503 cleanup_post(Expr,T,I1,NewExpr,T,I1,single/detect_lambda_result_quant_auto) :-
2504 construct_for_find_do_not_enumerate(Expr,KIND,TIds,Body,NewExpr,NewBody),
2505 perform_do_not_enumerate_analysis(TIds,Body,KIND,I1,NewBody).
2506 % sort args of commutative operators by term size
2507 cleanup_post(Expr, Type, I, NExpr, Type, NI, single/normalize_commutative_args) :-
2508 preferences:get_preference(normalize_ast_sort_commutative, true),
2509 sort_commutative_args(Expr, I, NExpr, NI).
2510 %,(NExpr=Expr -> true ; print('COMMUTE: '), translate:print_bexpr(b(Expr,Type,I)),nl, print(' TO: '), translate:print_bexpr(b(NExpr,Type,NI)),nl).
2511 %% COMMENT IN NEXT LINE TO CHECK validity of AST per NODE (helps find bugs)
2512 %%cleanup_post(Expr,pred,I,Expr,pred,I,single/checked) :- check_ast(true,b(Expr,pred,I)),fail.
2513 %%
2514 cleanup_post(Expr, pred, I, Expr, pred, [DI|I], single/detect_prob_ignore) :-
2515 ? get_info_labels(I,Labels), member(Label,Labels),
2516 ? is_prob_ignore_label(Label),
2517 !,
2518 DI=description('prob-ignore'), % detected by info_has_ignore_pragma/1
2519 nonmember(DI,I),
2520 add_message(detect_prob_ignore,'Detected prob-ignore label: ',Label,I).
2521
2522 is_prob_ignore_label(Label) :-
2523 atom_codes(Label,Cs),
2524 IGNORE = [112,114,111,98,DASH,105,103,110,111,114,101|_],
2525 % used to be: append("prob-ignore",_,IGNORE), but Rodin editor sometimes puts Dash 8722 rather than 45 in label
2526 ? suffix(Cs,IGNORE), % accept prob-ignore somewhere in the label
2527 ? member(DASH,[45, 8722, 95, 46, 32, 126, 61, 43, 35]). % "--_. ~=+#"
2528 % used to call reverse and match "erongi-borp"
2529
2530 cleanup_post_function(Override,X,_Type,I0,Res,Info,multi/function_override) :-
2531 preferences:get_preference(disprover_mode,true), % only applied in Disprover mode as it can remove WD problem; TO DO make it also applicable in normal mode
2532 get_texpr_expr(Override,overwrite(_F,SEXt)),
2533 SEXt = b(set_extension(LIST),_,_),
2534 member(b(couple(From,To),_,_),LIST),
2535 same_texpr(From,X),
2536 % ( F <+ { ... X|->To ...}) (X) ==> To
2537 %print_bexpr(b(function(Override,X),Type,_I)), print(' ==> '), print_bexpr(To),nl,
2538 !,
2539 get_texpr_expr(To,Res),
2540 get_texpr_info(To,I1),
2541 add_important_info_from_super_expression(I0,I1,Info).
2542 cleanup_post_function(Override,X,Type,Info,Res,Info,multi/function_override_ifte) :-
2543 preferences:get_preference(disprover_mode,true), % only applied in Disprover mode as it can remove WD
2544 % TO DO: should we do this generally? or simply deal with overwrite symbolically always?
2545 get_texpr_expr(Override,overwrite(F,SEXt)),
2546 SEXt = b(set_extension([Couple]),_,_),
2547 Couple = b(couple(From,To),_,_),
2548 % (f <+ {A|->B}) (x) -> if_then_else(x=A,B,f(x)) ; avoids having to explicitly compute f<+{A|->B}
2549 Res = if_then_else(EqXFrom,To,FX),
2550 safe_create_texpr(equal(X,From),pred,EqXFrom),
2551 safe_create_function_call(F,X,Type,Info,FX).
2552 cleanup_post_function(SEXt,ARG,_Type,I0,Res,Info,multi/function_set_extension) :-
2553 SEXt = b(set_extension(LIST),_,ListInfos), % TO DO: also support b(value(avl_set(A)),_,_)
2554 eval_set_extension_element(ARG,Value,not_available),
2555 ? select(b(couple(LHS,RHS),_,_),LIST,REST),
2556 ? (member(contains_wd_condition,ListInfos) % then we could remove WD problem, e.g., r = {1|->2, 2|-> 1/0}(1)
2557 -> (preferences:preference(find_abort_values,false) ;
2558 preferences:get_preference(disprover_mode,true))
2559 ; true),
2560 eval_set_extension_element(LHS,Value,not_available), %nl,print(found(RHS)),nl,
2561 % WE NEED TO Check that all LHS can be compared against ARG
2562 \+ member((b(couple(LHS2,_),_,_),REST),eval_set_extension_element(LHS2,Value,not_available)), % no other potential match
2563 \+ member((b(couple(LHS3,_),_,_),LIST), \+ eval_set_extension_element(LHS3,_,not_available)), % all left-hand-sides can be evaluated
2564 !, get_texpr_expr(RHS,Res), get_texpr_info(RHS,I1),
2565 add_important_info_from_super_expression(I0,I1,Info).
2566 % Detect if_then_else in format as printed by pp_expr2(if_then_else( ....)...) or as generated by B2TLA:
2567 cleanup_post_function(IFT,DUMMYARG,_Type,Info,if_then_else(IFPRED,THEN,ELSE),Info,multi/function_if_then_else) :-
2568 ? is_if_then_else(IFT,post,DUMMYARG,IFPRED,THEN,ELSE),
2569 (debug_mode(off) -> true
2570 ; print('% Recognised if-then-else expression: IF '), print_bexpr(IFPRED),
2571 print(' THEN '),print_bexpr(THEN), print(' ELSE '),print_bexpr(ELSE),nl
2572 ).
2573 cleanup_post_function(Composition,X,Type,Info,NewExpr,Info,multi/function_composition) :-
2574 (data_validation_mode ;
2575 get_preference(convert_comprehension_sets_into_closures,true)
2576 % there it can make a big difference in particular since relational composition (rel_composition_wf -> rel_compose_with_inf_fun case) was not fully symbolic; see Systerel data validation examples
2577 ),
2578 % (F;G)(X) --> G(F(X)) (F;G;H)(X) --> H(G(F(X))) ...
2579 peel_rel_composition(Composition,Type,Info,X,Result,Level),
2580 Level>0,
2581 Result = b(NewExpr,_,_),
2582 %check_ast(Result), % <---
2583 (debug_mode(off) -> true
2584 ; format('Function application of COMPOSITION (Nesting: ~w) translated to: ',[Level]),print_bexpr(Result),nl).
2585 cleanup_post_function(Fun,Arg,_Type,Info,function(Fun,Arg),NewInfo,single/function_inversion_annotation) :-
2586 data_validation_mode, % TODO: activate in general
2587 limited_propagation(Arg),
2588 NewInfo = [prob_annotation('INVERSION_PENALTY')|Info],
2589 (debug_mode(off) -> true
2590 ; add_message(ast_cleanup,'Function application not suited for propagation from result to argument: ',Arg,Info)).
2591
2592 % statically detect whether there is potential for propagating result values onto these expressions
2593 limited_propagation(b(Expr,_,_)) :- limited_prop_aux(Expr).
2594 limited_prop_aux(function(_,_)). % we need to propagate through at least one more function call
2595 limited_prop_aux(composition(_,_)). % argument is a function, composed of two other functions
2596 limited_prop_aux(iteration(_,_)).
2597 limited_prop_aux(record_field(Rec,_)) :- limited_propagation(Rec). % we only know part of the record; TODO: add a penalty even if Rec allows propagation
2598 %limited_prop_aux(external_function_call(_,_)). % MU probably ok, for other funs it depends
2599 limited_prop_aux(couple(A,B)) :-
2600 (limited_propagation(A)
2601 -> % back propagation on A not useful,
2602 (limited_propagation(B) -> true % back propagation on both arguments is not useful
2603 ; is_constant(B) % B is a constant and could only filter (if TRY_FIND_ABORT / find_abort_values false)
2604 )
2605 ; is_constant(A), limited_propagation(B) % what if both are a constant ?
2606 ).
2607 limited_prop_aux(minus(A,B)) :- (limited_propagation(A) -> true ; limited_propagation(B)).
2608 limited_prop_aux(add(A,B)) :- (limited_propagation(A) -> true ; limited_propagation(B)).
2609 limited_prop_aux(div(A,B)) :- (limited_propagation(A) -> true ; limited_propagation(B)).
2610 limited_prop_aux(multiplication(A,B)) :- (limited_propagation(A) -> true ; limited_propagation(B)).
2611 limited_prop_aux(let_expression(_,_,C)) :- limited_propagation(C).
2612 % TODO: detect more cases where propagating from result of function application to argument is of limited value
2613 % sequence operators: insert_tail, first, last, ..., sequence_extension (cf test 2387)
2614
2615 is_constant(b(C,_,_)) :- is_const_aux(C).
2616 is_const_aux(boolean_false).
2617 is_const_aux(boolean_true).
2618 is_const_aux(couple(A,B)) :- is_constant(A),is_constant(B).
2619 is_const_aux(empty_set).
2620 is_const_aux(empty_sequence).
2621 is_const_aux(integer(_)).
2622 is_const_aux(real(_)).
2623 is_const_aux(string(_)).
2624 is_const_aux(value(V)) :- nonvar(V), is_const_value(V).
2625 % not covered yet: value(_) and record(_)
2626 is_const_value(pred_true).
2627 is_const_value(pred_false).
2628 is_const_value(string(S)) :- ground(S).
2629 is_const_value(int(S)) :- integer(S).
2630 is_const_value(fd(V,T)) :- ground(V), ground(T).
2631 is_const_value(term(floating(F))) :- number(F).
2632 is_const_value((A,B)) :- nonvar(A), nonvar(B), is_const_value(A),is_const_value(B).
2633
2634
2635 :- use_module(closures,[is_recursive_closure/3]).
2636 % detect comprehension set or closure values that can be inlined in member/not_member checks
2637 is_comprehension_set(comprehension_set(TypedIds,Body),TypedIds,Body).
2638 is_comprehension_set(value(Closure),TypedIds,Body) :- nonvar(Closure),
2639 Closure = closure(P,T,Body),
2640 ? \+ is_recursive_closure(P,T,Body), % otherwise inlining may expose unbound rec. ID, see test 554
2641 \+ custom_explicit_sets:is_interval_closure_or_integerset(Closure,_,_), % this is already a value
2642 % TO DO: also detect simple member closures like seq(0..1)
2643 create_typed_ids(P,T,TypedIds).
2644
2645 cleanup_comprehension_set([TID],b(member(LHS,TSet),pred,_),Type,I,Set,I2,multi/remove_useless_comprehension_set) :-
2646 get_texpr_id(TID,ID),
2647 get_texpr_id(LHS,ID),
2648 TSet=b(Set,Type,I2),
2649 (member(prob_annotation('SYMBOLIC'),I)
2650 -> % maybe this set comprehension was created with the purpose of adding the symbolic annotation
2651 % e.g., Set = closure(SET) stemming from /*@symbolic*/ {x|x:closure1(SET)}
2652 fail % TODO: see if we can propagate the symbolic annotation to TSet
2653 ; true),
2654 % {ID|ID:Set} ==> Set
2655 not_occurs_in_expr(ID,TSet),
2656 !,
2657 add_hint_message(remove_useless_comprehension_set,'Removing useless comprehension set over: ',ID,I).
2658 cleanup_comprehension_set([TID],Body,_Type,I,NewExpr,NewInfo,single/detect_seq_comprehension_set) :-
2659 get_texpr_id(TID,ID),
2660 % {ID | #LenID. (ID : 1..LenID --> Set)} ==> seq(Set)
2661 % {ID | #LenID. (ID : 1..LenID >-> Set)} ==> iseq(Set)
2662 get_texpr_expr(Body,exists([TLen],TIBody)),
2663 get_texpr_id(TLen,LenID), LenID \= ID,
2664 get_texpr_expr(TIBody,IBody),
2665 ? get_member(IBody,LenID,ISet,TID2,FUNCTION),
2666 get_texpr_id(TID2,ID),
2667 ? get_seq_fun_aux(FUNCTION,ISet,Interval,SeqTypeSet),
2668 get_texpr_expr(Interval,interval(ONE,TLen2)),
2669 ? get_texpr_id_with_offset(TLen2,LenID,Offset), % LenID or something like LenID-1
2670 get_integer(ONE,StartingIndex),!,
2671 (StartingIndex = 1, Offset=0 % TODO: check if a negative offset is always ok for all Seq Types
2672 -> add_hint_message(detect_seq_comprehension_set,'Detecting sequence operator: ',ID,I),
2673 NewExpr = SeqTypeSet, NewInfo=I
2674 ; % we have something sequence like but with indexes not starting at 1, maybe at 0
2675 % e.g. {ID | #LenID. (ID : 0..LenID-1 --> Set)}; happens in Soton/UML-B drone model
2676 add_hint_message(detect_seq_comprehension_set,'Marking sequence like operator as symbolic, indexes are not starting at 1: ',ID,I),
2677 NewExpr = comprehension_set([TID],Body),
2678 %add_texpr_infos(Body,[prob_annotation('SYMBOLIC')],Body2),
2679 add_info_if_new(I,prob_annotation('SYMBOLIC'),NewInfo)
2680 ).
2681 % {RANGE_LAMBDA__|#x.(x : dom(F) & RANGE_LAMBDA__ = F(x))} --> ran(F) // generated by TLC4B -> TLA2B
2682 % TO DO: detect {R|R:INTEGER & #D.(D|->R:F)} as ran(F)
2683 cleanup_comprehension_set([TID],Body, _Type, I, range(Func), I, multi/detect_tla_range_comprehension_set) :-
2684 Body = b(exists([DomTID],EBody),pred,_),
2685 EBody = b(conjunct(LHS,RHS),pred,_),
2686 is_membership(LHS,DomTID1,b(domain(Func),_,_)),
2687 same_id(DomTID,DomTID1,_),
2688 is_equality(RHS,TID1,FunCall),
2689 FunCall = b(function(Func1,DomTID2),_,_),
2690 same_id(TID,TID1,_),
2691 same_id(DomTID,DomTID2,_),
2692 same_texpr(Func,Func1),
2693 always_well_defined_or_disprover_mode(FunCall), % we could also allow TLA minor mode
2694 add_hint_message(detect_tla_range_comprehension_set,'Detected range set-comprehension: ',Func,I).
2695 cleanup_comprehension_set([TID],Pred,Type,I,
2696 struct(b(rec(NewFieldSets),record(FieldTypes),I)),
2697 I,single/simplify_record) :-
2698 % {r|r'a : 1..1000 & r'b : 1..100 & r:struct(a:INTEGER,b:NAT,c:BOOL)} --> struct(a:1..1000,b:1..100,c:BOOL)
2699 % these kind of set comprehensions are generated by ProZ, see ROZ example model.tex test 1858
2700 % TO DO: maybe generalise this optimisation: currently it only works if all predicates can be assimilated into struct expression
2701 TID = b(identifier(ID),record(FieldTypes),_),
2702 conjunction_to_list(Pred,PL),
2703 l_update_record_field_membership(PL,ID,[],FieldSetsOut),
2704 maplist(construct_field_sets(FieldSetsOut),FieldTypes,NewFieldSets),
2705 (debug_mode(off) -> true
2706 ; print('Detected Record set comprehension: '),
2707 print_bexpr(b(struct(b(rec(NewFieldSets),record(FieldTypes),I)),Type,I)),nl).
2708 cleanup_comprehension_set(Ids1,E,_Type,I,comprehension_set(Ids2,E2),I,single/detect_lambda) :-
2709 preferences:get_preference(detect_lambdas,true),
2710 % used to lead to *** Enumerating lambda result warnings for test 1162, not anymore
2711 % does not yet detect: f = {x,y|x:NATURAL & (x> 1 &y=x+2)} & res = f[3..4]
2712 E = b(conjunct(LHS,Equality),pred,Info),
2713 nonmember(prob_annotation('LAMBDA'),Info), % not already processed
2714 ? identifier_equality(Equality,ID,TID1,Expr1),
2715 last(Ids1,TID), get_texpr_id(TID,ID),
2716 not_occurs_in_expr(ID,Expr1),
2717 not_occurs_in_predicate([ID],LHS),
2718 !,
2719 get_texpr_info(Equality,EqInfo),
2720 get_unique_id_inside('_lambda_result_',LHS,Expr1,ResultId), % currently the info field lambda_result is not enough: several parts of the ProB kernel match on the identifier name '_lambda_result_'
2721 TID1 = b(identifier(_),Type1,Info1),
2722 add_texpr_infos(b(identifier(ResultId),Type1,Info1),[lambda_result(ResultId),lambda_result_id_was(ID)],TID2),
2723 Equality2 = b(equal(TID2,Expr1),pred,[prob_annotation('LAMBDA-EQUALITY')|EqInfo]),
2724 E2 = b(conjunct(LHS,Equality2),pred,[prob_annotation('LAMBDA')|Info]),
2725 append(Ids0,[_],Ids1),
2726 append(Ids0,[TID2],Ids2),
2727 % code exists which is simpler, but has disadvantage of losing position info for equality
2728 (debug_mode(off) -> true ; format('Lambda using ~w detected: ',[ID]),print_bexpr(E2),nl).
2729
2730
2731 % extract membership for ID and detect optional restrictions for Length identfier LenID
2732 get_member(conjunct(TA,TB),LenID,ISet,TID2,FUNCTION) :-
2733 get_texpr_expr(TA,A), % detect LenId : NATURAL(1)
2734 ? get_mem_of_integerset(A,LenID,ISet), % TO DO: detect LenID>0, or LenID /=0
2735 get_texpr_expr(TB,B),
2736 get_member1(B,TID2,FUNCTION).
2737 get_member(IBody,_,'NATURAL',TID2,F) :- get_member1(IBody,TID2,F).
2738 get_member1(member(TID2,b(FUNCTION,_,_)),TID2,FUNCTION).
2739
2740 get_mem_of_integerset(member(TID2,b(SET,_,_)),LenID,ISet) :- !,
2741 get_texpr_id(TID2,LenID),
2742 is_integer_set(SET,ISet).
2743 get_mem_of_integerset(Pred,LenID,ISet) :-
2744 ? is_integer_set_constraint_pred(Pred,LenID,ISet).
2745
2746
2747 get_texpr_id_with_offset(Expr,ID,0) :- get_texpr_id(Expr,ID).
2748 get_texpr_id_with_offset(b(add(TID,Expr),integer,_),ID,Offset) :-
2749 get_texpr_id(TID,ID), get_integer(Expr,Offset).
2750 get_texpr_id_with_offset(b(minus(TID,Expr),integer,_),ID,NegOffset) :-
2751 get_texpr_id(TID,ID), get_integer(Expr,Offset), NegOffset is -Offset.
2752
2753 get_seq_fun_aux(total_function(Interval,TargetSet),'NATURAL',Interval,seq(TargetSet)).
2754 get_seq_fun_aux(total_function(Interval,TargetSet),'NATURAL1',Interval,seq1(TargetSet)).
2755 get_seq_fun_aux(total_injection(Interval,TargetSet),'NATURAL',Interval,iseq(TargetSet)).
2756 get_seq_fun_aux(total_injection(Interval,TargetSet),'NATURAL1',Interval,iseq1(TargetSet)).
2757 get_seq_fun_aux(total_bijection(Interval,TargetSet),'NATURAL',Interval,perm(TargetSet)).
2758 get_seq_fun_aux(total_bijection(Interval,TargetSet),'NATURAL1',Interval,perm(TargetSet)) :-
2759 definitely_not_empty_set(TargetSet).
2760
2761 % Detect TLA real division defined by Div_1(a, b) == CHOOSE({m|m:REAL & m*b=a})
2762 is_tla_real_division(external_function_call('CHOOSE',[SETCOMPR]),TA,TB) :-
2763 get_texpr_expr(SETCOMPR,comprehension_set([TID1],BODY)),
2764 get_texpr_id(TID1,ID),
2765 is_equality( BODY, MUL, TA),
2766 get_texpr_expr(MUL,multiplication_real(TID2,TB)),
2767 get_texpr_id(TID2,ID).
2768
2769 % --------------------------------
2770
2771 % check if Expression can be used in b_interpreter for optimised forall treatment in !(AllIds).(Expr:SET => RHS)
2772 % see can_be_used_for_unification in b_interpreter
2773 is_forall_membership_pattern_match(TID,AllIds,[TID],RestIds) :-
2774 get_texpr_id(TID,ID),!,
2775 ? select(TID2,AllIds,RestIds), def_get_texpr_id(TID2,ID).
2776 is_forall_membership_pattern_match(b(Expr,_,_),AllIds,PatMatchIds,RestIds) :-
2777 ? is_forall_membership_pattern_match2(Expr,AllIds,PatMatchIds,RestIds).
2778 is_forall_membership_pattern_match2(integer(_),AllIds,[],AllIds).
2779 is_forall_membership_pattern_match2(string(_),AllIds,[],AllIds).
2780 is_forall_membership_pattern_match2(real(_),AllIds,[],AllIds).
2781 is_forall_membership_pattern_match2(boolean_true,AllIds,[],AllIds).
2782 is_forall_membership_pattern_match2(boolean_false,AllIds,[],AllIds).
2783 is_forall_membership_pattern_match2(value(V),AllIds,[],AllIds) :- nonvar(V), is_const_value(V).
2784 is_forall_membership_pattern_match2(couple(TA,TB),AllIds,PatMatchIds,RestIds) :-
2785 ? is_forall_membership_pattern_match(TA,AllIds,Pat1,Rest1),
2786 ? is_forall_membership_pattern_match(TB,Rest1,Pat2,RestIds),
2787 append(Pat1,Pat2,PatMatchIds).
2788 % TODO: enumerate_set elements, freevals (but then they must be supported in can_be_used_for_unification)
2789
2790 % --------------------------------
2791
2792 construct_for_find_do_not_enumerate(exists(TIds,Pred),'EXISTS',TIds,Pred,exists(TIds,Pred2),Pred2).
2793 construct_for_find_do_not_enumerate(any(TIds,Pred,Body),'ANY',TIds,Pred,any(TIds,Pred2,Body),Pred2) :-
2794 data_validation_mode. % as we do not examine Body of the Any, we do not know if there are additional constraints on TIds in the body
2795 % tests where ANYs would be annotated 471, 565, 808, 1196, 1489, 1850
2796
2797 % try and perform analysis for a body of either exists, any or set_comprehension
2798 perform_do_not_enumerate_analysis(TIds,Body,KIND,Span,NewBody) :-
2799 get_preference(perform_enumeration_order_analysis,true),
2800 get_texpr_info(Body,BI),
2801 nonmember(prob_annotation('DO_NOT_ENUMERATE'(_)),BI), % analysis was already performed or manually annotated
2802 find_do_not_enumerate_variables(TIds,Body,SortedVs,DelayVsInOrder),
2803 !,
2804 findall(prob_annotation('DELAY_ENUMERATION'(PosNr,DNID)),nth1(PosNr,DelayVsInOrder,DNID),I1),
2805 (SortedVs = []
2806 -> NewInfos = [prob_annotation('DO_NOT_ENUMERATE'('$$NONE$$'))|I1] % dummy marking to avoid running analysis again
2807 ; findall(prob_annotation('DO_NOT_ENUMERATE'(DNID)),member(DNID,SortedVs),NewInfos,I1)
2808 ),
2809 (debug_mode(off) -> true
2810 ; I1=[], SortedVs=[] -> true
2811 ; ajoin(['Annotating ',KIND,' identifiers with DO_NOT_ENUMERATE: '],Msg),
2812 %write(SortedVs),nl,
2813 add_message(detect_lambda_result_auto,Msg,SortedVs:DelayVsInOrder,Span)
2814 ),
2815 add_texpr_infos(Body,NewInfos,NewBody).
2816 perform_do_not_enumerate_analysis(_,Body,_,_,Body).
2817
2818 :- public check_do_not_enum_result/2.
2819 % check if there is a difference with stored result in info field if it exists
2820 check_do_not_enum_result(NewInfos,BInfo) :- member(prob_annotation('DO_NOT_ENUMERATE'(_)),BInfo),!,
2821 findall(DNID,
2822 (member(prob_annotation('DO_NOT_ENUMERATE'(DNID)),BInfo), DNID \= '$$NONE$$'), OldIds),
2823 findall(DNID,
2824 (member(prob_annotation('DO_NOT_ENUMERATE'(DNID)),NewInfos), DNID \= '$$NONE$$'), NewIds),
2825 (OldIds = NewIds
2826 -> format('Same DO_NOT_ENUMERATE result: ~w~n',[OldIds])
2827 ; format('Difference in DO_NOT_ENUMERATE result:~nOLD: ~w~nNEW: ~w~n',[OldIds,NewIds])
2828 ).
2829 check_do_not_enum_result(_,_).
2830
2831 % --------------------
2832
2833 % we only sort at the top-level, as cleanup_post will work its way bottom-up:
2834 sort_commutative_args(Expr, I, Sorted, NI) :- nonvar(Expr),
2835 functor(Expr, Functor, 2),
2836 is_commutative(Functor),
2837 !,
2838 arg(1, Expr, Lhs),
2839 arg(2, Expr, Rhs),
2840 remove_all_infos_and_ground(Lhs,CNLhs), % remove infos for comparison
2841 remove_all_infos_and_ground(Rhs,CNRhs),
2842 get_texpr_expr(CNLhs,N1),
2843 get_texpr_expr(CNRhs,N2),
2844 ( N1 @> N2
2845 -> Sorted =.. [Functor,Rhs,Lhs],
2846 NI = [was(Expr)|I]
2847 ; Sorted =.. [Functor,Lhs,Rhs],
2848 NI = I
2849 ).
2850
2851
2852 is_commutative(conjunct).
2853 is_commutative(disjunct).
2854 is_commutative(equivalence).
2855 is_commutative(equal).
2856 is_commutative(not_equal).
2857 is_commutative(add).
2858 is_commutative(multiplication).
2859 is_commutative(union).
2860 is_commutative(intersection).
2861
2862 % --------------------
2863
2864 factor_disjunct(CEquality1,CEquality2,IOld,New,INew) :-
2865 % (x=2 & y=3) or (x=2 & y=4) -> x=2 & (y=3 or y=4) to improve constraint propagation
2866 Blacklist=[],
2867 conjunction_to_list(CEquality1,Preds1),
2868 conjunction_to_list(CEquality2,Preds2),
2869 ? select_equality(TId1,Preds1,Blacklist,TEqual,Expr1,RestPreds1,_,check_well_definedness), % also allow other preds, use safe_select(check_well_definedness,TEqual,Preds,Rest),
2870 get_texpr_id(TId1,Id),
2871 get_texpr_id(TId2,Id),
2872 ? select_equality(TId2,Preds2,Blacklist,_,Expr2,RestPreds2,_,check_well_definedness),
2873 same_texpr(Expr1,Expr2),
2874 conjunct_predicates_with_pos_info(RestPreds1,P1),
2875 conjunct_predicates_with_pos_info(RestPreds2,P2),
2876 % TO DO: do not recursively start from scratch in P1, one should start from the right of CEquality1:
2877 (fail, % disable recursive looking
2878 factor_disjunct(P1,P2,IOld,P12,INew) -> NewDisj = b(P12,pred,INew)
2879 ; disjunct_predicates_with_pos_info(P1,P2,NewDisj)),
2880 conjunct_predicates_with_pos_info(TEqual,NewDisj,NewPred),
2881 NewPred=b(New,pred,I2),
2882 include_important_info_from_removed_pred(IOld,I2,INew).
2883
2884 % ------------------------------------------
2885
2886 gen_rename(TID1,TID2,rename(ID1,ID2)) :- def_get_texpr_id(TID1,ID1), def_get_texpr_id(TID2,ID2).
2887
2888 is_not_member(not_member(LHS,RHS),LHS,RHS).
2889 is_not_member(negation(b(member(LHS,RHS),pred,_)),LHS,RHS).
2890
2891
2892 :- use_module(typing_tools,[create_maximal_type_set/2]).
2893 is_valid_id_member_check(b(member(MID,E),_,_),ID,E) :- same_id(ID,MID,SID),
2894 % + check that MID does not occur in E
2895 \+ occurs_in_expr(SID,E).
2896 is_valid_id_member_check(b(truth,_,_),ID,TypeExpr) :-
2897 get_texpr_type(ID,SType),
2898 create_maximal_type_set(SType,TypeExpr). % Note: this no longer introduces identifiers, which could clash
2899 is_valid_id_member_check(b(conjunct(A,B),_,_),ID,Res) :-
2900 ? is_valid_id_member_check(A,ID,EA),
2901 ? is_valid_id_member_check(B,ID,EB),
2902 get_texpr_type(EA,Type),
2903 safe_create_texpr(intersection(EA,EB),Type,Res).
2904
2905 contains_equality(TID1,TID2,RHS) :-
2906 ? b_interpreter:member_conjunct(b(equal(A,B),pred,_),RHS,_),
2907 (same_id(A,TID1,_),same_id(B,TID2,_) ; same_id(A,TID2,_),same_id(B,TID1,_)).
2908
2909 simplify_let_subst(Ids,Pred,Subst,NIds,RestPred,NewSubst) :-
2910 % remove let identifiers whose definitions are very simple, i.e. identifiers
2911 Eq = b(equal(TypID,TExpr),pred,_),
2912 can_be_optimized_away(TypID),
2913 get_texpr_id(TypID,ToReplace),
2914 b_interpreter:member_conjunct(Eq,Pred,RestPred),
2915 is_simple_expression(TExpr),
2916 nth0(_N,Ids,TI,NIds),get_texpr_id(TI,ToReplace),
2917 !,
2918 % Intitially there was an issue as we may also replace in the LHS of assignments
2919 % see e.g. TestLet = LET cnt BE cnt=1 IN IF cnt=0 THEN ABORT ELSE cnt :: {0,1} END END; in SubstitutionLaws
2920 % However, now the static type checker rejects those assignments
2921 replace_id_by_expr(Subst,ToReplace,TExpr,NSubst),
2922 % TO DO: it seems like cleanup rules are not applied on NSubst, e.g., function for set_extension rules
2923 debug_println(9,replaced_let_subst_id(ToReplace)),
2924 (Subst==NSubst -> NewSubst=NSubst ; clean_up(NSubst,[],NewSubst)).
2925
2926 can_be_optimized_away(b(_,_,I)) :- nonmember(do_not_optimize_away,I).
2927
2928 %replace_in_rhs(ID,E,RHS,CleanNewRHS) :- replace_id_by_expr(RHS,ID,E,NewRHS), clean_up(NewRHS,[],CleanNewRHS).
2929
2930 can_be_replaced(RHS,_,Ids) :- get_texpr_id(RHS,RHSID),!,
2931 ? \+ (member(TID2,Ids), get_texpr_id(TID2,RHSID)). % ID occurs in Ids, replacing it in Expr will move the scope
2932 % example: Z Test (\LET x==1 @ (\LET x==x+1; y==x @ 7*x+y)) = 15
2933 can_be_replaced(_RHS,UsedIds,Ids) :- % TO DO: compute used ids
2934 %find_identifier_uses(RHS,[],UsedIds),
2935 get_texpr_ids(Ids,AtomicIds), sort(AtomicIds,SortedIds),
2936 \+ ord_intersect(UsedIds,SortedIds).
2937
2938 % simplify LET Ids BE Ids=Exprs IN Expr END by moving one identifier Id inside
2939 simplify_let(Ids,Exprs,Expr,NIds,NExprs,CleanNewExpr) :-
2940 ? nth0(N,Ids,TId,NIds),
2941 get_texpr_id(TId,Id),
2942 can_be_optimized_away(TId),
2943 nth0(N,Exprs,LetExpr,NExprs),
2944 find_identifier_uses_if_necessary(LetExpr,[],LetExprIds),
2945 \+ ord_member(Id,LetExprIds), %\+ occurs_in_expr(Id,LetExpr), % illegal let, e.g., i = i+1;
2946 can_be_replaced(LetExpr,LetExprIds,Ids), % moving LetExpr will not produce scoping issues
2947 maplist(not_occurs_in_expr(Id),NExprs), % The ID is not used for defining other RHS in the same let
2948 ? simplify_let_aux(TId,Id,LetExpr,Expr,CleanNewExpr).
2949
2950 simplify_let_aux(_TId,Id,LetExpr,Expr,CleanNewExpr) :-
2951 % remove let identifiers whose definitions are very simple, i.e. identifiers
2952 is_simple_expression(LetExpr),
2953 % TId = LetExpr
2954 % TO DO: do not do this to outer variables which the user cares about !!
2955 !,
2956 %maplist(replace_in_rhs(Id,LetExpr),NExprs,NewExprs),
2957 ? replace_id_by_expr(Expr,Id,LetExpr,NExpr),
2958 NonGroundExceptions = do_not_ground_types, % see test 2493; TODO: should we pass NonGroundExceptions as parameter?
2959 ? clean_up(NExpr,NonGroundExceptions,CleanNewExpr). % clean up adjust eg used_ids info; necessary for test 568 in prob_safe_mode
2960 simplify_let_aux(TId,Id,LetExpr,Expr,CleanNewExpr) :-
2961 % push the let expression down the AST. E.g. "LET a=E IN (4*(a+z*a) + z)" would
2962 % be transformed to "4*(LET a=E IN (a+z*a)) + z"
2963 % If the final form is like "LET a=E IN a" it will be simplified to E.
2964 ? \+ do_not_to_move_let_inside(Expr),
2965 !,
2966 ( identifier_sub_ast(Expr,Id,SubPosition) ->
2967 ? prune_sub_ast_pos_list(SubPosition,Id,LetExpr,Expr,SafeSubPosition),
2968 SafeSubPosition = [_|_], % The LET can actually be moved down
2969 % SubPosition points to the highest point in the AST coveringa all occurences
2970 ? exchange_ast_position(SafeSubPosition,Expr,OldInner,NewInner,NExpr),
2971 get_texpr_type(OldInner,Type),
2972 ( get_texpr_id(OldInner,Id) -> % There is only one reference to Id,
2973 debug_format(19,'Simplified LET for ~w away, single usage~n',[Id]),
2974 NewInner = LetExpr % replace it with the expression
2975 % We need to check that we are not simply just exchanging lets with each other
2976 ; cycle_detection(Id,SafeSubPosition,Expr) -> debug_println(9,cycle(Id)),fail
2977 ; Type=pred -> % print(created_let_predicate(N,Id,SafeSubPosition,NIds)),nl,
2978 extract_important_info_from_subexpressions(LetExpr,OldInner,NewLetInfo), % maybe no longer necessary because of cleanups call below
2979 create_texpr(let_predicate([TId],[LetExpr],OldInner),pred,NewLetInfo,NewInner)
2980 ; % print(create_let_expression(TId)),nl,
2981 extract_important_info_from_subexpressions(LetExpr,OldInner,NewLetInfo), % maybe no longer necessary because of cleanups call below
2982 create_texpr(let_expression([TId],[LetExpr],OldInner),Type,NewLetInfo,NewInner)),
2983 NonGroundExceptions = do_not_ground_types, % see test 2493
2984 ? clean_up(NExpr,NonGroundExceptions,CleanNewExpr) % maybe we only need WD post rules ?
2985 ; always_well_defined_or_wd_improvements_allowed(LetExpr) ->
2986 % Id does not occur in the expression -> just remove the LET
2987 add_debug_message(b_ast_cleanup,'Identifier of LET not used: ',Id,Expr),
2988 CleanNewExpr = Expr
2989 ; gen_unused_let_id_msg(TId,Id,LetExpr),fail
2990 ),!.
2991 simplify_let_aux(TId,Id,LetExpr,Expr,CleanNewExpr) :- % do_not_to_move_let_inside has succeeded
2992 not_occurs_in_expr(Id,Expr),
2993 (always_well_defined_or_wd_improvements_allowed(LetExpr)
2994 -> add_debug_message(b_ast_cleanup,'Identifier of LET not used: ',Id,Expr)
2995 ; gen_unused_let_id_msg(TId,Id,LetExpr), fail
2996 ),
2997 CleanNewExpr=Expr.
2998
2999 ?gen_unused_let_id_msg(TID,Id,LetExpr) :- get_texpr_info(TID,Infos), member(generated_exists_parameter,Infos),!,
3000 add_debug_message(b_ast_cleanup,'Cannot remove unused identifier in (auto-generated) LET due to WD condition: ',Id,LetExpr).
3001 gen_unused_let_id_msg(_TID,Id,LetExpr) :-
3002 add_message(b_ast_cleanup,'Cannot remove unused identifier in LET due to WD condition: ',Id,LetExpr).
3003
3004
3005 % this has to be checked not just at the top-level but along the SubPosition path
3006 do_not_to_move_let_inside(b(E,_T,Infos)) :-
3007 (do_not_to_move_let_inside_aux(E) -> true
3008 ? ; E=exists(_,_), (get_preference(lift_existential_quantifiers,true) ; member(allow_to_lift_exists,Infos))
3009 ).
3010 %add_message(simplify_let,'Not moving LET inside: ',b(E,_T,Infos),Infos).
3011 % exists can be lifted which can also lead to duplication allow_to_lift_exists
3012 % for those quantifiers we may duplicate the computation of a let by moving it inside:
3013 do_not_to_move_let_inside_aux(forall(_,_,_)). % otherwise we may compute the let multiple times
3014 do_not_to_move_let_inside_aux(comprehension_set(_,_)). % ditto
3015 do_not_to_move_let_inside_aux(general_product(_,_,_)). % ditto (PI)
3016 do_not_to_move_let_inside_aux(general_sum(_,_,_)). % ditto (SIGMA)
3017 do_not_to_move_let_inside_aux(lambda(_,_,_)). % ditto
3018 do_not_to_move_let_inside_aux(quantified_intersection(_,_,_)). % ditto
3019 do_not_to_move_let_inside_aux(quantified_union(_,_,_)). % ditto
3020 %do_not_to_move_let_inside_aux(exists(_,_)). % can lead to duplication upon lifting or semi-lifting, e.g., if two exists are nested?
3021 % TODO: investigate if we should disable moving LET into exists in general
3022 do_not_to_move_let_inside_aux(convert_bool(_)). % can lead to duplication if reification fails
3023
3024
3025 not_occurs_in_expr(Id,Expr) :- \+ occurs_in_expr(Id,Expr).
3026
3027 cycle_detection(Id,SubPosition,Expr) :-
3028 ? (get_constructor(SubPosition,Expr,CC),
3029 \+ let_constructor(CC) -> fail % at least one other constructor found
3030 ; debug_println(9,cycle_let_detection(Id))
3031 ).
3032 % we have a let constructor which can be modified by simplify_let:
3033 let_constructor(let_expression).
3034 let_constructor(let_predicate).
3035 let_constructor(let_substitution).
3036
3037 % traverse a SubPositions List from identifier_sub_ast and check for potential duplication
3038 % by quantifiers, if found: prune list at that point
3039 prune_sub_ast_pos_list([],_,_,_,[]).
3040 prune_sub_ast_pos_list([Pos|T],Id,LetExpr,OldTExpr,Res) :-
3041 remove_bt(OldTExpr,OldExpr,NewExpr,_NewTExpr),
3042 (do_not_to_move_let_inside(OldTExpr)
3043 -> Res=[],
3044 (debug_mode(off) -> true ; add_message(simplify_let,'Not moving LET inside quantifier/bool: ',Id,OldTExpr))
3045 ; Res = [Pos|TR],
3046 ? syntaxtransformation(OldExpr,Subs,_Names,_NSubs,NewExpr),
3047 nth0(Pos,Subs, OldSelected,_Rest),
3048 ? prune_sub_ast_pos_list(T,Id,LetExpr,OldSelected,TR),
3049 (TR=[], avoid_top_level_let_within(OldExpr)
3050 -> Res=[] % we would create a let at the top-level of this
3051 ; Res = [Pos|TR]
3052 )
3053 ).
3054
3055 avoid_top_level_let_within(card(_)). % reification of card does not work yet with top-level let_predicate, for test 1562
3056 % Note: maybe it is best to avoid pushing into card completely, as even at the next
3057 % level the let could disturb the reification small set detection?
3058
3059 % get a SubPosition path (as produced by identifier_sub_ast) and
3060 % generate upon backtracking all constructors that are used along the Path
3061 get_constructor([Pos|T],OldTExpr,ConstructorForPos) :-
3062 remove_bt(OldTExpr,OldExpr,NewExpr,_NewTExpr),
3063 (functor(OldExpr,ConstructorForPos,_)
3064 ; syntaxtransformation(OldExpr,Subs,_Names,_NSubs,NewExpr),
3065 nth0(Pos,Subs, OldSelected,_Rest),
3066 ? get_constructor(T,OldSelected,ConstructorForPos)
3067 ).
3068
3069 is_simple_expression(TExpr) :-
3070 get_texpr_expr(TExpr,Expr),
3071 is_simple_expression2(Expr),!.
3072 is_simple_expression(TExpr) :-
3073 is_just_type(TExpr).
3074 is_simple_expression2(identifier(_)).
3075 is_simple_expression2(integer(_)).
3076 is_simple_expression2(real(_)).
3077 is_simple_expression2(string(_)).
3078 is_simple_expression2(boolean_true).
3079 is_simple_expression2(boolean_false).
3080 is_simple_expression2(empty_set).
3081 is_simple_expression2(empty_sequence).
3082 %is_simple_expression2(interval(Low,Up)) :- is_simple_expression(Low), is_simple_expression(Up).
3083 % TODO: simple couples? simple records?
3084
3085 % a variation of is_simple_expression, allowing some simple constructs
3086 is_simple_expression_lvl(TExpr,Lvl) :-
3087 get_texpr_expr(TExpr,Expr),
3088 is_simple_expression2_lvl(Expr,Lvl),!.
3089 is_simple_expression2_lvl(Cons,Lvl) :- simple_binary_constructor(Cons,A,B), !,
3090 Lvl>0, L1 is Lvl-1,
3091 is_simple_expression_lvl(A,L1),is_simple_expression_lvl(B,L1).
3092 is_simple_expression2_lvl(Cons,Lvl) :- simple_unary_constructor(Cons,A),!,
3093 Lvl>0, L1 is Lvl-1,
3094 is_simple_expression_lvl(A,L1).
3095 is_simple_expression2_lvl(E,_) :- is_simple_expression2(E).
3096
3097 simple_binary_constructor(function(A,B),A,B).
3098 simple_binary_constructor(couple(A,B),A,B).
3099 % TODO: simple records?
3100 simple_unary_constructor(reverse(A),A).
3101 simple_unary_constructor(set_extension([A]),A).
3102 simple_unary_constructor(sequence_extension([A]),A).
3103
3104 % check for duplication of complex LHS expressions by replacing ID with LHS NrOccurences of times for Rule
3105 is_replace_id_by_expr_ok(_LHS,_ID,NrOccurences,_Rule) :- NrOccurences < 2.
3106 is_replace_id_by_expr_ok(_LHS,_ID,_,_Rule) :-
3107 get_preference(normalize_ast,true),!. % is necessary at least for remove_member_comprehension, remove_not_member_comprehension
3108 is_replace_id_by_expr_ok(_LHS,_ID,_,_Rule) :-
3109 get_preference(use_common_subexpression_elimination,true),!.
3110 is_replace_id_by_expr_ok(LHS,_ID,NrOccurences,_Rule) :-
3111 (NrOccurences<3 -> Lvl=2 ; NrOccurences<6 -> Lvl=1 ; Lvl=0), % what heuristic should we use here; test 1750 seems to indicate that Lvl=4 would still be beneficial for NrOccurences=2 and lambda_guard1 rule
3112 is_simple_expression_lvl(LHS,Lvl).
3113 is_replace_id_by_expr_ok(LHS,ID,Count,Rule) :-
3114 debug_mode(on),
3115 format('replace ~w (~w times) not ok for ~w using: ',[ID,Count,Rule]), translate:print_bexpr(LHS),nl,fail.
3116
3117
3118 % detect either Event-B identity or id over full type
3119 is_event_b_identity(b(X,_,_)) :- is_event_b_identity_aux(X).
3120 is_event_b_identity_aux(event_b_identity).
3121 is_event_b_identity_aux(identity(T)) :- is_just_type(T).
3122
3123 :- use_module(library(avl),[avl_member/2]).
3124 % check if we have a set extension and return list of terms
3125 is_set_extension(b(S,T,I),L) :- is_set_extension_aux(S,T,I,L).
3126 is_set_extension_aux(set_extension(L),_,_,L).
3127 % TO DO: detect sequence_extension
3128 is_set_extension_aux(value(avl_set(A)),SetType,I,L) :- % computed by eval_set_extension
3129 is_set_type(SetType,Type),
3130 findall(b(value(M),Type,I),avl_member(M,A),L).
3131
3132 is_sequence_extension(b(S,T,I),L) :- is_sequence_extension_aux(S,T,I,L).
3133 is_sequence_extension_aux(sequence_extension(L),_,_,L).
3134 % TO DO: detect value/set_extensions
3135
3136 recursion_detection_enabled(A,B,I) :-
3137 ? (recursion_detection_enabled_aux(A,B,I) -> true).
3138 recursion_detection_enabled_aux(A,_B,I) :-
3139 animation_mode(b), % in B mode,
3140 memberchk(section(properties),I), % the rule should be only applied to properties
3141 % and where A is an abstract constant.
3142 get_texpr_info(A,AInfo),memberchk(loc(_,_,abstract_constants),AInfo).
3143 recursion_detection_enabled_aux(A,_B,_I) :-
3144 animation_minor_mode(eventb), % in Event-B,
3145 %TODO: Limit application to axioms
3146 get_texpr_info(A,AInfo), % A must be a constant
3147 memberchk(loc(_,constants),AInfo).
3148 recursion_detection_enabled_aux(_A,_B,_I) :-
3149 animation_minor_mode(z). % use always in Z
3150 recursion_detection_enabled_aux(_A,_B,Infos) :- % check for @desc recursive_let pragma
3151 member(description(D),Infos), rec_let_pragma(D).
3152
3153 rec_let_pragma(recursive_let).
3154 rec_let_pragma(letrec). % more compact exists in other languages
3155 rec_let_pragma(reclet). % Z syntax
3156
3157 % peel of relational compositions and replace with function application
3158 % used to translate (F;G)(X) --> G(F(X)) or (F;G;H)(X) --> H(G(F(X))) ...
3159 peel_rel_composition(b(composition(F,G),_,_),TypeGArg,Info,Arg,GFres,L1) :-
3160 get_texpr_type(G,SType),
3161 bsyntaxtree:is_set_type(SType,couple(TypeFArg,_)),
3162 !,
3163 %Note: rule is multi: we will detect compositions inside G at next iteration
3164 peel_rel_composition(F,TypeFArg,Info,Arg,FRes,Level), L1 is Level+1,
3165 safe_create_function_call(G,FRes,TypeGArg,Info,GFres).
3166 peel_rel_composition(Fun,TypeFArg,Info,Arg,FArg,0) :-
3167 safe_create_function_call(Fun,Arg,TypeFArg,Info,FArg). % TODO: apply function_call_opt
3168
3169 % create a function call and detect certain optimisations like lambda inlining
3170 safe_create_function_call(Fun,Arg,TypeFArg,Info,Res) :-
3171 safe_create_texpr(function(Fun,Arg),TypeFArg,Info,FArg),
3172 (cleanup_pre_function(Fun,Arg,TypeFArg,Info,CleanupRes,Info2,_)
3173 -> Res = b(CleanupRes,TypeFArg,Info2)
3174 ; Res=FArg
3175 ).
3176
3177
3178 construct_union_from_list([X],_,_,Res) :- !, Res=X.
3179 construct_union_from_list([X,Y|T],Type,Info,Res) :-
3180 construct_union_from_list([Y|T],Type,Info,RHS),
3181 Res = b(union(X,RHS),Type,Info).
3182 construct_inter_from_list([X],_,_,Res) :- !, Res=X.
3183 construct_inter_from_list([X,Y|T],Type,Info,Res) :-
3184 construct_inter_from_list([Y|T],Type,Info,RHS),
3185 Res = b(intersection(X,RHS),Type,Info).
3186
3187 % LEQ_SYM_BREAK / LEQ_SYM does not support all types yet:
3188 sym_break_supported_type(Var) :- var(Var),!,fail.
3189 sym_break_supported_type(integer).
3190 sym_break_supported_type(boolean).
3191 sym_break_supported_type(real).
3192 sym_break_supported_type(string).
3193 sym_break_supported_type(global(_)).
3194 sym_break_supported_type(couple(A,B)) :- sym_break_supported_type(A), sym_break_supported_type(B).
3195 sym_break_supported_type(record(F)) :- maplist(sym_break_supported_field,F).
3196 sym_break_supported_field(field(_,T)) :- sym_break_supported_type(T).
3197 % example with pairs: !(x,y).(x:s2 & y:s2 & x/=y => prj1(INTEGER,INTEGER)(x)/=prj1(INTEGER,INTEGER)(y)) (with let s2 = {x,y|x:1..10000 & y:{x+1}}); here we get a slow-down; maybe we should check if RHS complicated enough
3198 % here it is beneficial: !(x,y).(x:dom(s)&y:dom(s)&x/=y => s(x)+s(y)>0) with let s={x,y,v|x:1..10&y:1..50&v=x+y}; runtime goes down from 9.7 to 6.1 seconds
3199
3200 ?construct_sym_break(integer,TID1,TID2,Pred,Res) :- member_in_conjunction(Neq,Pred), is_id_inequality(Neq,TID1,TID2),
3201 !, get_texpr_info(TID1,Info1),
3202 Res = b(less(TID1,TID2),pred,Info1). % we don't need the external function; we can used <
3203 construct_sym_break(integer,TID1,TID2,_Pred,Res) :- !, get_texpr_info(TID1,Info1),
3204 Res = b(less_equal(TID1,TID2),pred,Info1). % we don't need the external function; we can used <= ; we could check whether < or <= already in Pred ? occurs in test 1360: #(vv,ww).(vv < ww & ww < vv)
3205 construct_sym_break(_,TID1,TID2,_,Res) :- get_texpr_info(TID1,Info1),
3206 Res = b(external_pred_call('LEQ_SYM',[TID1,TID2]),pred,Info1).
3207
3208 % construct {Expr1,Expr2}
3209 construct_set_extension(Expr1,Expr2,Res) :- same_texpr(Expr1,Expr2),!,
3210 get_texpr_type(Expr1,Type),
3211 extract_info(Expr1,Infos), % will also copy used_ids; ok as this does not change by adding set_extension
3212 Res = b(set_extension([Expr1]),set(Type),Infos).
3213 construct_set_extension(Expr1,Expr2,Res) :-
3214 get_texpr_type(Expr1,Type),
3215 extract_info(Expr1,Expr2,Infos),
3216 (Expr1 @=< Expr2 -> Lst=[Expr1,Expr2] ; Lst=[Expr2,Expr1]), % solves issue with ParserTests; {FALSE,TRUE}
3217 Res = b(set_extension(Lst),set(Type),Infos).
3218
3219 l_construct_set_extension([E1],[E2],Res) :- !, construct_set_extension(E1,E2,Res).
3220 l_construct_set_extension(L1,L2,Res) :- append(L1,L2,L12),
3221 L12=[Expr1|T],!,
3222 get_texpr_type(Expr1,Type),
3223 last(T,Expr2),
3224 extract_info(Expr1,Expr2,Infos), % TODO: improve info extraction; sort L12 values?
3225 Res = b(set_extension(L12),set(Type),Infos).
3226 l_construct_set_extension(A,B,Res) :-
3227 add_internal_error('Requires at least two els:',l_construct_set_extension(A,B,Res)),fail.
3228
3229 is_id_inequality(b(not_equal(A,B),pred,_),X,Y) :-
3230 (same_texpr(A,X) -> same_texpr(B,Y) ; same_texpr(A,Y), same_texpr(B,X)).
3231
3232
3233 %known_set(b(integer_set(_),set(integer),_)). % used for forall splitting; TODO: use is_integer_set ??
3234 %known_set(b(interval(_,_),set(integer),_)).
3235
3236 % detect if we have an if-then-else function (which is then applied to a dummy argument)
3237 is_if_then_else(b(comprehension_set([TDummyID1,ID2],CONJ),_Type,_),_,_DUMMYARG,IFPRED,THEN,ELSE) :-
3238 % we ignore the _DUMMYARG as here we do not check the value of DUMMYARG in the body
3239 % TO DO: also allow removal of equalities as in TLA case below
3240 % DETECT {Dummy,Res| Test => Res=THEN & not(Test) => Res=ELSE}
3241 get_texpr_id(ID2,LambdaID), get_texpr_id(TDummyID1,DummyID),
3242 ? is_ifte_case_conjunct(CONJ,IFPRED,EQ1,EQ2),
3243 ? is_equality_conj(EQ1,II1,THEN), get_texpr_id(II1,LambdaID),
3244 ? is_equality_conj(EQ2,II2,ELSE), get_texpr_id(II2,LambdaID),
3245 \+ occurs_in_expr(DummyID,IFPRED),\+ occurs_in_expr(LambdaID,IFPRED),
3246 \+ occurs_in_expr(DummyID,THEN), \+ occurs_in_expr(LambdaID,THEN),
3247 \+ occurs_in_expr(DummyID,ELSE), \+ occurs_in_expr(LambdaID,ELSE).
3248
3249 % Recognize B2TLA encodings as well: %((x).(x=0 & PRED|C1)\/%(x).(x=0 & not(PRED)|C2)) (0)
3250 %is_if_then_else(IF,_,_,_,_) :- nl,print(IF),nl,nl,fail.
3251 is_if_then_else(b(union(COMP1,COMP2),_Type,_),_,DUMMYARG,IFPRED,THEN,ELSE) :-
3252 ? if_then_else_lambda(COMP1,DUMMYARG,IFPRED,THEN),
3253 ? if_then_else_lambda(COMP2,DUMMYARG,NOT_IFPRED,ELSE),
3254 is_negation_of(IFPRED,NOT_IFPRED).
3255
3256 is_if_then_else(b(set_extension([CASE1,CASE2]),_,Info),POST,Arg,IFPRED,THEN,ELSE) :-
3257 (POST=post -> true ; data_validation_mode), % in cleanup_pre the wd info is not yet computed
3258 Arg = b(convert_bool(IFPRED),boolean,_),
3259 % {TRUE|->v1,FALSE|->v2}(bool(TEST)) --> IF TEST THEN v1 ELSE v2 END
3260 % example: {TRUE|->1,FALSE|->2}(bool(2>3)) --> IF 2>3 THEN 1 ELSE 2 END
3261 CASE1 = b(couple(b(B1,boolean,_),Val1),_,_),
3262 CASE2 = b(couple(b(B2,boolean,_),Val2),_,_),
3263 ( B1=boolean_true,B2=boolean_false -> THEN=Val1,ELSE=Val2
3264 ; B2=boolean_true,B1=boolean_false -> THEN=Val2,ELSE=Val1),
3265 (always_well_defined_or_disprover_mode(THEN),
3266 always_well_defined_or_disprover_mode(ELSE) -> true
3267 %,add_message(function_if_then_else,'Detected {TRUE|->v1,FALSE|->v2}(bool(TEST)) construct without WD condition, rewriting it to IF TEST THEN v1 ELSE v2 END','',Info)
3268 % otherwise: the transformation to IF-THEN-ELSE may remove WD problem
3269 ; silent_mode(on) -> true
3270 ; %data_validation_mode,
3271 add_message(function_if_then_else,'Detected {TRUE|->v1,FALSE|->v2}(bool(TEST)) construct with WD condition, you should probably rewrite it to IF TEST THEN v1 ELSE v2 END','',Info),
3272 true % fail
3273 ).
3274
3275 if_then_else_lambda(b(comprehension_set([TDummyID,TLAMBDAID],CONJ),_,_),DUMMYARG,IFPRED,RESULT) :-
3276 conjunction_to_nontyping_list(CONJ,CL),
3277 get_texpr_id(TDummyID,DummyID),
3278 get_texpr_id(TLAMBDAID,LambdaID),
3279 ? (remove_equality(DummyID,DUMMYVAL,CL,ConjList) % look if there is an equality for the DummyID
3280 -> same_texpr(DUMMYVAL,DUMMYARG), % TO DO: check that we apply the function with this value
3281 \+ occurs_in_expr(LambdaID,DUMMYVAL), % ensure this is really the same value
3282 \+ occurs_in_expr(DummyID,DUMMYVAL)
3283 ; ConjList=CL),
3284 ? remove_equality(LambdaID,RESULT,ConjList,RestList),
3285 \+ occurs_in_expr(LambdaID,RESULT),
3286 \+ occurs_in_expr(DummyID,RESULT), % otherwise this is not really a dummy identifier
3287 conjunct_predicates_with_pos_info(RestList,IFPRED),
3288 \+ occurs_in_expr(DummyID,IFPRED).
3289
3290 % DETECT (IFPRED => EQ1) & (not(IFPRED) => EQ2)
3291 is_ifte_case_conjunct(CONJ,IFPRED,EQ1,EQ2) :-
3292 is_a_conjunct(CONJ,IMP1,IMP2),
3293 is_an_implication_conj(IMP1,IFPRED,EQ1),
3294 is_an_implication_conj(IMP2,NOT_IFPRED,EQ2),
3295 ? is_negation_of(IFPRED,NOT_IFPRED).
3296 % TO DO: also deal with lazy_lets wrapped around
3297 %is_ifte_case_conjunct(lazy_let_pred(ID,IFPRED,CONJ),IFPRED,EQ1,EQ2) :-
3298 % is_a_conjunct(CONJ,IMP1,IMP2),
3299 % is_an_implication(IMP1,IFPRED,EQ1),
3300 % is_an_implication(IMP2,NOT_IFPRED,EQ2),
3301 % is_negation_of(IFPRED,NOT_IFPRED).
3302
3303 % detect explicit if-then-else for cleanup_post:
3304 explicit_if_then_else(if_then_else(IF,THEN,ELSE),IF,THEN,ELSE).
3305 explicit_if_then_else(if([b(if_elsif(IF,THEN),subst,_)|TAIL]),IF,THEN,ELSE) :-
3306 (TAIL = [b(if_elsif(b(truth,pred,_),EE),subst,_)|_] -> ELSE = EE
3307 ; TAIL = [] -> ELSE = b(skip,subst,[generated])
3308 ).
3309
3310 % just like is_an_implication but allow typing conjuncts (not yet removed in pre-phase)
3311 is_an_implication_conj(Pred,LHS,RHS) :- is_an_implication(Pred,LHS,RHS),!.
3312 is_an_implication_conj(b(conjunct(A,B),pred,_),LHS,RHS) :-
3313 (is_typing_predicate(A) -> is_an_implication_conj(B,LHS,RHS)
3314 ; is_typing_predicate(B) -> is_an_implication_conj(A,LHS,RHS)).
3315
3316 % just like is_equality but allow typing conjuncts (not yet removed in pre-phase)
3317 is_equality_conj(EQ,LHS,RHS) :- is_equality(EQ,LHS,RHS).
3318 is_equality_conj(b(conjunct(A,B),pred,_),LHS,RHS) :-
3319 (is_typing_predicate(A) -> is_equality_conj(B,LHS,RHS)
3320 ; is_typing_predicate(B) -> is_equality_conj(A,LHS,RHS)).
3321
3322 % remove a dummy equality from list
3323 remove_equality(ID,RHS,ConjList,Rest) :-
3324 DummyEQ = b(equal(DID,RHS),pred,_), % TO DO: also accept simple typing memberships ?
3325 get_texpr_id(DID,ID),
3326 ? select(DummyEQ,ConjList,Rest). %, print(eq(DID,RHS)),nl.
3327
3328 is_typing_conjunct(b(member(_,B),_,_)) :- is_just_type(B).
3329 is_typing_predicate(Typing) :- conjunction_to_list(Typing,LT), maplist(is_typing_conjunct,LT).
3330 conjunction_to_nontyping_list(Pred,List) :- conjunction_to_list(Pred,TList), exclude(is_typing_conjunct,TList,List).
3331
3332 % used e.g. for translating : ran({x1,...xn|P}) --> {xn| #(x1,...).(P)}
3333 % we annotate this exists as allow_to_lift; as the origin is a set comprehension which originally had all variables at the top-level (including the existentially quantified ones)
3334 create_outer_exists_for_dom_range(Ids,CompPred,NewCompPred) :-
3335 create_outer_exists_for_dom_range2(Ids,CompPred,NewCompPred1),
3336 compute_used_ids_info_if_necessary(NewCompPred1,NewCompPred).
3337 create_outer_exists_for_dom_range2(Ids,b(exists(InnerIds,P),pred,Infos),New) :-
3338 ? member(allow_to_lift_exists,Infos),
3339 append(Ids,InnerIds,NewIds),!, % simply add Ids to existing existential quantifier
3340 New = b(exists(NewIds,P),pred,NewInfos),
3341 remove_from_used_ids(Infos,Ids,NewInfos).
3342 create_outer_exists_for_dom_range2(Ids,P,New) :-
3343 % we could also use construct_optimized_exists/3 it does a full partitioning of P; see also components_partition_exists rule above
3344 create_exists_opt_liftable(Ids,P,New). % marked as liftable as origin is a set comprehension with all ids
3345 % calls create_exists_opt: detects also simple tautologies like #x.(x=E)
3346 % + predicates that do not use one of the quantified identifiers are moved outside
3347 %N=b(P2,T2,[allow_to_lift_exists|I2]). %, check_ast(N).
3348
3349 % remove newly quantified Typed IDs from used_ids info; if the info exists
3350 remove_from_used_ids(OldInfo,NewQuantifiedTIds,NewInfo) :-
3351 ? select(used_ids(OldUsed),OldInfo,I1),!,
3352 get_texpr_ids(NewQuantifiedTIds,NewQ),
3353 NewInfo = [used_ids(NewUsed)|I1],
3354 ord_subtract(OldUsed,NewQ,NewUsed).
3355 remove_from_used_ids(I,_,I).
3356
3357 % if _lambda_result_ occurs in list; rename it so that we do not get issues with enumeration
3358 rename_lambda_result_id(Ids,CompPred,NewIds,NewCompPred) :-
3359 ? select(ID,Ids,Rest),
3360 get_texpr_id(ID,'_lambda_result_'),
3361 !,
3362 get_unique_id_inside('__RANGE_LAMBDA__',CompPred,FRESHID), % if we don't rename then _lambda_result_ will not be enumerated ! TO DO: also check different from Ids if we want to remove __ prefix
3363 % TO DO: remove lambda_result(Info)
3364 ? rename_bt(CompPred,[rename('_lambda_result_',FRESHID)],NewCompPred),
3365 get_texpr_type(ID,IDType), get_texpr_info(ID,IDInfo),
3366 NewIds = [b(identifier(FRESHID),IDType,IDInfo)|Rest].
3367 rename_lambda_result_id(Ids,CompPred,Ids,CompPred).
3368
3369 contains_predicate(convert_bool(Pred),boolean,Pred,
3370 convert_bool(NewP),NewP).
3371 contains_predicate(comprehension_set(CompIds,Pred),_,Pred,
3372 comprehension_set(CompIds,NewP),NewP).
3373 contains_predicate(general_sum(Ids,Pred,Expression),integer,Pred,
3374 general_sum(Ids,NewP,Expression),NewP).
3375 contains_predicate(general_product(Ids,Pred,Expression),integer,Pred,
3376 general_product(Ids,NewP,Expression),NewP).
3377 contains_predicate(if_then_else(Pred,Then,Else),_,Pred,
3378 if_then_else(NewP,Then,Else),NewP).
3379 contains_predicate(assertion_expression(Pred,ErrMsg,Expr),_,Pred,
3380 assertion_expression(NewP,ErrMsg,Expr),NewP).
3381 contains_predicate(precondition(Pred,Body),subst,Pred,
3382 precondition(NewP,Body),NewP).
3383 contains_predicate(assertion(Pred,Body),subst,Pred,
3384 assertion(NewP,Body),NewP).
3385 contains_predicate(witness_then(Pred,Body),subst,Pred,
3386 witness_then(NewP,Body),NewP).
3387 contains_predicate(becomes_such(Vars,Pred),subst,Pred,
3388 becomes_such(Vars,NewP),NewP).
3389 contains_predicate(any(Parameters,Pred,Body),subst,Pred,
3390 any(Parameters,NewP,Body),NewP).
3391 contains_predicate(lazy_let_expr(ID,SharedExpr,MainExpr),pred, SharedExpr,
3392 lazy_let_expr(ID,NewSharedExpr,MainExpr), NewSharedExpr) :-
3393 get_texpr_type(SharedExpr,pred).
3394 contains_predicate(lazy_let_subst(ID,SharedExpr,MainExpr),pred, SharedExpr,
3395 lazy_let_subst(ID,NewSharedExpr,MainExpr), NewSharedExpr) :-
3396 get_texpr_type(SharedExpr,pred).
3397 contains_predicate(lazy_let_pred(ID,SharedExpr,MainExpr),pred, MainExpr,
3398 lazy_let_pred(ID,SharedExpr,NewMainExpr), NewMainExpr) :-
3399 \+ get_texpr_type(SharedExpr,pred).
3400 % while(COND,STMT,INV,VARIANT), select, if --> can have multiple predicates !!
3401 contains_predicates(while(Cond, Stmt,Invariant,Variant),subst, [Cond,Invariant],
3402 while(NewCond,Stmt,NewInv, Variant), [NewCond,NewInv]).
3403 contains_predicates(if(Whens),subst,Preds,
3404 if(NewWhens),NewPreds) :-
3405 get_predicates_from_list_of_cases(Whens,Preds,NewWhens,NewPreds).
3406 contains_predicates(select(Whens),subst,Preds,
3407 select(NewWhens),NewPreds) :-
3408 get_predicates_from_list_of_cases(Whens,Preds,NewWhens,NewPreds).
3409 contains_predicates(select(Whens,Else),subst,Preds,
3410 select(NewWhens,Else),NewPreds) :-
3411 get_predicates_from_list_of_cases(Whens,Preds,NewWhens,NewPreds).
3412 contains_predicates(lazy_let_pred(ID,SharedExpr,MainExpr),pred, [SharedExpr,MainExpr],
3413 lazy_let_pred(ID,NSharedExpr,NMainExpr), [NSharedExpr,NMainExpr]) :-
3414 get_texpr_type(SharedExpr,pred).
3415
3416 get_predicates_from_list_of_cases([],[],[],[]).
3417 get_predicates_from_list_of_cases([H|T],Preds,[NewH|NewT],NewPreds) :-
3418 (get_single_predicate(H,Pred,NH,NewPred)
3419 -> NewH=NH, Preds=[Pred|TP], NewPreds = [NewPred|NTP]
3420 ; NewH=H, Preds=TP, NewPreds = NTP
3421 ),
3422 get_predicates_from_list_of_cases(T,TP,NewT,NTP).
3423
3424 get_single_predicate(b(E,T,I),Preds,b(NewE,T,I),NewPreds) :-
3425 get_single_predicate_aux(E,Preds,NewE,NewPreds).
3426 get_single_predicate_aux(select_when(Pred,Body),Pred,select_when(NewPred,Body),NewPred).
3427 get_single_predicate_aux(if_elsif(Pred,Body),Pred,if_elsif(NewPred,Body),NewPred).
3428
3429
3430 % Detect useless statements in sequential compositions:
3431 % useful for LCHIP code, e.g., where dummy code is added for the code generator: i9 : (i9 : BOOL); i9 := TRUE
3432 % in test 1660 we remove an assignment that reads an unitialised variable
3433 filter_useless_subst_in_sequence([],_,R) :- !, R=[].
3434 filter_useless_subst_in_sequence([S1],_,R) :- !, R=[S1].
3435 filter_useless_subst_in_sequence([S1|S2],change,R) :- useless_subst_in_sequence(S1,S2),!,
3436 add_hint_message(filter_useless_subst_in_sequence,'Removing useless substitution in sequence','',S1),
3437 filter_useless_subst_in_sequence(S2,_,R).
3438 filter_useless_subst_in_sequence([S1|S2],Change,[S1|RS]) :- filter_useless_subst_in_sequence(S2,Change,RS).
3439
3440 useless_subst_in_sequence(b(Subst,subst,Info),Sequence2) :- % print(check(Subst,Sequence2)),nl,
3441 useless_code_before_sequence(Subst,Info,Sequence2).
3442
3443 useless_code_before_sequence(skip,_,_) :- !.
3444 useless_code_before_sequence(Subst,_,SubstList) :- is_non_failing_assignment(Subst,TID), def_get_texpr_id(TID,ID),
3445 is_dead(ID,SubstList).
3446
3447 % first naive version to compute if the variable ID is dead when followed by a list of substitutions
3448 is_dead(ID,[b(Subst,subst,Info)|_]) :- % we currently only look at first statement; TO DO: improve
3449 is_dead_aux(Subst,Info,ID).
3450 is_dead_aux(assign_single_id(TID,RHS),_Info,ID) :-
3451 get_texpr_id(TID,ID), % we assign to ID; TO DO: deal with other assignments and assignments to functions f(i) := ...
3452 find_identifier_uses_if_necessary(RHS,[],UsedIds),
3453 \+ ord_member(ID,UsedIds).
3454
3455 % non failing assignment without WD condition, note that we may still try and read identifiers that have not been initialised (having term(undefined) as value), see test 1660
3456 is_non_failing_assignment(becomes_such([TID],Pred),TID) :- is_truth(Pred).
3457 is_non_failing_assignment(becomes_element_of([TID],Set),TID) :- definitely_not_empty_set(Set).
3458 is_non_failing_assignment(assign_single_id(TID,RHS),TID) :- always_well_defined_or_disprover_mode(RHS).
3459 is_non_failing_assignment(assign([LHS],[RHS]),TID) :- always_well_defined_or_disprover_mode(RHS),
3460 get_lhs_assigned_identifier(LHS,TID).
3461
3462
3463 % ---------------------------------------------
3464
3465 :- use_module(extrasrc(b_expression_sharing),[cse_optimize_predicate/2]).
3466 % these are "global" optimizations at the predicate level
3467 % they are only called once a predicate has been completely constructed
3468 predicate_level_optimizations(Pred,NewPred) :-
3469 predicate_level_optimizations(Pred,NewPred,[]).
3470 predicate_level_optimizations(Pred,NewPred,Path) :-
3471 inner_predicate_level_optimizations(Pred,Pred1),
3472 (get_preference(use_common_subexpression_elimination,true),
3473 \+ do_not_optimise_in_context(Path)
3474 -> cse_optimize_predicate(Pred1,NewPred)
3475 ; NewPred=Pred1
3476 ). %,print_opt_debug_info(Pred,NewPred,Path).
3477 /*
3478 print_opt_debug_info(Pred,NewPred,Path) :-
3479 (Pred==NewPred -> true
3480 ; same_texpr(Pred,NewPred) -> true
3481 ; format('Optimized pred ~w: ',[Path]), print_bexpr(NewPred),nl
3482 % , (Path=[] -> trace ; true)
3483 ).
3484 */
3485
3486 do_not_optimise_in_context([path_arg(top_level(invariant),Nr)]) :-
3487 get_preference(use_po,true),
3488 debug_format(19,'% NOT applying CSE to Invariant Nr ~w (PROOF_INFO = TRUE)~n',[Nr]).
3489
3490 :- use_module(partition_detection,[detect_all_partitions_in_predicate/2]).
3491 % this predicate is also called for exists, forall, ...:
3492 inner_predicate_level_optimizations(Pred,NewPred) :-
3493 detect_all_partitions_in_predicate(Pred,NewPred1),
3494 (get_preference(remove_implied_constraints,true)
3495 -> remove_implied_constraints(NewPred1,NewPred)
3496 ; NewPred=NewPred1)
3497 . %,(Pred==NewPred -> true ; print('Optimized pred: '), print_bexpr(NewPred),nl).
3498
3499
3500
3501 % ----------------------------------
3502
3503 remove_implied_constraints(Predicate,NewPredicate) :-
3504 conjunction_to_list(Predicate,PList),
3505 remove_implied_constraints(PList,[],PNew),
3506 conjunct_predicates_with_pos_info(PNew,NewPredicate).
3507
3508 % remove constraints which are redundant for ProB
3509 % example:
3510 % n=1000 & f:1..n --> BOOL & f:1..n +-> BOOL & !x.(x:dom(f) => f(x) = bool(x>50)) & f: 1..n <-> BOOL & dom(f)=1..n
3511 % runtime goes from 500 ms down to 300 ms by remove +->, <-> and dom(f) checks
3512 % but test 1442 has issue: still unclear how useful this static detection is
3513 % it is probably most useful for proving/disproving where we have lots of redundant/derived hypotheses
3514
3515 remove_implied_constraints([],_,[]).
3516 remove_implied_constraints([Constraint|T],SoFar,Result) :-
3517 % print('Checking: '), print_bexpr(Constraint),nl,
3518 possible_implied_constraint(Constraint,C1),
3519 % print('Checking if implied constraint: '), print_bexpr(Constraint),nl,
3520 ? (member(TC2,T) ; member(TC2,SoFar)),
3521 get_texpr_expr(TC2,C2),
3522 ? implied_constraint2(C2,C1),
3523 (debug_mode(off) -> true
3524 ; print('Removing implied constraint: '), print_bexpr(Constraint),
3525 print(' <=== '), print_bexpr(TC2),nl),
3526 !,
3527 remove_implied_constraints(T,SoFar,Result).
3528 remove_implied_constraints([H|T],SoFar,[H|RT]) :- remove_implied_constraints(T,[H|SoFar],RT).
3529
3530 possible_implied_constraint(b(E,T,I),E) :-
3531 (possible_implied_constraint2(E,T,I) -> true).
3532 possible_implied_constraint2(member(_,b(FUNCTION,_,_)),_,_) :- functor(FUNCTION,F,2),
3533 (function_implication2(F,_) -> true ; F = relations).
3534 possible_implied_constraint2(equal(b(domain(_),_,_),_),_,_). % TO DO: other way around
3535
3536 % f: A --> B ==> f: A +-> B, f: A<->B, dom(f) = A
3537 % test 1442: issue with surjection
3538 implied_constraint2(member(Fun1,b(FUNCTION1,T,_)), member(Fun2,b(FUNCTION2,T,_))) :-
3539 functor(FUNCTION1,F1,2), arg(1,FUNCTION1,X1), arg(2,FUNCTION1,Y1),
3540 functor(FUNCTION2,F2,2), arg(1,FUNCTION2,X2), arg(2,FUNCTION2,Y2),
3541 ? function_implication(F1,F2),
3542 same_texpr(Fun1,Fun2),
3543 same_texpr(X1,X2),
3544 same_texpr(Y1,Y2).
3545 % f: A --> B ==> dom(f) = A
3546 implied_constraint2(member(Fun2,b(FUNCTION2,_,_)), equal(b(domain(Fun1),_,_),Domain)) :-
3547 functor(FUNCTION2,F2,2), arg(1,FUNCTION2,Domain2),
3548 total_function(F2),
3549 same_texpr(Fun1,Fun2),
3550 same_texpr(Domain,Domain2).
3551 % TODO: f: A -->> B ==> ran(f) = B ?
3552
3553
3554 total_function(total_bijection).
3555 total_function(total_injection).
3556 total_function(total_surjection).
3557 total_function(total_function).
3558 %total_relation(total_surjection_relation). % not sure if in this case the constraint is maybe not useful after all?
3559 %total_relation(total_relation).
3560
3561 function_implication(F1,F2) :- function_implication2(F1,F2).
3562 ?function_implication(F1,F2) :- function_implication2(F1,Z), function_implication(Z,F2).
3563
3564 function_implication2(total_bijection,total_injection).
3565 function_implication2(total_bijection,total_surjection).
3566 function_implication2(total_injection,total_function).
3567 function_implication2(total_surjection,total_function).
3568 function_implication2(total_function,partial_function).
3569 function_implication2(partial_function,relations).
3570 function_implication2(partial_injection,partial_function). % >+>
3571 function_implication2(partial_surjection,partial_function).
3572 %function_implication2(partial_bijection,partial_injection).
3573 %function_implication2(partial_bijection,partial_surjection).
3574 function_implication2(total_relation,relations).
3575 function_implication2(surjection_relation,relations).
3576 function_implication2(total_surjection_relation,total_relation).
3577 function_implication2(total_surjection_relation,surjection_relation).
3578
3579 % ------------------
3580
3581
3582 % divide a list of identifiers into domain and range identifiers
3583 get_domain_range_ids([D,R],[D],[R]) :- !.
3584 get_domain_range_ids([D1,D2|T],[D1|DT],R) :- get_domain_range_ids([D2|T],DT,R).
3585
3586
3587 % detect whether there is a pattern of a recursive usage of the identifier: ID(x) or ID[x] or x:ID
3588 find_recursive_usage(TExpr,ID) :-
3589 syntaxtraversion(TExpr,Expr,_,_,Subs,TNames), % print(try_id(ID,Expr,Subs,TNames)),nl,
3590 ( Expr = function(Fun,_), get_texpr_id(Fun,ID) -> true
3591 ; Expr = image(Rel,_), get_texpr_id(Rel,ID) -> true
3592 ; Expr = member(_,Set), get_texpr_id(Set,ID) -> true
3593 ? ; \+ (member(ID1,TNames),get_texpr_id(ID1,ID)), % new local variable with same name
3594 ? member(Sub,Subs), find_recursive_usage(Sub,ID)
3595 ).
3596
3597 :- use_module(bsyntaxtree,[transform_bexpr/3]).
3598 % find comprehension sets and mark them as recursive if they use the recursive ID
3599 mark_recursion(TExpr,RecID,NewTExpr) :-
3600 (transform_bexpr(b_ast_cleanup:mark_comprehension_set(RecID),TExpr,NewTExpr)
3601 -> true
3602 ; add_internal_error('Call failed: ',transform_bexpr(b_ast_cleanup:mark_comprehension_set(RecID),TExpr,NewTExpr)),
3603 NewTExpr=TExpr).
3604
3605 :- public mark_comprehension_set/3.
3606 mark_comprehension_set(RecID,b(lambda(Ids,P,Expr),Type,Info),
3607 b(lambda(Ids,P,Expr),Type,NInfo)) :-
3608 (find_recursive_usage(P,RecID) -> true ; find_recursive_usage(Expr,RecID)),
3609 get_texpr_ids(Ids,AtomicIds),
3610 (silent_mode(on) -> true
3611 ; format('Recursive lambda using ~w detected (name: ~w)~n',[AtomicIds,RecID]),
3612 error_manager:print_message_span(Info),nl
3613 ),
3614 add_texpr_infos(Info,[prob_annotation('SYMBOLIC'),prob_annotation('RECURSIVE')],NInfo).
3615 mark_comprehension_set(RecID,b(comprehension_set(Ids,P),Type,Info),
3616 b(comprehension_set(Ids,P),Type,NInfo)) :-
3617 % DO NOT MARK IT IF IT IS IN RESULT POSITION of recursive function ?
3618 ? find_recursive_usage(P,RecID),
3619 get_texpr_ids(Ids,AtomicIds),
3620 (silent_mode(on) -> true
3621 ; format('Recursive comprehension set using ~w detected (name: ~w)~n',[AtomicIds,RecID]),
3622 error_manager:print_message_span(Info),nl
3623 ),
3624 NInfo = [prob_annotation('SYMBOLIC'),prob_annotation('RECURSIVE')|Info]. % TO DO: only add if not already there
3625
3626 mark_comprehension_set_with(b(X,Type,I),ANN,b(X2,Type,I2)) :- % ANN = 'SYMBOLIC' or 'FORCE' or ...
3627 (X=comprehension_set(Ids,b(P,pred,IP))
3628 -> X2 = comprehension_set(Ids,b(P,pred,IP2)), I2=I,
3629 add_info_if_new(IP,prob_annotation(ANN),IP2)
3630 ; X2=X, add_info_if_new(I,prob_annotation(ANN),I2)
3631 ).
3632
3633 % pred(h) --> h-1, succ(h) --> h+1
3634 precompute_pred_succ_function_call(Fun,Arg,ArithOp) :-
3635 get_texpr_expr(Fun,PS),
3636 ( PS=predecessor -> Op=minus
3637 ; PS=successor -> Op=add), % we could use add_one predicate
3638 ArithOp =.. [Op,Arg,Integer],
3639 create_texpr(integer(1),integer,[],Integer).
3640
3641 %
3642 one(b(integer(1),integer,[])).
3643 create_interval_member(X,LowBound,UpBound,Member) :-
3644 safe_create_texpr(interval(LowBound,UpBound),set(integer),Interval),
3645 safe_create_texpr(member(X,Interval),pred,Member).
3646
3647 get_leq_comparison(less(A,B),A,B1) :- minus_one(B,BM1),
3648 safe_create_texpr(BM1,integer,B1).
3649 get_leq_comparison(greater(B,A),A,B1) :- get_leq_comparison(less(A,B),A,B1).
3650 get_leq_comparison(less_equal(A,B),A,B).
3651 get_leq_comparison(greater_equal(B,A),A,B).
3652
3653 minus_one(b(integer(I),integer,_),Res) :- !, I1 is I-1, Res=integer(I1).
3654 minus_one(B,minus(B,One)) :- one(One).
3655 add_one(b(integer(I),integer,_),Res) :- !, I1 is I+1, Res=integer(I1).
3656 add_one(B,add(B,One)) :- one(One).
3657
3658 % get_geq_comparison(Expr,LHS,RHS) ; RHS can be shifted by 1
3659 get_geq_comparison(less(B,A),A,B1) :- get_geq_comparison(greater(A,B),A,B1).
3660 get_geq_comparison(greater(A,B),A,B1) :- add_one(B,BP1),
3661 safe_create_texpr(BP1,integer,B1).
3662 get_geq_comparison(less_equal(B,A),A,B).
3663 get_geq_comparison(greater_equal(A,B),A,B).
3664 get_geq_comparison(member(A,SET),A,b(integer(Bound),integer,[])) :-
3665 is_inf_integer_set_with_lower_bound(SET,Bound).
3666 % comparison operators:
3667 comparison(equal(A,B),A,B,equal(SA,SB),SA,SB).
3668 comparison(not_equal(A,B),A,B,not_equal(SA,SB),SA,SB).
3669 comparison(greater(A,B),A,B,greater(SA,SB),SA,SB).
3670 comparison(less(A,B),A,B,less(SA,SB),SA,SB).
3671 comparison(greater_equal(A,B),A,B,greater_equal(SA,SB),SA,SB).
3672 comparison(less_equal(A,B),A,B,less_equal(SA,SB),SA,SB).
3673 % rules to simplify binary comparison arguments
3674 simplify_comparison_terms(b(A,T,_IA),b(B,T,_IB),RA,RB) :-
3675 simplify_comparison_terms2(A,B,RA,RB).
3676 % TO DO: expand into much better simplifier !
3677 simplify_comparison_terms2(minus(A1,A2),minus(B1,B2),ResA,ResB) :-
3678 ( same_texpr(A1,B1) -> ResA=B2, ResB=A2 % X-A2 < X-B2 <=> B2 < A2
3679 ; same_texpr(A2,B2) -> ResA=A1, ResB=B1). % A1-X < B1-X <=> A1 < B1
3680 simplify_comparison_terms2(add(A1,A2),add(B1,B2),ResA,ResB) :-
3681 ( same_texpr(A1,B1) -> ResA=A2, ResB=B2 % X+A2 < X+B2 <=> A2 < B2
3682 ; same_texpr(A2,B2) -> ResA=A1, ResB=B1 % A1+X < B1+X <=> A1 < B1
3683 ; same_texpr(A1,B2) -> ResA=A2, ResB=B1 % X+A2 < B1+X <=> A2 < B1
3684 ; same_texpr(A2,B1) -> ResA=A1, ResB=B2). % A1+X < X+B2 <=> A1 < B2
3685 % multiplication: beware of sign, same with division
3686
3687
3688
3689 % simplify equality/inequality Unifications:
3690 simplify_equality(b(A,T,_),b(B,T,_),A2,B2) :-
3691 simplify_equality_aux(A,B,T,A2,B2).
3692 simplify_equality_aux(set_extension([A1]),set_extension([B1]),_,A2,B2) :- !,
3693 opt_simplify_equality(A1,B1,A2,B2).
3694 simplify_equality_aux(CoupleA,Type,CoupleB,A3,B3) :-
3695 get_couple(CoupleA,Type,A1,A2),
3696 get_couple(CoupleB,Type,B1,B2),
3697 (same_texpr(A1,B1), % (1,x)=(1,3) -> x=3
3698 always_well_defined_or_disprover_mode(A1)
3699 -> opt_simplify_equality(A2,B2,A3,B3)
3700 ; same_texpr(A2,B2),always_well_defined_or_disprover_mode(A2)
3701 -> opt_simplify_equality(A1,B1,A3,B3)
3702 ; different_texpr_values(A1,B1), % (1,x)=(2,3) -> 1=2
3703 always_well_defined_or_wd_improvements_allowed(A2),
3704 always_well_defined_or_wd_improvements_allowed(B2)
3705 -> (A3,B3) = (A1,B1) % no need to compare A2,B2
3706 ; different_texpr_values(A2,B2), always_well_defined_or_wd_improvements_allowed(A1),
3707 always_well_defined_or_wd_improvements_allowed(B1)
3708 -> (A3,B3) = (A2,B2) % no need to compare A1,B1
3709 ).
3710
3711 % flexibly get a couple from either AST or value:
3712 get_couple(couple(A1,A2),_,A1,A2).
3713 get_couple(value(CVal),couple(T1,T2),A1,A2) :- nonvar(CVal), CVal=(V1,V2),
3714 A1=b(value(V1),T1,[]), A2=b(value(V2),T2,[]).
3715
3716 opt_simplify_equality(A1,B1,A2,B2) :-
3717 (simplify_equality(A1,B1,A2,B2) -> true ; A2=A1, B2=B1).
3718
3719 % record field set extraction:
3720 construct_field_sets(FieldsSetsOut, field(Name,Type), field(Name,NewSet)) :-
3721 ? (member(field_set(Name,NewSet),FieldsSetsOut)
3722 -> true
3723 ; create_maximal_type_set(Type,NewSet)
3724 ).
3725
3726 % traverse a list of conjuncts and check that they all restrict fields of a record ID
3727 % all sets are combined via intersection
3728 l_update_record_field_membership([],_) --> [].
3729 l_update_record_field_membership([H|T],ID) -->
3730 update_record_field_membership(H,ID), l_update_record_field_membership(T,ID).
3731 update_record_field_membership(b(member(b(LHS,_,_),TRHS),pred,_),ID) --> update2(LHS,TRHS,ID).
3732 update2(record_field(RECID,FieldName),TRHS,ID) --> {get_texpr_id(RECID,ID)},add_field_restriction(FieldName,TRHS).
3733 update2(identifier(ID),b(struct(b(rec(FieldSets),_,_)),_,_),ID) -->
3734 l_add_field_restriction(FieldSets).
3735
3736 l_add_field_restriction([]) --> [].
3737 l_add_field_restriction([field(FieldName,TRHS)|T]) -->
3738 add_field_restriction(FieldName,TRHS), l_add_field_restriction(T).
3739 add_field_restriction(FieldName,TRHS,FieldsIn,FieldsOut) :-
3740 ? (select(field_set(FieldName,OldSet),FieldsIn,F2)
3741 -> OldSet = b(_,Type,_),
3742 safe_create_texpr(intersection(OldSet,TRHS),Type,NewSet),
3743 FieldsOut = [field_set(FieldName,NewSet)|F2]
3744 ; FieldsOut = [field_set(FieldName,TRHS)|FieldsIn]).
3745 % end record field extraction
3746
3747
3748 extract_unions(A,R) :- get_texpr_expr(A,union(A1,A2)),!,
3749 extract_unions(A1,R1), extract_unions(A2,R2),
3750 append(R1,R2,R).
3751 extract_unions(A,[A]).
3752
3753 gen_member_predicates(B,SEl,TExpr) :- safe_create_texpr(member(SEl,B),pred,TExpr).
3754
3755 % when constructing an expression/predicate: important to ripple wd information up
3756 extract_important_info_from_subexpression(b(_,_,Info),NewInfo) :-
3757 include(important_info_from_sub_expr,Info,NewInfo).
3758
3759 extract_important_info_from_subexpressions(b(_,_,Info1),b(_,_,Info2),NewInfo) :-
3760 include(important_info_from_sub_expr,Info1,II1),
3761 (memberchk(contains_wd_condition,Info2), nonmember(contains_wd_condition,II1)
3762 -> NewInfo = [contains_wd_condition|II1]
3763 ; NewInfo=II1). % TO DO: maybe also import other Infos? merge position info (nodeid(_))?
3764 % other important ones: removed_typing ??
3765
3766 % include important info from removed conjunct (note: see also extract_info in bsyntaxtree)
3767 % include_important_info(RemovedPredInfo,RemainingPredInfo,NewInfo)
3768 include_important_info_from_removed_pred([],Info2,Info2).
3769 include_important_info_from_removed_pred([H1|Info1],Info2,NewInfo2) :-
3770 (is_removed_typing_info(H1), nonmember(removed_typing,Info2)
3771 -> NewInfo2 = [removed_typing|Info2]
3772 ; include_important_info_from_removed_pred(Info1,Info2,NewInfo2)).
3773
3774 is_removed_typing_info(was(_)).
3775 is_removed_typing_info(removed_typing).
3776
3777 important_info_from_sub_expr(removed_typing).
3778 important_info_from_sub_expr(contains_wd_condition).
3779 important_info_from_sub_expr(prob_annotation(_)).
3780 important_info_from_sub_expr(nodeid(_)).
3781 important_info_from_sub_expr(was(_)).
3782 %important_info(allow_to_lift_exists). % important but only for exists; should not be copied to outer predicates
3783
3784 % add important infos in case an expression gets simplified into a sub-expression, e.g., bool(X)=TRUE -> X
3785 add_important_info_from_super_expression(Infos,SubInfos,NewSubInfos) :-
3786 include(important_info_from_super_expression,Infos,Important), % print(add_important(Important)),nl,
3787 add_infos_if_new(Important,SubInfos,NewSubInfos).
3788
3789
3790 important_info_from_super_expression(label(_)).
3791 important_info_from_super_expression(P) :- is_rodin_label_info(P). % important for Rodin proof info; if an invariant is partioned
3792 %add_important_info_to_texpr_from_super(Infos,b(Sub,T,SubInfos),b(Sub,T,NewSubInfos)) :- !,
3793 % add_important_info_from_super_expression(Infos,SubInfos,NewSubInfos).
3794
3795 important_info_for_exists(allow_to_lift_exists).
3796 ?important_info_for_exists(Label) :- important_info_from_super_expression(Label).
3797 % add important infos to individual conjuncts which are exists constructs; used when partitioning of exists:
3798 add_important_infos_to_exists_conjuncts(TPred,SuperInfos,SuperIds,NewTPred) :-
3799 include(important_info_for_exists,SuperInfos,Important),
3800 (Important=[]
3801 -> NewTPred=TPred
3802 ; add_to_conjuncts_aux(TPred,Important,SuperIds,NewTPred)
3803 ).
3804 add_to_conjuncts_aux(b(Pred,Type,Infos),Important,SuperIds,b(NP,Type,NewSubInfos)) :-
3805 (Pred=conjunct(A,B)
3806 -> NP=conjunct(NA,NB), NewSubInfos=Infos,
3807 add_to_conjuncts_aux(A,Important,SuperIds,NA),
3808 add_to_conjuncts_aux(B,Important,SuperIds,NB)
3809 ? ; Pred=exists(InnerIds,_), member(TID,InnerIds),
3810 def_get_texpr_id(TID,ID),
3811 ord_member(ID,SuperIds) % the exists is probably related to the outer exists
3812 % (TODO: it could be a lifted clashing one: perform this annotation directly in construct_optimized_exists !!)
3813 -> append(Important,Infos,NewSubInfos), % copy infos from original exists
3814 NP=Pred
3815 ; NP=Pred, NewSubInfos=Infos).
3816
3817 % extract all assignments from a list of statements; last arg is the number of assignments extracted
3818 extract_assignments([],[],[],[],0).
3819 extract_assignments([H|T],ResLHS,ResRHS,Rest,Nr) :-
3820 is_ordinary_assignment(H,LHS,RHS,Cnt),!,
3821 extract_assignments(T,LT,RT,Rest,N),
3822 append(LHS,LT,ResLHS), append(RHS,RT,ResRHS), Nr is N+Cnt.
3823 extract_assignments([H|T],LT,RT,[H|Rest],Nr) :-
3824 extract_assignments(T,LT,RT,Rest,Nr).
3825 % assigned_after(Primed),modifies(Var)
3826
3827 % check if we have an ordinary assignment that can be merged, optimised:
3828 is_ordinary_assignment(b(S,_,Info),LHS,RHS,Cnt) :- is_ordinary_assignment_aux(S,Info,LHS,RHS,Cnt).
3829 is_ordinary_assignment_aux(skip,_Info,[],[],0).
3830 is_ordinary_assignment_aux(assign_single_id(LHS,RHS),_Info,[LHS],[RHS],0). % count=0: used for parallel merge: assign_single_id less useful to merge with
3831 is_ordinary_assignment_aux(assign(LHS,RHS),Info,LHS,RHS,1) :-
3832 \+ member(assigned_after(_),Info), % these assignments are treated in a special way
3833 \+ member(modifies(_),Info).
3834
3835 % merge assignments in a list of statements to be executed by sequential composition:
3836 merge_assignments([S1,S2|T],merged,Res) :- merge_two_assignments(S1,S2,New),!,
3837 merge_assignments([New|T],_,Res).
3838 merge_assignments([],no_merge,[]).
3839 merge_assignments([H|T],Merge,[H|TR]) :- merge_assignments(T,Merge,TR).
3840
3841 :- use_module(b_read_write_info,[get_lhs_assigned_identifier/2]).
3842 get_lhs_assigned_ids(LHS,SortedIds) :-
3843 maplist(get_lhs_assigned_identifier,LHS,TLHSAssign),
3844 get_sorted_ids(TLHSAssign,SortedIds).
3845 merge_two_assignments(S1,S2,NewAssignment) :-
3846 is_ordinary_assignment(S1,LHS1,RHS1,_),
3847 is_ordinary_assignment(S2,LHS2,RHS2,_),
3848 get_lhs_assigned_ids(LHS1,SortedIDs1),
3849 get_lhs_assigned_ids(LHS2,SortedIDs2),
3850 ord_disjoint(SortedIDs1,SortedIDs2), % no race condition
3851 maplist(not_occurs_in_predicate(SortedIDs1),RHS2),
3852 maplist(not_occurs_in_predicate(SortedIDs1),LHS2), % not used in left-hand side, e.g., f(x+y) := RHS
3853 get_texpr_info(S1,I1), get_texpr_info(S2,I2),
3854 merge_info(I1,I2,Infos),
3855 append(LHS1,LHS2,NewLHS),
3856 append(RHS1,RHS2,NewRHS),
3857 NewAssignment = b(assign(NewLHS,NewRHS),subst,Infos),
3858 (debug_mode(off) -> true ; print('Merged assignments: '),translate:print_subst(NewAssignment),nl).
3859 construct_sequence([],skip).
3860 construct_sequence([TH],H) :- !, TH=b(H,_,_).
3861 construct_sequence(List,sequence(List)).
3862
3863 % check if we have a simple expression which will not be complicated to calculate
3864 ?simple_expression(b(E,_,_)) :- simple2(E).
3865 % (simple2(E) -> true ; print(not_simple(E)),nl).
3866 simple2(bool_set).
3867 simple2(boolean_false).
3868 simple2(boolean_true).
3869 simple2(empty_sequence).
3870 simple2(empty_set).
3871 simple2(identifier(_)).
3872 %simple2(integer_set(_)).
3873 simple2(integer(_)).
3874 simple2(lazy_lookup_expr(_)).
3875 simple2(lazy_let_expr(_,A,B)) :- simple2(B), simple_expr_or_pred(A).
3876 simple2(max_int).
3877 simple2(min_int).
3878 simple2(real_set).
3879 simple2(real(_)).
3880 simple2(string_set).
3881 simple2(string(_)).
3882 simple2(value(_)).
3883 simple2(first_of_pair(_)). simple2(second_of_pair(_)).
3884 ?simple2(couple(A,B)) :- simple_expression(A), simple_expression(B).
3885 ?simple2(interval(A,B)) :- simple_expression(A), simple_expression(B).
3886 ?simple2(add(A,B)) :- simple_expression(A), simple_expression(B).
3887 ?simple2(minus(A,B)) :- simple_expression(A), simple_expression(B).
3888 ?simple2(multiplication(A,B)) :- simple_expression(A), simple_expression(B).
3889 simple2(unary_minus(A)) :- simple_expression(A).
3890 ?simple2(convert_bool(A)) :- simple_predicate(A).
3891 ?simple2(sequence_extension(A)) :- maplist(simple_expression,A).
3892 ?simple2(set_extension(A)) :- maplist(simple_expression,A). % a bit more expensive than sequence_extension: elements need to be compared
3893 simple2(X) :- is_integer_set(X,_).
3894
3895 simple_expr_or_pred(b(E,T,_)) :- (T=pred -> simplep2(E) ; simple2(E)).
3896
3897 ?simple_predicate(b(E,_,_)) :- simplep2(E).
3898 ?simplep2(equal(A,B)) :- simple_expression(A), simple_expression(B). % could be slightly more expensive if set type
3899 ?simplep2(not_equal(A,B)) :- simple_expression(A), simple_expression(B). % ditto
3900 simplep2(lazy_let_pred(_,A,B)) :- simple_predicate(B), simple_expr_or_pred(A).
3901 ?simplep2(less(A,B)) :- simple_expression(A), simple_expression(B).
3902 ?simplep2(less_equal(A,B)) :- simple_expression(A), simple_expression(B).
3903 simplep2(greater(A,B)) :- simple_expression(A), simple_expression(B).
3904 simplep2(greater_equal(A,B)) :- simple_expression(A), simple_expression(B).
3905
3906 % detect ID = Expr or Expr = ID
3907 identifier_equality(TExpr,ID,TID,Expr) :- is_equality(TExpr,LHS,RHS),
3908 ( get_texpr_id(LHS,ID), TID=LHS, Expr = RHS
3909 ; get_texpr_id(RHS,ID), TID=RHS, Expr = LHS).
3910
3911
3912 ?id_member_of_set_extension(TExpr,ID,TID,[Expr]) :- identifier_equality(TExpr,ID,TID,Expr).
3913 id_member_of_set_extension(b(member(TID,SEXT),pred,_),ID,TID,SList) :- get_texpr_id(TID,ID),
3914 is_set_extension(SEXT,SList).
3915
3916 % check if merging disjunctions of set_extensionts of this type is useful in CLP(FD) mode
3917 % see get_fd_type in clpfd_tables, ...
3918 type_contains_fd_index(V) :- var(V),!,fail.
3919 type_contains_fd_index(couple(A,_)) :- type_contains_fd_index(A).
3920 type_contains_fd_index(record([field(_,T1)|_])) :- type_contains_fd_index(T1).
3921 type_contains_fd_index(global(_)).
3922 type_contains_fd_index(integer).
3923 type_contains_fd_index(boolean).
3924
3925
3926 create_equalities_for_let(ORefs,Primed,Equalities) :-
3927 maplist(create_equality_for_let,ORefs,Primed,Equalities).
3928 create_equality_for_let(oref(PrimedId,OrigId,Type),TPrimed,Equality) :-
3929 create_texpr(identifier(OrigId),Type,[],TOrig),
3930 create_texpr(identifier(PrimedId),Type,[],TPrimed),
3931 safe_create_texpr(equal(TPrimed,TOrig),pred,Equality).
3932
3933 % inserts a let statement. If the original statement is a precondition or any, the let is moved
3934 % inside the original statement to prevent strange side-effects. This can be used for other,
3935 % non-value changing substitutions as well.
3936 insert_let(TExpr,Ids,P,NTExpr) :-
3937 remove_bt(TExpr,Expr,NewExpr,NTExpr),
3938 move_let_inside(Expr,Old,New,NewExpr),!,
3939 insert_let(Old,Ids,P,New).
3940 insert_let(TExpr,Ids,P,NTExpr) :-
3941 create_texpr(let(Ids,P,TExpr),subst,[],NTExpr).
3942 move_let_inside(precondition(Cond,Old),Old,New,precondition(Cond,New)).
3943 move_let_inside(any(Any,Where,Old),Old,New,any(Any,Where,New)).
3944
3945 % find_one_point_rules(+TypedIds,+Blacklist,+Predicates,
3946 % -LetIds,-LetExprs,-RemainingIds,-RemainingPredicates)
3947 % TypedIds: The ids that are quantified in the exists clause
3948 % Blacklist: All ids that must not be used in the found expression
3949 % Predicates: The predicates of the exists (without already used id=E predicates)
3950 % LetIds: The ids that can be introduced as LET
3951 % LetExprs. For each id (in LetIds) the corresponding expression
3952 % RemainingIds: The ids that are not converted into LETs
3953 % RemainingPredicates: The predicates after removing the id=E predicates
3954 % (e.g., f = {1|->2} & !e.(2:dom(f) & e=f(2) => e>100) should not generate a WD-error)
3955 find_one_point_rules(TIds,Preds,Blacklist,LetIds,Exprs,RestIds,NewPreds) :-
3956 typed_ids_to_avl(TIds,AVL),
3957 find_one_point_equalities(Preds,is_leftmost,AVL,Blacklist,LetIds,Exprs,RestIds,NewPreds).
3958
3959 :- use_module(library(avl),[avl_range/2, avl_fetch/3, avl_delete/4, empty_avl/1]).
3960 :- use_module(bsyntaxtree,[is_equality/3]).
3961 find_one_point_equalities([],_,AVL,_,[],[],RestIds,[]) :-
3962 avl_range(AVL,RestIds).
3963 find_one_point_equalities([TEqual|TPreds],WDLEFT,AVL,Blacklist,LetIds,Exprs,RestIds,NewPreds) :-
3964 split_equality(TEqual,TEq1,TEq2),
3965 %print('Splitting equality: '), translate:print_bexpr(TEqual),nl,
3966 !,
3967 find_one_point_equalities([TEq1,TEq2|TPreds],WDLEFT,AVL,Blacklist,LetIds,Exprs,RestIds,NewPreds).
3968 find_one_point_equalities([TEqual|TPreds],WDLEFT,AVL,Blacklist,[LetID|LetIds],[Expr|Exprs],RestIds,NewPreds) :-
3969 is_equality(TEqual,TA,TB),
3970 ( get_texpr_id(TA,Id),TB=Expr ; get_texpr_id(TB,Id),TA=Expr ),
3971 avl_fetch(Id,AVL,LetID), % we have an equality involving a quantified identifier
3972 %print(wdleft(WDLEFT,Id)),nl, print_bexpr(Expr),nl,
3973 (WDLEFT=is_leftmost
3974 -> true % all the expressions to the left of the equality are well-defined
3975 ; always_defined_full_check_or_disprover_mode(Expr)), % we can lift Id=Expr to an outer LET
3976 % example: UNION(x).(1:dom(f) & x=f(1)|{x}) --> do not lift x=f(1) out if f(1) is not WD, see test 2195
3977 find_identifier_uses_if_necessary(Expr,[],UsedIds),
3978 ord_disjoint(Blacklist,UsedIds),
3979 % TODO: what if we have an equality between two quantified ids in the blacklist?
3980 !,
3981 avl_delete(Id,AVL,_,AVL2),
3982 (empty_avl(AVL2) % check if we have found equalities for all ids
3983 -> NewPreds=TPreds, LetIds=[],Exprs=[],RestIds=[]
3984 ; % should we add Id to Blacklist; usually all ids are already in the blacklist
3985 % WDLEFT remains unchanged
3986 update_wd_to_left(WDLEFT,Expr,NewWDLEFT),
3987 find_one_point_equalities(TPreds,NewWDLEFT,AVL2,Blacklist,LetIds,Exprs,RestIds,NewPreds)
3988 ).
3989 find_one_point_equalities([TEqual|TPreds],_WDLEFT,AVL,Blacklist,LetIds,Exprs,RestIds,[TEqual|NewPreds]) :-
3990 %update_wd_to_left(WDLEFT,Expr,NewWDLEFT),
3991 find_one_point_equalities(TPreds,not_leftmost,AVL,Blacklist,LetIds,Exprs,RestIds,NewPreds).
3992
3993 % update information about whether the next conjunct should still be considered as leftmost concerning WD
3994 update_wd_to_left(is_leftmost,Expr,NewWD) :- always_defined_full_check_or_disprover_mode(Expr),!,
3995 NewWD = is_leftmost.
3996 update_wd_to_left(_,_,not_leftmost).
3997
3998
3999 :- use_module(library(avl),[list_to_avl/2]).
4000 get_avl_aux(TID,Id-TID) :- get_texpr_id(TID,Id).
4001
4002 % convert an unsorted typed identifier list to an AVL tree
4003 typed_ids_to_avl(TIds,AVL) :-
4004 maplist(get_avl_aux,TIds,L),
4005 list_to_avl(L,AVL).
4006
4007
4008 % select a predicate from Preds of the form id=Expr (or Expr=id) where Expr does not contain
4009 % references to identifiers in Blacklist. Rest is Preds without id=Expr
4010 select_equality(TId,Preds,Blacklist,TEqual,Expr,Rest,UsedIds,CheckWellDef) :-
4011 get_texpr_id(TId,Id),
4012 ? safe_select(CheckWellDef,TEqual,Preds,Rest),
4013 is_equality(TEqual,TA,TB), % the ast_cleanup rules have not run yet on the sub-expressions of the exists: detect more equalities
4014 ( get_texpr_id(TA,Id),TB=Expr ; get_texpr_id(TB,Id),TA=Expr ),
4015 find_identifier_uses_if_necessary(Expr,[],UsedIds),
4016 ord_disjoint(Blacklist,UsedIds).
4017
4018
4019 % safely select a predicate from List, preserving WD (well-definedness)
4020 safe_select(check_well_definedness,Element,[H|T],Rest) :- !,
4021 (Element=H,Rest=T % either first element
4022 ; % or if later element; then it must be well-defined; otherwise H could fail
4023 ? select(Element,T,TRest), Rest=[H|TRest],
4024 always_defined_full_check_or_disprover_mode(Element) % we cannot use always_well_defined(Element) in cleanup_pre; it is only computed in cleanup_post at the moment; TO DO: we now do compute in pre phase
4025 %, print(always_wd(Element)),nl
4026 ).
4027 ?safe_select(_,Element,List,Rest) :- select(Element,List,Rest).
4028
4029 % split predicate list into conjuncts using a certain list of ids and those not
4030 split_predicates(LP,Ids,UsingIds,NotUsingIds) :-
4031 get_sorted_ids(Ids,SIds),
4032 ? filter(not_occurs_in_predicate(SIds),LP,NP,UP),
4033 conjunct_predicates_with_pos_info(NP,NotUsingIds),
4034 conjunct_predicates_with_pos_info(UP,UsingIds).
4035
4036 not_occurs_in_predicate([],_Pred) :- !.
4037 not_occurs_in_predicate(SortedIDs,Pred) :- SortedIDs = [ID1|_],
4038 (ID1 = b(_,_,_) -> add_internal_error('Wrapped identifiers: ',not_occurs_in_predicate(SortedIDs,Pred)) ; true),
4039 find_identifier_uses_if_necessary(Pred,[],UsedIds),
4040 ord_disjoint(SortedIDs,UsedIds).
4041 get_sorted_ids(Ids,SIds) :-
4042 get_texpr_ids(Ids,UnsortedIds),sort(UnsortedIds,SIds).
4043
4044 pred_succ_compset(Op,comprehension_set([A,B],Pred)) :-
4045 %get_unique_id('_a_',AId),get_unique_id('_b_',BId),
4046 BId = '_lambda_result_',
4047 (Op = add -> AId = '_succ_' ; AId='_pred_'),
4048 create_texpr(identifier(AId),integer,[],A),
4049 create_texpr(identifier(BId),integer,[lambda_result(BId)],B),
4050 create_texpr(integer(1),integer,[],Integer),
4051 create_texpr(ArithOp,integer,[],TArithOp),
4052 ArithOp =.. [Op,A,Integer],
4053 safe_create_texpr(equal(B,TArithOp),pred,[prob_annotation('LAMBDA-EQUALITY')],Pred).
4054
4055 add_used_identifier_info(_Ids,_P,IOld,INew) :-
4056 ? member(used_ids(_),IOld),!,INew=IOld.
4057 add_used_identifier_info(Ids,P,IOld,[used_ids(FoundIds)|IOld]) :-
4058 % add used identifiers to information
4059 get_sorted_ids(Ids,Ignore),
4060 find_identifier_uses(P,Ignore,FoundIds).
4061
4062 add_used_ids_defined_by_equality(_Ids,P,IOld,INew) :-
4063 ? member(used_ids(UsedIds),IOld),!,
4064 findall(ID, (member_in_conjunction(Equality,P),
4065 identifier_equality(Equality,ID,_TID,Expr),
4066 ord_member(ID,UsedIds),
4067 not_occurs_in_expr(ID,Expr)), % TO DO: we could check also other ids defined by equality already found
4068 IdsDefinedByEquality),
4069 ? (select(used_ids_defined_by_equality(_),IOld,I1) -> true ; I1=IOld),
4070 (IdsDefinedByEquality=[] -> INew=I1
4071 ; %debug_println(9,used_ids_defined_by_equality(IdsDefinedByEquality)),
4072 INew = [used_ids_defined_by_equality(IdsDefinedByEquality)|I1]
4073 ).
4074 add_used_ids_defined_by_equality(Ids,P,IOld,INew) :-
4075 add_internal_error('No used_ids info:',add_used_ids_defined_by_equality(Ids,P,IOld,INew)),
4076 INew=IOld.
4077
4078
4079 % can be used to check the validity of the used_ids field, e.g., for existential quantifier
4080 check_used_ids_info(Parameters,Predicate,StoredUsedIds,PP) :-
4081 % get_global_identifiers(Ignored), and add to Parameters ??
4082 (add_used_identifier_info(Parameters,Predicate,[],[used_ids(UsedIds)])
4083 -> (StoredUsedIds=UsedIds -> true
4084 ; ord_subset(UsedIds,StoredUsedIds)
4085 -> format('Suboptimal used_ids info: ~w (actual ~w) [origin ~w with ~w]~n',[StoredUsedIds,UsedIds,PP,Parameters])
4086 %, print_bexpr(Predicate),nl
4087 ; add_internal_error('Incorrect used_ids info: ', check_used_ids_info(Parameters,Predicate,UsedIds,PP)),
4088 print_bexpr(Predicate),nl,
4089 (extract_span_description(Predicate,PosMsg) -> format('Location: ~w~n',[PosMsg]) ; true),
4090 ord_subtract(UsedIds,StoredUsedIds,Delta),
4091 format('Incorrect used_ids info: ~w (actual ~w)~nNot included: ~w~n~n',[StoredUsedIds,UsedIds,Delta])
4092 %, print_bexpr(Predicate),nl
4093 )
4094 ; add_internal_error('Could not computed used ids:',
4095 add_used_identifier_info(Parameters,Predicate,[],[used_ids(_)]))
4096 ).
4097
4098 % update used_ids_info for existential and universal quantifier (at top-level only !)
4099 recompute_used_ids_info(b(E,pred,Info0),Res) :-
4100 delete(Info0,used_ids(_),Info1),
4101 recompute_used_ids_info_aux(E,Info1,Info2),!, Res= b(E,pred,Info2).
4102 recompute_used_ids_info(TE,TE).
4103
4104 compute_used_ids_info_if_necessary(b(E,pred,Info1),Res) :-
4105 recompute_used_ids_info_aux(E,Info1,Info2),!, Res= b(E,pred,Info2).
4106 compute_used_ids_info_if_necessary(TE,TE).
4107
4108 recompute_used_ids_info_aux(exists(Parameters,Predicate),Info1,Info2) :-
4109 add_used_identifier_info(Parameters,Predicate,Info1,Info2).
4110 recompute_used_ids_info_aux(forall(Parameters,Lhs,Rhs),Info1,Info2) :-
4111 conjunct_predicates([Lhs,Rhs],Predicate),
4112 add_used_identifier_info(Parameters,Predicate,Info1,Info2).
4113 % for while loop we could recompute modifies and reads info
4114
4115 % generation of unique identifiers
4116 :- dynamic unique_id_counter/1.
4117 unique_id_counter(1).
4118
4119 get_unique_id_inside(Prefix,Pred,ResultId) :-
4120 (\+ occurs_in_expr(Prefix,Pred) % first try and see whether we need to append a number
4121 -> ResultId = Prefix
4122 ; get_unique_id(Prefix,ResultId)
4123 ).
4124 get_unique_id_inside(Prefix,Pred,Expr,ResultId) :-
4125 ( \+ occurs_in_expr(Prefix,Pred),
4126 \+ occurs_in_expr(Prefix,Expr) % first try and see whether we need to append a number
4127 -> ResultId = Prefix
4128 ; get_unique_id(Prefix,ResultId)
4129 ).
4130
4131 get_unique_id(Prefix,Id) :-
4132 retract(unique_id_counter(Old)),
4133 New is Old + 1,
4134 assertz(unique_id_counter(New)),
4135 safe_atom_chars(Prefix,CPrefix,get_unique_id1),
4136 number_chars(Old,CNumber),
4137 append(CPrefix,CNumber,CId),
4138 safe_atom_chars(Id,CId,get_unique_id2).
4139
4140 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
4141 % replace all variables in types by "any"
4142
4143 ground_type_to_any(T,Exceptions) :- var(T),!,
4144 ( exact_member(T,Exceptions) -> ! % any variable exact member in list is not grounded
4145 ; T=any).
4146 ground_type_to_any(record(Fields),Exceptions) :- !,
4147 % treat records separately, we do not want the list of fields to be bound to any; see B/Tickets/RecordPartiallyTyped
4148 ground_field_types(Fields,Exceptions).
4149 ground_type_to_any(seq(T),Exceptions) :- !, ground_type_to_any(T,Exceptions).
4150 ground_type_to_any(set(T),Exceptions) :- !, ground_type_to_any(T,Exceptions).
4151 ground_type_to_any(couple(A,B),Exceptions) :- !, ground_type_to_any(A,Exceptions), ground_type_to_any(B,Exceptions).
4152 ground_type_to_any(global(_),_) :- !.
4153 ground_type_to_any(freetype(_),_) :- !.
4154 ground_type_to_any(T,_) :- ground(T),!.
4155 ground_type_to_any(T,Exceptions) :-
4156 functor(T,_,Arity),
4157 ground_type_args(Arity,T,Exceptions).
4158 ground_type_args(0,_T,_Exceptions) :- !.
4159 ground_type_args(N,T,Exceptions) :-
4160 arg(N,T,Arg),
4161 ground_type_to_any(Arg,Exceptions),
4162 N2 is N-1,
4163 ground_type_args(N2,T,Exceptions).
4164
4165 ground_field_types(T,Exceptions) :- var(T),!,
4166 ( exact_member(T,Exceptions) -> ! % any variable exact member in list is not grounded
4167 ; print(grounding_open_ended_record),nl, % should we generate a warning here ?
4168 % Note: did happen for type checking definitions; e.g., via bvisual2:register_top_level(definitions)
4169 % now we pass do_not_ground_types for this
4170 T=[]
4171 ).
4172 ground_field_types([],_) :- !.
4173 ground_field_types([field(Name,Type)|T],Exceptions) :- !,
4174 (var(Name)
4175 -> add_internal_error('Unbound record field name: ',ground_field_types([field(Name,Type)|T],Exceptions))
4176 ; true),
4177 ground_type_to_any(Type,Exceptions),
4178 ground_field_types(T,Exceptions).
4179 ground_field_types(Other,Exceptions) :-
4180 add_internal_error('Illegal record field list: ',ground_field_types(Other,Exceptions)).
4181
4182 % annote variables of becomes_such with before_substitution infos
4183 annotate_becomes_such_vars(Ids1,Pred,Ids2) :-
4184 find_used_primed_ids(Pred,Ids1,BeforeAfter),
4185 maplist(add_before_after_info(BeforeAfter),Ids1,Ids2).
4186 % put optional before/after usage into the information of the identifiers
4187 % makes only sense in the context of becomes_such substitutions
4188 add_before_after_info(BeforeAfter,TId,TId2) :-
4189 def_get_texpr_id(TId,Id),
4190 ? ( member(ba(Id,BeforeId),BeforeAfter) ->
4191 get_texpr_type(TId,Type), get_texpr_info(TId,Info),
4192 create_texpr(identifier(Id),Type,[before_substitution(Id,BeforeId)|Info],TId2)
4193 ; TId = TId2 ).
4194
4195 % find all used pairs of before/after variables, e.g. ba(x,'x$0')
4196 % see becomes_such substitutions
4197 find_used_primed_ids(TExpr,PossibleIds,Uses) :-
4198 prime_identifiers0(PossibleIds,TP0),
4199 get_sorted_ids(TP0,SP0), % sorted list of primed ids
4200 find_used_primed_ids2(SP0,TExpr,[],Uses).
4201 find_used_primed_ids2(SP0,TExpr,In,Out) :-
4202 syntaxtraversion(TExpr,Expr,_,_Infos,Subs,_),
4203 ( (Expr = identifier(FullId),
4204 %member(before_substitution(Id,FullId),Infos) % this info is not available in Event-B mode
4205 ord_member(FullId,SP0),
4206 prime_atom0(Id,FullId))
4207 -> ord_add_element(In,ba(Id,FullId),Uses)
4208 ; In = Uses ),
4209 foldl(find_used_primed_ids2(SP0),Subs,Uses,Out).
4210
4211 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
4212 % find expressions which are possibly not well-defined
4213 is_possibly_undefined(Expr) :- always_wd(Expr),!,fail.
4214 is_possibly_undefined(Expr) :-
4215 safe_syntaxelement_det(Expr,Subs,_Names,_,_),
4216 % note: can be very long list Subs for set_extension
4217 ? member(Sub,Subs),
4218 get_texpr_info(Sub,Info),
4219 memberchk(contains_wd_condition,Info),!.
4220 is_possibly_undefined(Expr) :- % TODO: detect freetype constructors as not having a WD condition
4221 ? has_top_level_wd_condition(Expr). %%,print(wd(F,Expr)),nl.
4222
4223 has_top_level_wd_condition(Expr) :- functor(Expr,F,_),
4224 ? has_wd_condition(F,Expr).
4225
4226 % a few common cases which are always defined:
4227 always_wd(bool_set).
4228 always_wd(boolean_false).
4229 always_wd(boolean_true).
4230 always_wd(empty_set).
4231 always_wd(identifier(_)).
4232 always_wd(integer(_)).
4233 always_wd(integer_set(_)).
4234 always_wd(real_set).
4235 always_wd(real(_)).
4236 always_wd(string(_)).
4237 always_wd(string_set).
4238 %always_wd(value(_)). ?
4239 always_wd(truth).
4240
4241
4242 always_defined_full_check_or_disprover_mode(_) :- preferences:get_preference(disprover_mode,true),!.
4243 always_defined_full_check_or_disprover_mode(BExpr) :- \+ full_check_is_possibly_undefined(BExpr).
4244
4245 % a version which does the full traversal; can be used before contains_wd_condition has been computed
4246 full_check_is_possibly_undefined(BExpr) :- get_texpr_expr(BExpr,Expr),
4247 full_check_is_possibly_undefined_aux(Expr).
4248 full_check_is_possibly_undefined_aux(Expr) :-
4249 functor(Expr,F,_),has_wd_condition(F,Expr),!.
4250 full_check_is_possibly_undefined_aux(Expr) :-
4251 syntaxtraversion(_,Expr,_,_,Subs,_),
4252 ? member(Sub,Subs),
4253 full_check_is_possibly_undefined(Sub),!.
4254
4255 :- use_module(external_functions,[external_fun_has_wd_condition/1]).
4256 % determine if an operator has an attached WD condition (used to compute contains_wd_condition)
4257 % division and module must not divide by zero
4258 has_wd_condition(div,Expr) :- arg(2,Expr,DIV),
4259 ? \+ definitely_not_zero(DIV).
4260 has_wd_condition(floored_div,Expr) :- arg(2,Expr,DIV),
4261 ? \+ definitely_not_zero(DIV).
4262 has_wd_condition(div_real,Expr) :- arg(2,Expr,DIV),
4263 \+ definitely_not_zero(DIV).
4264 % functions must not be applied to values outside their domain
4265 has_wd_condition(function,_Expr). % if lambda over total domain we could remove wd_condition, but ast_cleanup rule then already replaces it with assertion_expression, which gets optimised away in this case
4266 has_wd_condition(assertion_expression,_). % gets translated from function application
4267 has_wd_condition(modulo,Expr) :- arg(2,Expr,DIV),
4268 ? (\+ definitely_not_zero(DIV) ;
4269 \+ definitely_not_negative(DIV) ;
4270 arg(1,Expr,A1), \+ definitely_not_negative(A1)).
4271 % power_of must have a non-negative exponent (?)
4272 has_wd_condition(power_of,Expr) :- arg(2,Expr,EXP),
4273 \+ definitely_not_negative(EXP).
4274 has_wd_condition(power_of_real,Expr) :- arg(1,Expr,Base), arg(2,Expr,EXP),
4275 (definitely_not_negative(Base)
4276 -> (definitely_not_zero(Base) -> fail % no WD if base > 0
4277 ; definitely_not_negative(EXP) -> fail % 0.0 ^ EXP is defined if EXP >=0
4278 ; true % 0.0 ^ -1.0 is a division by zero
4279 )
4280 ; true). % things like -1.0 ^ 0.5 is not a real number; we could check if EXP is guaranteed an integ
4281 % Note: REAL ** INTEGER has no WD condition, but power_of_real has a WD condition
4282 has_wd_condition(iteration,Expr) :- arg(2,Expr,Idx),
4283 \+ definitely_not_negative(Idx).
4284 % min and max need a non-empty set
4285 % also Atelier-B manual requires the set to have an upper limit
4286 has_wd_condition(max,Expr) :- arg(1,Expr,S), \+ definitely_not_empty_and_finite(S).
4287 has_wd_condition(min,Expr) :- arg(1,Expr,S), \+ definitely_not_empty_and_finite(S).
4288 has_wd_condition(max_real,Expr) :- arg(1,Expr,S), \+ definitely_not_empty_and_finite(S).
4289 has_wd_condition(min_real,Expr) :- arg(1,Expr,S), \+ definitely_not_empty_and_finite(S).
4290 % all the sequence operations must not be applied to non-sequence
4291 % relations and some must not be applied to empty-sequences
4292 has_wd_condition(size,E) :- arg(1,E,S), \+ definitely_sequence(S).
4293 has_wd_condition(first,E) :- arg(1,E,S), \+ definitely_not_empty_sequence(S).
4294 has_wd_condition(last,E) :- arg(1,E,S), \+ definitely_not_empty_sequence(S).
4295 has_wd_condition(front,E) :- arg(1,E,S), \+ definitely_not_empty_sequence(S).
4296 has_wd_condition(tail,E) :- arg(1,E,S), \+ definitely_not_empty_sequence(S).
4297 has_wd_condition(rev,E) :- arg(1,E,S), \+ definitely_sequence(S).
4298 has_wd_condition(concat,_).
4299 has_wd_condition(insert_front,_).
4300 has_wd_condition(insert_tail,_).
4301 has_wd_condition(restrict_front,_).
4302 has_wd_condition(restrict_tail,_).
4303 has_wd_condition(general_concat,_).
4304 % the general intersection must not be applied to an empty set of sets
4305 has_wd_condition(general_intersection,Expr) :- arg(1,Expr,S),
4306 \+ definitely_not_empty_set(S).
4307 has_wd_condition(quantified_intersection,_). % gets translated to general_intersection
4308 % card must not be applied to infinite sets:
4309 has_wd_condition(card,Expr) :- arg(1,Expr,S), \+ definitely_finite(S).
4310 has_wd_condition(general_sum,_). % TO DO: \+ definitely_finite2(comprehension_set(Ids,P))
4311 has_wd_condition(general_product,_). % ditto; note: sets which are summed/multiplied must be finite
4312 has_wd_condition(mu,_). % Z MU Operator
4313 has_wd_condition(freetype_destructor,_).
4314 has_wd_condition(external_function_call,Expr) :- arg(1,Expr,FunName),
4315 external_fun_has_wd_condition(FunName).
4316 has_wd_condition(external_pred_call,Expr) :- arg(1,Expr,FunName),
4317 external_fun_has_wd_condition(FunName).
4318 % external_subst_call?
4319 has_wd_condition(operation_call_in_expr,_). % we now assume all operation calls may have PRE-conditions
4320 % or involve recursion, and thus may loop; TO DO: compute this information per operation by a fixpoint algorithm
4321
4322 definitely_not_zero(b(integer(X),integer,_)) :- integer(X), X \= 0.
4323 definitely_not_zero(b(real(X),real,_)) :- atom(X), construct_real(X,R), R \= 0.0.
4324 definitely_not_negative(b(integer(X),integer,_)) :- number(X), X >= 0.
4325 % to do add more ?: card(_), ...
4326
4327
4328 % see definitely_not_empty_set/1 in bsyntaxtree
4329 definitely_not_empty_and_finite(b(S,_,_)) :- def_not_empty_fin2(S).
4330 def_not_empty_fin2(bool_set).
4331 def_not_empty_fin2(set_extension([_|_])).
4332 def_not_empty_fin2(sequence_extension([_|_])).
4333 def_not_empty_fin2(cartesian_product(A,B)) :- definitely_not_empty_and_finite(A), definitely_not_empty_and_finite(B).
4334 def_not_empty_fin2(union(A,B)) :- definitely_not_empty_and_finite(A), definitely_not_empty_and_finite(B).
4335 def_not_empty_fin2(overwrite(A,B)) :- definitely_not_empty_and_finite(A),definitely_not_empty_and_finite(B).
4336 def_not_empty_fin2(interval(A,B)) :- definitely_not_empty_set(b(interval(A,B),set(integer),[])).
4337 def_not_empty_fin2(value(S)) :- % what about closures ?
4338 definitely_not_empty_finite_value(S). %kernel_objects:not_empty_set(S).
4339
4340
4341 definitely_not_empty_sequence(b(S,_,_)) :- definitely_not_empty_sequence2(S).
4342 definitely_not_empty_sequence2(sequence_extension(_)).
4343
4344 definitely_sequence(b(S,_,_)) :- definitely_sequence2(S).
4345 definitely_sequence2(empty_sequence).
4346 definitely_sequence2(sequence_extension(_)).
4347
4348 :- use_module(typing_tools,[is_provably_finite_type/1, is_infinite_type/1]).
4349 is_infinite_ground_type(Type) :-
4350 ground(Type), is_infinite_type(Type). % non-ground types happen e.g. in test 472
4351
4352 definitely_finite(b(S,Type,_)) :-
4353 (ground(Type)
4354 -> (is_provably_finite_type(Type)
4355 -> true
4356 ; definitely_finite2(S) -> true
4357 %; \+ is_infinite_type(Type) -> print(no_longer_assuming_finite(Type)),nl,nl,fail
4358 )
4359 ; definitely_finite2(S)).
4360 definitely_finite2(bool_set).
4361 definitely_finite2(empty_set).
4362 definitely_finite2(empty_sequence).
4363 definitely_finite2(set_extension(_)).
4364 definitely_finite2(sequence_extension(_)).
4365 definitely_finite2(cartesian_product(A,B)) :- definitely_finite(A), definitely_finite(B).
4366 definitely_finite2(overwrite(A,B)) :- definitely_finite(A), definitely_finite(B).
4367 definitely_finite2(union(A,B)) :- definitely_finite(A), definitely_finite(B).
4368 definitely_finite2(intersection(A,B)) :- (definitely_finite(A) -> true ; definitely_finite(B)).
4369 definitely_finite2(set_subtraction(A,_)) :- definitely_finite(A).
4370 definitely_finite2(domain_restriction(_,B)) :- definitely_finite(B). % A finite does not guarantee finite relation
4371 definitely_finite2(domain_subtraction(_,B)) :- definitely_finite(B).
4372 definitely_finite2(range_restriction(A,_)) :- definitely_finite(A). % B finite does not guarantee finite relation
4373 definitely_finite2(range_subtraction(A,_)) :- definitely_finite(A).
4374 definitely_finite2(interval(_,_)).
4375 definitely_finite2(value(S)) :- nonvar(S),(S=[] ; S=avl_set(_)).
4376 % TO DO: add other operators : comprehension_set(Ids,P)
4377
4378
4379 ?definitely_infinite(b(S,_,_)) :- !,definitely_infinite2(S).
4380 definitely_infinite(S) :- add_internal_error('AST not wrapped:',definitely_infinite(S)),fail.
4381 definitely_infinite2(string_set).
4382 definitely_infinite2(real_set).
4383 definitely_infinite2(integer_set(X)) :-
4384 X='NATURAL' ; X='NATURAL1' ; X='INTEGER'.
4385 definitely_infinite2(seq1(S)) :- definitely_not_empty_set(S).
4386 definitely_infinite2(seq(S)) :- definitely_not_empty_set(S).
4387 definitely_infinite2(cartesian_product(A,B)) :- is_infinite_cart_prod(A,B).
4388 ?definitely_infinite2(pow_subset(S)) :- definitely_infinite(S).
4389 definitely_infinite2(pow1_subset(S)) :- definitely_infinite(S).
4390 definitely_infinite2(fin_subset(S)) :- definitely_infinite(S). % the set of finite subsets is infinite
4391 definitely_infinite2(fin1_subset(S)) :- definitely_infinite(S).
4392 definitely_infinite2(iseq(S)) :- definitely_infinite(S).
4393 definitely_infinite2(iseq1(S)) :- definitely_infinite(S).
4394 definitely_infinite2(perm(S)) :- definitely_infinite(S).
4395 ?definitely_infinite2(value(V)) :- infinite_value_set(V).
4396 definitely_infinite2(relations(A,B)) :- is_infinite_cart_prod(A,B).
4397 definitely_infinite2(partial_function(A,B)) :- is_infinite_cart_prod(A,B).
4398 definitely_infinite2(total_function(A,B)) :-
4399 (definitely_infinite(A) -> definitely_not_empty_set_card_gt1(B) % INTEGER-->{1} is finite, INTEGER-->BOOL is inf.
4400 ? ; definitely_infinite(B) -> definitely_not_empty_set(A)). % {TRUE} --> INTEGER is infinite
4401 definitely_infinite2(total_relation(A,B)) :- definitely_infinite2(total_function(A,B)).
4402 % TODO: partial_injection, total_injection, partial_surjection, total_surjection, total_bijection, partial_bijection,
4403 % surjection_relation, total_surjection_relation
4404 % cf total_surjection_card
4405
4406 % non empty sets with at least two elements:
4407 definitely_not_empty_set_card_gt1(bool_set).
4408 definitely_not_empty_set_card_gt1(A) :- definitely_infinite(A).
4409
4410 is_infinite_cart_prod(A,B) :-
4411 ? (definitely_infinite(A) -> definitely_not_empty_set(B) % INTEGER*{} is finite
4412 ? ; definitely_infinite(B) -> definitely_not_empty_set(A)).
4413
4414 infinite_value_set(V) :- var(V),!,fail.
4415 infinite_value_set(global_set(X)) :-
4416 X='NATURAL' ; X='NATURAL1' ; X='INTEGER'.
4417 infinite_value_set(closure(P,T,B)) :-
4418 % T \= [integer], % otherwise we could intersect with NATURAL,... ????
4419 custom_explicit_sets:is_infinite_closure(P,T,B).
4420 infinite_value_set(freetype(ID)) :- kernel_freetypes:is_infinite_freetype(ID).
4421
4422
4423
4424
4425 % check if %(Ids).(Pred|_) is infinite
4426 infinite_or_symbolic_domain_for_lambda(Ids,b(Expr,pred,_),Kind) :-
4427 ? inf_dom_aux(Expr,Ids,Kind).
4428 inf_dom_aux(member(TID2,InfSet),[TID],infinite) :- same_id(TID,TID2,_),
4429 ? definitely_infinite(InfSet).
4430 inf_dom_aux(truth,Ids,infinite) :-
4431 ? member(TID,Ids), get_texpr_type(TID,Type),
4432 is_infinite_ground_type(Type).
4433 inf_dom_aux(COMP,[TID|_],infinite) :- % A \= "" or A \= 0 or A \= B+1 or A < B*B or ...
4434 ? binary_inf_comparison(COMP,A,B),
4435 get_texpr_type(TID,Type), is_infinite_ground_type(Type),
4436 same_id(A,TID,ID),
4437 not_occurs_in_expr(ID,B). % ensure B does not depend on A; e.g. we have %x.(x/=x | E) is empty
4438 inf_dom_aux(equal(EXTFUN,BOOL),Ids,symbolic) :-
4439 % something like f = %s.(s:STRING & REGEX_MATCH(s,"[a-z]+")=TRUE | s)
4440 get_texpr_expr(EXTFUN,external_function_call(FUN,Args)),
4441 get_texpr_boolean(BOOL,_),
4442 is_symbolic_ext_pred(FUN,Args,Ids).
4443 inf_dom_aux(external_pred_call(FUN,Args),Ids,symbolic) :-
4444 is_symbolic_ext_pred(FUN,Args,Ids).
4445
4446 % a comparator which allows infinitely many values for first argument with fixed second argument
4447 ?binary_inf_comparison(not_equal(A,B),AA,BB) :- sym_unify(A,B,AA,BB).
4448 ?binary_inf_comparison(less(A,B),AA,BB) :- sym_unify(A,B,AA,BB).
4449 ?binary_inf_comparison(less_equal(A,B),AA,BB) :- sym_unify(A,B,AA,BB).
4450 ?binary_inf_comparison(greater(A,B),AA,BB) :- sym_unify(A,B,AA,BB).
4451 ?binary_inf_comparison(greater_equal(A,B),AA,BB) :- sym_unify(A,B,AA,BB).
4452
4453 sym_unify(A,B,A,B).
4454 sym_unify(A,B,B,A).
4455
4456 % not guaranteed to be infinite, but makes sense to keep symbolic
4457 is_symbolic_ext_pred(FUN,Args,[TID|_]) :-
4458 symbolic_ext_pred(FUN),
4459 def_get_texpr_id(TID,ID),
4460 ? (member(A,Args), occurs_in_expr(ID,A) -> true). % ensure the condition is not static and depends on an argument
4461
4462 % external predicates which indicate that the corresponding function should be kept symbolic
4463 symbolic_ext_pred('IS_REGEX').
4464 symbolic_ext_pred('GET_IS_REGEX').
4465 symbolic_ext_pred('REGEX_MATCH').
4466 symbolic_ext_pred('REGEX_IMATCH').
4467 symbolic_ext_pred('GET_IS_REGEX_MATCH').
4468 symbolic_ext_pred('GET_IS_REGEX_IMATCH').
4469 symbolic_ext_pred('STRING_EQUAL_CASE_INSENSITIVE').
4470 symbolic_ext_pred('STRING_IS_ALPHANUMERIC').
4471 symbolic_ext_pred('STRING_IS_DECIMAL').
4472 symbolic_ext_pred('STRING_IS_NUMBER').
4473 symbolic_ext_pred('GET_STRING_EQUAL_CASE_INSENSITIVE').
4474 symbolic_ext_pred('GET_STRING_IS_ALPHANUMERIC').
4475 symbolic_ext_pred('GET_STRING_IS_DECIMAL').
4476 symbolic_ext_pred('GET_STRING_IS_NUMBER').
4477 symbolic_ext_pred('GET_STRING_IS_INT').
4478 symbolic_ext_pred('FILE_EXISTS').
4479 symbolic_ext_pred('GET_FILE_EXISTS').
4480 symbolic_ext_pred('DIRECTORY_EXISTS').
4481 symbolic_ext_pred('GET_DIRECTORY_EXISTS').
4482 % TODO: add more external predicates
4483 %symbolic_ext_pred(X) :- nl,print(not_symbolic(X)),nl,fail.
4484
4485
4486 :- use_module(custom_explicit_sets,[quick_is_definitely_maximal_set/1]).
4487 % should we use is_just_type/1 instead ?? TO DO: check
4488 definitely_maximal_set(b(S,_,_)) :- definitely_maximal2(S).
4489 definitely_maximal2(integer_set('INTEGER')).
4490 definitely_maximal2(bool_set).
4491 definitely_maximal2(string_set).
4492 definitely_maximal2(typeset).
4493 definitely_maximal2(comprehension_set(_,b(truth,_,_))). % also covers is_integer_set(X,'INTEGER')
4494 definitely_maximal2(value(S)) :- nonvar(S),quick_is_definitely_maximal_set(S).
4495 % TO DO: cartesian product, records, ... if useful
4496
4497
4498 % just a sequence consisting of a single element
4499 is_singleton_sequence(b(sequence_extension([ELEMENT]),_,_),ELEMENT).
4500
4501 % check if type does not contain sets
4502 type_contains_no_sets(X) :- var(X),!,fail. % in test 472 we have a variable type
4503 type_contains_no_sets(integer).
4504 type_contains_no_sets(boolean).
4505 type_contains_no_sets(string).
4506 type_contains_no_sets(global(_)).
4507 type_contains_no_sets(couple(A,B)) :- type_contains_no_sets(A), type_contains_no_sets(B).
4508 type_contains_no_sets(record(Fields)) :- field_types_ok(Fields).
4509 field_types_ok([]).
4510 field_types_ok([field(_,Type)|T]) :- type_contains_no_sets(Type), field_types_ok(T).
4511
4512 % ----------------------------------
4513
4514
4515 select_conjunct(Predicate,Conjunction,Prefix,Suffix) :-
4516 conjunction_to_list(Conjunction,List),
4517 append(Prefix,[Predicate|Suffix],List).
4518
4519
4520 data_validation_mode :-
4521 (get_preference(data_validation_mode,true) -> true
4522 ; environ(prob_data_validation_mode,true)).
4523
4524 % optionally provide hints about rewritings or potential improvements
4525 add_hint_message(_,_Msg,_Term,_Span) :- debug_mode(off),
4526 get_preference(performance_monitoring_on,false), % should we use another preference?
4527 !.
4528 add_hint_message(Src,Msg,Term,Span) :-
4529 add_message(Src,Msg,Term,Span).
4530
4531 % ------------------------
4532
4533 % mini partial evaluation / constant expression evaluation of B expressions
4534 % TO DO: unify with b_compile and b_expression_sharing !
4535 % But this one only pre-computes top-level operators; assumes bottom-up traversal
4536
4537 :- use_module(kernel_card_arithmetic,[safe_pown/3]).
4538 :- use_module(library(avl),[avl_size/2]).
4539 pre_compute_static_int_expression(add(A,B),Result) :- % plus
4540 get_integer(A,IA), get_integer(B,IB),
4541 Result is IA+IB.
4542 pre_compute_static_int_expression(minus(A,B),Result) :- % plus
4543 get_integer(A,IA), get_integer(B,IB),
4544 Result is IA-IB.
4545 pre_compute_static_int_expression(unary_minus(A),Result) :- % plus
4546 get_integer(A,IA),
4547 Result is -IA.
4548 pre_compute_static_int_expression(multiplication(A,B),Result) :-
4549 get_integer(A,IA), get_integer(B,IB),
4550 Result is IA*IB.
4551 pre_compute_static_int_expression(div(A,B),Result) :- % TO DO: also add floored_div
4552 get_integer(B,IB), IB \= 0,
4553 get_integer(A,IA),
4554 Result is IA//IB.
4555 pre_compute_static_int_expression(modulo(A,B),Result) :-
4556 get_integer(B,IB), IB > 0,
4557 get_integer(A,IA), IA >= 0,
4558 Result is IA mod IB.
4559 pre_compute_static_int_expression(power_of(A,B),Result) :-
4560 get_integer(A,IA), get_integer(B,IB), IB >= 0,
4561 safe_pown(IA,IB,Result), number(Result).
4562 pre_compute_static_int_expression(card(A),Result) :-
4563 get_nonvar_val(A,AVal),
4564 (AVal=[] -> Result=0
4565 ; AVal=avl_set(AVL) -> avl_size(AVL,Result)).
4566
4567 get_nonvar_val(b(value(V),_,_),V) :- nonvar(V).
4568
4569 % ----------------------------------------
4570