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