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