1 | % (c) 2009-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen, | |
2 | % Heinrich Heine Universitaet Duesseldorf | |
3 | % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html) | |
4 | ||
5 | ||
6 | :- module(b_state_model_check, | |
7 | [b_set_up_valid_state/1, | |
8 | b_set_up_valid_state_with_pred/2, b_set_up_valid_state_with_pred/4, | |
9 | b_find_dynamic_assertion_violation/1, | |
10 | cbc_dynamic_assertions_check/1, % a version of the above with time-out and result | |
11 | b_check_valid_state/1, | |
12 | ||
13 | state_model_check_invariant/4, | |
14 | state_model_check_assertions/4, | |
15 | state_model_check/5, | |
16 | ||
17 | cbc_deadlock_freedom_check/3, get_all_guards_false_pred/1, | |
18 | get_unsorted_all_guards_false_pred/1, get_negated_guard/3, get_negated_guard/4, | |
19 | get_guard/2, get_guard_and_precision/3, | |
20 | ||
21 | cbc_static_assertions_check/1, cbc_static_assertions_check/2, | |
22 | ||
23 | tcltk_perform_cbc_check/4, | |
24 | cbc_find_redundant_invariants/2, | |
25 | ||
26 | set_up_transition/7, | |
27 | set_up_initialisation/5, | |
28 | ||
29 | execute_operation_by_predicate_in_state/5, | |
30 | execute_operation_by_predicate_in_state_with_pos/6, | |
31 | xtl_execute_operation_by_predicate_in_state/7, | |
32 | ||
33 | cbc_constants_det_check/1, tcltk_cbc_constants_det_check/1 | |
34 | ]). | |
35 | ||
36 | ||
37 | ||
38 | :- use_module(tools). | |
39 | ||
40 | :- use_module(module_information,[module_info/2]). | |
41 | :- module_info(group,cbc). | |
42 | :- module_info(description,'This module provides various tools for constraint-based checking of B machines.'). | |
43 | ||
44 | :- use_module(self_check). | |
45 | :- use_module(library(lists)). | |
46 | :- use_module(library(ordsets)). | |
47 | :- use_module(store). | |
48 | :- use_module(translate). | |
49 | :- use_module(b_enumerate,[ b_tighter_enumerate_all_values/2]). | |
50 | :- use_module(b_interpreter, | |
51 | [b_test_boolean_expression/4, b_test_boolean_expression/6, | |
52 | %b_det_test_boolean_expression/6, | |
53 | %b_not_test_boolean_expression/6, | |
54 | b_execute_top_level_operation_wf/8, | |
55 | b_execute_top_level_statement/7, | |
56 | set_up_typed_localstate/6]). | |
57 | :- use_module(b_interpreter_eventb, [b_event_constraints/7]). | |
58 | :- use_module(b_global_sets). | |
59 | :- use_module(bmachine). | |
60 | :- use_module(bsyntaxtree). | |
61 | ||
62 | :- use_module(kernel_objects). | |
63 | :- use_module(bsets_clp). | |
64 | ||
65 | :- use_module(solver_interface, [set_up_typed_localstate_for_pred/4]). | |
66 | :- use_module(preferences, [get_preference/2]). | |
67 | ||
68 | :- use_module(debug). | |
69 | :- use_module(typechecker). | |
70 | :- use_module(bmachine). | |
71 | :- use_module(kernel_waitflags). | |
72 | :- use_module(error_manager). | |
73 | :- use_module(probsrc(solver_interface),[apply_kodkod_or_other_optimisations/3]). | |
74 | ||
75 | /* --------------------------------------------------------- */ | |
76 | ||
77 | :- use_module(tools_printing,[format_with_colour_nl/4]). | |
78 | :- use_module(tools,[start_ms_timer/1, stop_ms_timer/1]). | |
79 | stop_silent_ms_timer(T) :- (silent_mode(on) -> true ; stop_ms_timer(T)). | |
80 | ||
81 | % constraint-based checking of invariant; checking if invariant is inductive for a given operation | |
82 | state_model_check_invariant(OpName,State,Operation,NormalisedNewState) :- | |
83 | state_model_check(OpName,invariant,State,Operation,NormalisedNewState). | |
84 | ||
85 | state_model_check_assertions(OpName,State,Operation,NormalisedNewState) :- | |
86 | state_model_check(OpName,assertions,State,Operation,NormalisedNewState). | |
87 | ||
88 | state_model_check(OpName,InvOrAssertion,State,Operation,NormalisedNewState) :- | |
89 | debug_println(9,'===> Starting Constraint-Based Checking'), | |
90 | start_ms_timer(Timer), | |
91 | if(cbc_model_check(OpName,InvOrAssertion,State,Operation,NewState), | |
92 | stop_silent_ms_timer(Timer), | |
93 | (stop_silent_ms_timer(Timer), | |
94 | format_with_colour_nl(user_output,[green],'No cbc counter example for ~w',[OpName]), | |
95 | fail)), | |
96 | nl, | |
97 | format_with_colour_nl(user_error,[red,bold],'Found cbc counter example for ~w',[OpName]), | |
98 | printsilent('% ===> Operation: '), translate_event(Operation,OpStr),println_silent(OpStr), | |
99 | printsilent('% ===> State: '),translate_bstate(State,StateStr),println_silent(StateStr), | |
100 | normalise_store(NewState,NormalisedNewState), | |
101 | printsilent('% ===> NewState: '),translate_bstate(NormalisedNewState,NStateStr),println_silent(NStateStr). | |
102 | ||
103 | :- use_module(library(avl)). | |
104 | cbc_model_check(OpName,InvOrAssertion,BeforeState,Operation,NewState) :- | |
105 | (nonvar(OpName), | |
106 | \+ b_is_operation_name(OpName), \+ b_is_initialisation_name(OpName) | |
107 | -> add_error(constraint_based_check,'Operation does not exist: ',OpName), fail | |
108 | ; true | |
109 | ), | |
110 | debug_println(9,operation_name(OpName)), | |
111 | b_get_properties_from_machine(Properties), | |
112 | b_get_invariant_from_machine(Invariant), | |
113 | b_get_machine_variables(Variables), | |
114 | b_get_machine_constants(Constants), | |
115 | % print_message(extracted_invariant(Variables,Invariant)), | |
116 | ||
117 | empty_state(EmptyState), | |
118 | set_up_typed_localstate(Constants,_FreshVars1,TypedVals1,EmptyState,State1,positive), | |
119 | b_global_sets:static_symmetry_reduction_for_global_sets(State1), | |
120 | (b_is_initialisation_name(OpName) | |
121 | -> State=State1, | |
122 | BeforeState = concrete_constants(State), % Ideally we could use root if State==[]; but ProB2 after prob2_invariant_check then tries to evaluate the invariants on it; TO DO: fix ProB2/ProB2UI first | |
123 | TypedVals=TypedVals1 | |
124 | ; BeforeState=State, | |
125 | set_up_typed_localstate(Variables,_FreshVars2,TypedVals2,State1,State,positive), | |
126 | append(TypedVals1,TypedVals2,TypedVals) | |
127 | ), | |
128 | init_wait_flags_with_call_stack(WF,[prob_command_context(cbc_model_check(OpName),unknown)]), | |
129 | ||
130 | % print_message(' set up start state:'), print_message(State), | |
131 | % translate:print_bexpr(Properties), | |
132 | empty_avl(Ai), | |
133 | b_test_boolean_expression(Properties,[],State,WF,Ai,A2), % A2 is used below for after state | |
134 | % print_message(' set up properties for constants'), | |
135 | ||
136 | get_target_pred(InvOrAssertion,OpName, Invariant, PriorPred,TargetPred), | |
137 | ||
138 | %print('Prior: '),translate:print_bexpr(PriorPred),nl, | |
139 | b_test_boolean_expression(PriorPred,[],State,WF,A2,_A3), | |
140 | % print_message(' set up invariant for start state'), | |
141 | ||
142 | set_up_transition_or_init(OpName,Operation,State1,State,NewState,_TransInfo,WF), | |
143 | debug_print(9,' finished setting up target state for operation:'), debug_println(9,OpName), | |
144 | %print_message(' target state:'), print_message(NewState), | |
145 | % Note: we are not setting up an enumerator for NewState; here we would need to be careful as we cannot use tight enumeration for NewState | |
146 | ||
147 | predicate_level_optimizations(TargetPred,OptTargetPred), | |
148 | ||
149 | (debug_mode(on) -> translate:print_bexpr(OptTargetPred),nl ; true), | |
150 | b_test_boolean_expression(OptTargetPred,[],NewState,WF,A2,_Ao), % not A3 but A2; as different State | |
151 | debug_println(9,' finished setting up invariant of proven invariants and negation of invariant for target state'), | |
152 | ||
153 | % print(enum(TypedVals)),nl, | |
154 | b_tighter_enumerate_all_values(TypedVals,WF), | |
155 | ||
156 | %(debug_mode(on) -> ground_wait_flag0(WF),portray_waitflags(WF),print_bt_message(grounding_wait_flags) ; true), | |
157 | ground_wait_flags(WF). | |
158 | ||
159 | % find target predicate for invariant or assertion checking | |
160 | get_target_pred(invariant,OpName, Invariant, PriorPred, TargetPred) :- | |
161 | (b_is_initialisation_name(OpName) -> create_texpr(truth,pred,[],PriorPred) ; PriorPred=Invariant), | |
162 | % Retrieve Information on proof status of the invariant | |
163 | (get_preference(use_po,true),get_proven_invariant(OpName,ProvenInvariant) -> true | |
164 | ; create_texpr(truth,pred,[],ProvenInvariant), println_silent(no_proven_invariant_info) | |
165 | ), | |
166 | (get_preference(use_po,false) -> UncheckedInvariant=Invariant | |
167 | ; b_specialized_invariant_for_op(OpName,UncheckedInvariant) -> true | |
168 | ; UncheckedInvariant=Invariant, println_silent(no_specialized_invariant_info_for_op(OpName)) | |
169 | ), | |
170 | %print_message('proven invariant:'),print(proven(ProvenInvariant)), | |
171 | create_negation(UncheckedInvariant,NegUncheckedInvariant), | |
172 | % we conjoin the predicates so that predicate-level optimizations can be applied (TO DO: also allow Properties to be used) | |
173 | conjunct_predicates([ProvenInvariant,NegUncheckedInvariant],TargetPred). | |
174 | get_target_pred(assertions,OpName, Invariant, PriorPred, TargetPred) :- | |
175 | % TODO: deal with initialisation for PriorPred | |
176 | get_unproven_assertion(UPA), | |
177 | create_negation(UPA,NegUPA), | |
178 | format('Trying to find Assertion Violation after ~w~n Target:',[OpName]),translate:print_bexpr(NegUPA),nl,nl, | |
179 | conjunct_predicates([Invariant,UPA],PriorPred), | |
180 | conjunct_predicates([Invariant,NegUPA],TargetPred). | |
181 | % Note: in Rodin we should in principle only use assertions appearing before each theorem | |
182 | % Also: it would make sense to assert Assertion before the test | |
183 | ||
184 | get_unproven_assertion(UPA) :- | |
185 | b_get_assertions(main,dynamic,Assertions), | |
186 | (get_preference(use_po,true) | |
187 | -> exclude(bmachine:is_discharged_assertion,Assertions,UnProvenAssertions) | |
188 | ; UnProvenAssertions = Assertions | |
189 | ), | |
190 | conjunct_predicates(UnProvenAssertions,UPA). | |
191 | ||
192 | set_up_transition_or_init(OpName,Operation,ConstantsState,State,NewState,TransInfo,WF) :- | |
193 | b_is_initialisation_name(OpName),!, | |
194 | State = [], | |
195 | set_up_initialisation(ConstantsState,NewState,Operation,TransInfo,WF). | |
196 | set_up_transition_or_init(OpName,Operation,ConstantsState,State,NewState,TransInfo,WF) :- | |
197 | set_up_transition(OpName,Operation,ConstantsState,State,NewState,TransInfo,WF). | |
198 | ||
199 | % set up constraints for an operation/event | |
200 | set_up_transition(OpName,Operation,ConstantsState,State,NewState,TransInfo,WF) :- | |
201 | is_event_b_transition(OpName),!, | |
202 | b_get_machine_variables(Variables), | |
203 | create_target_state(Variables,_Values,ConstantsState,NewState,WF), | |
204 | copy_unmodified_variables(Variables,OpName,State,NewState), | |
205 | event_b_transition(OpName,Operation,State,NewState,TransInfo,WF). | |
206 | set_up_transition(OpName,Operation,ConstantsState,State,NewState,TransInfo,WF) :- | |
207 | b_is_operation_name(OpName),!, | |
208 | % classical B | |
209 | append(ConstantsState,State,InState), | |
210 | append(ConstantsState,NewState,OutState), | |
211 | b_get_machine_variables(Variables), | |
212 | if(set_up_target_store(InState,OutState),true, | |
213 | (add_internal_error('Call failed: ',set_up_target_store(InState,OutState)),fail)), | |
214 | copy_unmodified_variables(Variables,OpName,InState,OutState), | |
215 | b_execute_top_level_operation_wf(OpName,Operation,_Paras,_Results,InState,OutState,TransInfo,WF). | |
216 | set_up_transition(OpName,_,_,_,_,_,_) :- | |
217 | add_internal_error('Unknown operation: ',set_up_transition(OpName)),fail. | |
218 | ||
219 | ||
220 | is_event_b_transition(OpName) :- | |
221 | b_get_machine_operation(OpName,[],_Parameters,_TEvent,eventb_operation(_ChangeSet,_Values,_Operation),_),!. | |
222 | event_b_transition(OpName,Operation,State,NewState,TransInfo,WF) :- | |
223 | b_get_machine_operation(OpName,[],Parameters,TEvent,eventb_operation(ChangeSet,Values,Operation),_), | |
224 | copy_variable_store(State,ChangeSet,_,NewState), | |
225 | b_event_constraints(TEvent,Parameters,Values,State,NewState,TransInfo,WF). | |
226 | ||
227 | create_target_state(Variables,Values,ConstantsState,NewState,WF) :- | |
228 | set_up_typed_localstate(Variables,Values,TypedVals,ConstantsState,NewState,positive), | |
229 | b_tighter_enumerate_all_values(TypedVals,WF). | |
230 | ||
231 | % TODO[DP, 7.4.2011]: refactor, see b_interpreter:b_execute_operation3/13 | |
232 | set_up_initialisation(ConstantsState,NewState,Operation,TransInfo,WF) :- | |
233 | b_get_machine_variables(Variables), | |
234 | create_target_state(Variables,Values,ConstantsState,NewState,WF), | |
235 | store:l_expand_and_normalise_values(Values,NormalisedValues), | |
236 | safe_univ(Operation,['$initialise_machine'|NormalisedValues]), | |
237 | b_safe_get_initialisation_from_machine(Body,OType), | |
238 | set_up_initialisation2(OType,Body,Variables,ConstantsState,NewState,TransInfo,WF). | |
239 | set_up_initialisation2(classic,Body,Variables,ConstantsState,NewState,[path(Path)],WF) :- | |
240 | set_up_undefined_localstate(Variables,ConstantsState,PreInitState), | |
241 | empty_state(EmptyState), | |
242 | b_execute_top_level_statement(Body,EmptyState,PreInitState,Updates,WF,Path,output_required), | |
243 | save_updates_in_existing_store(Updates,NewState). | |
244 | set_up_initialisation2(eventb_operation(_,_,_),Body,_Variables,ConstantsState,NewState,TransInfo,WF) :- | |
245 | b_event_constraints(Body,[],_Values,ConstantsState,NewState,TransInfo,WF). | |
246 | ||
247 | set_up_target_store([],Out) :- | |
248 | (var(Out) -> Out=[] | |
249 | ; true % OutStore already set up by somebody else | |
250 | ). | |
251 | set_up_target_store([bind(V,_)|In],OutStore) :- | |
252 | nonvar(OutStore),!, % OutStore already set up by somebody else | |
253 | (OutStore=[bind(VV,_)|T], V==VV | |
254 | -> set_up_target_store(In,T) | |
255 | ; add_binding(OutStore,V), set_up_target_store(In,OutStore)). | |
256 | set_up_target_store([bind(V,_)|In],[bind(V,_)|Out]) :- | |
257 | set_up_target_store(In,Out). | |
258 | ||
259 | add_binding(List,V) :- var(List), !, List = [bind(V,_)|_]. | |
260 | add_binding([],V) :- add_internal_error(add_binding,'Variable does not appear in store: ',V,unknown). | |
261 | add_binding([bind(VV,_)|T],V) :- | |
262 | (V==VV -> true /* ok, found the variable */ | |
263 | ; add_binding(T,V)). | |
264 | ||
265 | % copy over the variables that are not changed by the operation from OldStore to NewStore | |
266 | copy_unmodified_variables(Variables,OpName,OldStore,NewStore) :- | |
267 | ( get_operation_info(OpName,SubstitutionInfo) -> | |
268 | ( memberchk(modifies(ModIDs),SubstitutionInfo) -> | |
269 | get_texpr_ids(Variables,Ids), | |
270 | exclude(is_modified_var(ModIDs),Ids,UnmodifiedIds), | |
271 | maplist(copy_var(OldStore,NewStore),UnmodifiedIds) | |
272 | ; | |
273 | add_internal_error('Operation/Event has no modifies info: ', | |
274 | copy_unmodified_variables(Variables,OpName,OldStore,NewStore)) | |
275 | % assume that all variables modified: no copy_var calls | |
276 | ) | |
277 | ; OpName = 'INITIALISATION' -> true % nothing to copy | |
278 | ; OpName = 'SETUP_CONSTANTS' -> true % nothing to copy | |
279 | ; | |
280 | add_internal_error('Unknown Operation/Event:', copy_unmodified_variables(Variables,OpName,OldStore,NewStore)), | |
281 | fail | |
282 | ). | |
283 | is_modified_var(ModIDs,Id) :- | |
284 | memberchk(Id,ModIDs). | |
285 | copy_var(OldStore,NewStore,Id) :- | |
286 | lookup_value(Id,OldStore,V),lookup_value(Id,NewStore,VNew), | |
287 | equal_object(V,VNew). | |
288 | ||
289 | ||
290 | /* --------------------------------------------------------- */ | |
291 | % a database of available CBC checks: | |
292 | cbc_check('INV_NO_RED', | |
293 | 'INV_NO_RED: Find invariants which are redundant', | |
294 | Call,Res,Ok) :- Call = (tcltk_find_redundant_invariants(Res,Ok)). | |
295 | cbc_check('INV_AXM_SAT', | |
296 | 'INV_AXM_SAT: Check if there exists a state that satisfies the INVARIANT and the PROPERTIES (AXIOMS)', | |
297 | Call,Res,Ok) :- | |
298 | Call = (b_set_up_valid_state(State) -> Ok=true,translate_bstate(State,Res) ; Ok=false, Res='NO_VALID_STATE_FOUND'). | |
299 | cbc_check('DLK', | |
300 | 'DLK: Check that INVARIANT does not allow a deadlocking state', | |
301 | Call,Res,Ok) :- | |
302 | Call = (cbc_deadlock_freedom_check(State) -> Ok=false,translate_bstate(State,Res) ; Ok=true, Res='NO_DEADLOCK_FOUND'). | |
303 | cbc_check('THM_STATIC', | |
304 | 'THM_STATIC: Check that static ASSERTIONS (THEOREMS) follow from PROPERTIES (AXIOMS)', | |
305 | Call,TclRes,Ok) :- | |
306 | Call = (cbc_static_assertions_check(Res),translate_result(Res,Ok),functor(Res,TclRes,_)). | |
307 | %cbc_check('INV/INITIALISATION', | |
308 | % 'INV/INITIALISATION: Check if INITIALISATION can violate INVARIANT', | |
309 | % Call,TclRes,Ok) :- | |
310 | % Call = (tcltk_constraint_based_check_op('$initialise_machine',invariant,Res) -> translate_result(Res,Ok),functor(Res,TclRes,_) ; Ok=true). | |
311 | cbc_check(INVO, | |
312 | Label, | |
313 | Call,Res,Ok) :- | |
314 | b_top_level_operation(OpName), | |
315 | ajoin(['INV/',OpName],INVO), | |
316 | ajoin(['INV/',OpName,': Check that ',OpName,' preserves INVARIANT'],Label), | |
317 | Call = (state_model_check(OpName,invariant,_State,_Operation,NewState) | |
318 | -> Ok=false,translate_bstate(NewState,Res) ; Ok=true, Res='NO_INVARIANT_violation_found'). | |
319 | % TO DO: maybe dynamically generate cbc_checks (inv preservation per event); disable certain checks | |
320 | ||
321 | :- public translate_result/2. % used above | |
322 | translate_result(no_counterexample_found,Ok) :- !, Ok=true. | |
323 | translate_result(no_counterexample_exists,Ok) :- !, Ok=true. | |
324 | translate_result(no_counterexample_exists(_,_,_),Ok) :- !, Ok=true. | |
325 | translate_result(time_out,Ok) :- !, Ok=time_out. | |
326 | translate_result(_,false). | |
327 | ||
328 | tcltk_perform_cbc_check(ID,Text,Result,Ok) :- | |
329 | %print(tcltk_perform_cbc_check(ID,Text,Result,Ok)),nl, | |
330 | if(cbc_check(ID,Text,Call,Res,Ok), | |
331 | (println_silent(Text), | |
332 | call(Call), | |
333 | Result=Res, | |
334 | println_silent(result(Ok,Result)) | |
335 | ), | |
336 | (add_internal_error('Illegal CBC check: ',tcltk_perform_cbc_check(ID,Text,Result,Ok)), | |
337 | fail) | |
338 | ). | |
339 | % enum_warning:enter_new_error_scope(ScopeID), event_occurred_in_error_scope(enumeration_warning(_,_,_,_)), exit_error_scope(ScopeID,ErrOcc),ErrOcc=true | |
340 | ||
341 | ||
342 | :- use_module(probsrc(bsyntaxtree),[conjunction_to_list/2]). | |
343 | :- public tcltk_find_redundant_invariants/2. | |
344 | tcltk_find_redundant_invariants(list(Res),Ok) :- | |
345 | cbc_find_redundant_invariants(Invs,Timeout_occured), | |
346 | (Invs=[] -> Res = ['NO REDUNDANT INVARIANTS'], Ok=true | |
347 | ; Timeout_occured=true -> Res = ['REDUNDANT INVARIANTS (OR WITH TIME-OUT):'|Invs], Ok=false | |
348 | ; Res = ['REDUNDANT INVARIANTS:'|Invs], Ok=false). | |
349 | ||
350 | ||
351 | :- dynamic timeout_occured/0. | |
352 | cbc_find_redundant_invariants(RedundantInvs,Timeout_occured) :- | |
353 | retractall(timeout_occured), | |
354 | findall(RI, | |
355 | (b_find_redundant_invariant(RedInv,_,R,EnumWarning,ErrOcc), | |
356 | translate:translate_bexpression(RedInv,InvString), | |
357 | generate_explanation(R,EnumWarning,ErrOcc,InvString,RI), | |
358 | (R==time_out -> assertz(timeout_occured) ; true) | |
359 | ), | |
360 | RedundantInvs), | |
361 | (timeout_occured -> Timeout_occured = true ; Timeout_occured=false). | |
362 | ||
363 | generate_explanation(R,EnumWarning,ErrOcc,InvString,Res) :- | |
364 | (EnumWarning=true -> L1=[' /* ENUM WARNING */ '|L2] ; L1=L2), | |
365 | (ErrOcc=true -> L2=[' /* REQUIRED FOR WELL-DEFINEDNESS */ '] ; L2=[]), | |
366 | (R=redundant -> ajoin([InvString|L1],Res) | |
367 | ; R=useful -> EnumWarning=true, ajoin(['ENUMERATION WARNING (POSSIBLY USEFUL): ',InvString|L2],Res) | |
368 | ; R=time_out -> ajoin(['TIME OUT (POSSIBLY USEFUL): ',InvString|L1],Res) | |
369 | ). | |
370 | ||
371 | :- use_module(tools_timeout, [time_out_with_factor_call/3]). | |
372 | ||
373 | b_find_redundant_invariant(RedundantInv,State,Redundant,EnumWarning,ErrOcc) :- | |
374 | b_get_invariant_from_machine(Invariant), | |
375 | conjunction_to_list(Invariant,InvList), | |
376 | select(RedundantInv,InvList,RestInvariantList), | |
377 | (silent_mode(on) -> true ; | |
378 | print('CHECKING REDUNDANCY: '),translate:print_bexpr(RedundantInv),nl), | |
379 | create_negation(RedundantInv,NegRed), | |
380 | conjunct_predicates(RestInvariantList,AdaptedInvariant), | |
381 | %translate:print_bexpr(AdaptedInvariant),nl, | |
382 | enter_new_error_scope(ScopeID,b_find_redundant_invariant), | |
383 | ( time_out_with_factor_call(predicate_satisfiable_relevant_ids(NegRed,AdaptedInvariant,State),5, | |
384 | TO=time_out) | |
385 | -> (TO==time_out -> Redundant=time_out ; Redundant=useful) | |
386 | ; Redundant = redundant), | |
387 | (critical_enumeration_warning_occured_in_error_scope -> EnumWarning=true | |
388 | ; EnumWarning=false), | |
389 | exit_error_scope(ScopeID,ErrOcc,b_find_redundant_invariant), | |
390 | printsilent('RESULT: '),printsilent(Redundant),nls. | |
391 | ||
392 | ||
393 | ||
394 | /* --------------------------------------------------------- */ | |
395 | ||
396 | ||
397 | ||
398 | b_set_up_valid_state(State) :- b_set_up_valid_state_with_pred(State,b(truth,pred,[]),true,none). | |
399 | ||
400 | b_set_up_valid_state_with_pred(NormalisedState,Pred) :- | |
401 | b_set_up_valid_state_with_pred(NormalisedState,Pred,true,none). | |
402 | b_set_up_valid_state_with_pred(NormalisedState,Pred,UseInvariant,UseConstantsFromStateID) :- | |
403 | %enter_new_error_scope(ScopeID,cbc_find_state), | |
404 | predicate_satisfiable_all_ids(Pred,State,UseInvariant,UseConstantsFromStateID), | |
405 | normalise_store(State,NormalisedState). | |
406 | ||
407 | % find a state satisfying the invariant but violating the Assertions | |
408 | b_find_dynamic_assertion_violation(NormalisedState) :- | |
409 | get_unproven_assertion(UPA), | |
410 | create_negation(UPA,NegUPA), | |
411 | b_set_up_valid_state_with_pred(NormalisedState,NegUPA,true,none). | |
412 | ||
413 | % the same as above, but with time-out | |
414 | cbc_dynamic_assertions_check(Result) :- | |
415 | enter_new_error_scope(ScopeID,cbc_dynamic_assertions_check), | |
416 | start_ms_timer(Timer), | |
417 | ( time_out_with_factor_call(b_find_dynamic_assertion_violation(State),10,TO=time_out) -> | |
418 | (TO==time_out -> Result = time_out ; Result = counterexample_found(State)) | |
419 | ; critical_enumeration_warning_occured_in_error_scope -> Result = no_counterexample_found | |
420 | ; Result = no_counterexample_exists | |
421 | ), | |
422 | (debug_mode(on) -> print('cbc_dynamic_assertions_check: '),stop_ms_timer(Timer) ; true), | |
423 | exit_error_scope(ScopeID,_ErrOcc,cbc_dynamic_assertions_check). | |
424 | ||
425 | /* ---------------------- */ | |
426 | /* DEADLOCK FREEDOM CHECK */ | |
427 | /* ---------------------- */ | |
428 | ||
429 | :- use_module(bsyntaxtree,[predicate_identifiers/2]). | |
430 | :- use_module(b_ast_cleanup,[predicate_level_optimizations/2]). | |
431 | ||
432 | :- public cbc_deadlock_freedom_check/1. % used above | |
433 | cbc_deadlock_freedom_check(State) :- | |
434 | create_texpr(truth,pred,[],True), Filter=0, | |
435 | cbc_deadlock_freedom_check(State,True,Filter). | |
436 | ||
437 | % if Filter=1 we filter out guards which are inconsistent with the goal before solving the full predicate | |
438 | cbc_deadlock_freedom_check(State,Goal,Filter) :- | |
439 | debug_println(19,cbc_deadlock_freedom_check(State,Filter)),flush_output, | |
440 | ( is_truth(Goal) -> | |
441 | get_all_guards_false_pred(Target) | |
442 | ; | |
443 | print('Adding additional goal predicate: '),nl, | |
444 | print_bexpr(Goal),nl, | |
445 | ( Filter=1 -> | |
446 | get_all_guards_false_pred(AllGFalse,Goal) | |
447 | ; | |
448 | get_all_guards_false_pred(AllGFalse)), | |
449 | conjunct_predicates([AllGFalse,Goal],Target) | |
450 | ),!,flush_output, | |
451 | statistics(runtime,[Start,_]), | |
452 | statistics(walltime,[WStart,_]), | |
453 | cbc_deadlock_freedom_check2(Target,RState,Start,WStart,false,TO), % TO DO: control SkipIrrelevantComponents by preference or GUI | |
454 | (TO==time_out -> State=time_out ; State=RState). | |
455 | cbc_deadlock_freedom_check2(Target,NormalisedState,Start,WStart,SkipIrrelevantComponents,TO) :- | |
456 | get_texpr_expr(Target,T), T \= falsity, | |
457 | b_get_properties_from_machine(Properties), | |
458 | b_get_invariant_from_machine(Invariant), | |
459 | conjunct_predicates([Properties,Invariant,Target],Pred1), | |
460 | b_get_machine_variables(Variables), | |
461 | b_get_machine_constants(Constants), append(Constants,Variables,CV), | |
462 | ||
463 | apply_kodkod_or_other_optimisations(CV,Pred1,Pred), | |
464 | %predicate_level_optimizations(Pred2,Pred), % detect set partitions, etc..., now done inside b_interpreter_components | |
465 | ||
466 | set_up_typed_localstate_for_pred(CV,Pred,TypedVals,State), | |
467 | b_interpreter_components:reset_component_info(false), | |
468 | (debug_mode(on) -> translate:nested_print_bexpr_as_classicalb(Pred) ; true), | |
469 | %%visualize_graph:print_predicate_dependency_as_graph_for_dot(Pred,'~/Desktop/pdg.dot'), | |
470 | (SkipIrrelevantComponents==true | |
471 | -> predicate_identifiers(Target,TargetIds) % Warning: can skip over obvious inconsistencies TRUE:BOOL | |
472 | ; TargetIds=all), | |
473 | println_silent(target(TargetIds)), | |
474 | b_global_sets:static_symmetry_reduction_for_global_sets(State), | |
475 | time_out_with_factor_call( | |
476 | b_interpreter_components:b_trace_test_components(Pred,State,TypedVals,TargetIds), | |
477 | 10, (nl,TO=time_out)), | |
478 | statistics(runtime,[Stop,_]), Time is Stop - Start, | |
479 | statistics(walltime,[WStop,_]), WTime is WStop - WStart, | |
480 | (TO==time_out -> println_silent(time_out_during_deadlock_checking(Time)), NormalisedState=State | |
481 | ; TO=no_time_out, println_silent(deadlock_counter_example_found(Time,WTime)), | |
482 | normalise_store(State,NormalisedState) | |
483 | ). | |
484 | cbc_deadlock_freedom_check2(Target,_State,Start,WStart,_,no_time_out) :- | |
485 | (get_texpr_expr(Target,falsity) -> println_silent('Disjunction of guards obviously true') ; true), | |
486 | statistics(runtime,[Stop,_]), Time is Stop - Start, | |
487 | statistics(walltime,[WStop,_]), WTime is WStop - WStart, | |
488 | println_silent(no_deadlock_counter_example_found(Time,WTime)), %print_silent | |
489 | fail. | |
490 | ||
491 | % test if a predicate can be satisfied for some instantiation of constants and variables | |
492 | predicate_satisfiable(P) :- predicate_satisfiable(P,_),!, print('SATISFIABLE'),nl,nl. | |
493 | predicate_satisfiable(_) :- print('*UNSATISFIABLE*'),nl,nl,fail. | |
494 | predicate_satisfiable(Predicate,State) :- | |
495 | b_get_invariant_from_machine(Invariant), | |
496 | predicate_satisfiable_relevant_ids(Predicate,Invariant,State). | |
497 | ||
498 | predicate_satisfiable_all_ids(Predicate,State,UseInvariant,UseConstantsFromStateID) :- | |
499 | (UseInvariant=true -> b_get_invariant_from_machine(Invariant) ; create_texpr(truth,pred,[],Invariant)), | |
500 | predicate_satisfiable5(Predicate,Invariant,State,all,UseConstantsFromStateID). % all: look at all variables/constants: we want a complete solution | |
501 | ||
502 | predicate_satisfiable_relevant_ids(Predicate,Invariant,State) :- | |
503 | predicate_identifiers(Predicate,RelevantIds), % only look at relevant ids for Predicate; skip over components not involving them | |
504 | predicate_satisfiable5(Predicate,Invariant,State,RelevantIds,none). | |
505 | ||
506 | :- use_module(b_global_sets,[add_prob_deferred_set_elements_to_store/3]). | |
507 | :- use_module(state_space,[get_constants_state_for_id/2]). | |
508 | predicate_satisfiable5(Predicate,Invariant,State,RelevantIds,UseConstantsFromStateID) :- | |
509 | (number(UseConstantsFromStateID), | |
510 | get_constants_state_for_id(UseConstantsFromStateID,UseCState) | |
511 | -> % instead of finding solutions to constants we re-use the constants found in an existing state | |
512 | Constants=[], ReuseConstants=true, | |
513 | debug_format(19,'Reusing constant values from state id ~w~n',[UseConstantsFromStateID]), | |
514 | Properties = b(truth,pred,[]) % no need to check properties | |
515 | ; b_get_properties_from_machine(Properties), | |
516 | b_get_machine_constants(Constants), | |
517 | UseCState=[], ReuseConstants=false | |
518 | ), | |
519 | conjunct_predicates([Properties,Invariant,Predicate],TotPred0), | |
520 | b_get_machine_variables(Variables), | |
521 | append(Constants,Variables,CV), | |
522 | set_up_typed_localstate_for_pred(CV,TotPred0,TypedVals,State0), | |
523 | append(UseCState,State0,State), | |
524 | apply_kodkod_or_other_optimisations(CV,TotPred0,TotPred), | |
525 | %predicate_level_optimizations(TotPred1,TotPred), %now done inside b_interpreter_components | |
526 | b_interpreter_components:reset_component_info(false), | |
527 | (debug_mode(off) -> true ; translate:nested_print_bexpr_as_classicalb(Predicate)), | |
528 | (ReuseConstants==false | |
529 | -> b_global_sets:static_symmetry_reduction_for_global_sets(State) | |
530 | % we could check if there is just a single solution for constants, | |
531 | ; true | |
532 | ), | |
533 | add_prob_deferred_set_elements_to_store(State,State1,visible), | |
534 | % TO DO: catch time-outs | |
535 | b_interpreter_components:b_trace_test_components(TotPred,State1,TypedVals,RelevantIds). | |
536 | ||
537 | % we could call solve_components in solver_interface or solve_predicate directly | |
538 | % we could provide options to call setlog, Z3, WD prover, ... | |
539 | % we could also integrate this into apply_kodkod_or_other_optimisations | |
540 | % should we merge with solve_cbc_predicate_over_constants | |
541 | ||
542 | % -------------- | |
543 | ||
544 | % set up a predicate which is true if all guards are false | |
545 | get_all_guards_false_pred(AllGuardsFalsePred) :- | |
546 | findall(NegGuard, | |
547 | (b_is_operation_name(OpName), | |
548 | get_negated_guard(OpName,_,NegGuard)), ListOfNegGuards), | |
549 | conjunct_and_sort_smt_predicates(ListOfNegGuards,AllGuardsFalsePred). | |
550 | get_all_guards_false_pred(AllGuardsFalsePred,FilterPred) :- | |
551 | findall(NegGuard, | |
552 | (b_is_operation_name(OpName), | |
553 | get_negated_guard(OpName,Guard,NegGuard), | |
554 | conjunct_predicates([Guard,FilterPred],FGuard), | |
555 | nls,printsilent('---> CHECKING IF GUARD SATISFIABLE: '), printsilent(OpName),nls, | |
556 | predicate_satisfiable(FGuard) % if Guard not satisfiable given FilterPred: remove it | |
557 | ), ListOfNegGuards), | |
558 | conjunct_and_sort_smt_predicates(ListOfNegGuards,AllGuardsFalsePred). | |
559 | ||
560 | % the following is useful, e.g., for graphical visualization | |
561 | get_unsorted_all_guards_false_pred(AllGuardsFalsePred) :- | |
562 | findall(NegGuard, | |
563 | (b_is_operation_name(OpName), | |
564 | get_negated_guard(OpName,_,NegGuard)), ListOfNegGuards), | |
565 | conjunct_predicates(ListOfNegGuards,AllGuardsFalsePred). | |
566 | ||
567 | conjunct_and_sort_smt_predicates(List,Result) :- | |
568 | debug_println(9,'Counting basic predicates'), | |
569 | empty_avl(Ai), count(List,2,Ai,Ao), | |
570 | % portray_avl(Ao),nl, | |
571 | sort_smt_predicates(List,Ao,SList), | |
572 | %nl,print(sorted(SList)),nl, | |
573 | conjunct_smt_predicates(SList,Result) , debug_println(9,finished). | |
574 | ||
575 | conjunct_smt_predicates([],b(truth,pred,[])). | |
576 | conjunct_smt_predicates([P|T],Res) :- conjunct_smt_predicates(T,TRes), | |
577 | extract_info(P,TRes,Info), % extract e.g., wd condition info | |
578 | conjoin(P,TRes,[try_smt|Info],Res). % try_smt currently no longer useful ? | |
579 | ||
580 | % Count the number of occurences of given basic predicates | |
581 | count(b(Pred,pred,_Info),Rel,Ai,Ao) :- !,count2(Pred,Rel,Ai,Ao). | |
582 | count([],_,Ai,Ao) :- !,Ao=Ai. | |
583 | count([H|T],Rel,Ai,Ao) :- !,count(H,Rel,Ai,Aii), count(T,Rel,Aii,Ao). | |
584 | count(R,_,_,_) :- add_error_fail(count,'Illegal argument to count: ',R). | |
585 | ||
586 | count2(negation(Pred),Rel,Ai,Ao) :- !, count(Pred,Rel,Ai,Ao). | |
587 | count2(conjunct(A,B),Rel,Ai,Ao) :- !, count(A,Rel,Ai,Aii), count(B,Rel,Aii,Ao). | |
588 | count2(Pred,Rel,Ai,Ao) :- disjunctive_pred(Pred,A,B),!, | |
589 | (Rel>1 | |
590 | -> R1 is Rel-1, count(A,R1,Ai,Aii), count(B,R1,Aii,Ao) | |
591 | ; Ai=Ao). | |
592 | count2(Pred,Rel,Ai,Ao) :- smt_predicate(Pred),!, norm_pred(Pred,NP), | |
593 | (avl_fetch(NP,Ai,C1) -> Count is C1+Rel ; Count = Rel), | |
594 | avl_store(NP,Ai,Count,Ao). | |
595 | count2(_Pred,_Rel,A,A). | |
596 | ||
597 | disjunctive_pred(disjunct(A,B),A,B). | |
598 | disjunctive_pred(implication(A,B),A,B). | |
599 | disjunctive_pred(equivalence(A,B),A,B). | |
600 | ||
601 | ||
602 | sort_smt_predicates(b(Pred,pred,Info),Ai,b(SP,pred,Info)) :- sort_smt_predicates2(Pred,Ai,SP). | |
603 | sort_smt_predicates([],_,[]). | |
604 | sort_smt_predicates([H|T],Ai,[SH|ST]) :- sort_smt_predicates(H,Ai,SH), sort_smt_predicates(T,Ai,ST). | |
605 | ||
606 | sort_smt_predicates2(negation(Pred),AVL,negation(SPred)) :- !,sort_smt_predicates(Pred,AVL,SPred). | |
607 | sort_smt_predicates2(implication(A,B),AVL,implication(SA,SB)) :- !, | |
608 | sort_smt_predicates(A,AVL,SA), sort_smt_predicates(B,AVL,SB). | |
609 | sort_smt_predicates2(equivalence(A,B),AVL,equivalence(SA,SB)) :- !, | |
610 | sort_smt_predicates(A,AVL,SA), sort_smt_predicates(B,AVL,SB). | |
611 | sort_smt_predicates2(disjunct(A,B),AVL,disjunct(SA,SB)) :- !, % To do: also sort disjuncts | |
612 | sort_smt_predicates(A,AVL,SA), sort_smt_predicates(B,AVL,SB). | |
613 | sort_smt_predicates2(conjunct(A,B),AVL,Res) :- !, | |
614 | conjunction_to_count_list(b(conjunct(A,B),pred,[]),AVL,CountList), | |
615 | sort(CountList,SC), | |
616 | reverse(SC,SortedCList), % to do : use samsort with custom order | |
617 | project_count_list(SortedCList,PR), | |
618 | conjunct_smt_predicates(PR,BRes), | |
619 | (debug_mode(on) -> translate:print_bexpr(BRes),nl ; true), | |
620 | BRes = b(Res,pred,_). | |
621 | sort_smt_predicates2(X,_,X). | |
622 | ||
623 | project_count_list([],[]). | |
624 | project_count_list([count(_,P)|T],[P|PT]) :- project_count_list(T,PT). | |
625 | ||
626 | conjunction_to_count_list(C,AVL,List) :- is_a_conjunct(C,LHS,RHS),!, | |
627 | conjunction_to_count_list(LHS,AVL,L1), | |
628 | conjunction_to_count_list(RHS,AVL,R1), | |
629 | append(L1,R1,List). % TO DO: improve, use Difference Lists | |
630 | conjunction_to_count_list(b(Pred,pred,Info),AVL,[count(Count,b(Pred,pred,Info))]) :- smt_predicate(Pred),!, | |
631 | norm_pred(Pred,NX), | |
632 | (avl_fetch(NX,AVL,Count) -> true ; Count=0). | |
633 | conjunction_to_count_list(P,_AVL,[count(0,P)]). | |
634 | ||
635 | smt_predicate(equal(_,_)). | |
636 | smt_predicate(not_equal(_,_)). | |
637 | smt_predicate(member(_,_)). | |
638 | smt_predicate(not_member(_,_)). | |
639 | smt_predicate(less(_,_)). | |
640 | smt_predicate(less_equal(_,_)). | |
641 | smt_predicate(greater(_,_)). | |
642 | smt_predicate(greater_equal(_,_)). | |
643 | ||
644 | norm_pred(equal(A,B),Res) :- !,norm_equal(A,B,Res). | |
645 | norm_pred(not_equal(A,B),Res) :- !,norm_equal(A,B,Res). | |
646 | norm_pred(member(A,B),member(AA,BB)) :- !,norm_pred(A,AA),norm_pred(B,BB). | |
647 | norm_pred(not_member(A,B),member(AA,BB)) :- !,norm_pred(A,AA),norm_pred(B,BB). | |
648 | norm_pred(less(A,B),less(AA,BB)) :- !,norm_pred(A,AA),norm_pred(B,BB). | |
649 | norm_pred(greater(A,B),less(BB,AA)) :- !,norm_pred(A,AA),norm_pred(B,BB). | |
650 | norm_pred(less_equal(A,B),less(BB,AA)) :- !,norm_pred(A,AA),norm_pred(B,BB). | |
651 | norm_pred(greater_equal(A,B),less(AA,BB)) :- !,norm_pred(A,AA),norm_pred(B,BB). | |
652 | norm_pred(b(B,_,_),Res) :- !, norm_pred(B,Res). | |
653 | norm_pred(set_extension(L),Res) :- !, Res=set_extension(NL), norm_pred(L,NL). | |
654 | norm_pred(integer(A),Res) :- !,Res=A. | |
655 | norm_pred(identifier(A),Res) :- !,Res=A. | |
656 | norm_pred([],Res) :- !, Res=[]. | |
657 | norm_pred([H|T],Res) :- !, Res=[NH|NT], norm_pred(H,NH), norm_pred(T,NT). | |
658 | norm_pred(X,X). | |
659 | ||
660 | ||
661 | norm_equal(b(identifier(ID),_,_),_B,Res) :- !,Res=ID. | |
662 | norm_equal(A,B,Res) :- norm_pred(A,AA),norm_pred(B,BB), | |
663 | (AA==boolean_false -> AAA=boolean_true ; AAA=AA), | |
664 | (BB==boolean_false -> BBB=boolean_true ; BBB=BB), | |
665 | (BBB @< AAA -> Res = equal(AAA,BBB) ; Res= equal(BBB,AAA)). | |
666 | /* | |
667 | operation_satisfiable(OpName,FilterPred) :- get_machine_operation(OpName,_,_,_), | |
668 | get_negated_guard(OpName,Guard,_NegGuard), | |
669 | conjunct_predicates([Guard,FilterPred],FGuard), | |
670 | print('CHECKING IF GUARD SATISFIABLE: '), print(OpName),nl, | |
671 | predicate_satisfiable(FGuard).*/ | |
672 | ||
673 | % Optionally: Remove certain complicated parts from the guards | |
674 | /* | |
675 | simplify_guard(b(Pred,pred,Info),SPred) :- simplify_guard2(Pred,Info,SPred). | |
676 | simplify_guard2(conjunct(A,B),Info,Res) :- !, | |
677 | simplify_guard(A,SA), simplify_guard(B,SB), | |
678 | conjoin(SA,SB,Info,Res). | |
679 | simplify_guard2(exists(P,B),_Info,R) :- !, R=b(truth,pred,[]), | |
680 | print('REMOVED: '),translate:print_bexpr(b(exists(P,B),pred,[])),nl. | |
681 | simplify_guard2(X,Info,b(X,pred,Info)). | |
682 | */ | |
683 | ||
684 | conjoin(b(truth,_,_),B,_,R) :- !,R=B. | |
685 | conjoin(b(falsity,_,_),_B,_,R) :- !,R=b(falsity,pred,[]). | |
686 | conjoin(A,b(truth,_,_),_,R) :- !,R=A. | |
687 | conjoin(_A,b(falsity,_,_),_,R) :- !,R=b(falsity,pred,[]). | |
688 | conjoin(A,B,Info,b(conjunct(A,B),pred,Info)). | |
689 | ||
690 | get_negated_guard(OpName,Guard,NegationOfGuard) :- get_negated_guard(OpName,Guard,NegationOfGuard,_Precise). | |
691 | get_negated_guard(OpName,Guard,NegationOfGuard,Precise) :- | |
692 | get_guard_and_precision(OpName,Guard,Precise), | |
693 | SGuard=Guard, | |
694 | %simplify_guard(Guard,SGuard), %% comment in to remove complicated parts | |
695 | create_negation(SGuard,NegationOfGuard). % we used to add try_smt Info; no longer relevant !? | |
696 | ||
697 | ||
698 | :- use_module(b_operation_guards,[get_simplified_operation_enabling_condition/5]). | |
699 | %:- use_module(b_ast_cleanup, [clean_up/3]). | |
700 | :- use_module(b_interpreter_components,[construct_optimized_exists/3]). | |
701 | ||
702 | % get a guard, by translating all parameters into existential quantifiers | |
703 | get_guard(OpName,Guard) :- get_guard_and_precision(OpName,Guard,_). | |
704 | get_guard_and_precision(OpName,Guard,Precise) :- | |
705 | get_simplified_operation_enabling_condition(OpName,Parameters,EnablingCondition,_BecomesSuchVars,Precise), | |
706 | % Precise is either precise or imprecise | |
707 | % TO DO: partition; avoid lifting becomes_such_that conditions | |
708 | % (in EventB the feasibility PO will ensure that Guard => BecomeSuchThat is ok) | |
709 | construct_optimized_exists(Parameters,EnablingCondition,Guard). | |
710 | ||
711 | /* --------------------------------------------------------- */ | |
712 | ||
713 | :- use_module(tools_printing,[print_error/1]). | |
714 | b_check_valid_state(State) :- | |
715 | (b_valid_state(State) -> true | |
716 | ; print_error('Invalid State:'), | |
717 | print_error(State) | |
718 | ). | |
719 | ||
720 | b_valid_state(State) :- | |
721 | b_get_machine_variables(Variables), | |
722 | b_check_variable_types(Variables,State). | |
723 | ||
724 | ||
725 | % TODO(DP,6.5.2008): removed type check | |
726 | :- assert_pre(b_state_model_check:b_check_variable_types(V,S), (list_skeleton(V),list_skeleton(S))). | |
727 | % (list_skeleton(V),list_skeleton(VT),list_skeleton(S))). | |
728 | :- assert_post(b_state_model_check:b_check_variable_types(_V,_S),true). | |
729 | ||
730 | b_check_variable_types([],_). | |
731 | b_check_variable_types([Var|VT],State) :- | |
732 | def_get_texpr_id(Var,VarID), get_texpr_type(Var,Type), | |
733 | (store:lookup_value_for_existing_id(VarID,State,Val), | |
734 | Val\==fail | |
735 | -> (kernel_objects:basic_type(Val,Type) | |
736 | -> true | |
737 | ; print_error('Type Error ! Variable,Value,Type: '),print_error(VarID), | |
738 | print_error(Val),print_error(Type) | |
739 | ), | |
740 | b_check_variable_types(VT,State) | |
741 | ; add_error(b_check_variable_types,'Variable not defined in state: ', VarID), | |
742 | add_error(b_check_variable_types,'Be sure that INITIALISATION initialises the variable: ', VarID), | |
743 | print_error(State) | |
744 | ). | |
745 | ||
746 | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | |
747 | % constraint based assertion check | |
748 | :- use_module(preferences). | |
749 | ||
750 | cbc_static_assertions_check(Result) :- cbc_static_assertions_check(Result,[]). | |
751 | % currently supported options: tautology_check : check that assertions are tautologies | |
752 | cbc_static_assertions_check(Result,Options) :- | |
753 | get_cbc_assertions_predicate_to_solve(Options, Constants, TotalPredicate,true,_), | |
754 | enter_new_error_scope(ScopeID,cbc_static_assertions_check), | |
755 | start_ms_timer(Timer), | |
756 | (member(observe_state,Options) -> external_functions:observe_state(State) ; true), | |
757 | ( time_out_with_factor_call(cbc_static_assertions_check2(State,Constants, TotalPredicate),10,TO=time_out) | |
758 | % counter example was found or time out reached: | |
759 | -> (TO==time_out -> Result = time_out ; Result = counterexample_found(State)) | |
760 | % cbc_static_assertions check did not find a counter exmaple: | |
761 | ; critical_enumeration_warning_occured_in_error_scope -> Result = no_counterexample_found | |
762 | ; get_elapsed_walltime(Timer,WTime), | |
763 | cbc_static_assertions_contradiction_check(Constants,TotalPredicate,Result,Options,WTime) | |
764 | ), | |
765 | (debug_mode(on) -> print('cbc_static_assertions_check: '),stop_ms_timer(Timer) ; true), | |
766 | exit_error_scope(ScopeID,_ErrOcc,cbc_static_assertions_check). | |
767 | ||
768 | % in case of proof: check if we can establish a contradiction in the hypotheses | |
769 | cbc_static_assertions_contradiction_check(Constants,TotalPredicate,Result,Options,_) :- | |
770 | member(contradiction_check,Options), | |
771 | println_silent('Looking for contradiction in hypothesis'), | |
772 | get_cbc_assertions_predicate_to_solve(Options, Constants, TotalPredicate2,false,Goal), | |
773 | start_ms_timer(Timer), | |
774 | (time_out_with_factor_call(cbc_static_assertions_check2(_,Constants, TotalPredicate2),10,TO=time_out) | |
775 | -> debug_println(no_contradiction(TO)),fail ; true), | |
776 | get_elapsed_walltime(Timer,WTime), | |
777 | (critical_enumeration_warning_occured_in_error_scope | |
778 | -> print(no_contradiction(enumeration_warning)),nl,fail ; true), | |
779 | !, | |
780 | println_silent('*** CONTRADICTION IN HYPOTHESIS FOUND !'), | |
781 | translate:translate_bexpression_with_limit(Goal,GS), | |
782 | add_warning(contradiction_in_hypotheses, | |
783 | 'Prover double check result: Contradiction in hypotheses (or Bug) detected for goal: ',GS), | |
784 | compute_unsat_core_if_requested(Options,TotalPredicate2,WTime), | |
785 | Result = no_counterexample_exists(Constants,TotalPredicate,[contradiction_in_hypotheses]). | |
786 | cbc_static_assertions_contradiction_check(Constants,TotalPredicate,Result,Options,WTime) :- | |
787 | compute_unsat_core_if_requested(Options,TotalPredicate,WTime), | |
788 | Result = no_counterexample_exists(Constants,TotalPredicate,[]). | |
789 | ||
790 | cbc_static_assertions_check2(concrete_constants(NormalisedState),Constants, TotalPredicate) :- | |
791 | solve_cbc_predicate_over_constants(Constants,TotalPredicate,NormalisedState). | |
792 | ||
793 | ||
794 | %:- use_module(smt_solvers_interface(smt_solvers_interface),[smt_solve_predicate/4]). | |
795 | %solve_cbc_predicate_over_constants(_TypedConstants,TotalPredicate,NormalisedState) :- | |
796 | % %print(TypedConstants),nl, | |
797 | % translate:nested_print_bexpr(TotalPredicate),nl, | |
798 | % Solver=z3, | |
799 | % smt_solve_predicate(Solver,TotalPredicate,NormalisedState,Result), | |
800 | % % possible results: contradiction_found, no_solution_found(Reason), time_out, solution(_) | |
801 | % print(solver_res(Solver,Result)),nl, | |
802 | % (Result = contradiction_found -> !, fail ; Result = solution(_) -> !). | |
803 | solve_cbc_predicate_over_constants(Constants,TotalPredicate,NormalisedState) :- | |
804 | empty_state(EmptyState), | |
805 | set_up_typed_localstate(Constants,_FreshVars1,TypedVals,EmptyState,State,positive), | |
806 | b_global_sets:static_symmetry_reduction_for_global_sets(State), | |
807 | apply_kodkod_or_other_optimisations(Constants,TotalPredicate,TotPred), | |
808 | %predicate_level_optimizations(TotPred1,TotPred), % now done inside b_interpreter_components | |
809 | b_interpreter_components:reset_component_info(false), | |
810 | % TO DO: prioritise components containing parts/variables from Assertions (see set_projection_on_static_assertions/) | |
811 | b_interpreter_components:b_trace_test_components(TotPred,State,TypedVals,all), | |
812 | normalise_store(State,NormalisedState). | |
813 | ||
814 | ||
815 | ||
816 | % input Options: output: list of identifiers over which predicate solved + predicate itself | |
817 | get_cbc_assertions_predicate_to_solve(Options, Constants, TotalPredicate,NegateGoal,NegGoal) :- | |
818 | get_cbc_assertions_sequent(Options, Constants, Properties, GoalToProve), | |
819 | conjunct_predicates(GoalToProve,GoalC), | |
820 | (debug_mode(on) -> print('Trying to prove goal: '),nl,translate:nested_print_bexpr_as_classicalb(GoalC) ; true), | |
821 | (NegateGoal=true -> create_negation(GoalC,NegGoal) ; NegGoal=GoalC), | |
822 | %% print('Using Hypotheses: '),nl,translate:nested_print_bexpr_as_classicalb(Properties), %% | |
823 | conjunct_predicates([NegGoal,Properties],TotalPredicate). | |
824 | ||
825 | % ------------------------ | |
826 | ||
827 | get_cbc_assertions_sequent(Options, Constants, Properties, GoalToProve) :- | |
828 | b_get_machine_constants(AllConstants), | |
829 | (member(specific(Label),Options) -> WhichAss=specific(Label) | |
830 | ; member(main_assertions,Options) -> WhichAss=main | |
831 | ; WhichAss=all), | |
832 | b_get_assertions(WhichAss,static,Assertions), | |
833 | (get_preference(use_po,true), nonmember(tautology_check,Options) | |
834 | -> exclude(bmachine:is_discharged_assertion,Assertions,UnProvenAssertions) | |
835 | ; UnProvenAssertions = Assertions | |
836 | ), | |
837 | (member(tautology_check,Options) | |
838 | % used for ProB as an Atelier-B disprover/prover: the ASSERTIONS are an implication | |
839 | -> find_identifier_uses_l(UnProvenAssertions,[],Ids), | |
840 | include(id_mem(Ids),AllConstants,Constants), % only include constants used in tautology | |
841 | construct_sequent(UnProvenAssertions,Properties,GoalToProve) | |
842 | ; % Sequent: Properties |- UnProvenAssertions | |
843 | b_get_properties_from_machine(Properties), | |
844 | Constants = AllConstants, | |
845 | GoalToProve = UnProvenAssertions | |
846 | ). | |
847 | ||
848 | construct_sequent([IMPLICATION],HYP,[RHS]) :- | |
849 | is_an_implication(IMPLICATION,HYP,RHS),!. | |
850 | construct_sequent([b(negation(HYP),pred,I)],HYP,[RHS]) :- % relevant for test 1451 | |
851 | member(was(implication),I), | |
852 | !, | |
853 | RHS=b(falsity,pred,[]). | |
854 | construct_sequent(UPAssertions,b(truth,pred,[]),UPAssertions). | |
855 | ||
856 | id_mem(IDList,TID) :- get_texpr_id(TID,ID), member(ID,IDList). | |
857 | ||
858 | :- use_module(extrasrc(unsat_cores),[unsat_core_list_with_time_limit/5]). | |
859 | compute_unsat_core_if_requested(Options,Predicate,WTime) :- | |
860 | member(unsat_core,Options),!, | |
861 | format('Computing UNSAT CORE (~w ms to find initial contradiction)~n',[WTime]), | |
862 | UCOptions=[], | |
863 | unsat_core_list_with_time_limit(Predicate,WTime,UCOptions,no_solution_found,CorePredicates), | |
864 | nl,print('UNSAT CORE: '),nl, | |
865 | print('--------'),nl, | |
866 | translate:nested_print_bexpr_as_classicalb(CorePredicates), | |
867 | print('--------'),nl. | |
868 | compute_unsat_core_if_requested(_,_,_). | |
869 | ||
870 | ||
871 | %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% | |
872 | ||
873 | copy_binding_skel(bind(Id,_),bind(Id,_)). | |
874 | ||
875 | execute_operation_by_predicate_in_state(InVarsState,OpName,Predicate,Operation,OutVariablesState) :- | |
876 | execute_operation_by_predicate_in_state_with_pos(InVarsState,OpName,Predicate,Operation,OutVariablesState,unknown). | |
877 | ||
878 | :- use_module(state_space,[visited_expression/2]). | |
879 | % execute an operation in a state with an additional predicate | |
880 | % the predicate can talk about parameters, return values, the after state | |
881 | % and the before state using $0 identifiers. | |
882 | % Predicate usually parsed by b_parse_machine_operation_pre_post_predicate | |
883 | execute_operation_by_predicate_in_state_with_pos(const_and_vars(ID,InVariablesState),OpName,Predicate,Operation, | |
884 | const_and_vars(ID,OutVariablesState),Pos) :- !, | |
885 | visited_expression(ID,concrete_constants(ConstantsState)), | |
886 | execute_operation_by_predicate_in_state2(ConstantsState,InVariablesState,OpName,Predicate, | |
887 | Operation,OutVariablesState,Pos). | |
888 | execute_operation_by_predicate_in_state_with_pos(InVariablesState,OpName,Predicate,Operation,OutVariablesState,Pos) :- | |
889 | execute_operation_by_predicate_in_state2([],InVariablesState,OpName,Predicate,Operation,OutVariablesState,Pos). | |
890 | ||
891 | :- use_module(b_global_sets,[add_prob_deferred_set_elements_to_store/3]). | |
892 | :- use_module(specfile,[b_or_z_mode/0,xtl_mode/0,get_local_state_for_operation_transition/3]). | |
893 | execute_operation_by_predicate_in_state2(ConstantsState,InVariablesState,OpName,Predicate, | |
894 | Operation,NormalisedOutVariablesState,PositionInfo) :- | |
895 | b_or_z_mode, !, | |
896 | b_get_machine_variables(Variables), | |
897 | maplist(copy_binding_skel,InVariablesState,OutVariablesState), | |
898 | copy_unmodified_variables(Variables,OpName,InVariablesState,OutVariablesState), | |
899 | % format(' ** Copied for ~w: ~w~n',[OpName,OutVariablesState]), | |
900 | init_wait_flags_with_call_stack(WF,[operation_call(OpName,ParamValues,PositionInfo)]), | |
901 | add_prob_deferred_set_elements_to_store(ConstantsState,ConstantsState1,visible), | |
902 | append(ConstantsState1,InVariablesState,In), | |
903 | append(ConstantsState1,OutVariablesState,Out), | |
904 | % for Event-B we have to add b_machine_temp_predicate | |
905 | % b_execute_operation_with_parameters(Name,LocalState,InState,Results,Parameters,OutState,ParamValues,ResultValues,Path,Info,WF,OR) | |
906 | b_execute_top_level_operation_wf(OpName,Operation,ParamValues,ResultValues,In,Out,_TransInfo,WF), | |
907 | % format(' ** Exec for ~w (~w) --> ~w: ~w~n',[OpName,ParamValues,ResultValues,OutVariablesState]), | |
908 | setup_local_state_for_operation(OpName,ParamValues,ResultValues,OpLocalState), | |
909 | maplist(create_primed_binding,InVariablesState,PrimedVars), | |
910 | append(PrimedVars,Out,PredState), | |
911 | % format(' ** LS for ~w: ~w~n',[OpName,OpLocalState]), | |
912 | % format(' ** PredState for ~w: ~w~n',[OpName,PredState]), | |
913 | % print(predicate(Predicate)),nl, | |
914 | b_test_boolean_expression(Predicate,OpLocalState,PredState,WF), | |
915 | % print(grounding_waitflags),nl, | |
916 | ground_wait_flags(WF), | |
917 | normalise_store(OutVariablesState,NormalisedOutVariablesState). | |
918 | execute_operation_by_predicate_in_state2([],State,OpName,Predicate,OpTerm,NewState,PosInfo) :- | |
919 | xtl_execute_operation_by_predicate_in_state([],State,OpName,Predicate,OpTerm,NewState,PosInfo). | |
920 | ||
921 | :- use_module(xtl_interface,[xtl_transition/3,xtl_transition_with_symbolic/3,xtl_transition_parameters/2]). | |
922 | % special variant for XTL; allows to pass additional static bindings in addition to raw state (used by VisB) | |
923 | xtl_execute_operation_by_predicate_in_state(ExtraBinds,RawState,OpName,Predicate,OpTerm,NewState,PosInfo) :- | |
924 | xtl_mode, !, | |
925 | (xtl_transition_parameters(OpName,ParaNames) | |
926 | -> same_length(ParaNames,ParamValues) % registered OpName, set up uninstantiated OpTerm | |
927 | ; xtl_transition(RawState,OpTerm,NewState)), % unregistered OpName, try to find a non-symbolic transition | |
928 | init_wait_flags_with_call_stack(WF,[operation_call(OpName,ParamValues,PosInfo)]), | |
929 | OpTerm =.. [OpName|ParamValues], % skeleton with uninstantiated parameter values | |
930 | get_local_state_for_operation_transition(OpName,OpTerm,LocState), | |
931 | maplist(to_term_binds_for_b_pred,LocState,TLocState), | |
932 | append(TLocState,ExtraBinds,ETLocState), | |
933 | b_test_boolean_expression(Predicate,ETLocState,NewState,WF), % instantiate parameters, FIXME: e.g. STATE_PROPERTY is evaluated in current state, not post state; use set_current_state_for_external_fun | |
934 | xtl_transition_with_symbolic(RawState,OpTerm,NewState), % instantiated OpTerm, check if a matching transition exists | |
935 | ground_wait_flags(WF). | |
936 | ||
937 | to_term_binds_for_b_pred(bind(ID,Val),bind(ID,term(Val))). % for XTL we compare b(term(S),string,Infos) expressions | |
938 | ||
939 | gen_bind(TID,Val,bind(ID,Val)) :- def_get_texpr_id(TID,ID). | |
940 | ||
941 | :- use_module(probsrc(bmachine),[b_get_machine_operation_for_animation/4]). | |
942 | % generate an environment where operation parameters and results are stored: | |
943 | setup_local_state_for_operation(OpName,ParamValues,ResultValues,LocalState) :- | |
944 | b_get_machine_operation_for_animation(OpName,Results,Parameters,_Body), | |
945 | maplist(gen_bind,Parameters,ParamValues,ParamBindings), | |
946 | maplist(gen_bind,Results,ResultValues,ResultBindings), | |
947 | append(ResultBindings,ParamBindings,LocalState). | |
948 | ||
949 | ||
950 | :- use_module(btypechecker,[prime_atom0/2]). | |
951 | create_primed_binding(bind(ID,Val),bind(PID,Val)) :- prime_atom0(ID,PID). | |
952 | ||
953 | ||
954 | % ------------------------------------ | |
955 | ||
956 | % Determinacy Check for Constants | |
957 | % check if the values of the constants are forced to have one value | |
958 | ||
959 | :- use_module(bsyntaxtree, [safe_create_texpr/3, get_texpr_id/2]). | |
960 | cbc_constants_det_check(UseConstantsFromStateID) :- | |
961 | cbc_constants_det_check(UseConstantsFromStateID,[print_explanation],_,_,_,_), | |
962 | fail. | |
963 | cbc_constants_det_check(_). | |
964 | ||
965 | :- use_module(state_space,[is_concrete_constants_state_id/1]). | |
966 | tcltk_cbc_constants_det_check(list([list(['CONSTANT','FORCED', 'VALUE', 'Explanation', 'Source']) | Res ])) :- | |
967 | is_concrete_constants_state_id(StateID),!, | |
968 | set_unicode_mode, | |
969 | call_cleanup( | |
970 | findall(list([ID,FS,VS,CoreStr,CoreSrc]), | |
971 | (cbc_constants_det_check(StateID,[],ConstantID,Forced,ValStr,CorePred), | |
972 | get_core_str(Nr,CorePred,CoreStr,CoreSrc), | |
973 | (Nr=1 -> ID=ConstantID, VS = ValStr, FS = Forced ; ID = '', VS = '', FS = '')), | |
974 | Res), | |
975 | unset_unicode_mode). | |
976 | tcltk_cbc_constants_det_check(list([list(['SETUP_CONSTANTS first'])])) :- b_machine_has_constants,!. | |
977 | tcltk_cbc_constants_det_check(list([list(['MODEL HAS NO CONSTANTS'])])). | |
978 | ||
979 | :- use_module(error_manager,[get_tk_table_position_info/2]). | |
980 | :- use_module(bsyntaxtree,[conjunction_to_list/2, get_texpr_expr/2,get_texpr_id/2]). | |
981 | get_core_str(Nr,CorePred,TS,Src) :- | |
982 | (conjunction_to_list(CorePred,CL), CL \= [] -> true ; CL = [CorePred]), | |
983 | nth1(Nr,CL,P), | |
984 | get_preference(translation_limit_for_table_commands,Limit), | |
985 | translate_bexpression_with_limit(P,Limit,TS), | |
986 | get_tk_table_position_info(P,Src). | |
987 | ||
988 | :- use_module(bsyntaxtree,[predicate_components/2]). | |
989 | cbc_constants_det_check(UseConstantsFromStateID,Options,ConstantID,Forced,ValStr,CorePred) :- | |
990 | % we need one solution to start from (TODO: we could look at all set_constant solutions found) | |
991 | get_constants_state_for_id(UseConstantsFromStateID,UsedCState), | |
992 | format('~nChecking if value of constants in state ~w are forced~n',[UseConstantsFromStateID]), | |
993 | ||
994 | b_get_properties_from_machine(Properties), | |
995 | b_get_machine_constants(Constants), | |
996 | predicate_components(Properties,Components), | |
997 | nth1(Nr,Components,component(ComponentPred,CompIds)), % select component via backtracking | |
998 | CompIds \= [], | |
999 | format('Checking component ~w over identifiers ~w~n',[Nr,CompIds]), | |
1000 | ||
1001 | empty_state(EmptyState), | |
1002 | set_up_typed_localstate(Constants,_FreshVars1,TypedVals1,EmptyState,State1,positive), | |
1003 | init_wait_flags_with_call_stack(WF,[prob_command_context(cbc_constants_det_check,unknown)]), | |
1004 | empty_avl(Ai), | |
1005 | b_test_boolean_expression(ComponentPred,[],State1,WF,Ai,A2), % A2 is used below for after state | |
1006 | b_tighter_enumerate_all_values(TypedVals1,WF), | |
1007 | ||
1008 | member(ConstantID,CompIds), | |
1009 | member(bind(ConstantID,CVal),UsedCState), | |
1010 | nl, | |
1011 | member(TID,Constants), def_get_texpr_id(TID,ConstantID), | |
1012 | get_texpr_type(TID,Type), | |
1013 | safe_create_texpr(not_equal(TID,b(value(CVal),Type,[])),pred,NotEqual), | |
1014 | (b_test_boolean_expression(NotEqual,[],State1,WF,A2,_), | |
1015 | ground_wait_flags(WF) | |
1016 | -> format_with_colour_nl(user_output,[green],'--- CONSTANT ~w can take on another value',[ConstantID]), | |
1017 | Forced='FALSE', ValStr = '', | |
1018 | CorePred = b(truth,pred,[]) | |
1019 | ; translate_bvalue_with_limit(CVal,50,ValStr), | |
1020 | format_with_colour_nl(user_output,[blue],'*** CONSTANT ~w has the forced value ~w',[ConstantID,ValStr]), | |
1021 | Forced='TRUE', | |
1022 | (get_preference(cbc_provide_explanations,false) | |
1023 | -> CorePred = b(unknown_truth_value(no_explanation_computed),pred,[]) | |
1024 | ; write('Generating explanation '), | |
1025 | unsat_cores:unsat_chr_core_with_fixed_conjuncts_auto_time_limit(ComponentPred,NotEqual,1000,CorePred) | |
1026 | -> (member(print_explanation,Options) -> translate:nested_print_bexpr_as_classicalb(CorePred) ; true) | |
1027 | ; CorePred = b(unknown_truth_value(fail),pred,[]) | |
1028 | ) | |
1029 | ). | |
1030 | ||
1031 | ||
1032 |