1 % (c) 2014-2022 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 :- module(static_analysis, [dependent_actions/5, enable_analysis/6, disable_analysis/5,
6 action_dependent_to_itself/4, tcltk_enabling_analysis/2,
7 compute_dependendency_relation_of_all_events_in_the_model/3,
8 enable_graph/1,dependent_act/4,
9 syntactic_independence/3,
10 get_conj_inv_predicate/3, % predicate used in the enabling analysis module
11 catch_and_ignore_well_definedness_error/2,
12 test_path_non_failing/6,
13 test_path/6,
14 is_timeout/1
15 ]).
16
17 :- meta_predicate catch_enumeration_warning(0,0).
18 :- meta_predicate catch_and_ignore_well_definedness_error(0,*).
19 :- meta_predicate catch_and_ignore_well_definedness_error(*,0,*).
20
21
22 /* Modules and Infos for the code coverage analysis */
23 :- use_module(probsrc(module_information)).
24 :- module_info(group,model_checker).
25 :- module_info(description,'This module provides predicates for static analysis of Event-B and B models').
26
27 % Standard SICSTUS prolog libraries
28 %% :- use_module(library(lists)).
29 :- use_module(library(ordsets)).
30 :- use_module(library(ugraphs)).
31
32 % Classical B prolog modules
33 :- use_module(probsrc(bmachine),[b_top_level_operation/1, b_get_invariant_from_machine/1, b_get_properties_from_machine/1]).
34 :- use_module(probsrc(bsyntaxtree), [conjunct_predicates/2]).
35 :- use_module(probsrc(b_state_model_check), [get_negated_guard/3,get_guard/2]).
36 :- use_module(probsrc(bmachine),[b_get_machine_operation_for_animation/4]). % TODO: predicate used for determining whether an event is self-dependent to itself (consider whether to remove)
37
38 % Event-B prolog modules
39
40 % POR modules
41 :- use_module(probporsrc(enabling_predicates),[compute_enabling_predicate/5]).
42
43 % Importing predicates for using CBC
44 :- use_module(cbcsrc(cbc_path_solver), [testcase_path_timeout/9]).
45 :- use_module(probsrc(b_read_write_info), [b_get_read_write/3, b_get_read_write_vars/5, b_get_operation_read_guard_vars/4]).
46
47 % Other modules (used mostly for debugging)
48 :- use_module(probsrc(preferences),[get_preference/2]).
49 :- use_module(probsrc(error_manager),[real_error_occurred/0,
50 call_in_fresh_error_scope_for_one_solution/1,
51 add_internal_error/2, add_error_fail/3,
52 wd_error_occured/0, clear_wd_errors/0,
53 critical_enumeration_warning_occured_in_error_scope/0,
54 clear_enumeration_warnings/0]).
55 :- use_module(probsrc(debug),[debug_println/2, debug_mode/1, debug_format/3, formatsilent/2]).
56 :- use_module(probsrc(tools),[cputime/1]).
57
58 % Importing unit tests predicates
59 %% :- use_module(probsrc(self_check)).
60
61 is_timeout(timeout).
62 is_timeout(time_out).
63 is_timeout(clpfd_overflow).
64 is_timeout(overflow).
65 is_timeout(virtual_time_out).
66
67 % --------------------------- Static analysis for determining the dependece/independence of events (Begin) -----------------------------%
68
69 % check syntactically influence of executing OpName1 on OpName2's enabling and effect
70 syntactic_independence(OpName1,OpName2,Res) :-
71 b_top_level_operation(OpName1),
72 b_top_level_operation(OpName2),
73 b_get_read_write_vars(OpName1,GReads1,AReads1,Reads1,Writes1),
74 b_get_read_write_vars(OpName2,GReads2,AReads2,Reads2,Writes2),
75 \+ ord_intersect(Writes1,GReads2),% otherwise Op1 can influence guard of Op2
76 (ord_intersect(Writes1,AReads2)
77 -> % guard not modified, but effect of OpName2 could change
78 Res = syntactic_keep
79 ; (\+ ord_intersect(Writes1,Writes2), % no race
80 \+ ord_intersect(GReads1,Writes2), % no enabling/disabling of OpName1 by OpName2
81 \+ ord_intersect(AReads1,Writes2)) % no change of effect
82 -> (\+ ord_intersect(Reads1,Reads2)
83 -> Res = syntactic_fully_independent
84 ; Res = syntactic_independent
85 )
86 ; Res = syntactic_unchanged % guard is kept and operation effect of OpName2 unchanged; but there could be race conditions on writes or effects of OpName2 on OpName1
87 ).
88
89 dependent_actions1(OpName1,OpName2,FindInvViolations,Timeout,Res) :-
90 b_top_level_operation(OpName1),
91 b_top_level_operation(OpName2),
92 b_get_read_write_vars(OpName1,GReads1,AReads1,Reads1,Writes1),
93 ( OpName1=OpName2 -> action_dependent_to_itself(OpName1,GReads1,Writes1,Res) % TODO: Do we really need this kind of analysis???
94 ; OpName2 @< OpName1 -> Res = '-' % our checking is symmetric; check only one pair
95 ;
96 b_get_read_write_vars(OpName2,GReads2,AReads2,Reads2,Writes2),
97 ( ord_intersect(Writes1,Writes2) -> Res = race_dependent
98 ; (\+ ord_intersect(Writes1,Reads2),\+ ord_intersect(Writes2,Reads1)) -> Res = syntactic_independent
99 ;
100 (get_preference(use_cbc_analysis,true) -> % sometimes we don't want to use the CBC
101 (\+ord_intersect(AReads1,Writes2),
102 \+ord_intersect(AReads2,Writes1) ->
103 (get_preference(dependency_enable_predicates,true) ->
104 get_dependency_enabling_predicate(OpName1,GReads1,Writes1,OpName2,GReads2,Writes2,FindInvViolations,Timeout,Res)
105 ;
106 test_enabledness_condition(OpName1,GReads1,Writes1,OpName2,GReads2,Writes2,FindInvViolations,Timeout,Res)
107 )
108 ; Res = action_dependent
109 )
110 ; Res = dependent % use_cbc_analysis = false
111 )
112 )
113 ).
114
115 % Testing whether it is possible that the one of the events can disable the other one
116 test_enabledness_condition(OpName1,GReads1,Writes1,OpName2,GReads2,Writes2,FindInvViolations,Timeout,Res) :-
117 get_negated_guard(OpName1,PosGuard1,NegGuard1),
118 get_negated_guard(OpName2,PosGuard2,NegGuard2),
119 %% get_conj_inv_predicate([PosGuard1,PosGuard2],FindInvViolations,GuardsConj),
120 conjunct_predicates([PosGuard1,PosGuard2],GuardsConj), % both events are enabled
121 ( ord_intersect(GReads1,Writes2),
122 debug_format(19,'Testing if ~w can disable ~w (check inv. = ~w)~n',[OpName2,OpName1,FindInvViolations]),
123 test_path(GuardsConj,[OpName2],NegGuard1,FindInvViolations,Timeout,_R1)
124 -> Res = guard_dependent
125 ; ord_intersect(Writes1,GReads2),
126 debug_format(19,'Testing if ~w can disable ~w (check inv. = ~w)~n',[OpName1,OpName2,FindInvViolations]),
127 test_path(GuardsConj,[OpName1],NegGuard2,FindInvViolations,Timeout,_R2)
128 -> Res = guard_dependent
129 ; Res = independent
130 ).
131
132 get_dependency_enabling_predicate(OpName1,GReads1,Writes1,OpName2,GReads2,Writes2,FindInvViolations,Timeout,Res) :-
133 get_negated_guard(OpName1,PosGuard1,NegGuard1),
134 get_negated_guard(OpName2,PosGuard2,NegGuard2),
135 conjunct_predicates([PosGuard1,PosGuard2],GuardsConj),
136 ( (ord_intersect(GReads1,Writes2),test_path(GuardsConj,[OpName2],NegGuard1,FindInvViolations,Timeout,_R1)) ->
137 % get enabling predicate after executing OpName2
138 compute_enabling_predicate(OpName2,true,PosGuard1,FindInvViolations,predicate(Enable1)),
139 ( (ord_intersect(Writes1,GReads2),test_path(GuardsConj,[OpName1],NegGuard2,FindInvViolations,Timeout,_R2)) ->
140 % get enabling predicate after executing OpName1
141 compute_enabling_predicate(OpName1,true,PosGuard2,FindInvViolations,predicate(Enable2)),
142 conjunct_predicates([Enable1,Enable2],EnablingPredicate),
143 Res = guard_dependent(EnablingPredicate)
144 ;
145 Res = guard_dependent(Enable1)
146 )
147 ; (ord_intersect(Writes1,GReads2),test_path(GuardsConj,[OpName1],NegGuard2,FindInvViolations,Timeout,_R2)) ->
148 compute_enabling_predicate(OpName1,true,PosGuard2,FindInvViolations,predicate(Enable2)),
149 Res = guard_dependent(Enable2)
150 ;
151 Res = independent
152 ),
153 (Res = guard_dependent(Pred), debug_mode(on) ->
154 print('####### Enabling Dependency Predicate for '), print(OpName1), print('<->'), print(OpName2), print(' #######'),nl,
155 print('Predicate: '),translate:print_bexpr(Pred),nl,
156 print('####################################'),nl
157 ; true).
158
159 action_dependent_to_itself(OpName,Reads,Writes,Res) :-
160 b_get_machine_operation_for_animation(OpName,_Res,Params,_),
161 length(Params,Len),
162 (Len>0,\+ord_intersect(Reads,Writes) ->
163 Res = self_independent
164 ; Len = 0 ->
165 Res = '='
166 ;
167 Res = self_dependent
168 ).
169
170 % --------------------------- Static analysis for determining the dependece/independence of events (End) -----------------------------%
171
172
173 % --------------------------- Enabling anaysis used for the computation of ample sets (Begin) -----------------------------%
174
175 enable_analysis(OpName1,OpName2,FindInvViolations,UseEnableGraph,Timeout,Enable) :-
176 b_top_level_operation(OpName1),
177 b_top_level_operation(OpName2),
178 (OpName1 == OpName2 ->
179 Enable=impossible % on top level an operation cannot enable itself
180 ;
181 b_get_read_write(OpName1,_Reads1,Writes1),
182 b_get_operation_read_guard_vars(OpName2,true,GReads2,_Precise),
183 get_negated_guard(OpName2,PosGuard2,NegGuard2),
184 %enabling_analysis: filter_predicate(PosGuard2,Writes1,FilteredPosGuard2),
185 (get_preference(use_cbc_analysis,false) ->
186 (ord_intersect(Writes1,GReads2) ->
187 get_enabling_result(UseEnableGraph,OpName1,PosGuard2,FindInvViolations,_CBCResult,Enable)
188 ;
189 Enable=possible_keep
190 )
191 ;
192 get_guard(OpName1,Guard1),
193 conjunct_predicates([Guard1,NegGuard2],StartPred),
194 ( (ord_intersect(Writes1,GReads2),test_path(StartPred,[OpName1],PosGuard2,FindInvViolations,Timeout,R)) ->
195 get_enabling_result(UseEnableGraph,OpName1,PosGuard2,FindInvViolations,R,Enable)
196 ;
197 Enable=possible_keep_or_disable
198 )
199 )
200 ).
201
202 get_enabling_result(UseEnableGraph,OpName1,PosGuard2,FindInvViolations,CBCResult,Enable) :-
203 (UseEnableGraph=true -> %(OpName1 = close_door, OpName2 = push_call_button -> trace;true),
204 % check further if Enable is inconsistent, if so then we do not need to add an edge to the enable graph
205 (compute_enabling_predicate(OpName1,true,PosGuard2,FindInvViolations,Enable) ->
206 true
207 ;
208 add_error_fail(enable_analysis,'Error occurred while computing enabling predicate for ', OpName1/PosGuard2)
209 )
210 ;
211 (is_timeout(CBCResult)-> Enable=CBCResult; Enable=possible_enable)
212 ).
213
214 catch_enumeration_warning(Call,Handler) :-
215 % throw/1 predicate raises instantiation_error
216 catch(Call, enumeration_warning(enumerating(_),_Type,_,_,critical), call(Handler)).
217
218 catch_and_ignore_well_definedness_error(Call,Result) :-
219 catch_and_ignore_well_definedness_error('',Call,Result).
220 :- use_module(probsrc(debug), [silent_mode/1, set_silent_mode/1]).
221 catch_and_ignore_well_definedness_error(Ctxt,Call,Result) :-
222 silent_mode(CurMode), set_silent_mode(on),
223 call_cleanup(catch_enumeration_warning(Call, true),
224 set_silent_mode(CurMode)),
225 (real_error_occurred -> Result=error ; Result=success),
226 cleanup_enum_and_wd(Ctxt,Result). % only cleanup when we succeed; TODO: do we need to cover the failure of Call ?
227
228 cleanup_enum_and_wd(Ctxt,Result) :-
229 ? (critical_enumeration_warning_occured_in_error_scope ->
230 formatsilent('Enumeration warning occurred and will be ignored; result=~w. ~w~n',[Result,Ctxt]),
231 clear_enumeration_warnings
232 ; true),
233 (wd_error_occured ->
234 formatsilent('WD errors occurred and will be discarded; result=~w. ~w~n',[Result,Ctxt]),
235 clear_wd_errors
236 ; true).
237
238 disable_analysis(OpName1,OpName2,FindInvViolations,Timeout,Result) :-
239 b_top_level_operation(OpName1),
240 b_top_level_operation(OpName2),
241 b_get_read_write(OpName1,_Reads1,Writes1),
242 b_get_operation_read_guard_vars(OpName2,true,GReads2,_Precise),
243 get_negated_guard(OpName2,PosGuard2,NegGuard2),
244 (get_preference(use_cbc_analysis,false) ->
245 (ord_intersect(Writes1,GReads2) -> Result=possible_disable ; Result=possible_keep)
246 ;
247 get_guard(OpName1,PosGuard1),
248 conjunct_predicates([PosGuard1,PosGuard2],StartPred),
249 ( ord_intersect(Writes1,GReads2),
250 debug_format(19,'~nTesting if ~w (writing ~w) can disable ~w (reading ~w) with inv. = ~w~n',[OpName1,Writes1,OpName2,GReads2,FindInvViolations]),
251 %print('Start: '),translate:print_bexpr(StartPred),nl, print('Target: '),translate:print_bexpr(NegGuard2),nl,
252 test_path(StartPred,[OpName1],NegGuard2,FindInvViolations,Timeout,CBCResult)
253 ->
254 debug_format(19,'CBCResult=~w~n',[CBCResult]),
255 (is_timeout(CBCResult) -> Result=CBCResult
256 ; Result=possible_disable)
257 ;
258 Result=cannot_disable
259 )
260 ).
261
262 % test_path(+Start,+Path,+Goal,+WithInv,+Timeout,-R)
263 % Runs the CBC to check whether there is a possible execution of sequence of events Path in the loaded model
264 % starting at a state s satisfying Start and reaching a state s' satisfying Goal whitin Timeout milliseconds
265 % + Start: B predicate
266 % + Path: a list of events/operations
267 % + Goal: B predicate
268 % + Timeout: specifying a timeout (in milliseconds)
269 % - R: result (result could be either 'ok', 'timeout', 'interrupt', or 'unknown')
270 %%% pred(P) - adds P to invariant
271 %%% typing(P) - just use typing from invariant and add P
272
273 test_path(Start,Path,Goal,WithInv,Timeout,Res) :-
274 (Start=init ->
275 Start1 = init
276 ;
277 (WithInv=1 ->
278 Start1 = pred(Start),
279 get_conj_inv_predicate([Goal],WithInv,Goal_Inv)
280 ; Start1=typing(Start),
281 Goal_Inv = Goal)
282 ),
283 catch_and_ignore_well_definedness_error(path(Path),testcase_path_timeout(Start1,Timeout,Path,Goal_Inv,_,_,_,_,R),ER),
284 check_result(R,ER,Res).
285
286 test_path_non_failing(Start,Path,Goal,WithInv,Timeout,R) :-
287 (test_path(Start,Path,Goal,WithInv,Timeout,R) -> true; R = false).
288
289 check_result(R,ER,Res) :-
290 (nonvar(R) -> Res=R
291 ; ER = success -> Res = 'ok'
292 ; Res = 'unknown').
293
294 % conjoin a predicate with invariant and properties if specified
295 get_conj_inv_predicate(Preds,FindInvViolations,StartPred) :-
296 (FindInvViolations==1 ->
297 b_get_invariant_from_machine(Inv),
298 b_get_properties_from_machine(Prop),
299 conjunct_predicates([Prop,Inv|Preds],StartPred) % TO DO: project away
300 ;
301 (FindInvViolations==0 -> true ; add_internal_error('Illegal flag: ',get_conj_inv_predicate(Preds,FindInvViolations,StartPred))),
302 conjunct_predicates(Preds,StartPred)
303 ).
304
305 %reads_writes_intersection(Writes, Reads, ComputedResult, PositiveResult, Res) :-
306 % (ord_intersect(Writes,Reads) -> Res=PositiveResult ; Res=ComputedResult).
307
308 tcltk_enabling_analysis(list([list(['Origin'|Ops])|Result]),POR) :-
309 get_preference(timeout_cbc_analysis,Timeout),
310 %% compute_dependendency_relation_of_all_events_in_the_model(1,por(ample_sets,0,0,0),EnableGraph),
311 %% suitable_for_por(EnableGraph,POR),
312 POR = option_disabled,
313 findall(Op, b_top_level_operation(Op), Ops),
314 findall(list([OpName1|EnableList]),
315 (b_top_level_operation(OpName1),
316 findall(Enable,enable_analysis(OpName1,_OpName2,1,1,Timeout,Enable),EnableList)),
317 Result)
318 . %,print_enable_table([list(['Origin'|Ops])|Result]).
319
320 %% suitable_for_por(EnGraph,Result) :-
321 %% (not_all_reachable(EnGraph) ->
322 %% Result=true
323 %% ; Result=false
324 %% ).
325
326 %% not_all_reachable(EnGraph) :-
327 %% ample_sets: vertices(EnGraph,Vertices),
328 %% member(V,Vertices),
329 %% \+ (ample_sets: reachable(V,EnGraph,Reachable),Reachable=Vertices).
330 % --------------------------- Used for the ample sets (End) -----------------------------%
331
332
333
334
335 /************************** DEPENDENCY RELATION (BEGIN) ******************************/
336
337 /* predicate which determines the dependency relations between all actions in the model,
338 it should be called only once (prior to the model checking) */
339
340 :- dynamic enable_graph/1, dependent_act/4.
341
342 :- use_module(probsrc(runtime_profiler),[start_profile/2, stop_profile/4]).
343
344 compute_dependendency_relation_of_all_events_in_the_model(FindInvViolations,por(_TYPE,UseEnableGraph,Depth,_PGE),EnableGraph) :-
345 (enable_graph(EnableGraph) ->
346 % In case the dependency relations and the enable graph are already computed.
347 % Case possible if the user stopped the model checking for a while (and meanwhile didn't reloaded the model)
348 % and in case that he wants to continue the verification of the model the enable graph don't have
349 % to be computed again.
350 true
351 ;
352 start_profile(partial_order_reduction,Timer),
353 findall(Action, b_top_level_operation(Action),Actions),
354 sort(Actions,AllActions),
355 retractall(enable_graph(_)),
356 debug_println(19,'********** DETERMINE ACTION DEPENDENCIES AND ENABLE GRAPH *************'),
357 get_preference(timeout_cbc_analysis,Timeout),
358 cputime(T1),
359 call_in_fresh_error_scope_for_one_solution(
360 determine_dependency_enabling_relations(AllActions,Timeout,FindInvViolations,UseEnableGraph,Depth,EnableGraph)),
361 cputime(T2),
362 debug_println(19,'********** FINISHED ANALYSIS *************'),
363 D is T2-T1, format('Dependency Analysis Time: ~w ms~n',[D]),
364 assertz(enable_graph(EnableGraph)),
365 stop_profile(partial_order_reduction,compute_enable_graph,unknown,Timer)
366 ),
367 debug_println(9,enable_graph(EnableGraph)).
368
369 determine_dependency_enabling_relations(AllActions,Timeout,FindInvViolations,UseEnableGraph,Depth,EnableGraph) :-
370 determine_dependency_enabling_relations(AllActions,AllActions,Timeout,FindInvViolations,UseEnableGraph,Depth,Edges),
371 (UseEnableGraph = true ->
372 enable_graph: vertices_edges_predicates_to_egraph(AllActions,Edges,EnableGraph)
373 ; % to be removed later (here we just want to compare the graph implementation's performances of enable_graph and ugraph)
374 vertices_edges_to_ugraph(AllActions,Edges,EnableGraph)
375 ).
376
377
378 %determine_dependency_enabling_relations(AllActions,Timeout,FindInvViolations,Depth,EnableGraph) :-
379 % determine_dependency_enabling_relations(AllActions,AllActions,Timeout,FindInvViolations,Depth,Edges),
380 % enable_graph: vertices_edges_predicates_to_egraph(AllActions,Edges,EnableGraph).
381
382 determine_dependency_enabling_relations([],_AllActions,_Timeout,_FindInvViolations,_UseEnableGraph,_Depth,[]).
383 determine_dependency_enabling_relations([Act|Actions],AllActions,Timeout,FindInvViolations,UseEnableGraph,Depth,Edges) :-
384 determine_dependency_enabling_relations1(AllActions,Act,Timeout,FindInvViolations,UseEnableGraph,Depth,Edges1),
385 append(Edges1,Rest,Edges),
386 determine_dependency_enabling_relations(Actions,AllActions,Timeout,FindInvViolations,UseEnableGraph,Depth,Rest).
387
388 determine_dependency_enabling_relations1([],_Act,_Timeout,_FindInvViolations,_UseEnableGraph,_Depth,[]).
389 determine_dependency_enabling_relations1([Act2|Acts],Act1,Timeout,FindInvViolations,UseEnableGraph,Depth,Result) :-
390 ( (Act1==Act2,\+dependent_act(Act1,Act1,_Status,_)) ->
391 assertz(dependent_act(Act1,Act1,self,true)),
392 debug_println(9,dependent_act(Act1,Act1,self,true))
393 ; dependent_actions_symm(Act1,Act2,FindInvViolations,Timeout,Status,Coenabled) ->
394 assertz(dependent_act(Act1,Act2,Status,Coenabled)), % the dependency relation is symmetric
395 assertz(dependent_act(Act2,Act1,Status,Coenabled)),
396 debug_println(9,dependent_act(Act1,Act2,Status,Coenabled))
397 ;
398 true % no new dependencies have been discovered
399 ),
400 (may_enable(Act1,Act2,FindInvViolations,Timeout,UseEnableGraph,Depth,Edge) ->
401 Result = [Edge|Res1]
402 ;
403 Result = Res1
404 ),
405 %compute_if_coenabled(Act1,Act2,FindInvViolations,Timeout),
406 determine_dependency_enabling_relations1(Acts,Act1,Timeout,FindInvViolations,UseEnableGraph,Depth,Res1).
407
408 may_enable(Act1,Act2,FindInvViolations,Timeout,UseEnableGraph,_Depth,Edge) :-
409 enable_analysis(Act1,Act2,FindInvViolations,UseEnableGraph,Timeout,Enable),
410 (memberchk(Enable,[guaranteed,possible,possible_enable]) ->
411 (UseEnableGraph = true ->
412 Edge = Act1-b(truth,pred,[])-Act2
413 ;
414 Edge = Act1-Act2
415 )
416 ; Enable = predicate(Expr) -> Edge = Act1-Expr-Act2
417 ; is_timeout(Enable) -> Edge = Act1-Act2 % assume it is possible to enable Act2
418 ; fail
419 ).
420
421 /*
422 dependent_actions/2 determine statically or dynamically if two actions are dependent
423 two events/actions are syntactically dependent in the following three cases:
424 1. If both events modify at least one common variable.
425 2. Act1 modifies a variable in the guard of Act2. (Act1 can enable or disable Act2)
426 3. Act2 modifies a variable in the guard of Act1. (Act2 can enable or disable Act1)
427 */
428
429 %%% Act1 and Act2 are enabled in current state State,
430 %%% we don't have to check if both actions are enabled in
431 %%% some state
432 dependent_actions_symm(Act1,Act2,_FindInvViolations,_Timeout,Status,Coenabled) :-
433 dependent_act(Act1,Act2,Status,Coenabled),!,fail. % dependent relation is already computed
434 dependent_actions_symm(Act1,Act2,FindInvViolations,Timeout,Status,Coenabled) :-
435 dependent_actions_coenabled(Act1,Act2,FindInvViolations,Timeout,Status,Coenabled).
436
437 dependent_actions_coenabled(Act1,Act2,FindInvViolations,Timeout,Status,Coenabled) :-
438 dependent_actions1(Act1,Act2,FindInvViolations,Timeout,Res),
439 ( Res == '-' -> dependent_actions_coenabled(Act2,Act1,FindInvViolations,Timeout,Status,Coenabled) % Res = '-' : not checked due to symmetry
440 ; Res == syntactic_independent -> fail
441 ; Res == independent -> fail
442 ; Res == self_independent -> fail
443 ;
444 get_dependency_status(Res,Status),
445 check_if_coenabled_nonfailing(Act1,Act2,FindInvViolations,Timeout,Coenabled)
446 ).
447
448 dependent_actions(Act1,Act2,FindInvViolations,Timeout,Status) :-
449 dependent_actions1(Act1,Act2,FindInvViolations,Timeout,Res),
450 ( Res == '-' -> dependent_actions(Act2,Act1,FindInvViolations,Timeout,Status) % Res = '-' : not checked due to symmetry
451 ; Res == syntactic_independent -> fail
452 ; Res == independent -> fail
453 ; Res == self_independent -> fail
454 ; get_dependency_status(Res,Status)).
455
456
457 get_dependency_status(race_dependent,Status) :- !,Status=race.
458 get_dependency_status(action_dependent,Status) :- !,Status=action.
459 get_dependency_status(guard_dependent,Status) :- !,Status=guard.
460 get_dependency_status(guard_dependent(Pred),Status) :- !,Status=predicate(Pred).
461 get_dependency_status(dependent,Status) :- !,Status=general.
462 get_dependency_status(self_dependent,Status) :- !,Status=general. % not sure this is correct
463 get_dependency_status('=',Status) :- !, Status=general.
464 get_dependency_status(DStatus,_) :- add_error_fail(get_dependency_status, 'Unknown dependency status: ', DStatus).
465
466 % currently unused
467 % computes which events are co-enabled
468 % co-enabled relations is reflexive and symmetric
469 %:- dynamic coenabled/2.
470 %compute_if_coenabled(OpName1,OpName2,FindInvViolations,Timeout) :-
471 % (OpName1 == OpName2 ->
472 % assertz(coenabled(OpName1,OpName1))
473 % ;OpName2 @< OpName1 ->
474 % true % due symmetry we skip the computation of coenabled events in that case
475 % ;check_if_coenabled(OpName1,OpName2,FindInvViolations,Timeout) ->
476 % assertz(coenabled(OpName1,OpName2)),
477 % assertz(coenabled(OpName2,OpName1))
478 % ; % both events cannot be co-enabled
479 % true).
480
481 check_if_coenabled_nonfailing(OpName1,OpName2,FindInvViolations,Timeout,Result) :-
482 ? (check_if_coenabled(OpName1,OpName2,FindInvViolations,Timeout) ->
483 Result = true
484 ; Result = false).
485
486 :- use_module(cbcsrc(cbc_path_solver), [testcase_predicate_timeout/3]).
487 check_if_coenabled(OpName1,OpName2,FindInvViolations,Timeout) :-
488 get_guard(OpName1,PosGuard1),
489 get_guard(OpName2,PosGuard2),
490 conjunct_predicates([PosGuard1,PosGuard2],GuardsConj), % both events are enabled
491 (FindInvViolations=1 -> Pred = pred(GuardsConj) ; Pred=typing(GuardsConj)),
492 ? testcase_predicate_timeout(Pred,Timeout,_R).
493
494 /************************** DEPENDENCY RELATION (END) ******************************/
495
496
497 /*
498
499 The meaning of the following comments here is to give an idea how to validate the results from the Enabling analysis.
500 We use here the Linear Time Logic (proposed by Amir Pnueli) in order to give LTL-formulas to each possible table entry result that can prove that
501 the relation results between the operations of machine M produced by the Enabling analysis are correct. For instance,
502 if the Enabling analysis says that it is impossible operation B to be preceded by operation A in the state space of M (i.e. the result in
503 cell (A,B) of the table is 'impossible') then this property can be expressed by the LTL-formula "G ([a] => not X e(b))" and checked by
504 the LTL model checker of ProB.
505
506 * impossible:
507 The impossibility an action 'a' to enable action 'b' can be expressed by means of LTL-formulas as follows:
508 "G ([a] => not X e(b))" (dis)
509
510 If a disables b then (dis) should be satisfied by the model. The result of the enabling analysis
511 returns 'impossible' in cell (a,b) of the Enabling analysis table.
512
513 * guaranteed:
514 Action 'a' guaranteed enables action 'b' if there is an execution in the state space where after 'a' follows 'b' and
515 'a' and 'b' are never enabled simultaneously in the same state:
516 "G ( ([a] => X e(b)) & (not (e(a) & e(b))) )" (en)
517
518 * keep:
519 Action 'a' keeps action 'b' enabled:
520 "(G ((e(b) & [a]) => X e(b))) or (G ((not e(b) & [a]) => X not e(b)))" (keep)
521 */