1 % (c) 2021-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(b_intelligent_trace_replay, [get_transition_details/6,
6 perform_single_replay_step/5,
7 replay_json_trace_file/2, replay_json_trace_file/5,
8 read_json_trace_file/3,
9 tcltk_replay_json_trace_file/3,
10 replay_prolog_trace_file/1,
11
12 % API for interactive JSON trace replay:
13 load_json_trace_file_for_ireplay/1,
14 tk_get_stored_json_trace_description/1,
15 get_stored_json_replay_steps/1,
16 get_ireplay_status/3,
17 replay_of_current_step_is_possible/5,
18 replay_of_current_step_is_possible_with_trans/5,
19 replay_current_step/1,
20 replay_current_step_with_trans/5,
21 ireplay_fast_forward/1,
22 ireplay_fast_forward_with_trans/6,
23 skip_current_ireplay_step/1]).
24
25 :- use_module(module_information,[module_info/2]).
26 :- module_info(group,testing).
27 :- module_info(description,'Replay saved (JSON) traces in a flexible way.').
28 % successor to b_trace_checking
29
30 :- meta_predicate exclude_and_collect_errors(2,-,-,-,-).
31
32 :- use_module(state_space,[current_state_id/1, transition/4, visited_expression/2]). % transition(CurID,Term,TransId,DestID)
33
34 :- use_module(tools_strings,[ajoin/2,ajoin_with_sep/3]).
35 :- use_module(specfile,[extract_variables_from_state/2, get_state_for_b_formula/3, b_or_z_mode/0,
36 get_local_states_for_operation_transition/4, create_local_store_for_operation/4,
37 get_operation_name/2]).
38 :- use_module(error_manager).
39 :- use_module(debug).
40
41 % A single step is a list of informations about the step
42 % name/OperationName
43 % paras/List of =(Name,Value)
44
45 % TO DO: for match_spec use mutable counter for number of matches instead of used parameter
46
47 :- use_module(tcltk_interface,[compute_all_transitions_if_necessary/2]).
48
49 :- use_module(probsrc(bmachine),[b_get_operation_non_det_modifies/2]).
50 :- use_module(probsrc(bsyntaxtree), [def_get_texpr_id/2, get_texpr_ids/2, get_texpr_id/2, get_texpr_type/2]).
51 :- use_module(probsrc(tools_matching), [get_possible_fuzzy_matches_and_completions_msg/3]).
52 :- use_module(probsrc(b_interpreter),[b_test_boolean_expression_for_ground_state/5]).
53
54 perform_single_replay_step(FromID,TransID,DestID,MatchSpec,TransSpec) :-
55 %format('* FROM: ~w ',[FromID]),portray_match_spec(MatchSpec),nl,
56 ? (match_spec_has_optimize_field(MatchSpec)
57 -> findall(sol(MM,TID,DID),
58 perform_single_replay_step_statespace(FromID,TID,DID,MatchSpec,TransSpec,MM),
59 Sols),
60 mark_match_spec_as_used(MatchSpec),
61 length(Sols,NrSols),
62 min_member(sol(Mismatches,TransID,DestID),Sols),
63 format('Min. nr of mismatches found ~w among ~w candidate steps (starting from state ~w). ~n',[Mismatches,NrSols,FromID])
64 ; % just find first solution:
65 ? perform_single_replay_step_statespace(FromID,TransID,DestID,MatchSpec,TransSpec,_)
66 ).
67 perform_single_replay_step(FromID,TransID,DestID,MatchSpec,TransSpec) :-
68 ? perform_single_replay_step_by_pred(FromID,TransID,DestID,MatchSpec,TransSpec).
69
70
71
72
73 % Assumption: ParaStore and ResultStore are sorted
74 % returns the number of mismatches for those Keys marked as optimize
75 perform_single_replay_step_statespace(FromID,TransID,DestID,
76 MatchSpec,
77 transition_spec(OpName, _, ParaStore, ResultStore, DestStore, UnchangedVars, Preds, _Postconditions),
78 Mismatches) :-
79 mark_match_spec_as_used(MatchSpec),
80 get_opt_match_spec_val(opname,MatchSpec,OpMatch),
81 compute_all_transitions_if_necessary(FromID,false), % could be made optional
82 (OpMatch==match -> TOpName=OpName ; true),
83 ? get_sorted_transition_details(FromID,TransID,DestID,TOpName,FullParaStore,FullResultStore),
84 (TOpName=OpName -> MM0 = 0 ; MM0=1, assert_mismatch(OpMatch)),
85 count_store_mismatches(FullParaStore,ParaStore,paras,MatchSpec,MM0,MM1), % check if parameters match
86 count_store_mismatches(FullResultStore,ResultStore,results,MatchSpec,MM1,MM2), % check if operation return values match
87 get_unchanged_store(FromID,UnchangedVars,UnchangedStore),
88 (DestStore=[], UnchangedStore=[]
89 -> MM6=MM2
90 ; % check if variables in destination state match
91 visited_expression(DestID,DestState),
92 get_dest_store(DestState,FullDestStore),
93 count_store_mismatches(FullDestStore,DestStore,dest,MatchSpec,MM2,MM3),
94 count_store_mismatches(FullDestStore,UnchangedStore,unchanged,MatchSpec,MM3,MM4),
95 (get_match_spec_val(nondet_vars,MatchSpec,_)
96 -> b_get_op_non_det_modifies(OpName,NonDetModifies),
97 include(b_intelligent_trace_replay:bind_id_is_element_of(NonDetModifies),DestStore,D1),
98 count_store_mismatches(FullDestStore,D1,nondet_vars,MatchSpec,MM4,MM5),
99 include(b_intelligent_trace_replay:bind_id_is_element_of(NonDetModifies),UnchangedStore,D2),
100 count_store_mismatches(FullDestStore,D2,nondet_vars,MatchSpec,MM5,MM6)
101 ; MM6=MM4
102 )
103 ),
104 Mismatches = MM6,
105 (Preds=[] -> true
106 ; get_match_spec_val(preds,MatchSpec,match)
107 -> bsyntaxtree:conjunct_predicates(Preds,Pred),
108 format('Testing preds in destination state ~w after ~w: ',[FromID,DestID]),translate:print_bexpr(Pred),nl,
109 % TODO: insert_before_substitution_variables for $0 vars; check that it is consistent with Tcl/Tk and ProB2-UI
110 % maybe use annotate_becomes_such_vars or find_used_primed_ids
111 append(FullResultStore,FullParaStore,LocalStore),
112 b_test_boolean_expression_for_ground_state(Pred,LocalStore,FullDestStore,'trace replay', OpName)
113 ; true
114 ).
115
116 node_not_fully_explored(FromID,OpName) :-
117 (max_reached_for_node(FromID)
118 ; not_all_transitions_added(FromID)
119 ; not_interesting(FromID)
120 ; time_out_for_node(FromID,OpName,_)).
121
122 :- use_module(probsrc(preferences),[get_time_out_preference_with_factor/2]).
123 % lookup in state space failed; try perform by predicate
124 % Note: does not use optimize keys (yet), only match keys
125 perform_single_replay_step_by_pred(FromID,TransID,DestID,
126 MatchSpec,
127 transition_spec(OpName, _, ParaStore, ResultStore, DestStore, UnchangedVars, Preds,
128 _Postconditions)) :-
129 nonvar(OpName), % we currently cannot execute by predicate without knowing OpName
130 ? (node_not_fully_explored(FromID,OpName) -> true
131 ; debug_format(19,'Node ~w fully explored for ~w; no use in attempting execute by predicate~n',[FromID,OpName]),
132 fail
133 ),
134 mark_match_spec_as_used(MatchSpec),
135 !,
136 (ParaStore \= [], % check parameters of operation
137 get_match_spec_val(paras,MatchSpec,match)
138 -> b_get_operation_typed_paras(OpName,Parameters),
139 ? generate_predicates_from_store(operation_parameters,Parameters,ParaStore,ParaPreds)
140 ; ParaPreds = []),
141 (ResultStore \= [], % check return values of operation
142 get_match_spec_val(results,MatchSpec,match)
143 -> b_get_operation_typed_results(OpName,Results),
144 generate_predicates_from_store(operation_results,Results,ResultStore,ResultPreds)
145 ; ResultPreds = []),
146 get_machine_identifiers(OpName,TVars),
147 (DestStore = [] -> DestPreds=[]
148 ; get_match_spec_val(dest,MatchSpec,match)
149 ? -> generate_predicates_from_store(dest_variables,TVars,DestStore,DestPreds)
150 ; get_match_spec_val(nondet_vars,MatchSpec,match)
151 -> b_get_op_non_det_modifies(OpName,NonDetModifies),
152 include(b_intelligent_trace_replay:id_is_element_of(NonDetModifies),TVars,NDVars),
153 generate_predicates_from_store(non_det_vars,NDVars,DestStore,DestPreds)
154 ; DestPreds=[]
155 ),
156 get_unchanged_store(FromID,UnchangedVars,UnchangedStore),
157 (UnchangedStore = [] -> UnchangedPreds=[]
158 ; get_match_spec_val(unchanged,MatchSpec,match) ->
159 ? generate_predicates_from_store(unchanged_vars,TVars,UnchangedStore,UnchangedPreds)
160 ; get_match_spec_val(nondet_vars,MatchSpec,match) ->
161 include(b_intelligent_trace_replay:id_is_element_of(NonDetModifies),TVars,NDVars),
162 generate_predicates_from_store(non_det_vars,NDVars,UnchangedStore,UnchangedPreds)
163 ; UnchangedPreds=[]
164 ),
165 (get_match_spec_val(preds,MatchSpec,match) -> AddPreds=Preds ; AddPreds=[]),
166 append([ParaPreds,ResultPreds,DestPreds,UnchangedPreds,AddPreds],AllPreds),
167 conjunct_predicates(AllPreds,Pred),
168 format('Trying to execute ~w in state ~w by predicate: ',[OpName,FromID]), translate:print_bexpr(Pred),nl,flush_output,
169 get_time_out_preference_with_factor(5,TO), % TODO: store this in meta JSON info or options
170 safe_time_out(tcltk_interface:tcltk_add_user_executed_operation_typed(OpName,FromID,_,Pred,TransID,DestID),
171 TO, TimeOutRes),
172 (TimeOutRes = time_out
173 -> format_with_colour(user_output,[orange],'==> Timeout when executing ~w by predicate in state ~w~n',[OpName,FromID]),fail
174 ; true).
175
176 get_unchanged_store(_,[],UnchangedStore) :- !, UnchangedStore=[].
177 get_unchanged_store(FromID,UnchangedVars,UnchangedStore) :-
178 % copy old values to UnchangedStore
179 visited_expression(FromID,FromState),
180 extract_variables_from_state(FromState,FullFromStore),
181 sort(FullFromStore,SortedStore),
182 % TODO: generate warning when unchanged variable does not exist?
183 include(b_intelligent_trace_replay:bind_id_is_element_of(UnchangedVars),SortedStore,UnchangedStore).
184
185 generate_predicate_from_bind(Kind,TypedIDs,json_bind(ID,Val,Type,Pos),b(Res,pred,[])) :-
186 ? (member(b(identifier(ID),ExpectedType,_),TypedIDs) ->
187 (unify_types_strict(ExpectedType,Type)
188 -> TID = b(identifier(ID),ExpectedType,[]), TVal = b(value(Val),ExpectedType,[]),
189 Res = equal(TID,TVal)
190 ; pretty_type(ExpectedType,ETS), pretty_type(Type,TS), write(clash(Kind,ID,ETS,TS)),nl,
191 % error should probably be caught earlier:
192 add_warning(b_intelligent_trace_replay,'Ignoring value for stored identifier due to type clash: ',ID,Pos),
193 Res = truth
194 )
195 ; % the identifier is not in the list and should be ignored here; sanity checks are made somewhere else
196 Res = truth
197 ).
198 generate_predicate_from_bind(Kind,TypedIDs,bind(ID,Val),R) :- % bind without type infos, e.g., from unchanged store
199 ? generate_predicate_from_bind(Kind,TypedIDs,json_bind(ID,Val,any,unkown),R).
200
201 generate_predicates_from_store(Kind,TVars,DestStore,DestPreds) :-
202 ? maplist(b_intelligent_trace_replay:generate_predicate_from_bind(Kind,TVars),DestStore,DestPreds).
203
204 get_machine_identifiers(Op,TConsts) :- is_setup_constants_op(Op), !, b_get_machine_constants(TConsts).
205 get_machine_identifiers(_,TVars) :- b_get_machine_variables(TVars).
206
207 is_setup_constants_op('$setup_constants').
208 is_setup_constants_op('$partial_setup_constants').
209
210 b_get_op_non_det_modifies(Op,NonDetModifies) :- is_setup_constants_op(Op),
211 !,% return all constants as non-det modifies
212 b_get_machine_constants(TConsts),get_texpr_ids(TConsts,ND),
213 sort(ND,NonDetModifies).
214 b_get_op_non_det_modifies(OpName,NonDetModifies) :- b_get_operation_non_det_modifies(OpName,NonDetModifies).
215
216 % wrappers to deal with a few special transitions; TO DO: extend for CSP||B
217 b_get_operation_typed_results('$setup_constants',Results) :- !,
218 Results=[]. % for trace replay we assume setup_constants to have no result variables
219 b_get_operation_typed_results('$initialise_machine',Results) :- !, Results=[]. % ditto
220 b_get_operation_typed_results('$partial_setup_constants',Results) :- !, Results=[]. % ditto
221 b_get_operation_typed_results(OpName,Results) :- b_or_z_mode, !, b_get_machine_operation_typed_results(OpName,Results).
222 b_get_operation_typed_results(_,[]).
223
224 b_get_operation_typed_paras('$setup_constants',Paras) :- !,
225 Paras=[]. % for trace replay we assume setup_constants to have no parameters
226 b_get_operation_typed_paras('$initialise_machine',Paras) :- !, Paras=[]. % ditto
227 b_get_operation_typed_paras('$partial_setup_constants',Paras) :- !, Paras=[]. % ditto
228 b_get_operation_typed_paras(OpName,Paras) :- b_or_z_mode,!,
229 b_get_machine_operation_typed_parameters_for_animation(OpName,Paras).
230 b_get_operation_typed_paras(OpName,[]) :-
231 add_message(replay_json_trace_file,'Not in B mode, cannot obtain parameter info for: ',OpName).
232
233 % -------------------
234
235 % now a version with multiple MatchSpecs to be tried in order
236 % Flag can be used to see how many alternatives were tried
237 flexible_perform_single_replay_step(FromID,TransID,DestID,[MatchSpec1|TMS],TransitionSpec,MName) :-
238 skip_match_spec(FromID,TransitionSpec,MatchSpec1),!,
239 debug_println(9,skipping_redundant_failing_check(MatchSpec1)),
240 flexible_perform_single_replay_step(FromID,TransID,DestID,TMS,TransitionSpec,MName).
241 flexible_perform_single_replay_step(FromID,TransID,DestID,[MatchSpec1|TMS],TransitionSpec,MName) :-
242 ? if(perform_single_replay_step(FromID,TransID,DestID,MatchSpec1,TransitionSpec),
243 get_match_spec_txt(MatchSpec1,MName),
244 ? flexible_perform_single_replay_step(FromID,TransID,DestID,TMS,TransitionSpec,MName)
245 ).
246
247 % -------------------
248
249
250 % we only assert mismatches; if a variable remains untouched we matched perfectly
251 assert_mismatch(Var) :- var(Var),!, Var=optimize.
252 assert_mismatch(require_mismatch). % probably not useful; difficult to support by predicate
253 assert_mismatch(optimize).
254
255 precise_match_spec(match_spec(_,precise,KeyVals)) :-
256 KeyVals = [dest/match,opname/match,paras/match,preds/match,results/match,unchanged/match].
257 ignore_dest_match_spec(match_spec(_,params_and_results,KeyVals)) :-
258 KeyVals = [opname/match,paras/match,preds/match,results/match,nondet_vars/match,dest/optimize,unchanged/optimize].
259 %ignore_return_match_spec(match_spec(_,parameters_only,KeyVals)) :-
260 % KeyVals = [opname/match,paras/match,results/optimize,nondet_vars/optimize].
261 opname_optimize_match_spec(match_spec(_,keep_name,KeyVals)) :-
262 KeyVals = [opname/match,paras/optimize,results/optimize,nondet_vars/optimize,dest/optimize,unchanged/optimize].
263
264 % conditions on when to skip certain match_specs
265 % (we assume that the precise_match_spec was tried before)
266 skip_match_spec(root,TS,match_spec(_,params_and_results,_)) :- get_transition_spec_op(TS,'$setup_constants').
267 % for setup_constants: nondet_vars are all constants; so this is equivalent to precise
268 % for initialise_machine: paras are all variables
269 skip_match_spec(_,TS,match_spec(_,MS,_)) :- MS \= precise,
270 get_transition_spec_meta(TS,Meta),
271 % for an unknown operation we only try a precise replay (e.g., if operation just renamed), otherwise we skip it
272 member(unknown_operation/_,Meta).
273 % TODO: skip parameters_only if an operation has not results and no nondet_vars
274
275 match_spec_was_used(match_spec(UsedFlag,_,_)) :- UsedFlag==used.
276 mark_match_spec_as_used(match_spec(used,_,_)).
277
278 get_match_spec_txt(match_spec(_,Name,_),Name).
279 ?get_match_spec_val(Key,match_spec(_,_,List),Res) :- member(Key/Val,List),!,Res=Val.
280
281 get_opt_match_spec_val(Key,MS,Res) :- get_match_spec_val(Key,MS,Val),!, Res=Val.
282 get_opt_match_spec_val(_,_,optimize).
283
284 % check if it is useful to optimize the mismatches
285 ?match_spec_has_optimize_field(match_spec(_,_,KeyVals)) :- member(_/optimize,KeyVals).
286
287 :- public valid_match_spec_key/1.
288 valid_match_spec_key(dest).
289 valid_match_spec_key(nondet_vars).
290 valid_match_spec_key(opname).
291 valid_match_spec_key(paras).
292 valid_match_spec_key(results).
293 valid_match_spec_key(unchanged).
294
295 :- public portray_match_spec/1.
296 portray_match_spec(match_spec(UsedFlag,Name,List)) :-
297 (UsedFlag==used -> U=used ; U=not_yet_used),
298 format('~w (~w): ~w~n',[Name,U,List]).
299
300 % -------------------
301
302 get_dest_store(concrete_constants(C),SC) :- !, sort(C,SC).
303 get_dest_store(Store,Vars) :- b_or_z_mode,!, extract_variables_from_state(Store,Vars).
304 get_dest_store(_,[]). % CSP,... has no concept of variables
305
306
307 % count the number of mismatches for a given key and MatchSpec
308 % if MatchSpec requires match (perfect match) it will fail if Mismatches are 0
309 % it accumulates the global number of mismatches in a DCG style accumulator
310 count_store_mismatches(FullStore,PartialStore,Key,MatchSpec,MismatchesIn,MismatchesOut) :-
311 get_match_spec_val(Key,MatchSpec,MatchVal), !,
312 (MatchVal=match
313 -> MismatchesIn=MismatchesOut,
314 count_mismatches(FullStore,Key,PartialStore,0)
315 ; count_mismatches(FullStore,Key,PartialStore,Mismatches),
316 MismatchesOut is MismatchesIn+Mismatches,
317 %print(new_mm(MismatchesOut,Key,MatchVal,Mismatches)),nl,
318 (Mismatches=0 -> true
319 ; assert_mismatch(MatchVal))
320 ).
321 count_store_mismatches(_,_,_Key,_,M,M). % key does not exist; no matching required
322
323 % for maplist, include, exclude:
324 ?bind_id_is_element_of(Vars,Bind) :- is_bind(Bind,ID,_), member(ID,Vars). % we could use ord_member
325 id_is_element_of(Vars,TID) :- def_get_texpr_id(TID,ID), member(ID,Vars).
326
327 is_bind(bind(ID,Val),ID,Val).
328 is_bind(json_bind(ID,Val,_,_),ID,Val).
329
330 %check_no_mismatches(FullStore,Key,PartialStore) :- count_mismatches(FullStore,Key,PartialStore,0).
331
332 count_mismatches(FullStore,Key,PartialStore,Mismatches) :-
333 count_mismatches_aux(FullStore,Key,PartialStore,0,Mismatches).
334 :- use_module(probsrc(translate), [translate_bvalue_with_limit/3]).
335 % count mismatches in FullStore compared to partial reference store
336 % if result is set to 0, it will fail after first mismatch
337 count_mismatches_aux(_,_,[],Acc,Res) :- !,Res=Acc.
338 count_mismatches_aux([],Key,PartialStore,_,_) :-
339 ajoin(['Saved trace step contains unknown bindings for ',Key,': '],Msg),
340 add_error(b_intelligent_trace_replay,Msg,PartialStore),
341 fail.
342 count_mismatches_aux([Bind1|T],Key,[Bind2|T2],Acc,Res) :-
343 is_bind(Bind1,ID,Val), is_bind(Bind2,ID,Val2),!,
344 (check_value_equal(ID,Val,Val2)
345 -> count_mismatches_aux(T,Key,T2,Acc,Res)
346 ; (debug_mode(off) -> true
347 ; translate_bvalue_with_limit(Val,200,V1), translate_bvalue_with_limit(Val2,200,V2),
348 formatsilent_with_colour(user_output,[red],'==> Mismatch for ~w ~w:~n ~w~n (trace) ~w~n',[Key,ID,V1,V2])
349 %nl,print(Val),nl,nl,print(Val2),nl,nl,
350 ),
351 inc_mismatches(Acc,Acc1,Res),
352 count_mismatches_aux(T,Key,T2,Acc1,Res)
353 ).
354 count_mismatches_aux([_ID|T],Key,PartialStore,Acc,Res) :- count_mismatches_aux(T,Key,PartialStore,Acc,Res).
355
356 inc_mismatches(X,_,Res) :- number(Res),X>Res,!,fail. % we will never reach Res; could be 0 for perfect match
357 inc_mismatches(Acc,Acc1,_) :- Acc1 is Acc+1.
358
359 % check if saved value and actual value is identical
360 :- use_module(kernel_objects,[equal_object/3]).
361 check_value_equal(ID,Val1,Val2) :-
362 temporary_set_preference(allow_enumeration_of_infinite_types,true,OldValueOfPref),
363 call_cleanup(check_value_equal_aux(ID,Val1,Val2),
364 reset_temporary_preference(allow_enumeration_of_infinite_types,OldValueOfPref)).
365
366 % what if trace was saved with different SYMBOLIC pref value?
367 :- use_module(b_ast_cleanup, [clean_up/3]).
368 :- use_module(custom_explicit_sets, [same_closure/2]).
369 :- use_module(debug, [debug_mode/1]).
370 check_value_equal_aux(ID,closure(P1,T1,B1),C2) :- C2 = closure(P2,T2,B2),
371 C1 = closure(P1,T1,B1),
372 !, % we have two symbolic values
373 (same_closure(C1,C2)
374 -> true
375 ; % simple comparison failed, now try and normalize the symbolic values and compare again
376 temporary_set_preference(normalize_ast,true,CHANGE),
377 % normalize_ast_sort_commutative should probably be false, unless we improve the sorting
378 %print(compiling_cur_value(ID)),nl,
379 clean_up(B1,[],B1C),
380 %we could call: b_compiler:b_compile_closure(closure(P1,T1,B1C),closure(P12,T12,B12)),
381 %print(compiling_trace_value(ID)),nl,
382 clean_up(B2,[],B2C),
383 reset_temporary_preference(normalize_ast,CHANGE),
384 (same_closure(closure(P1,T1,B1C),closure(P2,T2,B2C))
385 -> true
386 ; Val=closure(P1,T1,B1C), Val2 = closure(P2,T2,B2C),
387 debug_mode(on),
388 translate_bvalue_with_limit(Val,500,V1), translate_bvalue_with_limit(Val2,500,V2),
389 formatsilent_with_colour(user_output,[red],'==> Symbolic Mismatch for ~w:~n ~w~n (trace) ~w~n',[ID,V1,V2]),
390 % trace, same_closure(closure(P1,T1,B1C),closure(P2,T2,B2C)),
391 fail
392 )
393 ).
394 %check_value_equal_aux(ID,Val1,Val2) :- !, equal_object(Val1,Val2,ID).
395 check_value_equal_aux(ID,Val1,Val2) :-
396 catch(
397 equal_object_time_out(Val1,Val2,ID,2500),
398 enumeration_warning(_A,_B,_C,_D,_E),
399 (format_with_colour(user_output,[red],'==> Enumeration warning when comparing values for ~w~n',[ID]),fail)
400 ).
401
402 :- use_module(tools_meta,[safe_time_out/3]).
403 equal_object_time_out(Val1,Val2,ID,TO) :-
404 safe_time_out(equal_object(Val1,Val2,ID),TO,TimeOutRes),
405 (TimeOutRes = time_out
406 -> format_with_colour(user_output,[red],'==> Timeout when comparing values for ~w~n',[ID]),fail
407 ; true).
408
409
410 :- use_module(specfile,[get_operation_internal_name/2,
411 state_corresponds_to_set_up_constants_only/2]).
412 :- use_module(bmachine,[b_get_machine_operation_parameter_names_for_animation/2,
413 b_get_machine_operation_typed_parameters_for_animation/2,
414 b_get_machine_operation_result_names/2,
415 b_get_machine_operation_typed_results/2,
416 b_get_machine_variables/1, b_get_machine_constants/1,
417 bmachine_is_precompiled/0, b_top_level_operation/1,
418 b_machine_name/1, b_is_variable/1, b_is_variable/2, b_is_constant/1, b_is_constant/2]).
419 :- use_module(probsrc(bsyntaxtree), [conjunct_predicates/2]).
420
421 :- use_module(probsrc(state_space),[max_reached_for_node/1, not_all_transitions_added/1,
422 time_out_for_node/3, not_interesting/1,
423 try_set_trace_by_transition_ids/1]).
424
425 :- use_module(library(lists)).
426
427 % get the information of a B state_space transition in more detailed form
428 % we get a store of parameter values and a store of result values and the operation name
429 get_transition_details(FromID,TransID,DestID,OpName,ParaStore,ResultStore) :-
430 ? transition(FromID,OperationTerm,TransID,DestID),
431 get_operation_internal_name(OperationTerm,OpName),
432 get_transition_details_aux(OpName,OperationTerm,DestID,ParaStore,ResultStore).
433
434 get_transition_details_aux('$setup_constants',_,DestID,ParaStore,ResultStore) :- !,
435 ResultStore=[],
436 visited_expression(DestID,DestState),
437 state_corresponds_to_set_up_constants_only(DestState,ParaStore).
438 get_transition_details_aux('$initialise_machine',_,DestID,ParaStore,ResultStore) :- !,
439 ResultStore=[],
440 visited_expression(DestID,DestState),
441 extract_variables_from_state(DestState,ParaStore).
442 get_transition_details_aux(OpName,OperationTerm,_,ParaStore,ResultStore) :-
443 get_local_states_for_operation_transition(OpName,OperationTerm,ParaStore,ResultStore).
444
445 get_transition_name(FromID,TransID,OpName) :-
446 transition(FromID,OperationTerm,TransID,_),
447 get_operation_name(OperationTerm,OpName).
448
449
450
451 % a variation where the two stores are sorted according to Prolog order:
452 get_sorted_transition_details(FromID,TransID,DestID,TOpName,SortedPS,SortedRS) :-
453 ? get_transition_details(FromID,TransID,DestID,TOpName,FullParaStore,FullResultStore),
454 sort(FullParaStore,SortedPS),
455 sort(FullResultStore,SortedRS).
456
457 % ------------------------
458
459 get_transition_spec_op(transition_spec(OpName, _, _, _, _, _, _, _),OpName).
460 get_transition_spec_meta(transition_spec(_, Meta, _, _, _, _, _, _),Meta).
461
462 % get textual representation of transition spec (portray/translate)
463 get_transition_spec_txt(transition_spec(OpName, Meta, ParaStore, ResultStore,
464 _DestStore, _Unchanged, _Preds, _Postconditions),Txt) :-
465 ? (member(description/Desc,Meta) -> ajoin([Desc,' :: '],DescTxt) ; DescTxt = ''),
466 (nonvar(OpName) -> OpTxt=OpName
467 ; member(unknown_operation/op(OldOpName,OldParas,OldResults),Meta)
468 -> translate_unknown_operation(OldOpName,OldParas,OldResults,OpTxt)
469 ; OpTxt='?'),
470 (ParaStore = [] -> ParaText1='', ParaText2=''
471 ; ParaText1=' paras: ',
472 maplist(get_bind_txt,ParaStore,Paras),
473 ajoin_with_sep(Paras,',',ParaText2)
474 ),
475 (ResultStore = [] -> ResultText1='', ResultText2=''
476 ; ResultText1=' results: ',
477 maplist(get_bind_txt,ResultStore,Results),
478 ajoin_with_sep(Results,',',ResultText2)
479 ),!,
480 ajoin([DescTxt,OpTxt,ParaText1,ParaText2,ResultText1,ResultText2],Txt).
481 get_transition_spec_txt(TS,'???') :- add_internal_error('Unknown transition spec:',TS).
482
483
484 translate_unknown_operation(OldOpName,OldParas,[],OpTxt) :- !,
485 translate_bindings(OldParas,OPS),
486 append(OPS,[')'],OpParaAtoms),
487 ajoin(['?',OldOpName,'('|OpParaAtoms],OpTxt).
488 translate_unknown_operation(OldOpName,OldParas,OldResults,OpTxt) :-
489 translate_bindings(OldResults,OPR),
490 translate_unknown_operation(OldOpName,OldParas,[],Op1),
491 ajoin([Op1,'-->'|OPR],OpTxt).
492
493 % translate a list of json_bind terms into a list for use with ajoin for pretty-priting
494 translate_bindings([],[]).
495 translate_bindings([json_bind(ID,Val,_Type,_Pos)|TJ],[ID,'=',TVal|TT]) :-
496 translate_bvalue_with_limit(Val,50,TVal),
497 (TJ = [] -> TT=[]
498 ; TT = [','|TT2], translate_bindings(TJ,TT2)).
499
500
501 get_bind_txt(Bind,Txt) :- is_bind(Bind,Id,Val),
502 simple_val(Val), !, % TODO: add parameter for short/long text
503 translate_bvalue_with_limit(Val,100,V1),
504 ajoin([Id,'=',V1],Txt).
505 get_bind_txt(Bind,Id) :- is_bind(Bind,Id,_).
506
507 simple_val(V) :- var(V),!,fail.
508 simple_val(int(_)).
509 simple_val(pred_false).
510 simple_val(pred_true).
511 simple_val(string(_)).
512 simple_val(fd(_,_)).
513
514
515 % perform some static checks on a transition spec: check if operations, parameters, variables exist
516 check_and_adapt_trace_step(transition_spec(OpName, Meta, _, _, DestStore, UnchangedVars,Preds, Postconditions), Step,
517 transition_spec(OpName, Meta, [], [], DestStore2,UnchangedVars2,Preds, Postconditions)) -->
518 {\+ b_or_z_mode},!,
519 exclude_and_collect_errors(unknown_variable_binding(Step,OpName),DestStore,DestStore2),
520 exclude_and_collect_errors(unknown_variable(Step,OpName),UnchangedVars,UnchangedVars2).
521 check_and_adapt_trace_step(transition_spec(OpName, Meta, ParaStore,ResultStore, DestStore, UnchangedVars,Preds, Postconditions),
522 Step,
523 transition_spec(OpName2,Meta2,ParaStore2,ResultStore2,DestStore2,UnchangedVars2,Preds2, Postconditions2)) -->
524 {b_get_operation_typed_results(OpName,TOpResults)},
525 {b_get_operation_typed_paras(OpName,TOpParas)},
526 !,
527 {OpName2=OpName},
528 {Meta2=Meta}, % TO DO: include excluded infos
529 {Preds2=Preds}, %TO DO: check if all identifiers bound
530 {Postconditions2=Postconditions}, % TODO Check operation names and predicate identifiers
531 ? exclude_and_collect_errors(unknown_para_binding(OpName,TOpParas,'parameter',Step),ParaStore,ParaStore2),
532 ? exclude_and_collect_errors(unknown_para_binding(OpName,TOpResults,'result variable',Step),ResultStore,ResultStore2),
533 ({is_setup_constants_op(OpName)}
534 ? -> exclude_and_collect_errors(unknown_constant_binding(Step),DestStore,DestStore2),
535 {UnchangedVars2 = []},
536 ({UnchangedVars = []} -> []
537 ; {add_error(b_intelligent_trace_replay,'Illegal unchanged info for SETUP_CONSTANTS',UnchangedVars)}
538 )
539 ? ; exclude_and_collect_errors(unknown_variable_binding(Step,OpName),DestStore,DestStore2),
540 ? exclude_and_collect_errors(unknown_variable(Step,OpName),UnchangedVars,UnchangedVars2)
541 ).
542 check_and_adapt_trace_step(transition_spec(OpName, Meta, PS, RS, DestStore, UnchangedVars,Preds, Postconditions), Step,
543 transition_spec(_, Meta2, [], [], DestStore2, UnchangedVars2,Preds, Postconditions)) -->
544 add_replay_error('Unknown operation: ',OpName), % TODO treat $JUMP
545 {Meta2 = [unknown_operation/op(OpName,PS,RS) | Meta],
546 findall(KOpid,b_top_level_operation(KOpid),Ops),
547 (get_possible_fuzzy_matches_and_completions_msg(OpName,Ops,FMsg)
548 -> ajoin(['Unknown operation in replay step ',Step,' (did you mean the operation ',FMsg,' ?) : '], Msg)
549 ; ajoin(['Unknown operation in replay step ',Step,': '], Msg)),
550 (member(pos/Pos,Meta) -> true ; Pos=unknown),
551 add_error(b_intelligent_trace_replay,Msg,OpName,Pos)
552 },
553 % TODO: maybe do a fuzzy match and check if a new operation not used in the trace file exists
554 exclude_and_collect_errors(unknown_variable_binding(Step,OpName),DestStore,DestStore2),
555 exclude_and_collect_errors(unknown_variable(Step,OpName),UnchangedVars,UnchangedVars2).
556
557 check_step_postconditions(transition_spec(_, _, _, _, _, _, _, Postconditions),StateID) -->
558 check_postconditions(Postconditions,1,StateID).
559
560 check_postconditions([],_,_) --> [].
561 check_postconditions([Postcondition|Postconditions],Nr,StateID) -->
562 check_postcondition(Postcondition,Nr,StateID),
563 {Nr1 is Nr+1},
564 check_postconditions(Postconditions,Nr1,StateID).
565
566 check_postcondition(state_predicate(Pred),Nr,StateID) -->
567 {get_state_for_b_formula(StateID,Pred,State)},
568 ({b_test_boolean_expression_for_ground_state(Pred,[],State,'trace replay postconditions',Nr)} ->
569 []
570 ;
571 add_replay_error('Failed postcondition (predicate):',Nr)
572 ).
573 check_postcondition(operation_enabled(OpName,Pred,Enabled),Nr,StateID) -->
574 {
575 precise_match_spec(MatchSpec),
576 TransitionSpec = transition_spec(OpName,[],[],[],[],[],[Pred],[]),
577 (perform_single_replay_step(StateID,_,_,MatchSpec,TransitionSpec) -> Actual = enabled ; Actual = disabled)
578 },
579 ({Enabled == Actual} ->
580 []
581 ;
582 {ajoin(['Failed postcondition (operation ',OpName,' should be ',Enabled,'):'],Msg)},
583 add_replay_error(Msg,Nr)
584 ).
585
586 % a version of exclude which also collects errors
587 exclude_and_collect_errors(_Pred,[],[]) --> [].
588 exclude_and_collect_errors(Pred,[H|T],Res) --> {call(Pred,H,Error)},!,
589 [Error],
590 exclude_and_collect_errors(Pred,T,Res).
591 exclude_and_collect_errors(Pred,[H|T],[H|Res]) --> % include item
592 ? exclude_and_collect_errors(Pred,T,Res).
593
594
595 add_replay_error(Msg,Term) --> {gen_replay_error(Msg,Term,Err)}, [Err].
596 gen_replay_error(Msg,Term,rerror(FullMSg)) :- ajoin([Msg,Term],FullMSg).
597 replay_error_occured(Errors) :- member(rerror(_),Errors).
598 get_replay_error(rerror(Msg),Msg).
599
600 :- use_module(probsrc(btypechecker), [unify_types_strict/2]).
601 :- use_module(probsrc(kernel_objects), [infer_value_type/2]).
602 :- use_module(probsrc(translate), [pretty_type/2]).
603
604 unknown_para_binding(OpName,TParas,Kind,Step,json_bind(ID,Value,ValType,ValPos),ErrorTerm) :-
605 ( get_texpr_id(TID,ID),
606 ? member(TID,TParas), get_texpr_type(TID,Type)
607 -> illegal_type(ID,Type,Value,ValType,ValPos,Kind,Step,ErrorTerm)
608 ; ajoin(['Ignoring unknown ',Kind,' for operation ',OpName,' at step ', Step, ': '],Msg),
609 gen_replay_error(Msg,ID,ErrorTerm)
610 ).
611 unknown_variable_binding(Step,_OpName,json_bind(Var,Value,ValType,ValPos),ErrorTerm) :- b_is_variable(Var,Type),!,
612 illegal_type(Var,Type,Value,ValType,ValPos,'variable',Step,ErrorTerm).
613 unknown_variable_binding(Step,OpName,json_bind(Var,_,_,_),ErrorTerm) :- unknown_variable(Step,OpName,Var,ErrorTerm).
614 unknown_variable(Step,OpName,Var,ErrorTerm) :- \+ b_is_variable(Var),
615 (b_is_constant(Var)
616 -> ajoin(['Ignoring constant at step ', Step, ' for ', OpName, ' (a variable is expected here): '],Msg)
617 ; b_get_machine_variables(TVars),get_texpr_ids(TVars,Vars),
618 get_possible_fuzzy_matches_and_completions_msg(Var,Vars,FMsg)
619 -> ajoin(['Ignoring unknown variable (did you mean ',FMsg,' ?) at step ', Step, ' for ', OpName, ': '],Msg)
620 ; ajoin(['Ignoring unknown variable at step ', Step, ' for ', OpName, ': '],Msg)
621 ),
622 gen_replay_error(Msg,Var,ErrorTerm).
623 unknown_constant_binding(Step,json_bind(Var,Value,ValType,ValPos),ErrorTerm) :- b_is_constant(Var,Type),!,
624 illegal_type(Var,Type,Value,ValType,ValPos,'constant',Step,ErrorTerm).
625 unknown_constant_binding(Step,json_bind(Var,_,_,_),ErrorTerm) :-
626 (b_is_variable(Var)
627 -> ajoin(['Ignoring variable at step ', Step, ' (a constant is expected here): '],Msg)
628 ; b_get_machine_constants(TVars),get_texpr_ids(TVars,Vars),
629 get_possible_fuzzy_matches_and_completions_msg(Var,Vars,FMsg)
630 -> ajoin(['Ignoring unknown constant (did you mean ',FMsg,' ?) at step ', Step, ': '],Msg)
631 ; ajoin(['Ignoring unknown constant at step ', Step, ': '],Msg)
632 ),
633 gen_replay_error(Msg,Var,ErrorTerm).
634
635
636 illegal_type(Var,Type,_Value,ValType,_ValPos,Kind,Step,ErrorTerm) :-
637 \+ unify_types_strict(Type,ValType),
638 pretty_type(ValType,VTS), pretty_type(Type,TS),
639 ajoin(['Ignoring ',Kind, ' at step ', Step,
640 ' due to unexpected type of value (', VTS, ' instead of ',TS,') for: '],ErrMsg),
641 gen_replay_error(ErrMsg,Var,ErrorTerm).
642 /*
643 | ?- perform_single_replay_step(X,TID,Dest,Match,transition_spec(Op,[],[],[],[active])).
644 X = 3,
645 TID = 86,
646 Dest = 5,
647 Match = match_spec(match,match,match,match,match),
648 Op = new ?
649 yes
650
651 */
652
653 % ------------------
654 %precise_replay_trace(Trace,FromID,TransIds,DestID) :-
655 % precise_match_spec(MatchSpec), % require precise replay
656 % replay_trace(Trace,[MatchSpec],[],1,FromID,TransIds,DestID,[],_). % Todo : check errors
657
658 :- use_module(tools_printing,[format_with_colour/4]).
659 :- use_module(probsrc(debug),[formatsilent_with_colour/4]).
660 % Note if we leave RestSpecs as a variable this will always do deterministic replay
661 % to achieve backtracking RestSpecs must be set to []
662 replay_trace([],_MatchSpecs,_Opts,_,ID,[],ID,[],[]).
663 replay_trace([TransSpec|T],MatchSpecs,Options,Step,FromID,TransIds,DestID,RestSpecs,
664 [replay_step(MatchInfo,Errors)|OtherMatches]) :-
665 get_transition_spec_txt(TransSpec,TTxt),
666 formatsilent_with_colour(user_output,[blue],'==> Replay step ~w: from state ~w for ~w~n',[Step,FromID,TTxt]),
667 statistics(walltime,[W1|_]),
668 % first perform static check of step:
669 ? phrase(check_and_adapt_trace_step(TransSpec,Step,CorrectedTransSpec),Errors,Errors1),
670 if((TransIds=[TransID|TTrans],
671 ? flexible_perform_single_replay_step(FromID,TransID,ID2,MatchSpecs,CorrectedTransSpec,MatchInfo)),
672 (phrase(check_step_postconditions(CorrectedTransSpec,ID2),Errors1),
673 statistics(walltime,[W2|_]), WTime is W2-W1,
674 get_transition_name(FromID,TransID,OpName), % show operation name used as feedback in case errors occur
675 (Errors == [] ->
676 formatsilent_with_colour(user_output,[green],'==> Replay step ~w successful (~w, ~w ms) leading to state ~w~n',[Step,MatchInfo,WTime,ID2])
677 ; Errors = [rerror(OneErr)] ->
678 formatsilent_with_colour(user_output,[red,bold],'==> Replay step ~w successful WITH ERROR (~w, ~w, ~w ms) leading to state ~w via ~w~n',[Step,MatchInfo,OneErr,WTime,ID2,OpName])
679 ;
680 length(Errors,NrErrors), Errors = [rerror(OneErr)|_],
681 formatsilent_with_colour(user_output,[red,bold],'==> Replay step ~w successful WITH ERRORS (~w, ~w errors [~w,...], ~w ms) leading to state ~w via ~w~n',[Step,MatchInfo,NrErrors,OneErr,WTime,ID2,OpName])
682 ;
683 length(Errors,NrErrors),
684 formatsilent_with_colour(user_output,[red,bold],'==> Replay step ~w successful WITH ERRORS (~w, ~w errors, ~w ms) leading to state ~w via ~w~n',[Step,MatchInfo,NrErrors,WTime,ID2,OpName])
685 ),
686 (get_preference(deterministic_trace_replay,true) -> !
687 % TO DO: use info from MatchSpec? (e.g., det for perfect match)
688 ; true
689 ; formatsilent_with_colour(user_output,[orange],'==> Backtracking replay step ~w (~w) leading to state ~w~n',[Step,MatchInfo,ID2])),
690 S1 is Step+1,
691 replay_trace(T,MatchSpecs,Options,S1,ID2,TTrans,DestID,RestSpecs,OtherMatches)
692 ),
693 (format_with_colour(user_output,[red,bold],'==> Replay step ~w FAILED~n',[Step]),
694 get_transition_spec_txt(TransSpec,Txt), formatsilent_with_colour(user_output,[red,bold],' ~w~n',[Txt]),
695 Errors1=[],
696 MatchInfo=failed,
697
698 (T = [_|_], nonmember(stop_at_failure,Options)
699 -> % try and skip this step and continue replay
700 RestSpecs=[TransSpec|RT],
701 TransIds=[skip|TTrans], % -1 signifies skipped transition
702 S1 is Step+1,
703 replay_trace(T,MatchSpecs,Options,S1,FromID,TTrans,DestID,RT,OtherMatches)
704 ; RestSpecs=[TransSpec|T], % the steps that were not replayed
705 TransIds=[], DestID=FromID,
706 OtherMatches=[]
707 )
708 )
709 ).
710
711 % ------------------
712
713
714 tcltk_replay_json_trace_file(FileName,ReplayStatus,list([Header|Entries])) :-
715 replay_json_trace_file_with_check(FileName,TransSpecs,ReplayStatus,TransIds,MatchInfoList),
716 try_set_trace_by_transition_ids(TransIds),
717 Header = list(['Step', 'TraceFile','Replayed', 'Match','Mismatches','Errors','State ID']),
718 (tk_get_trace_info(TransSpecs,root,1,TransIds,MatchInfoList,Entries)
719 -> true
720 ; add_internal_error('Could not compute replay table:',TransSpecs), Entries=[]).
721
722
723 :- use_module(probsrc(translate),[translate_event_with_limit/3]).
724
725 tk_get_trace_info([],_,_,_,_,[]).
726 tk_get_trace_info([TransSpec|TS2],CurID,Step,TransIds,MatchInfoList,
727 [list([Step,Txt,OpTxt,MI,list(DeltaList),list(Errors),CurID])|RestInfo]) :-
728 get_from_match_list(MatchInfoList,MI,Errors,MIL2),
729 get_transition_spec_txt(TransSpec,Txt),
730 (TransIds=[TID1|TI2], transition(CurID,OperationTerm,TID1,ToID)
731 -> %get_operation_internal_name(OperationTerm,OpName)
732 translate_event_with_limit(OperationTerm,30,OpTxt),
733 analyse_step_match(TransSpec,CurID,TID1,DeltaList)
734 ; TransIds=[TID1|TI2],
735 (number(TID1) -> TID1<0 ; true) % not a valid transition number; -1 or skip
736 -> ToID=CurID, OpTxt='skipped', DeltaList=[]
737 ; TI2=[], ToID=CurID, OpTxt='-', DeltaList=[]
738 ),
739 Step1 is Step+1,
740 tk_get_trace_info(TS2,ToID,Step1,TI2,MIL2,RestInfo).
741
742 get_from_match_list([replay_step(MI,Errors)|T],MatchInfo,TkErrors,T) :-
743 maplist(get_replay_error,Errors,TkErrors),
744 (MI=precise,TkErrors=[_|_] -> MatchInfo=precise_with_errs ; MatchInfo=MI).
745 get_from_match_list([],'-',['-'],[]).
746
747 % analyse how good a step matches the transition spec
748 % useful after replay to provide explanations to the user
749 analyse_step_match(TransSpec,FromID,TransID,DeltaList) :-
750 TransSpec = transition_spec(OpName, _, ParaStore, ResultStore, DestStore, _UnchangedVars, _Preds, _Postconditions),
751 get_sorted_transition_details(FromID,TransID,DestID,TOpName,FullParaStore,FullResultStore),
752 (TOpName=OpName -> DeltaList=DL1 ; DeltaList=['Name'|DL1]),
753 delta_store_match(FullParaStore,paras,ParaStore,DL1,DL2),
754 delta_store_match(FullResultStore,results,ResultStore,DL2,DL3),
755 visited_expression(DestID,DestState),
756 get_dest_store(DestState,FullDestStore),
757 delta_store_match(FullDestStore,dest,DestStore,DL3,DL4),
758 % TO DO: UnchangedVars and _Preds
759 DL4=[],!.
760 analyse_step_match(TransSpec,FromID,TransID,DeltaList) :-
761 add_internal_error('Call failed:',analyse_step_match(TransSpec,FromID,TransID,DeltaList)),
762 DeltaList=['??ERROR??'].
763
764 delta_store_match(_,_,[]) --> !.
765 delta_store_match([],_Key,Rest)
766 --> add_rest(Rest). % these bindings were probably filtered out during replay and error messages were generated
767 delta_store_match([Bind1|T],Key,[Bind2|T2]) -->
768 {is_bind(Bind1,ID,Val), is_bind(Bind2,ID,Val2)},
769 !,
770 ({check_value_equal(ID,Val,Val2)}
771 -> []
772 ; %translate_bvalue_with_limit(Val,100,V1), translate_bvalue_with_limit(Val2,100,V2),
773 [ID] % TO DO: provided detailed explanation using values
774 ),delta_store_match(T,Key,T2).
775 delta_store_match([_ID|T],Key,PartialStore) --> delta_store_match(T,Key,PartialStore).
776
777 add_rest([]) --> [].
778 add_rest([Bind|T]) --> {is_bind(Bind,ID,_)}, [ID], add_rest(T).
779
780 % -----------------------
781
782 replay_json_trace_file(FileName,ReplayStatus) :-
783 replay_json_trace_file_with_check(FileName,_,ReplayStatus,TransIds,_),
784 try_set_trace_by_transition_ids(TransIds).
785
786
787 % generate error/warning for imperfect or partial replay
788 replay_json_trace_file_with_check(FileName,Trace,ReplayStatus,TransIds,MatchInfoList) :-
789 replay_json_trace_file(FileName,Trace,ReplayStatus,TransIds,MatchInfoList),
790 length(TransIds,Steps),
791 length(Trace,AllSteps),
792 check_replay_status(ReplayStatus,Steps,AllSteps).
793
794 check_replay_status(imperfect,Steps,_) :- !,
795 ajoin(['Imperfect replay, steps replayed: '],Msg),
796 add_warning(replay_json_trace_file,Msg, Steps).
797 check_replay_status(partial,Steps,AllSteps) :- !,
798 ajoin(['Replay of all ',AllSteps,' steps not possible, steps replayed: '],Msg),
799 add_error(replay_json_trace_file,Msg, Steps).
800 check_replay_status(perfect,Steps,_) :-
801 add_message(replay_json_trace_file,'Perfect replay possible, steps replayed: ', Steps).
802
803 % ------------
804
805 :- use_module(tools,[start_ms_timer/1, stop_ms_timer_with_msg/2]).
806 :- use_module(bmachine_construction,[dummy_machine_name/2]).
807
808 replay_json_trace_file(FileName,Trace,ReplayStatus,TransIds,MatchInfoList) :- \+ bmachine_is_precompiled,!,
809 add_error(replay_json_trace_file,'No specification loaded, cannot replay trace file:',FileName),
810 Trace=[], TransIds=[], ReplayStatus=partial, MatchInfoList=[].
811 replay_json_trace_file(FileName,Trace,ReplayStatus,TransIds,MatchInfoList) :-
812 start_ms_timer(T1),
813 read_json_trace_file(FileName,ModelName,Trace),
814 stop_ms_timer_with_msg(T1,'Loading JSON trace file'),
815 precise_match_spec(MatchSpec), % require precise replay
816 ignore_dest_match_spec(MS2),
817 opname_optimize_match_spec(MS3),
818 % was ignore_return_match_spec(MS3), % TODO: when no return and no non-det vars: do not try MS3
819 start_ms_timer(T2),
820 temporary_set_preference(deterministic_trace_replay,true,CHNG),
821 replay_trace(Trace,[MatchSpec,MS2,MS3],[],1,root,TransIds,_DestID,RestTrace,MatchInfoList),
822 reset_temporary_preference(deterministic_trace_replay,CHNG),
823 stop_ms_timer_with_msg(T2,'Replaying JSON trace file'),
824 !,
825 (RestTrace = []
826 -> ((match_spec_was_used(MS3) % Grade=3
827 ; match_spec_was_used(MS2) %Grade=2
828 ? ; member(replay_step(_,Errs),MatchInfoList), replay_error_occured(Errs)
829 )
830 -> ReplayStatus=imperfect,
831 check_model_name(ModelName)
832 ; ReplayStatus=perfect
833 )
834 ; ReplayStatus=partial,
835 check_model_name(ModelName)
836 ).
837
838 :- use_module(specfile,[currently_opened_specification_name/1]).
839 check_model_name(ModelName) :-
840 currently_opened_specification_name(CurModelName),!,
841 (CurModelName=ModelName -> true
842 ; dummy_machine_name(ModelName,CurModelName) % CurModelName = MAIN_MACHINE_FOR_...
843 -> true
844 ; ModelName = 'dummy(uses)'
845 -> true % if modelName is "null" this is the value used
846 ; prob2_ui_suffix(ModelName,CurModelName) ->
847 % happens when ProB2-UI saves trace files; sometimes it adds (2), ... suffix, see issue #243
848 add_message(replay_json_trace_file, 'JSON trace file model name has a ProB2-UI suffix: ', ModelName)
849 ; ajoin(['JSON trace file model name ',ModelName,' does not match current model name: '],MMsg),
850 add_warning(replay_json_trace_file, MMsg, CurModelName)
851 ).
852 check_model_name(ModelName) :-
853 add_warning(replay_json_trace_file, 'Cannot determine current model name to check stored name:', ModelName).
854
855 :- set_prolog_flag(double_quotes, codes).
856 :- use_module(self_check).
857 :- assert_must_succeed(b_intelligent_trace_replay:prob2_ui_suffix('b_mch', 'b')).
858 :- assert_must_succeed(b_intelligent_trace_replay:prob2_ui_suffix('b_mch (2)', 'b')).
859 :- assert_must_succeed(b_intelligent_trace_replay:prob2_ui_suffix('b (2)', 'b')).
860 :- assert_must_fail(b_intelligent_trace_replay:prob2_ui_suffix('b', 'bc')).
861 :- assert_must_fail(b_intelligent_trace_replay:prob2_ui_suffix('b (2)', 'bc')).
862 % check if name matches current model name catering for ProB2-UI quirks
863 prob2_ui_suffix(JSONModelName,CurModelName) :-
864 atom_codes(JSONModelName,JCodes),
865 atom_codes(CurModelName,TargetCodes),
866 append(TargetCodes,After,JCodes),
867 (append("_mch",After2,After)
868 -> true % .eventb package file name
869 ; append(".mch",After2,After) -> true
870 ; After2=After),
871 valid_prob2_ui_suffix(After2).
872
873 valid_prob2_ui_suffix([]) :- !.
874 valid_prob2_ui_suffix([32|_]). % we could check that we have (2), ... after; but is it necessary?
875
876
877 error_occured_during_replay(MatchInfoList) :-
878 member(replay_step(_,Errs),MatchInfoList), replay_error_occured(Errs),!.
879
880 % ---------------------------------
881
882 replay_prolog_trace_file(FileName) :-
883 start_ms_timer(T1),
884 read_prolog_trace_file(FileName,_ModelName,Trace),
885 stop_ms_timer_with_msg(T1,'Loading Prolog trace file'),
886 replay_prolog2(FileName,Trace).
887
888 replay_prolog2(FileName,Trace) :-
889 precise_match_spec(MatchSpec),
890 start_ms_timer(T2),
891 replay_trace(Trace,[MatchSpec],[stop_at_failure],1,root,TransIds,_DestID,RestTrace,MatchInfoList),
892 stop_ms_timer_with_msg(T2,'Replaying JSON trace file'),
893 RestTrace=[], % will initiate backtracking
894 try_set_trace_by_transition_ids(TransIds),
895 (error_occured_during_replay(MatchInfoList)
896 -> add_error(replay_prolog_trace_file,'Errors occurred during replay of file:',FileName)
897 ; true).
898 replay_prolog2(FileName,_Trace) :-
899 add_error(replay_prolog_trace_file,'Could not fully replay file:',FileName).
900
901 read_prolog_trace_file(FileName,ModelName,Trace) :-
902 open(FileName,read,Stream,[encoding(utf8)]),
903 call_cleanup(parse_prolog_trace_file(FileName,Stream,ModelName,Trace),
904 close(Stream)).
905
906 parse_prolog_trace_file(File,Stream,ModelName,Trace) :-
907 safe_read_stream(Stream,0,Term),!,
908 (Term = end_of_file
909 -> Trace = [], ModelName = 'dummy(uses)',
910 add_warning(read_prolog_trace_file,'Empty trace file: ',File)
911 ; (Term = machine(ModelName)
912 -> Trace = T
913 ; Trace = [Term|T],
914 add_warning(read_prolog_trace_file,'File does not start with a machine/1 fact: ',Term)
915 ),
916 parse_prolog_trace_file_body(Stream,1,T)
917 ).
918
919 parse_prolog_trace_file_body(Stream,Step,Trace) :-
920 safe_read_stream(Stream,Step,Term),!,
921 (Term = end_of_file
922 -> Trace = []
923 ; skip_prolog_term(Term)
924 -> add_message(read_prolog_trace_file,'Skipping: ',Term),
925 parse_prolog_trace_file_body(Stream,Step,Trace)
926 ; Trace = [TransSpec|T],
927 convert_prolog_trace_step(Term,TransSpec),
928 S1 is Step + 1,
929 parse_prolog_trace_file_body(Stream,S1,T)
930 ).
931
932 safe_read_stream(Stream,Step,T) :-
933 catch(read(Stream,T), E, (
934 ajoin(['Exception while reading step ', Step, 'of trace file: '], Msg),
935 add_error(read_prolog_trace_file,Msg,[E]),
936 T=end_of_file
937 )).
938
939 skip_prolog_term('$check_value'(_ID,_Val)).
940 convert_prolog_trace_step(Fact,
941 transition_spec(OpName,Meta,ParaStore,ResultStore,DestStore,Unchanged,PredList,[])) :-
942 PredList=[], Unchanged=[], Meta=[], DestStore = [],
943 decompose_operation(Fact,OpName,ParaStore,ResultStore).
944 % TODO: deal with '$check_value'(ID,Val)
945 % decompose an operation term into name, parameter store and result store
946 decompose_operation('-->'(OpTerm,Results),OpName,ParaStore,ResultStore) :- !,
947 decompose_operation2(OpTerm,OpName,ParaStore),
948 (b_get_machine_operation_result_names(OpName,ResultNames)
949 -> create_sorted_store(ResultNames,Results,OpName,ResultStore)
950 ; ResultStore = []).
951 decompose_operation(OpTerm,OpName,ParaStore,[]) :- decompose_operation2(OpTerm,OpName,ParaStore).
952
953 is_setup_or_init('$initialise_machine','$initialise_machine').
954 is_setup_or_init(initialise_machine,'$initialise_machine'). % old style
955 is_setup_or_init(setup_constants,'$setup_constants'). % old style
956 is_setup_or_init(Op,Op) :- is_setup_constants_op(Op).
957
958 decompose_operation2(OpTerm,OpName,ParaStore) :-
959 functor(OpTerm,Functor,Arity),
960 is_setup_or_init(Functor,OpName),
961 !,
962 % the order of constants, variables etc has changed in ProB;
963 % in general we cannot reconstruct the association of the arguments to variables or constants
964 (Arity=0 -> true
965 ; add_message(b_intelligent_trace_replay,'Ignoring parameters of:',OpName)),
966 ParaStore=[].
967 decompose_operation2(OpTerm,OpName,ParaStore) :-
968 OpTerm =.. [OpName|Paras],
969 (b_get_machine_operation_parameter_names_for_animation(OpName,ParaNames)
970 -> create_sorted_store(ParaNames,Paras,OpName,ParaStore)
971 ; ParaStore = [],
972 add_error(read_prolog_trace_file,'Unknown operation in trace file:',OpName)
973 ).
974
975
976 create_sorted_store([],Paras,OpName,SortedParaStore) :- Paras = [_|_],
977 get_preference(show_eventb_any_arguments,false),!,
978 add_message(b_intelligent_trace_replay,'Prolog trace file contains values for virtual parameters (set SHOW_EVENTB_ANY_VALUES to TRUE to better replay this trace file): ',OpName),
979 SortedParaStore = [].
980 create_sorted_store(ParaNames,[],_OpName,SortedParaStore) :- ParaNames = [_|_],
981 get_preference(show_eventb_any_arguments,true),!,
982 add_message(b_intelligent_trace_replay,'Prolog trace file contains no values for parameters (maybe SHOW_EVENTB_ANY_VALUES was FALSE when trace file was created): ',ParaNames),
983 SortedParaStore = [].
984 create_sorted_store(ParaNames,Paras,OpName,SortedParaStore) :-
985 create_local_store_for_operation(ParaNames,Paras,OpName,ParaStore),
986 sort(ParaStore,SortedParaStore).
987
988
989
990 % ------------------------
991
992 :- use_module(extrasrc(json_parser),[json_parse_file/3]).
993
994 % read a JSON ProB2-UI trace file and extract model name and transition_spec list
995 read_json_trace_file(FileName,ModelName,Trace) :-
996 json_parse_file(FileName,Term,[rest(_),position_infos(true),strings_as_atoms(false)]),
997 %nl,print(Term),nl,nl,
998 !,
999 ? (extract_json_model_name(Term,M) -> ModelName=M ; ModelName = 'dummy(uses)'),
1000 ? (translate_json_trace_term(Term,FileName,Trace) -> true
1001 ; add_error(read_json_trace_file,'Could not translate JSON transitionList: ',Term),
1002 Trace = []).
1003
1004 % small JSON utilities; to do: merge with VisB utilities and factor out
1005 ?get_json_attribute(Attr,ObjList,Value) :- member(Equality,ObjList),
1006 is_json_equality_attr(Equality,Attr,Value).
1007 get_json_attribute_with_pos(Attr,ObjList,File,Value,Pos) :-
1008 ? member(Equality,ObjList),
1009 is_json_equality_attr_with_pos(Equality,File,Attr,Value,Pos).
1010
1011 is_json_equality_attr('='(Attr,Val),Attr,Val).
1012 is_json_equality_attr('='(Attr,Val,_Pos),Attr,Val). % we have position infos
1013
1014 is_json_equality_attr_with_pos('='(Attr,Val),_File,Attr,Val,unknown).
1015 is_json_equality_attr_with_pos('='(Attr,Val,JPos),File,Attr,Val,ProBPos) :- create_position(JPos,File,ProBPos).
1016
1017 create_position(From-To,File,ProBPos) :-
1018 ProBPos=src_position_with_filename_and_ec(From,1,To,1,File).
1019 % --------
1020
1021 :- use_module(probsrc(preferences), [reset_temporary_preference/2,temporary_set_preference/3, get_preference/2]).
1022 translate_json_trace_term(json(ObjList),FileName,Trace) :-
1023 ? get_json_key_list(transitionList,ObjList,List),
1024 List \= [], % optimization, dont set preferences
1025 !,
1026 % TODO: why is this not a call_cleanup?
1027 temporary_set_preference(repl_cache_parsing,true,CHNG),
1028 eval_strings:turn_normalising_off,
1029 ? maplist(translate_json_operation(FileName),List,Trace),
1030 eval_strings:turn_normalising_on,
1031 reset_temporary_preference(repl_cache_parsing,CHNG).
1032
1033 % no transitionList => just use empty list
1034 translate_json_trace_term(json(_),_,[]) :- !.
1035
1036 % extract model name from metadata which looks like this
1037 /*
1038 "metadata": {
1039 "fileType": "Trace",
1040 "formatVersion": 1,
1041 "savedAt": "2021-10-13T13:38:02Z",
1042 "creator": "tcltk (leuschel)",
1043 "proBCliVersion": "1.11.1-nightly",
1044 "proBCliRevision": "3cb800bbadfeaf4f581327245507a55ae5a5e66d",
1045 "modelName": "scheduler",
1046 "modelFile": "/Users/bourkaki/B/Benchmarks/scheduler.mch"
1047 }
1048 */
1049
1050 extract_json_model_name(json(ObjList),MachineName) :-
1051 get_json_key_object(metadata,ObjList,List),
1052 ? get_json_attribute(modelName,List,string(MC)),
1053 atom_codes(MachineName,MC).
1054
1055
1056 % translate a single JSON transition entry into a transition_spec term for replay_trace
1057 /* here is a typical entry for the scheduler model:
1058 {
1059 "name": "ready",
1060 "params": {
1061 "rr": "process3"
1062 },
1063 "results": {
1064 },
1065 "destState": {
1066 "active": "{process3}",
1067 "waiting": "{}"
1068 },
1069 "destStateNotChanged": [
1070 "ready"
1071 ],
1072 "preds": null
1073 },
1074 */
1075 translate_json_operation(FileName,json(Json),
1076 transition_spec(OpName,Meta,
1077 ParaStore,ResultStore,DestStore,Unchanged,PredList,Postconditions) ) :-
1078 ? get_json_attribute_with_pos(name,Json,FileName,string(OpNameC),Position), % name is required!
1079 atom_codes(OpName,OpNameC),
1080 (debug_mode(off) -> true ; add_message(translate_json_operation,'Processing operation: ',OpName,Position)),
1081 ? (get_json_key_object(params,Json,Paras)
1082 -> translate_json_paras(Paras,params(OpName),FileName,OpName,Bindings),
1083 sort(Bindings,ParaStore) % put the parameters into the standard Prolog order
1084 ; ParaStore = []
1085 ),
1086 ? (get_json_key_object(results,Json,ResParas)
1087 -> translate_json_paras(ResParas,results(OpName),FileName,OpName,Bindings2),
1088 sort(Bindings2,ResultStore)
1089 ; ResultStore = []
1090 ),
1091 ? (get_json_key_object(destState,Json,DestState)
1092 -> translate_json_paras(DestState,destState,FileName,OpName,Bindings3),
1093 sort(Bindings3,DestStore)
1094 ; DestStore = []
1095 ),
1096 ? (get_json_key_list(destStateNotChanged,Json,UnchList)
1097 -> maplist(translate_json_string,UnchList,UnchAtoms),
1098 sort(UnchAtoms,Unchanged)
1099 ; Unchanged = []
1100 ),
1101 ? (get_json_key_list(preds,Json,JPredList)
1102 -> (maplist(translate_json_pred,JPredList,PredList) -> true
1103 ; add_error(translate_json_operation,'Unable to parse predicates for operation:',OpName,Position),
1104 PredList = []
1105 )
1106 ; PredList = []
1107 ),
1108 ? (get_json_key_list(postconditions,Json,PostconditionList)
1109 -> maplist(translate_postcondition,PostconditionList,Postconditions)
1110 ; Postconditions = []
1111 ),
1112 ? (get_json_attribute(description,Json,string(DescCodes))
1113 -> atom_codes(Desc,DescCodes), Meta = [description/Desc,pos/Position]
1114 ; Meta = [pos/Position]
1115 ).
1116
1117 translate_postcondition(Json,Postcondition) :-
1118 get_json_attribute(kind,Json,string(KindCodes)),
1119 atom_codes(Kind,KindCodes),
1120 (translate_postcondition_kind(Kind,Json,Postcondition) -> true ; add_error(translate_postcondition,'translate_postcondition_kind failed',Json), fail).
1121
1122 translate_postcondition_kind('PREDICATE',Json,state_predicate(TPred)) :-
1123 !,
1124 get_json_attribute(predicate,Json,PredString),
1125 translate_json_pred(PredString,TPred).
1126 translate_postcondition_kind(Kind,Json,operation_enabled(OpName,TPred,Enabled)) :-
1127 enabled_kind(Kind,Enabled),
1128 !,
1129 get_json_attribute(operation,Json,string(OpNameCodes)),
1130 atom_codes(OpName,OpNameCodes),
1131 get_json_attribute(predicate,Json,PredString),
1132 (PredString = string([]) -> TPred = b(truth,pred,[])
1133 ; translate_json_pred(PredString,TPred)
1134 ).
1135
1136 enabled_kind('ENABLEDNESS',enabled).
1137 enabled_kind('DISABLEDNESS',disabled).
1138
1139
1140 get_json_key_object(Key,JSON,Object) :-
1141 ? get_json_attribute(Key,JSON,JObject),
1142 JObject \= @(null),
1143 (JObject = json(Object) -> true
1144 ; add_internal_error('Illegal JSON object for key:',Key:JObject),
1145 fail
1146 ).
1147 get_json_key_list(Key,JSON,List) :-
1148 ? get_json_attribute(Key,JSON,JList),
1149 JList \= @(null),
1150 (JList = array(List) -> true
1151 ; add_internal_error('Illegal JSON list for key:',Key:JList),
1152 fail
1153 ).
1154
1155 translate_json_string(string(AtomCodes),Atom) :- atom_codes(Atom,AtomCodes).
1156
1157 translate_json_paras([],_,_,_,R) :- !, R=[].
1158 translate_json_paras([Eq|T],Kind,FileName,OpName,[Bind|BT]) :-
1159 translate_json_para(Eq,Kind,FileName,OpName,Bind),!,
1160 translate_json_paras(T,Kind,FileName,OpName,BT).
1161 translate_json_paras([_|T],Kind,FileName,OpName,BT) :- translate_json_paras(T,Kind,FileName,OpName,BT).
1162
1163
1164 :- use_module(probsrc(b_global_sets),[add_prob_deferred_set_elements_to_store/3]).
1165 % TO DO: using eval_strings is very ugly, use a better API predicate
1166 translate_json_para(Equality,Kind,FileName,OpName,json_bind(Name,Value,Type,Pos)) :-
1167 is_json_equality_attr_with_pos(Equality,FileName,Name,string(ExpressionCodes),Pos),
1168 !,
1169 %format('Translating JSON Para ~w : ~s~n',[Name,C]),
1170 (eval_strings:repl_parse_expression(ExpressionCodes,Typed,Type,Error)
1171 -> (Error \= none -> add_parameter_error(Error,Name,ExpressionCodes,OpName,Pos)
1172 ; Type = pred -> add_parameter_error('use of predicate instead of expression',Name,ExpressionCodes,OpName,Pos)
1173 ; Type = subst -> add_parameter_error('unexpected substitution',Name,ExpressionCodes,OpName,Pos)
1174 ; (add_prob_deferred_set_elements_to_store([],EState,visible), % value should not depend on any state
1175 eval_strings:eval_expression_direct(Typed,EState,Value)
1176 -> \+ illegal_json_binding_type(Kind,Name,Type,Pos)
1177 ; add_parameter_error('evaluation error',Name,ExpressionCodes,OpName,Pos)
1178 )
1179 )
1180 ; add_parameter_error('parsing failed error',Name,ExpressionCodes,OpName,Pos)
1181 ).
1182 translate_json_para(Para,_,_,_,_) :-
1183 add_error(translate_json_para,'Unknown JSON para:',Para),fail.
1184
1185 :- use_module(specfile,[translate_operation_name/2]).
1186 add_parameter_error(Error,Name,ExpressionCodes,OpName,Pos) :-
1187 translate_operation_name(OpName,TOp),
1188 ajoin(['Ignoring JSON value for parameter ',Name,' of ',TOp,' due to ',Error,':'], Msg),
1189 atom_codes(A,ExpressionCodes),
1190 add_error(translate_json_para,Msg,A,Pos),fail.
1191
1192 %evaluate_codes_value(ExpressionCodes,Type,Value) :-
1193 % eval_strings:repl_parse_expression(ExpressionCodes,Typed,Type,Error), Error=none,
1194 % eval_strings:eval_expression_direct(Typed,Value).
1195
1196 ?illegal_json_binding_type(destState,ID,Type,Pos) :- get_expected_type(ID,Kind,ExpectedType),!,
1197 \+ unify_types_strict(Type,ExpectedType), pretty_type(Type,TS), pretty_type(ExpectedType,ETS),
1198 ajoin(['Ignoring JSON destState value for ',Kind,' ',ID,' due to illegal type ',TS, ', expected:'], Msg),
1199 add_error(translate_json_para,Msg,ETS,Pos).
1200 illegal_json_binding_type(destState,ID,_Type,Pos) :-
1201 add_error(translate_json_para,'Ignoring JSON destState value for unknown identifier:',ID,Pos).
1202 % unknown operations are now dealt with later in check_and_adapt_trace_step
1203 %illegal_json_binding_type(params(Op),ID,_Type,Pos) :-
1204 % b_or_z_mode, % otherwise no types available
1205 % \+ b_top_level_operation(Op), !,
1206 % findall(KOpid,b_top_level_operation(KOpid),Ops),
1207 % (get_possible_fuzzy_matches_and_completions_msg(Op,Ops,FMsg)
1208 % -> ajoin(['Ignoring JSON value for parameter ',ID,' of unknown operation (did you mean the operation ',FMsg,' ?) : '], Msg)
1209 % ; ajoin(['Ignoring JSON value for parameter ',ID,' of unknown operation: '], Msg)),
1210 % add_error(translate_json_para,Msg,Op,Pos).
1211 illegal_json_binding_type(params(Op),ID,Type,Pos) :-
1212 b_or_z_mode, % otherwise no types available
1213 b_top_level_operation(Op),
1214 b_get_machine_operation_typed_parameters_for_animation(Op,Params),
1215 ? member(b(identifier(ID),ExpectedType,_),Params),!,
1216 \+ unify_types_strict(Type,ExpectedType), pretty_type(Type,TS), pretty_type(ExpectedType,ETS),
1217 ajoin(['Ignoring JSON value for parameter ',ID,' of operation ', Op, ' due to illegal type ',TS, ', expected:'], Msg),
1218 add_error(translate_json_para,Msg,ETS,Pos).
1219 illegal_json_binding_type(params(Op),ID,_Type,Pos) :-
1220 b_or_z_mode, % otherwise show_eventb_any_arguments makes no sense
1221 b_top_level_operation(Op),
1222 (b_get_machine_operation_typed_parameters_for_animation(Op,[]),
1223 get_preference(show_eventb_any_arguments,false)
1224 % TODO: check if ID is a valid virtual parameter, or if trace file was generated with preference set to true
1225 -> ajoin(['Ignoring JSON value for parameter ',ID,', operation has no parameters (setting SHOW_EVENTB_ANY_VALUES to TRUE may help):'],Msg)
1226 ; ajoin(['Ignoring JSON value for unknown parameter ',ID,' for:'],Msg)
1227 ),
1228 add_error(translate_json_para,Msg,Op,Pos).
1229 illegal_json_binding_type(results(Op),ID,Type,Pos) :-
1230 b_or_z_mode, % otherwise there are no typred results available
1231 b_get_machine_operation_typed_results(Op,Results), member(b(identifier(ID),ExpectedType,_),Results),!,
1232 \+ unify_types_strict(Type,ExpectedType), pretty_type(Type,TS), pretty_type(ExpectedType,ETS),
1233 ajoin(['Ignoring JSON value for result ',ID,' of operation ', Op, ' due to illegal type ',TS], Msg),
1234 add_error(translate_json_para,Msg,ETS,Pos).
1235 % unknown operations are now dealt with later in check_and_adapt_trace_step
1236 %illegal_json_binding_type(results(_Op),ID,_Type,Pos) :-
1237 % add_error(translate_json_para,'Ignoring JSON value for unknown operation result:',ID,Pos).
1238
1239 get_expected_type(ID,variable,ExpectedType) :- bmachine_is_precompiled, b_is_variable(ID,ExpectedType).
1240 get_expected_type(ID,constant,ExpectedType) :- bmachine_is_precompiled, b_is_constant(ID,ExpectedType).
1241
1242 % TODO: already check results, ...
1243
1244 translate_json_pred(string(PredCodes),TPred) :-
1245 OuterQuantifier = no_quantifier,
1246 % TO DO: parse in context of operation ! otherwise we get type error for pp=pp for example where pp is a parameter
1247 eval_strings:repl_parse_predicate(PredCodes,OuterQuantifier,TPred,_TypeInfo). % , print(pred_ok(TPred)),nl.
1248
1249 /*
1250 after reading a JSON ProB2-UI file looks like this:
1251
1252 json([description=string([70,105,108,101,32,99,114,101,97,116,101,100,32,98,121,32,80,114,111,66,32,84,99,108,47,84,107]),transitionList=array([json([name=string([36,105,110,105,116,105,97,108,105,115,101,95,109,97,99,104,105,110,101]),params=json([]),results=json([]),destState=json([active=string([123,125]),ready=string([123,125]),waiting=string([123,125])]),destStateNotChanged=array([]),preds=@(null)]),json([name=string([110,101,119]),params=json([pp=string([112,114,111,99,101,115,115,51])]),results=json([]),destState=json([waiting=string([123,112,114,111,99,101,115,115,51,125])]),destStateNotChanged=array([string([97,99,116,105,118,101]),string([114,101,97,100,121])]),preds=@(null)]),json([name=string([114,101,97,100,121]),params=json([rr=string([112,114,111,99,101,115,115,51])]),results=json([]),destState=json([active=string([123,112,114,111,99,101,115,115,51,125]),waiting=string([123,125])]),destStateNotChanged=array([string([114,101,97,100,121])]),preds=@(null)]),json([name=string([115,119,97,112]),params=json([]),results=json([]),destState=json([active=string([123,125]),waiting=string([123,112,114,111,99,101,115,115,51,125])]),destStateNotChanged=array([string([114,101,97,100,121])]),preds=@(null)]),json([name=string([110,101,119]),params=json([pp=string([112,114,111,99,101,115,115,50])]),results=json([]),destState=json([waiting=string([123,112,114,111,99,101,115,115,50,44,112,114,111,99,101,115,115,51,125])]),destStateNotChanged=array([string([97,99,116,105,118,101]),string([114,101,97,100,121])]),preds=@(null)])]),metadata=json([fileType=string([84,114,97,99,101]),formatVersion=number(1),savedAt=string([50,48,50,49,45,49,48,45,49,51,84,49,51,58,51,56,58,48,50,90]),creator=string([116,99,108,116,107,32,40,108,101,117,115,99,104,101,108,41]),proBCliVersion=string([49,46,49,49,46,49,45,110,105,103,104,116,108,121]),proBCliRevision=string([51,99,98,56,48,48,98,98,97,100,102,101,97,102,52,102,53,56,49,51,50,55,50,52,53,53,48,55,97,53,53,97,101,53,97,53,101,54,54,100]),modelName=string([115,99,104,101,100,117,108,101,114]),modelFile=string([47,85,115,101,114,115,47,108,101,117,115,99,104,101,108,47,103,105,116,95,114,111,111,116,47,112,114,111,98,95,101,120,97,109,112,108,101,115,47,112,117,98,108,105,99,95,101,120,97,109,112,108,101,115,47,66,47,66,101,110,99,104,109,97,114,107,115,47,115,99,104,101,100,117,108,101,114,46,109,99,104])])])
1253
1254 */
1255
1256 % -------------------------
1257
1258 % Interactive Trace Replay API
1259
1260 % load a trace file and store it for interactive replay
1261 load_json_trace_file_for_ireplay(FileName) :-
1262 read_json_trace_file(FileName,ModelName,Trace),
1263 reset_json_trace_replay,
1264 store_json_trace(Trace,0,Len),
1265 assert(current_replay_step(1)),
1266 assert(loaded_json_trace_file(FileName,ModelName,Len)).
1267
1268 :- dynamic loaded_json_trace_file/3, json_trace_replay_step/3.
1269 :- dynamic current_replay_step/1, json_trace_replayed_info/2.
1270
1271
1272 :- use_module(eventhandling,[register_event_listener/3]).
1273 :- register_event_listener(clear_specification,reset_json_trace_replay,
1274 'Reset interactive trace replay.').
1275
1276 reset_json_trace_replay :-
1277 retractall(current_replay_step(_)),
1278 retractall(loaded_json_trace_file(_,_,_)),
1279 retractall(json_trace_replay_step(_,_,_)),
1280 retractall(json_trace_replayed_info(_,_)).
1281
1282 store_json_trace([],L,L).
1283 store_json_trace([TransSpec|T],StepNr,Len) :-
1284 S1 is StepNr + 1,
1285 get_transition_spec_txt(TransSpec,TTxt),
1286 formatsilent_with_colour(user_output,[blue],'==> Trace step ~w: ~w~n',[S1,TTxt]),
1287 phrase(check_and_adapt_trace_step(TransSpec,S1,CorrectedTransSpec),StaticErrors),
1288 assert(json_trace_replay_step(S1,CorrectedTransSpec,StaticErrors)),
1289 store_json_trace(T,S1,Len).
1290
1291 get_trace_step_info(StepNr,StepDescr) :-
1292 json_trace_replay_step(StepNr,TransSpec,StaticErrors),
1293 get_transition_spec_txt(TransSpec,TTxt),
1294 (StaticErrors = [] -> StaticTT=[]
1295 ; length(StaticErrors,NrStaticErrors),
1296 StaticTT = [' (static errors: ',NrStaticErrors,')']
1297 ),
1298 (json_trace_replayed_info(StepNr,Info),
1299 get_replay_info_text(Info,TextAtoms)
1300 -> append(StaticTT,TextAtoms,TT),
1301 ajoin([StepNr,': ',TTxt | TT],StepDescr)
1302 ; ajoin([StepNr,': ',TTxt | StaticTT],StepDescr)
1303 ).
1304
1305 get_replay_info_text(replay(FromID,TransID,MatchInfo,Errors),TextAtoms) :-
1306 transition(FromID,OperationTerm,TransID,_ToID),
1307 translate_event_with_limit(OperationTerm,40,OpTxt),
1308 !,
1309 (Errors=[] -> TextAtoms = [' * REPLAYED (', MatchInfo,') : ',OpTxt]
1310 ; length(Errors,NrErrors),
1311 TextAtoms = [' * REPLAYED (', MatchInfo, ', errors: ',NrErrors,') : ', OpTxt]
1312 ).
1313 get_replay_info_text(skipped,[' SKIPPED']) :- !.
1314 get_replay_info_text(X,[X]).
1315
1316 tk_get_stored_json_trace_description(list(List)) :-
1317 findall(StepDescr,get_trace_step_info(_,StepDescr),List).
1318
1319 get_stored_json_replay_steps(List) :-
1320 findall(ireplay_step(StepNr,TTxt,StaticErrors),
1321 (json_trace_replay_step(StepNr,TransSpec,RErrors),
1322 maplist(get_rerror,RErrors,StaticErrors),
1323 get_transition_spec_txt(TransSpec,TTxt)),
1324 List).
1325
1326 try_replay_next_step(MatchSpecs,CurStepNr,FromID,TransID,DestId,MatchInfo,TkTransInfos,TkErrors) :-
1327 (var(CurStepNr) -> current_replay_step(CurStepNr) ; true), % allow to pass a fixed Nr from ProB2
1328 (var(FromID) -> current_state_id(FromID) ; true), % allow to pass a fixed ID from ProB2
1329 json_trace_replay_step(CurStepNr,TransSpec,StaticErrors),
1330 flexible_perform_single_replay_step(FromID,TransID,DestId,MatchSpecs,TransSpec,MatchInfo),
1331 phrase(check_step_postconditions(TransSpec,DestId),Errors,StaticErrors),
1332 get_transition_name(FromID,TransID,OpName),
1333 length(Errors,NrErrs),
1334 formatsilent_with_colour(user_output,[green], '==> Replay step ~w (~w) ~w leading to state ~w~n',[CurStepNr,MatchInfo,OpName,DestId]),
1335 (NrErrs>0 -> formatsilent_with_colour(user_output,[orange],' Errors (~w): ~w~n',[NrErrs,Errors]) ; true),
1336 findall(TInfo,get_transition_info(TransSpec,TInfo),TkTransInfos),
1337 maplist(get_rerror,Errors,TkErrors). % make errors atomic for Tk
1338
1339 get_rerror(Err,Msg) :- get_replay_error(Err,Msg),!.
1340 get_rerror(Err,Msg) :- atom(Err),!,Msg=Err.
1341 get_rerror(Err,F) :- functor(Err,F).
1342
1343 :- use_module(translate,[translate_bexpression_with_limit/3]).
1344 % get text descriptions for a transition_spec, to be shown to user e.g. in Tk listbox:
1345 get_transition_info(transition_spec(_Op, _Meta, Paras, Results, DestStore,_UnchangedVars,_Preds,_Post),InfoTxt) :-
1346 (Kind=para, List=Paras
1347 ; Kind=result, List=Results
1348 ; Kind=dest, List=DestStore),
1349 get_binding_txt(List,Txt),
1350 ajoin([Kind,' : ',Txt],InfoTxt).
1351 get_transition_info(transition_spec(_Op, _, _, _, _,UnchangedVars,_,_),InfoTxt) :-
1352 member(ID,UnchangedVars),
1353 ajoin(['unchanged : ',ID],InfoTxt).
1354 get_transition_info(transition_spec(_Op, _, _, _, _,_,Preds,_),InfoTxt) :-
1355 member(TP,Preds),
1356 translate_bexpression_with_limit(TP,250,TPS),
1357 ajoin(['pred : ',TPS],InfoTxt).
1358
1359 get_binding_txt(List,BindingText) :-
1360 member(json_bind(Var,Value,_ValType,_ValPos),List),
1361 translate_bvalue_with_limit(Value,200,VS),
1362 ajoin([Var,'=',VS],BindingText).
1363
1364 default_match_specs([MatchSpec,MS2,MS3]) :-
1365 precise_match_spec(MatchSpec), % require precise replay
1366 ignore_dest_match_spec(MS2),
1367 opname_optimize_match_spec(MS3).
1368
1369 ireplay :- default_match_specs(MS),
1370 ireplay(MS).
1371
1372 :- use_module(probsrc(state_space), [extend_trace_by_transition_ids/1]).
1373 ireplay(MatchSpecs) :-
1374 replay_current_step(MatchSpecs,_),!,
1375 ireplay(MatchSpecs).
1376 ireplay(MatchSpecs) :-
1377 skip_current_ireplay_step(_),
1378 ireplay(MatchSpecs).
1379
1380 % get information about how the status of replaying a loaded trace is:
1381 get_ireplay_status(CurStepNr,Steps,Finished) :-
1382 loaded_json_trace_file(_,_,Steps),
1383 current_replay_step(CurStepNr),
1384 (CurStepNr =< Steps
1385 -> Finished=not_finished
1386 ; Finished=finished).
1387
1388 replay_of_current_step_is_possible(CurStepNr,OpName,MatchInfo,list(TransInfos),list(Errors)) :- % Tk
1389 default_match_specs(MS),
1390 try_replay_next_step(MS,CurStepNr,FromID,TransID,_DestId,MatchInfo,TransInfos,Errors),
1391 get_transition_name(FromID,TransID,OpName).
1392
1393 replay_of_current_step_is_possible_with_trans(CurStepNr,FromID,OpTerm,MatchInfo,list(Errors)) :- % ProB2
1394 default_match_specs(MS),
1395 try_replay_next_step(MS,CurStepNr,FromID,TransID,DestID,MatchInfo,_TransInfos,Errors),
1396 create_op_transition(FromID,TransID,DestID,OpTerm).
1397
1398 create_op_transition(FromID,TransID,DestID,op(TransID,OpName,FromID,DestID)) :-
1399 get_transition_name(FromID,TransID,OpName).
1400
1401 % try and replay as much as possible
1402 ireplay_fast_forward(NrReplayed) :-
1403 default_match_specs(MS), ireplay_fast_forward(MS,0,NrReplayed).
1404
1405 ireplay_fast_forward(MatchSpecs,Nr,NrReplayed) :-
1406 replay_current_step(MatchSpecs,_),!,
1407 N1 is Nr+1,
1408 ireplay_fast_forward(MatchSpecs,N1,NrReplayed).
1409 ireplay_fast_forward(_,NrReplayed,NrReplayed).
1410
1411 ireplay_fast_forward_with_trans(CurStepNr,FromID,NrReplayed,Transitions,MatchInfos,Errors) :- % for ProB2
1412 default_match_specs(MS),
1413 ireplay_fast_forward_with_trans(MS,CurStepNr,FromID,0,NrReplayed,Transitions,MatchInfos,Errors).
1414 ireplay_fast_forward_with_trans(MS,CurStepNr,FromID,Nr,NrReplayed,[OpTerm|T1],[MatchInfo|M1],[Errors|E1]) :-
1415 replay_current_step_with_trans(MS,CurStepNr,FromID,OpTerm,MatchInfo,Errors),!,
1416 OpTerm = op(_,_,_,DestID),
1417 N1 is Nr+1,
1418 NextStepNr is CurStepNr+1,
1419 ireplay_fast_forward_with_trans(MS,NextStepNr,DestID,N1,NrReplayed,T1,M1,E1).
1420 ireplay_fast_forward_with_trans(_,_,_,NrReplayed,NrReplayed,[],[],[]).
1421
1422 % replay the currently selected step of the JSON trace, matching one step of the trace with one animation step
1423 replay_current_step(CurStepNr) :- % Tk
1424 default_match_specs(MS), replay_current_step(MS,CurStepNr).
1425
1426 % try and replay current step according to match specifications
1427 replay_current_step(MatchSpecs,CurStepNr) :-
1428 try_replay_next_step(MatchSpecs,CurStepNr,FromID,TransID,_DestID,MatchInfo,_,Errors),!,
1429 extend_trace_by_transition_ids([TransID]), % update state space
1430 assert(json_trace_replayed_info(CurStepNr,replay(FromID,TransID,MatchInfo,Errors))),
1431 increase_step_nr.
1432
1433 %replay_current_step_with_trans(FromID,OpTerm,MatchInfo,Errors) :- % ProB2
1434 % default_match_specs(MS),
1435 % replay_current_step_with_trans(MS,FromID,OpTerm,MatchInfo,Errors).
1436 replay_current_step_with_trans(MatchSpecs,CurStepNr,FromID,OpTerm,MatchInfo,Errors) :- % ProB2
1437 try_replay_next_step(MatchSpecs,CurStepNr,FromID,TransID,DestID,MatchInfo,_,Errors),!,
1438 create_op_transition(FromID,TransID,DestID,OpTerm).
1439
1440 % skip the current replay step and go to the next one
1441 skip_current_ireplay_step(CurStepNr) :-
1442 current_replay_step(CurStepNr),
1443 json_trace_replay_step(CurStepNr,TransSpec,_StaticErrors),
1444 get_transition_spec_txt(TransSpec,TTxt),
1445 formatsilent_with_colour(user_output,[orange],'Skipping replay step ~w : ~w~n',[CurStepNr,TTxt]),
1446 assert(json_trace_replayed_info(CurStepNr,skipped)),
1447 increase_step_nr.
1448
1449 increase_step_nr :-
1450 retract(current_replay_step(CurStepNr)),
1451 S1 is CurStepNr+1,
1452 assert(current_replay_step(S1)).
1453
1454 % :- b_intelligent_trace_replay:load_json_trace_file_for_interactive_replay('/Users/leuschel/git_root/prob_examples/public_examples/B/CBC/ConstantsAndVars/MyAwesomeLift.prob2trace'), b_intelligent_trace_replay:ireplay.
1455
1456
1457