1 | | % (c) 2009-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen, |
2 | | % Heinrich Heine Universitaet Duesseldorf |
3 | | % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html) |
4 | | |
5 | | |
6 | | :- module(bvisual2,[ %reset_bvisual/0, |
7 | | bv_get_top_level/1 |
8 | | , bv_expand_formula/3 % also used to get string of entry |
9 | | , bv_get_values/3 |
10 | | , bv_get_values/2 |
11 | | , bv_insert_formula/3 |
12 | | %, bv_include_variables/0 |
13 | | , bv_get_value_unlimited/3 |
14 | | , bv_get_values_unlimited/3 |
15 | | , bv_is_explanation_node/1 |
16 | | , bv_print_to_file/3 |
17 | | , bv_write_all_variables_and_constants/2 |
18 | | , set_bvisual2_translation_mode/1 |
19 | | , bvisual2_translation_mode/1 |
20 | | , bv_get_top_level_formula/4 |
21 | | , bv_get_top_level_formula/5 |
22 | | , bv_value_to_atom/2 |
23 | | , bv_show_formula_origin/2 |
24 | | , bv_formula_description/2 |
25 | | , bv_formula_extended_description/2 |
26 | | , bv_formula_discharged_info/2 |
27 | | , bv_get_formula_functor_symbol/2 |
28 | | , bv_get_btvalue/4 |
29 | | , bv_is_child_formula/1 |
30 | | , bv_formula_labels/2 |
31 | | , bv_is_typed_formula/1 |
32 | | , bv_is_typed_predicate/1 |
33 | | , bv_is_typed_identifier/2 |
34 | | , bv_get_stored_formula_expr/2 |
35 | | , tcltk_register_new_user_formula/1 |
36 | | , html_debug_operation_for_stateid/4 |
37 | | , bv_top_level_set/2 |
38 | | ]). |
39 | | |
40 | | :- meta_predicate bv_time_out_call(0,-,-,-). |
41 | | :- meta_predicate call_with_temp_preference(*,*,0). |
42 | | :- meta_predicate with_bvisual2_translation_mode(0). |
43 | | |
44 | | :- use_module(probsrc(module_information),[module_info/2]). |
45 | | :- module_info(group,ast). |
46 | | :- module_info(description,'This module contains functionality to analyse B expressions and predicates by evaluating and decomposing them into substructures.'). |
47 | | |
48 | | :- use_module(library(lists)). |
49 | | :- use_module(library(codesio)). |
50 | | %:- use_module(library(timeout)). |
51 | | |
52 | | :- use_module(probsrc(bmachine), [ b_machine_has_constants_or_properties/0 |
53 | | , b_get_machine_variables_in_original_order/1 |
54 | | , b_get_machine_constants/1 |
55 | | , b_get_machine_operation/4 |
56 | | , b_get_properties_from_machine/1 |
57 | | , b_machine_additional_property/1 |
58 | | , get_invariant_list_with_proof_info/1 |
59 | | , b_get_static_assertions_from_machine/1 |
60 | | , b_get_assertions_from_main_machine/2 |
61 | | , b_get_dynamic_assertions_from_machine/1 |
62 | | , b_get_assertion_count/3 |
63 | | , b_get_operation_variant/3 |
64 | | , b_get_operation_description/2 |
65 | | ]). |
66 | | :- use_module(probsrc(specfile),[ state_corresponds_to_initialised_b_machine/2 |
67 | | , state_corresponds_to_set_up_constants/2, property/2, xtl_mode/0 |
68 | | ]). |
69 | | :- use_module(probsrc(state_space), [ visited_expression/2 |
70 | | , current_state_id/1 |
71 | | , invariant_not_yet_checked/1 |
72 | | , invariant_violated/1 |
73 | | , transition/3 |
74 | | ]). |
75 | | :- use_module(probsrc(store),[ empty_state/1 |
76 | | , normalise_store/2 |
77 | | ]). |
78 | | :- use_module(probsrc(b_interpreter),[ |
79 | | b_not_test_boolean_expression_cs/5 |
80 | | , b_test_boolean_expression_for_ground_state/5 |
81 | | , b_test_boolean_expression/4 |
82 | | , b_compute_expression_nowf/6 |
83 | | , b_execute_statement_nowf/5 |
84 | | , set_up_typed_localstate/6 |
85 | | , properties_were_filtered/1 |
86 | | ]). |
87 | | :- use_module(probsrc(translate),[ translate_bexpression_to_codes/2 |
88 | | , translate_subst_or_bexpr_with_limit/3 |
89 | | , get_texpr_top_level_symbol/4 |
90 | | , translate_bvalue_for_expression_with_limit/4 |
91 | | , translate_bvalue_for_expression/3 |
92 | | , translate_bvalue_with_type_and_limit/4 |
93 | | , translate_bvalue/2 |
94 | | , translate_any_state/2 |
95 | | , translate_b_state_to_comma_list/3 |
96 | | , translate_prolog_exception/2 |
97 | | , translate_eventb_direct_definition_header/3 |
98 | | , translate_eventb_direct_definition_body/2 |
99 | | ]). |
100 | | :- use_module(probsrc(bsyntaxtree),[ get_texpr_expr/2 |
101 | | , get_texpr_type/2 |
102 | | , get_texpr_info/2 |
103 | | , get_texpr_id/2 |
104 | | , is_texpr/1 |
105 | | , create_texpr/4 |
106 | | , safe_create_texpr/3 |
107 | | , syntaxtraversion/6 |
108 | | , conjunction_to_list/2 |
109 | | , conjunct_predicates/2 |
110 | | , create_exists/3 |
111 | | , create_or_merge_exists/3 |
112 | | , create_forall/3 |
113 | | , texpr_contains_wd_condition/1 |
114 | | %, find_identifier_uses/3 |
115 | | ]). |
116 | | :- use_module(probsrc(b_ast_cleanup),[ clean_up_pred/3 |
117 | | ]). |
118 | | :- use_module(probsrc(error_manager),[ get_all_errors_and_clear/1 |
119 | | , get_perror/4 |
120 | | , time_out_with_enum_warning_one_solution/3 |
121 | | ]). |
122 | | :- use_module(probsrc(preferences), [ get_preference/2 |
123 | | , set_preference/2 |
124 | | ]). |
125 | | :- use_module(probsrc(kernel_waitflags), [ init_wait_flags_with_call_stack/2 |
126 | | , ground_wait_flags/1]). |
127 | | :- use_module(probsrc(b_enumerate),[ b_tighter_enumerate_values_in_ctxt/3 ]). |
128 | | :- use_module(probsrc(tools_files),[ put_codes/2]). |
129 | | :- use_module(probsrc(tools_strings),[ strip_newlines/2, atom_prefix/2]). |
130 | | :- use_module(probltlsrc(ltl),[get_ltl_formula_strings/2]). % did lead to SPIO_E_TOO_MANY_OPEN_FILES |
131 | | :- use_module(probltlsrc(ltl_translate),[pp_ltl_formula/2, get_ltl_sub_formulas/3]). |
132 | | :- use_module(probltlsrc(ltl_propositions), [is_atomic_ltl_property/1, check_atomic_property_formula/2]). |
133 | | :- use_module(probltlsrc(ltl_tools),[temporal_parser/3]). |
134 | | |
135 | | :- use_module(probsrc(bmachine_eventb), [ stored_operator_direct_definition/8]). |
136 | | :- use_module(probsrc(debug), [debug_format/3, debug_mode/1]). |
137 | | |
138 | | :- set_prolog_flag(double_quotes, codes). |
139 | | |
140 | | :- dynamic top_level_node/1, subnode/2, supernode/2. |
141 | | :- dynamic stored_formula/2, expanded/1, explanation_parent/1. |
142 | | :- dynamic id_counter/1. |
143 | | :- dynamic formula_cache/3. |
144 | | % We store the information whether a node can introduce new values as an (counter-)example |
145 | | % in example_node/1; the value is computed in explore_node/2. |
146 | | % For such nodes, the found examples are stored in local_state/3. |
147 | | :- dynamic example_node/1,local_state/3. |
148 | | |
149 | | |
150 | | |
151 | | bv_value_to_atom(p(P),R) :- !, % a predicate value |
152 | | (P=true -> R='TRUE' ; P=false -> R='FALSE' ; R=P). |
153 | | bv_value_to_atom(e(_),R) :- !, R='ERROR'. |
154 | | bv_value_to_atom(v(V),R) :- !, R=V. % a value, already pretty-printed !?? |
155 | | bv_value_to_atom(i,R) :- !, R='INACTIVE'. |
156 | | bv_value_to_atom(bv_info(V),R) :- !, R=V. |
157 | | bv_value_to_atom(V,V). |
158 | | |
159 | | |
160 | | :- dynamic variables_should_be_included/0. |
161 | | variables_should_be_included. |
162 | | %bv_include_variables :- |
163 | | % (variables_should_be_included -> true ; assertz(variables_should_be_included)). |
164 | | |
165 | | clear_bvisual :- |
166 | | retractall(top_level_node(_)), |
167 | | retractall(subnode(_,_)), % TO DO: do not delete user formulas for a simple re-load ?! |
168 | | retractall(supernode(_,_)), |
169 | | retractall(stored_formula(_,_)), |
170 | | retractall(expanded(_)), |
171 | | retractall(explanation_parent(_)), |
172 | | retractall(formula_cache(_,_,_)), |
173 | | retractall(example_node(_)), |
174 | | retractall(local_state(_,_,_)), |
175 | | retractall(specfile_property_cache(_,_)), |
176 | | retractall(specfile_property_cached_state(_)). |
177 | | % This predicate should be called after loading a new specification |
178 | | % and before using the other predicates below |
179 | | reset_bvisual :- |
180 | | clear_bvisual, |
181 | | register_top_level. |
182 | | |
183 | | :- public portray_bvisual/0. % debugging utility |
184 | | portray_bvisual :- %listing(top_level_node/1), listing(subnode/2), listing(stored_formula/2) |
185 | | top_level_node(N), bv_portray(N,1),fail. |
186 | | portray_bvisual. |
187 | | bv_portray(ID,Level) :- |
188 | | (stored_formula(ID,Form) -> functor(Form,F,_) ; F = '??'), |
189 | | (expanded(ID) -> E=expanded ; E = 'not_expanded'), |
190 | | indent(Level),format('~w -> ~w [~w]~n',[ID,F,E]), |
191 | | L1 is Level+1, |
192 | | subnode(ID,ID2), |
193 | | bv_portray(ID2,L1). |
194 | | indent(0) :- !. |
195 | | indent(N) :- N>0,!, N1 is N-1, print(' '), indent(N1). |
196 | | |
197 | | % returns the top-level nodes as a list of IDs |
198 | | bv_get_top_level(Tops) :- |
199 | | findall( Id, top_level_node(Id), Tops ). |
200 | | |
201 | | % bv_expand_formula(+FormulaID,-LabelAtom,-) |
202 | | % Input: Id |
203 | | % Output: Label of Formula, list of children |
204 | | bv_expand_formula(Id,Label,Children) :- |
205 | | expanded(Id),!, |
206 | | get_node_label(Id,Label), |
207 | | findall(C, subnode(Id,C), Children). |
208 | | bv_expand_formula(Id,Label,Children) :- |
209 | | get_node_label(Id,Label), |
210 | | explore_node(Id,Children). |
211 | | |
212 | | % bv_get_values in current state |
213 | | bv_get_values(Ids,Values) :- |
214 | | current_state_id(StateId), |
215 | | bv_get_values(Ids,StateId,Values). |
216 | | |
217 | | :- use_module(probsrc(specfile),[prepare_state_for_specfile_trans/3]). |
218 | | :- use_module(probsrc(tools),[start_ms_timer/1,get_elapsed_runtime/2]). |
219 | | |
220 | | % bv_get_values(+IdsOfFormulas,+CurrentStateID,-ValuesOfFormulas) |
221 | | bv_get_values(Ids,StateId,Values) :- |
222 | | visited_expression(StateId,State),!, |
223 | | prepare_state_for_specfile_trans(State,StateId,PreparedState), |
224 | | bv_get_default_formula_timeout(Timeout), |
225 | | start_ms_timer(Timer), |
226 | | bv_get_values2(Ids,PreparedState,StateId,Timeout,Timer,Values). |
227 | | bv_get_values(Ids,_StateId,Values) :- |
228 | | % in case that the state ID cannot be resolved, we |
229 | | % return an error for each formula |
230 | | same_length(Ids,Values), |
231 | | same_value(Values,e('unknown state')). |
232 | | same_value([],_). |
233 | | same_value([V|Rest],V) :- same_value(Rest,V). |
234 | | |
235 | | % get timeout for standard formula evaluation of an entry in the bvisual2 table: |
236 | | bv_get_default_formula_timeout(BVTimeout) :- |
237 | | get_preference(time_out,Timeout), |
238 | | (Timeout =< 1200 -> BVTimeout = Timeout |
239 | | ; BVTimeout is 1200 + (Timeout-1000)// 5). |
240 | | |
241 | | % Insert a new formula |
242 | | % bv_insert_formula(+TypeCheckedExpression,+ParentID,-IDofNewFormula) |
243 | | bv_insert_formula(TExpr,ParentId,Id) :- %print(bv_insert_formula(TExpr,ParentId)),nl, |
244 | | get_new_id(Id), |
245 | | assertz( stored_formula(Id,TExpr) ), |
246 | | assertz( subnode(ParentId,Id) ), |
247 | | assertz( supernode(Id,ParentId) ), |
248 | | (ParentId == top -> assertz(top_level_node(Id)) ; true). |
249 | | |
250 | | bv_time_out_call(Call,ValueFromCall,Timeout,Value) :- |
251 | | catch(bv_time_out_call2(Call,ValueFromCall,Timeout,Value),Exception, |
252 | | (Value=e(ErrStr),translate_prolog_exception(Exception,ErrStr))). |
253 | | bv_time_out_call2(Call,ValueFromCall,Timeout,Value) :- |
254 | | (time_out_with_enum_warning_one_solution( Call, |
255 | | Timeout, |
256 | | Result) |
257 | | -> |
258 | | ( Result == success -> Value = ValueFromCall |
259 | | ; Result = virtual_time_out(failure_enumeration_warning(_Info,_,_,_,critical)) -> Value = e('?(\x221E\)') % Value = e('\x22A5\?(\x221E\)') % 8734 in decimal % Feedback for user : increasing MAXINT,... could mean ProB can find a solution; However, increasing TIMEOUT value will not help |
260 | | ; Result = virtual_time_out(_) -> Value = e('?(\x221E\)') % infinity symbol: Feedback to the user : probably no way to solve the issue apart from ensuring that set comprehensions are finite ... |
261 | | ; Value = e(timeout)) |
262 | | ). |
263 | | |
264 | | % compute a local timeout based on how long the bv_get_values command has been running thus far: |
265 | | get_local_formula_timeout(DefaultTimeout,TimerSinceStart,FormulaTimeout) :- |
266 | | get_elapsed_runtime(TimerSinceStart,Delta), |
267 | | (Delta > 2*DefaultTimeout % then reduce timeout |
268 | | -> Factor is Delta / DefaultTimeout, |
269 | | debug_format(19,'Reducing timeout by factor of ~w (runtime thus far: ~w, default timeout: ~w)~n',[Factor,Delta,DefaultTimeout]), |
270 | | FormulaTimeout is integer(DefaultTimeout / Factor) |
271 | | ; FormulaTimeout=DefaultTimeout). |
272 | | |
273 | | bv_get_values2([],_,_,_,_,[]). |
274 | | bv_get_values2([Id|Irest],State,StateId,Timeout,TimerSinceStart,[Value|Vrest]) :- |
275 | | get_local_formula_timeout(Timeout,TimerSinceStart,FormulaTimeout), |
276 | | bv_get_value(Id,State,StateId,FormulaTimeout,Value), |
277 | | bv_get_values2(Irest,State,StateId,Timeout,TimerSinceStart,Vrest). |
278 | | |
279 | | bv_get_value(Id,State1,StateId,Timeout,FinalValue) :- |
280 | | bv_get_value_unprocessed(Id,State1,StateId,Timeout,Value), |
281 | | value_post_processing(Value,FinalValue). |
282 | | bv_get_value_unprocessed(Id,State1,StateId,Timeout,Value) :- |
283 | | is_active(Id,StateId,State1,State,LocalState),!, %print(is_active(Id)), debug:nl_time, |
284 | | ( is_cached(Id,StateId,State1,Value1) -> |
285 | | FromCache = true |
286 | | ; bv_get_value1(Id,StateId,State,LocalState,Timeout,Value1) -> |
287 | | FromCache = false %, print(evaluated),debug:nl_time |
288 | | ; |
289 | | Value1 = e('evaluation failed'), |
290 | | FromCache = false), |
291 | | handle_errors(Value1,Value), |
292 | | (FromCache==false, should_be_cached(Id) -> write_to_cache(Id,StateId,State1,Value) ; true). |
293 | | bv_get_value_unprocessed(_Id,_State1,_StateId,_Timeout,i). % INACTIVE |
294 | | |
295 | | bv_get_value1(Id,StateId,State,LocalState,Timeout,Value) :- |
296 | | stored_formula(Id,Formula), |
297 | | bv_get_value2(Formula,Id,StateId,State,LocalState,Timeout,Value). |
298 | | |
299 | | bv_get_value2(Formula,Id,_,State,LocalState,Timeout,Value) :- |
300 | | is_texpr(Formula),!, |
301 | | get_texpr_type(Formula,Type), |
302 | | bv_get_texpr_value3(Type,Id,Formula,LocalState,State,Timeout,Value). |
303 | | bv_get_value2(named_subformula(_,Formula,Error),Id,StateId,State,LocalState,Timeout,Value) :- !, |
304 | | (Error='$no_error' -> bv_get_value2(Formula,Id,StateId,State,LocalState,Timeout,Value) |
305 | | ; Value = e(Error)). |
306 | | bv_get_value2(bind(_ID,Value),_,_,_,_,_,btvalue(Value)). |
307 | | bv_get_value2(textnode(Value,_),_,_,_State,_LS,_,v(Value)). |
308 | | bv_get_value2(textnode3(_,Value,_),_,_,_State,_LS,_,ResValue) :- |
309 | | (color_based_on_value(Value,_) -> ResValue = Value % already using encoding |
310 | | ; ResValue = v(Value)). |
311 | | %bv_get_value2(cbc_path(_LastStateID,Path,_Last),_,_,_State,_LS,_,v(NrOfPaths)) :- |
312 | | % append(Path,_,Prefix), |
313 | | % findall(Last,sap:cb_path(_,Prefix,Last),AllPathsWithPrefix), |
314 | | % length(AllPathsWithPrefix,NrOfPaths). |
315 | | bv_get_value2(variant(_Name,_ConvOrAnt,Variant),Id,StateId,State,LocalState,Timeout,Value) :- !, |
316 | | bv_get_value2(Variant,Id,StateId,State,LocalState,Timeout,Value). |
317 | | bv_get_value2(ltl_named_formula(_Name,String),_Id,_StateId,_,_LocalState,_Timeout,Value) :- !, |
318 | | strip_newlines(String,String2), Value=v(String2). |
319 | | bv_get_value2(ltl_formula(_,Tree),_Id,StateId,_,_LocalState,_Timeout,Value) :- !, |
320 | | (is_atomic_ltl_property(Tree) -> |
321 | | (check_atomic_property_formula(Tree,StateId) -> Value = p(true) ; Value=p(false)) |
322 | | ; Value = v('-')). % TO DO: we could evaluate the formulas on back and forward history; ap(enabled(E)) |
323 | | bv_get_value2(guard(_Name,Parameters,Guard),Id,StateId,State,LocalState,Timeout,Value) :- !, |
324 | | get_guard_formula(Parameters,Guard,Expr), |
325 | | bv_get_value2(Expr,Id,StateId,State,LocalState,Timeout,Value). |
326 | | bv_get_value2(guard_theorems(_Name,Parameters,Guard,Theorems),FID,StateId,State,LocalState,Timeout,Value) :- !, |
327 | | get_guard_theorems_formula(Parameters,Guard,Theorems,Expr), |
328 | | bv_get_value2(Expr,FID,StateId,State,LocalState,Timeout,Value). |
329 | | bv_get_value2(raw_state_pp,_,_,State,_LS,_,v(Value)) :- !, % raw pretty printed stated |
330 | | translate_any_state(State,Value). |
331 | | bv_get_value2(property_pp(Nr),_,_,State,_LS,_,v(Value)) :- !, % xtl or csp properties |
332 | | get_specfile_property(State,Nr,Value). |
333 | | bv_get_value2(Node,_,_,_State,_LS,_,e(unknown)) :- |
334 | | format('Unknown bvisual2 node: ~w~n',[Node]). |
335 | | |
336 | | |
337 | | :- dynamic specfile_property_cache/2, specfile_property_cached_state/1. |
338 | | get_specfile_property(State,Nr,PVal) :- recompute_specfile_property_cache(State), |
339 | | specfile_property_cache(Nr,PVal). |
340 | | |
341 | | recompute_specfile_property_cache(State) :- \+ specfile_property_cached_state(State), |
342 | | retractall(specfile_property_cached_state(_)), |
343 | | assert(specfile_property_cached_state(State)), |
344 | | retractall(specfile_property_cache(_,_)), |
345 | | findall(P,specfile:property(State,P),List), |
346 | | is_property_atom(_Atom,Nr), |
347 | | nth1(Nr,List,PVal), |
348 | | write_to_codes(PVal,C), atom_codes(Value,C), |
349 | | assert(specfile_property_cache(Nr,Value)),fail. |
350 | | recompute_specfile_property_cache(_). |
351 | | |
352 | | |
353 | | |
354 | | bv_get_texpr_value3(pred,Id,Formula,LocalState,State,Timeout,Value) :- |
355 | | !, |
356 | | % print('CHECKING PREDICATE: '), translate:print_bexpr(Formula),nl, |
357 | | CS = 'state view table', |
358 | | (bv_time_out_call(b_test_boolean_expression_for_ground_state(Formula,LocalState,State,CS,Id),true,Timeout,ValuePos) -> true ; ValuePos=false), |
359 | | ( get_preference(double_evaluation_when_analysing,true) -> |
360 | | CS2 = 'state view table (negated)', |
361 | | (bv_time_out_call(b_not_test_boolean_expression_cs(Formula,LocalState,State,CS2,Id),true,Timeout,ValueNeg) |
362 | | -> true ; ValueNeg=false), |
363 | | combine_predicate_values(ValuePos,ValueNeg,Value) |
364 | | ; encode_predicate_value(ValuePos,Value)). |
365 | | bv_get_texpr_value3(subst,_Id,Formula,LocalState,State,Timeout,Res) :- !, |
366 | | (bv_time_out_call(b_execute_statement_nowf(Formula,LocalState,State,OutState,prob_command_context), |
367 | | OutState,Timeout,Value) |
368 | | -> ( Value = e(E) -> Res = e(E) % e for exception or timeout |
369 | | ; Res = btstate(Value) |
370 | | ) |
371 | | ; Res = e(infeasible) |
372 | | ). |
373 | | bv_get_texpr_value3(_,Id,Formula,LocalState,State,Timeout,Res) :- |
374 | | CS = 'state view table', |
375 | | (bv_time_out_call(b_compute_expression_nowf(Formula,LocalState,State,FValue,CS,Id),FValue,Timeout,Value) |
376 | | -> ( Value = e(E) -> Res = e(E) % e for exception or timeout |
377 | | ; Res = btvalue(Value,Formula) |
378 | | ) |
379 | | ; texpr_contains_wd_condition(Formula) -> Res = e(undefined) |
380 | | ). |
381 | | |
382 | | |
383 | | |
384 | | encode_predicate_value(e(Error),e(Error)). |
385 | | encode_predicate_value(bv_info(Error),bv_info(Error)). |
386 | | encode_predicate_value(true,p(true)). |
387 | | encode_predicate_value(false,p(false)). |
388 | | combine_predicate_values(e(_Error),true,p(false)) :- |
389 | | print('### Ignoring Timeout in Positive Case of DOUBLE_EVALUATION as Negated Predicate is TRUE'),nl. |
390 | | combine_predicate_values(e(_Error),false,p(true)) :- |
391 | | print('### Ignoring Timeout in Positive Case of DOUBLE_EVALUATION as Negated Predicate is FALSE'),nl. |
392 | | combine_predicate_values(e(Error),e(_),e(Error)). |
393 | | combine_predicate_values(true,false,p(true)). |
394 | | combine_predicate_values(false,true,p(false)). |
395 | | combine_predicate_values(true,true,e('both true and false')). |
396 | | combine_predicate_values(false,false,e(undefined)). |
397 | | combine_predicate_values(true,e(_Error),p(true)) :- |
398 | | print('### Ignoring Timeout in Negative Case of DOUBLE_EVALUATION'),nl. |
399 | | combine_predicate_values(false,e(_Error),p(false)) :- |
400 | | print('### Ignoring Timeout in Negative Case of DOUBLE_EVALUATION'),nl. |
401 | | |
402 | | :- dynamic get_unlimited_value/0. |
403 | | |
404 | | |
405 | | value_post_processing(In,Out) :- |
406 | | with_bvisual2_translation_mode( |
407 | | (value_post_processing2(In,O) -> O=Out |
408 | | ; Out=e('internal error: failed to post-process value'))). |
409 | | value_post_processing2(v(Value),v(Value)). |
410 | | value_post_processing2(p(Value),p(Value)). |
411 | | value_post_processing2(e(Error),e(Error)). |
412 | | value_post_processing2(i,i). |
413 | | value_post_processing2(bv_info(I),bv_info(I)). |
414 | | value_post_processing2(btvalue(BValue,Expr),v(Value)) :- |
415 | | (get_unlimited_value -> translate_bvalue_for_expression(BValue,Expr,Value) |
416 | | ; translate_bvalue_for_expression_with_limit(BValue,Expr,600,Value) % one can always use bv_get_value_unlimited |
417 | | ). |
418 | | value_post_processing2(btvalue(BValue),v(Value)) :- |
419 | | % TO DO: get type for variables and constants |
420 | | (get_unlimited_value -> translate_bvalue(BValue,Value) |
421 | | ; translate_bvalue_with_type_and_limit(BValue,any,600,Value)). |
422 | | value_post_processing2(btstate(Updates),v(Value)) :- |
423 | | (Updates=[] -> Value='skip' |
424 | | ; get_unlimited_value -> translate_b_state_to_comma_list(Updates,100000,Value) % TODO: not unlimited |
425 | | ; translate_b_state_to_comma_list(Updates,600,Value)). |
426 | | |
427 | | |
428 | | |
429 | | |
430 | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
431 | | % caching of some values |
432 | | :- use_module(probsrc(store),[no_value_for_variable/2]). |
433 | | |
434 | | % we do not compute the theorems node, only its subnodes |
435 | | is_cached(theoremsc,_,_,v('')) :- !. |
436 | | is_cached(theoremscm,_,_,v('')) :- !. |
437 | | is_cached(theoremsv,_,_,v('')) :- !. |
438 | | is_cached(theoremsvm,_,_,v('')) :- !. |
439 | | is_cached(goal,_,_,v('')) :- !. |
440 | | % we use the invariant_violated flag of the state space as a kind of cache |
441 | | is_cached(inv,StateId,_State,Value) :- |
442 | | \+ invariant_not_yet_checked(StateId), |
443 | | (invariant_violated(StateId) -> Value=p(false) ; Value=p(true)). |
444 | | % axioms are usually true in the constants' state |
445 | | is_cached(axioms,StateId,concrete_constants(State),R) :- !, |
446 | | is_cached_constants_state(StateId,State,R). |
447 | | is_cached(axioms,StateId,[_|_],R) :- !, % states consisting of just a list are either constructed by |
448 | | % find valid state, state-based MC,... or when there are no constants |
449 | | % We assume PROPERTIES/axioms to be true; by constructing these commands have to satisfy the properties |
450 | | is_cached_constants_state(StateId,[],R). |
451 | | % this formula was already computed and cached for the given state |
452 | | is_cached(FormulaId,StateId,_State,Value) :- |
453 | | formula_cache(FormulaId,StateId,Value),!. |
454 | | % in case of axiom, we can look at the reverences constants' state |
455 | | is_cached(FormulaId,_,expanded_const_and_vars(ConstId,_,_,_),Value) :- is_cached_axiom(FormulaId,ConstId,Value). |
456 | | is_cached(FormulaId,_,const_and_vars(ConstId,_),Value) :- is_cached_axiom(FormulaId,ConstId,Value). |
457 | | is_cached_axiom(FormulaId,ConstId,Value) :- |
458 | | is_axiom_or_static_theorem(FormulaId), |
459 | | visited_expression(ConstId,ConstState), |
460 | | % we could avoid unpacking, but constants state are not packed anyway; full value is only used for partial_setup_constants below; TO DO avoid extracting ConstState |
461 | | is_cached(FormulaId,ConstId,ConstState,Value),!. |
462 | | |
463 | | is_cached_constants_state(StateId,State,R) :- |
464 | | % only if a partial_setup_constants event led to that |
465 | | % state, then something did not work |
466 | | ( transition(root,'$partial_setup_constants',StateId) -> |
467 | | (member(bind(_,Val),State), no_value_for_variable(Val,_) |
468 | | -> R = e('some constants have no values') |
469 | | ; properties_were_filtered(Nr), Nr>0 |
470 | | -> get_node_label(axioms,Axioms), |
471 | | ajoin(['some ',Axioms, ' (',Nr,') were ignored'],Msg), R = e(Msg) |
472 | | ; animation_minor_mode(eventb) -> R = e('some axioms may be false') |
473 | | ; R = e('some properties may be false') |
474 | | ) |
475 | | ; R = p(true)). |
476 | | |
477 | | should_be_cached(FormulaId) :- |
478 | | is_axiom_or_static_theorem(FormulaId). |
479 | | |
480 | | write_to_cache(FormulaId,_StateId,const_and_vars(ConstId,_),Value) :- |
481 | | is_axiom_or_static_theorem(FormulaId),!, |
482 | | visited_expression(ConstId,ConstState), |
483 | | write_to_cache(FormulaId,ConstId,ConstState,Value). |
484 | | write_to_cache(FormulaId,StateId,_State,Value) :- |
485 | | assertz(formula_cache(FormulaId,StateId,Value)). |
486 | | |
487 | | is_axiom_or_static_theorem(axioms) :- !. |
488 | | is_axiom_or_static_theorem(theoremsc) :- !. |
489 | | is_axiom_or_static_theorem(theoremscm) :- !. |
490 | | is_axiom_or_static_theorem(FormulaId) :- |
491 | | supernode(FormulaId,Parent),is_axiom_or_static_theorem(Parent). |
492 | | |
493 | | :- use_module(probsrc(tools_strings),[atom_codes_with_limit/3]). |
494 | | handle_errors(_,e(ErrorMsg)) :- |
495 | | get_all_errors_and_clear([Error|_]),!, % TO DO: use proper error scoping and do not trigger when error stored before calling bvisual2 |
496 | | write_to_codes(Error,ErrorCodes), |
497 | | atom_codes_with_limit(ErrorMsg,200,ErrorCodes). |
498 | | handle_errors(Value,Value). |
499 | | |
500 | | |
501 | | % is_active(+FormulaID,+InState,-PossiblyExpandedState) |
502 | | % says if a FormulaID makes sense for the current state, if not: it will be grayed out |
503 | | is_active(user,StateId,InState,OutState,LocalState) :- !, |
504 | | is_active(inv,StateId,InState,OutState,LocalState). |
505 | | is_active(inv,_StateId,InState,OutState,LocalState) :- !, |
506 | | empty_state(LocalState), |
507 | | state_corresponds_to_initialised_b_machine(InState,OutState). |
508 | | is_active(axioms,_StateId,InState,OutState,LocalState) :- !, |
509 | | InState \= root, |
510 | | empty_state(LocalState), |
511 | | state_corresponds_to_set_up_constants(InState,OutState), |
512 | | !. |
513 | | is_active(variants,StateId,InState,OutState,LocalState) :- !, |
514 | | is_active(inv,StateId,InState,OutState,LocalState). |
515 | | is_active(theoremsc,StateId,InState,OutState,LocalState) :- !, |
516 | | is_active(axioms,StateId,InState,OutState,LocalState). |
517 | | is_active(theoremscm,StateId,InState,OutState,LocalState) :- !, |
518 | | is_active(axioms,StateId,InState,OutState,LocalState). |
519 | | is_active(theoremsv,StateId,InState,OutState,LocalState) :- !, |
520 | | is_active(inv,StateId,InState,OutState,LocalState). |
521 | | is_active(theoremsvm,StateId,InState,OutState,LocalState) :- !, |
522 | | is_active(inv,StateId,InState,OutState,LocalState). |
523 | | is_active(guards_top_level,StateId,InState,OutState,LocalState) :- !, |
524 | | is_active(inv,StateId,InState,OutState,LocalState). |
525 | | is_active(guards_subsidiary,StateId,InState,OutState,LocalState) :- !, |
526 | | is_active(inv,StateId,InState,OutState,LocalState). |
527 | | is_active(guard_theorems,StateId,InState,OutState,LocalState) :- !, |
528 | | is_active(inv,StateId,InState,OutState,LocalState). |
529 | | is_active(variables,StateId,InState,OutState,LocalState) :- !, |
530 | | is_active(inv,StateId,InState,OutState,LocalState). |
531 | | is_active(constants,StateId,InState,OutState,LocalState) :- !, |
532 | | is_active(axioms,StateId,InState,OutState,LocalState). |
533 | | is_active(sets,_StateId,InState,OutState,LocalState) :- !, b_or_z_successsful_mode, |
534 | | empty_state(LocalState), InState=OutState. |
535 | | is_active(freetypes,_StateId,InState,OutState,LocalState) :- !, |
536 | | empty_state(LocalState), InState=OutState. |
537 | | is_active(goal,StateId,InState,OutState,LocalState) :- !, |
538 | | is_active(inv,StateId,InState,OutState,LocalState). |
539 | | is_active(user_formulas,StateId,InState,OutState,LocalState) :- !, |
540 | | is_active(inv,StateId,InState,OutState,LocalState). |
541 | | is_active(definitions,StateId,InState,OutState,LocalState) :- !, |
542 | | is_active(inv,StateId,InState,OutState,LocalState). |
543 | | is_active(ltl_formulas,StateId,InState,OutState,LocalState) :- !, |
544 | | is_active(inv,StateId,InState,OutState,LocalState). |
545 | | is_active(channels,_StateId,S,OutState,LocalState) :- !, |
546 | | csp_mode, OutState=S,empty_state(LocalState). |
547 | | is_active(datatypes,_StateId,S,OutState,LocalState) :- !, |
548 | | csp_mode, OutState=S,empty_state(LocalState). |
549 | | is_active(subtypes,_StateId,S,OutState,LocalState) :- !, |
550 | | csp_mode, OutState=S,empty_state(LocalState). |
551 | | is_active(raw_state,_StateId,S,OutState,LocalState) :- !, |
552 | | \+ b_or_z_mode, % maybe we should extract it for csp_and_b ? |
553 | | OutState=S,empty_state(LocalState). |
554 | | %is_active(cbc_tests,_StateId,_InState,_OutState,_LocalState) :- !, |
555 | | % sap:cb_path(_,[_],_). % show cbc_tests if we ran CBC test-case generator |
556 | | is_active(Atom,_StateId,S,OutState,LocalState) :- is_property_atom(Atom,Nr),!, |
557 | | get_specfile_property(S,Nr,_), |
558 | | OutState=S,empty_state(LocalState). |
559 | | is_active(NodeId,StateId,InState,OutState,LocalState) :- |
560 | | supernode(NodeId,Super), |
561 | | is_active(Super,StateId,InState,OutState,InLocalState), |
562 | | % check if the parent node introduces example values (e.g. in a exists-clause) |
563 | | % If yes, the local state is extended by the values |
564 | | ( example_node(Super) -> |
565 | | find_example(Super,StateId,OutState,InLocalState,LocalState) |
566 | | ; |
567 | | InLocalState = LocalState). |
568 | | |
569 | | find_example(NodeId,StateId,_State,_InLocalState,LocalState) :- |
570 | | % check if the value was computed and cached before |
571 | | local_state(NodeId,StateId,Result),!, |
572 | | % if Result is not of the form example/1, no example |
573 | | % was found. Just fail to show inactive state |
574 | | Result = example(LocalState). |
575 | | find_example(NodeId,StateId,State,InLocalState,LocalState) :- |
576 | | % how the example is computed depends on the expression (e.g. exists) |
577 | | % and the outcome of the parent node (true or false) |
578 | | bv_get_values([NodeId],StateId,[V]),!, |
579 | | stored_formula(NodeId,Formula), |
580 | | ( find_example1(Formula,V,State,InLocalState,LocalState) -> |
581 | | Result = example(LocalState) |
582 | | ; |
583 | | Result = not_found), |
584 | | % currently we just ignore errors |
585 | | handle_errors(_,_), |
586 | | assertz( local_state(NodeId,StateId,Result) ), |
587 | | Result = example(_). |
588 | | find_example1(TExpr,V,State,InLocalState,LocalState) :- |
589 | | is_texpr(TExpr),!, |
590 | | get_texpr_expr(TExpr,Expr), |
591 | | find_example2(Expr,V,State,InLocalState,LocalState). |
592 | | find_example1(guard(_Name,Parameters,Guard),V,State,InLocalState,LocalState) :- |
593 | | create_or_merge_exists(Parameters,Guard,Exists), |
594 | | find_example1(Exists,V,State,InLocalState,LocalState). |
595 | | find_example1(guard_theorems(_Name,Parameters,Guard,Theorems),V,State,InLocalState,LocalState) :- |
596 | | create_forall(Parameters,b(implication(Guard,Theorems),pred,[]),ForAll), |
597 | | find_example1(ForAll,V,State,InLocalState,LocalState). |
598 | | find_example2(let_predicate(Ids,AssignmentExprs,Pred),Status,State,InLocalState,LocalState) :- |
599 | | % translate LET back to exists |
600 | | create_exists_for_let(Ids,AssignmentExprs,Pred,_,ExistsPred), |
601 | | find_example2(exists(Ids,ExistsPred),Status,State,InLocalState,LocalState). |
602 | | find_example2(let_expression(Ids,AssignmentExprs,_Expr),_Status,State,InLocalState,LocalState) :- |
603 | | % translate LET expression to exists to find solution for assignments |
604 | | % _Status is typically v(Value) |
605 | | create_exists_for_let(Ids,AssignmentExprs,b(truth,pred,[]),_,ExistsPred), |
606 | | find_example2(exists(Ids,ExistsPred),p(true),State,InLocalState,LocalState). |
607 | | find_example2(exists(Ids,Predicate),p(true),State,InLocalState,LocalState) :- |
608 | | find_solution_for_predicate(Ids,Predicate,State,InLocalState,LocalState). |
609 | | find_example2(exists(Ids,Predicate),p(false),State,InLocalState,LocalState) :- |
610 | | Predicate = b(conjunct(_,_),pred,_), % we have a false conjunct: try and find maximal prefix that is satisfiable |
611 | | conjunction_to_list(Predicate,PredList), |
612 | | maxsat_conjunct(Ids,PredList,[],State,InLocalState,no_solution,LocalState), |
613 | | LocalState \= no_solution, |
614 | | !. |
615 | | find_example2(exists(Ids,Predicate),p(false),State,InLocalState,LocalState) :- |
616 | | safe_create_texpr(negation(Predicate),pred,Negation), |
617 | | find_solution_for_predicate(Ids,Negation,State,InLocalState,LocalState). |
618 | | find_example2(forall(Ids,Pre,Condition),p(false),State,InLocalState,LocalState) :- |
619 | | safe_create_texpr(negation(Condition),pred,Negation), |
620 | | conjunct_predicates([Pre,Negation],Predicate), |
621 | | find_solution_for_predicate(Ids,Predicate,State,InLocalState,LocalState). |
622 | | find_example2(forall(Ids,Pre,Condition),p(true),State,InLocalState,LocalState) :- |
623 | | conjunct_predicates([Pre,Condition],Predicate), |
624 | | find_solution_for_predicate(Ids,Predicate,State,InLocalState,LocalState), |
625 | | !. |
626 | | find_example2(forall(Ids,Pre,_),p(true),State,InLocalState,LocalState) :- |
627 | | % the LHS of the forall is never true; try find maximal subsequence for it: |
628 | | find_example2(exists(Ids,Pre),p(false),State,InLocalState,LocalState). |
629 | | find_example2(comprehension_set(Ids,Predicate),v(VS),State,InLocalState,LocalState) :- |
630 | | (empty_val_str(VS) -> PVal=false ; PVal=true), |
631 | | find_example2(exists(Ids,Predicate),p(PVal),State,InLocalState,LocalState). |
632 | | empty_val_str(VS) :- (VS = '{}' -> true ; atom(VS),atom_codes(VS,[8709])). % unicode empty set |
633 | | |
634 | | find_solution_for_predicate(Ids,Predicate,State,InLocalState,NormedLocalState) :- |
635 | | get_preference(time_out,Timeout), |
636 | | set_up_typed_localstate(Ids,_FreshVars,TypedVals,InLocalState,LocalState,positive), |
637 | | (time_out_with_enum_warning_one_solution( |
638 | | (init_wait_flags_with_call_stack(WF,[prob_command_context(find_solution_for_predicate,unknown)]), |
639 | | b_tighter_enumerate_values_in_ctxt(TypedVals,Predicate,WF), |
640 | | b_test_boolean_expression(Predicate,LocalState,State,WF), |
641 | | ground_wait_flags(WF)), |
642 | | Timeout,Result) |
643 | | -> Result == success, |
644 | | normalise_store(LocalState,NormedLocalState) |
645 | | ). |
646 | | |
647 | | create_exists_for_let(Ids,AssignmentExprs,Pred,Equalities,ExistsPred) :- |
648 | | maplist(create_equality,Ids,AssignmentExprs,Equalities), |
649 | | append(Equalities,[Pred],L), |
650 | | conjunct_predicates(L,ExistsPred). |
651 | | |
652 | | create_equality(ID,Expr,Equality) :- |
653 | | safe_create_texpr(equal(ID,Expr),pred,Equality). |
654 | | |
655 | | % find maximal subsequence of conjuncts that are satisfiable and return LocalState solution found |
656 | | maxsat_conjunct(Ids,[LHS|Rest],ConSoFar,State,InLocalState,_BestLocalStateSoFar,ResLocalState) :- |
657 | | append(ConSoFar,[LHS],NewConjunctList), |
658 | | %print('TRY: '), translate:print_bexpr(LHS),nl, |
659 | | conjunct_predicates(NewConjunctList,NewConjunct), |
660 | | find_solution_for_predicate(Ids,NewConjunct,State,InLocalState,LocalState), |
661 | | !, % print('+'), |
662 | | maxsat_conjunct(Ids,Rest,NewConjunctList,State,InLocalState, LocalState,ResLocalState). |
663 | | maxsat_conjunct(Ids,[_|Rest],ConSoFar,State,InLocalState,BestLocalStateSoFar,Res) :- !, % allows skipping conjuncts |
664 | | maxsat_conjunct(Ids,Rest,ConSoFar,State,InLocalState,BestLocalStateSoFar,Res). |
665 | | maxsat_conjunct(_Ids,_Rest,_ConSoFar,_State,_InLocalState,BestLocalStateSoFar,Res) :- |
666 | | Res = BestLocalStateSoFar. |
667 | | |
668 | | explore_node(Id,Children) :- |
669 | | stored_formula(Id,Formula), |
670 | | check_if_example_node(Id,Formula), |
671 | | get_subformulas(Formula,Subs,Kind), |
672 | | assertz( expanded(Id) ), |
673 | | (Kind = explanation(Operator) |
674 | | -> assert_as_explanation(Id,ExplId,Operator), Children = [ExplId|Children1], |
675 | | register_formulas(Subs,Id,Children1) |
676 | | ; register_formulas(Subs,Id,Children)). |
677 | | |
678 | | assert_as_explanation(Parent,Id,Operator) :- |
679 | | assertz(explanation_parent(Parent)), |
680 | | % add a text line; showing that we did an equivalence rewrite |
681 | | get_new_id(Id), |
682 | | assertz( stored_formula(Id,textnode3('\x21D4\',bv_info(Operator),[])) ), % unicode translation |
683 | | assertz( subnode(Parent,Id) ), |
684 | | assertz( supernode(Id,Parent) ). |
685 | | |
686 | | bv_is_explanation_node(NodeId) :- |
687 | | supernode(NodeId,ParentId), |
688 | | explanation_parent(ParentId). |
689 | | |
690 | | % the following predicates determine whether the node introduces |
691 | | % example values and stores that information in example_node/1. |
692 | | check_if_example_node(Id,Formula) :- |
693 | | is_example_node(Formula),!, |
694 | | assertz( example_node(Id) ). |
695 | | check_if_example_node(_Id,_Formula). |
696 | | is_example_node(TFormula) :- |
697 | | is_texpr(TFormula),!, |
698 | | get_texpr_expr(TFormula,Formula), |
699 | | is_example_node2(Formula). |
700 | | is_example_node(guard(_Name,[_|_],_Guard)). |
701 | | is_example_node(guard_theorems(_Name,[_|_],_Guard,_Theorems)). |
702 | | is_example_node2(exists(_Ids,_Cond)). |
703 | | is_example_node2(forall(_Ids,_Pre,_Cond)). |
704 | | is_example_node2(let_predicate(_Ids,_E,_Cond)). |
705 | | is_example_node2(let_expression(_Ids,_E,_Cond)). |
706 | | is_example_node2(comprehension_set(_Ids,_Cond)). |
707 | | |
708 | | % subformula_rule/4 defines wich subformulas should be |
709 | | % shown in an evaluation tree for a formula. If no |
710 | | % rule matches, the standard subformulas are used |
711 | | subformula_rule(forall(Ids,P,R),_,Subs,quantifier) :- |
712 | | append(Ids,[P,R],Subs). |
713 | | subformula_rule(let_predicate(Ids,AssignmentExprs,Pred),_,Subs,quantifier) :- |
714 | | % see create_exists_for_let(Ids,AssignmentExprs,Pred,Equalities,_ExistsPred), |
715 | | maplist(create_equality,Ids,AssignmentExprs,Equalities), |
716 | | append(Equalities,[Pred],EP), % show equalities and then one subnode for the predicate |
717 | | append(Ids,EP,Subs). |
718 | | subformula_rule(exists(Ids,P),_,Subs,quantifier) :- |
719 | | conjunction_to_list(P,PL), |
720 | | append(Ids,PL,Subs). |
721 | | subformula_rule(comprehension_set(Ids,P),_,Subs,quantifier) :- |
722 | | conjunction_to_list(P,PL), |
723 | | append(Ids,PL,Subs). |
724 | | subformula_rule(conjunct(A,B),_,Subs,normal) :- |
725 | | safe_create_texpr(conjunct(A,B),pred,E), |
726 | | conjunction_to_list(E,Subs). |
727 | | subformula_rule(disjunct(A,B),_,Subs,normal) :- |
728 | | disjunction_to_list(A,B,Subs). |
729 | | subformula_rule(let_expression(Ids,AssignmentExprs,Expr),_,Subs,quantifier) :- |
730 | | maplist(create_equality,Ids,AssignmentExprs,Equalities), |
731 | | append(Equalities,[Expr],EP), % show equalities and then one subnode for the expression |
732 | | append(Ids,EP,Subs). |
733 | | subformula_rule(Formula,TFormula,Subs,Kind) :- |
734 | | get_preference(show_bvisual_formula_explanations,true), |
735 | | subformula_explanation_rule(Formula,TFormula,Subs,Kind). |
736 | | |
737 | | subformula_explanation_rule(equal(A,B),TF,[Sub1,Sub2],explanation(equal)) :- |
738 | | get_texpr_type(A,T),T=set(SType), |
739 | | \+ (kernel_objects:max_cardinality(SType,Max),number(Max),Max<10), % sets can never be very large |
740 | | is_not_bvexpr(TF), % do not apply to explanation expressions |
741 | | no_empty_set(A),no_empty_set(B), |
742 | | !, |
743 | | create_bvexpr(set_subtraction(A,B),T,AminusB), |
744 | | create_bvexpr(set_subtraction(B,A),T,BminusA), |
745 | | create_bvexpr(empty_set,T,Empty), |
746 | | create_bvexpr(equal(AminusB,Empty),pred,Sub1), |
747 | | create_bvexpr(equal(BminusA,Empty),pred,Sub2). |
748 | | subformula_explanation_rule(subset(A,B),_,[Equals],explanation(subset)) :- |
749 | | subset_rule(A,B,Equals). |
750 | | subformula_explanation_rule(subset_strict(A,B),_,[AmBEmpty,NotEquals],explanation(subset_strict)) :- |
751 | | subset_rule(A,B,AmBEmpty), |
752 | | get_texpr_type(A,T), |
753 | | create_bvexpr(set_subtraction(B,A),T,BminusA), |
754 | | create_bvexpr(empty_set,T,Empty), |
755 | | create_bvexpr(not_equal(BminusA,Empty),pred,NotEquals). |
756 | | subformula_explanation_rule(not_subset(A,B),_,Subs,Kind) :- |
757 | | subformula_explanation_rule(subset(A,B),_,Subs,Kind). % it is an equivalent rewrite to the negation |
758 | | subformula_explanation_rule(not_subset_strict(A,B),_,Subs,Kind) :- |
759 | | subformula_explanation_rule(subset_strict(A,B),_,Subs,Kind). % it is an equivalent rewrite to the negation |
760 | | subformula_explanation_rule(member(TM,TS),_,Children,explanation(Func)) :- |
761 | | get_texpr_expr(TS,S), |
762 | | subformula_member_rule(S,TM,TS,Children),!, |
763 | | functor(S,Func,_). |
764 | | |
765 | | subset_rule(A,B,Equals) :- % A<:B <=> A\B = {} |
766 | | get_texpr_type(A,T), |
767 | | create_bvexpr(set_subtraction(A,B),T,AminusB), |
768 | | create_bvexpr(empty_set,T,Empty), |
769 | | create_bvexpr(equal(AminusB,Empty),pred,Equals1), |
770 | | add_texpr_description(Equals1,'Subset check: find elements in left not in right set',Equals). |
771 | | |
772 | | :- use_module(probsrc(bsyntaxtree),[is_just_type/1,add_texpr_description/3]). |
773 | | |
774 | | subformula_member_rule(partial_function(TDom,TRan),TM,TS,[TDoubles]) :- |
775 | | is_just_type(TDom), |
776 | | is_just_type(TRan), |
777 | | !, |
778 | | % this rule describes the plain function check, without |
779 | | % checking domains |
780 | | texpr_function_type(TS,FunctionType,DomType,RanType), |
781 | | create_texpr(identifier(d),DomType,[],TDomId), |
782 | | create_texpr(identifier(r1),RanType,[],TRanId1), |
783 | | create_texpr(identifier(r2),RanType,[],TRanId2), |
784 | | create_texpr(comprehension_set([TDomId,TRanId1],TExists),FunctionType,[],TDoubles0), |
785 | | % create_exists([TRanId2],TPred,TExists1), % moved below so that used ids can be computed |
786 | | create_texpr(couple(TDomId,TRanId1),couple(DomType,RanType),[],TCouple1), |
787 | | create_texpr(couple(TDomId,TRanId2),couple(DomType,RanType),[],TCouple2), |
788 | | safe_create_texpr(not_equal(TRanId1,TRanId2),pred,Unequal), |
789 | | create_texpr(member(TCouple1,TM),pred,[],TMember1), |
790 | | create_texpr(member(TCouple2,TM),pred,[],TMember2), |
791 | | conjunct_predicates([Unequal,TMember1,TMember2],TPred), |
792 | | create_exists([TRanId2],TPred,TExists1), % now also computes used identifiers; cleanup no longer required ? |
793 | | % This is necessary to register the used identifiers |
794 | | clean_up_pred(TExists1,[],TExists), |
795 | | add_texpr_description(TDoubles0,'Partial function check: find counter-example pairs for functionality',TDoubles). |
796 | | subformula_member_rule(partial_function(TA,TB),TM,TS,[TFunCheck|SetChecks]) :- |
797 | | create_function_check(TM,TS,TFunCheck,TDomain,TRange), |
798 | | create_domain_range_checks(TDomain,TRange,TA,TB,SetChecks). |
799 | | subformula_member_rule(total_function(TA,TB),TM,TS,[TFunCheck|SetChecks]) :- |
800 | | create_function_check(TM,TS,TFunCheck,TDomain,TRange), |
801 | | create_total_domain_range_checks(TDomain,TRange,TA,TB,SetChecks). |
802 | | subformula_member_rule(partial_injection(TA,TB),TM,TS,[TFunCheck,TInjCheck|SetChecks]) :- |
803 | | create_function_check(TM,TS,TFunCheck,TDomain,TRange), |
804 | | create_injection_check(TM,TS,TInjCheck), |
805 | | create_domain_range_checks(TDomain,TRange,TA,TB,SetChecks). |
806 | | subformula_member_rule(total_injection(TA,TB),TM,TS,[TFunCheck,TInjCheck|SetChecks]) :- |
807 | | create_function_check(TM,TS,TFunCheck,TDomain,TRange), |
808 | | create_injection_check(TM,TS,TInjCheck), |
809 | | create_total_domain_range_checks(TDomain,TRange,TA,TB,SetChecks). |
810 | | subformula_member_rule(partial_surjection(TA,TB),TM,TS,Children) :- |
811 | | create_function_check(TM,TS,TFunCheck,TDomain,TRange), |
812 | | create_texpr(equal(TRange,TB),pred,[],TRanCheck), |
813 | | create_optional_subset_check(TDomain,TA,DomChecks), |
814 | | append([TFunCheck|DomChecks],[TRanCheck],Children). |
815 | | subformula_member_rule(total_surjection(TA,TB),TM,TS,[TFunCheck,TDomCheck,TRanCheck]) :- |
816 | | create_function_check(TM,TS,TFunCheck,TDomain,TRange), |
817 | | create_texpr(equal(TDomain,TA),pred,[],TDomCheck), |
818 | | create_texpr(equal(TRange,TB),pred,[],TRanCheck). |
819 | | subformula_member_rule(total_bijection(TA,TB),TM,TS,[TFunCheck,TInjCheck,TDomCheck,TRanCheck]) :- |
820 | | create_function_check(TM,TS,TFunCheck,TDomain,TRange), |
821 | | create_injection_check(TM,TS,TInjCheck), |
822 | | create_texpr(equal(TDomain,TA),pred,[],TDomCheck), |
823 | | create_texpr(equal(TRange,TB),pred,[],TRanCheck). |
824 | | subformula_member_rule(partial_bijection(TA,TB),TM,TS,Children) :- |
825 | | create_function_check(TM,TS,TFunCheck,TDomain,TRange), |
826 | | create_injection_check(TM,TS,TInjCheck), |
827 | | create_optional_subset_check(TDomain,TA,DomChecks), |
828 | | create_texpr(equal(TRange,TB),pred,[],TRanCheck), |
829 | | append([TFunCheck,TInjCheck|DomChecks],[TRanCheck],Children). |
830 | | subformula_member_rule(pow_subset(TA),TM,_TS,[NewCheck]) :- |
831 | | % TM : POW(TA) <=> TM \ TA = {} |
832 | | get_texpr_type(TM,Type), |
833 | | create_bvexpr(set_subtraction(TM,TA),Type,Diff), |
834 | | create_bvexpr(empty_set,Type,Empty), |
835 | | create_bvexpr(equal(Diff,Empty),pred,NewCheck). |
836 | | % TO DO: add rules for <:, <<:, FIN, POW1, FIN1 |
837 | | |
838 | | :- use_module(probsrc(typing_tools),[create_maximal_type_set/2]). |
839 | | |
840 | | create_function_check(TM,TS,TFunCheck,TDomain,TRange) :- |
841 | | texpr_function_type(TS,FunctionType,DomType,RanType), |
842 | | create_maximal_type_set(DomType,TDom), % we could use typeset/0, but requires going through ast_cleanup |
843 | | create_maximal_type_set(RanType,TRan), % ditto |
844 | | create_bvexpr(partial_function(TDom,TRan),set(FunctionType),TFun), |
845 | | create_bvexpr(member(TM,TFun),pred,TFunCheck0), |
846 | | create_bvexpr(domain(TM),set(DomType),TDomain), |
847 | | create_bvexpr(range(TM),set(RanType),TRange), |
848 | | add_texpr_description(TFunCheck0,'Check partial function',TFunCheck). |
849 | | |
850 | | create_domain_range_checks(TDomain,TRange,TA,TB,SetChecks) :- |
851 | | create_optional_subset_check(TDomain,TA,DomCheck), |
852 | | create_optional_subset_check(TRange,TB,RanCheck), |
853 | | append(DomCheck,RanCheck,SetChecks). |
854 | | create_total_domain_range_checks(TDomain,TRange,TA,TB,[TIsTotal|RanCheck]) :- |
855 | | create_texpr(equal(TDomain,TA),pred,[description('Check domain of total function')],TIsTotal), |
856 | | create_optional_subset_check(TRange,TB,RanCheck). |
857 | | create_optional_subset_check(TSubset,TSuperset,Check) :- |
858 | | ( is_just_type(TSuperset) -> |
859 | | Check = [] |
860 | | ; |
861 | | create_texpr(subset(TSubset,TSuperset),pred,[description('Check domain/range of function')],TPred), |
862 | | Check = [TPred]). |
863 | | |
864 | | create_injection_check(TM,TS,TCheckExpr) :- |
865 | | texpr_function_type(TS,FunctionType,DomType,RanType), |
866 | | create_texpr(identifier(d1),DomType,[],TDomId1), |
867 | | create_texpr(identifier(d2),DomType,[],TDomId2), |
868 | | create_texpr(identifier(r1),RanType,[],TRanId), |
869 | | create_texpr(comprehension_set([TDomId1,TRanId],TExists),FunctionType,[bv_function_check(TM)],TCheckExpr), |
870 | | %create_exists([TDomId2],TPred,TExists1), |
871 | | create_texpr(couple(TDomId1,TRanId),couple(DomType,RanType),[],TCouple1), |
872 | | create_texpr(couple(TDomId2,TRanId),couple(DomType,RanType),[],TCouple2), |
873 | | create_texpr(not_equal(TDomId1,TDomId2),pred,[],Unequal), |
874 | | create_texpr(member(TCouple1,TM),pred,[],TMember1), |
875 | | create_texpr(member(TCouple2,TM),pred,[],TMember2), |
876 | | conjunct_predicates([Unequal,TMember1,TMember2],TPred), |
877 | | create_exists([TDomId2],TPred,TExists1), % now also computes used identifiers; cleanup no longer required ? |
878 | | % This is necessary to register the used identifiers |
879 | | clean_up_pred(TExists1,[],TExists2), |
880 | | add_texpr_description(TExists2,'Find counter-example pairs for injectivity',TExists). |
881 | | |
882 | | texpr_function_type(TFun,FunType,DomType,RanType) :- |
883 | | get_texpr_type(TFun,set(FunType)), |
884 | | FunType = set(couple(DomType,RanType)). |
885 | | |
886 | | |
887 | | create_bvexpr(Expr,Type,TExpr) :- |
888 | | create_texpr(Expr,Type,[bvisual],TExpr). |
889 | | is_not_bvexpr(TExpr) :- |
890 | | get_texpr_info(TExpr,Infos),nonmember(bvisual,Infos). |
891 | | %is_bvexpr(TExpr) :- get_texpr_info(TExpr,Infos),memberchk(bvisual,Infos). |
892 | | |
893 | | no_empty_set(E) :- \+ is_empty_set(E). |
894 | | |
895 | | is_empty_set(b(E,_,_)) :- is_empty_set_aux(E). |
896 | | is_empty_set_aux(empty_set). |
897 | | is_empty_set_aux(empty_sequence). |
898 | | is_empty_set_aux(value(X)) :- X==[]. |
899 | | |
900 | | get_subformulas(TFormula,Subs,Kind) :- |
901 | | is_texpr(TFormula), |
902 | | get_texpr_expr(TFormula,Formula), |
903 | | subformula_rule(Formula,TFormula,Subs,Kind),!. |
904 | | get_subformulas(TFormula,Subs,syntaxtraversion) :- |
905 | | is_texpr(TFormula),!, |
906 | | bv_syntaxtraversion(TFormula,Subs). |
907 | | get_subformulas(named_subformula(_,TFormula,_),Subs,Kind) :- !, |
908 | | (get_subformulas(TFormula,TSubs,Kind),TSubs \= [] |
909 | | -> Subs = [TFormula] |
910 | | ; Kind=syntaxtraversion, Subs=[]). |
911 | | get_subformulas(textnode(_,Subs),Subs,textnode) :- !. |
912 | | get_subformulas(textnode3(_,_,Subs),Subs,textnode) :- !. |
913 | | get_subformulas(guard(_Name,Parameters,Guard),Subs,guard) :- !, |
914 | | conjunction_to_list(Guard,GuardSubs), |
915 | | append(Parameters,GuardSubs,Subs). |
916 | | get_subformulas(variant(_Name,_ConvOrAnt,Variant),Subs,variant) :- !, |
917 | | Subs = [Variant]. |
918 | | get_subformulas(ltl_named_formula(_,String),Subs,ltl_formula) :- !, |
919 | | temporal_parser(String,ltl,Formula), |
920 | | Subs = [ltl_formula(String,Formula)]. |
921 | | get_subformulas(ltl_formula(_,Formula),Subs,ltl_formula) :- !, |
922 | | get_bv_ltl_sub_formulas(Formula,Subs). |
923 | | get_subformulas(guard_theorems(_Name,[],_Guard,Theorems),Subs,guard_theorems) :- !, |
924 | | conjunction_to_list(Theorems,Subs). |
925 | | get_subformulas(guard_theorems(_Name,Parameters,Guard,Theorems),Subs,guard_theorems) :- !, |
926 | | append(Parameters,[b(implication(Guard,Theorems),pred,[])],Subs). |
927 | | %get_subformulas(cbc_path(_,Path,_),Subs) :- !, |
928 | | % append(Path,[X],XPath), |
929 | | % findall(cbc_path(LastStateID,XPath,X), sap:cb_path(LastStateID,XPath,_), Subs). |
930 | | get_subformulas(bind(_,_),S,K) :- !,S=[], K=none. |
931 | | get_subformulas(Node,[],none) :- format('No subformulas for ~w~n',[Node]). |
932 | | |
933 | | bv_syntaxtraversion(b(rec(Fields),_,_),Subs) :- |
934 | | maplist(transform_field,Fields,Subs1),!, |
935 | | Subs = Subs1. % Note: there are no new quantified names/identifiers; just field names |
936 | | bv_syntaxtraversion(TFormula,Subs) :- |
937 | | syntaxtraversion(TFormula,_,_,_,Subs1,Names), |
938 | | (Names = [] -> filter_trivial_expressions(Subs1,Subs) ; Subs = []). |
939 | | |
940 | | transform_field(field(Name,TVal),named_subformula(Name,TVal,'$no_error')). |
941 | | |
942 | | :- use_module(probsrc(preferences),[get_prob_application_type/1]). |
943 | | filter_trivial_expressions([],[]). |
944 | | filter_trivial_expressions([TI|Irest],Out) :- |
945 | | get_texpr_expr(TI,I),get_texpr_info(TI,Info), |
946 | | ( get_preference(show_bvisual_formula_functor_from,Lim), Lim>=0 -> Out = [TI|Orest] |
947 | | % only functor shown when expanding; we should show all sub formulas; otherwise it is confusing to the user |
948 | | ; get_prob_application_type(Type), Type \= tcltk -> Out = [TI|Orest] % in ProB2 we always just show the functor now |
949 | | ; is_trivial(I,Info) -> Out = Orest |
950 | | ; Out = [TI|Orest]), |
951 | | filter_trivial_expressions(Irest,Orest). |
952 | | |
953 | | % is_trivial/2 is true for expressions that should not appear as single nodes |
954 | | % in the evaluation tree, because they are too simple. |
955 | | % The first argument is the expression, the second its information list |
956 | | is_trivial(integer(_),_). |
957 | | is_trivial(integer_set(_),_). |
958 | | is_trivial(empty_set,_). |
959 | | is_trivial(boolean_true,_). |
960 | | is_trivial(boolean_false,_). |
961 | | is_trivial(bool_set,_). |
962 | | is_trivial(truth,_). |
963 | | is_trivial(falsity,_). |
964 | | is_trivial(identifier(_),Info) :- |
965 | | memberchk(given_set,Info). |
966 | | is_trivial(identifier(_),Info) :- |
967 | | memberchk(enumerated_set_element,Info). |
968 | | % TO DO: treat value(_) ? |
969 | | |
970 | | :- use_module(probsrc(tools_strings),[ajoin/2]). |
971 | | :- use_module(probsrc(specfile),[animation_minor_mode/1, csp_mode/0, b_or_z_mode/0, |
972 | | get_specification_description/2]). |
973 | | get_node_label(inv,invariants) :- animation_minor_mode(eventb),!. |
974 | | get_node_label(inv,I):- !, get_specification_description(invariant,I). |
975 | | get_node_label(axioms,axioms) :- animation_minor_mode(eventb),!. |
976 | | get_node_label(axioms,S):- !, get_specification_description(properties,S). |
977 | | get_node_label(variants,variants) :- animation_minor_mode(eventb),!. |
978 | | get_node_label(variants,'VARIANT') :- !. % not used there |
979 | | get_node_label(theoremsc,'theorems (on constants)') :- animation_minor_mode(eventb),!. |
980 | | get_node_label(theoremsc,'ASSUME (on constants)') :- animation_minor_mode(tla),!. |
981 | | get_node_label(theoremsc,'ALL ASSERTIONS (on CONSTANTS)') :- b_get_assertion_count(static,AllNr,MainNr), MainNr < AllNr, !. |
982 | | get_node_label(theoremsc,'ASSERTIONS (on CONSTANTS)') :- !. |
983 | | get_node_label(theoremscm,'MAIN ASSERTIONS (on CONSTANTS)') :- !. % should only trigger in B mode at the moment |
984 | | get_node_label(theoremsv,'theorems (on variables)') :- animation_minor_mode(eventb),!. |
985 | | get_node_label(theoremsv,'ALL ASSERTIONS (on VARIABLES)') :- b_get_assertion_count(dynamic,AllNr,MainNr), MainNr < AllNr, !. |
986 | | get_node_label(theoremsv,'ASSERTIONS (on VARIABLES)') :- !. |
987 | | get_node_label(theoremsvm,'MAIN ASSERTIONS (on VARIABLES)') :- !. % should only trigger in B mode at the moment |
988 | | get_node_label(sets,'sets') :- animation_minor_mode(eventb),!. |
989 | | get_node_label(sets,'SETS') :- !. |
990 | | get_node_label(freetypes,'inductive datatypes') :- animation_minor_mode(eventb),!. |
991 | | get_node_label(freetypes,'FREETYPES') :- !. |
992 | | get_node_label(goal,'GOAL') :- !. |
993 | | get_node_label(variables,'variables') :- animation_minor_mode(eventb),!. |
994 | | get_node_label(variables,'VARIABLES') :- !. |
995 | | get_node_label(constants,'constants') :- animation_minor_mode(eventb),!. |
996 | | get_node_label(constants,'CONSTANTS') :- !. |
997 | | get_node_label(guards_top_level,'event guards') :- animation_minor_mode(eventb),!. |
998 | | get_node_label(guards_top_level,'ACTIONS (guards)') :- animation_minor_mode(tla),!. |
999 | | get_node_label(guards_top_level,'OPERATIONS (guards/preconditions)') :- !. % GUARDS/PRE |
1000 | | get_node_label(guards_subsidiary,'subsidiary event guards') :- animation_minor_mode(eventb),!. |
1001 | | get_node_label(guards_subsidiary,'SUBSIDIARY ACTIONS (guards)') :- animation_minor_mode(tla),!. |
1002 | | get_node_label(guards_subsidiary,'SUBSIDIARY OPERATIONS (guards/preconditions)') :- !. % GUARDS/PRE |
1003 | | get_node_label(guard_theorems,'theorems (in guards)') :- !. |
1004 | | get_node_label(user_formulas,'USER FORMULAS') :- !. |
1005 | | get_node_label(definitions,'theory operators') :- animation_minor_mode(eventb),!. |
1006 | | get_node_label(definitions,'DEFINITIONS') :- !. |
1007 | | get_node_label(ltl_formulas,'LTL Formulas') :- !. |
1008 | | %get_node_label(cbc_tests,'CBC_TESTS') :- !. |
1009 | | get_node_label(channels,'channel') :- !. |
1010 | | get_node_label(datatypes,'datatype') :- !. |
1011 | | get_node_label(subtypes,'subtype') :- !. |
1012 | | get_node_label(raw_state,'raw_state') :- !. |
1013 | | get_node_label(Atom,Label) :- is_property_atom(Atom,Nr),!, |
1014 | | (xtl_mode -> ajoin(['xtl_property ',Nr],Label) ; Label='property'). |
1015 | | get_node_label(Id,Label) :- |
1016 | | stored_formula(Id,Formula),!, |
1017 | | get_node_label2(Formula,Label). |
1018 | | get_node_label(Id,'??') :- format('Unknown node: ~w~n',[Id]). |
1019 | | |
1020 | | get_node_label2(textnode(Text,_),Text) :- !. |
1021 | | get_node_label2(textnode3(Text,_,_),Text) :- !. |
1022 | | get_node_label2(bind(TID,_),ID) :- !, |
1023 | | (is_texpr(TID),get_texpr_id(TID,R) -> ID = R ; ID = TID). |
1024 | | get_node_label2(named_subformula(Name,_,_),Res) :- !, Res=Name. |
1025 | | get_node_label2(guard(Name,_Parameters,_Guard),Name) :- !. |
1026 | | get_node_label2(guard_theorems(Name,_Parameters,_Guard,_Theorems),Name) :- !. |
1027 | | get_node_label2(variant(OpName,ConvOrAnt,_Variant),Name) :- !, |
1028 | | ajoin([OpName,' |-> ',ConvOrAnt],Name). |
1029 | | get_node_label2(ltl_named_formula(Name,_),Res) :- !, Res=Name. |
1030 | | get_node_label2(ltl_formula(String,_Tree),Name) :- !, strip_newlines(String,Name). |
1031 | | get_node_label2(TExpr,Label) :- |
1032 | | is_texpr(TExpr),!, |
1033 | | % Mode = unicode, latex or ascii; but unicode_mode makes Viewer slower |
1034 | | with_bvisual2_translation_mode(get_node_label3(TExpr,Label)). |
1035 | | get_node_label2(Term,Label) :- |
1036 | | functor(Term,F,Arity), |
1037 | | ajoin(['unknown node type: ',F,'/',Arity],Label). |
1038 | | |
1039 | | get_node_label3(TExpr,Label) :- |
1040 | | with_bvisual2_translation_mode(translate_subst_or_bexpr_with_limit(TExpr,500,TS)), |
1041 | | ( get_preference(show_bvisual_formula_functor_from,Lim), Lim>=0, |
1042 | | get_texpr_top_level_symbol(TExpr,Functor,_,_OpType), |
1043 | | %(OpType=infix ; OpType=postfix), |
1044 | | (Lim=0 -> true ; atom_length(TS,Len), Len>=Lim) |
1045 | | -> %ajoin([Functor,' \x25AB\ ',TS],Label) % unicode small block / box |
1046 | | ajoin(['[',Functor, '] ',TS],Label0) |
1047 | | ; Label0=TS |
1048 | | ), |
1049 | | (animation_minor_mode(eventb), %maybe in future we also have proof info for Classical B |
1050 | | get_preference(show_bvisual_proof_info_icons,true), |
1051 | | get_discharged_info(TExpr,Proven,_) |
1052 | | -> (Proven=proven -> ajoin(['\x2705\ ',Label0],Label) % alternatives \x2705\ \x2713\ \x2714\ |
1053 | | ; ajoin([' \x25EF\ ',Label0],Label)) % x2B55 |
1054 | | ; Label=Label0). |
1055 | | |
1056 | | |
1057 | | :- dynamic bvisual2_translation_mode/1. |
1058 | | bvisual2_translation_mode(unicode). % any mode accepted by translate:set_translation_mode |
1059 | | set_bvisual2_translation_mode(X) :- retractall(bvisual2_translation_mode(_)), |
1060 | | assertz(bvisual2_translation_mode(X)). |
1061 | | |
1062 | | :- use_module(probsrc(translate), [with_translation_mode/2]). |
1063 | | :- use_module(probsrc(preferences), [temporary_set_preference/3,reset_temporary_preference/2]). |
1064 | | with_bvisual2_translation_mode(Call) :- |
1065 | | bvisual2_translation_mode(Mode), |
1066 | | temporary_set_preference(expand_avl_upto,5000,Chng), |
1067 | | call_cleanup(with_translation_mode(Mode,Call), |
1068 | | reset_temporary_preference(expand_avl_upto,Chng)). |
1069 | | |
1070 | | |
1071 | | register_top_level :- register_top_level(_). |
1072 | | register_top_level(Id) :- |
1073 | ? | top_level2(Id,Formula,Subs), % print(register(Id,Subs)),nl, |
1074 | | register_top_level_formula(Id,Formula,Subs), |
1075 | | fail. |
1076 | | register_top_level(_Id). |
1077 | | |
1078 | | |
1079 | | :- use_module(probsrc(specfile),[b_or_z_mode/0, classical_b_mode/0,spec_file_has_been_successfully_loaded/0]). |
1080 | | :- use_module(probsrc(b_global_sets),[all_elements_of_type/2, b_get_fd_type_bounds/3]). |
1081 | | :- use_module(probsrc(bmachine),[b_get_machine_goal/1]). |
1082 | | b_or_z_successsful_mode :- b_or_z_mode, |
1083 | | true. %spec_file_has_been_successfully_loaded. % make unit test fail |
1084 | | |
1085 | | % top_level2(SectionID, ValueNode, ListOfSubs) |
1086 | | top_level2(variables,textnode('',Variables),Variables) :- b_or_z_successsful_mode, |
1087 | | variables_should_be_included, |
1088 | | b_get_machine_variables_in_original_order(Variables). |
1089 | | top_level2(constants,textnode('',Constants),Constants) :- b_or_z_successsful_mode, |
1090 | | variables_should_be_included, |
1091 | | b_get_machine_constants(Constants). |
1092 | | top_level2(sets,textnode('',Sets),Sets) :- b_or_z_successsful_mode, |
1093 | | findall(bind(S,All), |
1094 | | bv_top_level_set(S,All),Sets), Sets \= []. |
1095 | | top_level2(freetypes,textnode('',Sets),Sets) :- b_or_z_successsful_mode, |
1096 | | findall(All, top_level_freetype(_Set,All),Sets), Sets \= []. |
1097 | | top_level2(goal,Goal,Subs) :- b_or_z_successsful_mode, |
1098 | | b_get_machine_goal(Goal), |
1099 | | conjunction_to_list(Goal,Subs). |
1100 | | top_level2(inv,Invariant,Subs) :- b_or_z_successsful_mode, |
1101 | | get_invariant_list_with_proof_info(Subs), |
1102 | | conjunct_predicates(Subs,Invariant). |
1103 | | top_level2(variants,textnode('',Variants),Variants) :- animation_minor_mode(eventb), |
1104 | | spec_file_has_been_successfully_loaded, |
1105 | | findall(variant(Name,ConvOrAnt,Variant), |
1106 | | b_get_operation_variant(Name,ConvOrAnt,Variant), |
1107 | | Variants), |
1108 | | Variants = [_|_]. |
1109 | | top_level2(axioms,Props,AllSubs) :- b_or_z_successsful_mode, |
1110 | | b_machine_has_constants_or_properties, |
1111 | | b_get_properties_from_machine(Props), |
1112 | | conjunction_to_list(Props,Subs), |
1113 | | findall(AddPred,b_machine_additional_property(AddPred),VSubs), % could be VALUES clause |
1114 | | (VSubs=[] -> AllSubs = Subs ; append(Subs,VSubs,AllSubs)). |
1115 | | top_level2(theoremsc,Pred,Assertions) :- b_or_z_successsful_mode, |
1116 | | b_get_static_assertions_from_machine(Assertions),Assertions\=[], |
1117 | | conjunct_predicates(Assertions,Pred). |
1118 | | top_level2(theoremscm,Pred,Assertions) :- b_or_z_successsful_mode, |
1119 | | b_get_assertions_from_main_machine(static,Assertions), |
1120 | | %Assertions\=[], % in case we have less: show that there are none |
1121 | ? | b_get_assertion_count(static,AllNr,MainNr), MainNr < AllNr, |
1122 | | conjunct_predicates(Assertions,Pred). |
1123 | | top_level2(theoremsv,Pred,Assertions) :- b_or_z_successsful_mode, |
1124 | | b_get_dynamic_assertions_from_machine(Assertions),Assertions\=[], |
1125 | | conjunct_predicates(Assertions,Pred). |
1126 | | top_level2(theoremsvm,Pred,Assertions) :- b_or_z_successsful_mode, |
1127 | | b_get_assertions_from_main_machine(dynamic,Assertions), |
1128 | | %Assertions\=[], % in case we have less: show that there are none |
1129 | | b_get_assertion_count(dynamic,AllNr,MainNr), MainNr < AllNr, |
1130 | | conjunct_predicates(Assertions,Pred). |
1131 | | top_level2(guards_top_level,textnode('',EventGuards),EventGuards) :- b_or_z_successsful_mode, |
1132 | | findall(guard(Name,Params,Guard), |
1133 | | get_top_level_guard(Name,Params,Guard),EventGuards), |
1134 | | EventGuards = [_|_]. |
1135 | | top_level2(guards_subsidiary,textnode('',EventGuards),EventGuards) :- b_or_z_successsful_mode, |
1136 | | findall(guard(Name,Params,Guard), |
1137 | | get_subsidiary_guard(Name,Params,Guard),EventGuards), |
1138 | | EventGuards = [_|_]. |
1139 | | top_level2(guard_theorems,textnode('',EventGuards),EventGuards) :- b_or_z_successsful_mode, |
1140 | | findall(guard_theorems(Name,Params,Guard,GuardTheorems), |
1141 | | ( b_get_machine_operation(Name,_,_,TBody), |
1142 | | get_texpr_expr(TBody,Body), |
1143 | | Body = rlevent(_Name,_Section,_Status,Params,Guard,Theorems, |
1144 | | _Actions,_VWitnesses,_PWitnesses,_Unmod,_AbstractEvents), |
1145 | | Theorems \= [], |
1146 | | conjunct_predicates(Theorems,GuardTheorems) |
1147 | | ), |
1148 | | EventGuards), |
1149 | | EventGuards = [_|_]. |
1150 | | top_level2(user_formulas,textnode('',UserPredicates),UserPredicates) :- b_or_z_successsful_mode, |
1151 | | findall(UP,subnode(user_formulas,UP),UserPredicates), UserPredicates\=[]. |
1152 | | top_level2(definitions,textnode('',Defs),Defs) :- b_or_z_successsful_mode, |
1153 | | findall(Node,get_definition(Node),Defs), Defs\=[]. |
1154 | | top_level2(ltl_formulas,textnode('',Defs),Defs) :- b_or_z_successsful_mode, |
1155 | | findall(Node,get_ltl_named_formula(Node),Defs), Defs\=[]. |
1156 | | top_level2(channels,textnode('',Channels),Channels) :- csp_mode, spec_file_has_been_successfully_loaded, |
1157 | | findall(Node,get_csp_channel(Node),Cs), Cs\=[], sort(Cs,Channels). |
1158 | | top_level2(datatypes,textnode('',DT),DT) :- csp_mode, spec_file_has_been_successfully_loaded, |
1159 | | findall(Node,get_csp_datatype(Node),Cs), Cs\=[], sort(Cs,DT). |
1160 | | top_level2(subtypes,textnode('',DT),DT) :- csp_mode, spec_file_has_been_successfully_loaded, |
1161 | | findall(Node,get_csp_subtype(Node),Cs), Cs\=[], sort(Cs,DT). |
1162 | | top_level2(raw_state,raw_state_pp,[]) :- \+ b_or_z_mode, |
1163 | | spec_file_has_been_successfully_loaded. |
1164 | | top_level2(Atom,property_pp(Nr),[]) :- xtl_mode, % probably also useful for CSP mode |
1165 | | spec_file_has_been_successfully_loaded, |
1166 | | is_property_atom(Atom,Nr). |
1167 | | % we are now using a custom tree_inspector for the CBC Tests |
1168 | | /* top_level2(cbc_tests,textnode('',Paths),Paths) :- b_or_z_mode, |
1169 | | get_preference(user_is_an_expert_with_accessto_source_distribution,true), |
1170 | | %sap:cb_path(_,[_],_), % we have generated at least one test-case |
1171 | | % TO DO: we need a way to refresh this information after test-cases have been generated |
1172 | | % currently the only way seems to close the evaluation view, reload, generate the tests and then open the view |
1173 | | Paths = [cbc_path(root,[],'INITIALISATION')]. |
1174 | | */ |
1175 | | |
1176 | | % Tcl/Tk requires atoms as top_level properties |
1177 | | is_property_atom(property1,1). |
1178 | | is_property_atom(property2,2). |
1179 | | is_property_atom(property3,3). |
1180 | | is_property_atom(property4,4). |
1181 | | is_property_atom(property5,5). |
1182 | | is_property_atom(property6,6). |
1183 | | is_property_atom(property7,7). |
1184 | | is_property_atom(property8,8). |
1185 | | |
1186 | | :- use_module(probcspsrc(haskell_csp),[channel_type_list/2, dataTypeDef/2, subTypeDef/2]). |
1187 | | :- use_module(probsrc(translate),[translate_cspm_expression/2]). |
1188 | | get_csp_channel(bind(Channel,string(TypeString))) :- |
1189 | | channel_type_list(Channel,TypeList), % something like [dataType('SubSubMsg'),intType,boolType] |
1190 | | translate_cspm_expression(dotTuple(TypeList),TypeString). |
1191 | | get_csp_datatype(bind(DT,string(TypeString))) :- |
1192 | | dataTypeDef(DT,TypeList), % something like [dataType('SubSubMsg'),intType,boolType] |
1193 | | translate_cspm_expression(dataTypeDef(TypeList),TypeString). |
1194 | | get_csp_subtype(bind(DT,string(TypeString))) :- |
1195 | | subTypeDef(DT,TypeList), % something like [dataType('SubSubMsg'),intType,boolType] |
1196 | | translate_cspm_expression(dataTypeDef(TypeList),TypeString). |
1197 | | |
1198 | | :- use_module(probsrc(bmachine)). |
1199 | | :- use_module(probsrc(pref_definitions),[b_get_set_pref_definition/3]). |
1200 | | get_definition(textnode('GOAL',Subs)) :- b_get_machine_goal(Goal), conjunction_to_list(Goal,Subs). |
1201 | | get_definition(bind('SCOPE',string(S))) :- b_get_machine_searchscope(S). |
1202 | | get_definition(textnode('HEURISTIC_FUNCTION',[F])) :- b_get_machine_heuristic_function(F). |
1203 | | get_definition(textnode(STR,[F])) :- b_get_machine_animation_expression(STR,F). |
1204 | | get_definition(textnode(Name,[F])) :- b_get_machine_animation_function(F,Nr), |
1205 | | number_codes(Nr,NC), append("ANIMATION_FUNCTION",NC,C), atom_codes(Name,C). |
1206 | ? | get_definition(textnode(Name,[Term])) :- b_get_machine_setscope(SetName,Term), |
1207 | | atom_codes(SetName,NC), append("scope_",NC,C), atom_codes(Name,C). |
1208 | | get_definition(textnode(Name,[b(integer(Nr),integer,[])])) :- b_get_machine_operation_max(OpName,Nr), |
1209 | | atom_codes(OpName,NC), append("MAX_OPERATIONS_",NC,C), atom_codes(Name,C). |
1210 | | get_definition(textnode(PrefixCategory,Subs)) :- |
1211 | ? | special_def_category(PrefixCategory), % group special prefixes separately |
1212 | | findall(named_subformula(DefName,Body,Error), |
1213 | | (special_def_prefix(Prefix,Match,PrefixCategory), |
1214 | | (Match=perfect -> DefName=Prefix ; true), |
1215 | | get_useful_definition_for_bvisual2(expression,Prefix,DefName,_Pos,Body,Error)), |
1216 | | Subs), Subs \= []. |
1217 | | get_definition(named_subformula(DefName,Body,Error)) :- |
1218 | | get_useful_definition_for_bvisual2(_,'',DefName,_Pos,Body,Error). |
1219 | | get_definition(textnode3(Header,DefBodyStr, |
1220 | | [textnode3('Theory',FullThName,[]), |
1221 | | textnode3('Body',DefBodyStr,[]) | Tail |
1222 | | ])) :- |
1223 | | stored_operator_direct_definition(Name,ProjName,TheoryName,Parameters,RawDefBody,RawWD,ParaTypes,_Kind), |
1224 | | ajoin([ProjName,'.',TheoryName],FullThName), |
1225 | | translate_eventb_direct_definition_header(Name,Parameters,Header), |
1226 | | with_bvisual2_translation_mode(translate_eventb_direct_definition_body(RawDefBody,DefBodyStr)), |
1227 | | (ParaTypes = [] -> Tail = Tail2 |
1228 | | ; debug_mode(off), \+ ground(ParaTypes) -> Tail=Tail2 % non-ground types are for destructors, ... are not useful for average user |
1229 | | ; Tail = [textnode3('Type Parameters',TypeParaStr,[])|Tail2], |
1230 | | write_term_to_codes(ParaTypes,PC,[]), |
1231 | | atom_codes(TypeParaStr,PC) |
1232 | | ), |
1233 | | (RawWD=truth(_) -> Tail2=[] |
1234 | | ; Tail2 = [textnode3('WD Condition',WDStr,[])], |
1235 | | with_bvisual2_translation_mode(translate_eventb_direct_definition_body(RawWD,WDStr)) |
1236 | | ). |
1237 | | % TODO: show mapped Event-B and recursive operators; also: above still shown as string and type paras not shown |
1238 | | % TO DO: we could try and get more complex definitions if get_preference(type_check_definitions,true), see type_check_definitions; or we could just pretty print the RAW ast using transform_raw; |
1239 | | % NOTE: special definitions are also declared in |
1240 | | % - procDoSyntaxColouring in main_prob_tcltk_gui.tcl |
1241 | | % - isProBSpecialDefinitionName in Utils.java in de.be4.classicalb.core.parser.util |
1242 | | |
1243 | | special_def_category('CUSTOM_GRAPH'). |
1244 | | special_def_category('VISB'). |
1245 | | special_def_category('PREFERENCES'). |
1246 | | special_def_category('UML_SEQUENCE'). |
1247 | | % TODO: add ANIMATION function, ASSERT_CTL, ASSERT_LTL, GAME_MCTS, ... |
1248 | | special_def_prefix('CUSTOM_GRAPH_EDGES',prefix,'CUSTOM_GRAPH'). |
1249 | | special_def_prefix('CUSTOM_GRAPH_NODES',prefix,'CUSTOM_GRAPH'). |
1250 | | special_def_prefix('CUSTOM_GRAPH',prefix,'CUSTOM_GRAPH'). % perfect match required |
1251 | | special_def_prefix('VISB_DEFINITIONS_FILE',perfect,'VISB'). % perfect match required |
1252 | | special_def_prefix('VISB_JSON_FILE',perfect,'VISB'). % perfect match required |
1253 | | special_def_prefix('VISB_SVG_BOX',perfect,'VISB'). % perfect match required |
1254 | | special_def_prefix('VISB_SVG_CONTENTS',prefix,'VISB'). |
1255 | | special_def_prefix('VISB_SVG_OBJECTS',prefix,'VISB'). |
1256 | | special_def_prefix('VISB_SVG_UPDATES',prefix,'VISB'). |
1257 | | special_def_prefix('VISB_SVG_EVENTS',prefix,'VISB'). |
1258 | | special_def_prefix('VISB_SVG_HOVERS',prefix,'VISB'). |
1259 | | special_def_prefix('SET_PREF_',prefix,'PREFERENCES'). |
1260 | | special_def_prefix('scope_',prefix,'PREFERENCES'). |
1261 | | special_def_prefix('MAX_OPERATIONS_',prefix,'PREFERENCES'). |
1262 | | special_def_prefix('OPERATION_REUSE_OFF_',prefix,'PREFERENCES'). |
1263 | | special_def_prefix('SEQUENCE_CHART_',prefix,'UML_SEQUENCE'). |
1264 | | % these definitions are already displayed by bvisual2 separately (via b_get_machine_animation_expression, ...) |
1265 | | special_def_prefix('FORCE_SYMMETRY_',prefix,special). |
1266 | | special_def_prefix('GOAL',perfect,special). |
1267 | | special_def_prefix('SCOPE',perfect,special). |
1268 | | special_def_prefix('HEURISTIC_FUNCTION',perfect,special). |
1269 | | special_def_prefix('ANIMATION_FUNCTION',prefix,special). |
1270 | | special_def_prefix('ANIMATION_EXPRESSION',prefix,special). |
1271 | | special_def_prefix('GAME_PLAYER',perfect,special). |
1272 | | special_def_prefix('GAME_OVER',perfect,special). |
1273 | | special_def_prefix('GAME_VALUE',perfect,special). |
1274 | | special_def_prefix('GAME_MCTS_RUNS',perfect,special). |
1275 | | special_def_prefix('GAME_MCTS_TIMEOUT',perfect,special). |
1276 | | special_def_prefix('GAME_MCTS_CACHE_LAST_TREE',perfect,special). |
1277 | | |
1278 | ? | is_special_def_name(DefName) :- special_def_prefix(SPrefix,Match,_), |
1279 | | (Match=prefect -> DefName=SPrefix ; atom_prefix(SPrefix,DefName)). |
1280 | | |
1281 | | % only get definitions matching prefix; or if Prefix='' only show those not matching any special prefix |
1282 | | get_useful_definition_for_bvisual2(Type,Prefix,DefName,DefPos,Body,Error) :- |
1283 | ? | b_sorted_b_definition_prefixed(Type,Prefix,DefName,DefPos), |
1284 | ? | (Prefix='' -> \+ is_special_def_name(DefName) ; true), |
1285 | ? | (b_get_typed_definition_with_error_list(DefName,[variables],Body,ErrorsAndWarnings,Success) |
1286 | | -> \+ dangerous_body(Body), |
1287 | | (Success=true -> Error='$no_error' |
1288 | | ; member(Err1,ErrorsAndWarnings), |
1289 | | get_perror(Err1,_Kind,Msg,_Pos) -> Error=Msg |
1290 | | ) |
1291 | | ; % the definition has parameters, TODO: pretty print a bit like theory operators |
1292 | | fail, Error=failure, |
1293 | | b_get_definition(DefName,_DefType,_Paras,RawDefBody,_Deps), |
1294 | | with_bvisual2_translation_mode(translate_eventb_direct_definition_body(RawDefBody,DefBodyStr)), |
1295 | | Body = b(string(DefBodyStr),string,[]) |
1296 | | ). |
1297 | | |
1298 | | % we do not want to perform IO while expanding the state view |
1299 | | % e.g., if you include LibraryIO.def you would have GET_CODE_STDIN whose evaluation waits for user input |
1300 | | % TODO: we should probably also check during evaluation that we do not perform io or that IO is possible? |
1301 | | :- use_module(probsrc(external_functions), [ performs_io/1]). |
1302 | | dangerous_body(b(external_function_call(FUNCTION,_),_,_)) :- performs_io(FUNCTION). |
1303 | | |
1304 | | % ASSERT_LTL |
1305 | | % at the top-level we generate named formulas; we only parse when expanding later |
1306 | | % solves issues e.g., in CSP-B mode where the formulas use CSP constructs but the csp-guide has not been added yet |
1307 | | % see tests 1257, 1259, 1644, 1647 |
1308 | | get_ltl_named_formula(ltl_named_formula(FullName,FormulaAsString)) :- |
1309 | | get_ltl_formula_strings(Names,Strings), |
1310 | | nth1(Nr,Names,Name), |
1311 | | ajoin(['ASSERT_LTL',Name],FullName), % in CSP mode this would actually be assert Main |= LTL "formula" |
1312 | | (nth1(Nr,Strings,FormulaAsString) -> true). |
1313 | | |
1314 | | gen_ltl_bv_sub(Tree,ltl_formula(String,Tree)) :- |
1315 | | pp_ltl_formula(Tree,String). |
1316 | | |
1317 | | get_bv_ltl_sub_formulas(ap(bpred(Pred)),Subs) :- !, Subs = [Pred]. |
1318 | | get_bv_ltl_sub_formulas(LTLTee,BV_Subs) :- |
1319 | | get_ltl_sub_formulas(LTLTee,_,LTLSubs),!, |
1320 | | maplist(gen_ltl_bv_sub,LTLSubs,BV_Subs). |
1321 | | get_bv_ltl_sub_formulas(_,[]). |
1322 | | |
1323 | | |
1324 | | :- use_module(probsrc(b_operation_guards),[get_unsimplified_operation_enabling_condition/5]). |
1325 | | :- use_module(probsrc(bmachine),[b_top_level_operation/1]). |
1326 | | get_top_level_guard(OpName,Params,Guard) :- |
1327 | ? | b_top_level_operation(OpName), |
1328 | | get_unsimplified_operation_enabling_condition(OpName,Params,Guard,_BecomesSuchVars,_Precise), |
1329 | | \+ is_initialisation_op(OpName). |
1330 | | get_subsidiary_guard(OpName,Params,Guard) :- % get guards for non-top-level operations |
1331 | ? | get_unsimplified_operation_enabling_condition(OpName,Params,Guard,_BecomesSuchVars,_Precise), |
1332 | | \+ b_top_level_operation(OpName), |
1333 | | \+ is_initialisation_op(OpName). |
1334 | | |
1335 | | is_initialisation_op('$setup_constants'). |
1336 | | is_initialisation_op('$initialise_machine'). |
1337 | | |
1338 | | :- use_module(probsrc(custom_explicit_sets),[construct_interval_closure/3]). |
1339 | | :- use_module(probsrc(kernel_freetypes),[registered_freetype/2]). |
1340 | | :- use_module(probsrc(bmachine),[b_get_machine_set/2]). |
1341 | | :- use_module(probsrc(b_global_sets),[b_replaced_global_set/2]). |
1342 | | bv_top_level_set(TSet,AllEls) :- b_or_z_mode, |
1343 | ? | b_get_machine_set(Set,TSet), |
1344 | | (b_get_fd_type_bounds(Set,_Low,inf) |
1345 | | -> %L1 is Low+1, L2 is Low+2, |
1346 | | %AllEls= [fd(Low,Set),fd(L1,Set),fd(L2,Set),string('...')] % TODO: avoid type error |
1347 | | AllEls = string('infinite deferred set') |
1348 | | ; all_elements_of_type(Set,AllEls)). |
1349 | | bv_top_level_set(b(identifier(ID),any,[]),string(TS)) :- % replaced by record construction /detection |
1350 | | b_replaced_global_set(ID,NewTypeExpr), |
1351 | | with_bvisual2_translation_mode(translate_subst_or_bexpr_with_limit(NewTypeExpr,500,TS)). |
1352 | | bv_top_level_set(b(identifier('INT'),set(integer),[]),INTVAL) :- % we can return both typed ids and atomic ids |
1353 | ? | classical_b_mode, % INT only exists in pure B mode |
1354 | | get_preference(maxint,MAXINT), get_preference(minint,MININT), |
1355 | | construct_interval_closure(MININT,MAXINT,INTVAL). |
1356 | | |
1357 | | top_level_freetype(Set,textnode3(TopSet,'',AllCases)) :- |
1358 | | animation_minor_mode(eventb), % here types contain Prolog variables (polymorphism) + we have the constant(_) type |
1359 | | registered_freetype(SetP,Cases), |
1360 | | (SetP =.. [Set|TypeParas] -> true ; add_error(bvisual2,'Cannot instantiate type paras:',SetP)), |
1361 | | get_freetype_params(Set,TypeParaNames,TypeParas), |
1362 | | (TypeParaNames = [] -> TopSet = Set ; ajoin_with_sep(TypeParaNames,',',Ps),ajoin([Set,'(',Ps,')'],TopSet)), |
1363 | | findall(textnode3(Case,CaseString,Subs), |
1364 | | (member(case(CaseP,T),Cases),functor(CaseP,Case,_), |
1365 | | bv_pretty_type(T,TS), ajoin([Case,':',TS],CaseString), |
1366 | | findall(textnode3(Destructor,TD,[]),get_destructor_for_freetype(SetP,Case,Destructor,TD),Subs) |
1367 | | ),AllCases). |
1368 | | top_level_freetype(Set,AllCases) :- b_or_z_mode, \+ animation_minor_mode(eventb), |
1369 | | registered_freetype(Set,Cases), |
1370 | | % TO DO: improve presentation, maybe use translate:type_set(_Type,TDom) |
1371 | | findall(field(Case,Value), |
1372 | | (member(case(Case,T),Cases),gen_case_value(T,Value)), |
1373 | | Fields), |
1374 | | AllCases = bind(Set,struct(Fields)). |
1375 | | |
1376 | | get_freetype_params(Set,TypeParaNames,VirtualParaTypes) :- |
1377 | | (stored_operator_direct_definition(Set,_Proj,_Theory,TypeParaNames,_Def,_WD,_TypeParas, datatype_definition) |
1378 | | -> maplist(convert_name_to_type,TypeParaNames,VirtualParaTypes) |
1379 | | ; add_error(bvisual2,'Unknown freetype:',Set),TypeParaNames=[]). |
1380 | | convert_name_to_type(ParaName,global(ParaName)) :- atom(ParaName),!. % so that pretty_type works |
1381 | | convert_name_to_type(Type,_) :- add_error(bvisual,'Cannot convert parameter type:',Type). |
1382 | | get_destructor_for_freetype(Set,Case,Name,TypeAsString) :- |
1383 | | stored_operator_direct_definition(Name,_Proj,_Theory,[argument(Case,_CType)],_Def,_WD,_TypeParameters, |
1384 | | destructor(Set,ReturnType)), |
1385 | | bv_pretty_type(ReturnType,TypeAsString). |
1386 | | |
1387 | | :- use_module(probsrc(b_global_sets),[b_type2_set/2]). |
1388 | | gen_case_value(constant(List),Res) :- List=[_], !, Res=[]. % the constant has no arguments, provide empty set |
1389 | | gen_case_value(Type,Value) :- b_type2_set(Type,Value). |
1390 | | |
1391 | | bv_pretty_type(Type,Res) :- with_bvisual2_translation_mode(pretty_type(Type,TS)),!,Res=TS. |
1392 | | bv_pretty_type(Type,Res) :- add_error(bvisual2,'Cannot convert type:',Type), Res='?'. |
1393 | | |
1394 | | register_top_level_formula(Id,Formula,Subs) :- |
1395 | | assertz( stored_formula(Id,Formula) ), |
1396 | | register_formulas(Subs,Id,_), |
1397 | | assertz( top_level_node(Id) ), |
1398 | | assertz( expanded(Id) ). |
1399 | | |
1400 | | register_formulas([],_Parent,[]). |
1401 | | register_formulas([Formula|Frest],Parent,[SubId|Srest]) :- |
1402 | | register_formula(Formula,Parent,SubId), |
1403 | | register_formulas(Frest,Parent,Srest). |
1404 | | register_formula(Formula,Parent,Id) :- |
1405 | | get_new_id(Id), |
1406 | | assertz( stored_formula(Id,Formula) ), |
1407 | | assertz( subnode(Parent,Id) ), |
1408 | | assertz( supernode(Id,Parent) ). |
1409 | | |
1410 | | get_new_id(Id) :- |
1411 | | (retract(id_counter(Old)) -> true ; Old = 0), |
1412 | | Id is Old+1, |
1413 | | assertz( id_counter(Id) ). |
1414 | | |
1415 | | |
1416 | | disjunction_to_list(A,B,Out) :- |
1417 | | disjunction_to_list2(A,[B],Out,[]). |
1418 | | disjunction_to_list2(Expr,Rest) --> |
1419 | | {get_texpr_expr(Expr,disjunct(A,B)),!}, |
1420 | | disjunction_to_list2(A,[B|Rest]). |
1421 | | disjunction_to_list2(Expr,Rest) --> |
1422 | | [Expr],disjunction_to_list3(Rest). |
1423 | | disjunction_to_list3([]) --> !. |
1424 | | disjunction_to_list3([H|T]) --> disjunction_to_list2(H,T). |
1425 | | |
1426 | | |
1427 | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
1428 | | % some predicates for the support of the Tcl/Tk UI |
1429 | | |
1430 | | call_with_temp_preference(Prefs,Values,Call) :- |
1431 | | maplist(get_preference,Prefs,OldValues), |
1432 | | maplist(set_preference,Prefs,Values), |
1433 | | call_cleanup(Call,maplist(set_preference,Prefs,OldValues)),!. |
1434 | | |
1435 | | bv_get_values_unlimited(Ids,StateId,Values) :- |
1436 | | assertz(get_unlimited_value), |
1437 | | call_cleanup(call_with_temp_preference([expand_avl_upto],[-1],bv_get_values(Ids,StateId,Values)), |
1438 | | retractall(get_unlimited_value)). |
1439 | | |
1440 | | bv_get_value_unlimited(Id,StateId,Value) :- |
1441 | | visited_expression(StateId,State),!, |
1442 | | get_preference(time_out,Timeout), |
1443 | | assertz(get_unlimited_value), |
1444 | | call_cleanup(call_with_temp_preference([expand_avl_upto],[-1],bv_get_value(Id,State,StateId,Timeout,Value)), |
1445 | | retractall(get_unlimited_value)). |
1446 | | bv_get_value_unlimited(_Id,_StateId,e('unknown state')). |
1447 | | |
1448 | | bv_get_value_unlimited_and_unprocessed(Id,StateId,Value) :- |
1449 | | visited_expression(StateId,State),!, |
1450 | | get_preference(time_out,Timeout), |
1451 | | call_with_temp_preference([expand_avl_upto],[-1],bv_get_value_unprocessed(Id,State,StateId,Timeout,Value)). |
1452 | | bv_get_value_unlimited_and_unprocessed(_Id,_StateId,e('unknown state')). |
1453 | | |
1454 | | % get the raw value in Prolog encoding |
1455 | | bv_get_btvalue(Id,StateId,BExpr,BValue) :- |
1456 | | bv_get_value_unlimited_and_unprocessed(Id,StateId,V),!, |
1457 | | (V=btvalue(Value,E) |
1458 | | -> BExpr=E,BValue=Value |
1459 | | ; V=i -> add_error(bvisual2,'Cannot obtain value of inactive entry:',Id),fail |
1460 | | ; add_error(bvisual2,'Cannot extract value of entry:',Id:V),fail). |
1461 | | bv_get_btvalue(Id,_,_,_) :- |
1462 | | add_error(bvisual2,'Unknown identifier or section, cannot find value:',Id),fail. |
1463 | | |
1464 | | |
1465 | | :- use_module(probsrc(tools_commands),[edit_file/2]). |
1466 | | :- use_module(probsrc(error_manager),[extract_file_line_col/6,extract_span_description/2]). |
1467 | | bv_show_formula_origin(Id,Desc) :- |
1468 | | bv_get_stored_formula_expr(Id,Formula), |
1469 | | extract_file_line_col(Formula,FILE,LINE,_COL,_Erow,_Ecol), |
1470 | | extract_span_description(Formula,Desc), |
1471 | | edit_file(FILE,LINE). |
1472 | | |
1473 | | :- use_module(probsrc(bsyntaxtree),[get_texpr_description/2, get_texpr_labels/2]). |
1474 | | bv_formula_description(Id,Desc) :- |
1475 | | bv_get_stored_formula_expr(Id,Formula), |
1476 | | is_texpr(Formula), |
1477 | | get_texpr_description(Formula,Desc). |
1478 | | |
1479 | | % Extended description with additional information, |
1480 | | % such as the formula label and the number of sub-elements. |
1481 | | % Tcl/Tk displays this description in the context menu in the evaluation view. |
1482 | | % The ProB 2 UI displays similar information in tooltips in the state view, |
1483 | | % but those tooltips are constructed on the Java side. |
1484 | | bv_formula_extended_description(Id,Desc) :- |
1485 | | bvisual2_translation_mode(Mode), |
1486 | | with_translation_mode(Mode, bv_formula_extended_description_aux(Id,Desc)). |
1487 | | bv_formula_extended_description_aux(Id,Desc) :- |
1488 | | bv_get_stored_formula_expr(Id,Formula), |
1489 | | is_texpr(Formula), |
1490 | | (get_texpr_description(Formula,Desc0) |
1491 | | -> (get_first_label(Formula,Label) -> ajoin(['@',Label,': ',Desc0],Desc1) |
1492 | | ; Desc1=Desc0 |
1493 | | ) |
1494 | | ; get_first_label(Formula,Desc1) |
1495 | | % ; Desc = 'No description available via @desc pragma') |
1496 | | ; Desc1 = '' |
1497 | | ), |
1498 | | (bv_formula_discharged_description(Id,DInfo) |
1499 | | -> ajoin_with_nl(Desc1,DInfo,Desc2) |
1500 | | ; Desc2 = Desc1), |
1501 | | (bv_formula_size_description(Id,SzeD) |
1502 | | -> ajoin_with_nl(Desc2,SzeD,Desc3) |
1503 | | ; Desc3 = Desc2), |
1504 | | (texpr_contains_wd_condition(Formula) |
1505 | | -> ajoin_with_nl(Desc3,'Formula has wd condition',Desc4) |
1506 | | ; Desc4 = Desc3), |
1507 | | (display_type(Formula,TS) |
1508 | | -> ajoin(['Type: ',TS],TTS), ajoin_with_nl(Desc4,TTS,Desc) |
1509 | | ; Desc = Desc4), |
1510 | | Desc \= ''. |
1511 | | |
1512 | | :- use_module(probsrc(translate),[pretty_type/2]). |
1513 | | display_type(b(_,T,_),TS) :- \+ do_not_show_type(T), bv_pretty_type(T,TS). |
1514 | | % ltl |
1515 | | do_not_show_type(pred). |
1516 | | do_not_show_type(subst). |
1517 | | do_not_show_type(op(_)). |
1518 | | |
1519 | | ajoin_with_nl('',D2,Res) :- !, Res=D2. |
1520 | | ajoin_with_nl(D1,D2,Res) :- ajoin([D1,'\n',D2],Res). |
1521 | | |
1522 | | |
1523 | | bv_formula_discharged_info(Id,DischargedInfo) :- |
1524 | | bv_formula_discharged_info(Id,_,DischargedInfo). |
1525 | | bv_formula_discharged_info(Id,Proven,DischargedInfo) :- |
1526 | | bv_get_stored_formula_expr(Id,Formula), |
1527 | | get_discharged_info(Formula,Proven,DischargedInfo). |
1528 | | |
1529 | | get_discharged_info(Formula,Proven,DischargedInfo) :- |
1530 | | is_texpr(Formula), |
1531 | | get_texpr_info(Formula,I), |
1532 | | member(proof_status(Proven,DischargedInfo),I),!. |
1533 | | |
1534 | | :- use_module(probsrc(tools_strings),[ajoin_with_sep/3]). |
1535 | | bv_formula_discharged_description(Id,Desc) :- |
1536 | | bv_formula_discharged_info(Id,Proven,L), |
1537 | | ajoin_with_sep(L,',',DInfo), |
1538 | | ajoin(['Proof status is ',Proven,': ',DInfo],Desc). |
1539 | | |
1540 | | % extract some info about size and top-level function symbol of an entry: |
1541 | | bv_formula_size_description(Id,Desc) :- |
1542 | | get_nr_of_subformulas(Id,Nr), Nr>=1, |
1543 | | (stored_formula(Id,F), is_texpr(F) |
1544 | | -> SubName = 'subformulas', |
1545 | | (get_texpr_top_level_symbol(F,Symbol,_,_) |
1546 | | -> ajoin(['Formula (',Symbol,')'],Entry) ; Entry='Formula') |
1547 | | ; atom(Id),get_node_label(Id,SubName) |
1548 | | -> Entry = 'Entry' |
1549 | | ; SubName = 'children', Entry = 'Entry' |
1550 | | ), |
1551 | | ajoin([Entry, ' contains ', Nr, ' ', SubName],Desc). |
1552 | | |
1553 | | % compute number of subformulas/entries of a node: |
1554 | | get_nr_of_subformulas(Id,Nr) :- expanded(Id),!, |
1555 | | findall(1, subnode(Id,_), L), |
1556 | | length(L,Nr). |
1557 | | get_nr_of_subformulas(Id,Nr) :- |
1558 | | bv_get_stored_formula_expr(Id,Formula), |
1559 | | findall(1,get_subformulas(Formula,_,_Kind),L), |
1560 | | length(L,Nr). |
1561 | | |
1562 | | % get the top-level symbol of a formula |
1563 | | bv_get_formula_functor_symbol(Id,Symbol) :- |
1564 | | stored_formula(Id,F), is_texpr(F), |
1565 | | \+ top_level_node(Id), |
1566 | | bvisual2_translation_mode(Mode), |
1567 | | with_translation_mode(Mode, get_texpr_top_level_symbol(F,Symbol,_,_)). |
1568 | | |
1569 | | bv_is_child_formula(Id) :- \+ bv_is_topmost_formula(Id). |
1570 | | % check if node is topmost formula, attached to a top_level_node |
1571 | | bv_is_topmost_formula(Id) :- |
1572 | | supernode(Id,Super), |
1573 | | top_level_node(Super). |
1574 | | |
1575 | | |
1576 | | bv_formula_labels(Id,Labels) :- |
1577 | | bv_get_stored_formula_expr(Id,Formula), |
1578 | | is_texpr(Formula), |
1579 | | (get_texpr_labels(Formula,Labels) -> true). |
1580 | | |
1581 | | get_first_label(Formula,Desc) :- get_texpr_labels(Formula,Lbls) -> [Desc|_]=Lbls. |
1582 | | |
1583 | | bv_is_typed_formula(Id) :- bv_get_stored_formula_expr(Id,Formula), is_texpr(Formula). |
1584 | | bv_is_typed_predicate(Id) :- bv_get_stored_formula_expr(Id,Formula), Formula = b(_,pred,_). |
1585 | | bv_is_typed_identifier(Id,IDName) :- bv_get_stored_formula_expr(Id,Formula), Formula = b(identifier(IDName),_,_). |
1586 | | |
1587 | | bv_get_stored_formula_expr(Id,Formula) :- |
1588 | | stored_formula(Id,Stored), |
1589 | | extract_typed_formua(Stored,Formula). |
1590 | | |
1591 | | extract_typed_formua(bind(LHS,_),Formula) :- !, Formula=LHS. |
1592 | | extract_typed_formua(guard(Name,Parameters,Guard),Formula) :- !, |
1593 | | get_guard_formula(Parameters,Guard,GF), |
1594 | | (b_get_operation_description(Name,Desc) -> add_texpr_description(GF,Desc,Formula) |
1595 | | ; Formula = GF). |
1596 | | extract_typed_formua(variant(_Name,_ConvOrAnt,Variant),Formula) :- !, Formula=Variant. |
1597 | | extract_typed_formua(named_subformula(_,Formula,_),Res) :- !, Res=Formula. |
1598 | | extract_typed_formua(TF,TF). |
1599 | | |
1600 | | get_guard_formula([],Guard,Res) :- !, Res=Guard. |
1601 | | get_guard_formula(Parameters,Guard,Expr) :- create_or_merge_exists(Parameters,Guard,Expr). |
1602 | | get_guard_theorems_formula([],_Guard,Theorems,Res) :- !, Res=Theorems. |
1603 | | get_guard_theorems_formula(Parameters,Guard,Theorems,Expr) :- |
1604 | | create_forall(Parameters,b(implication(Guard,Theorems),pred,[]),Expr). |
1605 | | |
1606 | | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% |
1607 | | % |
1608 | | :- use_module(probsrc(tools_io)). |
1609 | | bv_print_to_file(IdList,StateId,Filename) :- |
1610 | | call_with_temp_preference([expand_avl_upto],[-1],bv_print_to_file_aux(IdList,StateId,Filename)). |
1611 | | bv_print_to_file_aux(IdList,StateId,Filename) :- |
1612 | | safe_open_file(Filename,write,S,[encoding(utf8)]), |
1613 | | bv_print_to_stream_l(IdList,S,StateId,false), |
1614 | | close(S). |
1615 | | |
1616 | | bv_print_to_stream_l([],_S,_StateId,_WriteAnd). |
1617 | | bv_print_to_stream_l([Id|Rest],S,StateId,WriteAnd) :- |
1618 | | bv_print_to_stream(Id,S,StateId,OutType,WriteAnd), |
1619 | | (OutType=predicate -> WriteAnd2=true ; WriteAnd2=WriteAnd), |
1620 | | bv_print_to_stream_l(Rest,S,StateId,WriteAnd2). |
1621 | | |
1622 | | bv_print_to_stream(Id,S,StateId,predicate,WriteAnd) :- |
1623 | | stored_formula(Id,Formula), |
1624 | | bv_print_formula_to_stream(Formula,Id,S,StateId,WriteAnd),!,nl(S). |
1625 | | bv_print_to_stream(Id,S,StateId,other,_WriteAnd) :- |
1626 | | get_node_label(Id,Label), |
1627 | | bv_get_values([Id],StateId,[Value]), |
1628 | | write(S,'/* '),write(S,Label),write(S,': '), |
1629 | | bv_print_std_value(Value,S),write(S,' */\n'). |
1630 | | bv_print_std_value(e(Msg),S) :- write(S,'ERROR( '), write(S,Msg), write(S,' )'). |
1631 | | bv_print_std_value(p(Value),S) :- write(S,Value). |
1632 | | bv_print_std_value(v(Value),S) :- write(S,Value). |
1633 | | bv_print_std_value(i,S) :- write(S,'INACTIVE'). |
1634 | | bv_print_std_value(bv_info(I),S) :- write(S,I). |
1635 | | |
1636 | | bv_print_formula_to_stream(Formula,Id,S,StateId,WriteAnd) :- |
1637 | | is_texpr(Formula), |
1638 | | get_texpr_type(Formula,Type), |
1639 | | bv_get_value_unlimited_and_unprocessed(Id,StateId,Value), |
1640 | | bv_print_formula_to_stream2(Type,Formula,Value,S,WriteAnd). |
1641 | | |
1642 | | bv_print_formula_to_stream2(pred,Formula,p(Value),S,WriteAnd) :- !, |
1643 | | bv_print_predicate_to_stream(Value,Formula,S,WriteAnd). |
1644 | | bv_print_formula_to_stream2(Type,Formula,btvalue(Value,_),S,WriteAnd) :- !, |
1645 | | create_texpr(value(Value),Type,[],TValue), |
1646 | | create_texpr(equal(Formula,TValue),pred,[],Equal), |
1647 | | write_bexpression(S,Equal,WriteAnd). |
1648 | | |
1649 | | bv_print_predicate_to_stream(true,Formula,S,WriteAnd) :- |
1650 | | write_bexpression(S,Formula,WriteAnd). |
1651 | | bv_print_predicate_to_stream(false,Formula,S,WriteAnd) :- |
1652 | | create_texpr(negation(Formula),pred,[],NegatedFormula), |
1653 | | write(S,' /* FALSE */ '),write_bexpression(S,NegatedFormula,WriteAnd). |
1654 | | |
1655 | | write_bexpression(Stream,Expression,WriteAnd) :- |
1656 | | (WriteAnd = true -> write(Stream,' & \n') ; true), |
1657 | | translate_bexpression_to_codes(Expression,Codes), |
1658 | | put_codes(Codes,Stream). |
1659 | | |
1660 | | bv_write_all_variables_and_constants(StateId,Filename) :- |
1661 | | call_with_temp_preference([expand_avl_upto],[-1],bv_write_all_variables_and_constants_aux(StateId,Filename)). |
1662 | | bv_write_all_variables_and_constants_aux(StateId,Filename) :- |
1663 | | bv_expand_formula(constants,_CLabel,ConstNodes), |
1664 | | bv_expand_formula(variables,_VLabel,VarNodes), |
1665 | | append(ConstNodes,VarNodes,Subnodes),expand_all(Subnodes), |
1666 | | append([constants|ConstNodes],[variables|VarNodes],Nodes), |
1667 | | bv_print_to_file(Nodes,StateId,Filename). |
1668 | | expand_all(Subnodes) :- |
1669 | | member(Node,Subnodes), |
1670 | | bv_expand_formula(Node,_,_), |
1671 | | fail. |
1672 | | expand_all(_Subnodes). |
1673 | | |
1674 | | |
1675 | | :- use_module(probsrc(eventhandling),[register_event_listener/3]). |
1676 | | :- register_event_listener(clear_specification,clear_bvisual, |
1677 | | 'Clear module bvisual2.'). |
1678 | | :- register_event_listener(specification_initialised,reset_bvisual, |
1679 | | 'Initialise module bvisual2.'). |
1680 | | :- register_event_listener(change_of_animation_mode,reset_bvisual, |
1681 | | 'Initialise module bvisual2.'). |
1682 | | |
1683 | | :- use_module(probsrc(self_check)). |
1684 | | % a very small use-case: |
1685 | | :- assert_must_succeed(( |
1686 | | reset_bvisual, |
1687 | | bv_get_top_level(T), %print(top(T)),nl, |
1688 | | %T == [variables,constants,inv], |
1689 | | member(inv,T), |
1690 | | bv_expand_formula(inv,Text,Sub), |
1691 | | %print(expand(Text,Sub)),nl, |
1692 | | Text == 'INVARIANT', |
1693 | | Sub = [H|_], |
1694 | | bv_expand_formula(H,_Text1,_Sub1), |
1695 | | %print(expand1(Text1,Sub1)),nl, |
1696 | | bv_get_values(Sub,root,Values), |
1697 | | %print(values(Values)),nl, % should be [i,...] or e('unknown state') |
1698 | | Values = [VI|_], (VI=i ; VI=e(_)), |
1699 | | reset_bvisual |
1700 | | )). |
1701 | | |
1702 | | % example bv_get_top_level_formula(theoremsc,Txt,Labels,Vals) |
1703 | | |
1704 | | bv_get_top_level_formula(Category,CatText,Labels,Values) :- |
1705 | | current_state_id(StateId), |
1706 | | bv_get_top_level_formula(Category,CatText,StateId,Labels,Values). |
1707 | | bv_get_top_level_formula(Category,CatText,StateId,Labels,Values) :- |
1708 | | bv_get_top_level(TL), |
1709 | | member(Category,TL), |
1710 | | bv_expand_formula(Category,CatText,Subs), |
1711 | | maplist(get_node_label,Subs,Labels), |
1712 | | bv_get_values(Subs,StateId,Values). |
1713 | | |
1714 | | % ------------------------------------ |
1715 | | |
1716 | | % provide HTML output of operation guards upto MaxLevel |
1717 | | % TO DO: provide option to provide parameter values, output to Latex,... |
1718 | | html_debug_operation_for_stateid(Stream,OpName,StateId,MaxLevel) :- |
1719 | | stored_formula(Id,guard(OpName,_,_)), |
1720 | | enter_level(Stream,0), |
1721 | | traverse(Stream,StateId,0,MaxLevel,Id), |
1722 | | exit_level(Stream,0). |
1723 | | |
1724 | | :- use_module(probsrc(tools),[html_escape/2]). |
1725 | | traverse(_,_StateId,Level,MaxLevel,_Id) :- Level>MaxLevel,!. |
1726 | | traverse(Stream,StateId,Level,MaxLevel,Id) :- |
1727 | | bv_expand_formula(Id,Label,Children), html_escape(Label,ELabel), |
1728 | | bv_get_values([Id],StateId,[Value]), |
1729 | | translate_value(Value,ValueS), html_escape(ValueS,EValueS), |
1730 | | % format('~w : ~w = ~w [~w] (level ~w)~n',[Id,Label,Value,ValueS,Level]), |
1731 | | stored_formula(Id,Formula), |
1732 | | (color_based_on_value(Value,Col) -> format(Stream,'<font color="~w">',[Col]) ; true), |
1733 | | (Formula = guard(_,_,_) |
1734 | | -> format(Stream,'<li>Guard of ~w = ~w</li>~n',[ELabel,EValueS]) |
1735 | | ; format(Stream,'<li>~w = ~w</li>~n',[ELabel,EValueS]) |
1736 | | ), |
1737 | | (color_based_on_value(Value,_) -> format(Stream,'</font>',[]) ; true), |
1738 | | (Level < MaxLevel |
1739 | | -> L1 is Level+1, |
1740 | | enter_level(Stream,L1), |
1741 | | maplist(traverse(Stream,StateId,L1,MaxLevel),Children), |
1742 | | exit_level(Stream,L1) |
1743 | | ; true). |
1744 | | |
1745 | | color_based_on_value(p(false),'INDIANRED'). |
1746 | | color_based_on_value(p(true),'DARKGREEN'). |
1747 | | color_based_on_value(e(_),red). |
1748 | | color_based_on_value(i,gray). |
1749 | | color_based_on_value(bv_info(_),gray). |
1750 | | |
1751 | | enter_level(Stream,L1) :- indent_ws(Stream,L1), format(Stream,'<ul>~n',[]). |
1752 | | exit_level(Stream,L1) :- indent_ws(Stream,L1), format(Stream,'</ul>~n',[]). |
1753 | | |
1754 | | indent_ws(_,X) :- X<1,!. |
1755 | | indent_ws(Stream,X) :- write(Stream,' '), X1 is X-1, indent_ws(Stream,X1). |
1756 | | |
1757 | | |
1758 | | translate_value(p(V),R) :- !,R=V. |
1759 | | translate_value(v(V),R) :- R=V. |
1760 | | translate_value(e(M),R) :- !, ajoin(['ERROR(',M,')'],R). |
1761 | | translate_value(i,R) :- !, R='INACTIVE'. |
1762 | | translate_value(bv_info(I),R) :- !, R=I. |
1763 | | translate_value(V,V). |
1764 | | |
1765 | | % -------------------------------- |
1766 | | |
1767 | | :- use_module(probsrc(error_manager),[add_error/3]). |
1768 | | :- use_module(probsrc(bmachine),[b_parse_machine_predicate_from_codes_open/5, b_parse_machine_formula_from_codes/7]). |
1769 | | tcltk_register_new_user_formula(F) :- tcltk_register_new_user_formula(formula,F). |
1770 | | tcltk_register_new_user_formula(Kind,F) :- |
1771 | | atom_codes(F,Codes), |
1772 | | TypingScope=[prob_ids(visible),variables], |
1773 | | (Kind=open_predicate |
1774 | | -> b_parse_machine_predicate_from_codes_open(exists,Codes,[],TypingScope,Typed) |
1775 | | ; b_parse_machine_formula_from_codes(Kind,Codes,TypingScope,Typed,_Type,true,Error) |
1776 | | ), |
1777 | | (Error=none -> true |
1778 | | ; add_error(tcltk_register_new_user_formula,'Error occured while parsing formula: ',Error),fail), |
1779 | | bv_insert_formula(Typed,user_formulas,_), |
1780 | | (top_level_node(user_formulas) -> true ; register_top_level(user_formulas) ). |
1781 | | %retractall(expanded(user_formulas)), |
1782 | | %bv_insert_formula(Typed,user,_),. |
1783 | | |
1784 | | % -------------------------------- |
1785 | | |
1786 | | |