1 % (c) 2009-2024 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 % bmachine provides access to the currently loaded B-machine and all its subsidiary machines
6
7 :- module(bmachine,[bmachine_is_precompiled/0,
8 b_enumerated_sets_precompiled/0,
9 b_set_initial_machine/0,
10 b_set_empty_machine/0,
11 b_set_machine/3,
12 b_set_typed_machine/2,
13 b_load_eventb_project/1, % used for loading .eventb files
14 b_set_eventb_project_flat/3, % set an Event-B project from terms
15
16 get_full_b_machine/2,
17 full_b_machine/1,
18 get_full_b_machine_sha_hash/1, % get SHA hash of loaded and type-checked B machine
19 b_machine_is_loaded/0,
20
21 get_proven_invariant/2,
22 get_unproven_invariants/1,
23 get_invariant_list_with_proof_info/1,
24 load_additional_information/1,
25 %% generate_specialized_invariants/0, %% no longer exists
26 get_operation_info/2,
27 b_get_operation_description/2,
28 get_operation_description_template_expr/2,
29
30 b_load_machine_from_file/1, b_load_machine_from_file/2,
31 b_load_machine_probfile/1, b_load_machine_probfile/2,
32 b_load_machine_from_list_of_facts/2,
33 b_load_machine_from_term/2, % used for Alloy
34 b_machine_precompile/0, other_spec_precompile/0,
35 b_machine_reset/0,
36
37 b_machine_name/1,
38
39 b_get_all_used_filenames/1, b_get_main_filename/1,
40 add_additional_filename/2,
41 set_additional_filename_as_parsing_default/3, reset_filename_parsing_default/2,
42 b_get_main_filenumber/1, b_filenumber/4, portray_filenumbers/0,
43 get_machine_file_number/4,
44 b_absolute_file_name_relative_to_main_machine/2,
45 b_get_animated_sections/1,
46
47 b_get_machine_set/1, b_get_machine_set/2,
48 b_get_named_machine_set/2, b_get_named_machine_set/3,
49 b_get_disjoint_constants_of_type/3, b_get_constant_represented_inside_global_set/2,
50 b_get_machine_constants/1, b_get_machine_all_constants/1,
51 b_machine_has_constants/0, b_machine_has_constants_or_properties/0,
52 b_is_constant/2, b_is_constant/1, b_is_unused_constant/1,
53 get_constant_span/2,
54 b_machine_has_variables/0,
55 b_is_variable/1, b_is_variable/2,
56 b_get_constant_variable_description/2,
57 constant_variable_marked_as_memo/1, constant_variable_marked_as_expand/1,
58 b_get_machine_variables_in_original_order/1, b_get_machine_variables/1,
59 get_primed_machine_variables/1,
60 get_nr_of_machine_variables/1, get_nr_of_machine_constants/1,
61 b_get_all_used_identifiers/1, % Note: may contain var$0 instead of var for becomes_such
62 b_get_all_used_identifiers_in_section/2, % ditto
63 get_machine_identifiers/2,
64 source_code_for_identifier/6,
65
66 b_get_properties_from_machine/1,
67 b_get_invariant_from_machine/1,
68 b_get_linking_invariant_from_machine/1,
69 b_machine_has_assertions/0,
70 b_get_static_assertions_from_machine/1, b_machine_has_static_assertions/0,
71 b_get_unproven_static_assertions_from_machine/1,
72 b_get_dynamic_assertions_from_machine/1, b_machine_has_dynamic_assertions/0,
73 b_get_unproven_dynamic_assertions_from_machine/1,
74 b_get_assertions_from_main_machine/2, b_main_machine_has_no_assertions/0,
75 b_machine_has_unproven_assertions/0, get_assertions_from_machine/2,
76 get_all_assertions_from_machine/1,
77 b_machine_has_proven_invariants/0,
78 b_get_assertions/3,
79 b_get_assertion_count/3,
80 is_discharged_assertion/1,
81
82 b_get_initialisation_from_machine/2,
83 b_machine_has_operations/0,
84 b_get_machine_operation/4, b_get_machine_operation/6,
85 b_get_machine_operation_for_animation/6, % does some rewriting for ANY parameters
86 b_get_machine_operation_for_animation/7, % additional Pos parameter
87 b_get_promoted_machine_operations/1,
88 b_top_level_operation/1, b_top_level_feasible_operation/1,
89 b_is_initialisation_name/1,
90 b_is_operation_name/1, b_get_operation_pos/2,
91 b_get_machine_operation_parameter_types/2,
92 b_get_machine_operation_parameter_names/2,
93 b_get_machine_operation_result_names/2,
94 b_get_machine_operation_typed_parameters/2,
95 b_get_machine_operation_typed_results/2,
96 b_get_machine_operation_signature/2,
97 b_machine_operation_names_in_reverse_order/1,
98 b_get_operation_variant/3,
99
100 b_get_machine_setscope/2,
101 b_get_machine_operation_max/2,
102 b_get_machine_goal/1,
103 b_set_machine_goal/1, b_set_machine_goal/2,
104 b_set_machine_searchscope/1, b_set_machine_searchscope/2,
105 b_set_parsed_typed_machine_goal/1, b_unset_machine_goal/0,
106 b_reset_machine_goal_from_DEFINITIONS/0,
107 b_parse_machine_expression_from_codes/2,
108 b_parse_machine_expression_from_codes_with_prob_ids/2,
109 b_parse_machine_expression_from_codes_with_prob_ids/3,
110 b_parse_machine_expression_from_codes_with_prob_ids/4,
111 b_parse_machine_expression_from_codes/5,
112 b_parse_machine_expression_from_codes/6,
113 b_parse_machine_subsitutions_from_codes/6,
114 b_parse_machine_formula/3, b_parse_machine_formula_from_codes/7,
115 b_parse_machine_predicate/2, b_parse_machine_predicate/3,
116 b_parse_optional_machine_predicate/2,
117 b_parse_machine_predicate_from_codes/3,
118 b_parse_machine_predicate_from_codes_open/5,
119 b_parse_machine_operation_pre_post_predicate/3, b_parse_machine_operation_pre_post_predicate/5,
120 get_machine_operation_additional_identifiers/2,
121
122 determine_type_of_formula/2, determine_type_of_formula/3,
123
124 parse_expression_raw_or_atom_with_prob_ids/2,
125
126 % a version where parsing and type checking are separate:
127 b_parse_wo_type_machine_predicate_from_codes_to_raw_expr/2,
128 b_type_check_raw_expr/4,
129
130 b_get_machine_searchscope/1,
131 b_get_machine_animation_function/2,
132 b_get_machine_heuristic_function/1,
133 b_get_machine_animation_expression/2,
134 b_get_machine_custom_edges_function/2,
135 b_get_machine_custom_nodes_function/2,
136 b_get_machine_custom_graph_function/2,
137 b_machine_temp_predicate/1,
138 %set_temp_predicate/2,
139 assert_temp_typed_predicate/1,
140 reset_temp_predicate/0,
141 add_additional_property/2, b_machine_additional_property/1,
142
143 get_animation_image/2, get_animation_image_source_file/2,
144 b_get_definition/5, b_get_definition_with_pos/6,
145 b_get_definition_string_from_machine/2, b_get_definition_string_from_machine/3,
146 b_definition_prefixed/5, b_sorted_b_definition_prefixed/4,
147 % get typed definitions without parameters:
148 b_get_typed_definition/3, b_get_typed_predicate_definition/3,
149 b_get_typed_expression_definition/3, b_get_true_expression_definition/1,
150
151 b_nth1_invariant/3, % get nth invariant with used Ids
152 b_invariant_number_list/1,
153 b_specialized_invariant_for_op/2,
154 b_specialized_invariant_mask_for_op/2,
155 b_operation_preserves_full_invariant/1, b_operation_preserves_invariant/2,
156 tcltk_get_specialized_invariant_for_op/2, tcltk_get_specialized_invariants_for_ops/1,
157 b_get_operation_normalized_read_write_info/3, % used to be b_normalized_rwsets_for_op/3,
158 b_get_operation_unchanged_variables/2,
159 b_operation_cannot_modify_state/1,
160 b_operation_reads_output_variables/3,
161 b_get_operation_non_det_modifies/2,
162
163 b_extract_values_clause_assignment/3,
164
165 b_type_expression/5,b_type_expression_for_full_b_machine/6,
166 b_type_open_predicate/5,b_type_open_predicate_with_errors/4,
167 b_type_open_exists_predicate/3,
168 type_with_errors/4,
169
170 b_show_machine_representation_unicode/4, b_show_machine_representation/4,
171 b_get_internal_prolog_representation_as_codes/1,
172 b_write_machine_representation_to_file/2,
173 b_write_machine_representation_to_file/3,
174 b_write_eventb_machine_to_classicalb_to_file/1,
175 b_show_eventb_as_classicalb/2,
176
177 b_get_machine_refinement_hierarchy/1,
178 b_get_refined_machine/1, b_get_refined_machine_name/1, b_get_refined_ancestors_names/1,
179 b_get_machine_header_position/2,
180 b_get_model_type/1,
181 b_machine_statistics/2,
182
183 % More Proof Information:
184 discharged_guard_strengthening/4,
185
186 % Flow information
187 wp_untyped/3, clear_wp/0,
188 nonchanging_guard/2,
189 typecheck_predicates/4
190 ]).
191
192 :- use_module(library(lists)).
193 :- use_module(library(ordsets)).
194
195 :- use_module(self_check).
196 :- use_module(error_manager).
197 :- use_module(debug).
198 :- use_module(bmachine_construction,[check_machine/4,type_in_machine_l/6,type_open_predicate_with_quantifier/6]).
199 :- use_module(bsyntaxtree).
200 :- use_module(bmachine_structure,[get_section/3,write_section/4,get_section_texprs/3]).
201 :- use_module(parsercall).
202 :- use_module(tools).
203 :- use_module(translate,[translate_machine/3,translate_eventb_to_classicalb/3]).
204 :- use_module(bmachine_eventb,[check_event_b_project/4,is_eventb_additional_info/1]).
205 :- use_module(kernel_freetypes,[reset_freetypes/0,add_freetype/2]).
206 :- use_module(b_machine_hierarchy).
207 :- use_module(kodkodsrc(kodkod), [replace_by_kodkod/3]).
208
209 :- use_module(b_global_sets,[find_inequal_global_set_identifiers/4,
210 b_get_prob_deferred_set_elements/2,
211 b_check_and_precompile_enumerated_sets/0,
212 b_check_and_precompile_deferred_sets/0,
213 b_check_and_precompile_global_set_symmetry/0]).
214
215 % for applying transformations on the machines
216 :- use_module(record_detection,[replace_sets_by_records/2]).
217 :- use_module(partition_detection,[detect_partitions/2]).
218
219 :- use_module(module_information,[module_info/2]).
220 :- module_info(group,ast).
221 :- module_info(description,'This module provides access to the various parts of the loaded B machine.').
222
223 :- set_prolog_flag(double_quotes, codes).
224
225 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
226 % bmachine: module for storing the currently loaded machine
227 % Contains predicates for getting (already typed) information about
228 % different parts of the machine
229 % many predicates are precompiled by b_precompile_machine/0, see below for
230 % details.
231
232 :- volatile bmachine_is_precompiled/0.
233 :- dynamic bmachine_is_precompiled/0. /* TRUE if the precompiled predicates have been set */
234
235 assert_bmachine_is_precompiled :-
236 (bmachine_is_precompiled -> true ; assertz(bmachine_is_precompiled), debug_println(4,bmachine_is_precompiled)).
237
238 :- volatile machine/2.
239 :- dynamic machine/2.
240 % there is only one main machine fact
241
242 % true if a machine is loaded
243 b_machine_is_loaded :- (machine(_,_) -> true).
244
245 get_full_b_machine(Name,Res) :-
246 (machine(Name,M) -> Res=M
247 ; ground(Name) -> add_error(bmachine,'No B machine with this name loaded:',Name), fail
248 ; add_error(bmachine,'No B machine loaded'), fail
249 ).
250
251 full_b_machine(machine(Name,M)) :- get_full_b_machine(Name,M).
252
253 :- use_module(extension('probhash/probhash'),[raw_sha_hash/2]).
254 get_full_b_machine_sha_hash(Hash) :- full_b_machine(FM), raw_sha_hash(FM,Hash).
255
256 b_set_machine(Main,Machines,Errors) :-
257 b_machine_reset,
258 ? check_machine(Main,Machines,M1,Errors1),!,
259 apply_machine_transformations(M1,ResultMachine),
260 ( no_real_perror_occurred(Errors1) ->
261 %% get_memory_used(M1), %%
262 assert_main_machine(ResultMachine)
263 %%, get_memory_used(M2),print_memory_used(M2), print_memory_used_difference(M1,M2),nl %%
264 ;
265 true),
266 Errors=Errors1.
267
268 assert_main_machine(X) :- %tools_printing:trace_print(X),nl,
269 nonvar(X), X=machine(A,B),
270 !,
271 assertz(machine(A,B)). %, print(machine_asserted),nl.
272 assert_main_machine(X) :- add_internal_error('Illegal format: ',assert_main_machine(X)),fail.
273
274 :- meta_predicate apply_transformation_step(*,2,*,*).
275 % apply some transformations on the machine that require global information
276 % (other local transformations can be found in ast_cleanup)
277 apply_machine_transformations -->
278 apply_transformation_step('record definition detection', replace_sets_by_records),
279 apply_transformation_step('partition detection', detect_partitions). % is this necessary?? done in ast_cleanup
280
281 apply_transformation_step(Name,Pred,In,Out) :-
282 ( call(Pred, In, Out) -> true
283 ;
284 ajoin(['applying ', Name, ' failed, skipping.'], Msg),
285 add_error(bmachine,Msg),
286 In=Out).
287
288 % try to translate (parts of) the properties to Kodkod
289 % if it succeeds, replace the translated predicates by
290 % calls to the Kodkod process
291 try_kodkod :-
292 get_preference(use_solver_on_load,kodkod),
293 b_get_machine_constants(Constants),
294 Constants = [_|_],!,
295 b_get_properties_from_machine(OldPredicate),
296 ( replace_by_kodkod(Constants,OldPredicate,NewPredicate) ->
297 retract(machine(N,OldMachine)),
298 retractall( b_get_properties_from_machine(_) ),
299 write_section(properties,NewPredicate,machine(N,OldMachine),NewMachine),
300 assertz( NewMachine ),
301 assertz( b_get_properties_from_machine(NewPredicate) )
302 ;
303 true).
304 try_kodkod.
305
306 :- use_module(bmachine_static_checks, [static_check_main_machine/1]).
307 % set a machine term as current machine, without calling type checking
308 % (used for Z translations)
309 b_set_typed_machine(M1,FromFile) :-
310 b_machine_clear,
311 static_check_main_machine(M1), % done by check_machine in b_set_machine above
312 apply_machine_transformations(M1,ResultMachine),
313 assert_main_machine(ResultMachine),
314 set_all_used_filenames([FromFile]).
315
316 b_set_eventb_project_flat(Models,Contextes,Proofs) :-
317 b_machine_clear,
318 set_animation_mode(b), set_animation_minor_mode(eventb),
319 analyse_eventb_hierarchy(Models,Contextes),
320 ( check_event_b_project(Models,Contextes,Proofs,M1) ->
321 apply_machine_transformations(M1,ResultMachine),
322 assert_main_machine(ResultMachine) % has the form machine/2
323 ;
324 % Note: if there are typecheck errors due to missing .ptm files for axiomatic operators it is not an internal error!
325 fail).
326
327 b_load_eventb_project(Filename) :-
328 read_eventb_project_from_file(Filename,Machines,Contexts,Proofs,Errors,Prefs),
329 (Errors=[] -> true ; add_error(b_load_eventb_project,'Errors in Event-B Package: ',Errors)),
330 set_stored_prefs(Prefs),
331 set_all_used_filenames([Filename]),
332 b_set_eventb_project_flat(Machines,Contexts,Proofs),
333 clear_wp,
334 (load_additional_information(Proofs) -> true ; add_error(b_load_eventb_project,'Failed to load proof information',Proofs)).
335 % generate_specialized_invariants.
336
337 read_eventb_project_from_file(Filename, Machines, Contexts, Proofs, Errors, Prefs) :-
338 open(Filename, read, Stream, [encoding(utf8)]),
339 call_cleanup(read_eventb_project_from_stream(Stream, Filename, LoadCommand, Prefs), close(Stream)),
340 (eventb_load_command(LoadCommand, Machines, Contexts, Proofs, Errors)
341 -> true
342 ; add_error_and_fail(b_load_eventb_project, 'This is not a valid EventB Project file:', Filename)
343 ).
344
345 read_eventb_project_from_stream(Stream, Filename, LC, Prefs) :-
346 safe_read(Stream, Filename, Term),
347 (Term == end_of_file
348 -> Prefs = []
349 ; process_eventb_project_term(Term, LC, Prefs, PrefsTail),
350 read_eventb_project_from_stream(Stream, Filename, LC, PrefsTail)
351 ).
352
353 safe_read(Stream,Filename,T) :-
354 catch(read(Stream,T), E, (
355 ajoin(['.eventb file "', Filename, '" is corrupted; exception occurred while reading:'],Msg),
356 add_error(safe_read,Msg,E),
357 T=end_of_file
358 )).
359
360 process_eventb_project_term(Term, _LC, Prefs, Prefs) :-
361 %tools_printing:nested_write_term_to_codes(Term,Cs), format('~s~n',[Cs]),
362 var(Term),
363 !,
364 add_warning(b_load_eventb_project, 'Bare variable term in Event-B project: ', Term).
365 process_eventb_project_term(package(LoadCommand), LC, Prefs, Prefs) :-
366 !,
367 (nonvar(LC)
368 -> add_error_and_fail(b_load_eventb_project, 'Duplicate package/1 term in Event-B project: ', package(LoadCommand))
369 ; LC = LoadCommand
370 ).
371 process_eventb_project_term(stored_preference(Pref,Val), _LC, [stored_preference(Pref,Val)|Prefs], Prefs) :- !.
372 process_eventb_project_term(emf_model(_Name,_Base64Xml), _LC, Prefs, Prefs) :- !. % not used
373 process_eventb_project_term(Term, _LC, Prefs, Prefs) :-
374 functor(Term, F, N),
375 add_warning(b_load_eventb_project, 'Unrecognized term in Event-B project: ', F/N).
376
377 eventb_load_command(LoadCommand, _, _, _, _) :- var(LoadCommand), !, fail.
378 eventb_load_command(load_event_b_project(Machines,Contexts,Proofs,Errors), Machines, Contexts, Proofs, Errors).
379 eventb_load_command(load_event_b_project(Machines,Contexts,Errors), Machines, Contexts, [], Errors) :-
380 print('% Deprecated EventB Project without Proof Info.'), nl.
381
382 set_stored_prefs([stored_preference(Pref,Val)|Prefs]) :-
383 printsilent(stored_preference(Pref,Val)), nls,
384 preferences:set_preference(Pref,Val),
385 set_stored_prefs(Prefs).
386 set_stored_prefs([]).
387
388 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
389 % Collect Proof Information from Event B
390
391 :- volatile discharged/3.
392 :- volatile discharged_theorem/3, wd_po/3, wp_untyped/3.
393 :- volatile nonchanging_guard/2, discharged_guard_strengthening/4.
394 :- dynamic discharged/3.
395 % discharged(Model,Event,Name) : invariant Name in model Model is preserved by Event (no matter which Event at which refinement level)
396 :- dynamic discharged_theorem/3.
397 :- dynamic wd_po/3.
398 :- dynamic wp_untyped/3.
399 :- dynamic nonchanging_guard/2.
400 :- dynamic discharged_guard_strengthening/4.
401
402 :- volatile b_specialized_invariant_for_op/2, b_operation_preserves_invariant/2.
403 :- dynamic b_specialized_invariant_for_op/2, b_operation_preserves_invariant/2.
404 :- volatile b_nth1_invariant/3, b_invariant_number_list/1,
405 b_specialized_invariant_mask_for_op/2, get_proven_invariant/2.
406 :- dynamic b_nth1_invariant/3, b_invariant_number_list/1, b_specialized_invariant_mask_for_op/2, get_proven_invariant/2.
407 :- volatile complete_discharged_info/0.
408 :- dynamic complete_discharged_info/0.
409
410
411 clear_wp :-
412 retractall( wp_untyped(_,_,_) ).
413 %retractall( wp_typed(_,_,_) ). only in flow.pl
414
415 load_additional_information([]) :- !.
416 load_additional_information([H|T]) :-
417 ? load_additional_information_fact(H),!,
418 load_additional_information(T).
419 load_additional_information([H|T]) :- !,
420 add_internal_error('Unknown additional info: ',load_additional_information_fact(H)),
421 load_additional_information(T).
422 load_additional_information(I) :- !,
423 add_internal_error('Additional info not a list: ',load_additional_information_fact(I)).
424
425 % old style proof info
426 load_additional_information_fact(discharged(Machine,Theorem)) :- % a discharged theorem
427 debug_println(9,discharged_theorem(Machine,old_style_proof_info,Theorem)),
428 assertz(discharged_theorem(Machine,invariant,Theorem)).
429 load_additional_information_fact(discharged(Machine,Event,Invariant)) :-
430 debug_println(9,discharged(Machine,Event,Invariant)),
431 assertz(discharged(Machine,Event,Invariant)).
432 load_additional_information_fact(Term) :- % theories are handled in bmachine_eventb.pl already
433 is_eventb_additional_info(Term).
434
435 % new style proof info po(Machine,Info,SourceList,Discharged)
436
437 load_additional_information_fact(po(Machine,'Invariant preservation',Source,true)) :- % invariant preservation
438 add_discharged_po_infos(Source,Machine).
439
440 load_additional_information_fact(po(Machine,'Invariant establishment',Source,true)) :- % invariant establishment
441 add_discharged_po_infos(Source,Machine).
442
443 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % invariant or theorem wd
444 ( Text = 'Well-definedness of Invariant'
445 ; Text = 'Well-definedness of Theorem'),
446 member(invariant(Invariant),Source),
447 debug_println(9,wd_po(Machine,Invariant,Proven)),
448 assertz(wd_po(Machine,Invariant,Proven)).
449 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % axiom or axiom theorem wd
450 ( Text = 'Well-definedness of Axiom'
451 ; Text = 'Well-definedness of Theorem'),
452 member(axiom(Axiom),Source),
453 debug_println(9,wd_axiom(Machine,Axiom,Proven)). % TO DO: assert and use
454 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % proven theorem as guard
455 Text = 'Well-definedness of Theorem',
456 member(guard(Grd),Source),
457 member(event(Evt),Source),
458 debug_println(9,wd_axiom(Machine,Evt/Grd,Proven)). % TO DO: assert and use
459 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % wd of action
460 Text = 'Well-definedness of action',
461 (member(action(ACT),Source) % probably the guard in the last event with discharged info ??
462 -> debug_println(9,wd_action(Machine,ACT,Proven)) % TO DO: assert and use, if false: discard proven invariants?!
463 ; format('Illegal Rodin PO source in ~w for ~w: ~w~n',[Machine,Text,Source])
464 ).
465 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % wd of guard
466 Text = 'Well-definedness of Guard',
467 (member(guard(GRD),Source) % probably the guard in the last event with discharged info ??
468 -> debug_println(9,wd_guard(Machine,GRD,Proven)) % TO DO: assert and use
469 ; format('Illegal Rodin PO source in ~w for ~w: ~w~n',[Machine,Text,Source])
470 ).
471 load_additional_information_fact(po(Machine,'Theorem',[invariant(Theorem)],true)) :- % a theorem
472 debug_println(9,discharged_theorem(Machine,invariant,Theorem)),
473 assertz(discharged_theorem(Machine,invariant,Theorem)).
474 load_additional_information_fact(po(Machine,'Theorem',[axiom(Theorem)],true)) :- % a theorem
475 debug_println(9,discharged_theorem(Machine,axiom,Theorem)),
476 assertz(discharged_theorem(Machine,axiom,Theorem)).
477 load_additional_information_fact(po(Machine,'Theorem',[guard(GuardTheorem),event(Event)],true)) :- % a theorem in a guard
478 debug_println(9,discharged_theorem(Machine,guard(Event),GuardTheorem)),
479 assertz(discharged_theorem(Machine,guard(Event),GuardTheorem)).
480
481 % stuff we don't yet care about
482 load_additional_information_fact(po(Machine,Text,Infos,Proven)) :-
483 ( Text = 'Guard strengthening (split)'
484 ; Text = 'Guard strengthening (merge)'
485 ; Text = 'Guard strengthening' ),
486 !,
487 (Proven=true, Infos = [event(AbsEvent),guard(Guard),event(ConcreteEvent)]
488 -> assertz(discharged_guard_strengthening(Machine,AbsEvent,Guard,ConcreteEvent)),
489 debug_println(19,discharged_guard_strengthening(Machine,AbsEvent,Guard,ConcreteEvent))
490 ; true
491 ).
492 load_additional_information_fact(po(_,'Variant of event',_,_)).
493 load_additional_information_fact(po(_,'Natural number variant of event',_,_)).
494 load_additional_information_fact(po(_,'Action simulation',_,_)).
495 load_additional_information_fact(po(_,'Feasibility of witness',_,_)).
496 load_additional_information_fact(po(_,'Feasibility of action',_,_)).
497 load_additional_information_fact(po(_,'Well-definedness of witness',_,_)).
498 load_additional_information_fact(po(_,'Well-definedness of variant',_,_)).
499 load_additional_information_fact(po(_,'Finiteness of variant',_,_)).
500 load_additional_information_fact(po(_,'Equality of common variables',_,_)).
501
502 load_additional_information_fact(po(_Machine,_Kind,_Source,false)). % ignore everything that is not proven
503
504 load_additional_information_fact(po(_Machine,_Kind,_Source,reviewed)). % ignore everything that is only reviewed
505
506 % ignore exporter version for now
507 % we are compatible to both versions 2 and 3 (added abstract constants)
508 load_additional_information_fact(exporter_version(V)) :- V=2 ; V=3.
509
510 % ignored because the pragmas are attached to the machine in load_event_b_project/4
511 load_additional_information_fact(pragma(_Type,_Source,_AttachedTo,_Content)).
512
513 load_additional_information_fact(wp(S,D,P)) :-
514 assertz( wp_untyped(S,D,P) ).
515
516 load_additional_information_fact(nonchanging_guard(E,P)) :-
517 typecheck_predicates(P,TypedPred,E,_),
518 assertz(nonchanging_guard(E,TypedPred)).
519
520 load_additional_information_fact(invariant(_I)). %ignore
521
522 typecheck_predicates([],[],_,_).
523 typecheck_predicates([H|T],[TH|TT],S,D) :-
524 (S='INITIALISATION' -> Scope1 = []; Scope1=[operation(S)]),
525 ((D='INITIALISATION';var(D)) -> Scope2 = Scope1; Scope2=[operation(D)|Scope1]),
526 Scope = [variables|Scope2],
527 b_type_expression(H,Scope, _, TH, _),
528 typecheck_predicates(T,TT,S,D).
529
530
531 add_discharged_po_infos(Source,Machine) :-
532 % Source = [event(A1),...,event(CurMachineEvent),invariant(Inv)]
533 % note that CurMachineEvent could be equal to A1; A1 can be split up into multiple events (one of which could have the same name as A1; see Ticket PROB-292)
534 get_bottom_event(Source,Event),
535 member(invariant(Invariant),Source),
536 debug_println(9,discharged(Machine,Event,Invariant)),
537 assertz(discharged(Machine,Event,Invariant)),
538 % TO DO: should we propagate info up to abstract events which are not split up or where all refinements preserve a certain invariant ??
539 fail.
540 add_discharged_po_infos(_Source,_Machine).
541
542 % get the last event entry in proof info source list
543 get_bottom_event(Source,Event) :-
544 (bottom_event(Source,'$NONE'(none),Event) -> true
545 ; add_error(bmachine,'Could not determine event for proof info: ',Source),fail).
546 bottom_event([],Ev,Ev) :- Ev \= '$NONE'(none).
547 bottom_event([event(E)|T],_,Res) :- !,bottom_event(T,E,Res).
548 bottom_event([_|T],E,Res) :- bottom_event(T,E,Res).
549
550 :- use_module(debug).
551
552 tcltk_get_specialized_invariants_for_ops(list(Res)) :-
553 findall([Name,InvHeader,TI | Tail],
554 ((b_top_level_operation(Name) ; Name='$initialise_machine'),
555 tcltk_get_specialized_invariant_for_op_single(Name,TI,NrUnProven),
556 tcltk_get_proven_invariant_for_op(Name,PI),
557 ajoin([' INVARIANT (',NrUnProven,')'],InvHeader),
558 (PI='none' -> Tail = ['END;']
559 ; Tail = [' NON-TRIVIAL PROVEN INVARIANT:', PI, 'END;']
560 )
561 ), Res).
562 tcltk_get_specialized_invariant_for_op_single(Event,TI,NrUnProven) :-
563 (b_specialized_invariant_for_op(Event,Invariant) ->
564 conjunction_to_list(Invariant,IL), length(IL,NrUnProven),
565 translate:translate_bexpression(Invariant,TI)
566 ; TI = 'not_simplified', NrUnProven='-').
567 tcltk_get_specialized_invariant_for_op(Event,list(TI)) :-
568 (b_specialized_invariant_for_op(Event,Invariant) ->
569 conjunction_to_list(Invariant,IL),
570 (IL=[] -> TI = ['fully_proven']
571 ; maplist(translate:translate_bexpression,IL,TI))
572 ; TI = ['not_simplified']).
573 tcltk_get_proven_invariant_for_op(Event,TI) :- % get non-trivially proven invariants
574 (get_proven_invariant(Event,Invariant), \+ is_truth(Invariant) ->
575 translate:translate_bexpression(Invariant,TI)
576 ; TI = 'none').
577
578
579 :- public b_nth1_invariant_calc/3.
580 b_nth1_invariant_calc(Nr,Invariant,UsedIds) :-
581 get_invariant_list_with_used_ids(IL,IL_Ids),
582 ? nth1(Nr,IL,Invariant),
583 nth1(Nr,IL_Ids,UsedIds).
584
585 % bmachine:b_nth1_invariant(Nr,Inv,Used), format('~nInvariant ~w over ~w~n',[Nr,Used]), translate:print_bexpr(Inv),nl,fail
586 % bmachine:b_specialized_invariant_mask_for_op(Op,Mask), format('Mask ~w : ~w~n',[Op,Mask]),fail
587
588 :- public b_invariant_number_list_calc/1.
589 b_invariant_number_list_calc(InvList) :-
590 findall(nth1_invariant(Nr),b_nth1_invariant(Nr,_,_),InvList).
591
592 % use proof information to compute subset of invariant that needs to be checked for operations
593
594 % one fact including the position of all unproven invariants
595 :- public b_specialized_invariant_mask_for_op_calc/2.
596 b_specialized_invariant_mask_for_op_calc(Event,Mask) :-
597 preferences:get_preference(use_po,true),
598 get_invariant_list_with_used_ids(IL,IL_Ids),
599 % Note: we can have interference with CSE here, as lazy_let_pred at top-level can merge several conjuncts (but CSE is now disabled for the invariant if PROOF_INFO = TRUE)
600 IL \= [], % otherwise: Invariant already trivial; no sense in keeping track of information
601 ? get_op_or_init_and_syntax_filter(Event,ProofInfoEventName,IL,IL_Ids,RIL),
602 exclude(is_proven_invariant(ProofInfoEventName),RIL,RL), % Warning !! The invariants are not all from Model; the discharged information could be for a proven invariant with the same label from another model, see examples/EventBPrologPackages/ProofDirected/TestR_label_reuse.eventb; this should now properly be dealt with by filter_proven_invariants
603 IL\=RL, /* something filtered out */
604 (RL=[]
605 -> Mask = [] % fully proven
606 ; findall(Nr,(nth1(Nr,IL,Inv),member(Inv,RL)),Mask)
607 ),
608 debug_println(4,b_specialized_invariant_mask_for_op(Event,Mask)).
609
610 % TODO: investigate whether we should pre-compute this or simply re-compute it as needed
611 :- public b_specialized_invariant_for_op_calc/2.
612 b_specialized_invariant_for_op_calc(Event,Invariant) :-
613 ? b_specialized_invariant_mask_for_op(Event,Mask),
614 findall(Inv,(member(Nr,Mask),b_nth1_invariant(Nr,Inv,_)),RL),
615 conjunct_predicates(RL,Invariant). %, print(simplified),nl,translate:print_bexpr(Invariant),nl.
616
617
618 get_op_or_init_and_syntax_filter('$initialise_machine','INITIALISATION',IL,_,IL). % INIT always sets all variables
619 get_op_or_init_and_syntax_filter(Event,Event,IL,IL_Ids,RIL) :-
620 ? b_is_operation_name(Event),
621 filter_syntactically_relevant_invariants(IL,IL_Ids,Event,RIL). % filter out all invariants not modified by Event
622
623 :- public b_operation_preserves_invariant_calc/2.
624 % check if an operation preserves the full invariant; according to proof information
625 b_operation_preserves_invariant_calc(Event,Preserved) :-
626 ? b_specialized_invariant_mask_for_op(Event,Mask),
627 (Mask=[] -> Preserved=full_invariant ; Preserved=partial_invariant).
628
629 b_operation_preserves_full_invariant(Op) :- b_specialized_invariant_mask_for_op(Op,[]).
630
631 :- public get_proven_invariant_calc/2.
632 % computes proven, relevant invariants (not trivial ones which are unaffected by Event) for main model
633 get_proven_invariant_calc(Event, Invariant) :-
634 preferences:get_preference(use_po,true),
635 b_machine_name(Model),
636 get_invariant_list_with_used_ids(IL,IL_Ids),
637 ? b_is_operation_name(Event),
638 %print(filter_syntactically_relevant_invariants(Event,Model)),debug:nl_time,
639 filter_syntactically_relevant_invariants(IL,IL_Ids,Event,RIL),
640 %print(select_proven_invariants(Event,Model)),debug:nl_time,
641 select_proven_invariants(RIL,Model,Event,RL),
642 %print(conjunct_predicates(Event,Model)),debug:nl_time,
643 conjunct_predicates(RL,Invariant).
644
645 get_invariant_list_with_used_ids(IL,IL_Ids) :-
646 b_get_invariant_from_machine(I),
647 conjunction_to_list_with_rodin_labels(I,IL),
648 maplist(find_id_uses_for_maplist,IL,IL_Ids).
649 find_id_uses_for_maplist(Inv,IDs) :- find_identifier_uses(Inv,[],IDs).
650
651 % get list of invariants with proof info (discharged(_)) added
652 get_invariant_list_with_proof_info(InvariantList) :-
653 findall(I,get_invariant_with_proof_status_calc(I,_),InvariantList).
654
655 :- use_module(probsrc(tools_lists),[count_occurences/2]).
656
657 % compute all invariants which are not fully proven for events (initialisation is not examined!):
658 get_unproven_invariants(UnProvenList) :-
659 findall(I,get_invariant_with_proof_status_calc(I,unproven),UnProvenList).
660
661 get_invariant_with_proof_status_calc(Invariant,Proven) :- % not precompiled at the moment
662 b_machine_name(Model),
663 b_get_invariant_from_machine(I),
664 conjunction_to_list_with_rodin_labels(I,IL), % ensure rodin labels are propagated down for proof info
665 ? member(Inv,IL),
666 findall(Status,invariant_proof_status_for_event(Inv,Model,_Event,Status),StatusList),
667 count_occurences(StatusList,Occs),
668 (member(unproven-_,Occs)
669 -> Proven=unproven
670 ; (debug_mode(on) -> print('INVARIANT proven for all events: '), translate:print_bexpr(Inv),nl ; true),
671 Proven=proven
672 ),
673 add_texpr_info_if_new(Inv,proof_status(Proven,Occs),Invariant).
674
675 %is_unproven_inv_for_model(_Invariant,_Model,_Event) :-
676 % preferences:get_preference(use_po,false),!. % information is used in bvisual2,...
677 invariant_proof_status_for_event(Invariant,Model,Event,Status) :-
678 ? b_is_operation_name(Event),
679 proof_status_for_inv2(Invariant,Model,Event,Status).
680
681 proof_status_for_inv2(Invariant,_,Event,unchanged) :-
682 \+ is_syntactically_relevant_invariant_for_event(Event,Invariant),!. % invariant unaffected by Event/Operation
683 proof_status_for_inv2(Invariant,Model,Event,proven) :-
684 ? is_proven_invariant_for_model(Model,Event,Invariant),!.
685 proof_status_for_inv2(_,_,_,unproven).
686
687
688 % filter_syntactically_relevant_invariants(+InvariantsList, +UsedIDs, +EventName, -RelevantItemsFromInvariantsList)
689 filter_syntactically_relevant_invariants(Invariants,IL_Ids,Event,Result) :-
690 get_operation_info(Event,SubstitutionInfo),
691 get_modifies_from_info(SubstitutionInfo,SortedModIds),
692 filter_syntactically_relevant_invariants2(Invariants,IL_Ids,SortedModIds,Result).
693 % noticeably faster than include, see e.g. public_examples/B/PerformanceTests/Generated/Generated4000.mch
694 %include(is_syntactically_relevant_inv(SortedModIds),Invariants,IL_Ids,Result).
695
696 is_syntactically_relevant_inv(SortedModIds,_Inv,IDs) :-
697 ord_intersect(SortedModIds,IDs).
698
699 filter_syntactically_relevant_invariants2([],_,_,[]).
700 filter_syntactically_relevant_invariants2([Inv|T],[IDs|TI],SortedModIds,R) :-
701 (is_syntactically_relevant_inv(SortedModIds,Inv,IDs)
702 -> R=[Inv|TR] ; R=TR),
703 filter_syntactically_relevant_invariants2(T,TI,SortedModIds,TR).
704
705 is_syntactically_relevant_invariant_for_event(Event,Inv) :-
706 get_operation_info(Event,SubstitutionInfo),
707 get_modifies_from_info(SubstitutionInfo,SortedModIds),
708 find_id_uses_for_maplist(Inv,IDs),
709 is_syntactically_relevant_inv(SortedModIds,_Inv,IDs).
710
711 get_modifies_from_info(SubstitutionInfo,SortedModIds) :-
712 ((memberchk(modifies(ModID),SubstitutionInfo) -> ground(ModID))
713 -> list_to_ord_set(ModID,SortedModIds) % is this necessary ?
714 ; SortedModIds=[]).
715
716 % filter_proven_invariants(+InvariantsList, +ModelName, +EventName, -RelevantItemsFromInvariantsList)
717 % this gets called during model checking time
718 is_proven_invariant(Event,E) :-
719 % print('Filter Check: '), print(Event), print(' : '),translate:print_bexpr(E),nl,
720 get_texpr_pos(E,POS),
721 POS = rodinpos(Model,Name,_), % only accept new rodinpos information with three parameters !
722 !, % the old one with two parameters could lead to confusion as labels can be reused
723 % TO DO: check that if E is not always well-defined that there are no unproven WD proof obligations !
724 ? discharged_invariant(Model,Name,Event),
725 check_wd_discharged_inv_or_thm(E,Model,Name,Event). %% print('DISCHARGED'(Model,Event,Name)),nl.
726
727 check_wd_discharged_inv_or_thm(E,_,_,_) :- always_well_defined(E),!.
728 check_wd_discharged_inv_or_thm(_,Model,Name,_Event) :- wd_po(Model,Name,ProofStatus),!,
729 ProofStatus=true.
730 check_wd_discharged_inv_or_thm(_,Model,Name,Event) :-
731 % no WD_PO associated or stored
732 % TO DO: we could try ProB-WD prover; but this situation only happens with old-style exports; we could use add_message
733 format('% Assuming invariant/theorem ~w is well-defined for event ~w:~w (no WD PO found).~n',[Name,Model,Event]).
734
735 % select_proven_invariants(+InvariantsList, +ModelName, +EventName, -RelevantItemsFromInvariantsList)
736 select_proven_invariants(Invariants,Model,Event,Result) :-
737 include(is_proven_invariant_for_model(Model,Event),Invariants,Result).
738
739 % Note: different from is_proven_invariant; TO DO: merge (here we assume main model)
740 is_proven_invariant_for_model(MainModel,Event,E) :-
741 ? get_rodin_name(E,Name), % if we do not have a rodin position we consider this as not proved
742 (get_rodin_model_name(E,Model) -> true
743 ; debug_format(19,'Could not get Rodin model name for invariant (deprecated .eventb format): ~w~n',[Name]),
744 Model=MainModel,
745 fail % we have an old style .eventb file; safer to assume not proven as there can be clashes of labels
746 ),
747 ? discharged_invariant(Model,Name,Event).
748
749 is_discharged_assertion(Theorem) :-
750 if( get_texpr_pos(Theorem,rodinpos(Model,Name,_)),
751 (discharged_theorem(Model,_,Name), % does not matter if invariant or axiom
752 check_wd_discharged_inv_or_thm(Theorem,Model,Name,assertion) ) % check that well-defined
753 , (animation_minor_mode(eventb),
754 (silent_mode(on) -> true
755 ; print('Could not get position information for theorem: '),
756 translate:print_bexpr(Theorem),nl,
757 get_texpr_pos(Theorem,POS),debug_println(19,get_texpr_pos(POS))
758 ),
759 fail)
760 ).
761 % derived predicate
762 discharged_invariant(Model,InvariantName,Event) :-
763 % InvariantName from model Model is preserved by Event and any of its refinements
764 discharged(Model,Event,InvariantName).
765 discharged_invariant(Model,InvariantName,Event) :-
766 % InvariantName from model Model is preserved by Event and any of its refinements
767 also_discharged(Model,Event,InvariantName).
768
769 b_machine_has_proven_invariants :-
770 (discharged(_,_,_) -> true).
771
772 % complete the discharged/3 information: propagating information from abstract events
773 % down to refined top-level events
774 :- public complete_discharged_info/0.
775 :- public complete_discharged_info_calc/0.
776 complete_discharged_info_calc :- debug_println(4,'completing discharged info: '),
777 statistics(runtime,[Start,_]),
778 (complete_discharged_info2 -> true ; true),
779 statistics(runtime,[Stop,_]), T is Stop-Start, debug_print(4,T), debug_println(4,' ms').
780 :- volatile discharged2/2, also_discharged/3.
781 :- dynamic discharged2/2.
782 :- dynamic also_discharged/3.
783 ?discharged_info_exists :- discharged2(_,_),!.
784 complete_discharged_info2 :- retractall(also_discharged(_,_,_)),
785 retractall(discharged2(_,_)),
786 ? discharged(Model,Event,_), % find out which Model and Events are used in discharged info
787 \+ discharged2(Model,Event), %print(discharged(Model,Event)),nl,
788 assertz(discharged2(Model,Event)),fail.
789 complete_discharged_info2 :- discharged_info_exists,
790 b_get_animated_sections(Sections),
791 ? discharged2(Model,Event), % Event in Model was proven to preserve an invariant in Model
792 b_get_abstract_events(Event,RModel,AbstractEvents), % search for a refinement of Model where the same event exists
793 RModel \= Model,
794 % i.e., invariant Name was proven in an abstract Model for Event
795 \+ is_abstract_event_in_list(Event,Model,AbstractEvents), % this event is *NOT* a refinement of the proven one
796 debug_println(4,removing_discharged(Model,Event)),
797 retractall(discharged(Model,Event,_Name)),
798 member(model(Model),Sections), % only generate error message if the Model is also animated using b_get_animated_sections, see example EventBPrologPackages/ProofDirected/TestInvPreserv_M2_ko_mch.eventb
799 % (otherwise the refinement may well exist but has been filtered out by restricting the animation levels)
800 add_error(event_refinement,'An event does not refine an abstract event of the same name: ',Event:Model:RModel),
801 % This will could cause errors in the proof information usage !
802 %print(AbstractEvents),nl,
803 fail.
804 complete_discharged_info2 :- discharged_info_exists,
805 complete_discharged_info3(_Model,_Event,_Name).
806 complete_discharged_info3(InvNameModel,AbsEvent,Name) :-
807 ? b_get_abstract_events(EventInRefinement,_RefModel,AbstrEvents),
808 ? is_abstract_event_in_list(AbsEvent,InvNameModel,AbstrEvents), % Event in InvNameModel is an abstract event of EventInRefinement
809 %print(check(InvNameModel,Event, EventInRefinement,RefModel)),nl,
810 discharged(InvNameModel,AbsEvent,Name), % print(chck2(Model,Event,Name)),nl,
811 %InvNameModel:Name has been proven for AbsEvent *at all relevant* levels
812 \+ discharged(InvNameModel,EventInRefinement,Name),
813 \+ also_discharged(InvNameModel,EventInRefinement,Name),
814 % this invariant has not yet been marked as proven for EventInRefinement
815 debug_println(4,also_discharged_in_refinement(InvNameModel:Name,EventInRefinement,refined_from(AbsEvent))),
816 assertz(also_discharged(InvNameModel,EventInRefinement,Name)),
817 fail.
818
819 %abstract_event_of_calc(TopLevelEvent,RModel,Event,Model) :-
820 % b_get_abstract_events(TopLevelEvent,RModel,AbstrEvents),
821 % is_abstract_event_in_list(Event,Model,AbstrEvents) , print(abs(TopLevelEvent,RModel,Event,Model)),nl.
822
823 is_abstract_event_in_list(Event,Model,AbstractEvents) :-
824 member(b(rlevent(AEvent,AModel,_S,_P,_G,_Thm,_Act,_VW,_PW,_Unm,AbstractEvents2),_,_),AbstractEvents),
825 (Event=AEvent, Model=AModel;
826 is_abstract_event_in_list(Event,Model,AbstractEvents2)).
827
828 % get events that are refined by an event
829 b_get_abstract_events(Name,Section,AbsEvents) :-
830 ? b_get_machine_operation(Name,_R,_P,Body,_OType,_OpPos),
831 get_texpr_expr(Body,RLEVENT),
832 RLEVENT = rlevent(_Name,Section,_Stat,_Parameters,_Grd,_Thm,_Act,_VWit,_PWit,_Unmod,AbsEvents).
833
834 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
835
836 :- volatile b_operation_reads_output_variables/3, b_operation_cannot_modify_state/1.
837 :- dynamic b_operation_reads_output_variables/3, b_operation_cannot_modify_state/1.
838
839 % test if we have a query or skip operation which cannot modify the state
840 % (preconditions, assertions could still fail though !)
841 :- public b_operation_cannot_modify_state_calc/1.
842 b_operation_cannot_modify_state_calc(Event) :-
843 ? b_get_operation_normalized_read_write_info(Event,_ReadVariables,[]).
844
845 :- use_module(b_read_write_info, [get_accessed_vars/4]).
846 % check if classical B operation reads its output variables
847 :- public b_operation_reads_output_variables_calc/3.
848 b_operation_reads_output_variables_calc(Event,ReadOutputVariablesIds,ReadOutputTypedInfo) :-
849 ? b_get_machine_operation(Event,ResultTuple,_TParas,TBody,_OType,_Pos),
850 def_get_texpr_ids(ResultTuple,ResIds),
851 sort(ResIds,SResIds),
852 get_operation_info(Event,SubstitutionInfo),
853 member(reads_locals(Reads),SubstitutionInfo), % locals are either arguments or return output variables
854 ord_intersection(Reads,SResIds,ReadOutputVariablesIds),
855 ReadOutputVariablesIds \= [],
856 % now recompute the information based on TBody after ast_cleanup: typing predicates have been removed
857 get_accessed_vars(TBody,[],_,AllReadsAfterAstCleanup), % important to pass [] as local variables
858 ord_intersection(AllReadsAfterAstCleanup,ReadOutputVariablesIds,ReadOutputVariablesIds2),
859 ReadOutputVariablesIds2 \= [],
860 (get_preference(allow_operations_to_read_outputs,true), debug_mode(off) -> true
861 ; ajoin(['Operation ', Event, ' is possibly reading or not always assigning to output parameters: '],Msg),
862 add_message(bmachine,Msg,ReadOutputVariablesIds2,ResultTuple)
863 % Note: analysis is not always precise: /public_examples/B/NewSyntax/CallOperationInExprSimple2.mch
864 ),
865 findall(reads_result(Index,ID,Type),
866 (nth1(Index,ResultTuple,b(identifier(ID),Type,_)), ord_member(ID,ReadOutputVariablesIds2)),
867 ReadOutputTypedInfo).
868
869
870
871 :- volatile b_get_operation_normalized_read_write_info/3, b_get_operation_unchanged_variables/2.
872 :- dynamic b_get_operation_normalized_read_write_info/3, b_get_operation_unchanged_variables/2.
873
874
875 :- use_module(bsyntaxtree,[get_global_identifiers/1]).
876
877 :- public b_get_operation_normalized_read_write_info_calc/3.
878 /* compute Read and Written Variables by an operation */
879 b_get_operation_normalized_read_write_info_calc(Event,SortedReadVariables,SortedWrittenVariables) :-
880 get_global_identifiers(IS), % Note: find identifier uses was called before global sets precompiled
881 ? get_operation_info(Event,SubstitutionInfo),
882 (memberchk(modifies(WrittenVariables),SubstitutionInfo)
883 -> sort(WrittenVariables,SWV), % normally not necessary; just to be sure
884 ord_subtract(SWV,IS,SortedWrittenVariables)
885 ; print(no_modifies_info(Event)),nl,fail),
886 (memberchk(reads(ReadVariables),SubstitutionInfo)
887 -> sort(ReadVariables,SWR),
888 ord_subtract(SWR,IS,SortedReadVariables)
889 ; debug_println(9,no_reads_info(Event)),fail). % happens currently in Event-B !
890 %% , print(read_write_set(Event,ReadVariables,WrittenVariables)),nl.
891
892 :- public b_get_operation_unchanged_variables_calc/2.
893 b_get_operation_unchanged_variables_calc(Event,UnchangedVariables) :-
894 b_get_machine_variables(TVars),
895 def_get_texpr_ids(TVars,V),
896 sort(V,SAllVars),
897 ? b_get_operation_normalized_read_write_info(Event,_,WrittenVars),
898 ord_subtract(SAllVars,WrittenVars,UnchangedVariables).
899
900
901
902 :- volatile b_get_operation_non_det_modifies/2.
903 :- dynamic b_get_operation_non_det_modifies/2.
904 :- public b_get_operation_non_det_modifies_calc/2.
905 :- use_module(b_read_write_info,[get_nondet_modified_vars/3]).
906 % determine which variables are non-deterministically written by an operation
907 b_get_operation_non_det_modifies_calc(OpName,NonDetModifies) :-
908 ? b_get_machine_operation(OpName,Results,Parameters,Body,_OpType,_),
909 append(Results,Parameters,TLocalVars),
910 get_texpr_ids(TLocalVars,LocalVars),
911 get_nondet_modified_vars(Body,LocalVars,NonDetModifies).
912 b_get_operation_non_det_modifies_calc('$initialise_machine',NonDetModifies) :-
913 b_get_initialisation_from_machine(Body,_),
914 get_nondet_modified_vars(Body,[],NonDetModifies),debug_println(19,init_not_det_modifies(NonDetModifies)).
915
916
917 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
918
919
920 :- volatile b_get_all_used_filenames/1, b_get_main_filename/1, b_get_main_filenumber/1.
921 :- dynamic b_get_all_used_filenames/1. % can be used, e.g., for second argument of pos info field
922 :- dynamic b_get_main_filename/1. % can be used in above list; there is also specfile:currently_opened_file
923 :- dynamic b_get_main_filenumber/1. % the number of the main_file in the b_get_all_used_filenames list (useful for pos information)
924 b_get_all_used_filenames([]).
925
926 % add an additional filename and obtain its number
927 add_additional_filename(Filename,ResNr) :- functor(Filename,unknown,_),!,
928 format('Unknown additional filename: ~w~n',[Filename]),
929 ResNr = -1.
930 add_additional_filename(Filename,ResNr) :-
931 b_get_all_used_filenames(Fs),
932 nth1(Nr,Fs,Filename),!,
933 ResNr=Nr.
934 add_additional_filename(Filename,ResNr) :-
935 retract(b_get_all_used_filenames(Fs)),
936 length(Fs,Len),
937 append(Fs,[Filename],NewFs),
938 assert(b_get_all_used_filenames(NewFs)),
939 ResNr is Len+1,
940 format('Registering new filename ~w with number ~w~n',[Filename,ResNr]).
941
942 % add additional filename and add as default for parsercalls
943 set_additional_filename_as_parsing_default(Filename,NewNr,OldNr) :-
944 add_additional_filename(Filename,NewNr),
945 set_default_filenumber(NewNr,OldNr).
946 reset_filename_parsing_default(NewNr,OldNr) :- % reset default filenumber back
947 reset_default_filenumber(NewNr,OldNr).
948
949 b_load_machine_from_file(Filename) :- b_load_machine_from_file(Filename,[]).
950 b_load_machine_from_file(Filename,Options) :-
951 (debug_mode(on)
952 -> get_parser_version(Version),
953 format('Java Parser Version: ~w~n',[Version]) % used to be called unconditionally to be sure to catch error if java or BParser.jar not available; but now we do not want the Java startup time unless really necessary
954 ; true),
955 b_reset_filenames_and_numbers,
956 debug_stats(loading(Filename)),
957 catch(load_b_machine_as_term(Filename,Machine,Options),
958 parse_errors(Errors),
959 (add_all_perrors_in_context_of_used_filenames(Errors,parse_error),fail)),
960 b_load_machine_from_term(Filename,Machine).
961
962
963 % add parse errors in context of current machine and its filenames
964 add_all_perrors_in_context_of_used_filenames(Errors,TypeOfError) :- Errors\=[],
965 b_get_all_used_filenames(Filenames), Filenames \= [],
966 !,
967 add_all_perrors(Errors,Filenames,TypeOfError).
968 add_all_perrors_in_context_of_used_filenames(Errors,TypeOfError) :-
969 (Errors=[] -> true ; debug_println(19,'Unable to obtain filenames for parse errors, probably preparse_error')),
970 add_all_perrors(Errors,[],TypeOfError).
971
972
973 % a way to load .prob files directly
974 b_load_machine_probfile(Filename) :- b_load_machine_probfile(Filename,[]).
975 b_load_machine_probfile(Filename,Options) :- b_reset_filenames_and_numbers,
976 load_b_machine_probfile_as_term(Filename,Options,Machine),
977 Machine = complete_machine(_MainName,_,Filenames),
978 Filenames = [BFilename|_], % assume first file is the main file
979 b_load_machine_from_term(BFilename,Machine).
980
981
982 % a way to load form a list of Facts which would be found in the .prob file
983 b_load_machine_from_list_of_facts(Filename,ListOfFacts) :- % Filename only used below for find_main_file_name and later to find out about position infos if they are in the main file or not
984 load_b_machine_list_of_facts_as_term(ListOfFacts,Machine),
985 b_load_machine_from_term(Filename,Machine).
986
987
988 b_reset_filenames_and_numbers :-
989 set_all_used_filenames([]),
990 retractall(b_get_main_filename(_)),
991 retractall(b_get_main_filenumber(_)),
992 retractall(b_filenumber(_,_,_,_)).
993
994 set_all_used_filenames(AllFilenames) :-
995 retractall(b_get_all_used_filenames(_)),
996 assertz(b_get_all_used_filenames(AllFilenames)).
997
998
999 b_load_machine_from_term(Filename,complete_machine(MainName,Machines,Filenames)) :-
1000 b_reset_filenames_and_numbers, % call in case we call this predicate directly from outside
1001 !,
1002 assertz(b_get_main_filename(Filename)),
1003 set_all_used_filenames(Filenames),
1004 store_filenumbers(Filenames),
1005 (find_main_file_name(Nr,Filenames,Filename) -> assertz(b_get_main_filenumber(Nr))
1006 ; ajoin(['Main filename ', Filename, ' does not appear in filenames list: '],Msg),
1007 add_warning(bmachine,Msg,Filenames)
1008 ),
1009 %print(find_main_file_name(Nr,Filenames,Filename)),nl,
1010 check_valid_machine_name(MainName),
1011 debug_stats(analyse_hierarchy(MainName,Filename)),
1012 (rewrite_complete_machine(MainName,Machines,Machines1) -> true ; Machines1 = Machines),
1013 (analyse_hierarchy(MainName,Machines1)
1014 -> true ; add_error(b_load_machine,'Analyse Hierarchy failed'),fail),
1015 debug_stats(type_check(MainName,Filename)),
1016 b_set_machine(MainName,Machines1,Errors), % Typechecking
1017 debug_stats(checked_machine(MainName,Filename)),
1018 add_all_perrors(Errors,Filenames,type_error), % TO DO: use type_check as source as this may also generate warnings
1019 no_real_perror_occurred(Errors).
1020 b_load_machine_from_term(F,X) :- add_internal_error('Illegal machine: ',b_load_machine_from_term(F,X)),
1021 fail.
1022
1023 rewrite_complete_machine(MainName,[DefMachine],[NewMachine]) :-
1024 DefMachine=definition_file(Pos,Defs),
1025 %print(defs(Defs)),nl,
1026 % Generate virtual abstract machine when loading a .def DEFINITION file
1027 debug_println(19,creating_virtual_abstract_machine_for_definition_file),
1028 Header = machine_header(Pos,MainName,[]),
1029 NewMachine = abstract_machine(Pos,machine(Pos),Header,[Defs]).
1030
1031 check_valid_machine_name(Name) :- atom(Name),atom_codes(Name,Codes),
1032 invalid_chars(Invalid),
1033 ? (member(C,Codes),ord_member(C,Invalid)
1034 -> ajoin(['Machine name ', Name, ' contains illegal character: '],Msg),
1035 atom_codes(IChar,[C]),
1036 add_warning(bmachine,Msg,IChar)
1037 ; true),
1038 !.
1039 check_valid_machine_name(Name) :- add_internal_error('Illegal machine name:',check_valid_machine_name(Name)).
1040
1041 invalid_chars(".").
1042
1043 :- use_module(tools_matching,[codes_to_lower_case/2]).
1044 find_main_file_name(Nr,_Filenames,File) :- safe_absolute_file_name(File,AF),
1045 tools:get_modulename_filename(AF,TAF), tools:get_filename_extension(AF,ExtF),
1046 (ExtF = prob
1047 -> when(nonvar(EXT), member(EXT,[mch,ref,imp,tla,rmch])) % any machine extension is ok for .prob file
1048 ; EXT =ExtF),
1049 (b_filenumber(TAF,EXT,Nr,_) -> true
1050 ; atom_codes(TAF,TAFCodes), codes_to_lower_case(TAFCodes,Low),
1051 b_filenumber(TAF2,EXT,Nr,_),
1052 atom_codes(TAF2,C2), codes_to_lower_case(C2,Low)
1053 -> ajoin(['Case mis-match between main filename ',TAF,' and stored filename: '],Msg),
1054 % can happen on some file-systems which are case-insensitive or when transferring .prob files from one OS to another
1055 add_message(bmachine,Msg,TAF2)
1056 ).
1057
1058
1059
1060 % remember as facts all B filenames, their extension and their number
1061 :- volatile b_filenumber/4.
1062 :- dynamic b_filenumber/4.
1063 store_filenumbers(Filenames) :- retractall(b_filenumber(_,_,_,_)),
1064 store_filenumbers(Filenames,1).
1065 store_filenumbers([],_).
1066 store_filenumbers([H|T],Nr) :-
1067 safe_absolute_file_name(H,AbsFname),tools:get_modulename_filename(AbsFname,ModuleName),
1068 tools:get_filename_extension(AbsFname,ExtF),
1069 assertz(b_filenumber(ModuleName,ExtF,Nr,AbsFname)),
1070 debug_println(9,b_filenumber(ModuleName,ExtF,Nr,AbsFname)),
1071 N1 is Nr+1,
1072 store_filenumbers(T,N1).
1073
1074 portray_filenumbers :-
1075 format('~w : ~w : ~w (~w)~n',['Nr','ext','Name','Full path']),
1076 b_filenumber(ModuleName,ExtF,Nr,AbsFname),
1077 format('~w : ~w : ~w (~w)~n',[Nr,ExtF,ModuleName,AbsFname]),
1078 fail.
1079 portray_filenumbers.
1080
1081 :- use_module(tools,[same_file_name/2]).
1082 get_machine_file_number(Name,Ext,Nr,File) :-
1083 ? if(b_filenumber(Name,Ext,Nr,File),
1084 true,
1085 (b_filenumber(StoredName,Ext,Nr,File),
1086 % on Windows the capitalisation of the stored name maybe different from the name in machine
1087 same_file_name(Name,StoredName)
1088 )).
1089
1090
1091 :- use_module(tools,[safe_absolute_file_name/3, get_parent_directory/2]).
1092 % open a file relateive to the main B file
1093 b_absolute_file_name_relative_to_main_machine(File,AbsFileName) :-
1094 b_get_main_filename(MainFileName),
1095 get_parent_directory(MainFileName,Directory),
1096 % in Jupyter: MainFileName does not exist; SICStus then treats it as a directory
1097 safe_absolute_file_name(File,AbsFileName,[relative_to(Directory)]).
1098
1099 % call to clear all data stored for machine
1100 b_machine_clear :-
1101 b_machine_reset,
1102 b_reset_filenames_and_numbers.
1103
1104 :- use_module(btypechecker,[reset_typechecker/0]).
1105 :- use_module(b_global_sets,[b_clear_global_set_type_definitions/0]).
1106 :- use_module(bmachine_construction,[reset_bmachine_construction/0]).
1107 b_machine_reset :- % print(b_machine_reset),nl,
1108 retractall(machine(_,_)),
1109 retractall(discharged_theorem(_,_,_)),
1110 retractall(discharged_guard_strengthening(_,_,_,_)),
1111 retractall(discharged(_,_,_)),
1112 retractall(wd_po(_,_,_)),
1113 retractall(also_discharged(_,_,_)),
1114 reset_temp_predicate,
1115 retractall(b_machine_additional_property(_)),
1116 reset_typechecker,
1117 b_clear_global_set_type_definitions,
1118 reset_bmachine_construction,
1119 startup_precompiled. % change so that error messages generated if we call them
1120
1121 :- use_module(eventhandling,[register_event_listener/3]).
1122 :- register_event_listener(clear_specification,b_machine_clear,
1123 'Reset bmachine facts.').
1124
1125 % :- use_module(library(random)).
1126 :- use_module(preferences,[get_preference/2]).
1127
1128
1129
1130
1131 % precompiled
1132 :- volatile b_machine_name/1.
1133 :- dynamic b_machine_name/1.
1134 :- public b_machine_name_calc/1.
1135 b_machine_name_calc(Name) :-
1136 get_full_b_machine(Name,_).
1137
1138 b_get_animated_sections(Sections) :-
1139 get_section_from_current_machine(meta,MetaInfos),
1140 ( member(animated_sections(Sections), MetaInfos) -> true
1141 ; add_error(bmachine,'No animated sections available'), fail).
1142
1143 :- volatile b_get_named_machine_set/3.
1144 :- dynamic b_get_named_machine_set/3.
1145 :- public b_get_named_machine_set_calc/3.
1146 ?b_get_named_machine_set(Set,Members) :- b_get_named_machine_set(Set,_,Members).
1147 % precompiled: all enumerated sets with their elements (all in atomic form)
1148 b_get_named_machine_set_calc(Set,TExpr,Members) :-
1149 get_section_from_current_machine(enumerated_sets,Sets),
1150 get_section_from_current_machine(enumerated_elements,Elems),
1151 get_texpr_id(TExpr,Set),
1152 get_texpr_type(TExpr,set(Type)),
1153 get_texpr_type(TElem,Type),
1154 ? member(TExpr,Sets),
1155 findall(E, (member(TElem,Elems), get_texpr_id(TElem,E)), Members).
1156
1157 :- volatile b_enumerated_sets_precompiled/0.
1158 :- dynamic b_enumerated_sets_precompiled/0.
1159 :- public b_enumerated_sets_precompiled_calc/0.
1160 b_enumerated_sets_precompiled_calc :-
1161 b_check_and_precompile_enumerated_sets.
1162
1163 :- volatile b_get_machine_set/2.
1164 :- dynamic b_get_machine_set/2.
1165 :- public b_get_machine_set_calc/2.
1166 ?b_get_machine_set(Set) :- b_get_machine_set(Set,_).
1167 % precompiled: all deferred and enumerated sets (in atomic form)
1168 b_get_machine_set_calc(Set,TExpr) :-
1169 get_section_from_current_machine(deferred_sets,Sets),
1170 get_texpr_id(TExpr,Set),
1171 ? member(TExpr,Sets).
1172 b_get_machine_set_calc(Set,TExpr) :-
1173 ? b_get_named_machine_set(Set,TExpr,_).
1174
1175 :- volatile b_get_machine_constants/1, b_get_machine_all_constants/1, b_get_machine_variables/1, b_get_machine_variables_in_original_order/1, b_is_constant/2, b_is_variable/2, b_get_constant_variable_description/2.
1176 :- dynamic b_get_machine_constants/1, b_get_machine_all_constants/1, b_get_machine_variables/1, b_get_machine_variables_in_original_order/1, b_is_constant/2, b_is_variable/2, b_get_constant_variable_description/2.
1177 b_machine_has_constants :- b_get_machine_constants([_|_]).
1178 :- public b_get_machine_all_constants_calc/1.
1179 % precompiled: all constants (abstract and concrete) in typed form
1180 b_get_machine_all_constants_calc(Csts) :-
1181 findall(C,get_multi_sections([abstract_constants,concrete_constants],C),Csts).
1182 :- public b_get_machine_constants_calc/1.
1183 % precompiled: all constants (abstract and concrete) in typed form; except for constant_represented inside global set
1184 b_get_machine_constants_calc(Csts) :-
1185 findall(C,
1186 (get_multi_sections([abstract_constants,concrete_constants],C),
1187 get_texpr_id(C,CID),
1188 \+ b_get_constant_represented_inside_global_set(CID,_)), % ignore constants detected as enumerated set elements
1189 Csts).
1190
1191 b_machine_has_variables :- b_get_machine_variables([_|_]).
1192
1193 :- public b_get_machine_variables_in_original_order_calc/1.
1194 % precompiled: all variables (abstract and concrete) in typed form
1195 b_get_machine_variables_in_original_order_calc(Vars) :-
1196 findall(V,get_multi_sections([abstract_variables,concrete_variables],V),Vars).
1197
1198 :- public b_get_machine_variables_calc/1.
1199 % get variables in order suitable for ord_member and optimized update storing
1200 b_get_machine_variables_calc(SVars) :-
1201 b_get_machine_variables_in_original_order(Vars),
1202 sort(Vars,SVars).
1203
1204 get_nr_of_machine_variables(Nr) :- b_get_machine_variables(L), length(L,Nr).
1205 get_nr_of_machine_constants(Nr) :- b_get_machine_constants(L), length(L,Nr).
1206
1207 ?b_is_constant(C) :- b_is_constant(C,_).
1208 :- public b_is_constant_calc/2.
1209 % precompiled: all constants (abstract and concrete) in atomic form
1210 b_is_constant_calc(Cst,Type) :-
1211 b_get_machine_constants(Constants),
1212 get_texpr_id(Term,Cst),
1213 get_texpr_type(Term,Type),
1214 ? member(Term,Constants).
1215 b_is_variable(V) :- b_is_variable(V,_).
1216 :- public b_is_variable_calc/2.
1217 % precompiled: all variables (abstract and concrete) in atomic form
1218 b_is_variable_calc(Var,Type) :-
1219 b_get_machine_variables(Vars), % b_get_machine_variables_in_original_order
1220 get_texpr_id(Term,Var),
1221 get_texpr_type(Term,Type),
1222 ? member(Term,Vars).
1223 % look up elements in several sections of the machine
1224 get_multi_sections(Sections,Elem) :-
1225 ? member(Section,Sections),
1226 get_section_from_current_machine(Section,List),
1227 ? member(Elem,List).
1228
1229 :- public b_get_constant_variable_description_calc/2.
1230 % get value of description pragmas @desc for variables and constants:
1231 b_get_constant_variable_description_calc(ID,Desc) :-
1232 (b_get_machine_constants(L) ; b_get_machine_variables(L)),
1233 get_texpr_id(Term,ID),
1234 ? member(Term,L),
1235 get_texpr_description(Term,Desc).
1236
1237
1238 :- use_module(probsrc(tools_strings), [atom_prefix/2]).
1239 % check if a constant or variable is annotated for memoization:
1240 constant_variable_marked_as_memo(ID) :- b_get_constant_variable_description(ID,MEMO),
1241 atom(MEMO),
1242 atom_prefix(memo,MEMO). % also allow /*@desc memoize */ , ...
1243
1244 % check if a constant or variable is annotated for expansion using @desc expand
1245 constant_variable_marked_as_expand(ID) :- b_get_constant_variable_description(ID,EXPAND), EXPAND=expand.
1246
1247
1248 :- volatile b_get_invariant_from_machine/1,
1249 b_get_linking_invariant_from_machine/1,
1250 b_get_properties_from_machine/1,
1251 b_get_static_assertions_from_machine/1,
1252 b_extract_values_clause_assignment/3,
1253 b_get_unproven_static_assertions_from_machine/1,
1254 b_get_dynamic_assertions_from_machine/1,
1255 b_get_unproven_dynamic_assertions_from_machine/1,
1256 b_get_assertions_from_main_machine/2,
1257 b_get_initialisation_from_machine/2,
1258 b_get_machine_operation/6,b_top_level_operation/1,
1259 b_get_machine_operation_for_animation/7,
1260 b_is_operation_name/1,
1261 b_get_promoted_machine_operations/1.
1262 :- dynamic b_get_invariant_from_machine/1,
1263 b_get_linking_invariant_from_machine/1,
1264 b_get_properties_from_machine/1,
1265 b_get_static_assertions_from_machine/1,
1266 b_extract_values_clause_assignment/3,
1267 b_get_unproven_static_assertions_from_machine/1,
1268 b_get_dynamic_assertions_from_machine/1,
1269 b_get_unproven_dynamic_assertions_from_machine/1,
1270 b_get_assertions_from_main_machine/2,
1271 b_get_initialisation_from_machine/2,
1272 b_get_machine_operation/6,b_top_level_operation/1,
1273 b_get_machine_operation_for_animation/7,
1274 b_is_operation_name/1,
1275 b_get_promoted_machine_operations/1.
1276
1277 :- public b_get_invariant_from_machine_calc/1.
1278 % precompiled: typed invariant (a predicate)
1279 b_get_invariant_from_machine_calc(Inv) :-
1280 get_section_from_current_machine(invariant,Inv).
1281
1282 :- public b_get_linking_invariant_from_machine_calc/1.
1283 % precompiled: typed linking invariant (a predicate)
1284 b_get_linking_invariant_from_machine_calc(Inv) :-
1285 get_section_from_current_machine(linking_invariant,Inv).
1286
1287 :- public b_get_properties_from_machine_calc/1.
1288 % precompiled: typed properties (a predicate)
1289 b_get_properties_from_machine_calc(SortedProp) :-
1290 get_section_from_current_machine(properties,Prop),
1291 (sort_properties(Prop,SortedProp) -> true %(Prop=SortedProp->true ; print(sorted(SortedProp)))
1292 ; add_error(sort_properties,'sort_properties failed: ',Prop),
1293 SortedProp=Prop).
1294
1295 sort_properties(Prop,SortedProp) :- % print(sort_properties),nl,statistics(runtime, [R1,_]),
1296 weigh_properties(Prop,1,_,[],SProp),
1297 % statistics(runtime, [R2,_]), RDiff is R2-R1,print(done_weigh(RDiff,SProp)),nl,
1298 sort(SProp,SSProp),
1299 % statistics(runtime, [R3,_]), RDiff2 is R3-R2,print(done_sort(RDiff2)),nl,
1300 remove_weights(SSProp,PropList),
1301 conjunct_predicates(PropList,SortedProp).
1302 % translate:print_bexpr(SortedProp).
1303
1304 remove_weights([],[]).
1305 remove_weights([prop(_W,_Nr,E)|T],[E|RT]) :- remove_weights(T,RT).
1306
1307 weigh_properties(Pred,Nr,ONr,InL,OutL) :-
1308 decompose_conjunct(Pred,LHS,RHS), % will propagate labels down to conjuncts LHS,RHS
1309 !,
1310 weigh_properties(LHS,Nr,N1,InL,L2),
1311 weigh_properties(RHS,N1,ONr,L2,OutL).
1312 weigh_properties(b(Pred,S,I),Nr,N1,T,[prop(Weight,Nr,b(Pred,S,I))|T]) :-
1313 N1 is Nr+1,
1314 ? (member(contains_wd_condition,I) -> Weight=32000 % do not move properties with WD info
1315 ; weigh_properties2(Pred,Weight)).
1316 % translate:print_bexpr(b(Pred,S,I)), print(' WEIGHT: '), print(Weight),nl
1317
1318 weigh_properties2(truth,W) :- !, W=1.
1319 weigh_properties2(falsity,W) :- !, W=1.
1320 weigh_properties2(equal(L,R),W) :- weigh_term(L,W1), !,
1321 ( weigh_term(R,W2) -> W is W1*W2
1322 ; W is 3200).
1323 % ; W is W1*20). %causes issue with ParityFunction test
1324 %weigh_properties2(equal(_,R),W) :- weigh_term(R,W2), !, W is W2*20.
1325 weigh_properties2(SOp,W) :- comparison(SOp,L,R),!,
1326 ( (weigh_term(L,W1), weigh_term(R,W2))
1327 -> W is 7+W1+W2 % try and give things like x>10 priority over x>y (to overcome CLP(FD) limitations)
1328 ; W=10).
1329 weigh_properties2(partition(LHS,RHS),W) :- weigh_term(LHS,W1), l_weigh_term(RHS,W2), !, W is W1*W2.
1330 ?weigh_properties2(not_equal(L,R),W) :- ((id(L),empty(R)) ; (id(R),empty(L))),!, W=1.
1331 weigh_properties2(not_equal(L,R),W) :- weigh_term(L,W1), weigh_term(R,W2),!,
1332 W is 20+W1*W2.
1333 weigh_properties2(_Rest,W) :- W=32000.
1334
1335 comparison(less(L,R),L,R).
1336 comparison(less_equal(L,R),L,R).
1337 comparison(greater(L,R),L,R).
1338 comparison(greater_equal(L,R),L,R).
1339
1340
1341 id(b(identifier(_),_,_)).
1342 empty(b(empty_set,_,_)).
1343 empty(b(empty_sequence,_,_)).
1344
1345 l_weigh_term([],0).
1346 l_weigh_term([H|T],R) :- l_weigh_term(T,TR), weigh_term(H,TH), R is TH+TR.
1347
1348 weigh_term(b(T,_,_),R) :- (weigh_term2(T,R) -> true ; fail). %R=20).
1349
1350 weigh_term2(value(_),1).
1351 weigh_term2(boolean_true,1).
1352 weigh_term2(boolean_false,1).
1353 weigh_term2(empty_set,1).
1354 weigh_term2(empty_sequence,1).
1355 weigh_term2(integer(_),1).
1356 weigh_term2(min_int,1).
1357 weigh_term2(max_int,1).
1358 weigh_term2(string(_),1).
1359 weigh_term2(real(_),1).
1360 weigh_term2(bool_set,2).
1361 weigh_term2(identifier(_),2).
1362 weigh_term2(set_extension(_),3).
1363 weigh_term2(integer_set(_),3).
1364 weigh_term2(interval(L,R),W) :- weigh_term(L,WL), weigh_term(R,WR), W is WL*WR.
1365
1366
1367
1368 b_machine_has_constants_or_properties :-
1369 (b_machine_has_constants -> true
1370 ; (b_get_properties_from_machine(Prop)), \+ is_truth(Prop)).
1371
1372 b_get_machine_operation_parameter_types(OpName,ParTypes) :-
1373 b_get_machine_operation_typed_parameters(OpName,Parameters),
1374 maplist(get_texpr_type,Parameters,ParTypes).
1375
1376 b_get_machine_operation_typed_parameters(Operation,Res) :-
1377 if(b_get_machine_operation_typed_parameters_aux(Operation,Paras),Res=Paras,
1378 (add_internal_error('Cannot get parameters: ',b_get_machine_operation_typed_parameters(Operation,Res)),fail)).
1379 % also recognises SETUP_CONSTANTS & INITIALISE_MACHINE
1380 b_get_machine_operation_typed_parameters_aux('$setup_constants',Constants) :-
1381 b_machine_has_constants_or_properties,
1382 b_get_machine_constants(Constants).
1383 b_get_machine_operation_typed_parameters_aux('$initialise_machine',Variables) :-
1384 b_get_machine_variables(Variables).
1385 b_get_machine_operation_typed_parameters_aux(OpName,Parameters) :-
1386 b_get_machine_operation(OpName,_R,Parameters,_Body,_OType,_OpPos).
1387
1388 b_get_machine_operation_parameter_names('@INITIALISATION',ParaNames) :- % for Tcl/Tk
1389 b_get_machine_operation_parameter_names('$initialise_machine',ParaNames).
1390 b_get_machine_operation_parameter_names('@PROPERTIES',ParaNames) :- % for Tcl/Tk
1391 b_get_machine_operation_parameter_names('$setup_constants',ParaNames).
1392 b_get_machine_operation_parameter_names(OpName,ParaNames) :-
1393 b_get_machine_operation_typed_parameters(OpName,Parameters),
1394 get_texpr_ids(Parameters,ParaNames).
1395
1396 b_get_machine_operation_typed_results('$setup_constants',[]).
1397 b_get_machine_operation_typed_results('$initialise_machine',[]).
1398 b_get_machine_operation_typed_results(OpName,Results) :-
1399 b_get_machine_operation(OpName,Results,_Parameters,_Body,_OType,_OpPos).
1400
1401 b_get_machine_operation_result_names('$setup_constants',[]).
1402 b_get_machine_operation_result_names('$initialise_machine',[]).
1403 b_get_machine_operation_result_names(OpName,ResultNames) :-
1404 b_get_machine_operation(OpName,Results,_Parameters,_Body,_OType,_OpPos),
1405 get_texpr_ids(Results,ResultNames).
1406
1407 b_get_machine_operation(Name,Results,Parameters,Body) :-
1408 ? b_get_machine_operation(Name,Results,Parameters,Body,_OType,_OpPos).
1409
1410 :- public b_get_assertions_from_main_machine_calc/2.
1411 b_get_assertions_from_main_machine_calc(static,FProp) :-
1412 ((b_get_static_assertions_from_machine(Prop),
1413 exclude(is_not_main_assertion,Prop,FProp)) -> true
1414 ; add_error(bmachine,'b_get_assertions_from_main_machine_calc static fails'), FProp=[]).
1415 b_get_assertions_from_main_machine_calc(dynamic,FProp) :-
1416 ((b_get_dynamic_assertions_from_machine(Prop),
1417 exclude(is_not_main_assertion,Prop,FProp)) -> true
1418 ; add_error(bmachine,'b_get_assertions_from_main_machine_calc dynamic fails'), FProp=[]).
1419 is_not_main_assertion(Assertion) :-
1420 get_texpr_pos(Assertion,Pos),
1421 error_manager:position_is_not_in_main_file(Pos).
1422
1423 % get nr of assertions and nr of main assertions for static/dynamic
1424 b_get_assertion_count(StaticOrDynamic,NrAll,NrMain) :-
1425 ? b_get_assertions(all,StaticOrDynamic,A), length(A,NrAll),
1426 b_get_assertions_from_main_machine(StaticOrDynamic,MA),length(MA,NrMain).
1427
1428 b_get_assertions(main,Mode,Ass) :- !,
1429 b_get_assertions_from_main_machine(Mode,Ass).
1430 b_get_assertions(specific(Label),Mode,LabelAss) :- !,
1431 b_get_assertions(all,Mode,Ass),
1432 %maplist(get_texpr_label,Ass,Labels), print(labels(Labels)),nl,
1433 include(has_label(Label),Ass,LabelAss),
1434 (LabelAss=[] -> ajoin(['No ',Mode,' assertion has label: '],Msg),
1435 add_warning(b_get_assertions,Msg,Label) ; true).
1436 b_get_assertions(_,static,Ass) :- b_get_static_assertions_from_machine(Ass).
1437 b_get_assertions(_,dynamic,Ass) :- b_get_dynamic_assertions_from_machine(Ass).
1438 b_main_machine_has_no_assertions :-
1439 b_get_assertions_from_main_machine(static,[]),
1440 b_get_assertions_from_main_machine(dynamic,[]).
1441
1442
1443 %has_label(Label,Expr) :- get_texpr_label(Expr,Label1), format('Labels ~w =? ~w~n',[Label1,Label]), fail.
1444 has_label(Label,Expr) :- get_texpr_label(Expr,Label).
1445
1446 :- public b_get_static_assertions_from_machine_calc/1.
1447 % precompiled: typed assertions (a list of predicates)
1448 b_get_static_assertions_from_machine_calc(Prop) :-
1449 get_section_from_current_machine(assertions,Prop1),
1450 exclude(predicate_uses_variables,Prop1,Prop),!.
1451 b_get_static_assertions_from_machine_calc(Prop) :-
1452 add_error(bmachine,'b_get_static_assertions_from_machine_calc fails'), Prop=[].
1453
1454 :- dynamic b_machine_has_static_assertions/0.
1455 :- public b_machine_has_static_assertions_calc/0.
1456 b_machine_has_static_assertions_calc :-
1457 b_get_static_assertions_from_machine([_|_]).
1458
1459 :- public b_get_unproven_static_assertions_from_machine_calc/1.
1460 b_get_unproven_static_assertions_from_machine_calc(FAssertions) :-
1461 b_get_static_assertions_from_machine(Assertions),
1462 filter_out_proven_assertions(Assertions,FAssertions),!.
1463 b_get_unproven_static_assertions_from_machine_calc(Prop) :-
1464 add_error(bmachine,'b_get_unproven_static_assertions_from_machine_calc fails'), Prop=[].
1465
1466 filter_out_proven_assertions([],[]).
1467 filter_out_proven_assertions([A1|T],R) :-
1468 (is_discharged_assertion(A1)
1469 -> R = TR %, print('Proven: '), translate:print_bexpr(A1),nl
1470 ; R = [A1|TR]),
1471 filter_out_proven_assertions(T,TR).
1472
1473 :- public b_get_dynamic_assertions_from_machine_calc/1.
1474 b_get_dynamic_assertions_from_machine_calc(Prop) :-
1475 get_section_from_current_machine(assertions,Prop1),
1476 include(predicate_uses_variables,Prop1,Prop),!.
1477 b_get_dynamic_assertions_from_machine_calc(Prop) :-
1478 add_error(bmachine,'b_get_dynamic_assertions_from_machine_calc fails'), Prop=[].
1479
1480
1481 :- dynamic b_machine_has_dynamic_assertions/0.
1482 :- public b_machine_has_dynamic_assertions_calc/0.
1483 b_machine_has_dynamic_assertions_calc :-
1484 b_get_dynamic_assertions_from_machine([_|_]).
1485
1486 b_machine_has_assertions :- (b_machine_has_static_assertions -> true ; b_machine_has_dynamic_assertions).
1487
1488 b_machine_has_unproven_assertions :-
1489 b_get_unproven_dynamic_assertions_from_machine([_|_]) -> true
1490 ; b_get_unproven_static_assertions_from_machine([_|_]).
1491
1492
1493 get_all_assertions_from_machine(Assertions) :-
1494 findall(A,((SD=static;SD=dynamic),get_assertions_from_machine(SD,SS),member(A,SS)),Assertions).
1495
1496 get_assertions_from_machine(Type,Assertions) :-
1497 ( Type=(dynamic) ->
1498 (get_preference(use_po,true)
1499 -> b_get_unproven_dynamic_assertions_from_machine(Assertions)
1500 ; b_get_dynamic_assertions_from_machine(Assertions)
1501 )
1502 ; Type=(static) ->
1503 (get_preference(use_po,true)
1504 -> b_get_unproven_static_assertions_from_machine(Assertions)
1505 ; b_get_static_assertions_from_machine(Assertions)
1506 )
1507 ),
1508 Assertions = [_|_].
1509
1510 :- public b_get_unproven_dynamic_assertions_from_machine_calc/1.
1511 b_get_unproven_dynamic_assertions_from_machine_calc(FAssertions) :-
1512 b_get_dynamic_assertions_from_machine(Assertions),
1513 filter_out_proven_assertions(Assertions,FAssertions),!.
1514 b_get_unproven_dynamic_assertions_from_machine_calc(Prop) :-
1515 add_error(bmachine,'b_get_unproven_dynamic_assertions_from_machine_calc fails'), Prop=[].
1516
1517 predicate_uses_variables(Pred) :-
1518 b_get_machine_variables(Vars),
1519 get_texpr_ids(Vars,Ids),
1520 list_to_ord_set(Ids,OrdVars),
1521 find_identifier_uses(Pred,[],UsedVars),
1522 list_to_ord_set(UsedVars,OrdUsedVars),
1523 ord_intersect(OrdVars,OrdUsedVars).
1524
1525 :- public b_get_initialisation_from_machine_calc/2.
1526 % precompiled: typed initialisation (a substitution)
1527 b_get_initialisation_from_machine_calc(Init,OType) :-
1528 get_section_from_current_machine(initialisation,Init),
1529 ( get_texpr_expr(Init,rlevent(_Name,_Section,_Status,Params,_Guard,_Theorems,_Actions,_VWitnesses,_PWitnesses,_Unmod,_AbstractEvents)) ->
1530 get_operation_type(Init,'INITIALISATION',Params,OType)
1531 ;
1532 OType = classic).
1533 % precompiled: operations, Name is in atomic form, Results and Parameters are lists
1534 % of typed identifiers, Body is a typed substitution
1535
1536 :- volatile b_machine_operation_names_in_reverse_order/1.
1537 :- dynamic b_machine_operation_names_in_reverse_order/1.
1538 % a list of operation names in reverse order; this way we can randomize the
1539 % generation of the successor states
1540 precompile_operation_names_in_reverse_order :-
1541 retractall(b_machine_operation_names_in_reverse_order(_)),
1542 ? b_get_machine_operation(Name,_Results,_Parameters,_Body,_OType,_OpPos),
1543 asserta(b_machine_operation_names_in_reverse_order(Name)),
1544 fail.
1545 precompile_operation_names_in_reverse_order.
1546
1547 :- use_module(specfile, [animation_minor_mode/1, classical_b_mode/0]).
1548 :- use_module(extrasrc(b_expression_sharing),[cse_optimize_substitution/2]).
1549 :- public b_get_machine_operation_calc/6.
1550 b_get_machine_operation_calc(Name,Results,Parameters,NewBody,OType,OpPos) :-
1551 %well_def_analyser:get_hyps_for_top_level_operations([],Hyps),
1552 is_ground(Name,NameGround),
1553 get_section_from_current_machine(operation_bodies,Ops),
1554 get_texpr_expr(Op,operation(TId,Results,Parameters,Body)),
1555 get_texpr_id(TId,op(Name)),
1556 ? member(Op,Ops),
1557 % remove choicepoints when name was ground
1558 (NameGround==ground -> !; true),
1559 get_operation_type(Op,Name,Parameters,OType),
1560 (get_texpr_pos(TId,OpPos) -> true ; OpPos = unknown),
1561 ( get_preference(use_common_subexpression_also_for_substitutions,true),
1562 get_preference(use_common_subexpression_elimination,true),
1563 \+ animation_minor_mode(eventb) % CSE_SUBST not yet available for Event-B
1564 -> debug_println(19,applying_cse_to(Name)),
1565 cse_optimize_substitution(Body,OpBody)
1566 ; OpBody = Body),
1567 NewBody=OpBody.
1568
1569 b_get_machine_operation_signature(Name,SignatureStr) :-
1570 b_get_machine_operation_calc(Name,Results,Parameters,_,_,_),
1571 get_texpr_ids(Parameters,PIds),
1572 ajoin_with_sep(PIds,',',Args),
1573 (Results = []
1574 -> ajoin([Name,'(',Args,')'],SignatureStr)
1575 ; get_texpr_ids(Results,RIds),
1576 ajoin_with_sep(RIds,',',Res),
1577 ajoin([Res,'<--',Name,'(',Args,')'],SignatureStr)
1578 ).
1579
1580 %well_def_analyser:transform_machine_operation(Name,Results,Parameters,OpBody,Hyps,[create_not_discharged_msg(message)],NewBody).
1581 get_operation_type([],_Name,_Parameters,classic).
1582 get_operation_type(Op,Name,Parameters,OType) :-
1583 get_texpr_info(Op,Info),
1584 ? ( member(eventb(_),Info) ->
1585 OType=eventb_operation(SortedChangeSet,Ps,OpPattern),
1586 ? member(modifies(ChangeSet),Info),!,
1587 sort(ChangeSet,SortedChangeSet), % maybe not necessary ?
1588 same_length(Parameters,Ps),
1589 OpPattern =.. [Name|Ps]
1590 ;
1591 OType=classic).
1592
1593 :- volatile get_operation_info/2, get_operation_description_template_expr/2.
1594 :- dynamic get_operation_info/2, get_operation_description_template_expr/2.
1595 :- public get_operation_info_calc/2, get_operation_description_template_expr_calc/2.
1596 % precompiled: operation infos
1597 get_operation_info_calc(OpName,Info) :-
1598 get_section_from_current_machine(operation_bodies,Ops),
1599 create_texpr(operation(TId,_Results,_Parameters,_Body),_,Info1,TOp), % rlevent()
1600 get_texpr_id(TId,op(OpName)),
1601 ? member(TOp,Ops),
1602 (get_texpr_description(TOp,Desc) % description_operation
1603 -> Info = [description(Desc)|Info1], debug_format(19,'Operation ~w has description: ~w~n',[OpName,Desc])
1604 ; Info=Info1).
1605
1606 b_get_operation_description(OpName,Desc) :-
1607 get_operation_info(OpName,Infos),
1608 member(description(Desc),Infos).
1609
1610 % get a typed string expression that can compute an operation description (based on vars, paras, ...)
1611 get_operation_description_template_expr_calc(OpName,TemplateStringExpr) :-
1612 get_error_context(Context),
1613 call_cleanup(get_op_desc_template_expr_calc2(OpName,TemplateStringExpr),restore_error_context(Context)).
1614
1615 get_op_desc_template_expr_calc2(OpName,TemplateStringExpr) :-
1616 ? get_operation_info(OpName,Infos),
1617 member(description(Desc),Infos),
1618 get_info_pos(Infos,OpPos), % Unfortunately this is the entire position from beginning of operation to desc label */
1619 atom(Desc),
1620 atom_codes(Desc,DescCodes),
1621 set_error_context(checking_context('Checking description template for operation: ',OpName)),
1622 transform_string_template(DescCodes,OpPos,RawTemplateExpr),
1623 %translate:print_raw_bexpr(RawTemplateExpr),nl,
1624 GenerateParseErrors=true,
1625 get_machine_operation_typing_scope(OpName,Scope,[]),
1626 b_type_only(RawTemplateExpr,Scope,Type,TemplateStringExpr,GenerateParseErrors),
1627 (debug_mode(off) -> true
1628 ; format('Template description expression for operation ~w:~n ',[OpName]),
1629 translate:print_bexpr(TemplateStringExpr),nl
1630 ),
1631 (Type=string -> true ; add_internal_error('Not string type:',Type)).
1632
1633
1634 :- public b_top_level_operation_calc/1.
1635 % precompiled: operation names (in atomic form) of top-level operations (promoted operations)
1636 b_top_level_operation_calc(Name) :-
1637 is_ground(Name,NameGround),
1638 get_section_from_current_machine(promoted,Promoted),
1639 get_texpr_id(TId,op(Name)),
1640 ? member(TId,Promoted),
1641 (NameGround==ground -> !; true).
1642 :- public b_get_promoted_machine_operations_calc/1.
1643 b_get_promoted_machine_operations_calc(Ops) :-
1644 get_section_from_current_machine(promoted,Ops).
1645
1646 :- volatile b_top_level_feasible_operation/1.
1647 :- dynamic b_top_level_feasible_operation/1.
1648 :- public b_top_level_feasible_operation_calc/1.
1649 % filter out operations which are commented out statically by using 1=2 or similar in guard
1650 ?b_top_level_feasible_operation_calc(Name) :- b_top_level_operation(Name),
1651 b_get_machine_operation(Name,_,_,Body,_,_Pos),
1652 \+ infeasible_tsubst(Body).
1653 % TO DO: investigate how to link up with cbc feasibility analysis
1654
1655 infeasible_tsubst(b(S,_,_)) :- infeasible_subst(S).
1656 infeasible_subst(precondition(G,_)) :- is_falsity(G).
1657 infeasible_subst(select([b(select_when(G,_),_,_)])) :- is_falsity(G).
1658 infeasible_subst(any(_,G,_)) :- is_falsity(G).
1659
1660 % this succeeds not just for top-level operations
1661 %b_is_operation_name(Name) :- b_get_machine_operation(Name,_,_,_,_,_). is slower
1662 :- public b_is_operation_name_calc/1.
1663 b_is_operation_name_calc(Name) :-
1664 ? b_get_machine_operation(Name,_,_,_,_,_).
1665
1666 b_get_operation_pos(Name,Pos) :-
1667 b_get_machine_operation(Name,_,_,_,_,Pos).
1668
1669 b_get_operation_variant(Name,ConvOrAnt,Variant) :-
1670 ? b_get_machine_operation(Name,_,_,TBody),
1671 get_texpr_expr(TBody,Body),
1672 Body = rlevent(Name,_Section,Status,
1673 _Params,_Guard,_Theorems,_Actions,_VWitnesses,_PWitnesses,_Unmod,_AbstractEvents),
1674 % TO DO: look maybe higher up in refinement hierarchy
1675 get_texpr_expr(Status,S),
1676 functor(S,ConvOrAnt,1),
1677 (ConvOrAnt = convergent ; ConvOrAnt = anticipated),
1678 arg(1,S,Variant).
1679
1680 b_machine_has_operations :-
1681 (b_is_operation_name(_) -> true).
1682 % -----------------------------
1683
1684
1685 % the names of definitions which have a given Prefix,
1686 % Type is expression or predicate, Name is an atomic name
1687 b_definition_prefixed(Type,Prefix,Suffix,Name,Pos) :-
1688 safe_atom_chars(Prefix,PrefixChars,b_definition_prefixed1),
1689 append(PrefixChars,SuffixChars,FullChars),
1690 (ground(Suffix) -> safe_atom_chars(Suffix,SuffixChars,b_definition_prefixed2),
1691 safe_atom_chars(Name,FullChars,b_definition_prefixed3)
1692 ; true),
1693 ? b_get_definition_with_pos(Name,Type,Pos,_,_,_),
1694 safe_atom_chars(Name,FullChars,b_definition_prefixed4),
1695 safe_atom_chars(Suffix,SuffixChars,b_definition_prefixed5).
1696
1697 % TODO: should we also look for theory direct definitions for Event-B models?
1698 % :- use_module(bmachine_eventb,[stored_operator_direct_definition/8]).
1699 % stored_operator_direct_definition(Id,_Proj,_Thy,Parameters,_Def,_WD,_TP,_Kind),
1700 % or add auxiliary definition files for Event-B models
1701
1702
1703 % get definitions in alphabetical order of name:
1704 % predictable order is relevant for SVG_OBJECTS to know which objects are on top of each other
1705 b_sorted_b_definition_prefixed(Type,DEFPREFIX,DefName,DefPos) :-
1706 sorted_list_of_defs(Type,DEFPREFIX,SortedList),
1707 member(def(DefName,DefPos),SortedList).
1708 sorted_list_of_defs(Type,DEFPREFIX,SortedList) :-
1709 findall(def(DefName,DefPos),
1710 b_definition_prefixed(Type,DEFPREFIX,_Tail,DefName,DefPos),
1711 List),
1712 sort(List,SortedList).
1713
1714 :- use_module(bmachine_construction,[type_open_formula/8]).
1715 type_check_definitions :-
1716 temporary_set_preference(allow_untyped_identifiers,true_with_string_type,CHNG), % we may not have all identifiers visible
1717 get_error_context(Context),
1718 call_cleanup(type_check_definitions2,restore_error_context(Context)),
1719 reset_temporary_preference(allow_untyped_identifiers,CHNG).
1720 type_check_definitions2 :-
1721 get_preference(type_check_definitions,true),
1722 full_b_machine(Machine),
1723 b_get_definition_with_pos(Name,Type,DefPos,Args,RawExpr,_Deps),
1724 % TO DO: do not re-analyse definitions already analysed for ANIMATION_FUNCTION,...
1725 (Type = predicate ; Type=expression), % can we also allow substitutions ?
1726 debug_format(9,'Type checking DEFINITION ~w~n',[Name]),
1727 set_error_context(checking_context('Type checking DEFINITION: ',Name)),
1728 Scope = [variables], % prob_ids(visible),
1729 %type_with_errors(RawExpr,Scope,_,_TExpr),
1730 AllowNewIds=true,
1731 % TO DO: improve solution below, e.g., delete Args from visible variables or rename Args to fresh ids!
1732 (Args=[] -> RawExpr2=RawExpr
1733 ; Type=predicate -> RawExpr2 = exists(none,Args,conjunct(none,truth(none),RawExpr)) % wrap Args into quantifier, avoid clash with variables,... ; conjunct used to avoid warnings about body of exists
1734 ; RawExpr2=exists(none,Args,equal(none,RawExpr,RawExpr)) % TODO: better solution to avoid duplicating RawExpr
1735 ),
1736 (type_open_formula(RawExpr2,Scope,AllowNewIds,Machine,FType,Identifiers,_TPred,Errors) % maybe no need to run cleanup?
1737 -> Errors = [_|_],
1738 format('Error for DEFINITION ~w of type ~w over identifiers ~w~n',[Name,FType,Identifiers]),
1739 add_all_perrors_in_context_of_used_filenames(Errors,definition_type_error),
1740 fail
1741 % TO DO: check for local clashes?
1742 ; add_error(bmachine,'Type checking DEFINITION failed: ',Name,DefPos)
1743 ),
1744 fail.
1745 type_check_definitions2 :- debug_format(9,'Finished type checking DEFINITIONs~n',[]).
1746
1747 b_get_definition(Name,DefType,Args,RawExpr,Deps) :-
1748 ? b_get_definition_with_pos(Name,DefType,_DefPos,Args,RawExpr,Deps).
1749
1750 :- public portray_defs/0. % debugging utility
1751 portray_defs :-
1752 b_get_definition_with_pos(Name,DefType,DefPos,_Args,_RawExpr,_),
1753 add_message(bmachine,'DEFINITION: ',Name:DefType,DefPos),fail.
1754 portray_defs.
1755
1756 b_get_definition_with_pos(Name,DefType,DefPos,Args,RawExpr,Deps) :- %print(get_def(Name)),nl,
1757 get_section_from_current_machine(definitions,Defs),
1758 ? member(definition_decl(Name,DefType,DefPos,Args,RawExpr,Deps),Defs).
1759 % the next calls get typed definitions without parameters:
1760 % (To treat definitions with parameters one would have to add the parameters to the type environment, see type_check_definitions2)
1761 b_get_typed_predicate_definition(Name,Scope,ResTExpr) :-
1762 ? b_get_definition(Name,predicate,[],RawExpr,_Deps),
1763 type_with_errors_in_context(RawExpr,Scope,_,TExpr,machine_context),
1764 ResTExpr=TExpr. % Do unification after to not prevent generation of type errors.
1765 b_get_typed_expression_definition(Name,Scope,ResTExpr) :-
1766 b_get_definition(Name,expression,[],RawExpr,_Deps),
1767 type_with_errors_in_context(RawExpr,Scope,_,TExpr,machine_context),
1768 ResTExpr=TExpr. % Do unification after to not prevent generation of type errors, e.g., test 1691
1769 b_get_true_expression_definition(Name) :-
1770 b_get_typed_expression_definition(Name,[variables],PF),
1771 PF = b(boolean_true,boolean,_).
1772 %b_get_typed_subst_definition(Name,Scope,Parameters,TExpr) :-
1773 % temporary_set_preference(allow_local_operation_calls,true,CHNG),
1774 % b_get_definition(Name,substitution,Parameters,RawExpr,_Deps),
1775 % type_with_errors(RawExpr,[operation_bodies|Scope],_,TExpr), % need to remove variables to avoid clash warnings
1776 % reset_temporary_preference(allow_local_operation_calls,CHNG).
1777 b_get_typed_definition(Name,Scope,TExpr) :-
1778 ? b_get_definition(Name,_DefType,[],RawExpr,_Deps),
1779 type_with_errors_in_context(RawExpr,Scope,_,TExpr,machine_context).
1780
1781 type_with_errors(RawExpr,Scope,Type,TExpr) :-
1782 type_with_errors_in_context(RawExpr,Scope,Type,TExpr,not_in_machine_context([])).
1783 type_with_errors_in_context(RawExpr,Scope,Type,TExpr,Context) :- % print(scope(Scope)),nl,
1784 b_type_expression(RawExpr,Scope,Type,TExpr,Errors),!,
1785 (Context=not_in_machine_context(Filenames)
1786 -> add_all_perrors(Errors,Filenames,type_expression_error) % [] for REPL, or JSON file for VisB
1787 ; add_all_perrors_in_context_of_used_filenames(Errors,type_expression_error)
1788 ),
1789 no_real_perror_occurred(Errors).
1790
1791 % here we do not add perrors; just fail
1792 type_without_errors(RawExpr,Scope,Type,TExpr) :-
1793 b_type_expression(RawExpr,Scope,Type,TExpr,Errors),!,
1794 no_real_perror_occurred(Errors).
1795
1796
1797 b_type_open_predicate_with_errors(OptionalQuantifier,RawPred,Scope,TPred) :-
1798 b_type_open_predicate(OptionalQuantifier,RawPred,Scope,TPred,Errors),
1799 add_all_perrors(Errors,[],type_expression_error),
1800 no_real_perror_occurred(Errors).
1801 b_type_open_predicate(OptionalQuantifier,RawPred,Scope,TPred,Errors) :-
1802 b_type_open_predicate_for_full_b_machine(_Machine,OptionalQuantifier,RawPred,Scope,TPred,Errors).
1803 b_type_open_predicate_for_full_b_machine(Machine,OptionalQuantifier,RawPred,Scope,TPred,Errors) :-
1804 (var(Machine) -> full_b_machine(Machine) ; true),
1805 replace_prob_set_elements_in_scope(Scope,Scope1),
1806 type_open_predicate_with_quantifier(OptionalQuantifier,RawPred,Scope1,Machine,TPred,Errors),!.
1807 b_type_open_exists_predicate(Raw,Typed,Errors) :-
1808 b_type_open_predicate(open(exists),Raw,[prob_ids(visible),variables],Typed,Errors).
1809
1810 b_type_expression(RawExpr,_Scope,Type,TExpr,Errors) :-
1811 b_type_literal(RawExpr,T,TE),!,
1812 Type=T,TExpr=TE,Errors=[].
1813 b_type_expression(RawExpr,Scope,Type,TExpr,Errors) :-
1814 b_type_expression_for_full_b_machine(_,RawExpr,Scope,Type,TExpr,Errors).
1815
1816 % type literals without setting up scope, ...
1817 % TODO: also use for type_in_machine_l
1818 b_type_literal(boolean_false(Pos),boolean,b(boolean_false,boolean,[nodeid(Pos)])).
1819 b_type_literal(boolean_true(Pos),boolean,b(boolean_true,boolean,[nodeid(Pos)])).
1820 b_type_literal(integer(Pos,Int),integer,b(integer(Int),integer,[nodeid(Pos)])).
1821 b_type_literal(real(Pos,R),real,b(real(R),real,[nodeid(Pos)])).
1822 b_type_literal(string(Pos,Atom),string,b(string(Atom),string,[nodeid(Pos)])).
1823
1824
1825 b_type_expression_for_full_b_machine(M,RawExpr,Scope,Type,TExpr,Errors) :-
1826 b_type_expressions_l(M,[RawExpr],Scope,[Type],[TExpr],Errors).
1827
1828 b_type_expressions_l(Machine,RawExprs,Scope,Types,TExprs,Errors) :-
1829 (var(Machine) -> full_b_machine(Machine) ; true),
1830 % in case you type check multiple expressions for a complex machine it is better to extract the machine once
1831 replace_prob_set_elements_in_scope(Scope,Scope1),
1832 % we need this, for example for tcltk_check_state_sequence_from_file, when deferred set elements written by TLC are in the file
1833 ? type_in_machine_l(RawExprs,Scope1,Machine,Types,TExprs,Errors),!.
1834
1835 replace_prob_set_elements_in_scope(Scope,Res) :- var(Scope),!,
1836 add_internal_error('Scope is a variable (use, e.g., [constants,variables,operation_bodies,...]):',replace_prob_set_elements_in_scope(Scope,Res)),
1837 Res=Scope.
1838 replace_prob_set_elements_in_scope(Scope,NewScope) :-
1839 ? ( select(prob_ids(AllOrVisible),Scope,identifier(Ids),NewScope) -> % replaces prob by deferred set element identifiers
1840 % for example if we have SETS PID then we would have PID1,... in Ids unless PID1 is known to be another identifier
1841 b_get_prob_deferred_set_elements(DefIDs,AllOrVisible),
1842 exclude(known_identifier,DefIDs,Ids) % exclude those ids that would clash
1843 % TO DO: add option to translate_identifiers using translate:keyword_to_id_cache
1844 ;
1845 Scope = NewScope).
1846
1847
1848 known_identifier(X) :- get_texpr_id(X,ID),
1849 (bmachine:b_is_constant(ID,_) ;
1850 bmachine:b_is_variable(ID,_)).
1851
1852 % ------------------------
1853
1854 % a generic predicate to find all kinds of identifiers
1855
1856 :- use_module(b_global_sets,[b_global_set/1, is_b_global_constant/3]).
1857 :- use_module(probsrc(kernel_freetypes),[registered_freetype/2, freetype_case_db/3]).
1858 :- use_module(probsrc(bmachine_eventb), [ stored_operator/2]).
1859 %! mode get_machine_identifiers(+Category, -ListOfIdentifiers)
1860 get_machine_identifiers(machines,MN) :-
1861 findall(FID, (b_filenumber(FID,Type,_,_),Type \= def),MN).
1862 get_machine_identifiers(definition_files,DFN) :-
1863 findall(FID, b_filenumber(FID,def,_,_),DFN).
1864 get_machine_identifiers(definitions,DN) :-
1865 findall(DefID,b_get_definition(DefID,_,_,_,_),DN).
1866 get_machine_identifiers(sets,Sets) :-
1867 findall(GS,b_global_set(GS),Sets).
1868 get_machine_identifiers(set_constants,Csts) :-
1869 findall(Cst,is_b_global_constant(_GS,_,Cst),Csts).
1870 get_machine_identifiers(constants,CN) :-
1871 b_get_machine_constants(Constants),
1872 get_texpr_ids(Constants,CN).
1873 get_machine_identifiers(freetypes,FN) :-
1874 findall(FID,((registered_freetype(F,_) ; freetype_case_db(F,_,_)),functor(F,FID,_)),FN).
1875 get_machine_identifiers(operators,FN) :-
1876 findall(Name,stored_operator(Name,_Kind),FN). % we could exclude Kind=datatype_definition, as listed in freetypes?
1877 get_machine_identifiers(variables,VN) :-
1878 b_get_machine_variables(Variables),
1879 get_texpr_ids(Variables,VN).
1880 get_machine_identifiers(operations,Ops) :-
1881 findall(Op,b_top_level_operation(Op),Ops).
1882
1883 :- use_module(b_global_sets,[b_global_deferred_set/1,all_elements_of_type/2]).
1884 :- use_module(input_syntax_tree,[get_raw_position_info/2]).
1885 % try and get source code for an identifier
1886 source_code_for_identifier(ID,constant,Type,OriginStr,OriginTerm,Source) :- b_is_constant(ID),!,
1887 get_constant_type_and_origin(ID,Type,OriginStr,OriginTerm),
1888 findall(Def,get_constant_definition(ID,Def),AllDefs),
1889 (AllDefs=[_|_] -> conjunct_predicates(AllDefs,Source)
1890 ; % try and find other type of predicates defining ID
1891 findall(Pred,get_constant_predicate(ID,Pred),AllPreds),
1892 conjunct_predicates(AllPreds,Source)).
1893 source_code_for_identifier(ID,variable,Type,OriginStr,OriginTerm,Source) :- b_is_variable(ID),!,
1894 get_variable_type_and_origin(ID,Type,OriginStr,OriginTerm),
1895 Source = b(truth,pred,[]). % TO DO: improve
1896 source_code_for_identifier(ID,Kind,Type,OriginStr,OriginTerm,Source) :- b_get_machine_set(ID,TID),!,
1897 (b_global_deferred_set(ID) -> Kind = deferred_set ; Kind = enumerated_set),
1898 Type = set(global(ID)),
1899 all_elements_of_type(ID,All),
1900 translate:translate_span_with_filename(TID,OriginStr), OriginTerm=TID,
1901 Source = b(equal(TID,b(value(All),Type,[])),pred,[]).
1902 source_code_for_identifier(ID,Kind,Type,OriginStr,OriginTerm,Source) :-
1903 global_set_element(ID,GID),!,
1904 (b_global_deferred_set(GID)
1905 -> Kind = deferred_set_element ; Kind = enumerated_set_element),
1906 b_get_machine_set(GID,TGID),
1907 Type = global(ID),
1908 all_elements_of_type(GID,All),
1909 translate:translate_span_with_filename(TGID,OriginStr), OriginTerm=TGID,
1910 Source = b(equal(TGID,b(value(All),set(Type),[])),pred,[]).
1911 source_code_for_identifier(ID,definition,Type,OriginStr,OriginTerm,Source) :-
1912 b_get_definition(ID,DefType,Args,RawExpr,_Deps),!,
1913 Type = DefType,
1914 % Definitions are only present in RAW form
1915 get_raw_position_info(RawExpr,PosInfo),
1916 translate:translate_span_with_filename(PosInfo,OriginStr), % the position info does not always seem to be valid (when coming from DEFINITION FILE) !??! TO DO fix
1917 OriginTerm=PosInfo,
1918 source_code_for_definition(DefType,ID,Args,RawExpr,Source).
1919 source_code_for_identifier(ID,file,Type,OriginStr,OriginTerm,b(string(Source),string,[])) :-
1920 b_filenumber(ID,Kind,_,Filename),
1921 extension_kind(Kind,Type),
1922 !,
1923 ajoin([Type,' ',ID],Source),
1924 OriginTerm =src_position_with_filename(1,0,0,Filename),
1925 OriginStr = Filename.
1926 source_code_for_identifier(ID,Kind,subst,OriginStr,OriginTerm,Source) :-
1927 b_find_operation(ID,Res,TParas,Body,OType),
1928 (OType=classic -> Kind = operation ; Kind=event),
1929 translate:translate_span_with_filename(Body,OriginStr),Body=OriginTerm,
1930 get_texpr_info(Body,Info),
1931 Source=b(operation(b(identifier(ID),subst,[]),Res,TParas,Body),subst,Info).
1932 source_code_for_identifier(ID,assertion,pred,OriginStr,OriginTerm,Assertion) :-
1933 b_get_assertions(all,_,Ass), member(Assertion,Ass),
1934 get_texpr_label(Assertion,ID), OriginTerm = Assertion,
1935 translate:translate_span_with_filename(Assertion,OriginStr).
1936 source_code_for_identifier(ID,invariant,pred,OriginStr,OriginTerm,Invariant) :-
1937 b_get_invariant_from_machine(C), conjunction_to_list(C,L), member(Invariant,L),
1938 get_texpr_label(Invariant,ID), OriginTerm = Invariant,
1939 translate:translate_span_with_filename(Invariant,OriginStr).
1940 % TO DO: look for invariant labels as ids ?
1941
1942 :- use_module(tools,[ split_last/4 ]).
1943 b_find_operation(ID,Res,TParas,Body,OType) :-
1944 b_get_machine_operation(ID,Res,TParas,Body,OType,_Pos).
1945 b_find_operation(ID,Res,TParas,Body,OType) :-
1946 b_get_machine_operation(ID2,Res,TParas,Body,OType,_Pos),
1947 split_last(ID2, '.', _, ID).
1948
1949 extension_kind(mch,'MACHINE').
1950 extension_kind(ref,'REFINEMENT').
1951 extension_kind(def,'DEFINITIONS FILE').
1952 extension_kind(imp,'IMPLEMENTATION').
1953
1954 source_code_for_definition(predicate,ID,_,RawExpr,Source) :-
1955 b_type_open_exists_predicate(RawExpr,Typed,Errors),
1956 (no_real_perror_occurred(Errors) -> true ; debug_println(9,errs(ID,Errors))),
1957 Source=Typed.
1958 source_code_for_definition(expression,ID,Args,RawExpr,Source) :-
1959 % TO DO: add parameters to avoid type errors; but we get Typed anyway
1960 b_type_expression(RawExpr,[prob_ids(visible),variables],Type,Typed,Errors),
1961 (no_real_perror_occurred(Errors) -> true ; debug_println(9,errs(ID,Args,Type,Errors))),
1962 Source=Typed.
1963 % TO DO: treate substitutions
1964 source_code_for_definition(DefType,ID,_Args,_RawExpr,Source) :-
1965 Source=b(identifier(ID),DefType,[]).
1966
1967 :- use_module(b_global_sets,[lookup_global_constant/2,prob_deferred_set_element/4]).
1968 global_set_element(ID,GlobalSetID) :- lookup_global_constant(ID,fd(_,GlobalSetID)).
1969 global_set_element(ID,GlobalSetID) :-
1970 prob_deferred_set_element(GlobalSetID,_Elem,ID,all).
1971
1972 get_constant_span(ID,Span) :-
1973 b_get_machine_constants(Constants),
1974 TID = b(identifier(ID),_,Span),
1975 member(TID,Constants).
1976
1977 get_constant_type_and_origin(ID,Type,OriginStr,OriginTerm) :-
1978 b_get_machine_constants(Constants),
1979 TID = b(identifier(ID),Type,_Infos),
1980 member(TID,Constants),
1981 % we could also use member(origin(Origin),Infos)
1982 translate:translate_span_with_filename(TID,OriginStr), OriginTerm=TID.
1983 get_variable_type_and_origin(ID,Type,OriginStr,OriginTerm) :-
1984 b_get_machine_variables(Vars),
1985 TID = b(identifier(ID),Type,_Infos),
1986 member(TID,Vars),
1987 % we could also use member(origin(Origin),Infos)
1988 translate:translate_span_with_filename(TID,OriginStr), OriginTerm=TID.
1989
1990 get_constant_definition(ID,FullDef) :-
1991 b_get_properties_from_machine(Prop),
1992 EqDef = b(equal(LHS,RHS),pred,_),
1993 member_in_conjunction_cse(FullDef,EqDef,Prop),
1994 (get_texpr_id(LHS,ID) ; get_texpr_id(RHS,ID)).
1995
1996 get_constant_predicate(ID,FullPred) :-
1997 b_get_properties_from_machine(Prop),
1998 member_in_conjunction_cse(FullPred,Pred,Prop),
1999 involves_id(Pred,ID).
2000 involves_id(ID,b(E,_,_)) :- involves_id_aux(E,ID).
2001 involves_id_aux(member(LHS,_),ID) :- get_texpr_id(LHS,ID).
2002 involves_id_aux(subset(LHS,_),ID) :- get_texpr_id(LHS,ID).
2003 involves_id_aux(subset_strict(LHS,_),ID) :- get_texpr_id(LHS,ID).
2004
2005 :- volatile b_get_machine_setscope/2.
2006 :- dynamic b_get_machine_setscope/2.
2007 :- public b_get_machine_setscope_calc/2.
2008 % precompiled: definitions of the form "scope_SET == Expr",
2009 % Set is the name of the Set, TExpr the typed expression
2010 b_get_machine_setscope_calc(Set,TExpr) :-
2011 b_definition_prefixed(expression, scope_, Set, Name,_),
2012 % TO DO: check if it is a SET
2013 b_get_typed_definition(Name,[],TExpr).
2014
2015 % get a specific MAX_OPERATIONS Value for an operation
2016 :- volatile b_get_machine_operation_max/2.
2017 :- dynamic b_get_machine_operation_max/2.
2018 :- public b_get_machine_operation_max_calc/2.
2019 % precompiled: definitions of the form "scope_SET == Expr",
2020 % Set is the name of the Set, TExpr the typed expression
2021 b_get_machine_operation_max_calc(Set,MaxOp) :-
2022 b_definition_prefixed(expression, 'MAX_OPERATIONS_', Set, Name,DefPos),
2023 (b_get_typed_definition(Name,[constants],DEF), % scope=constants allows to use other definitions
2024 DEF=b(integer(MaxOp),integer,_)
2025 % TO DO: check if it is an operation
2026 %, MaxOp >= 0 we now use negative numbers for randomised restart
2027 -> true
2028 ; add_warning(b_get_machine_operation_max_calc,'Definition must specify an integer (negative numbers means using randomised restart) ',Name,DefPos),
2029 fail
2030 ).
2031
2032 :- volatile b_get_machine_goal/1.
2033 :- dynamic b_get_machine_goal/1.
2034 :- public b_get_machine_goal_calc/1.
2035 % precompiled: definition of GOAL, a typed predicate
2036 ?b_get_machine_goal_calc(TPred) :- get_goal(TPred).
2037
2038 b_reset_machine_goal_from_DEFINITIONS :-
2039 get_goal(TPred),
2040 b_set_parsed_typed_machine_goal(TPred).
2041 get_goal(Goal) :-
2042 get_proz_settings(Settings),memberchk(goal(Goal),Settings),!.
2043 get_goal(Goal) :- % print(getting_goal),nl,
2044 get_texpr_type(Goal,pred),
2045 ? b_get_typed_predicate_definition('GOAL',[variables],Goal).
2046
2047 :- volatile b_get_machine_searchscope/1.
2048 :- dynamic b_get_machine_searchscope/1.
2049 :- public b_get_machine_searchscope_calc/1.
2050 % precompiled: definition of SCOPE, a typed predicate
2051 b_get_machine_searchscope_calc(TPred) :-
2052 get_texpr_type(TPred,pred),
2053 b_get_typed_definition('SCOPE',[variables],TPred).
2054
2055 :- volatile b_get_definition_string_from_machine/3.
2056 :- dynamic b_get_definition_string_from_machine/3.
2057 :- public b_get_definition_string_from_machine_calc/3.
2058 % precompiled: string definitions, Name == "String"
2059 b_get_definition_string_from_machine(Name,String) :-
2060 ? b_get_definition_string_from_machine(Name,_,String).
2061 b_get_definition_string_from_machine_calc(Name,Pos,String) :-
2062 ? b_get_definition(Name,expression,[],string(Pos,Str),_Deps),
2063 get_texpr_expr(TExpr,string(String)),
2064 type_with_errors_in_context(string(Pos,Str),[],_,TExpr,machine_context).
2065
2066 get_animation_image(Nr,S) :-
2067 animation_minor_mode(z),
2068 get_proz_animation_function(_,_,Images),!,
2069 nth1(Nr,Images,S).
2070 get_animation_image(Nr,S) :- number(Nr),!,
2071 number_codes(Nr,TailCodes),
2072 /* ANIMATION_IMG */
2073 atom_codes(Def_Name,[65,78,73,77,65,84,73,79,78,95,73,77,71|TailCodes]),
2074 b_get_definition_string_from_machine(Def_Name,S).
2075 get_animation_image(Nr,S) :-
2076 b_get_definition_string_from_machine(Def_Name,S),
2077 /* ANIMATION_IMG */
2078 atom_codes(Def_Name,[65,78,73,77,65,84,73,79,78,95,73,77,71|TailCodes]),
2079 number_codes(Nr,TailCodes).
2080
2081 :- use_module(error_manager,[extract_file_number_and_name/3]).
2082 :- use_module(specfile,[b_or_z_mode/0]).
2083 get_animation_image_source_file(Nr,File) :- b_or_z_mode,
2084 % get source file where Animation image is defined; relevant for finding images
2085 b_get_definition_string_from_machine(Def_Name,Pos,_),
2086 atom_codes(Def_Name,[65,78,73,77,65,84,73,79,78,95,73,77,71|TailCodes]),
2087 number_codes(Nr,TailCodes),
2088 extract_file_number_and_name(Pos,_,File).
2089
2090 get_proz_animation_function(Function,Default,Images) :-
2091 get_proz_settings(Settings),
2092 memberchk(animation_function(Function,Default,Images),Settings).
2093 get_proz_settings(Settings) :-
2094 machine(_,Sections),memberchk(meta/Meta,Sections),
2095 memberchk(proz_settings(Settings),Meta).
2096
2097
2098 :- volatile b_get_machine_animation_function/2.
2099 :- dynamic b_get_machine_animation_function/2.
2100 :- public b_get_machine_animation_function_calc/2.
2101 :- use_module(tools,[safe_number_codes/2]).
2102 :- use_module(bsyntaxtree,[is_set_type/2]).
2103 % precompiled: definition of ANIMATION_FUNCTION, a typed expression
2104 b_get_machine_animation_function_calc(AFun,Nr) :-
2105 get_proz_animation_function(TFun,Default,_),!,
2106 ( Nr = -1, AFun = Default
2107 ; Nr = 0, TFun \= none, AFun=TFun
2108 ).
2109 b_get_machine_animation_function_calc(TFun,Nr) :-
2110 get_definition_with_nr_suffix("ANIMATION_FUNCTION",Nr,Def_Name),
2111 b_get_typed_expression_definition(Def_Name,[variables],TFun), % only type it afterwards; avoid throwing type errors for other definitions
2112 get_texpr_type(TFun,Type),
2113 (is_set_type(Type,couple(_,_)) -> true
2114 ; add_warning(b_get_machine_animation_function_calc,'Illegal type for ANIMATION_FUNCTION: ',Def_Name:Type,TFun),
2115 fail).
2116
2117
2118 :- volatile b_get_machine_heuristic_function/1.
2119 :- dynamic b_get_machine_heuristic_function/1.
2120 :- public b_get_machine_heuristic_function_calc/1.
2121 b_get_machine_heuristic_function_calc(TFun) :- %print(extracting_heuristic_fun(TFun)),nl,
2122 get_texpr_type(TFun,integer),
2123 b_get_typed_expression_definition('HEURISTIC_FUNCTION',[variables],TFun).
2124
2125 :- volatile b_get_machine_animation_expression/2.
2126 :- dynamic b_get_machine_animation_expression/2.
2127 :- public b_get_machine_animation_expression_calc/2.
2128 b_get_machine_animation_expression_calc(STR,AExpr) :- %print(extracting_heuristic_fun(TFun)),nl,
2129 ? useful_animation_expression(STR),
2130 b_get_typed_expression_definition(STR,[variables],AExpr).
2131 b_get_machine_animation_expression_calc(DefName,AExpr) :-
2132 b_definition_prefixed(_,'ANIMATION_EXPRESSION',_,DefName,_DefPos),
2133 b_get_typed_expression_definition(DefName,[variables],AExpr).
2134
2135 %useful_animation_expression('ANIMATION_EXPRESSION'). % for state viewer
2136 useful_animation_expression('GAME_PLAYER'). % for MCTS, should return "min" or "max"
2137 useful_animation_expression('GAME_OVER').
2138 useful_animation_expression('GAME_VALUE').
2139 useful_animation_expression('GAME_MCTS_RUNS').
2140 useful_animation_expression('GAME_MCTS_TIMEOUT').
2141 useful_animation_expression('GAME_MCTS_CACHE_LAST_TREE').
2142
2143
2144 % Custom nodes and edges for a custom graph representation of a state
2145 :- volatile b_get_machine_custom_nodes_function/2, b_get_machine_custom_edges_function/2,
2146 b_get_machine_custom_graph_function/2.
2147 :- dynamic b_get_machine_custom_nodes_function/2, b_get_machine_custom_edges_function/2,
2148 b_get_machine_custom_graph_function/2.
2149 :- public b_get_machine_custom_nodes_function_calc/2.
2150 b_get_machine_custom_nodes_function_calc(TFun,Nr) :-
2151 get_definition_with_nr_suffix("CUSTOM_GRAPH_NODES",Nr,Def_Name),
2152 b_get_typed_expression_definition(Def_Name,[variables],TFun).
2153 :- public b_get_machine_custom_edges_function_calc/2.
2154 b_get_machine_custom_edges_function_calc(TFun,Nr) :-
2155 get_definition_with_nr_suffix("CUSTOM_GRAPH_EDGES",Nr,Def_Name),
2156 b_get_typed_expression_definition(Def_Name,[variables],TFun).
2157 :- public b_get_machine_custom_graph_function_calc/2.
2158 b_get_machine_custom_graph_function_calc(TFun,Nr) :-
2159 get_definition_with_nr_suffix("CUSTOM_GRAPH",Nr,Def_Name), % single function for graph attributes, possibly edges and nodes
2160 b_get_typed_expression_definition(Def_Name,[variables],TFun).
2161
2162
2163 get_definition_with_nr_suffix(Prefix,Nr,Def_Name) :-
2164 ? b_get_definition(Def_Name,expression,[],_RawExpr,_Deps),
2165 atom_codes(Def_Name,AC),
2166 append(Prefix,TailCodes,AC),
2167 (TailCodes=[] -> Nr=0
2168 ; TailCodes = "_DEFAULT" -> Nr = -1
2169 ; safe_number_codes(Nr,TailCodes)).
2170
2171
2172 % ------------------------
2173
2174 :- volatile b_get_constant_represented_inside_global_set/2.
2175 :- dynamic b_get_constant_represented_inside_global_set/2.
2176
2177 :- public b_get_constant_represented_inside_global_set_calc/2.
2178 b_get_constant_represented_inside_global_set_calc(X,GlobalSetName) :-
2179 b_get_disjoint_constants_of_type(GlobalSetName, DisjointConstants,_),
2180 ? member(X,DisjointConstants). /* X will be integrated into the global_set */
2181
2182
2183 :- volatile b_get_disjoint_constants_of_type/3.
2184 :- dynamic b_get_disjoint_constants_of_type/3.
2185 :- public b_get_disjoint_constants_of_type_calc/3.
2186 b_get_disjoint_constants_of_type_calc(GlobalSetName, DisjointConstants, AllConstantsIDs) :-
2187 b_get_machine_all_constants(Constants), /* get all the constants */
2188 b_get_properties_from_machine(Properties),
2189 ? b_get_machine_set(GlobalSetName),
2190 \+ b_get_named_machine_set(GlobalSetName,_), % not an explicitly enumerated set
2191 find_constants_of_type(Constants,GlobalSetName,AllConstantsIDs,_GSConstants),
2192 find_inequal_global_set_identifiers(AllConstantsIDs,global(GlobalSetName),Properties,DisjointConstants),
2193 DisjointConstants \= [],
2194 debug_println(9,disjoint_enumerated_constants(GlobalSetName,DisjointConstants)).
2195 % TO DO: remove from Properties irrelevant conjuncts; sort AllConstantsIDs by having first those with max disequalities
2196
2197 find_constants_of_type([],_GS,[],[]) :- !.
2198 find_constants_of_type([b(identifier(ID),global(GS),INFO)|T], GS, [ID|IT],
2199 [b(identifier(ID),global(GS),INFO)|TT]) :- !,
2200 find_constants_of_type(T,GS,IT,TT).
2201 find_constants_of_type([b(_,_,_)|T], GS, IT, TT) :- !,
2202 find_constants_of_type(T,GS,IT,TT).
2203 find_constants_of_type(X,GS,_,_) :- print(find_constants_of_type_error(X,GS)),nl,fail.
2204
2205
2206 % ------------------------
2207 :- volatile b_get_all_used_identifiers_in_section/2.
2208 :- dynamic b_get_all_used_identifiers_in_section/2.
2209 :- public b_get_all_used_identifiers_in_section_calc/2.
2210
2211 % Note: may contain var$0 instead of var for becomes_such
2212 b_get_all_used_identifiers_in_section_calc(SECTION,Identifiers) :-
2213 full_b_machine(BMachine),
2214 ? member(SECTION,[constraints,properties,invariant,assertions,
2215 initialisation,operation_bodies]),
2216 findall(I, find_used_identifier_in_machine_section(BMachine,SECTION,I), Ids),
2217 %print(section_ids(SECTION,Ids)),nl,
2218 sort(Ids,Identifiers).
2219
2220 :- volatile b_get_all_used_identifiers/1.
2221 :- dynamic b_get_all_used_identifiers/1.
2222 :- public b_get_all_used_identifiers_calc/1.
2223 :- use_module(library(ordsets),[ord_union/2]).
2224 % Precompiled: b_get_all_used_identifiers_calc/1 returns a list of all
2225 % identifiers used in machine sections that contain expressions and predicates
2226 b_get_all_used_identifiers_calc(Identifiers) :-
2227 findall(I, b_get_all_used_identifiers_in_section(_,I), ListOfList),
2228 ord_union(ListOfList,Identifiers). % ,print(all(Identifiers)),nl.
2229
2230 find_used_identifier_in_machine_section(Machine,Sec,Identifier) :-
2231 % treat it like a list of expressions
2232 ? get_section_texprs(Sec,Machine,TExprs),
2233 % and find all identifiers in each expression
2234 ? member(TExpr,TExprs),
2235 find_identifier_uses(TExpr,[],Ids),
2236 ? member(Identifier,Ids).
2237
2238 :- volatile b_is_unused_constant/1.
2239 :- dynamic b_is_unused_constant/1.
2240 :- public b_is_unused_constant_calc/1.
2241 b_is_unused_constant_calc(UnusedConstant) :-
2242 findall(C,b_is_constant(C),CL), %b_get_machine_constants(Constants), gives typed ids
2243 CL\=[] ,sort(CL,Constants),
2244 b_get_all_used_identifiers_in_section(invariant,I1),
2245 b_get_all_used_identifiers_in_section(assertions,I2),
2246 b_get_all_used_identifiers_in_section(initialisation,I3),
2247 b_get_all_used_identifiers_in_section(operation_bodies,I4),
2248 % TODO: get constants used in VisB definitions
2249 ord_union([I1,I2,I3,I4],UsedIds),
2250 %print(used(UsedIds)),nl,
2251 ord_subtract(Constants,UsedIds,UnusedConstants),
2252 UnusedConstants\=[],
2253 (b_get_machine_variables([]) -> true
2254 ; length(UnusedConstants,NrUC),
2255 (silent_mode(on) -> true
2256 ; (NrUC>10,debug_mode(off),UnusedConstants=[C1,C2|_]) ->
2257 print_message_with_max_depth(unused_constants(NrUC,[C1,C2,'...']),500)
2258 ; print_message_with_max_depth(unused_constants(NrUC,UnusedConstants),500))
2259 ),
2260 ? member(UnusedConstant,UnusedConstants).
2261
2262
2263 % precompiled: Skel is the operation skeleton, SpecializedInv a typed predicate
2264 % (Skel,SpecializedInv) :-
2265 % b_get_machine_operation(Name,_Res,Params,_Body),
2266 % atom_concat('SIMPLIFIED_INV_OP_',Name,ASNC),
2267 % b_get_typed_definition(ASNC,[variables,identifiers(Params)],SpecializedInv),
2268 % length(Params,Len),
2269 % functor(Skel,Name,Len),
2270 % print(b_specialized_invariant_for_op(Skel)).
2271
2272
2273 get_section_from_current_machine(Section,Content) :-
2274 full_b_machine(BMachine),
2275 get_section(Section,BMachine,Content).
2276
2277 is_ground(X,R) :- ground(X),!,R=ground.
2278 is_ground(_,nonground).
2279
2280 b_set_empty_machine :- debug_println(9,setting_empty_machine),
2281 empty_machine(Main,Machines),
2282 b_set_machine(Main,Machines,[]).
2283
2284 b_get_machine_refinement_hierarchy(Hierarchy) :-
2285 \+ machine(_Name,_M),!,Hierarchy=[]. %No B Machine loaded
2286 b_get_machine_refinement_hierarchy(Hierarchy) :-
2287 get_section_from_current_machine(meta,Infos),
2288 member(hierarchy/Hierarchy,Infos),!.
2289
2290 b_get_refined_machine_name(Machine) :-
2291 b_get_machine_refinement_hierarchy([_Main,Machine|_Rest]).
2292 b_get_refined_ancestors_names(list(AncestorList)) :-
2293 b_get_machine_refinement_hierarchy([_Main|AncestorList]).
2294 b_get_refined_machine(M) :-
2295 get_section_from_current_machine(meta,Infos),
2296 member(refined_machine/M,Infos), !.
2297
2298
2299
2300 b_get_machine_header_position(MachName,Position) :-
2301 get_section_from_current_machine(meta,Infos),
2302 member(header_pos/HeaderPosList,Infos),
2303 % List with elements MachineName/PositionOfMachineHeader
2304 member(MachName/Position,HeaderPosList).
2305
2306 % model type can be system for Atelier-B Event-B
2307 b_get_model_type(M) :-
2308 get_section_from_current_machine(meta,Infos),
2309 member(model_type/M,Infos), !.
2310
2311 % TODO(DP,6.8.2008)
2312 :- volatile b_machine_temp_predicate/1.
2313 :- dynamic b_machine_temp_predicate/1.
2314
2315 %set_temp_predicate(CustomPredicate) :-
2316 % b_parse_machine_predicate(CustomPredicate,TypedPred),
2317 % assert_temp_typed_predicate(TypedPred).
2318 %
2319 %% set a temporary predicate as additional guard
2320 %set_temp_predicate(CustomPredicate,'$initialise_machine') :- !,set_temp_predicate(CustomPredicate).
2321 %set_temp_predicate(CustomPredicate,'$setup_constants') :- !,set_temp_predicate(CustomPredicate).
2322 %set_temp_predicate(CustomPredicate,OpName) :-
2323 % b_parse_machine_operation_pre_post_predicate(CustomPredicate,TypedPred, OpName,true),
2324 % assert_temp_typed_predicate(TypedPred).
2325
2326 % Note: it can be a good idea to use inline_prob_deferred_set_elements_into_bexpr/2 before:
2327 assert_temp_typed_predicate(TypedPred) :-
2328 reset_temp_predicate,
2329 assertz(b_machine_temp_predicate(TypedPred)).
2330
2331
2332 reset_temp_predicate :- retractall(b_machine_temp_predicate(_)).
2333
2334 :- volatile b_machine_additional_property/1.
2335 :- dynamic b_machine_additional_property/1.
2336
2337 % additional properties for set_up_constants
2338 % TO DO: check if there are constants/properties; otherwise raise warning
2339 add_additional_property(CustomPredicate,Description) :-
2340 format('Adding Property: ~w~n',[CustomPredicate]),
2341 b_parse_machine_predicate(CustomPredicate,TypedPred),
2342 add_texpr_info_if_new(TypedPred,description(Description),TP2),
2343 assertz(b_machine_additional_property(TP2)).
2344
2345 :- use_module(btypechecker, [unify_types_strict/2]).
2346 :- use_module(bsyntaxtree, [safe_create_texpr/4]).
2347 :- use_module(probsrc(translate), [pretty_type/2]).
2348
2349 :- public b_extract_values_clause_assignment_calc/3.
2350 b_extract_values_clause_assignment_calc(ID,Type,TVal) :-
2351 % extract equalities from VALUES clause
2352 get_section_from_current_machine(values,Values),
2353 member(b(values_entry(TID,TVal),_,Info),Values),
2354 get_texpr_id(TID,ID),
2355 get_texpr_type(TID,Type),
2356 debug_println(20,values_entry(ID,Type,TVal)),
2357 (b_is_constant(ID,OtherType),
2358 unify_types_strict(Type,OtherType)
2359 -> (member(description(_),Info) -> Info1=Info
2360 ; Info1=[description('from VALUES clause') | Info]),
2361 safe_create_texpr(equal(TID,TVal),pred,Info1,Equality),
2362 (debug_mode(off) -> true ; add_message(bmachine,'Adding property for VALUES: ',Equality,Equality)),
2363 assertz(b_machine_additional_property(Equality)),
2364 (b_extract_values_clause_assignment(ID,_,_)
2365 -> add_error(bmachine,'Multiple VALUES entries for constant: ',ID,TID)
2366 ; true)
2367 ; b_get_machine_set(ID) -> true % will be dealt with in b_global_sets for deferred sets
2368 ; b_get_constant_represented_inside_global_set(ID,_) ->
2369 add_message(bmachine,'Ignoring VALUES entry for constant (already detected as enumerated set element): ',ID,TID)
2370 ; lookup_global_constant(ID,fd(_,GSET)) ->
2371 ajoin(['Ignoring VALUES entry for element of enumerated set ',GSET,': '],Msg),
2372 add_message(bmachine,Msg,ID,TID)
2373 % TODO: detect case when this is a deferred set element not detected as (virtual) enumerated element
2374 ; b_is_constant(ID,OtherType) -> pretty_type(OtherType,OT), pretty_type(Type,TT),
2375 ajoin(['Cannot adapt value type ',TT,' to abstract type ',OT,', ignoring VALUES entry for: '],Msg),
2376 add_warning(bmachine,Msg,ID,TID)
2377 ; add_error(bmachine,'VALUES clause for unknown constant: ',ID,TID),
2378 fail
2379 ).
2380
2381
2382 % -------------------
2383
2384 :- use_module(specfile,[unset_animation_minor_modes/1,reset_animation_minor_modes/1]).
2385 :- use_module(translate,[set_unicode_mode/0, unset_unicode_mode/0, set_print_type_infos/1]).
2386 b_show_machine_representation_unicode(Rep,AdditionalInfo,UnsetMinorModes,Unicode) :-
2387 Unicode=true,!,
2388 set_unicode_mode,
2389 call_cleanup(b_show_machine_representation(Rep,AdditionalInfo,UnsetMinorModes,none),unset_unicode_mode).
2390 b_show_machine_representation_unicode(Rep,AdditionalInfo,UnsetMinorModes,_) :-
2391 b_show_machine_representation(Rep,AdditionalInfo,UnsetMinorModes,none).
2392
2393
2394 % AdditionalInfo=true means show additional information as comments (promoted, ...)
2395 % UnsetMinorModes will print in default classical B style
2396 % TypeInfos: none, needed or all
2397 b_show_machine_representation(Rep,AdditionalInfo,UnsetMinorModes,TypeInfos) :-
2398 full_b_machine(BMachine),
2399 (UnsetMinorModes==true -> unset_animation_minor_modes(L) ; L=[]),
2400 set_print_type_infos(TypeInfos),
2401 translate_machine(BMachine,Rep,AdditionalInfo),
2402 set_print_type_infos(none),
2403 (UnsetMinorModes==true -> reset_animation_minor_modes(L) ; true).
2404
2405 :- use_module(tools_printing,[nested_write_term_to_codes/2]).
2406 b_get_internal_prolog_representation_as_codes(Codes) :-
2407 full_b_machine(BMachine),
2408 nested_write_term_to_codes(BMachine,Codes).
2409
2410 :- use_module(tools,[get_tail_filename/2,split_filename/3,safe_atom_chars/3]).
2411 % TypingLevel = none, needed or all
2412 b_write_machine_representation_to_file(TypingLevel,PPFILE) :-
2413 b_write_machine_representation_to_file('$auto',TypingLevel,PPFILE).
2414 b_write_machine_representation_to_file('$auto',TypingLevel,PPFILE) :- !, % automatically infer machine name
2415 %get_full_b_machine(Name,M),
2416 get_tail_filename(PPFILE,Tail),
2417 split_filename(Tail,MachName,_Ext),
2418 b_write_machine_representation_to_file3(MachName,TypingLevel,PPFILE).
2419 b_write_machine_representation_to_file(MachName,TypingLevel,PPFILE) :-
2420 % provide explicit machine name; useful for diff checks
2421 b_write_machine_representation_to_file3(MachName,TypingLevel,PPFILE).
2422
2423 :- use_module(translate,[set_print_type_infos/1]).
2424 :- use_module(tools_files, [write_to_utf8_file_or_user_output/2]).
2425 b_write_machine_representation_to_file3(MachName,Level,PPFILE) :-
2426 debug_println(20,'% Pretty-Printing Internal Representation to File: '),
2427 debug_println(20,PPFILE),
2428 translate:set_print_type_infos(Level), % none, needed or all
2429 get_full_b_machine(_Name,M),
2430 (translate_machine_to_classicalb(MachName,M,Rep)
2431 -> translate:set_print_type_infos(none)
2432 ; add_internal_error('Translating machine failed: ',b_write_machine_representation_to_file3(MachName,Level,PPFILE)),
2433 set_print_type_infos(none),
2434 fail),
2435 write_to_utf8_file_or_user_output(PPFILE,Rep).
2436
2437 :- use_module(specfile).
2438 translate_machine_to_classicalb(MachName,M,Rep) :-
2439 temporary_set_preference(expand_avl_upto,-1,CHNG), % avoid printing sets using condensed #
2440 (animation_minor_mode(X)
2441 -> remove_animation_minor_mode,
2442 call_cleanup(translate_machine(machine(MachName,M),Rep,false), set_animation_minor_mode(X))
2443 ; translate_machine(machine(MachName,M),Rep,false)),
2444 reset_temporary_preference(expand_avl_upto,CHNG).
2445
2446 b_write_eventb_machine_to_classicalb_to_file(PPFILE) :-
2447 get_tail_filename(PPFILE,Tail),
2448 split_filename(Tail,MachName,_Ext),
2449 b_show_eventb_as_classicalb1(MachName,Rep,_AdditionalInfo),
2450 write_to_utf8_file_or_user_output(PPFILE,Rep).
2451
2452 :- use_module(preferences,[temporary_set_preference/3,reset_temporary_preference/2]).
2453 b_show_eventb_as_classicalb1(MachName,Rep,AdditionalInfo) :-
2454 full_b_machine(machine(_Name,MachineBody)),
2455 % limit abstract level to 0
2456 b_limit_abstract_level_to_zero(MachineBody,MachineBodyLevel0),
2457 temporary_set_preference(translate_print_typing_infos,true,CHNG),
2458 temporary_set_preference(translate_ids_to_parseable_format,true,CHNG2),
2459 temporary_set_preference(expand_avl_upto,-1,CHNG3), % avoid printing sets using condensed #
2460 (translate_eventb_to_classicalb(machine(MachName,MachineBodyLevel0),AdditionalInfo,Rep)
2461 -> reset_temporary_preference(translate_print_typing_infos,CHNG),
2462 reset_temporary_preference(translate_ids_to_parseable_format,CHNG2),
2463 reset_temporary_preference(expand_avl_upto,CHNG3)
2464 ; add_internal_error('Translating Event-B machine to Classical B failed: ',b_show_eventb_as_classicalb1(MachName,Rep,AdditionalInfo)),
2465 reset_temporary_preference(translate_print_typing_infos,CHNG),
2466 reset_temporary_preference(translate_ids_to_parseable_format,CHNG2),
2467 reset_temporary_preference(expand_avl_upto,CHNG3),
2468 fail).
2469
2470 b_limit_abstract_level_to_zero(MachineBody,MachineBodyLevel0) :-
2471 maplist(b_set_to_level_zero,MachineBody,MachineBodyLevel0).
2472
2473 % TODO: set to level zero also the other events of the Event-B machine
2474 b_set_to_level_zero(initialisation/InitEvent,initialisation/InitEventLevelZero) :-
2475 get_texpr_expr(InitEvent,rlevent(Id,Sec,St,Par,Grd,Thms,Act,VW,PW,Ums,_Abs)),
2476 get_texpr_info(InitEvent,Info),
2477 create_texpr(rlevent(Id,Sec,St,Par,Grd,Thms,Act,VW,PW,Ums,[]),subst,Info,InitEventLevelZero).
2478 b_set_to_level_zero(X,X).
2479
2480 b_show_eventb_as_classicalb(Rep,AdditionalInfo) :-
2481 full_b_machine(BMachine),
2482 translate_eventb_to_classicalb(BMachine,AdditionalInfo,Rep).
2483
2484 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2485
2486 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2487 % precompilation: predicates are precompiled by calling the ..._calc predicate
2488
2489 :- use_module(state_packing).
2490 :- use_module(tools,[start_ms_timer/1,stop_ms_walltimer_with_msg/2]).
2491 % maybe this predicate should be directly called by b_load_machine
2492 b_machine_precompile :- debug_println(9,'Precompiling B Machine'),
2493 start_ms_timer(T1),
2494 get_full_b_machine(_,_),
2495 auto_precompile,
2496 (debug_mode(on) -> stop_ms_walltimer_with_msg(T1,'auto_precompile: ') ; true),
2497 precompile_operation_names_in_reverse_order,
2498 % TODO(DP, 14.8.2008): remove reference to b_global_sets
2499 start_ms_timer(T2),
2500 b_check_and_precompile_deferred_sets,
2501 (debug_mode(on) -> stop_ms_walltimer_with_msg(T2,'precompiling global sets: ') ; true),
2502 % TODO(DP, 12.9.2008): remove reference to kernel_freetypes
2503 reset_freetypes,
2504 get_section_from_current_machine(freetypes,Freetypes),
2505 add_all_freetypes(Freetypes),
2506 auto_precompile_phase2,
2507 b_check_and_precompile_global_set_symmetry,
2508 state_packing:precompile_state_packing,
2509 do_machine_consistency_check,
2510 try_kodkod,
2511 (debug_mode(on) -> stop_ms_walltimer_with_msg(T1,'complete precompiling B machine: ') ; true).
2512
2513 add_all_freetypes([]).
2514 add_all_freetypes([freetype(Name,Cases)|Rest]) :-
2515 add_freetype(Name,Cases),
2516 add_all_freetypes(Rest).
2517
2518
2519 other_spec_precompile :- retractall(bmachine_is_precompiled),
2520 /* call if you do not animate a B specification */
2521 is_precompiled_predicate(Pred/Arity),
2522 functor(Pattern,Pred,Arity),
2523 retractall(Pattern),
2524 (precompiled_predicate_no_error_when_not_precompiled(Pred/Arity)
2525 -> assertz( (Pattern :- fail ))
2526 ; assertz( (Pattern :- print_message('No B machine available for '),print_message(Pattern),fail) )
2527 ),
2528 fail.
2529 other_spec_precompile :-
2530 retractall(b_get_machine_constants(_)),
2531 assertz( b_get_machine_constants([]) ),
2532 retractall(b_get_machine_variables_in_original_order(_)),
2533 assertz( b_get_machine_variables_in_original_order([]) ),
2534 retractall(b_get_machine_variables(_)),
2535 assertz( b_get_machine_variables([]) ),
2536 retractall(b_get_static_assertions_from_machine(_)),
2537 assertz( b_get_static_assertions_from_machine([]) ),
2538 retractall(b_machine_has_static_assertions),
2539 retractall(b_get_unproven_static_assertions_from_machine(_)),
2540 assertz( b_get_unproven_static_assertions_from_machine([]) ),
2541 retractall(b_get_dynamic_assertions_from_machine(_)),
2542 assertz( b_get_dynamic_assertions_from_machine([]) ),
2543 retractall(b_machine_has_dynamic_assertions),
2544 retractall(b_get_unproven_dynamic_assertions_from_machine(_)),
2545 assertz( b_get_unproven_dynamic_assertions_from_machine([]) ),
2546 retractall( b_get_machine_searchscope(_) ),
2547 retractall( b_get_machine_goal(_) ),
2548 assert_bmachine_is_precompiled, debug_println(4,other_spec_precompile).
2549
2550 ?is_precompiled_predicate(P) :- precompiled_predicate(P).
2551 ?is_precompiled_predicate(P) :- precompiled_predicate_phase2(P).
2552
2553 % phase 1 precompilation: required by b_global_sets
2554 precompiled_predicate(b_machine_name/1).
2555 precompiled_predicate(b_get_named_machine_set/3).
2556 precompiled_predicate(b_enumerated_sets_precompiled/0).
2557 precompiled_predicate(b_get_properties_from_machine/1).
2558 precompiled_predicate(b_get_machine_all_constants/1).
2559 precompiled_predicate(b_get_machine_set/2).
2560 precompiled_predicate(b_get_disjoint_constants_of_type/3).
2561 precompiled_predicate(b_get_constant_represented_inside_global_set/2).
2562 precompiled_predicate(b_get_machine_constants/1).
2563 precompiled_predicate(b_get_machine_variables_in_original_order/1).
2564 precompiled_predicate(b_get_machine_variables/1).
2565 precompiled_predicate(b_get_invariant_from_machine/1).
2566 precompiled_predicate(b_get_linking_invariant_from_machine/1).
2567 precompiled_predicate(b_is_constant/2).
2568 precompiled_predicate(b_is_variable/2).
2569 precompiled_predicate(b_get_constant_variable_description/2).
2570 precompiled_predicate(b_get_static_assertions_from_machine/1).
2571 precompiled_predicate(b_machine_has_static_assertions/0).
2572 precompiled_predicate(b_get_unproven_static_assertions_from_machine/1).
2573 precompiled_predicate(b_get_dynamic_assertions_from_machine/1).
2574 precompiled_predicate(b_machine_has_dynamic_assertions/0).
2575 precompiled_predicate(b_get_unproven_dynamic_assertions_from_machine/1).
2576 precompiled_predicate(b_get_assertions_from_main_machine/2).
2577 precompiled_predicate(b_get_initialisation_from_machine/2).
2578 precompiled_predicate(b_get_machine_operation/6).
2579 precompiled_predicate(b_top_level_operation/1).
2580 precompiled_predicate(b_is_operation_name/1).
2581 precompiled_predicate(b_top_level_feasible_operation/1).
2582 precompiled_predicate(b_get_promoted_machine_operations/1).
2583 precompiled_predicate(get_operation_info/2).
2584 precompiled_predicate(b_get_machine_operation_for_animation/7).
2585 precompiled_predicate(get_operation_description_template_expr/2).
2586 precompiled_predicate(b_get_machine_goal/1).
2587 precompiled_predicate(b_get_machine_setscope/2).
2588 precompiled_predicate(b_get_machine_operation_max/2).
2589 precompiled_predicate(b_get_machine_searchscope/1).
2590 precompiled_predicate(b_get_definition_string_from_machine/3).
2591 precompiled_predicate(b_get_machine_animation_function/2).
2592 precompiled_predicate(b_get_machine_heuristic_function/1).
2593 precompiled_predicate(b_get_machine_animation_expression/2).
2594 precompiled_predicate(b_get_machine_custom_nodes_function/2).
2595 precompiled_predicate(b_get_machine_custom_edges_function/2).
2596 precompiled_predicate(b_get_machine_custom_graph_function/2).
2597 precompiled_predicate(complete_discharged_info/0). % just call it before calling b_specialized_invariant_for_op_calc !
2598 precompiled_predicate(get_proven_invariant/2).
2599 precompiled_predicate(b_nth1_invariant/3).
2600 precompiled_predicate(b_invariant_number_list/1).
2601 precompiled_predicate(b_specialized_invariant_mask_for_op/2).
2602 precompiled_predicate(b_specialized_invariant_for_op/2).
2603 precompiled_predicate(b_operation_preserves_invariant/2).
2604 precompiled_predicate(b_get_all_used_identifiers_in_section/2).
2605 precompiled_predicate(b_get_all_used_identifiers/1).
2606 precompiled_predicate(b_is_unused_constant/1).
2607 precompiled_predicate(b_extract_values_clause_assignment/3). % depends on b_is_constant/1
2608 precompiled_predicate(b_machine_statistics/2).
2609
2610 % require b_global_sets to be initialised
2611 precompiled_predicate_phase2(b_get_operation_normalized_read_write_info/3).
2612 precompiled_predicate_phase2(b_get_operation_unchanged_variables/2).
2613 precompiled_predicate_phase2(b_operation_cannot_modify_state/1).
2614 precompiled_predicate_phase2(b_operation_reads_output_variables/3).
2615 precompiled_predicate_phase2(b_get_operation_non_det_modifies/2).
2616
2617 % these functions sometimes get called also in csp mode; simply fail silently for those cases in other_spec_precompile
2618 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_animation_function/2).
2619 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_heuristic_function/1).
2620 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_animation_expression/2).
2621 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_custom_nodes_function/2).
2622 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_custom_edges_function/2).
2623 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_custom_graph_function/2).
2624
2625 % on startup, all precompiled predicates yield error message
2626 startup_precompiled :- retractall(bmachine_is_precompiled),
2627 ? is_precompiled_predicate(Pred/Arity),
2628 functor(Pattern,Pred,Arity),
2629 retractall(Pattern),
2630 assertz( (Pattern :- add_error(bmachine,'B machine not precompiled for ',Pattern),fail) ),
2631 fail.
2632 startup_precompiled :- debug_println(4,startup_precompiled).
2633
2634 :- startup_precompiled.
2635
2636 % for each predicate in "precompiled_predicate", auto_precompile computes
2637 % all solutions by calling the predicate with an appended _calc
2638 auto_precompile :- % startup_precompiled,
2639 % failure-driven loop
2640 ? precompiled_predicate(Pred/Arity), %print(precompile(Pred/Arity)),nl,
2641 %statistics(walltime,[Tot,Delta]), format('Precompiling ~w/~w [~w ms (Delta ~w) ms]~n',[Pred,Arity,Tot,Delta]),
2642 ? auto_precompile2(Pred,Arity,Pattern),
2643 (Pattern -> true /* this pattern already asserted */
2644 ; assertz(Pattern)), fail.
2645 auto_precompile :-
2646 assert_bmachine_is_precompiled, debug_println(4,auto_precompile).
2647 auto_precompile_phase2 :-
2648 % failure-driven loop
2649 ? precompiled_predicate_phase2(Pred/Arity), %print(precompile(Pred/Arity)),nl,
2650 ? auto_precompile2(Pred,Arity,Pattern),
2651 (Pattern -> true /* this pattern already asserted */
2652 ; assertz(Pattern)), fail.
2653 auto_precompile_phase2.
2654
2655 % if the precompiled predicates is e.g. foo/2 then
2656 % Pattern=foo(A,B) and Call=foo_calc(A,B)
2657 auto_precompile2(Pred,Arity,Pattern) :-
2658 atom_concat(Pred,'_calc',CallFunctor),
2659 functor(Pattern,Pred,Arity),
2660 functor(Call,CallFunctor,Arity),
2661 unify_args(Arity,Call,Pattern),
2662 retractall(Pattern), % probably just removes clause added by startup_precompiled
2663 % the failure-driven loop for one predicate
2664 ? call(Call).
2665
2666 unify_args(0,_,_) :- !.
2667 unify_args(N,A,B) :-
2668 arg(N,A,Arg), arg(N,B,Arg),
2669 N1 is N-1, unify_args(N1,A,B).
2670
2671
2672 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2673 % set machine goal
2674
2675 b_set_machine_goal(Goal) :- b_set_machine_goal(Goal,false).
2676 b_set_machine_goal(Goal,WithDeferredSets) :-
2677 get_tc_scope(WithDeferredSets,Scope),
2678 b_parse_machine_predicate(Goal,Scope,TypedPred),
2679 b_set_parsed_typed_machine_goal(TypedPred).
2680
2681 b_set_parsed_typed_machine_goal(TypedPred) :-
2682 retractall(b_get_machine_goal(_)),
2683 assertz(b_get_machine_goal(TypedPred)).
2684
2685 b_unset_machine_goal :-
2686 retractall(b_get_machine_goal(_)).
2687
2688
2689 % get typechecking scope:
2690 get_tc_scope(with_deferred,Scope) :- !,
2691 Scope = [prob_ids(visible),variables,external_library(all_available_libraries)].
2692 % with external libraries we can use e.g. GET_IS_DET_OUTPUT("OpName")=FALSE
2693 get_tc_scope(with_deferred_and_primed,Scope) :- !,
2694 get_primed_machine_variables(PV), % this can be useful for visualisation, but will not work during mc
2695 Scope = [prob_ids(visible),identifier(PV),variables,external_library(all_available_libraries)].
2696 get_tc_scope(_,[variables]).
2697
2698 % set search_scope, restricting model checking to states which satisfy the SCOPE DEFINITION predicate
2699 b_set_machine_searchscope(Goal) :- b_set_machine_searchscope(Goal,with_deferred).
2700 b_set_machine_searchscope(Goal,WithDeferredSets) :-
2701 get_tc_scope(WithDeferredSets,Scope),
2702 b_parse_machine_predicate(Goal,Scope,TypedPred),
2703 b_set_parsed_typed_machine_searchscope(TypedPred).
2704 b_set_parsed_typed_machine_searchscope(TypedPred) :-
2705 retractall(b_get_machine_searchscope(_)),
2706 assertz(b_get_machine_searchscope(TypedPred)).
2707
2708 % also allow empty string, and #invariant and #not_invariant
2709 b_parse_optional_machine_predicate(TargetString,Target) :-
2710 is_empty_string(TargetString),!,create_texpr(truth,pred,[],Target).
2711 b_parse_optional_machine_predicate('#invariant',Invariant) :- !,
2712 b_get_invariant_from_machine(Invariant).
2713 b_parse_optional_machine_predicate('#not_invariant',TargetPredicate) :- !,
2714 b_get_invariant_from_machine(Invariant),
2715 bsyntaxtree:create_negation(Invariant,TargetPredicate).
2716 b_parse_optional_machine_predicate(TargetString,Target) :-
2717 b_parse_machine_predicate(TargetString,Target).
2718
2719 is_empty_string(Atom) :-
2720 atom_codes(Atom,Codes),
2721 is_empty_string2(Codes).
2722 is_empty_string2([]).
2723 is_empty_string2([32|Codes]) :- is_empty_string2(Codes).
2724
2725
2726 % parsing a string as predicate with deferred set elements
2727 b_parse_machine_predicate(Pred,TypedPred) :- b_parse_machine_predicate(Pred,[variables],TypedPred).
2728 b_parse_machine_predicate(Pred,Scope,TypedPred) :-
2729 atom_codes(Pred,Codes),
2730 b_parse_machine_predicate_from_codes(Codes,Scope,TypedPred).
2731 b_parse_machine_predicate_from_codes(Codes,Scope,TypedPred) :-
2732 b_parse_machine_predicate_from_codes2(Codes,[],Scope,TypedPred,closed).
2733 b_parse_machine_predicate_from_codes_open(OptionalQuantifier,Codes,Defs,Scope,TypedPred) :-
2734 b_parse_machine_predicate_from_codes2(Codes,Defs,Scope,TypedPred,open(OptionalQuantifier)).
2735
2736 b_parse_machine_predicate_from_codes2(Codes,Defs,Scope,TypedPred,Mode) :-
2737 debug_println(9,parse_predicate(Mode)),
2738 (Defs=[] -> true ; debug_println(9,'% Ignoring DEFINITIONS')),
2739 b_parse_wo_type_machine_predicate_from_codes_to_raw_expr(Codes,Parsed),
2740 %format('Raw Parsed AST = ~w~n',[Parsed]),
2741 b_type_check_raw_expr(Parsed,Scope,TypedPred,Mode).
2742
2743 check_codes(X) :- (X=[] ; X=[H|_], number(H)),!.
2744 check_codes(X) :- add_error(bmachine,'Error while parsing: not a code list: ',X),fail.
2745
2746 b_parse_wo_type_machine_predicate_from_codes_to_raw_expr(Codes,ParsedRaw) :-
2747 check_codes(Codes),
2748 catch(
2749 parse_predicate(Codes,ParsedRaw), % ,print(ParsedRaw),nl),
2750 Exception,
2751 ( Exception = parse_errors(Errors) -> %print(errors(Errors)),nl,
2752 add_all_perrors(Errors,[],parse_machine_predicate_error),fail
2753 ;
2754 add_error(bmachine,'Exception while parsing predicate: ',Exception),
2755 fail)).
2756
2757 b_type_check_raw_expr(ParsedRaw,Scope,TypedPred,Mode) :-
2758 debug_println(9,type_with_errors(ParsedRaw)),
2759 ( Mode == closed ->
2760 type_with_errors(ParsedRaw,Scope,pred,TypedPred)
2761 ; Mode = open(OptionalQuantifier) ->
2762 b_type_open_predicate_with_errors(OptionalQuantifier,ParsedRaw,Scope,TypedPred)).
2763
2764 % a flexible version: convert atom to codes, but also accept codes list
2765 flexible_atom_codes([],R) :- !, R=[].
2766 flexible_atom_codes(A,R) :- atom(A), !, atom_codes(A,R).
2767 flexible_atom_codes([H|T],List) :- !, List=[H|T].
2768 flexible_atom_codes(Other,List) :- add_internal_error('Not atom or codes list: ',flexible_atom_codes(Other,List)),
2769 List=Other.
2770
2771 b_parse_machine_operation_pre_post_predicate(AtomOrCodes,TypedPred,OpName) :-
2772 b_parse_machine_operation_pre_post_predicate(AtomOrCodes,[],TypedPred,OpName,true).
2773 b_parse_machine_operation_pre_post_predicate(AtomOrCodes,ExtraScope,TypedPred,OpName,GenerateParseErrors) :-
2774 flexible_atom_codes(AtomOrCodes,Codes),
2775 b_parse_predicate(Codes,Parsed,GenerateParseErrors),
2776 get_machine_operation_typing_scope(OpName,Scope,ExtraScope),
2777 b_type_only(Parsed,Scope,pred,TypedPred,GenerateParseErrors).
2778
2779 % Note: B and Event-B have different way of priming; this is aimed at classical B
2780 % and supposes predicate used together with execute_operation_by_predicate_in_state
2781 % in classical B x$0 refers to the value before a substitution (e.g., becomes_such)
2782 get_primed_machine_variables(Ids) :-
2783 b_get_machine_variables(Vars),
2784 maplist(prime_variable,Vars,Ids).
2785 :- use_module(btypechecker,[prime_atom0/2]). % add $0 at end of variable
2786 prime_variable(b(identifier(ID),T,I),b(identifier(PID),T,I)) :- prime_atom0(ID,PID).
2787
2788 is_initialisation_op('$setup_constants').
2789 is_initialisation_op('$initialise_machine').
2790
2791 % analog version to b_is_operation_name:
2792 b_is_initialisation_name('$initialise_machine').
2793
2794
2795 get_machine_operation_typing_scope(OpName,Scope,ExtraScope) :-
2796 ( get_machine_operation_additional_identifiers(OpName,V) -> true
2797 ; add_error_fail(get_machine_operation_typing_scope,'Unknown operation:', OpName)),
2798 Scope = [prob_ids(visible),identifier(V),variables,external_library(all_available_libraries)|ExtraScope].
2799
2800 % get additional ids to add to Scope for typing with identifier(V)
2801 get_machine_operation_additional_identifiers(OpName,V) :-
2802 is_initialisation_op(OpName),!, V=[].
2803 get_machine_operation_additional_identifiers(OpName,V) :-
2804 b_get_machine_operation_for_animation(OpName,Results,Paras,_,_,true,_),
2805 append(Paras,Results,PR), % b_get_machine_operation_typed_parameters
2806 get_primed_machine_variables(PV),
2807 append(PV,PR,V).
2808
2809 % interface predicate b_get_machine_operation_for_animation/6
2810 b_get_machine_operation_for_animation(Name,Results,Parameters,Body,OType,TopLevel) :-
2811 ? b_get_machine_operation_for_animation(Name,Results,Parameters,Body,OType,TopLevel,_OpPos).
2812
2813 :- public b_get_machine_operation_for_animation_calc/7.
2814 % adds some additional ANY parameters if preference is set
2815 b_get_machine_operation_for_animation_calc('$initialise_machine',[],Parameters,Body,OType,_TopLevel,OpPos) :-
2816 b_get_machine_variables(DeclaredVars), Parameters=DeclaredVars,
2817 OpPos = unknown, % TODO: improve
2818 b_get_initialisation_from_machine(Body,OType).
2819 b_get_machine_operation_for_animation_calc(Name,Results,Parameters,Body,OType,TopLevel,OpPos) :-
2820 get_preference(show_eventb_any_arguments,EVENTB),
2821 ? b_get_machine_operation(Name,Results,RealParameters,RealBody,OType,OpPos),
2822 % TO DO: check whether we should only keep b_top_level_operation(Name) in case TopLevel==true !
2823 %length(RealParameters,P), format('Get Mach Op ~w ; paras ~w ; EB ~w, TopLevel=~w~n',[Name,P,EVENTB,TopLevel]),
2824 ((Results=[_|_] ; RealParameters=[_|_] ; EVENTB=false)
2825 -> Parameters=RealParameters, Body=RealBody
2826 ; translate_any_into_parameters(RealBody,FakeParameters,FakeBody),
2827 length(FakeParameters,Len),
2828 (Len > 255
2829 -> add_message(bmachine,'Not adding any parameters to operation, max_arity (255) exceeded: ',Name:Len,OpPos),
2830 Parameters=RealParameters, Body=RealBody
2831 ; ( TopLevel=true, Parameters=FakeParameters, Body=FakeBody
2832 ; TopLevel=false, Parameters=RealParameters, Body=RealBody
2833 )
2834 )
2835 ; Parameters=RealParameters, Body=RealBody
2836 ).
2837
2838 % TO DO: limit to max_arity
2839 translate_any_into_parameters(b(E,Type,Info),Parameters,NewSubst) :-
2840 translate_any_into_parameters_aux(E,Type,Info,Parameters,NewSubst).
2841 translate_any_into_parameters_aux(any(Parameters,PreCond,ABody),Type,Info,Parameters,NewSubst) :-
2842 NewSubst=b(select([b(select_when(PreCond,ABody),Type,Info)]),Type,Info). % TO DO: go deeper ? (nested ANY ?)
2843 translate_any_into_parameters_aux(let(Parameters,Defs,LBody),Type,Info,Parameters,NewSubst) :-
2844 NewSubst=b(select([b(select_when(Defs,LBody),Type,Info)]),Type,Info). % TO DO: go deeper ? ANY could have been translated into several LETs ?
2845 translate_any_into_parameters_aux(lazy_let_subst(Id,IdExpr,Body),Type,Info,Parameters,NewSubst) :-
2846 NewSubst=b(lazy_let_subst(Id,IdExpr,NewInnerSubst),Type,Info),
2847 translate_any_into_parameters(Body,Parameters,NewInnerSubst).
2848
2849
2850 % add deferred set prob_ids and external libraries as well
2851 % ExtraScope could e.g. be [identifier(TypedIDLIst)]
2852 b_parse_machine_expression_from_codes_with_prob_ids(Codes,ExtraScope,TypedExpr,GenerateParseErrors) :-
2853 extend_typing_scope_for_stored_lets([prob_ids(visible),variables,
2854 external_library(all_available_libraries)|ExtraScope],
2855 Scope),
2856 b_parse_machine_expression_from_codes4(Codes,Scope,TypedExpr,GenerateParseErrors).
2857 b_parse_machine_expression_from_codes_with_prob_ids(Codes,ExtraScope,TypedExpr) :-
2858 b_parse_machine_expression_from_codes_with_prob_ids(Codes,ExtraScope,TypedExpr,true).
2859 b_parse_machine_expression_from_codes_with_prob_ids(Codes,TypedExpr) :-
2860 b_parse_machine_expression_from_codes_with_prob_ids(Codes,[],TypedExpr,true).
2861
2862 b_parse_machine_expression_from_codes(Codes,TypedExpr) :-
2863 b_parse_machine_expression_from_codes4(Codes,[variables],TypedExpr,true).
2864
2865 b_parse_machine_expression_from_codes4(Codes,Scope,TypedExpr,GenerateParseErrors) :-
2866 b_parse_machine_expression_from_codes(Codes,Scope,TypedExpr,_Type,GenerateParseErrors,Error),!,
2867 (Error=none -> true
2868 ; generate_parse_errors_for(GenerateParseErrors,Position),
2869 add_error(b_parse_machine_expression_from_codes,'Errors occured during parsing:', Error,Position),
2870 % format(user_error,'Parsing: ~s~n',[Codes]),
2871 fail).
2872
2873
2874 %b_parse_machine_expression_from_codes(Codes,TypedExpr) :-
2875 % b_parse_machine_expression_from_codes(Codes,TypedExpr,_Type,false,Error), Error=none.
2876
2877 b_parse_machine_expression_from_codes(Codes,Typed,Type,GenerateParseErrors,Error) :-
2878 b_parse_machine_expression_from_codes(Codes,[variables],
2879 Typed,Type,GenerateParseErrors,Error).
2880 b_parse_machine_expression_from_codes(Codes,Scope,
2881 Typed,Type,GenerateParseErrors,Error) :-
2882 b_parse_machine_formula_from_codes(expression,Codes,Scope,
2883 Typed,Type,GenerateParseErrors,Error).
2884
2885 % parse substitutions so as to allow operation calls; useful for REPL or trace files:
2886 b_parse_machine_subsitutions_from_codes(Codes,Scope,
2887 Typed,Type,GenerateParseErrors,Error) :-
2888 temporary_set_preference(allow_local_operation_calls,true,CHNG),
2889 call_cleanup(
2890 b_parse_machine_formula_from_codes(substitution,Codes,Scope,
2891 Typed,Type,GenerateParseErrors,Error),
2892 reset_temporary_preference(allow_local_operation_calls,CHNG)).
2893
2894 % a variant of b_parse_machine_predicate that allows also expressions
2895 b_parse_machine_formula(PredOrExpr,Scope,TypedPredOrExpr) :-
2896 atom_codes(PredOrExpr,Codes),
2897 b_parse_machine_formula_from_codes(formula,Codes,Scope,
2898 TypedPredOrExpr,_Type,true,Error), Error=none.
2899
2900 % Kind = expression, predicate, formula, substitution
2901 % GnerateParseErrors = true, false, type_errors_only, gen_parse_errors_for/2
2902 b_parse_machine_formula_from_codes(Kind,Codes,Scope,
2903 Typed,Type,GenerateParseErrors,Error) :-
2904 b_parse_only(Kind,Codes, ParsedAST, GenerateParseErrors, Error),
2905 %print(parsed(Parsed,Error)),nl,
2906 ( nonvar(Error) -> true /* either exception or parse error occured */
2907 ; generate_no_parse_errors(GenerateParseErrors), type_without_errors(ParsedAST,Scope,Type,Typed) -> Error=none
2908 ; b_type_only(ParsedAST,Scope,Type,Typed,GenerateParseErrors) -> Error=none
2909 ; Error=type_error).
2910
2911 % typing with or without errors, depending on GenerateParseErrors flag
2912 b_type_only(ParsedAST,Scope,Type,Typed,gen_parse_errors_for(_Pos)) :- !,
2913 % ParsedAST now contains filenumber for additional file
2914 type_with_errors_in_context(ParsedAST,Scope,Type,Typed,machine_context).
2915 b_type_only(ParsedAST,Scope,Type,Typed,false) :- !,
2916 type_without_errors(ParsedAST,Scope,Type,Typed).
2917 b_type_only(ParsedAST,Scope,Type,Typed,_GenerateParseErrors) :-
2918 type_with_errors_in_context(ParsedAST,Scope,Type,Typed,no_machine_context([])).
2919
2920 % GenerateParseErrors can also provide context filename
2921 b_parse_predicate(Codes,ParsedAST,GenerateParseErrors) :-
2922 b_parse_only(predicate,Codes, ParsedAST, GenerateParseErrors,Error),
2923 Error=none.
2924
2925 b_parse_only(Kind,Codes, ParsedAST, _,Error) :- (Codes \= [] , Codes \= [_|_]),!,
2926 add_internal_error('Not a codes list: ',b_parse_only(Kind,Codes, ParsedAST, _, Error)),
2927 Error = internal_error.
2928 b_parse_only(Kind,Codes, ParsedAST, GenerateParseErrors,Error) :-
2929 generate_parse_errors_for(GenerateParseErrors,Position),!,
2930 % we should generate errors in a particular file context
2931 (extract_file_number_and_name(Position,FileNr,Filename) -> true ; FileNr = -1),
2932 (number(FileNr) -> NewFileNr=FileNr ; add_additional_filename(Filename,NewFileNr)),
2933 catch( parse_at_position_in_file(Kind,Codes,ParsedAST,Position,NewFileNr),
2934 Exception,
2935 ((Exception = parse_errors(Errors) ->
2936 add_all_perrors(Errors,[Filename],parse_machine_formula_error),
2937 Error=parse_error
2938 ;
2939 ajoin(['Exception while parsing ',Kind,': '],Msg),
2940 add_error(bmachine,Msg,Exception,Position),
2941 Error=exception))).
2942 b_parse_only(Kind,Codes, ParsedAST, _GenerateParseErrors,_Error) :-
2943 catch( parse(Kind,Codes,ParsedAST),
2944 Exception,
2945 (debug_println(19,parse_exception(Exception)),fail)).
2946
2947 %generate_type_errors_for(type_errors_only,unknown,[]).
2948 %generate_type_errors_for(GenerateParseErrors,Pos) :- generate_parse_errors_for(GenerateParseErrors,Pos).
2949
2950 generate_parse_errors_for(true,unknown).
2951 generate_parse_errors_for(gen_parse_errors_for(Pos),Pos).
2952
2953 generate_no_parse_errors(false).
2954
2955 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2956
2957 % a flexible parsing predicate, useful for dot and table tools to be called from
2958 % either probcli or prob2 with either atoms or with raw ASTs:
2959
2960 :- use_module(eval_let_store,[extend_typing_scope_for_stored_lets/2]).
2961 parse_expression_raw_or_atom_with_prob_ids(Expr,TypedExpr) :-
2962 extend_typing_scope_for_stored_lets([prob_ids(visible),variables,external_library(all_available_libraries)],Scope),
2963 parse_expression_raw_or_atom3(Expr,Scope,TypedExpr).
2964
2965 parse_expression_raw_or_atom3('$VARIABLES',_,TypedExpr) :- !,
2966 b_get_machine_variables(DeclaredVars),
2967 gen_couple_from_list(DeclaredVars,TypedExpr).
2968 parse_expression_raw_or_atom3(RawAST,Scope,TypedExpr) :- compound(RawAST),!, % allow to pass raw AST as well
2969 type_with_errors(RawAST,Scope,Type,TypedExpr),
2970 ((Type=pred ; Type=subst)
2971 -> add_error(parse_expression,'Expected expression formula but obtained: ',Type),fail
2972 ; true ).
2973 parse_expression_raw_or_atom3(VorE,Scope,TypedExpr) :-
2974 atom_codes(VorE,VorECodes),
2975 % to do: maybe support b_parse_machine_expression_from_codes_with_prob_ids
2976 b_parse_machine_expression_from_codes4(VorECodes,Scope,TypedExpr,true).
2977
2978 :- use_module(bsyntaxtree, [create_couple/3]).
2979 gen_couple_from_list([],string('NO VARIABLES')).
2980 gen_couple_from_list([TID],Res) :- !, Res=TID.
2981 gen_couple_from_list([TID|T],Couple) :-
2982 gen_couple_from_list(T,Rest),
2983 create_couple(TID,Rest,Couple).
2984
2985
2986 :- use_module(btypechecker,[prime_atom0/2]). % add $0 at end of variable
2987 :- use_module(bsyntaxtree, [find_typed_identifier_uses/2,get_texpr_id/2]).
2988 % compute requirements for evaluating formula
2989 % requires_nothing, requires_constants, requires_variables
2990 determine_type_of_formula(TypedExpr,Class) :-
2991 determine_type_of_formula(TypedExpr,_,Class).
2992 determine_type_of_formula(TypedExpr,Identifiers,Class) :-
2993 find_typed_identifier_uses(TypedExpr,Identifiers),
2994 determine_type_of_formula2(Identifiers,Class).
2995 determine_type_of_formula2([],Res) :- !, Res = requires_nothing.
2996 determine_type_of_formula2(Ids,Res) :-
2997 member(TID,Ids), get_texpr_id(TID,ID),
2998 (b_is_variable(ID,_) -> true
2999 ; prime_atom0(Original,ID),
3000 (b_is_variable(Original,_) -> true ; add_warning(bmachine,'Unknown primed variable: ',ID))
3001 ),
3002 !, Res = requires_variables.
3003 determine_type_of_formula2(Ids,Res) :-
3004 member(TID,Ids), get_texpr_id(TID,ID),
3005 b_is_constant(ID,_),
3006 !, Res = requires_constants.
3007 determine_type_of_formula2(_,requires_nothing).
3008 % only open, implicitly existentially quantified variables
3009 % also, TO DO: check that insert_before_substitution_variables / $0 variables are properly treated
3010
3011 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
3012 % consistency check to spot some errors
3013 do_machine_consistency_check :-
3014 specfile:animation_mode(b), % TODO (dp,27.09.2012): this is just an ugly hack
3015 type_check_definitions,
3016 ? minor_mode_to_check,
3017 %debug:time(bmachine:all_operations_have_valid_read_modifies_infos).
3018 !,
3019 all_operations_have_valid_read_modifies_infos.
3020 do_machine_consistency_check.
3021
3022 % In future, all formalisms should provide the relevent data
3023 minor_mode_to_check :- animation_minor_mode(eventb),!.
3024 ?minor_mode_to_check :- classical_b_mode.
3025
3026 all_operations_have_valid_read_modifies_infos :-
3027 %findall(O,b_get_machine_operation(O,_,_,_,_),OpNames),
3028 %maplist(operation_has_valid_read_modifies_infos,OpNames).
3029 ? b_is_operation_name(OpName),
3030 operation_has_valid_read_modifies_infos(OpName),fail.
3031 all_operations_have_valid_read_modifies_infos.
3032
3033 operation_has_valid_read_modifies_infos(OpName) :- % print(check(OpName)),nl,
3034 ( operation_has_valid_read_modifies_infos2(OpName) -> true
3035 ; add_failed_call_error(operation_has_valid_read_modifies_infos2(OpName))).
3036 operation_has_valid_read_modifies_infos2(OpName) :-
3037 b_get_operation_normalized_read_write_info(OpName,Reads,Writes),
3038 maplist(check_read(OpName),Reads),
3039 %print(operation(OpName,reads(Reads),writes(Writes))),nl,
3040 maplist(check_write(OpName),Writes).
3041
3042
3043 check_read(OpName,Id) :-
3044 ? ( (check_is_var(Id); check_is_constant(Id) ; check_is_operation(Id)) -> true
3045 ;
3046 ajoin(['Unknown identifier "',Id,'" in "reads" information of operation:'],Msg),
3047 add_internal_error(bmachine,Msg,OpName,unknown)).
3048 check_write(OpName,Id) :-
3049 ( check_is_var(Id) -> true
3050 ;
3051 ajoin(['Unknown variable "',Id,'" in "modifies" information of operation:'],Msg),
3052 add_internal_error(bmachine,Msg,OpName,unknown)).
3053
3054 check_is_var(Id) :-
3055 b_is_variable(Id,_).
3056 %get_texpr_id(E,Id),
3057 %b_get_machine_variables(Vars),
3058 %memberchk(E,Vars).
3059 check_is_constant(Id) :- b_is_constant(Id,_).
3060 check_is_constant(Id) :- b_get_constant_represented_inside_global_set(Id,_).
3061 % b_get_machine_all_constants(Constants),
3062 % get_texpr_id(TId,Id),
3063 % memberchk(TId,Constants).
3064 check_is_constant(Id) :- b_get_machine_set(Id).
3065 check_is_constant(Id) :- b_get_named_machine_set(Id,_).
3066 check_is_constant(Id) :-
3067 b_get_named_machine_set(_,Elems),member(Id,Elems).
3068 %check_is_constant(Id) :- % add later when we deal FREETYPE section in classical B as in Z
3069 % kernel_freetypes:freetype_register_db(Id,_) ;
3070 % kernel_freetypes:freetype_case_db(Id,_,_).
3071
3072 check_is_operation(op(ID)) :-
3073 b_is_operation_name(ID), % TO DO: check that other predicates can deal with op(Id) infos
3074 get_preference(allow_operation_calls_in_expr,true).
3075
3076 % provide access to number of constants, ....:
3077
3078 :- volatile b_machine_statistics/2.
3079 :- dynamic b_machine_statistics/2.
3080 :- public b_machine_statistics_calc/2.
3081 b_machine_statistics_calc(files,Nr) :-
3082 b_get_all_used_filenames(L),length(L,Nr).
3083 b_machine_statistics_calc(deferred_sets,Nr) :-
3084 get_section_from_current_machine(deferred_sets,L),length(L,Nr).
3085 b_machine_statistics_calc(enumerated_sets,Nr) :-
3086 get_section_from_current_machine(enumerated_sets,L),length(L,Nr).
3087 b_machine_statistics_calc(definitions,Nr) :-
3088 get_section_from_current_machine(definitions,L),length(L,Nr).
3089 b_machine_statistics_calc(constants,Nr) :- b_get_machine_constants(L), length(L,Nr).
3090 b_machine_statistics_calc(variables,Nr) :- b_get_machine_variables(L), length(L,Nr).
3091 b_machine_statistics_calc(properties,Nr) :-
3092 b_get_properties_from_machine(C), conjunction_to_list(C,L),length(L,Nr).
3093 b_machine_statistics_calc(invariants,Nr) :-
3094 b_get_invariant_from_machine(C), conjunction_to_list(C,L),length(L,Nr).
3095 b_machine_statistics_calc(static_assertions,Nr) :-
3096 b_get_static_assertions_from_machine(L), length(L,Nr).
3097 b_machine_statistics_calc(dynamic_assertions,Nr) :-
3098 b_get_dynamic_assertions_from_machine(L), length(L,Nr).
3099 b_machine_statistics_calc(operations,Nr) :- findall(N,b_is_operation_name(N),L),length(L,Nr).
3100
3101 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
3102 % default and initial machines
3103 b_set_initial_machine :-
3104 initial_machine(Main,Machines),
3105 b_set_machine(Main,Machines,[]).
3106
3107 initial_machine(phonebook,[M]) :-
3108 M = abstract_machine(none,machine(none),machine_header(none,phonebook,[]),Body),
3109 Body = [sets(none, [deferred_set(none,'Name'),
3110 deferred_set(none,'Code')]),
3111 definitions(none,[ScopeName,ScopeCode,TraceTest0]),
3112 variables(none, [identifier(none, db)]),
3113 invariant(none, member(none,
3114 identifier(none, db),
3115 partial_function(none,
3116 identifier(none, 'Name'),
3117 identifier(none, 'Code')))),
3118 initialisation(none,
3119 assign(none, [identifier(none, db)], [empty_set(none)])),
3120 operations(none, [Add,Lookup,Update,Reset])],
3121
3122 % definitions
3123 ScopeName = expression_definition(none,
3124 scope_Name,
3125 [],
3126 interval(none, integer(none, 1), integer(none, 3))),
3127 ScopeCode = expression_definition(none,
3128 scope_Code,
3129 [],
3130 interval(none, integer(none, 1), integer(none, 2))),
3131 TraceTest0 = expression_definition(none, trace_Test0, [], empty_sequence(none)),
3132
3133 % add operation
3134 Add = operation(none,
3135 identifier(none, add),
3136 [],
3137 [identifier(none,cc),identifier(none,nn)],
3138 precondition(none, AddPre, AddAssign)),
3139 AddPre = conjunct(none,
3140 conjunct(none,
3141 member(none, identifier(none,nn), identifier(none,'Name')),
3142 member(none, identifier(none,cc), identifier(none,'Code'))),
3143 not_member(none,
3144 identifier(none,nn),
3145 domain(none, identifier(none,db)))),
3146 AddAssign = assign(none,
3147 [identifier(none,db)],
3148 [union(none,
3149 identifier(none,db),
3150 set_extension(none,
3151 [couple(none,[identifier(none,nn),
3152 identifier(none,cc)])]))]),
3153
3154 % lookup operation
3155 Lookup = operation(none,
3156 identifier(none, lookup),
3157 [identifier(none, cc)],
3158 [identifier(none, nn)],
3159 precondition(none, LookupPre, LookupAssign)),
3160 LookupPre = member(none, identifier(none,nn), domain(none,identifier(none,db))),
3161 LookupAssign = assign(none,
3162 [identifier(none, cc)],
3163 [function(none, identifier(none, db), identifier(none, nn))]),
3164
3165 % update operation
3166 Update = operation(none,
3167 identifier(none, update),
3168 [],
3169 [identifier(none,nn),identifier(none,cc)],
3170 precondition(none, UpdatePre, UpdateAssign)),
3171 UpdatePre = conjunct(none,
3172 conjunct(none,
3173 member(none, identifier(none,nn), identifier(none,'Name')),
3174 member(none, identifier(none,cc), identifier(none,'Code'))),
3175 member(none,
3176 identifier(none,nn),
3177 domain(none, identifier(none,db)))),
3178 UpdateAssign = assign(none,
3179 [function(none, identifier(none,db), identifier(none,nn))],
3180 [identifier(none, cc)]),
3181
3182 % reset operation
3183 Reset = operation(none,
3184 identifier(none,reset),
3185 [],
3186 [],
3187 precondition(none, ResetPre, ResetAssign)),
3188 ResetPre = member(none,
3189 identifier(none, db),
3190 total_function(none, identifier(none,'Name'), identifier(none,'Code'))),
3191 ResetAssign = assign(none,[identifier(none,db)],[empty_set(none)]).
3192
3193 empty_machine(empty_machine,[M]) :-
3194 M = abstract_machine(none,machine(none),machine_header(none,empty_machine,[]),Body),
3195 Body = [].
3196
3197 % after transformation this gives
3198 % machine(empty_machine,[deferred_sets/[],enumerated_sets/[],enumerated_elements/[],parameters/[],internal_parameters/[],abstract_constants/[],concrete_constants/[],abstract_variables/[],concrete_variables/[],promoted/[],unpromoted/[],(constraints)/b(truth,pred,[]),properties/b(truth,pred,[initial]),invariant/b(truth,pred,[initial]),linking_invariant/b(truth,pred,[initial]),assertions/[],initialisation/b(skip,subst,[generated]),operation_bodies/[],definitions/[],used/[],freetypes/[],operators/[],values/[],meta/[model_type/machine,hierarchy/[empty_machine],header_pos/[empty_machine/none]]])
3199
3200 % Code to inspect sizes of operations:
3201 % findall(op(Sz,Op),(bmachine:b_get_machine_operation_for_animation(Op,_,_,Body,_,_Top), terms:term_size(Body,Sz)),L), sort(L,SL), print(SL),nl.