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