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