1 % (c) 2009-2019 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_set_initial_machine/0,
9 b_set_empty_machine/0,
10 b_set_machine/3,
11 b_set_typed_machine/1,
12 b_load_eventb_project/1, % used for loading .eventb files
13 b_set_eventb_project_flat/3, % set an Event-B project from terms
14
15 get_full_b_machine/2,
16 full_b_machine/1,
17
18 get_proven_invariant/2,
19 get_unproven_invariants/1,
20 load_additional_information/1,
21 %% generate_specialized_invariants/0, %% no longer exists
22 get_operation_info/2,
23
24 b_load_machine_from_file/1, b_load_machine_probfile/1,
25 b_load_machine_from_list_of_facts/2,
26 b_load_machine_from_term/2, % used for Alloy
27 b_machine_precompile/0, other_spec_precompile/0,
28 b_machine_reset/0,
29
30 b_machine_name/1,
31
32 b_get_all_used_filenames/1, b_get_main_filename/1,
33 b_get_main_filenumber/1, b_filenumber/4,
34 b_absolute_file_name_relative_to_main_machine/2,
35 b_get_animated_sections/1,
36
37 b_get_machine_set/1, b_get_machine_set/2,
38 b_get_named_machine_set/2,
39 b_get_disjoint_constants_of_type/3, b_get_constant_represented_inside_global_set/2,
40 b_get_machine_constants/1, b_get_machine_all_constants/1,
41 b_machine_has_constants/0, b_machine_has_constants_or_properties/0,
42 b_is_constant/2, b_is_constant/1, b_is_unused_constant/1,
43 b_machine_has_variables/0,
44 b_is_variable/1, b_is_variable/2,
45 b_get_constant_variable_description/2,
46 b_get_machine_variables/1,
47 b_get_all_used_identifiers/1, b_get_all_used_identifiers_in_section/2,
48 source_code_for_identifier/6,
49
50 b_get_properties_from_machine/1,
51 b_get_invariant_from_machine/1,
52 b_get_linking_invariant_from_machine/1,
53 b_machine_has_assertions/0,
54 b_get_static_assertions_from_machine/1, b_machine_has_static_assertions/0,
55 b_get_unproven_static_assertions_from_machine/1,
56 b_get_dynamic_assertions_from_machine/1, b_machine_has_dynamic_assertions/0,
57 b_get_unproven_dynamic_assertions_from_machine/1,
58 b_get_assertions_from_main_machine/2, b_main_machine_has_no_assertions/0,
59 b_machine_has_unproven_assertions/0, get_assertions_from_machine/2,
60 get_all_assertions_from_machine/1,
61 b_machine_has_proven_invariants/0,
62 b_get_assertions/3,
63 b_get_assertion_count/3,
64 is_discharged_assertion/1,
65
66 b_get_initialisation_from_machine/2,
67 b_get_machine_operation/4, b_get_machine_operation/6,
68 b_get_promoted_machine_operations/1,
69 b_top_level_operation/1, b_is_operation_name/1, b_get_operation_pos/2,
70 b_get_machine_operation_parameter_types/2,
71 b_get_machine_operation_parameter_names/2,
72 b_get_machine_operation_typed_parameters/2,
73 b_machine_operation_names_in_reverse_order/1,
74 b_get_operation_variant/3,
75
76 b_get_machine_setscope/2,
77 b_get_machine_operation_max/2,
78 b_get_machine_goal/1,
79 b_set_machine_goal/1, b_set_machine_goal/2,
80 b_set_machine_searchscope/1, b_set_machine_searchscope/2,
81 b_set_parsed_typed_machine_goal/1,
82 b_reset_machine_goal_from_DEFINITIONS/0,
83 b_parse_machine_expression_from_codes/2,
84 b_parse_machine_expression_from_codes_with_prob_ids/2,
85 b_parse_machine_expression_from_codes/5,
86 b_parse_machine_expression_from_codes/6,
87 b_parse_machine_formula/3, b_parse_machine_formula_from_codes/7,
88 b_parse_machine_predicate/2, b_parse_machine_predicate/3,
89 b_parse_optional_machine_predicate/2,
90 b_parse_machine_predicate_from_codes/3,
91 b_parse_machine_predicate_from_codes_open/5,
92 b_parse_machine_operation_pre_post_predicate/3,
93
94 determine_type_of_formula/2,
95
96 parse_expression_raw_or_atom/2, parse_expression_raw_or_atom_with_prob_ids/2,
97
98 % a version where parsing and type checking are separate:
99 b_parse_wo_type_machine_predicate_from_codes_to_raw_expr/2,
100 b_type_check_raw_expr/4,
101
102 b_get_machine_searchscope/1,
103 b_get_machine_animation_function/2,
104 b_get_machine_heuristic_function/1,
105 b_get_machine_animation_expression/1,
106 b_get_machine_custom_edges_function/2,
107 b_get_machine_custom_nodes_function/2,
108 b_machine_temp_predicate/1, set_temp_predicate/2, assert_temp_typed_predicate/1,
109 reset_temp_predicate/0,
110 add_additional_property/1, b_machine_additional_property/1,
111
112 get_animation_image/2, get_animation_image_source_file/2,
113 b_get_definition/5,
114 b_get_definition_string_from_machine/2,
115 b_definition_prefixed/4,
116 % get typed definitions without parameters:
117 b_get_typed_definition/3, b_get_typed_predicate_definition/3,
118 b_get_typed_expression_definition/3, b_get_true_expression_definition/1,
119
120 b_specialized_invariant_for_op/2, b_operation_preserves_full_invariant/1,
121 tcltk_get_specialized_invariant_for_op/2, tcltk_get_specialized_invariants_for_ops/1,
122 b_get_operation_normalized_read_write_info/3, % used to be b_normalized_rwsets_for_op/3,
123 reuse_operation_effect/2, candidate_operation_for_reuse/1,
124 b_operation_cannot_modify_state/1,
125 b_operation_reads_output_variables/3,
126 b_get_operation_non_det_modifies/2,
127
128 b_extract_values_clause_assignment/3,
129
130 b_type_expression/5,b_type_expression_for_full_b_machine/6,
131 b_type_open_predicate/5,b_type_open_predicate_with_errors/4,
132 b_type_open_exists_predicate/3,
133 type_with_errors/4,
134
135 b_show_machine_representation/3, b_write_machine_representation_to_file/2,
136 b_write_eventb_machine_to_classicalb_to_file/1,
137 b_show_eventb_as_classicalb/2,
138
139 b_get_machine_refinement_hierarchy/1,b_get_refined_machine/1,
140 b_get_model_type/1,
141 b_machine_statistics/2,
142
143 % More Proof Information:
144 discharged_guard_strengthening/4,
145
146 % Flow information
147 wp_untyped/3, clear_wp/0,
148 nonchanging_guard/2,
149 typecheck_predicates/4
150 ]).
151
152 :- use_module(library(lists)).
153 :- use_module(library(ordsets)).
154
155 :- use_module(self_check).
156 :- use_module(error_manager).
157 :- use_module(debug).
158 :- use_module(bmachine_construction,[check_machine/4,type_in_machine_l/6,type_open_predicate_with_quantifier/6]).
159 :- use_module(bsyntaxtree).
160 :- use_module(bmachine_structure,[get_section/3,write_section/4,get_section_texprs/3]).
161 :- use_module(parsercall).
162 :- use_module(tools).
163 :- use_module(translate,[translate_machine/3,translate_eventb_to_classicalb/3]).
164 :- use_module(bmachine_eventb,[check_event_b_project/4,is_eventb_additional_info/1]).
165 :- use_module(kernel_freetypes,[reset_freetypes/0,add_freetype/2]).
166 :- use_module(b_machine_hierarchy).
167 :- use_module('kodkod/kodkod', [replace_by_kodkod/3]).
168
169 :- use_module(b_global_sets,[find_inequal_global_set_identifiers/4,
170 b_get_prob_deferred_set_elements/2,
171 b_check_and_precompile_global_set_type_definitions/0]).
172
173 % for applying transformations on the machines
174 :- use_module(record_detection,[replace_sets_by_records/2]).
175 :- use_module(partition_detection,[detect_partitions/2]).
176
177 :- use_module(module_information,[module_info/2]).
178 :- module_info(group,infrastructure).
179 :- module_info(description,'This module provides access to the various parts of the loaded B machine.').
180
181 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
182 % bmachine: module for storing the currently loaded machine
183 % Contains predicates for getting (already typed) information about
184 % different parts of the machine
185 % many predicates are precompiled by b_precompile_machine/0, see below for
186 % details.
187
188 :- volatile bmachine_is_precompiled/0.
189 :- dynamic bmachine_is_precompiled/0. /* TRUE if the precompiled predicates have been set */
190
191 assert_bmachine_is_precompiled :-
192 (bmachine_is_precompiled -> true ; assert(bmachine_is_precompiled), debug_println(4,bmachine_is_precompiled)).
193
194 :- volatile machine/2.
195 :- dynamic machine/2.
196 % there is only one main machine fact
197
198 get_full_b_machine(Name,Res) :-
199 (machine(Name,M) -> Res=M
200 ; (ground(Name) -> add_error(bmachine,'No B machine with this name loaded:',Name)
201 ; add_error(bmachine,'No B machine loaded')),
202 fail
203 ).
204
205 full_b_machine(machine(Name,M)) :- get_full_b_machine(Name,M).
206
207 b_set_machine(Main,Machines,Errors) :-
208 b_machine_reset,
209 ? ~~mnf( check_machine(Main,Machines,M1,Errors1) ),!,
210 apply_machine_transformations(M1,ResultMachine),
211 ( no_real_perror_occurred(Errors1) ->
212 %% get_memory_used(M1), %%
213 assert_main_machine(ResultMachine)
214 %%, get_memory_used(M2),print_memory_used(M2), print_memory_used_difference(M1,M2),nl %%
215 ; otherwise ->
216 true),
217 Errors=Errors1.
218
219 assert_main_machine(X) :- nonvar(X), X=machine(A,B),!,assert(machine(A,B)). %, print(machine_asserted),nl.
220 assert_main_machine(X) :- add_internal_error('Illegal format: ',assert_main_machine(X)),fail.
221
222 :- meta_predicate apply_transformation_step(*,2,*,*).
223 % apply some transformations on the machine that require global information
224 % (other local transformations can be found in ast_cleanup)
225 apply_machine_transformations -->
226 apply_transformation_step('record definition detection', replace_sets_by_records),
227 apply_transformation_step('partition detection', detect_partitions).
228
229 apply_transformation_step(Name,Pred,In,Out) :-
230 ( call(Pred, In, Out) -> true
231 ; otherwise ->
232 ajoin(['applying ', Name, ' failed, skipping.'], Msg),
233 add_error(bmachine,Msg),
234 In=Out).
235
236 % try to translate (parts of) the properties to Kodkod
237 % if it succeeds, replace the translated predicates by
238 % calls to the Kodkod process
239 try_kodkod :-
240 get_preference(try_kodkod_on_load,true),
241 b_get_machine_constants(Constants),
242 Constants = [_|_],!,
243 b_get_properties_from_machine(OldPredicate),
244 ( replace_by_kodkod(Constants,OldPredicate,NewPredicate) ->
245 retract(machine(N,OldMachine)),
246 retractall( b_get_properties_from_machine(_) ),
247 write_section(properties,NewPredicate,machine(N,OldMachine),NewMachine),
248 assert( NewMachine ),
249 assert( b_get_properties_from_machine(NewPredicate) )
250 ; otherwise ->
251 true).
252 try_kodkod.
253
254 % set a machine term as current machine, without calling type checking
255 % (used for Z translations)
256 b_set_typed_machine(M1) :-
257 b_machine_clear,
258 apply_machine_transformations(M1,ResultMachine),
259 assert_main_machine(ResultMachine).
260
261 b_set_eventb_project_flat(Models,Contextes,Proofs) :-
262 b_machine_clear,
263 analyse_eventb_hierarchy(Models,Contextes),
264 ( check_event_b_project(Models,Contextes,Proofs,M1) ->
265 apply_machine_transformations(M1,ResultMachine),
266 assert_main_machine(ResultMachine) % has the form machine/2
267 ; otherwise ->
268 % Note: if there are typecheck errors due to missing .ptm files for axiomatic operators it is not an internal error!
269 add_internal_error('Loading Event-B Model failed; Please submit bug report.',b_set_eventb_project_flat(_,_,_)), %,project(Models,Contextes)),
270 fail).
271
272
273 :- volatile package/1, stored_preference/2.
274 :- dynamic package/1, stored_preference/2.
275 clear_package :- retractall(package(_)),retractall(stored_preference(_,_)).
276
277 b_load_eventb_project(Filename) :-
278 clear_package,
279 consult_without_redefine_warning(Filename),
280 (package(load_event_b_project(Machines,Contexts,Proofs,Errors))
281 -> true
282 ; package(load_event_b_project(Machines,Contexts,Errors))
283 -> Proofs=[], print('% Deprecated EventB Project without Proof Info.'),nl
284 ; add_error_and_fail(b_load_eventb_project,'This is not an EventB Project file:',Filename)
285 ),
286 (Errors=[] -> true ; add_error(b_load_eventb_project,'Errors in Event-B Package: ',Errors)),
287 read_stored_prefs,
288 b_set_eventb_project_flat(Machines,Contexts,Proofs),
289 clear_wp,
290 (load_additional_information(Proofs) -> true ; add_error(b_load_eventb_project,'Failed to load proof information',Proofs)).
291 % generate_specialized_invariants.
292
293 read_stored_prefs :- stored_preference(Pref,Val), print(stored_preference(Pref,Val)),nl,
294 preferences:set_preference(Pref,Val),fail.
295 read_stored_prefs.
296
297 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
298 % Collect Proof Information from Event B
299
300 :- volatile discharged/3.
301 :- volatile discharged_theorem/3, wd_po/3, wp_untyped/3.
302 :- volatile nonchanging_guard/2, discharged_guard_strengthening/4.
303 :- dynamic discharged/3.
304 % discharged(Model,Event,Name) : invariant Name in model Model is preserved by Event (no matter which Event at which refinement level)
305 :- dynamic discharged_theorem/3.
306 :- dynamic wd_po/3.
307 :- dynamic wp_untyped/3.
308 :- dynamic nonchanging_guard/2.
309 :- dynamic discharged_guard_strengthening/4.
310
311 :- volatile b_specialized_invariant_for_op/2.
312 :- dynamic b_specialized_invariant_for_op/2.
313 :- volatile get_proven_invariant/2.
314 :- dynamic get_proven_invariant/2.
315
316
317
318 clear_wp :-
319 retractall( wp_untyped(_,_,_) ).
320 %retractall( wp_typed(_,_,_) ). only in flow.pl
321
322 load_additional_information([]).
323 load_additional_information([H|T]) :-
324 load_additional_information_fact(H),!,
325 load_additional_information(T).
326 load_additional_information([H|T]) :-
327 add_internal_error('Unknown additional info: ',load_additional_information_fact(H)),
328 load_additional_information(T).
329
330 % old style proof info
331 load_additional_information_fact(discharged(Machine,Theorem)) :- % a discharged theorem
332 debug_println(9,discharged_theorem(Machine,old_style_proof_info,Theorem)),
333 assert(discharged_theorem(Machine,invariant,Theorem)).
334 load_additional_information_fact(discharged(Machine,Event,Invariant)) :-
335 debug_println(9,discharged(Machine,Event,Invariant)),
336 assert(discharged(Machine,Event,Invariant)).
337 load_additional_information_fact(Term) :- % theories are handled in bmachine_eventb.pl already
338 is_eventb_additional_info(Term).
339
340 % new style proof info po(Machine,Info,SourceList,Discharged)
341
342 load_additional_information_fact(po(Machine,'Invariant preservation',Source,true)) :- % invariant preservation
343 add_discharged_po_infos(Source,Machine).
344
345 load_additional_information_fact(po(Machine,'Invariant establishment',Source,true)) :- % invariant establishment
346 add_discharged_po_infos(Source,Machine).
347
348 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % invariant or theorem wd
349 ( Text = 'Well-definedness of Invariant'
350 ; Text = 'Well-definedness of Theorem'),
351 member(invariant(Invariant),Source),
352 debug_println(9,wd_po(Machine,Invariant,Proven)),
353 assert(wd_po(Machine,Invariant,Proven)).
354 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % axiom or axiom theorem wd
355 ( Text = 'Well-definedness of Axiom'
356 ; Text = 'Well-definedness of Theorem'),
357 member(axiom(Axiom),Source),
358 debug_println(9,wd_axiom(Machine,Axiom,Proven)). % TO DO: assert and use
359 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % proven theorem as guard
360 Text = 'Well-definedness of Theorem',
361 member(guard(Grd),Source),
362 member(event(Evt),Source),
363 debug_println(9,wd_axiom(Machine,Evt/Grd,Proven)). % TO DO: assert and use
364
365 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % wd of action
366 Text = 'Well-definedness of action',
367 member(action(ACT),Source), % probably the guard in the last event with discharged info ??
368 debug_println(9,wd_action(Machine,ACT,Proven)). % TO DO: assert and use
369 load_additional_information_fact(po(Machine,Text,Source,Proven)) :- % wd of guard
370 Text = 'Well-definedness of Guard',
371 member(guard(GRD),Source), % probably the guard in the last event with discharged info ??
372 debug_println(9,wd_guard(Machine,GRD,Proven)). % TO DO: assert and use
373
374 load_additional_information_fact(po(Machine,'Theorem',[invariant(Theorem)],true)) :- % a theorem
375 debug_println(9,discharged_theorem(Machine,invariant,Theorem)),
376 assert(discharged_theorem(Machine,invariant,Theorem)).
377 load_additional_information_fact(po(Machine,'Theorem',[axiom(Theorem)],true)) :- % a theorem
378 debug_println(9,discharged_theorem(Machine,axiom,Theorem)),
379 assert(discharged_theorem(Machine,axiom,Theorem)).
380 load_additional_information_fact(po(Machine,'Theorem',[guard(GuardTheorem),event(Event)],true)) :- % a theorem in a guard
381 debug_println(9,discharged_theorem(Machine,guard(Event),GuardTheorem)),
382 assert(discharged_theorem(Machine,guard(Event),GuardTheorem)).
383
384 % stuff we don't yet care about
385 load_additional_information_fact(po(Machine,Text,Infos,Proven)) :-
386 ( Text = 'Guard strengthening (split)'
387 ; Text = 'Guard strengthening (merge)'
388 ; Text = 'Guard strengthening' ),
389 !,
390 ((Proven=true, Infos = [event(AbsEvent),guard(Guard),event(ConcreteEvent)])
391 -> assert(discharged_guard_strengthening(Machine,AbsEvent,Guard,ConcreteEvent)),
392 print(discharged_guard_strengthening(Machine,AbsEvent,Guard,ConcreteEvent)),nl
393 ; true
394 ).
395 load_additional_information_fact(po(_,'Variant of event',_,_)).
396 load_additional_information_fact(po(_,'Natural number variant of event',_,_)).
397 load_additional_information_fact(po(_,'Action simulation',_,_)).
398 load_additional_information_fact(po(_,'Feasibility of witness',_,_)).
399 load_additional_information_fact(po(_,'Feasibility of action',_,_)).
400 load_additional_information_fact(po(_,'Well-definedness of witness',_,_)).
401 load_additional_information_fact(po(_,'Well-definedness of variant',_,_)).
402 load_additional_information_fact(po(_,'Finiteness of variant',_,_)).
403 load_additional_information_fact(po(_,'Equality of common variables',_,_)).
404
405 load_additional_information_fact(po(_Machine,_Kind,_Source,false)). % ignore everything that is not proven
406
407 load_additional_information_fact(po(_Machine,_Kind,_Source,reviewed)). % ignore everything that is only reviewed
408
409 % ignore exporter version for now
410 % we are compatible to both versions 2 and 3 (added abstract constants)
411 load_additional_information_fact(exporter_version(V)) :- V=2 ; V=3.
412
413 % ignored because the pragmas are attached to the machine in load_event_b_project/4
414 load_additional_information_fact(pragma(_Type,_Source,_AttachedTo,_Content)).
415
416 load_additional_information_fact(wp(S,D,P)) :-
417 assert( wp_untyped(S,D,P) ).
418
419 load_additional_information_fact(nonchanging_guard(E,P)) :-
420 typecheck_predicates(P,TypedPred,E,_),
421 assert(nonchanging_guard(E,TypedPred)).
422
423 load_additional_information_fact(invariant(_I)). %ignore
424
425 typecheck_predicates([],[],_,_).
426 typecheck_predicates([H|T],[TH|TT],S,D) :-
427 (S='INITIALISATION' -> Scope1 = []; Scope1=[operation(S)]),
428 ((D='INITIALISATION';var(D)) -> Scope2 = Scope1; Scope2=[operation(D)|Scope1]),
429 Scope = [variables|Scope2],
430 b_type_expression(H,Scope, _, TH, _),
431 typecheck_predicates(T,TT,S,D).
432
433
434 add_discharged_po_infos(Source,Machine) :-
435 % Source = [event(A1),...,event(CurMachineEvent),invariant(Inv)]
436 % 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)
437 get_bottom_event(Source,Event),
438 member(invariant(Invariant),Source),
439 debug_println(9,discharged(Machine,Event,Invariant)),
440 assert(discharged(Machine,Event,Invariant)),
441 % TO DO: should we propagate info up to abstract events which are not split up or where all refinements preserve a certain invariant ??
442 fail.
443 add_discharged_po_infos(_Source,_Machine).
444
445 % get the last event entry in proof info source list
446 get_bottom_event(Source,Event) :-
447 (bottom_event(Source,'$NONE'(none),Event) -> true
448 ; add_error(bmachine,'Could not determine event for proof info: ',Source),fail).
449 bottom_event([],Ev,Ev) :- Ev \= '$NONE'(none).
450 bottom_event([event(E)|T],_,Res) :- !,bottom_event(T,E,Res).
451 bottom_event([_|T],E,Res) :- bottom_event(T,E,Res).
452
453 :- use_module(debug).
454
455 %b_specialized_invariant_for_op_calc(Event,Invariant) :-
456 % b_get_invariant_from_machine(Invariant).
457
458 tcltk_get_specialized_invariants_for_ops(list(Res)) :-
459 findall([Name,' INVARIANT ',TI, '\n' | Tail],
460 ((b_top_level_operation(Name) ; Name='$initialise_machine'),
461 tcltk_get_specialized_invariant_for_op(Name,TI),
462 tcltk_get_proven_invariant_for_op(Name,PI),
463 (PI='none' -> Tail = ['END;']
464 ; Tail = [' NON-TRIVIAL PROVEN INVARIANT:', PI, 'END;']
465 )
466 ), Res).
467 tcltk_get_specialized_invariant_for_op(Event,TI) :-
468 (b_specialized_invariant_for_op(Event,Invariant) ->
469 translate:translate_bexpression(Invariant,TI)
470 ; TI = 'not_simplified').
471 tcltk_get_proven_invariant_for_op(Event,TI) :-
472 (get_proven_invariant(Event,Invariant), \+ is_truth(Invariant) ->
473 translate:translate_bexpression(Invariant,TI)
474 ; TI = 'none').
475
476 % use proof information to compute subset of invariant that needs to be checked for operations
477 :- public b_specialized_invariant_for_op_calc/2.
478 b_specialized_invariant_for_op_calc(Event,Invariant) :-
479 ? preferences:get_preference(use_po,true),
480 ? get_invariant_list_with_used_ids(IL,IL_Ids),
481 % 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)
482 ? IL \= [], % otherwise: Invariant already trivial; no sense in keeping track of information
483 ? get_op_or_init_and_syntax_filter(Event,ProofInfoEventName,IL,IL_Ids,RIL),
484 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
485 \+ (IL=RL), /* something filtered out */
486 debug_println(9,simplified(Event)),
487 conjunct_predicates(RL,Invariant). %, print(simplified),nl,translate:print_bexpr(Invariant),nl.
488
489
490 get_op_or_init_and_syntax_filter('$initialise_machine','INITIALISATION',IL,_,IL). % INIT always sets all variables
491 get_op_or_init_and_syntax_filter(Event,Event,IL,IL_Ids,RIL) :-
492 ? b_is_operation_name(Event),
493 filter_syntactically_relevant_invariants(IL,IL_Ids,Event,RIL). % filter out all invariants not modified by Event
494
495 % check if an operation preserves the full invariant; according to proof information
496 b_operation_preserves_full_invariant(Event) :-
497 b_specialized_invariant_for_op(Event,Invariant),
498 is_truth(Invariant).
499
500 :- public get_proven_invariant_calc/2.
501 % computes proven, relevant invariants (not trivial ones which are unaffected by Event) for main model
502 get_proven_invariant_calc(Event, Invariant) :-
503 ? preferences:get_preference(use_po,true),
504 ? b_machine_name(Model),
505 ? get_invariant_list_with_used_ids(IL,IL_Ids),
506 ? b_is_operation_name(Event),
507 %print(filter_syntactically_relevant_invariants(Event,Model)),debug:nl_time,
508 ~~mnf(filter_syntactically_relevant_invariants(IL,IL_Ids,Event,RIL)),
509 %print(select_proven_invariants(Event,Model)),debug:nl_time,
510 ~~mnf(select_proven_invariants(RIL,Model,Event,RL)),
511 %print(conjunct_predicates(Event,Model)),debug:nl_time,
512 conjunct_predicates(RL,Invariant).
513
514 get_invariant_list_with_used_ids(IL,IL_Ids) :-
515 b_get_invariant_from_machine(I),
516 conjunction_to_list(I,IL),
517 maplist(find_id_uses_for_maplist,IL,IL_Ids).
518 find_id_uses_for_maplist(Inv,IDs) :- find_identifier_uses(Inv,[],IDs).
519
520 % compute all invariants which are not fully proven:
521 get_unproven_invariants(UnProvenList) :-
522 findall(I,get_unproven_invariant_calc(I),UnProvenList).
523 get_unproven_invariant_calc(Invariant) :- % not precompiled at the moment
524 b_machine_name(Model),
525 b_get_invariant_from_machine(I),
526 conjunction_to_list(I,IL),
527 member(Invariant,IL),
528 (is_unproven_inv_for_model(Invariant,Model,_) -> true
529 ; debug_mode(on) -> print('PROVEN INVARIANT: '), translate:print_bexpr(Invariant),nl,fail
530 ).
531 is_unproven_inv_for_model(_Invariant,_Model,_Event) :-
532 preferences:get_preference(use_po,false),!.
533 is_unproven_inv_for_model(Invariant,Model,Event) :-
534 b_is_operation_name(Event),
535 is_syntactically_relevant_invariant_for_event(Event,Invariant),
536 \+ is_proven_invariant_for_model(Model,Event,Invariant).
537
538
539 % filter_syntactically_relevant_invariants(+InvariantsList, +UsedIDs, +EventName, -RelevantItemsFromInvariantsList)
540 filter_syntactically_relevant_invariants(Invariants,IL_Ids,Event,Result) :-
541 get_operation_info(Event,SubstitutionInfo),
542 get_modifies_from_info(SubstitutionInfo,SortedModIds),
543 filter_syntactically_relevant_invariants2(Invariants,IL_Ids,SortedModIds,Result).
544 % noticeably faster than include, see e.g. public_examples/B/PerformanceTests/Generated/Generated4000.mch
545 %include(is_syntactically_relevant_inv(SortedModIds),Invariants,IL_Ids,Result).
546
547 is_syntactically_relevant_inv(SortedModIds,_Inv,IDs) :-
548 ord_intersect(SortedModIds,IDs).
549
550 filter_syntactically_relevant_invariants2([],_,_,[]).
551 filter_syntactically_relevant_invariants2([Inv|T],[IDs|TI],SortedModIds,R) :-
552 (is_syntactically_relevant_inv(SortedModIds,Inv,IDs)
553 -> R=[Inv|TR] ; R=TR),
554 filter_syntactically_relevant_invariants2(T,TI,SortedModIds,TR).
555
556 is_syntactically_relevant_invariant_for_event(Event,Inv) :-
557 get_operation_info(Event,SubstitutionInfo),
558 get_modifies_from_info(SubstitutionInfo,SortedModIds),
559 find_id_uses_for_maplist(Inv,IDs),
560 is_syntactically_relevant_inv(SortedModIds,_Inv,IDs).
561
562 get_modifies_from_info(SubstitutionInfo,SortedModIds) :-
563 ((memberchk(modifies(ModID),SubstitutionInfo) -> ground(ModID))
564 -> list_to_ord_set(ModID,SortedModIds) % is this necessary ?
565 ; SortedModIds=[]).
566
567 % filter_proven_invariants(+InvariantsList, +ModelName, +EventName, -RelevantItemsFromInvariantsList)
568 % this gets called during model checking time
569 is_proven_invariant(Event,E) :-
570 % print('Filter Check: '), print(Event), print(' : '),translate:print_bexpr(E),nl,
571 get_texpr_pos(E,POS),
572 POS = rodinpos(Model,Name,_), % only accept new rodinpos information with three parameters !
573 !, % the old one with two parameters could lead to confusion as labels can be reused
574 % TO DO: check that if E is not always well-defined that there are no unproven WD proof obligations !
575 discharged_invariant(Model,Name,Event),
576 check_wd_discharged_inv_or_thm(E,Model,Name,Event). %% print('DISCHARGED'(Model,Event,Name)),nl.
577
578 check_wd_discharged_inv_or_thm(E,_,_,_) :- always_well_defined(E),!.
579 check_wd_discharged_inv_or_thm(_,Model,Name,_Event) :- wd_po(Model,Name,ProofStatus),!,
580 ProofStatus=true.
581 check_wd_discharged_inv_or_thm(_,Model,Name,Event) :-
582 format('% Assuming invariant/theorem ~w is well-defined for event ~w:~w.~n',[Name,Model,Event]).
583
584 % select_proven_invariants(+InvariantsList, +ModelName, +EventName, -RelevantItemsFromInvariantsList)
585 select_proven_invariants(Invariants,Model,Event,Result) :-
586 include(is_proven_invariant_for_model(Model,Event),Invariants,Result).
587
588 % Note: different from is_proven_invariant; TO DO: merge (here we assume main model)
589 is_proven_invariant_for_model(MainModel,Event,E) :- %% print(chck(MainModel,Event)),nl,
590 get_rodin_name(E,Name), % if we do not have a rodin position we consider this as not proved
591 (get_rodin_model_name(E,Model) -> true
592 ; formatsilent('Could not get Rodin model name for invariant: ~w~n',[Name]),
593 Model=MainModel,
594 fail % we have an old style .eventb file; safer to assume not proven as there can be clashes of labels
595 ),
596 discharged_invariant(Model,Name,Event).
597
598 is_discharged_assertion(Theorem) :-
599 if( get_texpr_pos(Theorem,rodinpos(Model,Name,_)),
600 (discharged_theorem(Model,_,Name), % does not matter if invariant or axiom
601 check_wd_discharged_inv_or_thm(Theorem,Model,Name,assertion) ) % check that well-defined
602 , (specfile:animation_minor_mode(eventb),
603 (silent_mode(on) -> true
604 ; print('Could not get position information for theorem: '),
605 translate:print_bexpr(Theorem),nl,
606 get_texpr_pos(Theorem,POS),debug_println(19,get_texpr_pos(POS))
607 ),
608 fail)
609 ).
610 % derived predicate
611 discharged_invariant(Model,InvariantName,Event) :-
612 % InvariantName from model Model is preserved by Event and any of its refinements
613 discharged(Model,Event,InvariantName).
614 discharged_invariant(Model,InvariantName,Event) :-
615 % InvariantName from model Model is preserved by Event and any of its refinements
616 also_discharged(Model,Event,InvariantName).
617
618 b_machine_has_proven_invariants :-
619 (discharged(_,_,_) -> true).
620
621 % complete the discharged/3 information: propagating information from abstract events
622 % down to refined top-level events
623 :- public complete_discharged_info_calc/0.
624 complete_discharged_info_calc :- debug_println(4,'completing discharged info: '),
625 statistics(runtime,[Start,_]),
626 (complete_discharged_info2 -> true ; true),
627 statistics(runtime,[Stop,_]), T is Stop-Start, debug_print(4,T), debug_println(4,' ms').
628 :- volatile discharged2/2, also_discharged/3.
629 :- dynamic discharged2/2.
630 :- dynamic also_discharged/3.
631 discharged_info_exists :- discharged2(_,_),!.
632 complete_discharged_info2 :- retractall(also_discharged(_,_,_)),
633 retractall(discharged2(_,_)),
634 discharged(Model,Event,_), % find out which Model and Events are used in discharged info
635 \+ discharged2(Model,Event), %print(discharged(Model,Event)),nl,
636 assert(discharged2(Model,Event)),fail.
637 complete_discharged_info2 :- discharged_info_exists,
638 b_get_animated_sections(Sections),
639 discharged2(Model,Event), % Event in Model was proven to preserve an invariant in Model
640 b_get_abstract_events(Event,RModel,AbstractEvents), % search for a refinement of Model where the same event exists
641 RModel \= Model,
642 % i.e., invariant Name was proven in an abstract Model for Event
643 \+ is_abstract_event_in_list(Event,Model,AbstractEvents), % this event is *NOT* a refinement of the proven one
644 debug_println(4,removing_discharged(Model,Event)),
645 retractall(discharged(Model,Event,_Name)),
646 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
647 % (otherwise the refinement may well exist but has been filtered out by restricting the animation levels)
648 add_error(event_refinement,'An event does not refine an abstract event of the same name: ',Event:Model:RModel),
649 % This will could cause errors in the proof information usage !
650 %print(AbstractEvents),nl,
651 fail.
652 complete_discharged_info2 :- discharged_info_exists,
653 complete_discharged_info3(_Model,_Event,_Name).
654 complete_discharged_info3(InvNameModel,AbsEvent,Name) :-
655 b_get_abstract_events(EventInRefinement,_RefModel,AbstrEvents),
656 is_abstract_event_in_list(AbsEvent,InvNameModel,AbstrEvents), % Event in InvNameModel is an abstract event of EventInRefinement
657 %print(check(InvNameModel,Event, EventInRefinement,RefModel)),nl,
658 discharged(InvNameModel,AbsEvent,Name), % print(chck2(Model,Event,Name)),nl,
659 %InvNameModel:Name has been proven for AbsEvent *at all relevant* levels
660 \+ discharged(InvNameModel,EventInRefinement,Name),
661 \+ also_discharged(InvNameModel,EventInRefinement,Name),
662 % this invariant has not yet been marked as proven for EventInRefinement
663 debug_println(4,also_discharged_in_refinement(InvNameModel:Name,EventInRefinement,refined_from(AbsEvent))),
664 assert(also_discharged(InvNameModel,EventInRefinement,Name)),
665 fail.
666
667 %abstract_event_of_calc(TopLevelEvent,RModel,Event,Model) :-
668 % b_get_abstract_events(TopLevelEvent,RModel,AbstrEvents),
669 % is_abstract_event_in_list(Event,Model,AbstrEvents) , print(abs(TopLevelEvent,RModel,Event,Model)),nl.
670
671 is_abstract_event_in_list(Event,Model,AbstractEvents) :-
672 member(b(rlevent(AEvent,AModel,_S,_P,_G,_Thm,_Act,_VW,_PW,_Unm,AbstractEvents2),_,_),AbstractEvents),
673 (Event=AEvent, Model=AModel;
674 is_abstract_event_in_list(Event,Model,AbstractEvents2)).
675
676 % get events that are refined by an event
677 b_get_abstract_events(Name,Section,AbsEvents) :-
678 b_get_machine_operation(Name,_R,_P,Body,_OType,_OpPos),
679 get_texpr_expr(Body,RLEVENT),
680 RLEVENT = rlevent(_Name,Section,_Stat,_Parameters,_Grd,_Thm,_Act,_VWit,_PWit,_Unmod,AbsEvents).
681
682 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
683
684 :- volatile b_operation_reads_output_variables/3, b_operation_cannot_modify_state/1.
685 :- dynamic b_operation_reads_output_variables/3, b_operation_cannot_modify_state/1.
686
687 % test if we have a query or skip operation which cannot modify the state
688 % (preconditions, assertions could still fail though !)
689 :- public b_operation_cannot_modify_state_calc/1.
690 b_operation_cannot_modify_state_calc(Event) :-
691 ? b_get_operation_normalized_read_write_info(Event,_ReadVariables,[]).
692
693 :- use_module(b_read_write_info, [get_accessed_vars/4]).
694 % check if classical B operation reads its output variables
695 :- public b_operation_reads_output_variables_calc/3.
696 b_operation_reads_output_variables_calc(Event,ReadOutputVariablesIds,ReadOutputTypedInfo) :-
697 ? b_get_machine_operation(Event,Res,_TParas,TBody,_OType,_Pos),
698 def_get_texpr_ids(Res,ResIds),
699 sort(ResIds,SResIds),
700 get_operation_info(Event,SubstitutionInfo),
701 member(reads_locals(Reads),SubstitutionInfo),
702 ord_intersection(Reads,SResIds,ReadOutputVariablesIds),
703 ReadOutputVariablesIds \= [],
704 % now recompute the information based on TBody after ast_cleanup: typing predicates have been removed
705 get_accessed_vars(TBody,[],_,AllReadsAfterAstCleanup),
706 ord_intersection(AllReadsAfterAstCleanup,ReadOutputVariablesIds,ReadOutputVariablesIds2),
707 ReadOutputVariablesIds2 \= [],
708 debug_format(20,'Operation ~w is reading output parameters: ~w!~n',[Event,ReadOutputVariablesIds2]),
709 findall(reads_result(Index,ID,Type),
710 (nth1(Index,Res,b(identifier(ID),Type,_)), ord_member(ID,ReadOutputVariablesIds2)),
711 ReadOutputTypedInfo).
712
713
714 % Reuse information
715
716 :- volatile b_get_operation_normalized_read_write_info/3.
717 :- dynamic b_get_operation_normalized_read_write_info/3.
718 :- volatile reuse_operation_effect/2, candidate_operation_for_reuse/1.
719 :- dynamic reuse_operation_effect/2, candidate_operation_for_reuse/1.
720
721 :- use_module(bsyntaxtree,[get_global_identifiers/1]).
722
723 :- public b_get_operation_normalized_read_write_info_calc/3.
724 /* compute Read and Written Variables by an operation */
725 b_get_operation_normalized_read_write_info_calc(Event,SortedReadVariables,SortedWrittenVariables) :-
726 ? get_global_identifiers(IS), % Note: find identifier uses was called before global sets precompiled
727 ? get_operation_info(Event,SubstitutionInfo),
728 (memberchk(modifies(WrittenVariables),SubstitutionInfo)
729 -> sort(WrittenVariables,SWV), % normally not necessary; just to be sure
730 ord_subtract(SWV,IS,SortedWrittenVariables)
731 ; print(no_modifies_info(Event)),nl,fail),
732 (memberchk(reads(ReadVariables),SubstitutionInfo)
733 -> sort(ReadVariables,SWR),
734 ord_subtract(SWR,IS,SortedReadVariables)
735 ; debug_println(9,no_reads_info(Event)),fail). % happens currently in Event-B !
736 %% , print(read_write_set(Event,ReadVariables,WrittenVariables)),nl.
737
738 :- use_module(specfile, [animation_minor_mode/1]).
739 :- public reuse_operation_effect_calc/2.
740 % True if after Executing Operation G:
741 % the effect of the operation H (which writes variables in WriteH) is unaffected
742 reuse_operation_effect_calc(G,H) :- get_preference(try_operation_reuse,true),
743 (specfile:animation_minor_mode(eventb) -> print('% OPERATION_REUSE not available for Event-B models'),nl,fail
744 % this doesn't work ; see eg. prob_examples/examples/EventBPrologPackages/Advance_WP2/v6_Sep2014/ex_mch.eventb -animate 300 which generates deadlock
745 ; true),
746 b_is_operation_name(G),
747 b_get_operation_normalized_read_write_info(G,_ReadG,WriteG), %print(analyse_reuse(G,_ReadG,WriteG)),nl,
748 WriteG \= [], /* otherwise we have a skip operation; we will not recompute state anyway */
749 b_get_machine_operation(H,_Results,_Parameters,_Body,OpType,_), % TO DO: check if _Body complicated enough
750 b_get_operation_normalized_read_write_info(H,ReadH,WriteH),
751 \+ ord_intersect(WriteG,ReadH),
752 (OpType = classic
753 -> \+ ord_intersect(WriteG,WriteH) % because for the moment we do not yet detect whether a potentially written variable by H is really written !
754 % TO DO: either store in reuse_operation the actual variables written, then we can remove the above line
755 % or compute the variables that are potentially written PotWriteH and intersect with those
756 ; true
757 ),
758 (debug:debug_mode(on) -> format('After: ~w reuse: ~w~n',[G,H]) ; true)
759 %,format('~nAfter: ~w (writes ~w)~n reuse: ~w (reads ~w, writes ~w)~n',[G,WriteG,H,ReadH,WriteH]) %%
760 .
761 reuse_operation_effect_calc(_,_) :- get_preference(try_operation_reuse,true),
762 findall(G,b_is_operation_name(G),LG), length(LG,NrOps), TotPairs is NrOps*NrOps,
763 findall((G,H),reuse_operation_effect(G,H),Pairs), length(Pairs,NrReuse),
764 formatsilent('OPERATION_REUSE Statistics: ~w reuse pairs (for ~w operations, i.e. ~w pairs)~n',[NrReuse,NrOps,TotPairs]),
765 fail.
766
767 :- public candidate_operation_for_reuse_calc/1.
768 % True if for that operation we may be able sometimes to reuse previously calculated effects
769 candidate_operation_for_reuse_calc(Op) :- reuse_operation_effect(_,Op). % no need to avoid multiple solutions; auto_precompile will remove them
770
771 :- public print_reuse/0.
772 print_reuse :-
773 findall((G,H),reuse_operation_effect(G,H),L),
774 print_reuse_info(L).
775
776 print_reuse_info([]).
777 print_reuse_info([(G,H)|T]) :- print('When applying '),print(H),print(' after '),
778 print(G),print(' recalculate only '),
779 b_get_operation_normalized_read_write_info(H,_ReadH,WriteH),
780 print(WriteH),nl, print_reuse_info(T).
781
782 :- volatile b_get_operation_non_det_modifies/2.
783 :- dynamic b_get_operation_non_det_modifies/2.
784 :- public b_get_operation_non_det_modifies_calc/2.
785 :- use_module(b_read_write_info,[get_nondet_modified_vars/3]).
786 % determine which variables are non-deterministically written by an operation
787 b_get_operation_non_det_modifies_calc(OpName,NonDetModifies) :-
788 ? b_get_machine_operation(OpName,Results,Parameters,Body,_OpType,_),
789 append(Results,Parameters,TLocalVars),
790 get_texpr_ids(TLocalVars,LocalVars),
791 get_nondet_modified_vars(Body,LocalVars,NonDetModifies),debug_println(19,non_det_modifies(OpName,NonDetModifies)).
792 b_get_operation_non_det_modifies_calc('$initialise_machine',NonDetModifies) :-
793 b_get_initialisation_from_machine(Body,_),
794 get_nondet_modified_vars(Body,[],NonDetModifies),debug_println(19,init_not_det_modifies(NonDetModifies)).
795
796
797 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
798
799
800 consult_without_redefine_warning(File) :-
801 prolog_flag(redefine_warnings, Old, off),
802 (% load in dynamic mode: so that we can retract later
803 my_consult(File)
804 -> OK=true ; OK=false),
805 prolog_flag(redefine_warnings, _, Old),
806 (OK=true -> true ;
807 add_error_and_fail(bmachine,'Consulting of File failed: ',File)).
808
809 my_consult(File) :- on_exception(error(existence_error(_,_),_),
810 load_files(File,[compilation_mode(assert_all)]),
811 add_error_fail(my_consult,'File does not exist: ',File)).
812
813 :- volatile b_get_all_used_filenames/1, b_get_main_filename/1, b_get_main_filenumber/1.
814 :- dynamic b_get_all_used_filenames/1. % can be used, e.g., for second argument of pos info field
815 :- dynamic b_get_main_filename/1. % can be used in above list; there is also specfile:currently_opened_file
816 :- dynamic b_get_main_filenumber/1. % the number of the main_file in the b_get_all_used_filenames list (useful for pos information)
817
818 b_load_machine_from_file(Filename) :-
819 (debug_mode(on)
820 -> get_parser_version(Version),
821 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
822 ; true),
823 b_load_reset,
824 debug_stats(loading(Filename)),
825 catch(load_b_machine_as_term(Filename,Machine),
826 parse_errors(Errors),
827 (add_all_perrors_in_context_of_used_filenames(Errors,parse_error),fail)),
828 b_load_machine_from_term(Filename,Machine).
829
830
831 % add parse errors in context of current machine and its filenames
832 add_all_perrors_in_context_of_used_filenames(Errors,TypeOfError) :- Errors\=[],
833 b_get_all_used_filenames(Filenames),!,
834 add_all_perrors(Errors,Filenames,TypeOfError).
835 add_all_perrors_in_context_of_used_filenames(Errors,TypeOfError) :-
836 (Errors=[] -> true ; debug_println(19,'Unable to obtain filenames for parse errors, probably preparse_error')),
837 add_all_perrors(Errors,[],TypeOfError).
838
839
840 % a way to load .prob files directly
841 b_load_machine_probfile(Filename) :- b_load_reset,
842 load_b_machine_probfile_as_term(Filename,Machine),
843 b_load_machine_from_term(Filename,Machine).
844
845 % a way to load form a list of Facts which would be found in the .prob file
846 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
847 load_b_machine_list_of_facts_as_term(ListOfFacts,Machine),
848 b_load_machine_from_term(Filename,Machine).
849
850
851
852 b_load_reset :-
853 retractall(b_get_all_used_filenames(_)), retractall(b_get_main_filename(_)),
854 retractall(b_get_main_filenumber(_)).
855
856 b_load_machine_from_term(Filename,complete_machine(MainName,Machines,Filenames)) :-
857 b_load_reset, % call in case we call this predicate directly from outside
858 !,
859 assert(b_get_main_filename(Filename)),assert(b_get_all_used_filenames(Filenames)),
860 store_filenumbers(Filenames),
861 (find_main_file_name(Nr,Filenames,Filename) -> assert(b_get_main_filenumber(Nr))
862 ; ajoin(['Main filename ', Filename, ' does not appear in filenames list: '],Msg),
863 add_warning(bmachine,Msg,Filenames)
864 ),
865 %print(find_main_file_name(Nr,Filenames,Filename)),nl,
866 check_valid_machine_name(MainName),
867 debug_stats(analyse_hierarchy(MainName,Filename)),
868 (analyse_hierarchy(MainName,Machines)
869 -> true ; add_error(b_load_machine,'Analyse Hierarchy failed'),fail),
870 debug_stats(type_check(MainName,Filename)),
871 ~~mnf( b_set_machine(MainName,Machines,Errors) ), % Typechecking
872 debug_stats(checked_machine(MainName,Filename)),
873 add_all_perrors(Errors,Filenames,type_error), % TO DO: use type_check as source as this may also generate warnings
874 no_real_perror_occurred(Errors).
875 b_load_machine_from_term(F,X) :- add_internal_error('Illegal machine: ',b_load_machine_from_term(F,X)),
876 fail.
877
878 check_valid_machine_name(Name) :- atom(Name),atom_codes(Name,Codes),
879 invalid_chars(Invalid),
880 ? (member(C,Codes),ord_member(C,Invalid)
881 -> ajoin(['Machine name ', Name, ' contains illegal character: '],Msg),
882 atom_codes(IChar,[C]),
883 add_warning(bmachine,Msg,IChar)
884 ; true),
885 !.
886 check_valid_machine_name(Name) :- add_internal_error('Illegal machine name:',check_valid_machine_name(Name)).
887
888 invalid_chars(".").
889
890 find_main_file_name(Nr,_Filenames,File) :- safe_absolute_file_name(File,AF),
891 tools:get_modulename_filename(AF,TAF), tools:get_filename_extension(AF,ExtF),
892 (ExtF = prob -> member(EXT,[mch,ref,imp,tla,rmch]) % any machine extension is ok for .prob file
893 ; EXT =ExtF),
894 b_filenumber(TAF,EXT,Nr,_).
895 %find_main_file_name_aux(Nr,Filenames,TAF,EXT).
896 %find_main_file_name_aux(1,[H|_],TAF,ExtF) :- absolute_file_name(H,AF),tools:get_modulename_filename(AF,TAF),
897 % tools:get_filename_extension(AF,ExtF).
898 %find_main_file_name_aux(Nr,[_|T],TAF,ExtF) :- find_main_file_name_aux(N1,T,TAF,ExtF), Nr is N1+1.
899
900
901 % remember as facts all B filenames, their extension and their number
902 :- volatile b_filenumber/4.
903 :- dynamic b_filenumber/4.
904 store_filenumbers(Filenames) :- retractall(b_filenumber(_,_,_,_)),
905 store_filenumbers(Filenames,1).
906 store_filenumbers([],_).
907 store_filenumbers([H|T],Nr) :-
908 safe_absolute_file_name(H,AF),tools:get_modulename_filename(AF,ModuleName),
909 tools:get_filename_extension(AF,ExtF),
910 assert(b_filenumber(ModuleName,ExtF,Nr,AF)),
911 debug_println(9,b_filenumber(ModuleName,ExtF,Nr,AF)),
912 N1 is Nr+1,
913 store_filenumbers(T,N1).
914
915 :- use_module(tools,[safe_absolute_file_name/3]).
916 % open a file relateive to the main B file
917 b_absolute_file_name_relative_to_main_machine(File,AbsFileName) :-
918 b_get_main_filename(MainFileName),
919 safe_absolute_file_name(File,AbsFileName,[relative_to(MainFileName)]).
920
921 % call to clear all data stored for machine
922 b_machine_clear :-
923 b_machine_reset,
924 retractall(b_filenumber(_,_,_,_)).
925
926 :- use_module(btypechecker,[reset_typechecker/0]).
927 :- use_module(b_global_sets,[b_clear_global_set_type_definitions/0]).
928 :- use_module(bmachine_construction,[reset_bmachine_construction/0]).
929 b_machine_reset :- % print(b_machine_reset),nl,
930 retractall(machine(_,_)),
931 retractall(discharged_theorem(_,_,_)),
932 retractall(discharged_guard_strengthening(_,_,_,_)),
933 retractall(discharged(_,_,_)),
934 retractall(wd_po(_,_,_)),
935 retractall(also_discharged(_,_,_)),
936 reset_temp_predicate,
937 retractall(b_machine_additional_property(_)),
938 reset_typechecker,
939 b_clear_global_set_type_definitions,
940 reset_bmachine_construction,
941 startup_precompiled. % change so that error messages generated if we call them
942
943 :- use_module(eventhandling,[register_event_listener/3]).
944 :- register_event_listener(clear_specification,b_machine_clear,
945 'Reset bmachine facts.').
946
947 % :- use_module(library(random)).
948 :- use_module(preferences,[get_preference/2]).
949
950
951
952
953 % precompiled
954 :- volatile b_machine_name/1.
955 :- dynamic b_machine_name/1.
956 :- public b_machine_name_calc/1.
957 b_machine_name_calc(Name) :-
958 get_full_b_machine(Name,_).
959
960 b_get_animated_sections(Sections) :-
961 get_section_from_current_machine(meta,MetaInfos),
962 ( member(animated_sections(Sections), MetaInfos) -> true
963 ; otherwise -> add_error(bmachine,'No animated sections available'), fail).
964
965 :- volatile b_get_named_machine_set/3.
966 :- dynamic b_get_named_machine_set/3.
967 :- public b_get_named_machine_set_calc/3.
968 ?b_get_named_machine_set(Set,Members) :- b_get_named_machine_set(Set,_,Members).
969 % precompiled: all enumerated sets with their elements (all in atomic form)
970 b_get_named_machine_set_calc(Set,TExpr,Members) :-
971 ? get_section_from_current_machine(enumerated_sets,Sets),
972 ? get_section_from_current_machine(enumerated_elements,Elems),
973 ? get_texpr_id(TExpr,Set),
974 ? get_texpr_type(TExpr,set(Type)),
975 ? get_texpr_type(TElem,Type),
976 ? member(TExpr,Sets),
977 findall(E, (member(TElem,Elems), get_texpr_id(TElem,E)), Members).
978
979 :- volatile b_get_machine_set/2.
980 :- dynamic b_get_machine_set/2.
981 :- public b_get_machine_set_calc/2.
982 ?b_get_machine_set(Set) :- b_get_machine_set(Set,_).
983 % precompiled: all deferred and enumerated sets (in atomic form)
984 b_get_machine_set_calc(Set,TExpr) :-
985 ? get_section_from_current_machine(deferred_sets,Sets),
986 ? get_texpr_id(TExpr,Set),
987 ? member(TExpr,Sets).
988 b_get_machine_set_calc(Set,TExpr) :-
989 ? b_get_named_machine_set(Set,TExpr,_).
990
991 :- volatile b_get_machine_constants/1, b_get_machine_all_constants/1, b_get_machine_variables/1, b_is_constant/2, b_is_variable/2, b_get_constant_variable_description/2.
992 :- dynamic b_get_machine_constants/1, b_get_machine_all_constants/1, b_get_machine_variables/1, b_is_constant/2, b_is_variable/2, b_get_constant_variable_description/2.
993 b_machine_has_constants :- b_get_machine_constants([_|_]).
994 :- public b_get_machine_all_constants_calc/1.
995 % precompiled: all constants (abstract and concrete) in typed form
996 b_get_machine_all_constants_calc(Csts) :-
997 findall(C,get_multi_sections([abstract_constants,concrete_constants],C),Csts).
998 :- public b_get_machine_constants_calc/1.
999 % precompiled: all constants (abstract and concrete) in typed form; except for constant_represented inside global set
1000 b_get_machine_constants_calc(Csts) :-
1001 findall(C,
1002 (get_multi_sections([abstract_constants,concrete_constants],C),
1003 get_texpr_id(C,CID),
1004 \+ b_get_constant_represented_inside_global_set(CID,_)), Csts).
1005
1006 b_machine_has_variables :- b_get_machine_variables([_|_]).
1007 :- public b_get_machine_variables_calc/1.
1008 % precompiled: all variables (abstract and concrete) in typed form
1009 b_get_machine_variables_calc(Vars) :-
1010 findall(V,get_multi_sections([abstract_variables,concrete_variables],V),Vars).
1011
1012
1013 ?b_is_constant(C) :- b_is_constant(C,_).
1014 :- public b_is_constant_calc/2.
1015 % precompiled: all constants (abstract and concrete) in atomic form
1016 b_is_constant_calc(Cst,Type) :-
1017 ? b_get_machine_constants(Constants),
1018 ? get_texpr_id(Term,Cst),
1019 ? get_texpr_type(Term,Type),
1020 ? member(Term,Constants).
1021 b_is_variable(V) :- b_is_variable(V,_).
1022 :- public b_is_variable_calc/2.
1023 % precompiled: all variables (abstract and concrete) in atomic form
1024 b_is_variable_calc(Var,Type) :-
1025 ? b_get_machine_variables(Vars),
1026 ? get_texpr_id(Term,Var),
1027 ? get_texpr_type(Term,Type),
1028 ? member(Term,Vars).
1029 % look up elements in several sections of the machine
1030 get_multi_sections(Sections,Elem) :-
1031 ? member(Section,Sections),
1032 ? get_section_from_current_machine(Section,List),
1033 ? member(Elem,List).
1034
1035 :- public b_get_constant_variable_description_calc/2.
1036 % get value of description pragmas @desc for variables and constants:
1037 b_get_constant_variable_description_calc(ID,Desc) :-
1038 ? (b_get_machine_constants(L) ; b_get_machine_variables(L)),
1039 get_texpr_id(Term,ID),
1040 ? member(Term,L),
1041 get_texpr_description(Term,Desc).
1042
1043
1044 :- volatile b_get_invariant_from_machine/1,
1045 b_get_linking_invariant_from_machine/1,
1046 b_get_properties_from_machine/1,
1047 b_get_static_assertions_from_machine/1,
1048 b_extract_values_clause_assignment/3,
1049 b_get_unproven_static_assertions_from_machine/1,
1050 b_get_dynamic_assertions_from_machine/1,
1051 b_get_unproven_dynamic_assertions_from_machine/1,
1052 b_get_assertions_from_main_machine/2,
1053 b_get_initialisation_from_machine/2,
1054 b_get_machine_operation/6,b_top_level_operation/1,
1055 b_is_operation_name/1,
1056 b_get_promoted_machine_operations/1.
1057 :- dynamic b_get_invariant_from_machine/1,
1058 b_get_linking_invariant_from_machine/1,
1059 b_get_properties_from_machine/1,
1060 b_get_static_assertions_from_machine/1,
1061 b_extract_values_clause_assignment/3,
1062 b_get_unproven_static_assertions_from_machine/1,
1063 b_get_dynamic_assertions_from_machine/1,
1064 b_get_unproven_dynamic_assertions_from_machine/1,
1065 b_get_assertions_from_main_machine/2,
1066 b_get_initialisation_from_machine/2,
1067 b_get_machine_operation/6,b_top_level_operation/1,
1068 b_is_operation_name/1,
1069 b_get_promoted_machine_operations/1.
1070
1071 :- public b_get_invariant_from_machine_calc/1.
1072 % precompiled: typed invariant (a predicate)
1073 b_get_invariant_from_machine_calc(Inv) :-
1074 get_section_from_current_machine(invariant,Inv).
1075
1076 :- public b_get_linking_invariant_from_machine_calc/1.
1077 % precompiled: typed linking invariant (a predicate)
1078 b_get_linking_invariant_from_machine_calc(Inv) :-
1079 get_section_from_current_machine(linking_invariant,Inv).
1080
1081 :- public b_get_properties_from_machine_calc/1.
1082 % precompiled: typed properties (a predicate)
1083 b_get_properties_from_machine_calc(SortedProp) :-
1084 get_section_from_current_machine(properties,Prop),
1085 (sort_properties(Prop,SortedProp) -> true %(Prop=SortedProp->true ; print(sorted(SortedProp)))
1086 ; (add_error(sort_properties,'sort_properties failed: ',Prop),
1087 print(sort_properties_failed),nl,SortedProp=Prop)).
1088
1089 sort_properties(Prop,SortedProp) :- % print(sort_properties),nl,statistics(runtime, [R1,_]),
1090 ~~mnf(weigh_properties(Prop,1,_,[],SProp)),
1091 % statistics(runtime, [R2,_]), RDiff is R2-R1,print(done_weigh(RDiff,SProp)),nl,
1092 sort(SProp,SSProp),
1093 % statistics(runtime, [R3,_]), RDiff2 is R3-R2,print(done_sort(RDiff2)),nl,
1094 ~~mnf(remove_weights(SSProp,PropList)),
1095 ~~mnf(conjunct_predicates(PropList,SortedProp)).
1096 % translate:print_bexpr(SortedProp).
1097
1098 remove_weights([],[]).
1099 remove_weights([prop(_W,_Nr,E)|T],[E|RT]) :- remove_weights(T,RT).
1100
1101 weigh_properties(Pred,Nr,ONr,InL,OutL) :-
1102 decompose_conjunct(Pred,LHS,RHS), % will propagate labels down to conjuncts LHS,RHS
1103 !,
1104 weigh_properties(LHS,Nr,N1,InL,L2),
1105 weigh_properties(RHS,N1,ONr,L2,OutL).
1106 weigh_properties(b(Pred,S,I),Nr,N1,T,[prop(Weight,Nr,b(Pred,S,I))|T]) :-
1107 N1 is Nr+1, weigh_properties2(Pred,Weight).
1108 % translate:print_bexpr(b(Pred,S,I)), print(' WEIGHT: '), print(Weight),nl
1109
1110 weigh_properties2(truth,W) :- !, W=1.
1111 weigh_properties2(falsity,W) :- !, W=1.
1112 weigh_properties2(equal(L,R),W) :- weigh_term(L,W1), !,
1113 ( weigh_term(R,W2) -> W is W1*W2
1114 ; W is 3200).
1115 % ; W is W1*20). %causes issue with ParityFunction test
1116 %weigh_properties2(equal(_,R),W) :- weigh_term(R,W2), !, W is W2*20.
1117 weigh_properties2(SOp,W) :- comparison(SOp,L,R),!,
1118 ( (weigh_term(L,W1), weigh_term(R,W2))
1119 -> W is 7+W1+W2 % try and give things like x>10 priority over x>y (to overcome CLP(FD) limitations)
1120 ; W=10).
1121 weigh_properties2(partition(LHS,RHS),W) :- weigh_term(LHS,W1), l_weigh_term(RHS,W2), !, W is W1*W2.
1122 ?weigh_properties2(not_equal(L,R),W) :- ((id(L),empty(R)) ; (id(R),empty(L))),!, W=1.
1123 weigh_properties2(not_equal(L,R),W) :- weigh_term(L,W1), weigh_term(R,W2),!,
1124 W is 20+W1*W2.
1125 weigh_properties2(_Rest,W) :- W=32000.
1126
1127 comparison(less(L,R),L,R).
1128 comparison(less_equal(L,R),L,R).
1129 comparison(greater(L,R),L,R).
1130 comparison(greater_equal(L,R),L,R).
1131
1132
1133 id(b(identifier(_),_,_)).
1134 empty(b(empty_set,_,_)).
1135 empty(b(empty_sequence,_,_)).
1136
1137 l_weigh_term([],0).
1138 l_weigh_term([H|T],R) :- l_weigh_term(T,TR), weigh_term(H,TH), R is TH+TR.
1139
1140 weigh_term(b(T,_,_),R) :- (weigh_term2(T,R) -> true ; fail). %R=20).
1141
1142 weigh_term2(value(_),1).
1143 weigh_term2(boolean_true,1).
1144 weigh_term2(boolean_false,1).
1145 weigh_term2(empty_set,1).
1146 weigh_term2(empty_sequence,1).
1147 weigh_term2(integer(_),1).
1148 weigh_term2(min_int,1).
1149 weigh_term2(max_int,1).
1150 weigh_term2(string(_),1).
1151 weigh_term2(bool_set,2).
1152 weigh_term2(identifier(_),2).
1153 weigh_term2(set_extension(_),3).
1154 weigh_term2(integer_set(_),3).
1155 weigh_term2(interval(L,R),W) :- weigh_term(L,WL), weigh_term(R,WR), W is WL*WR.
1156
1157
1158
1159 b_machine_has_constants_or_properties :-
1160 (b_machine_has_constants -> true
1161 ; (b_get_properties_from_machine(Prop)), \+ is_truth(Prop)).
1162
1163 b_get_machine_operation_parameter_types(OpName,ParTypes) :-
1164 b_get_machine_operation_typed_parameters(OpName,Parameters),
1165 maplist(get_texpr_type,Parameters,ParTypes).
1166
1167 b_get_machine_operation_typed_parameters(Operation,Res) :-
1168 if(b_get_machine_operation_typed_parameters_aux(Operation,Paras),Res=Paras,
1169 (add_internal_error('Cannot get parameters: ',b_get_machine_operation_typed_parameters(Operation,Res)),fail)).
1170 % also recognises SETUP_CONSTANTS & INITIALISE_MACHINE
1171 b_get_machine_operation_typed_parameters_aux('$setup_constants',Constants) :-
1172 b_machine_has_constants_or_properties,
1173 b_get_machine_constants(Constants).
1174 b_get_machine_operation_typed_parameters_aux('$initialise_machine',Variables) :-
1175 b_get_machine_variables(Variables).
1176 b_get_machine_operation_typed_parameters_aux(OpName,Parameters) :-
1177 b_get_machine_operation(OpName,_R,Parameters,_Body,_OType,_OpPos).
1178
1179 b_get_machine_operation_parameter_names('@INITIALISATION',ParaNames) :- % for Tcl/Tk
1180 b_get_machine_operation_parameter_names('$initialise_machine',ParaNames).
1181 b_get_machine_operation_parameter_names('@PROPERTIES',ParaNames) :- % for Tcl/Tk
1182 b_get_machine_operation_parameter_names('$setup_constants',ParaNames).
1183 b_get_machine_operation_parameter_names(OpName,ParaNames) :-
1184 b_get_machine_operation_typed_parameters(OpName,Parameters),
1185 get_texpr_ids(Parameters,ParaNames).
1186
1187 b_get_machine_operation(Name,Results,Parameters,Body) :-
1188 ? b_get_machine_operation(Name,Results,Parameters,Body,_OType,_OpPos).
1189
1190 :- public b_get_assertions_from_main_machine_calc/2.
1191 b_get_assertions_from_main_machine_calc(static,FProp) :-
1192 ((b_get_static_assertions_from_machine(Prop),
1193 exclude(is_not_main_assertion,Prop,FProp)) -> true
1194 ; add_error(bmachine,'b_get_assertions_from_main_machine_calc static fails'), FProp=[]).
1195 b_get_assertions_from_main_machine_calc(dynamic,FProp) :-
1196 ((b_get_dynamic_assertions_from_machine(Prop),
1197 exclude(is_not_main_assertion,Prop,FProp)) -> true
1198 ; add_error(bmachine,'b_get_assertions_from_main_machine_calc dynamic fails'), FProp=[]).
1199 is_not_main_assertion(Assertion) :-
1200 get_texpr_pos(Assertion,Pos),
1201 error_manager:position_is_not_in_main_file(Pos).
1202
1203 % get nr of assertions and nr of main assertions for static/dynamic
1204 b_get_assertion_count(StaticOrDynamic,NrAll,NrMain) :-
1205 b_get_assertions(all,StaticOrDynamic,A), length(A,NrAll),
1206 b_get_assertions_from_main_machine(StaticOrDynamic,MA),length(MA,NrMain).
1207
1208 b_get_assertions(main,Mode,Ass) :- !,
1209 b_get_assertions_from_main_machine(Mode,Ass).
1210 b_get_assertions(specific(Label),Mode,LabelAss) :- !,
1211 b_get_assertions(all,Mode,Ass),
1212 %maplist(get_texpr_label,Ass,Labels), print(labels(Labels)),nl,
1213 include(has_label(Label),Ass,LabelAss),
1214 (LabelAss=[] -> ajoin(['No ',Mode,' assertion has label: '],Msg),
1215 add_warning(b_get_assertions,Msg,Label) ; true).
1216 b_get_assertions(_,static,Ass) :- b_get_static_assertions_from_machine(Ass).
1217 b_get_assertions(_,dynamic,Ass) :- b_get_dynamic_assertions_from_machine(Ass).
1218 b_main_machine_has_no_assertions :-
1219 b_get_assertions_from_main_machine(static,[]),
1220 b_get_assertions_from_main_machine(dynamic,[]).
1221
1222
1223 %has_label(Label,Expr) :- get_texpr_label(Expr,Label1), format('Labels ~w =? ~w~n',[Label1,Label]), fail.
1224 has_label(Label,Expr) :- get_texpr_label(Expr,Label).
1225
1226 :- public b_get_static_assertions_from_machine_calc/1.
1227 % precompiled: typed assertions (a list of predicates)
1228 b_get_static_assertions_from_machine_calc(Prop) :-
1229 get_section_from_current_machine(assertions,Prop1),
1230 exclude(predicate_uses_variables,Prop1,Prop),!.
1231 b_get_static_assertions_from_machine_calc(Prop) :-
1232 add_error(bmachine,'b_get_static_assertions_from_machine_calc fails'), Prop=[].
1233
1234 :- dynamic b_machine_has_static_assertions/0.
1235 :- public b_machine_has_static_assertions_calc/0.
1236 b_machine_has_static_assertions_calc :-
1237 b_get_static_assertions_from_machine([_|_]).
1238
1239 :- public b_get_unproven_static_assertions_from_machine_calc/1.
1240 b_get_unproven_static_assertions_from_machine_calc(FAssertions) :-
1241 b_get_static_assertions_from_machine(Assertions),
1242 filter_out_proven_assertions(Assertions,FAssertions),!.
1243 b_get_unproven_static_assertions_from_machine_calc(Prop) :-
1244 add_error(bmachine,'b_get_unproven_static_assertions_from_machine_calc fails'), Prop=[].
1245
1246 filter_out_proven_assertions([],[]).
1247 filter_out_proven_assertions([A1|T],R) :-
1248 (is_discharged_assertion(A1)
1249 -> R = TR %, print('Proven: '), translate:print_bexpr(A1),nl
1250 ; R = [A1|TR]),
1251 filter_out_proven_assertions(T,TR).
1252
1253 :- public b_get_dynamic_assertions_from_machine_calc/1.
1254 b_get_dynamic_assertions_from_machine_calc(Prop) :-
1255 get_section_from_current_machine(assertions,Prop1),
1256 include(predicate_uses_variables,Prop1,Prop),!.
1257 b_get_dynamic_assertions_from_machine_calc(Prop) :-
1258 add_error(bmachine,'b_get_dynamic_assertions_from_machine_calc fails'), Prop=[].
1259
1260
1261 :- dynamic b_machine_has_dynamic_assertions/0.
1262 :- public b_machine_has_dynamic_assertions_calc/0.
1263 b_machine_has_dynamic_assertions_calc :-
1264 b_get_dynamic_assertions_from_machine([_|_]).
1265
1266 b_machine_has_assertions :- (b_machine_has_static_assertions -> true ; b_machine_has_dynamic_assertions).
1267
1268 b_machine_has_unproven_assertions :-
1269 b_get_unproven_dynamic_assertions_from_machine([_|_]) -> true
1270 ; b_get_unproven_static_assertions_from_machine([_|_]).
1271
1272
1273 get_all_assertions_from_machine(Assertions) :-
1274 findall(A,((SD=static;SD=dynamic),get_assertions_from_machine(SD,SS),member(A,SS)),Assertions).
1275
1276 get_assertions_from_machine(Type,Assertions) :-
1277 ( Type=(dynamic) ->
1278 (get_preference(use_po,true)
1279 -> b_get_unproven_dynamic_assertions_from_machine(Assertions)
1280 ; b_get_dynamic_assertions_from_machine(Assertions)
1281 )
1282 ; Type=(static) ->
1283 (get_preference(use_po,true)
1284 -> b_get_unproven_static_assertions_from_machine(Assertions)
1285 ; b_get_static_assertions_from_machine(Assertions)
1286 )
1287 ),
1288 Assertions = [_|_].
1289
1290 :- public b_get_unproven_dynamic_assertions_from_machine_calc/1.
1291 b_get_unproven_dynamic_assertions_from_machine_calc(FAssertions) :-
1292 b_get_dynamic_assertions_from_machine(Assertions),
1293 filter_out_proven_assertions(Assertions,FAssertions),!.
1294 b_get_unproven_dynamic_assertions_from_machine_calc(Prop) :-
1295 add_error(bmachine,'b_get_unproven_dynamic_assertions_from_machine_calc fails'), Prop=[].
1296
1297 predicate_uses_variables(Pred) :-
1298 b_get_machine_variables(Vars),
1299 get_texpr_ids(Vars,Ids),
1300 list_to_ord_set(Ids,OrdVars),
1301 find_identifier_uses(Pred,[],UsedVars),
1302 list_to_ord_set(UsedVars,OrdUsedVars),
1303 ord_intersect(OrdVars,OrdUsedVars).
1304
1305 :- public b_get_initialisation_from_machine_calc/2.
1306 % precompiled: typed initialisation (a substitution)
1307 b_get_initialisation_from_machine_calc(Init,OType) :-
1308 get_section_from_current_machine(initialisation,Init),
1309 ( get_texpr_expr(Init,rlevent(_Name,_Section,_Status,Params,_Guard,_Theorems,_Actions,_VWitnesses,_PWitnesses,_Unmod,_AbstractEvents)) ->
1310 get_operation_type(Init,'INITIALISATION',Params,OType)
1311 ; otherwise ->
1312 OType = classic).
1313 % precompiled: operations, Name is in atomic form, Results and Parameters are lists
1314 % of typed identifiers, Body is a typed substitution
1315
1316 :- volatile b_machine_operation_names_in_reverse_order/1.
1317 :- dynamic b_machine_operation_names_in_reverse_order/1.
1318 % a list of operation names in reverse order; this way we can randomize the
1319 % generation of the successor states
1320 precompile_operation_names_in_reverse_order :-
1321 retractall(b_machine_operation_names_in_reverse_order(_)),
1322 ? b_get_machine_operation(Name,_Results,_Parameters,_Body,_OType,_OpPos),
1323 asserta(b_machine_operation_names_in_reverse_order(Name)),
1324 fail.
1325 precompile_operation_names_in_reverse_order.
1326
1327 :- public b_get_machine_operation_calc/6.
1328 b_get_machine_operation_calc(Name,Results,Parameters,OpBody,OType,OpPos) :-
1329 ? is_ground(Name,NameGround),
1330 ? get_section_from_current_machine(operation_bodies,Ops),
1331 ? get_texpr_expr(Op,operation(TId,Results,Parameters,Body)),
1332 ? get_texpr_id(TId,op(Name)),
1333 ? member(Op,Ops),
1334 % remove choicepoints when name was ground
1335 (NameGround==ground -> !; true),
1336 get_operation_type(Op,Name,Parameters,OType),
1337 (get_texpr_pos(TId,OpPos) -> debug_println(9,op_pos(Name,OpPos)) ; OpPos = unknown),
1338 ((get_preference(use_common_subexpression_also_for_substitutions,true),
1339 get_preference(use_common_subexpression_elimination,true),
1340 \+ specfile:animation_minor_mode(eventb) % CSE_SUBST not yet available for Event-B
1341 )
1342 -> print(applying_cse_to(Name)),nl,
1343 b_expression_sharing:cse_optimize_substitution(Body,OpBody)
1344 ; OpBody = Body).
1345 get_operation_type([],_Name,_Parameters,classic).
1346 get_operation_type(Op,Name,Parameters,OType) :-
1347 get_texpr_info(Op,Info),
1348 ( member(eventb(_),Info) ->
1349 OType=eventb_operation(SortedChangeSet,Ps,OpPattern),
1350 member(modifies(ChangeSet),Info),!,
1351 sort(ChangeSet,SortedChangeSet), % maybe not necessary ?
1352 same_length(Parameters,Ps),
1353 OpPattern =.. [Name|Ps]
1354 ; otherwise ->
1355 OType=classic).
1356
1357 :- volatile get_operation_info/2.
1358 :- dynamic get_operation_info/2.
1359 :- public get_operation_info_calc/2.
1360 % precompiled: operation infos
1361 get_operation_info_calc(OpName,Info) :-
1362 ? get_section_from_current_machine(operation_bodies,Ops),
1363 ? create_texpr(operation(TId,_Results,_Parameters,_Body),_,Info,TOp),
1364 ? get_texpr_id(TId,op(OpName)),
1365 ? member(TOp,Ops).
1366
1367 :- public b_top_level_operation_calc/1.
1368 % precompiled: operation names (in atomic form) of top-level operations (promoted operations)
1369 b_top_level_operation_calc(Name) :-
1370 ? is_ground(Name,NameGround),
1371 ? get_section_from_current_machine(promoted,Promoted),
1372 ? get_texpr_id(TId,op(Name)),
1373 ? member(TId,Promoted),
1374 (NameGround==ground -> !; true).
1375 :- public b_get_promoted_machine_operations_calc/1.
1376 b_get_promoted_machine_operations_calc(Ops) :-
1377 get_section_from_current_machine(promoted,Ops).
1378
1379 % this succeeds not just for top-level operations
1380 %b_is_operation_name(Name) :- b_get_machine_operation(Name,_,_,_,_,_). is slower
1381 :- public b_is_operation_name_calc/1.
1382 b_is_operation_name_calc(Name) :-
1383 ? b_get_machine_operation(Name,_,_,_,_,_).
1384
1385 b_get_operation_pos(Name,Pos) :-
1386 b_get_machine_operation(Name,_,_,_,_,Pos).
1387
1388 b_get_operation_variant(Name,ConvOrAnt,Variant) :-
1389 b_get_machine_operation(Name,_,_,TBody),
1390 get_texpr_expr(TBody,Body),
1391 Body = rlevent(Name,_Section,Status,
1392 _Params,_Guard,_Theorems,_Actions,_VWitnesses,_PWitnesses,_Unmod,_AbstractEvents),
1393 % TO DO: look maybe higher up in refinement hierarchy
1394 get_texpr_expr(Status,S),
1395 functor(S,ConvOrAnt,1),
1396 (ConvOrAnt = convergent ; ConvOrAnt = anticipated),
1397 arg(1,S,Variant).
1398
1399
1400 % -----------------------------
1401
1402
1403 % the names of definitions which have a given Prefix,
1404 % Type is expression or predicate, Name is an atomic name
1405 b_definition_prefixed(Type,Prefix,Suffix,Name) :-
1406 ? safe_atom_chars(Prefix,PrefixChars,b_definition_prefixed1),
1407 ? append(PrefixChars,SuffixChars,FullChars),
1408 ? (ground(Suffix) -> safe_atom_chars(Suffix,SuffixChars,b_definition_prefixed2),safe_atom_chars(Name,FullChars,b_definition_prefixed3); true),
1409 ? b_get_definition(Name,Type,_,_,_),
1410 safe_atom_chars(Name,FullChars,b_definition_prefixed4),
1411 safe_atom_chars(Suffix,SuffixChars,b_definition_prefixed5).
1412
1413 :- use_module(bmachine_construction,[type_open_formula/8]).
1414 type_check_definitions :-
1415 temporary_set_preference(allow_untyped_identifiers,true_with_string_type,CHNG), % we may not have all identifiers visible
1416 type_check_definitions2,
1417 reset_temporary_preference(allow_untyped_identifiers,CHNG).
1418 type_check_definitions2 :-
1419 get_preference(type_check_definitions,true),
1420 full_b_machine(Machine),
1421 b_get_definition(Name,Type,Args,RawExpr,_Deps),
1422 % TO DO: do not re-analyse definitions already analysed for ANIMATION_FUNCTION,...
1423 (Type = predicate ; Type=expression), % can we also allow substitutions ?
1424 debug_format(9,'Type checking DEFINITION ~w~n',[Name]),
1425 get_error_context(Context),
1426 set_error_context(checking_context('Type checking DEFINITION: ',Name)),
1427 Scope = [variables], % prob_ids(visible),
1428 %type_with_errors(RawExpr,Scope,_,_TExpr),
1429 AllowNewIds=true,
1430 % TO DO: improve solution below, e.g., delete Args from visible variables or rename Args to fresh ids!
1431 (Args=[] -> RawExpr2=RawExpr
1432 ; 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
1433 ; RawExpr2=exists(none,Args,equal(none,RawExpr,RawExpr)) % TODO: better solution to avoid duplicating RawExpr
1434 ),
1435 type_open_formula(RawExpr2,Scope,AllowNewIds,Machine,FType,Identifiers,_TPred,Errors),
1436 (Errors = [_|_] ->
1437 format('Error for DEFINITION ~w of type ~w over identifiers ~w~n',[Name,FType,Identifiers]),
1438 add_all_perrors_in_context_of_used_filenames(Errors,definition_type_error)
1439 ; true),
1440 restore_error_context(Context),
1441 fail.
1442 type_check_definitions2 :- debug_format(9,'Finished type checking DEFINITIONs~n',[]).
1443
1444 b_get_definition(Name,DefType,Args,RawExpr,Deps) :-
1445 ? get_section_from_current_machine(definitions,Defs),
1446 ? member(definition_decl(Name,DefType,_Pos,Args,RawExpr,Deps),Defs).
1447 % the next calls get typed definitions without parameters:
1448 % (To treat definitions with parameters one would have to add the parameters to the type environment, see type_check_definitions2)
1449 b_get_typed_predicate_definition(Name,Scope,TExpr) :-
1450 ? b_get_definition(Name,predicate,[],RawExpr,_Deps),
1451 type_with_errors_in_context(RawExpr,Scope,_,TExpr,machine_context).
1452 b_get_typed_expression_definition(Name,Scope,TExpr) :-
1453 b_get_definition(Name,expression,[],RawExpr,_Deps),
1454 type_with_errors_in_context(RawExpr,Scope,_,TExpr,machine_context).
1455 b_get_true_expression_definition(Name) :-
1456 b_get_typed_expression_definition(Name,[variables],PF),
1457 PF = b(boolean_true,boolean,_).
1458 %b_get_typed_subst_definition(Name,Scope,Parameters,TExpr) :-
1459 % temporary_set_preference(allow_local_operation_calls,true,CHNG),
1460 % b_get_definition(Name,substitution,Parameters,RawExpr,_Deps),
1461 % type_with_errors(RawExpr,[operation_bodies|Scope],_,TExpr), % need to remove variables to avoid clash warnings
1462 % reset_temporary_preference(allow_local_operation_calls,CHNG).
1463 b_get_typed_definition(Name,Scope,TExpr) :-
1464 ? b_get_definition(Name,_DefType,[],RawExpr,_Deps),
1465 type_with_errors_in_context(RawExpr,Scope,_,TExpr,machine_context).
1466
1467 type_with_errors(RawExpr,Scope,Type,TExpr) :-
1468 type_with_errors_in_context(RawExpr,Scope,Type,TExpr,not_in_machine_context).
1469 type_with_errors_in_context(RawExpr,Scope,Type,TExpr,Context) :- % print(scope(Scope)),nl,
1470 b_type_expression(RawExpr,Scope,Type,TExpr,Errors),!,
1471 (Context=not_in_machine_context
1472 -> add_all_perrors(Errors,[],type_expression_error) % no file name list available
1473 ; add_all_perrors_in_context_of_used_filenames(Errors,type_expression_error)
1474 ),
1475 no_real_perror_occurred(Errors).
1476
1477 b_type_open_predicate_with_errors(OptionalQuantifier,RawPred,Scope,TPred) :-
1478 b_type_open_predicate(OptionalQuantifier,RawPred,Scope,TPred,Errors),
1479 add_all_perrors(Errors,[],type_expression_error),
1480 no_real_perror_occurred(Errors).
1481 b_type_open_predicate(OptionalQuantifier,RawPred,Scope,TPred,Errors) :-
1482 b_type_open_predicate_for_full_b_machine(_Machine,OptionalQuantifier,RawPred,Scope,TPred,Errors).
1483 b_type_open_predicate_for_full_b_machine(Machine,OptionalQuantifier,RawPred,Scope,TPred,Errors) :-
1484 (var(Machine) -> full_b_machine(Machine) ; true),
1485 replace_prob_set_elements_in_scope(Scope,Scope1),
1486 type_open_predicate_with_quantifier(OptionalQuantifier,RawPred,Scope1,Machine,TPred,Errors),!.
1487 b_type_open_exists_predicate(Raw,Typed,Errors) :-
1488 b_type_open_predicate(open(exists),Raw,[prob_ids(visible),variables],Typed,Errors).
1489
1490 b_type_expression(RawExpr,Scope,Type,TExpr,Errors) :-
1491 b_type_expression_for_full_b_machine(_,RawExpr,Scope,Type,TExpr,Errors).
1492
1493 b_type_expression_for_full_b_machine(M,RawExpr,Scope,Type,TExpr,Errors) :-
1494 b_type_expressions_l(M,[RawExpr],Scope,[Type],[TExpr],Errors).
1495
1496 b_type_expressions_l(Machine,RawExprs,Scope,Types,TExprs,Errors) :-
1497 (var(Machine) -> full_b_machine(Machine) ; true),
1498 % in case you type check multiple expressions for a complex machine it is better to extract the machine once
1499 replace_prob_set_elements_in_scope(Scope,Scope1),
1500 % we need this, for example for tcltk_check_state_sequence_from_file, when deferred set elements written by TLC are in the file
1501 ~~mnf( type_in_machine_l(RawExprs,Scope1,Machine,Types,TExprs,Errors) ),!.
1502
1503 replace_prob_set_elements_in_scope(Scope,Res) :- var(Scope),!,
1504 add_internal_error('Scope is a variable (use, e.g., [constants,variables,operation_bodies,...]):',replace_prob_set_elements_in_scope(Scope,Res)),
1505 Res=Scope.
1506 replace_prob_set_elements_in_scope(Scope,NewScope) :-
1507 ? ( select(prob_ids(AllOrVisible),Scope,identifier(Ids),NewScope) -> % replaces prob by deferred set element identifiers
1508 % for example if we have SETS PID then we would have PID1,... in Ids unless PID1 is known to be another identifier
1509 b_get_prob_deferred_set_elements(DefIDs,AllOrVisible),
1510 exclude(known_identifier,DefIDs,Ids) % exclude those ids that would clash
1511 % TO DO: add option to translate_identifiers using translate:keyword_to_id_cache
1512 ; otherwise ->
1513 Scope = NewScope).
1514
1515
1516 known_identifier(X) :- get_texpr_id(X,ID),
1517 (bmachine:b_is_constant(ID,_) ;
1518 bmachine:b_is_variable(ID,_)).
1519
1520
1521 :- use_module(b_global_sets,[b_global_deferred_set/1,all_elements_of_type/2]).
1522 :- use_module(input_syntax_tree,[get_raw_position_info/2]).
1523 % try and get source code for an identifier
1524 source_code_for_identifier(ID,constant,Type,OriginStr,OriginTerm,Source) :- b_is_constant(ID),!,
1525 get_constant_type_and_origin(ID,Type,OriginStr,OriginTerm),
1526 findall(Def,get_constant_definition(ID,Def),AllDefs),
1527 (AllDefs=[_|_] -> conjunct_predicates(AllDefs,Source)
1528 ; % try and find other type of predicates defining ID
1529 findall(Pred,get_constant_predicate(ID,Pred),AllPreds),
1530 conjunct_predicates(AllPreds,Source)).
1531 source_code_for_identifier(ID,variable,Type,OriginStr,OriginTerm,Source) :- b_is_variable(ID),!,
1532 get_variable_type_and_origin(ID,Type,OriginStr,OriginTerm),
1533 Source = b(truth,pred,[]). % TO DO: improve
1534 source_code_for_identifier(ID,Kind,Type,OriginStr,OriginTerm,Source) :- b_get_machine_set(ID,TID),!,
1535 (b_global_deferred_set(ID) -> Kind = deferred_set ; Kind = enumerated_set),
1536 Type = set(global(ID)),
1537 all_elements_of_type(ID,All),
1538 translate:translate_span_with_filename(TID,OriginStr), OriginTerm=TID,
1539 Source = b(equal(TID,b(value(All),Type,[])),pred,[]).
1540 source_code_for_identifier(ID,Kind,Type,OriginStr,OriginTerm,Source) :-
1541 global_set_element(ID,GID),!,
1542 (b_global_deferred_set(GID)
1543 -> Kind = deferred_set_element ; Kind = enumerated_set_element),
1544 b_get_machine_set(GID,TGID),
1545 Type = global(ID),
1546 all_elements_of_type(GID,All),
1547 translate:translate_span_with_filename(TGID,OriginStr), OriginTerm=TGID,
1548 Source = b(equal(TGID,b(value(All),set(Type),[])),pred,[]).
1549 source_code_for_identifier(ID,definition,Type,OriginStr,OriginTerm,Source) :-
1550 b_get_definition(ID,DefType,Args,RawExpr,_Deps),!,
1551 Type = DefType,
1552 % Definitions are only present in RAW form
1553 get_raw_position_info(RawExpr,PosInfo),
1554 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
1555 OriginTerm=PosInfo,
1556 source_code_for_definition(DefType,ID,Args,RawExpr,Source).
1557 source_code_for_identifier(ID,file,Type,OriginStr,OriginTerm,b(string(Source),string,[])) :-
1558 b_filenumber(ID,Kind,_,Filename),
1559 extension_kind(Kind,Type),
1560 !,
1561 ajoin([Type,' ',ID],Source),
1562 OriginTerm =src_position_with_filename(1,0,0,Filename),
1563 OriginStr = Filename.
1564 source_code_for_identifier(ID,Kind,subst,OriginStr,OriginTerm,Source) :-
1565 b_find_operation(ID,Res,TParas,Body,OType),
1566 (OType=classic -> Kind = operation ; Kind=event),
1567 translate:translate_span_with_filename(Body,OriginStr),Body=OriginTerm,
1568 get_texpr_info(Body,Info),
1569 Source=b(operation(b(identifier(ID),subst,[]),Res,TParas,Body),subst,Info).
1570 source_code_for_identifier(ID,assertion,pred,OriginStr,OriginTerm,Assertion) :-
1571 b_get_assertions(all,_,Ass), member(Assertion,Ass),
1572 get_texpr_label(Assertion,ID), OriginTerm = Assertion,
1573 translate:translate_span_with_filename(Assertion,OriginStr).
1574 source_code_for_identifier(ID,invariant,pred,OriginStr,OriginTerm,Invariant) :-
1575 b_get_invariant_from_machine(C), conjunction_to_list(C,L), member(Invariant,L),
1576 get_texpr_label(Invariant,ID), OriginTerm = Invariant,
1577 translate:translate_span_with_filename(Invariant,OriginStr).
1578 % TO DO: look for invariant labels as ids ?
1579
1580 :- use_module(tools,[ split_last/4 ]).
1581 b_find_operation(ID,Res,TParas,Body,OType) :-
1582 b_get_machine_operation(ID,Res,TParas,Body,OType,_Pos).
1583 b_find_operation(ID,Res,TParas,Body,OType) :-
1584 b_get_machine_operation(ID2,Res,TParas,Body,OType,_Pos),
1585 split_last(ID2, '.', _, ID).
1586
1587 extension_kind(mch,'MACHINE').
1588 extension_kind(ref,'REFINEMENT').
1589 extension_kind(def,'DEFINITIONS FILE').
1590 extension_kind(imp,'IMPLEMENTATION').
1591
1592 source_code_for_definition(predicate,ID,_,RawExpr,Source) :-
1593 b_type_open_exists_predicate(RawExpr,Typed,Errors),
1594 (no_real_perror_occurred(Errors) -> true ; debug_println(9,errs(ID,Errors))),
1595 Source=Typed.
1596 source_code_for_definition(expression,ID,Args,RawExpr,Source) :-
1597 % TO DO: add parameters to avoid type errors; but we get Typed anyway
1598 b_type_expression(RawExpr,[prob_ids(visible),variables],Type,Typed,Errors),
1599 (no_real_perror_occurred(Errors) -> true ; debug_println(9,errs(ID,Args,Type,Errors))),
1600 Source=Typed.
1601 % TO DO: treate substitutions
1602 source_code_for_definition(DefType,ID,_Args,_RawExpr,Source) :-
1603 Source=b(identifier(ID),DefType,[]).
1604
1605 :- use_module(b_global_sets,[lookup_global_constant/2,prob_deferred_set_element/4]).
1606 global_set_element(ID,GlobalSetID) :- lookup_global_constant(ID,fd(_,GlobalSetID)).
1607 global_set_element(ID,GlobalSetID) :-
1608 prob_deferred_set_element(GlobalSetID,_Elem,ID,all).
1609
1610
1611 get_constant_type_and_origin(ID,Type,OriginStr,OriginTerm) :-
1612 b_get_machine_constants(Constants),
1613 TID = b(identifier(ID),Type,_Infos),
1614 member(TID,Constants),
1615 % we could also use member(origin(Origin),Infos)
1616 translate:translate_span_with_filename(TID,OriginStr), OriginTerm=TID.
1617 get_variable_type_and_origin(ID,Type,OriginStr,OriginTerm) :-
1618 b_get_machine_variables(Vars),
1619 TID = b(identifier(ID),Type,_Infos),
1620 member(TID,Vars),
1621 % we could also use member(origin(Origin),Infos)
1622 translate:translate_span_with_filename(TID,OriginStr), OriginTerm=TID.
1623
1624 get_constant_definition(ID,FullDef) :-
1625 b_get_properties_from_machine(Prop),
1626 EqDef = b(equal(LHS,RHS),pred,_),
1627 member_in_conjunction_cse(FullDef,EqDef,Prop),
1628 (get_texpr_id(LHS,ID) ; get_texpr_id(RHS,ID)).
1629
1630 get_constant_predicate(ID,FullPred) :-
1631 b_get_properties_from_machine(Prop),
1632 member_in_conjunction_cse(FullPred,Pred,Prop),
1633 involves_id(Pred,ID).
1634 involves_id(ID,b(E,_,_)) :- involves_id_aux(E,ID).
1635 involves_id_aux(member(LHS,_),ID) :- get_texpr_id(LHS,ID).
1636 involves_id_aux(subset(LHS,_),ID) :- get_texpr_id(LHS,ID).
1637 involves_id_aux(strict_subset(LHS,_),ID) :- get_texpr_id(LHS,ID).
1638
1639 :- volatile b_get_machine_setscope/2.
1640 :- dynamic b_get_machine_setscope/2.
1641 :- public b_get_machine_setscope_calc/2.
1642 % precompiled: definitions of the form "scope_SET == Expr",
1643 % Set is the name of the Set, TExpr the typed expression
1644 b_get_machine_setscope_calc(Set,TExpr) :-
1645 b_definition_prefixed(expression, scope_, Set, Name),
1646 % TO DO: check if it is a SET
1647 b_get_typed_definition(Name,[],TExpr).
1648
1649 % get a specific MAX_OPERATIONS Value for an operation
1650 :- volatile b_get_machine_operation_max/2.
1651 :- dynamic b_get_machine_operation_max/2.
1652 :- public b_get_machine_operation_max_calc/2.
1653 % precompiled: definitions of the form "scope_SET == Expr",
1654 % Set is the name of the Set, TExpr the typed expression
1655 b_get_machine_operation_max_calc(Set,MaxOp) :-
1656 b_definition_prefixed(expression, 'MAX_OPERATIONS_', Set, Name),
1657 (b_get_typed_definition(Name,[constants],DEF), % scope=constants allows to use other definitions
1658 DEF=b(integer(MaxOp),integer,_)
1659 % TO DO: check if it is an operation
1660 %, MaxOp >= 0 we now use negative numbers for randomised restart
1661 -> true
1662 ; add_warning(b_get_machine_operation_max_calc,'Definition must specify an integer (negative numbers means using randomised restart) ',Name),
1663 fail
1664 ).
1665
1666 :- volatile b_get_machine_goal/1.
1667 :- dynamic b_get_machine_goal/1.
1668 :- public b_get_machine_goal_calc/1.
1669 % precompiled: definition of GOAL, a typed predicate
1670 ?b_get_machine_goal_calc(TPred) :- get_goal(TPred).
1671
1672 b_reset_machine_goal_from_DEFINITIONS :-
1673 get_goal(TPred),
1674 b_set_parsed_typed_machine_goal(TPred).
1675 get_goal(Goal) :-
1676 get_proz_settings(Settings),memberchk(goal(Goal),Settings),!.
1677 get_goal(Goal) :- % print(getting_goal),nl,
1678 ? get_texpr_type(Goal,pred),
1679 ? b_get_typed_predicate_definition('GOAL',[variables],Goal).
1680
1681 :- volatile b_get_machine_searchscope/1.
1682 :- dynamic b_get_machine_searchscope/1.
1683 :- public b_get_machine_searchscope_calc/1.
1684 % precompiled: definition of SCOPE, a typed predicate
1685 b_get_machine_searchscope_calc(TPred) :-
1686 get_texpr_type(TPred,pred),
1687 b_get_typed_definition('SCOPE',[variables],TPred).
1688
1689 :- volatile b_get_definition_string_from_machine/3.
1690 :- dynamic b_get_definition_string_from_machine/3.
1691 :- public b_get_definition_string_from_machine_calc/3.
1692 % precompiled: string definitions, Name == "String"
1693 b_get_definition_string_from_machine(Name,String) :-
1694 b_get_definition_string_from_machine(Name,_,String).
1695 b_get_definition_string_from_machine_calc(Name,Pos,String) :-
1696 ? b_get_definition(Name,expression,[],string(Pos,Str),_Deps),
1697 get_texpr_expr(TExpr,string(String)),
1698 type_with_errors_in_context(string(Pos,Str),[],_,TExpr,machine_context).
1699
1700 :- use_module(specfile,[animation_minor_mode/1]).
1701 get_animation_image(Nr,S) :-
1702 animation_minor_mode(z),
1703 get_proz_animation_function(_,_,Images),!,
1704 nth1(Nr,Images,S).
1705 get_animation_image(Nr,S) :- number(Nr),!,
1706 number_codes(Nr,TailCodes),
1707 /* ANIMATION_IMG */
1708 atom_codes(Def_Name,[65,78,73,77,65,84,73,79,78,95,73,77,71|TailCodes]),
1709 b_get_definition_string_from_machine(Def_Name,S).
1710 get_animation_image(Nr,S) :-
1711 b_get_definition_string_from_machine(Def_Name,S),
1712 /* ANIMATION_IMG */
1713 atom_codes(Def_Name,[65,78,73,77,65,84,73,79,78,95,73,77,71|TailCodes]),
1714 number_codes(Nr,TailCodes).
1715
1716 :- use_module(error_manager,[extract_file_number_and_name/3]).
1717 :- use_module(specfile,[b_or_z_mode/0]).
1718 get_animation_image_source_file(Nr,File) :- b_or_z_mode,
1719 % get source file where Animation image is defined; relevant for finding images
1720 b_get_definition_string_from_machine(Def_Name,Pos,_),
1721 atom_codes(Def_Name,[65,78,73,77,65,84,73,79,78,95,73,77,71|TailCodes]),
1722 number_codes(Nr,TailCodes),
1723 extract_file_number_and_name(Pos,_,File).
1724
1725 get_proz_animation_function(Function,Default,Images) :-
1726 get_proz_settings(Settings),
1727 memberchk(animation_function(Function,Default,Images),Settings).
1728 get_proz_settings(Settings) :-
1729 machine(_,Sections),memberchk(meta/Meta,Sections),
1730 memberchk(proz_settings(Settings),Meta).
1731
1732
1733 :- volatile b_get_machine_animation_function/2.
1734 :- dynamic b_get_machine_animation_function/2.
1735 :- public b_get_machine_animation_function_calc/2.
1736 :- use_module(tools,[safe_number_codes/2]).
1737 :- use_module(bsyntaxtree,[get_texpr_set_type/2]).
1738 % precompiled: definition of ANIMATION_FUNCTION, a typed expression
1739 b_get_machine_animation_function_calc(AFun,Nr) :-
1740 get_proz_animation_function(TFun,Default,_),!,
1741 ( Nr = -1, AFun = Default
1742 ; Nr = 0, TFun \= none, AFun=TFun
1743 ).
1744 b_get_machine_animation_function_calc(TFun,Nr) :-
1745 get_definition_with_nr_suffix("ANIMATION_FUNCTION",Nr,Def_Name),
1746 b_get_typed_expression_definition(Def_Name,[variables],TFun), % only type it afterwards; avoid throwing type errors for other definitions
1747 (get_texpr_set_type(TFun,couple(_,_)) -> true
1748 ; get_texpr_type(TFun,Type),
1749 add_warning(b_get_machine_animation_function_calc,'Illegal type for ANIMATION_FUNCTION: ',Def_Name:Type),fail).
1750
1751
1752 :- volatile b_get_machine_heuristic_function/1.
1753 :- dynamic b_get_machine_heuristic_function/1.
1754 :- public b_get_machine_heuristic_function_calc/1.
1755 b_get_machine_heuristic_function_calc(TFun) :- %print(extracting_heuristic_fun(TFun)),nl,
1756 get_texpr_type(TFun,integer),
1757 b_get_typed_expression_definition('HEURISTIC_FUNCTION',[variables],TFun).
1758
1759 :- volatile b_get_machine_animation_expression/1.
1760 :- dynamic b_get_machine_animation_expression/1.
1761 :- public b_get_machine_animation_expression_calc/1.
1762 b_get_machine_animation_expression_calc(AExpr) :- %print(extracting_heuristic_fun(TFun)),nl,
1763 b_get_typed_expression_definition('ANIMATION_EXPRESSION',[variables],AExpr).
1764
1765 % Custom nodes and edges for a custom graph representation of a state
1766 :- volatile b_get_machine_custom_nodes_function/2, b_get_machine_custom_edges_function/2.
1767 :- dynamic b_get_machine_custom_nodes_function/2, b_get_machine_custom_edges_function/2.
1768 :- public b_get_machine_custom_nodes_function_calc/2.
1769 b_get_machine_custom_nodes_function_calc(TFun,Nr) :-
1770 get_definition_with_nr_suffix("CUSTOM_GRAPH_NODES",Nr,Def_Name),
1771 get_texpr_set_type(TFun,_),
1772 b_get_typed_expression_definition(Def_Name,[variables],TFun).
1773 :- public b_get_machine_custom_edges_function_calc/2.
1774 b_get_machine_custom_edges_function_calc(TFun,Nr) :- %print(extracting_heuristic_fun(TFun)),nl,
1775 get_definition_with_nr_suffix("CUSTOM_GRAPH_EDGES",Nr,Def_Name),
1776 get_texpr_set_type(TFun,couple(_,_)),
1777 b_get_typed_expression_definition(Def_Name,[variables],TFun).
1778
1779
1780 get_definition_with_nr_suffix(Prefix,Nr,Def_Name) :-
1781 ? b_get_definition(Def_Name,expression,[],_RawExpr,_Deps),
1782 atom_codes(Def_Name,AC),
1783 append(Prefix,TailCodes,AC),
1784 (TailCodes=[] -> Nr=0
1785 ; TailCodes = "_DEFAULT" -> Nr = -1
1786 ; safe_number_codes(Nr,TailCodes)).
1787
1788
1789 % ------------------------
1790
1791 :- volatile b_get_constant_represented_inside_global_set/2.
1792 :- dynamic b_get_constant_represented_inside_global_set/2.
1793
1794 :- public b_get_constant_represented_inside_global_set_calc/2.
1795 b_get_constant_represented_inside_global_set_calc(X,GlobalSetName) :-
1796 b_get_disjoint_constants_of_type(GlobalSetName, DisjointConstants,_),
1797 member(X,DisjointConstants). /* X will be integrated into the global_set */
1798
1799
1800 :- volatile b_get_disjoint_constants_of_type/3.
1801 :- dynamic b_get_disjoint_constants_of_type/3.
1802 :- public b_get_disjoint_constants_of_type_calc/3.
1803 b_get_disjoint_constants_of_type_calc(GlobalSetName, DisjointConstants, AllConstantsIDs) :-
1804 b_get_machine_all_constants(Constants), /* get all the constants */
1805 b_get_properties_from_machine(Properties),
1806 ? b_get_machine_set(GlobalSetName),
1807 \+ b_get_named_machine_set(GlobalSetName,_), % not an enumerated set
1808 find_constants_of_type(Constants,GlobalSetName,AllConstantsIDs,_GSConstants),
1809 find_inequal_global_set_identifiers(AllConstantsIDs,global(GlobalSetName),Properties,DisjointConstants),
1810 DisjointConstants \= [],
1811 debug_println(9,disjoint_constants(GlobalSetName,DisjointConstants)).
1812 % TO DO: remove from Properties irrelevant conjuncts; sort AllConstantsIDs by having first those with max disequalities
1813
1814 find_constants_of_type([],_GS,[],[]) :- !.
1815 find_constants_of_type([b(identifier(ID),global(GS),INFO)|T], GS, [ID|IT],
1816 [b(identifier(ID),global(GS),INFO)|TT]) :- !,
1817 find_constants_of_type(T,GS,IT,TT).
1818 find_constants_of_type([b(_,_,_)|T], GS, IT, TT) :- !,
1819 find_constants_of_type(T,GS,IT,TT).
1820 find_constants_of_type(X,GS,_,_) :- print(find_constants_of_type_error(X,GS)),nl,fail.
1821
1822
1823
1824
1825 % ------------------------
1826 :- volatile b_get_all_used_identifiers_in_section/2.
1827 :- dynamic b_get_all_used_identifiers_in_section/2.
1828 :- public b_get_all_used_identifiers_in_section_calc/2.
1829
1830 b_get_all_used_identifiers_in_section_calc(SECTION,Identifiers) :-
1831 ? full_b_machine(BMachine),
1832 ? member(SECTION,[constraints,properties,invariant,assertions,
1833 initialisation,operation_bodies]),
1834 findall(I, find_used_identifier_in_machine_section(BMachine,SECTION,I), Ids),
1835 %print(section_ids(SECTION,Ids)),nl,
1836 sort(Ids,Identifiers).
1837
1838 :- volatile b_get_all_used_identifiers/1.
1839 :- dynamic b_get_all_used_identifiers/1.
1840 :- public b_get_all_used_identifiers_calc/1.
1841 :- use_module(library(ordsets),[ord_union/2]).
1842 % Precompiled: b_get_all_used_identifiers_calc/1 returns a list of all
1843 % identifiers used in machine sections that contain expressions and predicates
1844 b_get_all_used_identifiers_calc(Identifiers) :-
1845 findall(I, b_get_all_used_identifiers_in_section(_,I), ListOfList),
1846 ord_union(ListOfList,Identifiers). % ,print(all(Identifiers)),nl.
1847
1848 find_used_identifier_in_machine_section(Machine,Sec,Identifier) :-
1849 % treat it like a list of expressions
1850 ? get_section_texprs(Sec,Machine,TExprs),
1851 % and find all identifiers in each expression
1852 ? member(TExpr,TExprs),
1853 ? find_identifier_uses(TExpr,[],Ids),
1854 ? member(Identifier,Ids).
1855
1856 :- volatile b_is_unused_constant/1.
1857 :- dynamic b_is_unused_constant/1.
1858 :- public b_is_unused_constant_calc/1.
1859 b_is_unused_constant_calc(UnusedConstant) :-
1860 ? findall(C,b_is_constant(C),CL), %b_get_machine_constants(Constants), gives typed ids
1861 ? CL\=[] ,sort(CL,Constants),
1862 ? b_get_all_used_identifiers_in_section(invariant,I1),
1863 ? b_get_all_used_identifiers_in_section(assertions,I2),
1864 ? b_get_all_used_identifiers_in_section(initialisation,I3),
1865 ? b_get_all_used_identifiers_in_section(operation_bodies,I4),
1866 ? ord_union([I1,I2,I3,I4],UsedIds),
1867 %print(used(UsedIds)),nl,
1868 ? ord_subtract(Constants,UsedIds,UnusedConstants),
1869 ? UnusedConstants\=[],
1870 ? (b_get_machine_variables([]) -> true
1871 ; length(UnusedConstants,NrUC),
1872 (silent_mode(on) -> true
1873 ; (NrUC>10,UnusedConstants=[C1,C2|_]) ->
1874 print_message_with_max_depth(unused_constants(NrUC,[C1,C2,'...']),500)
1875 ; print_message_with_max_depth(unused_constants(NrUC,UnusedConstants),500))
1876 ),
1877 ? member(UnusedConstant,UnusedConstants).
1878
1879
1880 % precompiled: Skel is the operation skeleton, SpecializedInv a typed predicate
1881 % (Skel,SpecializedInv) :-
1882 % b_get_machine_operation(Name,_Res,Params,_Body),
1883 % atom_concat('SIMPLIFIED_INV_OP_',Name,ASNC),
1884 % b_get_typed_definition(ASNC,[variables,identifiers(Params)],SpecializedInv),
1885 % length(Params,Len),
1886 % functor(Skel,Name,Len),
1887 % print(b_specialized_invariant_for_op(Skel)).
1888
1889
1890 get_section_from_current_machine(Section,Content) :-
1891 full_b_machine(BMachine),
1892 ~~mnf( get_section(Section,BMachine,Content) ).
1893
1894 is_ground(X,R) :- ground(X),!,R=ground.
1895 is_ground(_,nonground).
1896
1897 b_set_empty_machine :- debug_println(9,setting_empty_machine),
1898 empty_machine(Main,Machines),
1899 b_set_machine(Main,Machines,[]).
1900
1901 b_get_machine_refinement_hierarchy(Hierarchy) :-
1902 \+ machine(_Name,_M),!,Hierarchy=[]. %No B Machine loaded
1903 b_get_machine_refinement_hierarchy(Hierarchy) :-
1904 get_section_from_current_machine(meta,Infos),
1905 member(hierarchy/Hierarchy,Infos),!.
1906
1907 b_get_refined_machine(M) :-
1908 get_section_from_current_machine(meta,Infos),
1909 member(refined_machine/M,Infos), !.
1910
1911 % model type can be system for Atelier-B Event-B
1912 b_get_model_type(M) :-
1913 get_section_from_current_machine(meta,Infos),
1914 member(model_type/M,Infos), !.
1915
1916 % TODO(DP,6.8.2008)
1917 :- volatile b_machine_temp_predicate/1.
1918 :- dynamic b_machine_temp_predicate/1.
1919
1920 set_temp_predicate(CustomPredicate) :-
1921 b_parse_machine_predicate(CustomPredicate,TypedPred),
1922 assert_temp_typed_predicate(TypedPred).
1923
1924 % set a temporary predicate as additional guard
1925 set_temp_predicate(CustomPredicate,'$initialise_machine') :- !,set_temp_predicate(CustomPredicate).
1926 set_temp_predicate(CustomPredicate,'$setup_constants') :- !,set_temp_predicate(CustomPredicate).
1927 set_temp_predicate(CustomPredicate,OpName) :-
1928 b_parse_machine_operation_pre_post_predicate(CustomPredicate,TypedPred, OpName),
1929 assert_temp_typed_predicate(TypedPred).
1930
1931 assert_temp_typed_predicate(TypedPred) :-
1932 reset_temp_predicate,
1933 assert(b_machine_temp_predicate(TypedPred)).
1934
1935
1936 reset_temp_predicate :- retractall(b_machine_temp_predicate(_)).
1937
1938 :- volatile b_machine_additional_property/1.
1939 :- dynamic b_machine_additional_property/1.
1940
1941 % additional properties for set_up_constants
1942 % TO DO: check if there are constants/properties; otherwise raise warning
1943 add_additional_property(CustomPredicate) :-
1944 format('Adding Property: ~w~n',[CustomPredicate]),
1945 b_parse_machine_predicate(CustomPredicate,TypedPred),
1946 assert(b_machine_additional_property(TypedPred)).
1947
1948 :- use_module(bsyntaxtree, [safe_create_texpr/4]).
1949
1950 :- public b_extract_values_clause_assignment_calc/3.
1951 b_extract_values_clause_assignment_calc(ID,Type,TVal) :-
1952 % extract equalities from VALUES clause
1953 get_section_from_current_machine(values,Values),
1954 member(b(values_entry(TID,TVal),_,Info),Values),
1955 get_texpr_id(TID,ID),
1956 get_texpr_type(TID,Type),
1957 debug_println(20,values_entry(ID,Type,TVal)),
1958 (b_is_constant(ID)
1959 -> safe_create_texpr(equal(TID,TVal),pred,Info,Equality),
1960 assert(b_machine_additional_property(Equality)),
1961 (b_extract_values_clause_assignment(ID,_,_)
1962 -> add_error(bmachine,'Multiple VALUES entries for constant: ',ID,TID)
1963 ; true)
1964 ; b_get_machine_set(ID) -> true % will be dealt with in b_global_sets
1965 ; add_error(bmachine,'VALUES clause assigns to unknown constant: ',ID,TID),
1966 fail
1967 ).
1968
1969 % -------------------
1970
1971 :- use_module(specfile,[unset_animation_minor_modes/1,reset_animation_minor_modes/1]).
1972 b_show_machine_representation(Rep,AdditionalInfo,UnsetMinorModes) :-
1973 full_b_machine(BMachine),
1974 (UnsetMinorModes==true -> unset_animation_minor_modes(L) ; L=[]),
1975 translate_machine(BMachine,Rep,AdditionalInfo),
1976 (UnsetMinorModes==true -> reset_animation_minor_modes(L) ; true).
1977
1978 :- use_module(tools,[get_tail_filename/2,split_filename/3,safe_atom_chars/3]).
1979 b_write_machine_representation_to_file(Level,PPFILE) :-
1980 %get_full_b_machine(Name,M),
1981 get_tail_filename(PPFILE,Tail),
1982 split_filename(Tail,MachName,_Ext),
1983 b_write_machine_representation_to_file3(MachName,Level,PPFILE).
1984
1985 :- use_module(translate,[set_print_type_infos/1]).
1986 :- use_module(tools_files, [write_to_utf8_file_or_user_output/2]).
1987 b_write_machine_representation_to_file3(MachName,Level,PPFILE) :-
1988 debug_println(20,'% Pretty-Printing Internal Representation to File: '),
1989 debug_println(20,PPFILE),
1990 translate:set_print_type_infos(Level), % needed or all
1991 get_full_b_machine(_Name,M),
1992 (translate_machine_to_classicalb(MachName,M,Rep)
1993 -> translate:set_print_type_infos(none)
1994 ; add_internal_error('Translating machine failed: ',b_write_machine_representation_to_file3(MachName,Level,PPFILE)),
1995 set_print_type_infos(none),
1996 fail),
1997 write_to_utf8_file_or_user_output(PPFILE,Rep).
1998
1999 :- use_module(specfile).
2000 translate_machine_to_classicalb(MachName,M,Rep) :-
2001 temporary_set_preference(expand_avl_upto,-1,CHNG), % avoid printing sets using condensed #
2002 (animation_minor_mode(X)
2003 -> remove_animation_minor_mode,
2004 call_cleanup(translate_machine(machine(MachName,M),Rep,false), set_animation_minor_mode(X))
2005 ; translate_machine(machine(MachName,M),Rep,false)),
2006 reset_temporary_preference(expand_avl_upto,CHNG).
2007
2008 b_write_eventb_machine_to_classicalb_to_file(PPFILE) :-
2009 get_tail_filename(PPFILE,Tail),
2010 split_filename(Tail,MachName,_Ext),
2011 b_show_eventb_as_classicalb1(MachName,Rep,_AdditionalInfo),
2012 write_to_utf8_file_or_user_output(PPFILE,Rep).
2013
2014 :- use_module(preferences,[temporary_set_preference/3,reset_temporary_preference/2]).
2015 b_show_eventb_as_classicalb1(MachName,Rep,AdditionalInfo) :-
2016 full_b_machine(machine(_Name,MachineBody)),
2017 % limit abstract level to 0
2018 b_limit_abstract_level_to_zero(MachineBody,MachineBodyLevel0),
2019 temporary_set_preference(translate_print_typing_infos,true,CHNG),
2020 temporary_set_preference(translate_ids_to_parseable_format,true,CHNG2),
2021 temporary_set_preference(expand_avl_upto,-1,CHNG3), % avoid printing sets using condensed #
2022 (translate_eventb_to_classicalb(machine(MachName,MachineBodyLevel0),AdditionalInfo,Rep)
2023 -> reset_temporary_preference(translate_print_typing_infos,CHNG),
2024 reset_temporary_preference(translate_ids_to_parseable_format,CHNG2),
2025 reset_temporary_preference(expand_avl_upto,CHNG3)
2026 ; add_internal_error('Translating Event-B machine to Classical B failed: ',b_show_eventb_as_classicalb1(MachName,Rep,AdditionalInfo)),
2027 reset_temporary_preference(translate_print_typing_infos,CHNG),
2028 reset_temporary_preference(translate_ids_to_parseable_format,CHNG2),
2029 reset_temporary_preference(expand_avl_upto,CHNG3),
2030 fail).
2031
2032 b_limit_abstract_level_to_zero(MachineBody,MachineBodyLevel0) :-
2033 maplist(b_set_to_level_zero,MachineBody,MachineBodyLevel0).
2034
2035 % TODO: set to level zero also the other events of the Event-B machine
2036 b_set_to_level_zero(initialisation/InitEvent,initialisation/InitEventLevelZero) :-
2037 get_texpr_expr(InitEvent,rlevent(Id,Sec,St,Par,Grd,Thms,Act,VW,PW,Ums,_Abs)),
2038 get_texpr_info(InitEvent,Info),
2039 create_texpr(rlevent(Id,Sec,St,Par,Grd,Thms,Act,VW,PW,Ums,[]),subst,Info,InitEventLevelZero).
2040 b_set_to_level_zero(X,X).
2041
2042 b_show_eventb_as_classicalb(Rep,AdditionalInfo) :-
2043 full_b_machine(BMachine),
2044 translate_eventb_to_classicalb(BMachine,AdditionalInfo,Rep).
2045
2046 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2047
2048 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2049 % precompilation: predicates are precompiled by calling the ..._calc predicate
2050
2051 :- use_module(state_packing).
2052 :- use_module(tools,[start_ms_timer/1,stop_ms_walltimer_with_msg/2]).
2053 % maybe this predicate should be directly called by b_load_machine
2054 b_machine_precompile :- debug_println(9,'Precompiling B Machine'),
2055 start_ms_timer(T1),
2056 get_full_b_machine(_,_),
2057 auto_precompile,
2058 (debug_mode(on) -> stop_ms_walltimer_with_msg(T1,'auto_precompile: ') ; true),
2059 precompile_operation_names_in_reverse_order,
2060 % TODO(DP, 14.8.2008): remove reference to b_global_sets
2061 start_ms_timer(T2),
2062 b_check_and_precompile_global_set_type_definitions,
2063 (debug_mode(on) -> stop_ms_walltimer_with_msg(T2,'precompiling global sets: ') ; true),
2064 % TODO(DP, 12.9.2008): remove reference to kernel_freetypes
2065 reset_freetypes,
2066 get_section_from_current_machine(freetypes,Freetypes),
2067 add_all_freetypes(Freetypes),
2068 auto_precompile_phase2,
2069 state_packing:precompile_state_packing,
2070 do_machine_consistency_check,
2071 try_kodkod,
2072 (debug_mode(on) -> stop_ms_walltimer_with_msg(T1,'complete precompiling B machine: ') ; true).
2073 add_all_freetypes([]).
2074 add_all_freetypes([freetype(Name,Cases)|Rest]) :-
2075 add_freetype(Name,Cases),
2076 add_all_freetypes(Rest).
2077
2078
2079 other_spec_precompile :- retractall(bmachine_is_precompiled),
2080 /* call if you do not animate a B specification */
2081 is_precompiled_predicate(Pred/Arity),
2082 functor(Pattern,Pred,Arity),
2083 retractall(Pattern),
2084 (precompiled_predicate_no_error_when_not_precompiled(Pred/Arity)
2085 -> assert( (Pattern :- fail ))
2086 ; assert( (Pattern :- print_message('No B machine available for '),print_message(Pattern),fail) )
2087 ),
2088 fail.
2089 other_spec_precompile :-
2090 retractall(b_get_machine_constants(_)),
2091 assert( b_get_machine_constants([]) ),
2092 retractall(b_get_machine_variables(_)),
2093 assert( b_get_machine_variables([]) ),
2094 retractall(b_get_static_assertions_from_machine(_)),
2095 assert( b_get_static_assertions_from_machine([]) ),
2096 retractall(b_machine_has_static_assertions),
2097 retractall(b_get_unproven_static_assertions_from_machine(_)),
2098 assert( b_get_unproven_static_assertions_from_machine([]) ),
2099 retractall(b_get_dynamic_assertions_from_machine(_)),
2100 assert( b_get_dynamic_assertions_from_machine([]) ),
2101 retractall(b_machine_has_dynamic_assertions),
2102 retractall(b_get_unproven_dynamic_assertions_from_machine(_)),
2103 assert( b_get_unproven_dynamic_assertions_from_machine([]) ),
2104 retractall( b_get_machine_searchscope(_) ),
2105 retractall( b_get_machine_goal(_) ),
2106 assert_bmachine_is_precompiled, debug_println(4,other_spec_precompile).
2107
2108 is_precompiled_predicate(P) :- precompiled_predicate(P).
2109 is_precompiled_predicate(P) :- precompiled_predicate_phase2(P).
2110
2111 % phase 1 precompilation
2112 precompiled_predicate(b_machine_name/1).
2113 precompiled_predicate(b_get_named_machine_set/3).
2114 precompiled_predicate(b_get_properties_from_machine/1).
2115 precompiled_predicate(b_get_machine_all_constants/1).
2116 precompiled_predicate(b_get_machine_set/2).
2117 precompiled_predicate(b_get_disjoint_constants_of_type/3).
2118 precompiled_predicate(b_get_constant_represented_inside_global_set/2).
2119 precompiled_predicate(b_get_machine_constants/1).
2120 precompiled_predicate(b_get_machine_variables/1).
2121 precompiled_predicate(b_get_invariant_from_machine/1).
2122 precompiled_predicate(b_get_linking_invariant_from_machine/1).
2123 precompiled_predicate(b_is_constant/2).
2124 precompiled_predicate(b_is_variable/2).
2125 precompiled_predicate(b_get_constant_variable_description/2).
2126 precompiled_predicate(b_get_static_assertions_from_machine/1).
2127 precompiled_predicate(b_machine_has_static_assertions/0).
2128 precompiled_predicate(b_get_unproven_static_assertions_from_machine/1).
2129 precompiled_predicate(b_get_dynamic_assertions_from_machine/1).
2130 precompiled_predicate(b_machine_has_dynamic_assertions/0).
2131 precompiled_predicate(b_get_unproven_dynamic_assertions_from_machine/1).
2132 precompiled_predicate(b_get_assertions_from_main_machine/2).
2133 precompiled_predicate(b_get_initialisation_from_machine/2).
2134 precompiled_predicate(b_get_machine_operation/6).
2135 precompiled_predicate(b_top_level_operation/1).
2136 precompiled_predicate(b_is_operation_name/1).
2137 precompiled_predicate(b_get_promoted_machine_operations/1).
2138 precompiled_predicate(get_operation_info/2).
2139 precompiled_predicate(b_get_machine_goal/1).
2140 precompiled_predicate(b_get_machine_setscope/2).
2141 precompiled_predicate(b_get_machine_operation_max/2).
2142 precompiled_predicate(b_get_machine_searchscope/1).
2143 precompiled_predicate(b_get_definition_string_from_machine/3).
2144 precompiled_predicate(b_get_machine_animation_function/2).
2145 precompiled_predicate(b_get_machine_heuristic_function/1).
2146 precompiled_predicate(b_get_machine_animation_expression/1).
2147 precompiled_predicate(b_get_machine_custom_nodes_function/2).
2148 precompiled_predicate(b_get_machine_custom_edges_function/2).
2149 precompiled_predicate(complete_discharged_info/0). % just call it before calling b_specialized_invariant_for_op_calc !
2150 precompiled_predicate(get_proven_invariant/2).
2151 precompiled_predicate(b_specialized_invariant_for_op/2).
2152 precompiled_predicate(b_get_all_used_identifiers_in_section/2).
2153 precompiled_predicate(b_get_all_used_identifiers/1).
2154 precompiled_predicate(b_is_unused_constant/1).
2155 precompiled_predicate(b_extract_values_clause_assignment/3).
2156 precompiled_predicate(b_machine_statistics/2).
2157
2158 % require b_global_sets to be initialised
2159 precompiled_predicate_phase2(b_get_operation_normalized_read_write_info/3).
2160 precompiled_predicate_phase2(b_operation_cannot_modify_state/1).
2161 precompiled_predicate_phase2(b_operation_reads_output_variables/3).
2162 precompiled_predicate_phase2(reuse_operation_effect/2).
2163 precompiled_predicate_phase2(b_get_operation_non_det_modifies/2).
2164 precompiled_predicate_phase2(candidate_operation_for_reuse/1).
2165
2166 % these functions sometimes get called also in csp mode; simply fail silently for those cases in other_spec_precompile
2167 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_animation_function/2).
2168 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_heuristic_function/1).
2169 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_animation_expression/1).
2170 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_custom_nodes_function/2).
2171 precompiled_predicate_no_error_when_not_precompiled(b_get_machine_custom_edges_function/2).
2172
2173 % on startup, all precompiled predicates yield error message
2174 startup_precompiled :- retractall(bmachine_is_precompiled),
2175 ? precompiled_predicate(Pred/Arity),
2176 functor(Pattern,Pred,Arity),
2177 retractall(Pattern),
2178 assert( (Pattern :- add_error(bmachine,'B machine not precompiled for ',Pattern),fail) ),
2179 fail.
2180 startup_precompiled :- debug_println(4,startup_precompiled).
2181
2182 :- startup_precompiled.
2183
2184 % for each predicate in "precompiled_predicate", auto_precompile computes
2185 % all solutions by calling the predicate with an appended _calc
2186 auto_precompile :-
2187 % failure-driven loop
2188 ? precompiled_predicate(Pred/Arity), %print(precompile(Pred/Arity)),nl,
2189 %statistics(walltime,[Tot,Delta]), format('Precompiling ~w/~w [~w ms (Delta ~w) ms]~n',[Pred,Arity,Tot,Delta]),
2190 ? auto_precompile2(Pred,Arity,Pattern),
2191 (Pattern -> true /* this pattern already asserted */
2192 ; assert(Pattern)), fail.
2193 auto_precompile :- assert_bmachine_is_precompiled, debug_println(4,auto_precompile).
2194 auto_precompile_phase2 :-
2195 % failure-driven loop
2196 ? precompiled_predicate_phase2(Pred/Arity), %print(precompile(Pred/Arity)),nl,
2197 ? auto_precompile2(Pred,Arity,Pattern),
2198 (Pattern -> true /* this pattern already asserted */
2199 ; assert(Pattern)), fail.
2200 auto_precompile_phase2.
2201 % if the precompiled predicates is e.g. foo/2 then
2202 % Pattern=foo(A,B) and Call=foo_calc(A,B)
2203 auto_precompile2(Pred,Arity,Pattern) :-
2204 ? atom_concat(Pred,'_calc',CallFunctor),
2205 ? functor(Pattern,Pred,Arity),
2206 ? functor(Call,CallFunctor,Arity),
2207 ? unify_args(Arity,Call,Pattern),
2208 % delete all existing solutions
2209 ? retractall(Pattern), %print(retractall(Pattern)),nl,
2210 % the failure-driven loop for one predicate
2211 ? call(Call).
2212 unify_args(0,_,_) :- !.
2213 unify_args(N,A,B) :-
2214 arg(N,A,Arg), arg(N,B,Arg),
2215 N1 is N-1, unify_args(N1,A,B).
2216
2217 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2218 % set machine goal
2219
2220 b_set_machine_goal(Goal) :- b_set_machine_goal(Goal,false).
2221 b_set_machine_goal(Goal,WithDeferredSets) :-
2222 (WithDeferredSets=with_deferred -> Scope = [prob_ids(visible),variables] ; Scope = [variables]),
2223 b_parse_machine_predicate(Goal,Scope,TypedPred),
2224 b_set_parsed_typed_machine_goal(TypedPred).
2225 b_set_parsed_typed_machine_goal(TypedPred) :-
2226 retractall(b_get_machine_goal(_)),
2227 assert(b_get_machine_goal(TypedPred)).
2228
2229
2230 b_set_machine_searchscope(Goal) :- b_set_machine_searchscope(Goal,with_deferred).
2231 b_set_machine_searchscope(Goal,WithDeferredSets) :-
2232 (WithDeferredSets=with_deferred -> Scope = [prob_ids(visible),variables] ; Scope = [variables]),
2233 b_parse_machine_predicate(Goal,Scope,TypedPred),
2234 b_set_parsed_typed_machine_searchscope(TypedPred).
2235 b_set_parsed_typed_machine_searchscope(TypedPred) :-
2236 retractall(b_get_machine_searchscope(_)),
2237 assert(b_get_machine_searchscope(TypedPred)).
2238
2239 % also allow empty string, and #invariant and #not_invariant
2240 b_parse_optional_machine_predicate(TargetString,Target) :-
2241 is_empty_string(TargetString),!,create_texpr(truth,pred,[],Target).
2242 b_parse_optional_machine_predicate('#invariant',Invariant) :- !,
2243 b_get_invariant_from_machine(Invariant).
2244 b_parse_optional_machine_predicate('#not_invariant',TargetPredicate) :- !,
2245 b_get_invariant_from_machine(Invariant),
2246 bsyntaxtree:create_negation(Invariant,TargetPredicate).
2247 b_parse_optional_machine_predicate(TargetString,Target) :-
2248 b_parse_machine_predicate(TargetString,Target).
2249
2250 is_empty_string(Atom) :-
2251 atom_codes(Atom,Codes),
2252 is_empty_string2(Codes).
2253 is_empty_string2([]).
2254 is_empty_string2([32|Codes]) :- is_empty_string2(Codes).
2255
2256
2257 % parsing a string as predicate with deferred set elements
2258 b_parse_machine_predicate(Pred,TypedPred) :- b_parse_machine_predicate(Pred,[variables],TypedPred).
2259 b_parse_machine_predicate(Pred,Scope,TypedPred) :-
2260 atom_codes(Pred,Codes),
2261 b_parse_machine_predicate_from_codes(Codes,Scope,TypedPred).
2262 b_parse_machine_predicate_from_codes(Codes,Scope,TypedPred) :-
2263 b_parse_machine_predicate_from_codes2(Codes,[],Scope,TypedPred,closed).
2264 b_parse_machine_predicate_from_codes_open(OptionalQuantifier,Codes,Defs,Scope,TypedPred) :-
2265 b_parse_machine_predicate_from_codes2(Codes,Defs,Scope,TypedPred,open(OptionalQuantifier)).
2266
2267 b_parse_machine_predicate_from_codes2(Codes,Defs,Scope,TypedPred,Mode) :-
2268 debug_println(9,parse_predicate(Mode)),
2269 (Defs=[] -> true ; debug_println(9,'% Ignoring DEFINITIONS')),
2270 b_parse_wo_type_machine_predicate_from_codes_to_raw_expr(Codes,Parsed),
2271 b_type_check_raw_expr(Parsed,Scope,TypedPred,Mode).
2272
2273 check_codes(X) :- (X=[] ; X=[H|_], number(H)),!.
2274 check_codes(X) :- add_error(bmachine,'Error while parsing: not a code list: ',X),fail.
2275
2276 b_parse_wo_type_machine_predicate_from_codes_to_raw_expr(Codes,ParsedRaw) :-
2277 check_codes(Codes),
2278 catch(
2279 parse_predicate(Codes,ParsedRaw), % ,print(ParsedRaw),nl),
2280 Exception,
2281 ( Exception = parse_errors(Errors) -> %print(errors(Errors)),nl,
2282 add_all_perrors(Errors,[],parse_machine_predicate_error),fail
2283 ; otherwise ->
2284 add_error(bmachine,'Exception while parsing predicate: ',Exception),
2285 fail)).
2286
2287 b_type_check_raw_expr(ParsedRaw,Scope,TypedPred,Mode) :-
2288 debug_println(9,type_with_errors(ParsedRaw)),
2289 ( Mode == closed ->
2290 type_with_errors(ParsedRaw,Scope,pred,TypedPred)
2291 ; Mode = open(OptionalQuantifier) ->
2292 b_type_open_predicate_with_errors(OptionalQuantifier,ParsedRaw,Scope,TypedPred)).
2293
2294
2295 b_parse_machine_operation_pre_post_predicate(Pred,TypedPred,OpName) :-
2296 atom_codes(Pred,Codes),
2297 catch( parse_predicate(Codes,Parsed),
2298 Exception,
2299 ( Exception = parse_errors(Errors) ->
2300 add_all_perrors(Errors,[],parse_pre_predicate_error),fail
2301 ; otherwise ->
2302 add_error(bmachine,'Exception while parsing predicate: ',Exception),
2303 fail)),
2304 ( b_get_machine_operation(OpName,Results,Paras,_)
2305 -> append(Paras,Results,PR), % b_get_machine_operation_typed_parameters
2306 get_primed_machine_variables(PV),
2307 append(PV,PR,V)
2308 ; is_initialisation_op(OpName) -> V=[]
2309 ; add_error_fail(b_parse_machine_operation_pre_post_predicate,'Unknown operation:', OpName)),
2310 Scope = [prob_ids(visible),identifier(V),variables],
2311 %print(typing(Parsed,V)),nl,
2312 type_with_errors(Parsed,Scope,pred,TypedPred).
2313
2314 % Note: B and Event-B have different way of priming; this is aimed at classical B
2315 % and supposes predicate used together with execute_operation_by_predicate_in_state
2316 get_primed_machine_variables(Ids) :-
2317 b_get_machine_variables(Vars),
2318 maplist(prime_variable,Vars,Ids).
2319 :- use_module(btypechecker,[prime_atom0/2]).
2320 prime_variable(b(identifier(ID),T,I),b(identifier(PID),T,I)) :- prime_atom0(ID,PID).
2321
2322 is_initialisation_op('$setup_constants').
2323 is_initialisation_op('$initialise_machine').
2324
2325 b_parse_machine_expression_from_codes_with_prob_ids(Codes,TypedExpr) :-
2326 b_parse_machine_expression_from_codes3(Codes,[prob_ids(visible),variables],TypedExpr).
2327 b_parse_machine_expression_from_codes(Codes,TypedExpr) :-
2328 b_parse_machine_expression_from_codes3(Codes,[variables],TypedExpr).
2329
2330 b_parse_machine_expression_from_codes3(Codes,Scope,TypedExpr) :-
2331 b_parse_machine_expression_from_codes(Codes,Scope,TypedExpr,_Type,true,Error),!,
2332 (Error=none -> true
2333 ; add_error(b_parse_machine_expression_from_codes,'Errors occured during parsing: ', Error),
2334 % format(user_error,'Parsing: ~s~n',[Codes]),
2335 fail).
2336
2337
2338 %b_parse_machine_expression_from_codes(Codes,TypedExpr) :-
2339 % b_parse_machine_expression_from_codes(Codes,TypedExpr,_Type,false,Error), Error=none.
2340
2341 b_parse_machine_expression_from_codes(Codes,Typed,Type,GenerateParseErrors,Error) :-
2342 b_parse_machine_expression_from_codes(Codes,[variables],
2343 Typed,Type,GenerateParseErrors,Error).
2344 b_parse_machine_expression_from_codes(Codes,Scope,
2345 Typed,Type,GenerateParseErrors,Error) :-
2346 b_parse_machine_formula_from_codes(expression,Codes,Scope,
2347 Typed,Type,GenerateParseErrors,Error).
2348
2349 % a variant of b_parse_machine_predicate that allows also expressions
2350 b_parse_machine_formula(PredOrExpr,Scope,TypedPredOrExpr) :-
2351 atom_codes(PredOrExpr,Codes),
2352 b_parse_machine_formula_from_codes(formula,Codes,Scope,
2353 TypedPredOrExpr,_Type,true,Error), Error=none.
2354
2355 % Kind = expression, predicate, formula, substitution
2356 b_parse_machine_formula_from_codes(Kind,Codes,Scope,
2357 Typed,Type,GenerateParseErrors,Error) :-
2358 b_parse_only(Kind,Codes, ParsedAST, GenerateParseErrors, Error),
2359 %print(parsed(Parsed,Error)),nl,
2360 ( nonvar(Error) -> true /* either exception or parse error occured */
2361 ; type_with_errors(ParsedAST,Scope,Type,Typed) -> Error=none
2362 ; otherwise -> Error=type_error).
2363
2364 b_parse_only(Kind,Codes, ParsedAST, _,Error) :- (Codes \= [] , Codes \= [_|_]),!,
2365 add_internal_error('Not a codes list: ',b_parse_only(Kind,Codes, ParsedAST, _, Error)),
2366 Error = internal_error.
2367 b_parse_only(Kind,Codes, ParsedAST, GenerateParseErrors,Error) :-
2368 catch( parse(Kind,Codes,ParsedAST),
2369 Exception,
2370 ( GenerateParseErrors=true,
2371 ( Exception = parse_errors(Errors) ->
2372 add_all_perrors(Errors,[],parse_machine_formula_error),
2373 Error=parse_error
2374 ; otherwise ->
2375 ajoin(['Exception while parsing ',Kind,': '],Msg),
2376 add_error(bmachine,Msg,Exception),
2377 Error=exception))).
2378
2379
2380 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2381
2382 % a flexible parsing predicate, useful for dot and table tools to be called from
2383 % either probcli or prob2 with either atoms or with raw ASTs:
2384
2385 parse_expression_raw_or_atom(Expr,TypedExpr) :-
2386 parse_expression_raw_or_atom3(Expr,[variables],TypedExpr).
2387 parse_expression_raw_or_atom_with_prob_ids(Expr,TypedExpr) :-
2388 parse_expression_raw_or_atom3(Expr,[prob_ids(visible),variables],TypedExpr).
2389
2390 parse_expression_raw_or_atom3('$VARIABLES',_,TypedExpr) :- !,
2391 bmachine:b_get_machine_variables(DeclaredVars),
2392 gen_couple_from_list(DeclaredVars,TypedExpr).
2393 parse_expression_raw_or_atom3(RawAST,Scope,TypedExpr) :- compound(RawAST),!, % allow to pass raw AST as well
2394 type_with_errors(RawAST,Scope,Type,TypedExpr),
2395 ((Type=pred ; Type=subst)
2396 -> add_error(state_space_reduction,'Expected expression formula but obtained: ',Type),fail
2397 ; true ).
2398 parse_expression_raw_or_atom3(VorE,Scope,TypedExpr) :-
2399 atom_codes(VorE,VorECodes),
2400 % to do: maybe support b_parse_machine_expression_from_codes_with_prob_ids
2401 b_parse_machine_expression_from_codes3(VorECodes,Scope,TypedExpr).
2402
2403 :- use_module(bsyntaxtree, [create_couple/3]).
2404 gen_couple_from_list([],string('NO VARIABLES')).
2405 gen_couple_from_list([TID],Res) :- !, Res=TID.
2406 gen_couple_from_list([TID|T],Couple) :-
2407 gen_couple_from_list(T,Rest),
2408 create_couple(TID,Rest,Couple).
2409
2410
2411 :- use_module(bsyntaxtree, [find_typed_identifier_uses/2,get_texpr_id/2]).
2412 % compute requirements for evaluating formula
2413 determine_type_of_formula(TypedExpr,Class) :-
2414 find_typed_identifier_uses(TypedExpr,Identifiers),
2415 determine_type_of_formula2(Identifiers,Class).
2416 determine_type_of_formula2([],requires_nothing).
2417 determine_type_of_formula2(Ids,Res) :-
2418 member(TID,Ids), get_texpr_id(TID,ID),
2419 b_is_variable(ID,_),
2420 !, Res = requires_variables.
2421 determine_type_of_formula2(_,requires_constants).
2422
2423 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2424 % consistency check to spot some errors
2425 do_machine_consistency_check :-
2426 specfile:animation_mode(b), % TODO (dp,27.09.2012): this is just an ugly hack
2427 type_check_definitions,
2428 minor_mode_to_check,
2429 %debug:time(bmachine:all_operations_have_valid_read_modifies_infos).
2430 !,
2431 all_operations_have_valid_read_modifies_infos.
2432 do_machine_consistency_check.
2433
2434 % In future, all formalisms should provide the relevent data
2435 minor_mode_to_check :- specfile:animation_minor_mode(eventb),!.
2436 minor_mode_to_check :- specfile:animation_minor_mode(_),!,fail.
2437 minor_mode_to_check. % classical B
2438
2439 all_operations_have_valid_read_modifies_infos :-
2440 %findall(O,b_get_machine_operation(O,_,_,_,_),OpNames),
2441 %maplist(operation_has_valid_read_modifies_infos,OpNames).
2442 ? b_is_operation_name(OpName),
2443 operation_has_valid_read_modifies_infos(OpName),fail.
2444 all_operations_have_valid_read_modifies_infos.
2445
2446 operation_has_valid_read_modifies_infos(OpName) :- % print(check(OpName)),nl,
2447 ( operation_has_valid_read_modifies_infos2(OpName) -> true
2448 ; otherwise ->
2449 add_failed_call_error(operation_has_valid_read_modifies_infos2(OpName))).
2450 operation_has_valid_read_modifies_infos2(OpName) :-
2451 b_get_operation_normalized_read_write_info(OpName,Reads,Writes),
2452 maplist(check_read(OpName),Reads),
2453 %print(operation(OpName,reads(Reads),writes(Writes))),nl,
2454 maplist(check_write(OpName),Writes).
2455
2456
2457 check_read(OpName,Id) :-
2458 ? ( (check_is_var(Id);check_is_constant(Id) ; check_is_operation(Id)) -> true
2459 ; otherwise ->
2460 ajoin(['Unknown identifier ',Id,' in "reads" information of operation:'],Msg),
2461 add_internal_error(bmachine,Msg,OpName,unknown)).
2462 check_write(OpName,Id) :-
2463 ( check_is_var(Id) -> true
2464 ; otherwise ->
2465 ajoin(['Unknown variable ',Id,' in "modifies" information of operation:'],Msg),
2466 add_internal_error(bmachine,Msg,OpName,unknown)).
2467
2468 check_is_var(Id) :-
2469 b_is_variable(Id,_).
2470 %get_texpr_id(E,Id),
2471 %b_get_machine_variables(Vars),
2472 %memberchk(E,Vars).
2473 check_is_constant(Id) :- b_is_constant(Id,_).
2474 check_is_constant(Id) :- b_get_constant_represented_inside_global_set(Id,_).
2475 % b_get_machine_all_constants(Constants),
2476 % get_texpr_id(TId,Id),
2477 % memberchk(TId,Constants).
2478 check_is_constant(Id) :- b_get_machine_set(Id).
2479 check_is_constant(Id) :- b_get_named_machine_set(Id,_).
2480 check_is_constant(Id) :-
2481 b_get_named_machine_set(_,Elems),member(Id,Elems).
2482
2483 check_is_operation(op(ID)) :-
2484 b_is_operation_name(ID), % TO DO: check that other predicates can deal with op(Id) infos
2485 get_preference(allow_operation_calls_in_expr,true).
2486
2487 % provide access to number of constants, ....:
2488
2489 :- volatile b_machine_statistics/2.
2490 :- dynamic b_machine_statistics/2.
2491 :- public b_machine_statistics_calc/2.
2492 b_machine_statistics_calc(constants,Nr) :- b_get_machine_constants(L), length(L,Nr).
2493 b_machine_statistics_calc(variables,Nr) :- b_get_machine_variables(L), length(L,Nr).
2494 b_machine_statistics_calc(properties,Nr) :-
2495 b_get_properties_from_machine(C), conjunction_to_list(C,L),length(L,Nr).
2496 b_machine_statistics_calc(invariants,Nr) :-
2497 b_get_invariant_from_machine(C), conjunction_to_list(C,L),length(L,Nr).
2498 b_machine_statistics_calc(static_assertions,Nr) :-
2499 b_get_static_assertions_from_machine(L), length(L,Nr).
2500 b_machine_statistics_calc(dynamic_assertions,Nr) :-
2501 b_get_dynamic_assertions_from_machine(L), length(L,Nr).
2502 b_machine_statistics_calc(operations,Nr) :- findall(N,b_is_operation_name(N),L),length(L,Nr).
2503
2504 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2505 % default and initial machines
2506 b_set_initial_machine :-
2507 initial_machine(Main,Machines),
2508 b_set_machine(Main,Machines,[]).
2509
2510 initial_machine(phonebook,[M]) :-
2511 M = abstract_machine(none,machine(none),machine_header(none,phonebook,[]),Body),
2512 Body = [sets(none, [deferred_set(none,'Name'),
2513 deferred_set(none,'Code')]),
2514 definitions(none,[ScopeName,ScopeCode,TraceTest0]),
2515 variables(none, [identifier(none, db)]),
2516 invariant(none, member(none,
2517 identifier(none, db),
2518 partial_function(none,
2519 identifier(none, 'Name'),
2520 identifier(none, 'Code')))),
2521 initialisation(none,
2522 assign(none, [identifier(none, db)], [empty_set(none)])),
2523 operations(none, [Add,Lookup,Update,Reset])],
2524
2525 % definitions
2526 ScopeName = expression_definition(none,
2527 scope_Name,
2528 [],
2529 interval(none, integer(none, 1), integer(none, 3))),
2530 ScopeCode = expression_definition(none,
2531 scope_Code,
2532 [],
2533 interval(none, integer(none, 1), integer(none, 2))),
2534 TraceTest0 = expression_definition(none, trace_Test0, [], empty_sequence(none)),
2535
2536 % add operation
2537 Add = operation(none,
2538 identifier(none, add),
2539 [],
2540 [identifier(none,cc),identifier(none,nn)],
2541 precondition(none, AddPre, AddAssign)),
2542 AddPre = conjunct(none,
2543 conjunct(none,
2544 member(none, identifier(none,nn), identifier(none,'Name')),
2545 member(none, identifier(none,cc), identifier(none,'Code'))),
2546 not_member(none,
2547 identifier(none,nn),
2548 domain(none, identifier(none,db)))),
2549 AddAssign = assign(none,
2550 [identifier(none,db)],
2551 [union(none,
2552 identifier(none,db),
2553 set_extension(none,
2554 [couple(none,[identifier(none,nn),
2555 identifier(none,cc)])]))]),
2556
2557 % lookup operation
2558 Lookup = operation(none,
2559 identifier(none, lookup),
2560 [identifier(none, cc)],
2561 [identifier(none, nn)],
2562 precondition(none, LookupPre, LookupAssign)),
2563 LookupPre = member(none, identifier(none,nn), domain(none,identifier(none,db))),
2564 LookupAssign = assign(none,
2565 [identifier(none, cc)],
2566 [function(none, identifier(none, db), identifier(none, nn))]),
2567
2568 % update operation
2569 Update = operation(none,
2570 identifier(none, update),
2571 [],
2572 [identifier(none,nn),identifier(none,cc)],
2573 precondition(none, UpdatePre, UpdateAssign)),
2574 UpdatePre = conjunct(none,
2575 conjunct(none,
2576 member(none, identifier(none,nn), identifier(none,'Name')),
2577 member(none, identifier(none,cc), identifier(none,'Code'))),
2578 member(none,
2579 identifier(none,nn),
2580 domain(none, identifier(none,db)))),
2581 UpdateAssign = assign(none,
2582 [function(none, identifier(none,db), identifier(none,nn))],
2583 [identifier(none, cc)]),
2584
2585 % reset operation
2586 Reset = operation(none,
2587 identifier(none,reset),
2588 [],
2589 [],
2590 precondition(none, ResetPre, ResetAssign)),
2591 ResetPre = member(none,
2592 identifier(none, db),
2593 total_function(none, identifier(none,'Name'), identifier(none,'Code'))),
2594 ResetAssign = assign(none,[identifier(none,db)],[empty_set(none)]).
2595
2596 empty_machine(empty_machine,[M]) :-
2597 M = abstract_machine(none,machine(none),machine_header(none,empty_machine,[]),Body),
2598 Body = [].