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