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 :- module(state_space,
6 [get_state_space_stats/3, get_state_space_stats/4,
7 gen_new_state_id/1,
8 history/1, forward_history/1,
9 get_action_trace/1, % old trace/1
10 get_action_trace_with_limit/2,
11 get_action_term_trace/1,
12 op_trace_ids/1, add_to_op_trace_ids/1, remove_from_op_trace_ids/1, reset_op_trace_ids/0,
13 get_state_id_trace/1,
14 current_state_id/1, current_expression/2,
15 set_current_state_id/1,
16 current_options/1, set_current_options/1,
17 get_current_predecessor_state_id/1,
18
19 add_id_at_front/1, add_id_at_end/1,
20 add_id_random/1, /* from state_space_open_nodes_c */
21 add_id_with_weight/2, add_id_to_process/3,
22 pop_id_from_front/1, pop_id_from_end/1, pop_id_oldest/1,
23 retract_open_node/1, open_ids_empty/0,
24 top_front_id/1, top_front_weight/1,
25
26 visited_expression/3, visited_expression/2, visited_expression_id/1,
27 find_hashed_packed_visited_expression/3,
28 retract_visited_expression/2,
29 not_all_transitions_added/1,
30 not_invariant_checked/1, set_invariant_checked/1,
31 invariant_not_yet_checked/1, invariant_still_to_be_checked/1,
32 not_interesting/1, % nodes ignored because they do not satisfy a user-provided scope predicate
33 mark_as_not_interesting/1,
34 max_reached_for_node/1,
35 max_reached_or_timeout_for_node/1,
36 use_no_timeout/1, time_out_for_node/1, time_out_for_node/3,
37 hash_to_id/2,id_to_marker/2, hash_to_nauty_id/2,
38 register_back_edge/2, try_compute_depth_of_state_id/2,
39 invariant_violated/1, time_out_for_invariant/1, time_out_for_assertions/1,
40 set_invariant_violated/1,
41
42 state_error_exists/0, state_error/3, store_state_error/3,
43 set_context_state/1, set_context_state/2,
44 update_context_state/1, clear_context_state/0, get_current_context_state/1,
45 store_error_for_context_state/2,
46 copy_current_errors_to_state/2,
47 store_abort_error_for_context_state_if_possible/4,
48 abort_error_exists_in_context_state/1,
49
50 transition/3,transition/4, any_transition/3,
51 store_transition/4,
52 deadlocked_state/1, % no outgoing edge
53 is_initial_state_id/1, is_concrete_constants_state_id/1,
54 multiple_concrete_constants_exist/0,
55 get_constants_state_for_id/2, get_constants_state_for_id/3,
56 get_constants_state_id_for_id/2,
57 try_get_unique_constants_state/1,
58 get_constants_id_for_state_id/2,
59 get_variables_state_for_id/2,
60 out_degree/2,
61 operation_not_yet_covered/1, operation_name_not_yet_covered/1,
62 get_operation_name_coverage_infos/4,
63 mark_operation_as_covered/1,
64 initialise_operation_not_yet_covered/0,
65
66 transition_info/2, store_transition_infos/2,
67 keep_transition_info/1,
68 compute_transitions_if_necessary/1,
69
70 state_space_initialise/0, state_space_initialise_with_stats/0,
71 state_space_reset/0,
72 state_space_add/2, state_space_packed_add/2,
73 delete_node/1,
74
75 current_state_corresponds_to_initialised_b_machine/0,
76 current_state_corresponds_to_fully_setup_b_machine/0,
77 current_state_corresponds_to_setup_constants_b_machine/0,
78 visited_state_corresponds_to_initialised_b_machine/1,
79 visited_state_corresponds_to_setup_constants_b_machine/1,
80
81 specialized_inv/2, %reuse_operation/4,
82 assert_max_reached_for_node/1, assert_time_out_for_node/3,
83 assert_time_out_for_invariant/1, assert_time_out_for_assertions/1,
84
85 set_max_nr_of_new_impl_trans_nodes/1,
86 get_max_nr_of_new_impl_trans_nodes/1,
87 impl_trans_term/3, impl_trans_term_all/2,
88 impl_trans_id/4, impl_trans_not_complete/1,
89 compute_transitions_if_necessary_saved/1,
90 max_nr_of_new_nodes_limit_not_reached/0,
91
92 find_trace_to_initial_state/2, find_initialised_states/1,
93
94 tcltk_save_state_space/1, tcltk_load_state/1,
95 compute_full_state_space_hash/1,
96
97 execute_id_trace_from_current/3,
98 set_trace_by_transition_ids/1, try_set_trace_by_transition_ids/1,
99 extend_trace_by_transition_ids/1,
100 extract_term_trace_from_transition_ids/2,
101
102 add_counterexample_node/1, add_counterexample_op/1,
103 reset_counterexample/0, set_counterexample_by_transition_ids/1,
104 counterexample_node/1, counterexample_op/1 % specific predicates to register counter examples
105 ]).
106
107 :- use_module(library(lists)).
108
109 :- use_module(self_check).
110 :- use_module(error_manager).
111 :- use_module(gensym).
112 :- use_module(preferences).
113 :- use_module(tools).
114 %:- use_module(state_space_exploration_modes,[compute_hash/3]).
115
116 :- use_module(extension('counter/counter'),
117 [counter_init/0, new_counter/1, get_counter/2, inc_counter/1, inc_counter/2, inc_counter_by/2, reset_counter/1, set_counter/2]).
118
119 :- use_module(module_information).
120 :- module_info(group,state_space).
121 :- module_info(description,'This module keeps track of the visited states by the animator/model checker.').
122
123 % ----------------------------------
124
125 :- load_files(library(system), [when(compile_time), imports([environ/2])]).
126 :- if((environ(prob_myheap,false) ; \+ predicate_property(load_foreign_resource(_), _))).
127 :- use_module(state_space_open_nodes). %% comment in to use only Prolog datastructures
128 :- else.
129 :- use_module(state_space_open_nodes_c). %% comment in to use C++ multimap queue; can make use of HEURISTIC_FUNCTION
130 :- endif.
131
132 % ----------------------------------
133
134 get_state_space_stats(NrNodes,NrTransitions,ProcessedNodes) :-
135 get_counter(states,N), NrNodes is N+1,
136 get_counter(transitions,NrTransitions),
137 get_counter(processed_nodes,ProcessedNodes).
138
139 get_state_space_stats(NrNodes,NrTransitions,ProcessedNodes,IgnoredNodes) :-
140 get_state_space_stats(NrNodes,NrTransitions,ProcessedNodes),
141 get_counter(not_interesting_nodes,IgnoredNodes).
142
143 gen_new_state_id(Nr) :-
144 inc_counter(states,N1), Nr is N1-1. % only one C call
145 %get_counter(states,Nr), inc_counter(states).
146 reset_state_counter :- reset_counter(states).
147 reset_state_counter(Nr) :- set_counter(states,Nr).
148
149 get_state_id_trace(StateIds) :-
150 history(History),
151 current_state_id(CurID),
152 reverse([CurID|History],StateIds).
153
154 get_current_predecessor_state_id(PriorID) :-
155 history([PriorID|_]).
156
157 :- dynamic history/1.
158 history([]).
159
160
161 :- dynamic forward_history/1.
162
163 :- dynamic current_state_id/1.
164 current_state_id(root).
165 /* INITIAL STATE, third arg: clp(fd) constraints as generated
166 by fd_copy_term */
167
168 current_expression(ID,State) :- current_state_id(ID),
169 visited_expression(ID,State).
170 current_packed_expression(ID,State) :- current_state_id(ID),
171 packed_visited_expression(ID,State).
172
173 :- use_module(specfile,[state_corresponds_to_initialised_b_machine/1,
174 state_corresponds_to_fully_setup_b_machine/1,
175 state_corresponds_to_set_up_constants/1]).
176 current_state_corresponds_to_initialised_b_machine :-
177 current_packed_expression(_,PS), unpack_state_top_level(PS,TLState),
178 state_corresponds_to_initialised_b_machine(TLState).
179 visited_state_corresponds_to_initialised_b_machine(ID) :-
180 packed_visited_expression(ID,PS), unpack_state_top_level(PS,TLState),
181 state_corresponds_to_initialised_b_machine(TLState).
182
183 current_state_corresponds_to_fully_setup_b_machine :-
184 current_packed_expression(_,PS), unpack_state_top_level(PS,TLState),
185 state_corresponds_to_fully_setup_b_machine(TLState).
186
187 current_state_corresponds_to_setup_constants_b_machine :-
188 current_packed_expression(_,PS), unpack_state_top_level(PS,TLState),
189 state_corresponds_to_set_up_constants(TLState).
190
191 visited_state_corresponds_to_setup_constants_b_machine(ID) :-
192 packed_visited_expression(ID,PS), unpack_state_top_level(PS,TLState),
193 state_corresponds_to_set_up_constants(TLState).
194
195 :- dynamic current_options/1.
196 current_options([]).
197
198 set_current_options(Options) :-
199 retractall( current_options(_) ),
200 assertz( current_options(Options) ).
201
202 :- dynamic packed_visited_expression/2.
203 %packed_visited_expression(v_0,true).
204
205 :- use_module(state_packing).
206
207 retract_visited_expression(ID,State) :- retract(packed_visited_expression(ID,PState)),
208 unpack_state(PState,State).
209
210 retractall_visited_expression(ID) :- retractall(packed_visited_expression(ID,_)).
211
212 state_space_packed_add(Id,PackedTerm) :- assertz(packed_visited_expression(Id,PackedTerm)).
213
214 state_space_add(Id,Term) :-
215 (pack_state(Term,PackedTerm) -> assertz(packed_visited_expression(Id,PackedTerm))
216 ; add_internal_error('State packing failed: ',pack_state(Term,_)),
217 assertz(packed_visited_expression(Id,Term))).
218
219 % deprecated:
220 visited_expression(ID,State,true) :- visited_expression(ID,State).
221 % not call(CurBody); for the moment we always have true as last argument
222
223 ?visited_expression(A,B) :- packed_visited_expression(A,PB),
224 (unpack_state(PB,R) -> B=R ; add_internal_error('Unpacking state failed: ',unpack_state(PB,R)),R=A).
225
226 %visited_expression_id(A) :- packed_visited_expression(A,_). % avoid unpacking state
227 % even better: not to look up fact at all to avoid constructing state term, this is done below:
228 :- use_module(library(between),[between/3]).
229 visited_expression_id(ID) :- number(ID),!, ID>=0, get_counter(states,N), ID<N.
230 visited_expression_id(ID) :- ID==root,!.
231 visited_expression_id(root).
232 ?visited_expression_id(Nr) :- Nr \== root, get_counter(states,N), N1 is N-1, between(0,N1,Nr).
233
234 % given a hash and a packed state: find ID (fail if does not exist)
235 find_hashed_packed_visited_expression(Hash,PackedState,ID) :-
236 hash_to_id(Hash,ID),
237 (packed_visited_expression(ID,PackedState)
238 -> true /* warning: may instantiate State if not ground */
239 ; print(hash_collision(Hash,ID)),nl,fail
240 ).
241
242
243 :- dynamic not_invariant_checked/1.
244 set_invariant_checked(ID) :- %print(inv_checked(ID)),nl,
245 ? retract(not_invariant_checked(ID)).
246
247 invariant_not_yet_checked(ID) :-
248 not_all_transitions_added(ID) ; /* assumption: if not all transitions added then we haven't checked invariant yet */
249 not_invariant_checked(ID) ;
250 not_interesting(ID). % assumption: if a node is marked as not interesting it will not be examined
251
252 % difference with invariant_not_yet_checked: not interesting nodes not reported and cannot be backtracked
253 invariant_still_to_be_checked(ID) :-
254 (not_all_transitions_added(ID) -> true ; not_invariant_checked(ID) -> true).
255
256 :- dynamic not_interesting/1.
257 %not_interesting(v_0).
258
259 :- dynamic max_reached_for_node/1.
260 /* true if not all outgoing transistions were computed due to the limit
261 on the number of operations/initialisations computed */
262 :- dynamic time_out_for_node/3, use_no_timeout/1, time_out_for_invariant/1, time_out_for_assertions/1.
263
264 time_out_for_node(ID) :- (var(ID) -> visited_expression_id(ID) ; true),
265 (time_out_for_node(ID,_,_) -> true ; fail).
266
267 :- dynamic transition/4.
268 %transition(v_0,a,1,v_1).
269
270 store_transition(Org,Action,Dest,Id) :-
271 %get_counter(transitions,Id), inc_counter(transitions),
272 inc_counter(transitions,Id1), Id is Id1-1, % only one C call
273 assertz(transition(Org,Action,Id,Dest)).
274
275 ?deadlocked_state(Origin) :- \+ any_transition(Origin,_,_).
276
277 is_concrete_constants_state_id(ID) :-
278 ? transition(root,_,ID),
279 packed_visited_expression(ID,concrete_constants(_)).
280
281 % check if we have multiple constant setups
282 multiple_concrete_constants_exist :-
283 ? is_concrete_constants_state_id(ID),
284 ? is_concrete_constants_state_id(ID2), ID2 \= ID,!.
285
286
287 is_initial_state_id(InitialStateID) :-
288 transition(root,_,State),
289 packed_visited_expression(State,P),
290 (P = concrete_constants(_) % also covers '$partial_setup_constants'
291 -> state_space:transition(State,_,InitialStateID)
292 ; InitialStateID=State).
293
294 % get the constants for a state (if there are constants), avoid unpacking variables
295 get_constants_state_for_id(ID,CS) :- get_constants_state_for_id(ID,[],CS).
296 get_constants_state_for_id(ID,Opts,ConstantsState) :-
297 packed_visited_expression(ID,PState),
298 unpack_state_top_level(PState,TLState),
299 (TLState = const_and_vars(CID,_) -> get_constants_state_for_id(CID,[],ConstantsState)
300 ; unpack_state(PState,UPState),
301 (UPState = concrete_constants(CS) -> ConstantsState=CS
302 ; UPState = [_|_], member(allow_variable_list,Opts),
303 ConstantsState=UPState,
304 % could be that we have a state where constants and variables are mixed in a single list
305 % e.g., ProB2's FindStateCommand does currently not create new intermediate constant states
306 add_message(get_constants_state_for_id,'State is a list of bindings and has no reference to a constant valuation: ',ID)
307 )
308 ).
309
310 % get the state id for associated constants state for a state (if there are constants)
311 get_constants_state_id_for_id(ID,CstID) :-
312 packed_visited_expression(ID,PState),
313 unpack_state_top_level(PState,TLState),
314 get_constants_id_for_id_aux(TLState,ID,CstID).
315 get_constants_id_for_id_aux(concrete_constants(_),ID,ID).
316 get_constants_id_for_id_aux(const_and_vars(ID,_),_,ID).
317
318 get_variables_state_for_id(ID,VarState) :-
319 visited_expression(ID,State),
320 get_vars_aux(State,VarState).
321 %get_vars_aux(concrete_constants(ConstantsState),[]).
322 get_vars_aux(const_and_vars(_,Vars),State) :- !, State=Vars.
323 get_vars_aux([],[]).
324 get_vars_aux([H|T],[H|T]).
325
326 % check if there is a unique constants state:
327 try_get_unique_constants_state(ConstantsState) :-
328 transition(root,_,_TransID,DestID),
329 \+ (transition(root,_,_,DestID2), DestID2 \= DestID), % no other transition exists
330 \+ max_reached_or_timeout_for_node(root),
331 DestID \= root, % DestID=root should never happen
332 get_constants_state_for_id(DestID,ConstantsState).
333
334 % returns id of constants state for a state (if it exists)
335 get_constants_id_for_state_id(ID,ConstID) :-
336 packed_visited_expression(ID,'$cst_vars'(ConstID,_)).
337
338 ?any_transition(Origin,TransID,Destination) :- transition(Origin,_,TransID,Destination).
339
340 ?transition(Origin,Action,Destination) :- transition(Origin,Action,_TransID,Destination).
341
342 :- dynamic transition_info/2.
343 store_transition_infos([],_TransId).
344 store_transition_infos([Info|Irest],TransId) :-
345 store_transition_info(Info,TransId),
346 store_transition_infos(Irest,TransId).
347 store_transition_info(Info,TransId) :- %print(info(Info,TransId)),nl,
348 (keep_transition_info(Info)
349 -> assertz(transition_info(TransId,Info))
350 ; true).
351
352 % Do not store path info by default
353 keep_transition_info(path(_)) :- !,fail.
354 keep_transition_info(eventtrace(_)) :- !,preference(eventtrace,true).
355 keep_transition_info(event(_)) :- !,preference(store_event_transinfo,true).
356 keep_transition_info(_). % store everything else
357
358 reset_transition_store :-
359 retractall(transition(_,_,_,_)),
360 retractall(transition_info(_,_)),
361 reset_counter(transitions),
362 reset_counterexample.
363
364 /*
365 Version with packing of transitions:
366 store_transition(Org,Action,Dest,Id) :-
367 retract(transition_counter(Id)),
368 NewId is Id+1,
369 assertz(transition_counter(NewId)),
370 Action =.. [ActionName|Parameters],
371 pack_values(Parameters,PackedParameters),
372 assertz(packed_transition(Org,ActionName,PackedParameters,Id,Dest)).
373
374 transition(Origin,Action,TransID,Destination) :- nonvar(Action),!,
375 Action =.. [ActionName|Parameters],
376 packed_transition(Origin,ActionName,PackedParameters,TransID,Destination),
377 unpack_values(PackedParameters,Parameters).
378 transition(Origin,Action,TransID,Destination) :-
379 packed_transition(Origin,ActionName,PackedParameters,TransID,Destination),
380 unpack_values(PackedParameters,Parameters),
381 Action =.. [ActionName|Parameters].
382 any_transition(Origin,TransID,Destination) :- packed_transition(Origin,_,_,TransID,Destination).
383 */
384
385 % compute out-degree of a node
386 out_degree(ID,OutDegree) :- findall(0, transition(ID,_,_,_), L), length(L,OutDegree).
387
388 ?operation_name_not_yet_covered(OpName) :- operation_not_yet_covered(OpName).
389
390
391 get_operation_name_coverage_infos(PossibleNr,FeasibleNr,UncovNr,UncoveredList) :-
392 findall(ON, specfile:get_possible_event(ON), Possible), length(Possible,PossibleNr),
393 findall(OF, specfile:get_feasible_event(OF), Feasible), length(Feasible,FeasibleNr),
394 findall(OpName, state_space: operation_name_not_yet_covered(OpName), UncoveredList),
395 length(UncoveredList,UncovNr).
396
397
398 :- dynamic operation_not_yet_covered/1.
399 %operation_not_yet_covered(b).
400
401 :- use_module(probsrc(debug),[formatsilent/2]).
402 mark_operation_as_covered(OpName) :-
403 (retract(operation_not_yet_covered(OpName))
404 -> (preferences:get_preference(provide_trace_information,true)
405 -> formatsilent('Covered ~w~n',[OpName])
406 ; true),
407 ? (operation_not_yet_covered(_) -> true ; formatsilent('~nALL OPERATIONS COVERED~n',[]))
408 ; true
409 ).
410
411
412 :- use_module(bmachine,[b_top_level_operation/1]).
413 :- use_module(debug,[debug_println/1]).
414 :- use_module(probcspsrc(haskell_csp),[channel/2]).
415 initialise_operation_not_yet_covered :- retractall(operation_not_yet_covered(_)),
416 b_or_z_mode,
417 ? b_top_level_operation(Name),
418 % b_get_machine_operation(Name,_,Par,_), length(Par,Arity), functor(Op,Name,Arity),
419 % Note: no '-->' added
420 assertz(operation_not_yet_covered(Name)),
421 debug_println(operation_not_yet_covered(Name)),
422 fail.
423 /* Missing: treat operations with return values */
424 initialise_operation_not_yet_covered :- csp_mode, \+ csp_with_bz_mode,
425 ? channel(Name,_),
426 assertz(operation_not_yet_covered(Name)),
427 debug_println(operation_not_yet_covered(Name)),
428 fail.
429 initialise_operation_not_yet_covered.
430
431 state_error_exists :- state_error(_,_,_),!.
432 :- dynamic state_error/3.
433
434 %state_error([],invariant_violated).
435
436 reset_next_state_error_id_counter :- reset_counter(next_state_error_id).
437 :- use_module(tools_printing, [print_error/1, format_error_with_nl/2]).
438 :- use_module(error_manager,[print_error_span/1]).
439 store_state_error(State,Error,Id) :- state_error(State,Id,Error),!. % do not store identical error twice
440 store_state_error(State,Error,Id) :-
441 %retract( next_state_error_id(Id) ),
442 inc_counter(next_state_error_id,Id),
443 % tools_printing:print_term_summary(Error),nl, tools_printing:nested_print_term(Error),nl,
444 assertz( state_error(State,Id,Error) ).
445 store_error_for_context_state(Error,Id) :-
446 ( context_state(State,Errs) ->
447 (Errs<25
448 -> store_state_error(State,Error,Id), E1 is Errs+1,
449 %assertz(context_state(State,E1))
450 set_context_number_of_errors(E1)
451 ; store_state_error(State,max_state_errors_reached(25),Id)
452 )
453 ;
454 add_internal_error('No known context when calling store_error_for_context_state: ',store_error_for_context_state(Error,Id)),
455 fail).
456
457 % check if we already have a certain type of error in the current context state
458 abort_error_exists_in_context_state(ErrType) :- get_current_context_state(State),
459 Error = abort_error(ErrType,_Msg,_Term,_Pos),
460 state_error(State,_Id,Error).
461
462 % copy current errors from error_manager to state errors
463 copy_current_errors_to_state(StateID,Context) :-
464 % error_manager:logged_error(Source,ErrMsg,_Context,Span), % will not retract
465 error_manager:get_error_with_span(Source,ErrMsg,Span), % will retract
466 store_state_error(StateID,abort_error(Source,ErrMsg,'',span_context(Span,Context)),SID),
467 % TO DO: use other error class
468 debug_println(stored(Source,SID,_Context,ErrMsg)),
469 fail.
470 copy_current_errors_to_state(_,_).
471
472 store_abort_error_for_context_state_if_possible(ErrType,Msg,Term,Span) :-
473 %print(store(Msg,Term,Span)),nl,
474 ( get_current_context_state(State) ->
475 error_manager:get_error_context(Context),
476 (abort_error_for_same_location_exists(State,Id1,ErrType,Msg,Span),
477 abort_error_for_same_location_exists(State,Id2,ErrType,Msg,Span),
478 Id2>Id1
479 -> /* two errors of same type, for same state and same source location exists */
480 /* TO DO: maybe merge state errors */
481 simplify_span(Span,Span1),
482 compress_span(Span1,Span2),
483 store_state_error(State,abort_error(ErrType,'Further identical errors occurred (not stored !)',Term,span_context(Span2,Context)),_)
484 ;
485 format_error_with_nl('! An error occurred in state ~w: ~w !',[State,ErrType]),
486 % usual errors: precondition_error, while_invariant_violation, while_variant_error,
487 % assert_error, well_definedness_error, card_overflow_error
488 print_error(Msg),
489 print_error_term(Term,Span),
490 % print_error(context_state_id(State)), % printed by print_error_context
491 print_error_context,
492 (debug_mode(on),visited_expression(State,S) -> translate:translate_bstate(S,O),print_error(O) ; true),
493 compress_span(Span,Span2),
494 print_error_span(Span2),
495 store_state_error(State,abort_error(ErrType,Msg,Term,span_context(Span2,Context)),_)
496 ),
497 (add_new_event_in_error_scope(abort_error(ErrType)) -> true ; true), % should we use well_definedness_error?
498 assert_real_error_occurred(abort_error) % Note that in this case the error manager list of errors maybe empty even though real_error_occured is true. (see ProB2 kernel test de.prob.cli.integration.rules.RulesMachineTest > testReuseStateSpace)
499 ; % no current context_state exists:
500 compress_span(Span,Span2),
501 add_error(ErrType,Msg,Term,Span2)
502 ).
503
504
505 :- use_module(bsyntaxtree, [find_identifier_uses/3]).
506 compress_span(span_context(Span,C),span_context(CS,C)) :- !,
507 compress_span(Span,CS).
508 compress_span(pos_context(Span1,C,Span2),pos_context(CS1,C,CS2)) :- !,
509 compress_span(Span1,CS1),
510 compress_span(Span2,CS2).
511 compress_span(span_predicate(Pred,LS,S),Res) :- find_identifier_uses(Pred,[],Ids),
512 sort(Ids,SIds),
513 filter_state(LS,SIds,FLS),
514 filter_state(S,SIds,FS), % TODO: do we need to store the global state? we can reconstruct it ?
515 % format('Compressed span_predicate (~w)~n',[Ids]),
516 !,
517 Res = span_predicate(Pred,FLS,FS).
518 compress_span(S,S).
519 % avoid storing large useless values
520 % TO DO: probably we should stop storing spans when a certain threshold of number of errors is reached
521
522
523 :- use_module(library(ordsets),[ord_member/2]).
524 filter_state([],_,[]).
525 filter_state([bind(ID,L)|T],Vars,Res) :-
526 (ord_member(ID,Vars) -> Res = [bind(ID,L)|RT] ; Res=RT),
527 filter_state(T,Vars,RT).
528
529
530 :- use_module(translate, [translate_error_term/3]).
531 print_error_term(T,S) :- (var(T);var(S)),!,
532 print_error('### VARIABLE error term or span:'), print_error(print_error_term(T,S)).
533 print_error_term(Term,Span) :- translate_error_term(Term,Span,S),
534 (S='' -> true ; print_error(S)).
535
536 abort_error_for_same_location_exists(State,Id,ErrType,Msg,Span) :-
537 ? state_error(State,Id,abort_error(ErrType,Msg,_Term2,span_context(Span2,_Ctxt2))),
538 same_span_location(Span2,Span).
539 % should be moved to error_manager ?
540 same_span_location(span_context(Span1,C),span_context(Span2,C)) :- !, same_span_location(Span1,Span2).
541 same_span_location(pos_context(Span1,C,_),pos_context(Span2,C,_)) :- !,
542 same_span_location(Span1,Span2). % should we check second span?
543 same_span_location(span_predicate(Pred1,_,_),span_predicate(Pred2,_,_)) :- !,Pred1=Pred2.
544 same_span_location(X,X).
545
546 :- dynamic saved_nested_context_state/2.
547 save_nested_context_state(_S) :-
548 bb_get(state_space_context_state,ID),
549 bb_get(state_space_context_errors,Errs),!,
550 %print(saving_context_state(_S,ID,Errs)),nl,
551 asserta(saved_nested_context_state(ID,Errs)).
552 save_nested_context_state(_).
553
554 % actually pops context state
555 clear_context_state :-
556 ? retract(saved_nested_context_state(ID,Errs)),!, %print(restoring_nested(ID,Errs)),nl,
557 bb_put(state_space_context_state,ID),
558 bb_put(state_space_context_errors,Errs).
559 clear_context_state :-
560 (bb_delete(state_space_context_state,_) -> true ; true).
561 %(retract(context_state(_,_)) -> true ; true). % retractall seems to be slowing down with use
562
563 % Note: Each Prolog module maintains its own blackboard for bb_get/bb_put
564 context_state(ID,Errs) :-
565 bb_get(state_space_context_state,ID), bb_get(state_space_context_errors,Errs).
566
567 % sets a new context state; pushing the previous one if necessary
568 set_context_state(State) :- %print(set_id(State)),nl,
569 save_nested_context_state(State),
570 bb_put(state_space_context_state,State),
571 bb_put(state_space_context_errors,0).
572
573 set_context_state(State,_Context) :- % Context can be used for debugging later
574 set_context_state(State).
575
576 % update current context state, without storing nested states
577 update_context_state(State) :-
578 bb_put(state_space_context_state,State),
579 bb_put(state_space_context_errors,0).
580
581 get_current_context_state(ID) :- bb_get(state_space_context_state,ID).
582 %get_current_context_state(ID) :- context_state(ID,_).
583
584 set_context_number_of_errors(Errs) :- bb_put(state_space_context_errors,Errs).
585
586 retractall_invariant_violated(State) :-
587 retractall(state_error(State,_,invariant_violated)).
588 invariant_violated(State) :-
589 ? state_error(State,_,invariant_violated).
590 set_invariant_violated(State) :-
591 ( invariant_violated(State) -> true
592 ; time_out_for_invariant(ID) -> print('Timeout for node: '), print(ID),nl,
593 print('Not setting invariant violation status'),nl
594 ; store_state_error(State,invariant_violated,_)
595 ).
596
597 %:- set_invariant_violated([]). % why is this ??
598
599
600 :- dynamic hash_to_id/2.
601 :- dynamic id_to_marker/2.
602 :- dynamic id_back_edge/3. % optional facts to keep track where a state was constructed from
603
604 :- dynamic hash_to_nauty_id/2. % used in nauty mode to map nauty id's to hash values
605
606 :- dynamic specialized_inv/2. /* stores whether for a node a specialized invariant
607 version could be computed */
608
609 % :- dynamic reuse_operation/4. /* when for a state and given operation name we can reuse the operation computed for another state */
610 % used to be used for OPERATION_REUSE TRUE
611
612 :- use_module(hashing).
613 state_space_startup :- % call once at startup to ensure all counters exist
614 counter_init,
615 new_counter(states), new_counter(processed_nodes), new_counter(transitions),
616 new_counter(next_state_error_id),
617 new_counter(not_interesting_nodes),
618 reset_open_ids. % also calls myheap init
619 state_space_initialise :- counter_init, reset_gennum, reset_gensym,
620 new_counter(states), new_counter(processed_nodes), new_counter(transitions),
621 new_counter(next_state_error_id), new_counter(not_interesting_nodes),
622 reset_state_counter, reset_processed_nodes_counter, reset_next_state_error_id_counter,
623 retractall_visited_expression(_),
624 reset_open_ids,
625 reset_stored_values, % state_packing
626 retractall(not_invariant_checked(_)),
627 reset_not_interesting,
628 retractall(max_reached_for_node(_)),
629 retractall(time_out_for_node(_,_,_)),
630 retractall(time_out_for_invariant(_)),
631 retractall(time_out_for_assertions(_)),
632 retractall(use_no_timeout(_)),
633 retractall(state_error(_,_,_)),
634 clear_context_state,
635 reset_transition_store,
636 retractall(operation_not_yet_covered(_)),
637 retractall(hash_to_id(_,_)),
638 retractall(id_back_edge(_,_,_)),
639 retractall(hash_to_nauty_id(_,_)),
640 retractall(id_to_marker(_,_)),
641 retractall(specialized_inv(_,_)),
642 %retractall(reuse_operation(_,_,_,_)),
643 state_space_add(root,root),
644 add_id_at_front(root),
645 my_term_hash(root,RootHash),
646 assertz(hash_to_id(RootHash,root)),
647 %assertz(not_invariant_checked(root)),
648 state_space_reset.
649
650 :- use_module(eventhandling,[register_event_listener/3]).
651 :- register_event_listener(startup_prob,state_space_startup,
652 'Initialise Statespace Counters.').
653 :- register_event_listener(reset_specification,state_space_initialise,
654 'Reset Statespace.').
655 :- register_event_listener(change_of_animation_mode,state_space_initialise,
656 'Reset Statespace.').
657 :- register_event_listener(specification_initialised,initialise_operation_not_yet_covered,
658 'Init coverage info.').
659 :- register_event_listener(reset_prob,state_space_initialise,
660 'Reset Statespace.').
661
662 /* A version of reset which checks how much memory is used by each fact */
663 /* state_space:init_with_stats */
664 state_space_initialise_with_stats :-
665 reset_gennum, reset_gensym, reset_state_counter, reset_processed_nodes_counter,
666 reset_next_state_error_id_counter,
667 ? retract_open_ids_with_statistics,
668 ? retract_with_statistics(state_space,[packed_visited_expression(_,_),
669 not_invariant_checked(_),
670 not_interesting(_),
671 max_reached_for_node(_),
672 time_out_for_node(_,_,_),
673 time_out_for_invariant(_),
674 time_out_for_assertions(_),
675 use_no_timeout(_),
676 state_error(_,_,_),
677 transition(_,_,_,_),
678 transition_info(_,_),
679 operation_not_yet_covered(_),
680 hash_to_id(_,_),
681 hash_to_nauty_id(_,_),
682 id_to_marker(_,_),
683 specialized_inv(_,_),
684 %reuse_operation(_,_,_,_),
685 history(_), forward_history(_), op_trace_ids(_)]),
686 reset_not_interesting,
687 ? retract_stored_values_with_statistics,
688 clear_context_state,
689 reset_transition_store,
690 state_space_add(root,root),
691 add_id_at_front(root),
692 %assertz(not_invariant_checked(root)),
693 state_space_reset,
694 initialise_operation_not_yet_covered.
695
696
697
698 :- dynamic op_trace_ids/1.
699 reset_trace :- retractall(op_trace_ids(_)), assertz(op_trace_ids([])).
700 get_action_trace(T) :- trace(T).
701 get_action_term_trace(PT) :- get_action_trace_with_limit(0,T), project_on_action_term(T,PT).
702 trace(Trace) :- get_action_trace_with_limit(500,Trace).
703 get_action_trace_with_limit(Limit,Trace) :-
704 op_trace_ids(IDT), reverse(IDT,RIDT),
705 extract_trace_from_transition_ids(RIDT,root,Limit,[],Trace).
706
707 reset_op_trace_ids :- retractall(op_trace_ids(_)), assertz(op_trace_ids([])).
708 add_to_op_trace_ids(OpID) :- retract(op_trace_ids(OpIDS)), assertz(op_trace_ids([OpID|OpIDS])).
709 remove_from_op_trace_ids(OpID) :- retract(op_trace_ids(OpIDS)),
710 (OpIDS = [R|Rest]
711 -> assertz(op_trace_ids(Rest)), OpID = R
712 ; assertz(op_trace_ids(OpIDS)), fail).
713
714 % translate a list of transition ids (from root) into a list of operation terms
715 extract_term_trace_from_transition_ids(TransIDListFromRoot,Trace) :-
716 extract_trace_from_transition_ids(TransIDListFromRoot,root,0,[],ActionTrace),
717 reverse_and_project_on_action_term(ActionTrace,[],Trace).
718
719 reverse_and_project_on_action_term([],A,A).
720 reverse_and_project_on_action_term([action(_,Term)|T],Acc,Res) :- !,
721 reverse_and_project_on_action_term(T,[Term|Acc],Res).
722 reverse_and_project_on_action_term([H|T],Acc,Res) :-
723 add_error(reverse_and_project_on_action_term,'Illegal action: ',H),
724 reverse_and_project_on_action_term(T,[H|Acc],Res).
725
726 project_on_action_term([],[]).
727 project_on_action_term([action(_,Term)|T],Res) :- !, Res=[Term|TR],
728 project_on_action_term(T,TR).
729 project_on_action_term([H|T],Res) :-
730 add_error(project_on_action_term,'Illegal action: ',H),
731 project_on_action_term(T,Res).
732
733 extract_trace_from_transition_ids([],_CurrentState,_,Trace,Trace).
734 extract_trace_from_transition_ids([TransId|Rest],CurrentState,Limit,AccTrace,Trace) :-
735 compute_op_string(TransId,CurrentState,Limit,OpTerm,OpString,DestState),!,
736 extract_trace_from_transition_ids(Rest,DestState,Limit,
737 [action(OpString,OpTerm)|AccTrace],Trace).
738 extract_trace_from_transition_ids([TransId|_],CurrentState,_,_,_Trace) :-
739 add_error(state_space,'Could not execute transition id: ', TransId:from(CurrentState)),fail.
740
741 :- use_module(translate,[translate_event_with_src_and_target_id/5]).
742 compute_op_string(jump(TO),_CurID,_,Term,String,DestID) :- !, Term=jump,String=jump,DestID=TO.
743 compute_op_string(TransId,CurID,Limit,Term,String,DestID) :- transition(CurID,Term,TransId,DestID),
744 translate_event_with_src_and_target_id(Term,CurID,DestID,Limit,String).
745
746 % reset history and forward history, but not state-space itself
747 state_space_reset :-
748 reset_trace,
749 retractall(history(_)),
750 retractall(forward_history(_)),
751 retractall(current_state_id(_)),
752 retractall(current_options(_)),
753 assertz(history([])),
754 assertz(current_state_id(root)).
755
756 reset_not_interesting :- retractall(not_interesting(_)), reset_counter(not_interesting_nodes).
757
758 mark_as_not_interesting(ID) :- assertz(not_interesting(ID)), inc_counter(not_interesting_nodes).
759
760 set_current_state_id(ID) :- (retract(current_state_id(_)) -> true ; true),
761 assertz(current_state_id(ID)).
762
763 state_space_clean_all :-
764 retractall(state_space_version_in_file(_)),
765 retractall_visited_expression(_),
766 reset_open_ids,
767 retractall(not_invariant_checked(_)),
768 reset_not_interesting,
769 retractall(max_reached_for_node(_)),
770 retractall(time_out_for_node(_,_,_)),
771 retractall(time_out_for_invariant(_)),
772 retractall(time_out_for_assertions(_)),
773 retractall(use_no_timeout(_)),
774 retractall(state_error(_,_,_)),
775 clear_context_state,
776 reset_transition_store,
777 retractall(operation_not_yet_covered(_)),
778 retractall(hash_to_id(_,_)),
779 retractall(id_back_edge(_,_,_)),
780 retractall(hash_to_nauty_id(_,_)),
781 retractall(id_to_marker(_,_)),
782 retractall(specialized_inv(_,_)),
783 %retractall(reuse_operation(_,_,_,_)),
784 retractall(history(_)),
785 retractall(forward_history(_)),
786 retractall(op_trace_ids(_)),
787 retractall(current_state_id(_)),
788 retractall(current_options(_)).
789
790 % this is only used from within the Tcl/Tk animator at the moment:
791 delete_node(ID) :- print(deleting(ID)),nl,
792 retractall_visited_expression(ID),
793 retractall_invariant_violated(ID),
794 retract_open_node_and_update_processed_nodes(ID),
795 retractall(not_invariant_checked(ID)),
796 (retract(not_interesting(ID)) -> inc_counter_by(not_interesting_nodes,-1) ; true),
797 retractall(max_reached_for_node(ID)),
798 retractall(time_out_for_node(ID,_,_)),
799 retractall(time_out_for_invariant(ID)),
800 retractall(time_out_for_assertions(ID)),
801 retractall(use_no_timeout(ID)),
802 retractall(state_error(ID,_,_)),
803 retractall(transition(ID,_,_,_)),
804 % to do: check if operation_not_yet_covered(_) changes
805 retract_hash(ID),
806 retractall(id_to_marker(ID,_)).
807
808 retract_hash(ID) :- retract(hash_to_id(Hash,ID)), retractall(hash_to_nauty_id(_TermHash,Hash)),fail.
809 retract_hash(_).
810
811 assert_max_reached_for_node(Id) :- %print_message(max_reached_for_node(Id)),
812 (max_reached_for_node(Id) -> true ; assertz(max_reached_for_node(Id))).
813
814 :- use_module(probsrc(debug),[debug_mode/1]).
815 assert_time_out_for_node(Id,OpName,TypeOfTimeOut) :-
816 (debug_mode(off),functor(TypeOfTimeOut,virtual_time_out,_) -> true % can easily happen when parameters are unbounded
817 ; print_message(time_out_for_node(Id,OpName,TypeOfTimeOut))),
818 (time_out_for_node(Id,OpName,_) -> true ; assertz(time_out_for_node(Id,OpName,TypeOfTimeOut))).
819 assert_time_out_for_invariant(Id) :- print_message(time_out_for_invariant(Id)),
820 (time_out_for_invariant(Id) -> true ; assertz(time_out_for_invariant(Id))).
821 assert_time_out_for_assertions(Id) :- print_message(time_out_for_assertions(Id)),
822 (time_out_for_assertions(Id) -> true ; assertz(time_out_for_assertions(Id))).
823
824 max_reached_or_timeout_for_node(Id) :-
825 ? (max_reached_for_node(Id) ; time_out_for_node(Id,_,_)).
826 /* ---------------------- */
827 /* state space saving */
828 /* ---------------------- */
829
830 :- dynamic state_space_version_in_file/1. %
831 state_space_version(1).
832
833 check_state_space_version :- state_space_version(V),
834 (state_space_version_in_file(F) -> true ; F=0),
835 (V>F -> add_message(state_space,'Warning: saved state_space may be incompatible with current version: ',F:V) ; true).
836
837 % save all infos of state space (transitions, evaluated invariants, ...)
838 tcltk_save_state_space(File) :-
839 print('% saving full state space to: '), print(File),nl,
840 open(File,write,Stream,[encoding(utf8)]),
841 print_state_space(Stream),
842 close(Stream),
843 print_message(done).
844
845
846 :- use_module(tools_printing, [print_dynamic_fact/2,print_dynamic_pred/4]).
847 print_state_space(Stream) :-
848 state_space_version(V),
849 print_dynamic_fact(Stream,state_space_version_in_file(V)),
850 % TO DO: maybe also save some important preferences, and warn user and/or propose to adapt preferences ?
851 print_dynamic_pred(Stream,state_space,history,1),
852 print_dynamic_pred(Stream,state_space,forward_history,1),
853 print_dynamic_pred(Stream,state_space,op_trace_ids,1),
854 print_dynamic_pred(Stream,state_space,current_state_id,1),
855 print_dynamic_pred(Stream,state_space,current_options,1),
856 print_dynamic_pred(Stream,state_space,packed_visited_expression,2),
857 print_dynamic_pred(Stream,state_space,not_invariant_checked,1),
858 print_dynamic_pred(Stream,state_space,not_interesting,1),
859 print_dynamic_pred(Stream,state_space,max_reached_for_node,1),
860 print_dynamic_pred(Stream,state_space,time_out_for_node,3),
861 print_dynamic_pred(Stream,state_space,use_no_timeout,1),
862 print_dynamic_pred(Stream,state_space,transition,4),
863 print_dynamic_pred(Stream,state_space,transition_info,2),
864 print_dynamic_pred(Stream,state_space,operation_not_yet_covered,1),
865 print_dynamic_pred(Stream,state_space,state_error,3),
866 print_state_space_open_nodes(Stream),
867 print_stored_values(Stream),
868 get_counter(states,X),
869 write_term(Stream,saved_gennum_count(X),[quoted(true)]),write(Stream,'.'),nl(Stream).
870
871 saved_gennum_count(99999).
872
873 /* ---------------------- */
874 /* state space loading */
875 /* ---------------------- */
876
877 tcltk_load_state(File) :- state_space_clean_all,
878 print('Loading: '), print(File),nl,
879 user_consult_without_redefine_warning(File), % this will read in bind_skeleton/2, ..., next_value_id/1
880 check_state_space_version,
881 print('Generating open node info'),nl,
882 transfer_open_node_info,
883 print('Transfer state packing info'),nl,
884 transfer_state_packing_info,
885 print('Recomputing hash index'),nl,
886 recompute_all_hash,
887 (saved_gennum_count(X) -> reset_state_counter(X) ; true),
888 reset_processed_nodes_counter, % TO DO: restore or save it
889 reset_next_state_error_id_counter, % DITTO
890 print('Done'),nl,!.
891 tcltk_load_state(File) :-
892 add_error(tcltk_load_state,'Could not load state from file: ',File),
893 state_space_initialise.
894
895 :- dynamic not_all_z_saved/1, not_all_transitions_added_saved/1.
896 :- dynamic bind_skeleton/2, stored_value/2, stored_value_hash_to_id/2, next_value_id/1.
897
898 % transfer facts read into state_space into other modules:
899 transfer_open_node_info :- retract(not_all_z_saved(X)), %print(not_all_z(X)),nl,
900 assert_not_all_z(X),fail.
901 transfer_open_node_info :- retract(not_all_transitions_added_saved(X)),
902 assert_not_all_transitions_added(X),fail.
903 transfer_open_node_info.
904 % now for transferring to state_packing module info generated by print_stored_values
905 transfer_state_packing_info :- retract(bind_skeleton(X,Y)), %print(skel(X)),nl,
906 assertz(state_packing:bind_skeleton(X,Y)),fail.
907 transfer_state_packing_info :- retract(stored_value(X,Y)),
908 assertz(state_packing:stored_value(X,Y)),fail.
909 transfer_state_packing_info :- retract(stored_value_hash_to_id(X,Y)),
910 assertz(state_packing:stored_value_hash_to_id(X,Y)),fail.
911 transfer_state_packing_info :- retract(next_value_id(X)),
912 state_packing:set_next_value_id(X),fail.
913 transfer_state_packing_info.
914
915 recompute_all_hash :-
916 retractall(hash_to_id(_,_)),retractall(id_to_marker(_,_)),
917 retractall(hash_to_nauty_id(_,_)),
918 ? visited_expression(ID,StateTemplate),
919 state_space_exploration_modes:compute_hash(StateTemplate,Hash,Marker),
920 assertz(hash_to_id(Hash,ID)),
921 assertz(id_to_marker(ID,Marker)),
922 fail.
923 recompute_all_hash.
924
925 :- use_module(hashing,[my_term_hash/2]).
926 % generates a hash for the entire state space not depending on the order in which states where added
927 compute_full_state_space_hash(Hash) :-
928 %listing(hash_to_id/2), listing(packed_visited_expression/2),
929 findall(Hash,hash_to_id(Hash,_),ListOfHashCodes),
930 sort(ListOfHashCodes,SortedList),
931 my_term_hash(SortedList,Hash).
932 % TO DO: also provide transition hashes
933
934 :- use_module(tools_meta,[safe_on_exception/3]).
935 user_consult_without_redefine_warning(File) :-
936 get_set_optional_prolog_flag(redefine_warnings, Old, off),
937 get_set_optional_prolog_flag(single_var_warnings, Old2, off),
938 (safe_on_exception(Exc,
939 %consult(File), %
940 load_files([File], [load_type(source),compilation_mode(consult),encoding(utf8)]),
941 (nl,print('Exception occurred:'),print(Exc),nl,fail))
942 -> OK=true ; OK=false),
943 get_set_optional_prolog_flag(redefine_warnings, _, Old),
944 get_set_optional_prolog_flag(single_var_warnings, _, Old2),
945 OK=true.
946
947
948
949 execute_id_trace_from_current(ID,OpIDL,StateIDList) :-
950 current_state_id(CurID),
951 reverse([CurID|StateIDList],Rev),
952 Rev = [Dest|TRev], (Dest==ID -> true ; print(not_eq(Dest,ID)),nl),
953 retract(history(H)),
954 update_forward_history(OpIDL), % check if OpIDL conforms to forward history and keep it
955 append(TRev,H,NewH),
956 assertz(history(NewH)),
957 retract(op_trace_ids(OldTrace)),
958 reverse(OpIDL,NewTrace),
959 append(NewTrace,OldTrace,Trace),
960 assertz(op_trace_ids(Trace)),
961 retractall(current_state_id(_)),
962 assertz(current_state_id(ID)).
963 %execute_trace_to_node(OpL,StateIDList). /* <----- BOTTLENECK FOR LONG SEQUENCES */
964 %generate_trace([],Acc,Acc).
965 %generate_trace([OpTerm|T],Acc,Res) :-
966 % translate:translate_event(OpTerm,OpString),
967 % generate_trace(T,[action(OpString,OpTerm)|Acc],Res).
968
969 update_forward_history(TransitionIds) :-
970 (retract(forward_history(Forward)),
971 prune_forward_history(TransitionIds,Forward,NewForward)
972 -> assert(forward_history(NewForward))
973 ; true).
974 % try and prune forward history if it matches operation trace
975 prune_forward_history([],ForwardHistory,ForwardHistory).
976 prune_forward_history([TransID|T],[forward(_,TransID)|TF],Res) :-
977 prune_forward_history(T,TF,Res).
978
979 try_set_trace_by_transition_ids(TransIds) :-
980 (set_trace_by_transition_ids(TransIds) -> true
981 ; add_internal_error('Call failed:',set_trace_by_transition_ids(TransIds))).
982
983 set_trace_by_transition_ids(TransitionIds) :-
984 extract_history_from_transition_ids(TransitionIds,root,[],[],Last,History,OpTrace),
985 %visited_expression(Last,LastState,LastCond),
986 retractall(history(_)),
987 retractall(forward_history(_)), % TODO: we could try and recover a new forward history if transition ids match current history^forward history
988 update_forward_history(TransitionIds),
989 retractall(current_state_id(_)),
990 retractall(op_trace_ids(_)),
991 assertz(history(History)),
992 assertz(op_trace_ids(OpTrace)),
993 assertz(current_state_id(Last)).
994
995
996 extract_history_from_transition_ids([],CurrentState,History,Trace,CurrentState,History,Trace).
997 extract_history_from_transition_ids([TransId|Rest],CurrentState,AccHist,AccTrace,Last,History,Trace) :-
998 transition(CurrentState,_,TransId,DestState),!,
999 extract_history_from_transition_ids(Rest,DestState,[CurrentState|AccHist],
1000 [TransId|AccTrace],Last,History,Trace).
1001 extract_history_from_transition_ids([skip|Rest],CurrentState,AccHist,AccTrace,Last,History,Trace) :- !,
1002 extract_history_from_transition_ids(Rest,CurrentState,AccHist,AccTrace,Last,History,Trace).
1003 extract_history_from_transition_ids([TransId|_],CurrentState,_,_,_,_,_Trace) :-
1004 add_error(state_space,'Could not execute transition id: ', TransId:from(CurrentState)),fail.
1005
1006 % extend trace from current state
1007 extend_trace_by_transition_ids(TransitionIds) :-
1008 current_state_id(CurID),
1009 history(OldH), op_trace_ids(OldOT),
1010 extract_history_from_transition_ids(TransitionIds,CurID,OldH,OldOT,Last,History,OpTrace),
1011 retractall(history(_)), retractall(forward_history(_)),
1012 retractall(current_state_id(_)),
1013 retractall(op_trace_ids(_)),
1014 assertz(history(History)),
1015 assertz(op_trace_ids(OpTrace)),
1016 assertz(current_state_id(Last)).
1017
1018 /* --------------------------------- */
1019 :- dynamic max_nr_of_new_nodes/1.
1020
1021 % negative number or non-number signifies no limit
1022 set_max_nr_of_new_impl_trans_nodes(MaxNrOfNewNodes) :-
1023 retractall(max_nr_of_new_nodes(_)),
1024 (number(MaxNrOfNewNodes), MaxNrOfNewNodes>=0
1025 -> assertz(max_nr_of_new_nodes(MaxNrOfNewNodes))
1026 ; true). % no need to store limit; we will explore as much as needed
1027
1028 get_max_nr_of_new_impl_trans_nodes(MaxNrOfNewNodes) :-
1029 (max_nr_of_new_nodes(Max) -> MaxNrOfNewNodes=Max; MaxNrOfNewNodes = 0).
1030
1031 % used e.g., in refinement or ltl checker
1032 impl_trans_term(From,ActionAsTerm,To) :-
1033 compute_transitions_if_necessary_saved(From),
1034 ? transition(From,ActionAsTerm,_TID,To).
1035
1036 % a variation also giving the transition id:
1037 impl_trans_id(From,ActionAsTerm,TransitionID,To) :-
1038 compute_transitions_if_necessary_saved(From),
1039 ? transition(From,ActionAsTerm,TransitionID,To).
1040
1041 impl_trans_term_all(From,Ops) :-
1042 compute_transitions_if_necessary_saved(From),
1043 findall(op(Id,ActionAsTerm,To),
1044 transition(From,ActionAsTerm,Id,To),
1045 Ops).
1046
1047 % true if e.g., a time-out occurred during computation of all transitions
1048 impl_trans_not_complete(From) :- max_reached_or_timeout_for_node(From).
1049
1050 compute_transitions_if_necessary_saved(From) :-
1051 catch(
1052 compute_transitions_if_necessary(From),
1053 error(forced_interrupt_error('User has interrupted the current execution'),_),
1054 user_interrupts:process_interrupted_error_message).
1055
1056 :- use_module(tcltk_interface,[compute_all_transitions_if_necessary/2]).
1057 compute_transitions_if_necessary(From) :-
1058 not_all_transitions_added(From),!,
1059 decrease_max_nr_of_new_nodes(From),
1060 compute_all_transitions_if_necessary(From,false).
1061 compute_transitions_if_necessary(_From).
1062
1063 decrease_max_nr_of_new_nodes(ID) :-
1064 retract(max_nr_of_new_nodes(Max)),!,
1065 ( Max>0 ->
1066 NewMax is Max-1,
1067 assertz(max_nr_of_new_nodes(NewMax))
1068 ; Max=0 -> NM is -1,
1069 assertz(max_nr_of_new_nodes(NM)),
1070 add_warning(state_space,'Maximum number of new nodes reached for CTL/LTL/refinement check, node id = ',ID),
1071 fail
1072 ; % negative number: re-assert and fail
1073 assertz(max_nr_of_new_nodes(Max)),
1074 fail).
1075 decrease_max_nr_of_new_nodes(_). % no limit stored; just proceed
1076
1077 % will be called from TCL/TK side
1078 max_nr_of_new_nodes_limit_not_reached :-
1079 max_nr_of_new_nodes(N),N>0.
1080
1081 :- use_module(specfile,[b_or_z_mode/0, csp_mode/0, csp_with_bz_mode/0]).
1082 retract_open_node(NodeID) :- retract_open_node_and_update_processed_nodes(NodeID),
1083 (b_or_z_mode -> assertz(not_invariant_checked(NodeID)) ; true).
1084
1085 reset_processed_nodes_counter :- reset_counter(processed_nodes).
1086 %reset_processed_nodes_counter(Nr) :- set_counter(processed_nodes,Nr).
1087
1088 retract_open_node_and_update_processed_nodes(NodeID) :-
1089 retract_open_node_direct(NodeID),
1090 inc_processed.
1091
1092 inc_processed :-
1093 inc_counter(processed_nodes).
1094
1095 pop_id_from_front(ID) :- pop_id_from_front_direct(ID), inc_processed.
1096 pop_id_from_end(ID) :- pop_id_from_end_direct(ID), inc_processed.
1097 ?pop_id_oldest(ID) :- pop_id_oldest_direct(ID), inc_processed.
1098
1099
1100
1101 /* --------------------------------- */
1102
1103 % find initialised states; very similar to is_initial_state_id/1
1104 % but is used by ltl/ctl/sap
1105 % TO DO: merge these two variations of the same concept
1106
1107 :- use_module(specfile,[animation_mode/1]).
1108
1109 find_initialised_states(Init) :-
1110 animation_mode(Mode),
1111 ( init_states_mode_cst_init(Mode) ->
1112 findall(I,find_init1(root,I,_),Init)
1113 ; init_states_mode_one_step(Mode) ->
1114 next_states_from_root(Init)
1115 ;
1116 fail).
1117
1118 % find trace to some initialised state
1119 find_trace_to_initial_state(Target,Trace) :- animation_mode(Mode),
1120 ? find_aux(Mode,Target,Trace).
1121 find_aux(Mode,Target,[root,Target]) :-
1122 init_states_mode_one_step(Mode).
1123 find_aux(Mode,Target,[root|Trace]) :-
1124 init_states_mode_cst_init(Mode),
1125 ? find_init1(root,Target,Trace).
1126
1127
1128 init_states_mode_cst_init(b).
1129 init_states_mode_cst_init(z).
1130 init_states_mode_cst_init(csp_and_b).
1131
1132 init_states_mode_one_step(csp).
1133 init_states_mode_one_step(cspm).
1134 init_states_mode_one_step(xtl).
1135 %init_states_mode_one_step(promela).
1136
1137 next_states_from_root(States) :-
1138 impl_trans_term_all(root,Ops),
1139 findall(S, member(op(_Id,_,S),Ops), States).
1140
1141 find_init1(Start,Init,Trace) :- Start==Init,!,Trace=[]. % usually called with Start=Init=root
1142 find_init1(Start,Init,[State|Rest]) :-
1143 ? impl_trans_term(Start,O,State),
1144 ? find_init2(O,State,Init,Rest).
1145 find_init2(O,Init,Init,[]) :-
1146 has_functor_and_maybe_tau(O,'$initialise_machine').
1147 find_init2(O,State,Init,Path) :-
1148 has_functor_and_maybe_tau(O,'$setup_constants'),
1149 ? find_init1(State,Init,Path).
1150 find_init2(start_cspm_MAIN,State,Init,Path) :-
1151 ? find_init1(State,Init,Path).
1152 find_init2(start_cspm(_Proc),State,Init,Path) :-
1153 find_init1(State,Init,Path).
1154
1155 % has_functor_and_maybe_tau(Term,Functor)
1156 % checks if Term has the form "Functor(...)" or "tau(Functor(...))"
1157 % this is used for CSP||B specification where the initialisation is wrapped with
1158 % in a tau operator
1159 has_functor_and_maybe_tau(tau(Term),Functor) :-
1160 has_functor_and_maybe_tau(Term,Functor),!.
1161 has_functor_and_maybe_tau(Term,Functor) :-
1162 functor(Term,Functor,_).
1163
1164 % compute how far the state is from the root node using back_edge markers (if available)
1165 try_compute_depth_of_state_id(root,R) :- !, R=0.
1166 try_compute_depth_of_state_id(Node,Depth) :- id_back_edge(Node,Depth,_Back).
1167
1168 % optional registering of back_edges: to quickly find trace from root and to computed depth/diameter
1169 register_back_edge(ID,FromID) :-
1170 try_compute_depth_of_state_id(FromID,D),!,
1171 D1 is D+1,
1172 assertz(id_back_edge(ID,D1,FromID)).
1173 register_back_edge(ID,FromID) :- write(cannot_store_back_edge(ID,FromID)),nl.
1174
1175 /* --------------------------------- */
1176
1177 %
1178 % Code to compute equivalence classes
1179 % using the standard DFA minimization algorithm
1180
1181 :- dynamic equivalent/2.
1182 % state_space:compute_equivalence_classes
1183 :- public compute_equivalence_classes/0.
1184
1185 compute_equivalence_classes :- init_equi,
1186 split_equivalence_classes,nl,
1187 print_equi.
1188
1189 print_equi :- state_space:equivalent(A,B), visited_expression(A,State),
1190 visited_expression(B,StateB),
1191 nl,
1192 print(A), print(' : '), print(State),nl,
1193 print(B), print(' : '), print(StateB),nl,fail.
1194 print_equi.
1195
1196 init_equi :- retractall(equivalent(_,_)),
1197 packed_visited_expression(ID,_State),
1198 \+ not_all_transitions_added(ID),
1199 findall(Action,transition(ID,Action,_,_),List),
1200 packed_visited_expression(ID2,_S2), ID2 @> ID,
1201 \+ not_all_transitions_added(ID2),
1202 findall(Action,transition(ID2,Action,_,_),List),
1203 assertz(equivalent(ID,ID2)), % they have the same signature
1204 %print(equivalent(ID,ID2)),nl,
1205 fail.
1206 init_equi :- print(finished_initialising),nl.
1207
1208 split_equivalence_classes :- retractall(echange),
1209 equivalent(ID1,ID2),
1210 transition(ID1,A,_,Dest1),
1211 transition(ID2,A,_,Dest2),
1212 \+ check_equi(Dest1,Dest2),
1213 retract(equivalent(ID1,ID2)), % splitting class
1214 % print(diff(ID1,ID2, A, Dest1, Dest2)),nl,
1215 assert_echange,
1216 fail.
1217 split_equivalence_classes :- echange -> split_equivalence_classes ; true.
1218
1219 :- dynamic echange/0.
1220 assert_echange :- echange -> true ; assertz(echange),print('.'),flush_output.
1221
1222 check_equi(A,B) :- A=B -> true ; A @<B -> equivalent(A,B) ; equivalent(B,A).
1223
1224 /*
1225 % benchmark how much time it takes to copy the state space state_space:bench_state_space.
1226 bench_state_space :-
1227 statistics(walltime,_),
1228 (state_space:packed_visited_expression(ID,S), assertz(pve(ID,S)),fail ; true),
1229 statistics(walltime,[_,Delta]), format('Time to copy packed_visited_expression: ~w ms~n',[Delta]),
1230 (state_space:transition(A,B,C,D), assertz(tr(A,B,C,D)),fail ; true),
1231 statistics(walltime,[_,Delta2]), format('Time to copy transition: ~w ms~n',[Delta2]),
1232 (state_packing:stored_value(A,B), assertz(sv(A,B)),fail ; true),
1233 (state_packing:stored_value_hash_to_id(A,B), assertz(svhi(A,B)),fail ; true),
1234 statistics(walltime,[_,Delta3]), format('Time to copy stored_value: ~w ms~n',[Delta3]).
1235 */
1236
1237 :- public portray_state_space/0.
1238 portray_state_space :- packed_visited_expression(ID,S), functor(S,F,N),
1239 format('State ~w : ~w/~w~n',[ID,F,N]), fail.
1240 portray_state_space :- transition(ID,Action,TransID,DestID),
1241 format(' ~w: ~w -- ~w --> ~w~n',[TransID,ID,Action,DestID]),fail.
1242 portray_state_space.
1243
1244 bench_state_space :- statistics(walltime,[W1,_]),
1245 (packed_visited_expression(_,_), fail ; true),
1246 statistics(walltime,[W2,_]), T1 is W2-W1,
1247 format('Time to inspect all states: ~w ms walltime~n',[T1]),
1248 (visited_expression(_,_), fail ; true),
1249 statistics(walltime,[W3,_]), T2 is W3-W2,
1250 format('Time to inspect and unpack all states: ~w ms walltime~n',[T2]),
1251 (transition(_,_,_,_), fail ; true),
1252 statistics(walltime,[W4,_]), T3 is W4-W3,
1253 format('Time to inspect all transitions: ~w ms walltime~n',[T3]),
1254 (visited_expression(_,E), my_term_hash(E,_), fail ; true),
1255 statistics(walltime,[W5,_]), T4 is W5-W4,
1256 format('Time to inspect, unpack and hash all states: ~w ms walltime~n',[T4]).
1257
1258 % ----------------------------
1259 % COUNTER EXAMPLE MANAGEMENT
1260
1261 % store counter example nodes and transition ids; used by LTL model checking for example
1262
1263
1264 :- dynamic counterexample_node/1.
1265 :- dynamic counterexample_op/1.
1266
1267 add_counterexample_node(NodeID) :- assertz(counterexample_node(NodeID)).
1268 add_counterexample_op(TransID) :-
1269 (counterexample_op(TransID) -> true ; assertz(counterexample_op(TransID))).
1270
1271
1272 reset_counterexample :-
1273 retractall(counterexample_node(_)),
1274 retractall(counterexample_op(_)).
1275
1276 :- register_event_listener(play_counterexample,reset_counterexample,
1277 'Reset marked nodes from previous counterexamples.').
1278
1279 set_counterexample_by_transition_ids(TransIds) :-
1280 set_trace_by_transition_ids(TransIds),
1281 maplist(add_counterexample_op,TransIds),
1282 extract_history_from_transition_ids(TransIds,root,[],[],_Last,History,_OpTrace),
1283 maplist(add_counterexample_node,History).