1 % (c) 2009-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(value_persistance, [set_storage_directory/1,set_storage_directory/2,
6 unset_storage_directory/0,
7 save_constants/1,
8 load_constants/2,
9 cache_is_activated/0, clear_applicable_flag/0,
10 load_partial_constants/3, % load saved constants for sub-machines
11 lookup_cached_transitions/4,
12 add_new_transitions_to_cache/1,
13 add_new_transition_to_cache_from_expanded_state/4, % mainly for execute_modus
14 start_cache_execute_modus/1, stop_cache_execute_modus/0,
15 tcltk_load_constants/1,
16 delete_cache_files/0,
17 delete_cache_files_for_machine/1,
18 show_cache_file_contents/1, % portray contents of cache files
19 print_value_persistance_stats/0,
20 get_value_persistance_stats/1
21 ]).
22
23
24 :- use_module(library(lists)).
25 :- use_module(library(file_systems)).
26 :- use_module(library(fastrw)). % fast_read/2
27
28 :- use_module(debug).
29 :- use_module(tools).
30 :- use_module(error_manager, [add_error/2,add_error/3]).
31 :- use_module(state_space, [transition/3,visited_expression/2,
32 time_out_for_node/1,not_all_transitions_added/1,
33 time_out_for_node/3,transition/4,
34 transition_info/2 %,max_reached_for_node/1
35 ]).
36 :- use_module(succeed_max, [max_reached/1]).
37 :- use_module(preferences).
38 :- use_module(b_machine_hierarchy).
39 :- use_module(specfile, [animation_mode/1, classical_b_mode/0,
40 state_corresponds_to_initialised_b_machine/2]).
41 :- use_module(store, [lookup_value/3]).
42 :- use_module(kernel_objects, [equal_object/2]).
43 :- use_module(bmachine, [b_get_machine_refinement_hierarchy/1,
44 b_top_level_operation/1, get_operation_info/2]).
45 %:- use_module(bmachine_structure, [get_section/3]).
46 :- use_module(b_global_sets, [is_b_global_constant/3,b_global_set/1]).
47 :- use_module(bsyntaxtree).
48 :- use_module(extension('probhash/probhash'),[raw_sha_hash/2]).
49 :- use_module(tools_printing,[format_with_colour_nl/4]).
50 :- use_module(runtime_profiler,[start_profile/2, stop_profile/4]).
51 :- use_module(memoization,[export_memo_state/1, import_memo_state/1]).
52
53 :- use_module(module_information).
54 :- module_info(group,interpreter).
55 :- module_info(description,'This module is responsible for caching constants and operations on disk').
56
57 :- dynamic storage_directory/1.
58 % storage_directory('/home/plagge/svn/alstomprob/examples/cache/').
59 :- volatile storage_directory/1.
60 :- dynamic is_applicable_internal/1.
61 :- volatile is_applicable_internal/1.
62
63 /**********************************************************************/
64 /* common for loading and saving: */
65 /**********************************************************************/
66
67 cache_is_activated :-
68 storage_directory(_).
69
70 cache_is_applicable_for_constants :-
71 cache_is_applicable, get_preference(cache_constants,true).
72 cache_is_applicable_for_transitions :-
73 cache_is_applicable, get_preference(cache_operations,true).
74
75 cache_is_applicable :-
76 is_applicable_internal(Applicable),!,Applicable=true.
77 cache_is_applicable :-
78 cache_is_activated,
79 % b_mode, % only for B models
80 classical_b_mode,
81 b_get_machine_refinement_hierarchy([_]), % only if there is no refinement - we cache no refinements
82 preferences:get_preference(symmetry_mode,off), % with symmetry on: you cannot simply patch operation updates
83 formatinfo('value caching: cache IS applicable',[]),
84 assert_once( is_applicable_internal(true) ),!.
85 cache_is_applicable :-
86 debug_format(19,'value persistance, cache NOT applicable~n',[]),
87 assert_once( is_applicable_internal(false) ),fail.
88
89 :- use_module(tools,[get_parent_directory_of_directory/2]).
90 set_storage_directory(Dir) :- set_storage_directory(Dir,strict).
91 set_storage_directory(Dir,Create) :-
92 unset_storage_directory,
93 (absolute_file_name(Dir,AbsDir,[file_type(directory),access(exist),fileerrors(fail)])
94 -> assertz(storage_directory(AbsDir))
95 ; Create=create_if_needed,
96 get_parent_directory_of_directory(Dir,ParentDir),
97 directory_exists(ParentDir),
98 % parent directory exists; try to create the directory itself
99 absolute_file_name(Dir,AbsDir,[file_type(directory),access(none),fileerrors(fail)]),
100 formatinfo('Trying to create cache directory: ~w',[AbsDir]),
101 make_directory(AbsDir)
102 -> assertz(storage_directory(AbsDir))
103 ; add_error(cache,'Could not set cache directory, directory does not exist: ',Dir)).
104
105 reset_value_persistance :-
106 unset_storage_directory,
107 reset_counters.
108 unset_storage_directory :-
109 retractall(storage_directory(_)),
110 clear_applicable_flag.
111
112 % should be called if e.g. animation mode information changes (csp_and_b mode)
113 clear_applicable_flag :-
114 retractall(is_applicable_internal(_)).
115 :- use_module(eventhandling,[register_event_listener/3]).
116 :- register_event_listener(change_of_animation_mode,clear_applicable_flag, 'Clear Cache Info.').
117 :- register_event_listener(reset_prob,reset_value_persistance, 'Reset Cache').
118
119 %:- use_module(version, [revision/1]).
120 :- use_module(version,[version/4]).
121 get_revision_info(info(V1,V2,V3,V4,ValuePersistanceRevision)) :-
122 % revision(Revision), % revision not used: it differs between probcli and ProB Tcl/Tk
123 version(V1,V2,V3,V4),
124 ValuePersistanceRevision = '$Rev$'.
125
126 collect_computation_parameters(Name,[machine_name(Name)
127 ,prob_revision(Revision)
128 %,machine_hash(Hash)
129 ,constants_signature(ConstSig)
130 |Prefs]) :-
131 find_relevant_preferences(Prefs),
132 get_revision_info(Revision),
133 %machine_hash(Name,Hash),
134 compute_constants_signature(Name,ConstSig).
135
136 /* returns a list of Pref/Value pairs for each preference that is regarded
137 a relevant when computing values for constants. See is_relevant_preference/2
138 below */
139 find_relevant_preferences(Prefs) :-
140 findall(preference(Pref,Value), relevant_preference(Pref,Value), Unsorted),
141 sort(Unsorted,Prefs).
142
143 % value_persistance:find_relevant_preferences(L), member(preference(P,_),L), print(P),nl,fail.
144
145 relevant_preference(Pref,Value) :-
146 preference_category(Pref,Category),
147 ( is_relevant_preference(Pref,Category) -> true; fail), % just to introduce a local cut
148 get_preference(Pref,Value).
149
150 /* is_relevant_preference(+Preference,+Category)
151 is used to specify those preferencees whose values are stored in the constants file.
152 If such a preference changes, the constants have to be recomputed */
153
154 is_relevant_preference(Pref,_) :- nonvar(Pref),
155 irrelevant_preference(Pref),!,fail.
156 is_relevant_preference(_Pref,animation).
157 is_relevant_preference(_Pref,hidden).
158 is_relevant_preference(_Pref,advanced).
159
160 % number_animated_abstractions : only relevant for Event-B + if refinement
161 irrelevant_preference(cache_operations_runtime_limit). % only influences what gets stored; re-use always safe
162 irrelevant_preference(cache_constants). % ditto
163 irrelevant_preference(cache_operations). % ditto
164 irrelevant_preference(clash_strict_checks). % no influence on values computed
165 irrelevant_preference(strict_raise_warnings). % no influence on values computed
166 irrelevant_preference(warn_if_definition_hides_variable). % no influence on values computed
167 %irrelevant_preference(strict_raise_enum_warnings). % no sure if it can affect outcome in meaningful; could result in symbolic instead values??
168 irrelevant_preference(jvm_parser_heap_size_mb). % no influence on values computed
169 irrelevant_preference(jvm_parser_additional_args). % ditto
170 irrelevant_preference(use_safety_ltl_model_checker). % ditto
171 irrelevant_preference(store_only_one_incoming_transition). % ditto
172 irrelevant_preference(forget_state_space). % ditto
173 irrelevant_preference(type_check_definitions). % ditto
174 irrelevant_preference(expand_avl_upto). % only affects pretty-printing
175 irrelevant_preference(bool_expression_as_predicate). % only used inside REPL/eval
176 irrelevant_preference(use_large_jvm_for_parser).
177 irrelevant_preference(expand_forall_upto). % only relevant in predicate analysis
178 irrelevant_preference(time_out). % if time_out occurs: no re-use anyway
179 irrelevant_preference(performance_monitoring_on). % just prints messages
180 irrelevant_preference(performance_monitoring_expansion_limit).
181 irrelevant_preference(kodkod_for_components) :- \+ preference(use_solver_on_load,kodkod).
182 irrelevant_preference(do_neginvariant_checking). % just indicates whether invariant evaluated doubly
183 irrelevant_preference(provide_trace_information). % just provides feedback; should not change values
184 irrelevant_preference(prob_profiling_on). % ditto
185 irrelevant_preference(prob_source_profiling_on). % ditto
186 irrelevant_preference(use_closure_expansion_memoization). % only influences performance
187 irrelevant_preference(warn_when_expanding_infinite_closures). % only generates extra warnings
188 irrelevant_preference(use_small_window).
189 irrelevant_preference(tk_show_source_pane).
190 irrelevant_preference(check_prolog_b_ast).
191 irrelevant_preference(use_font_size_for_columns).
192 irrelevant_preference(user_is_an_expert_with_accessto_source_distribution).
193 irrelevant_preference(default_to_runtime_type_checking_on_startup_for_expert).
194 irrelevant_preference(number_of_recent_documents).
195 irrelevant_preference(number_of_searched_patterns).
196 irrelevant_preference(number_of_replaced_patterns).
197 irrelevant_preference(number_of_eval_history_elements).
198 irrelevant_preference(number_of_eval_csp_history_elements).
199 irrelevant_preference(number_of_checked_ltl_formulas).
200 irrelevant_preference(machines_path).
201 irrelevant_preference(tlc_number_of_workers).
202 irrelevant_preference(tlc_use_prob_constant_setup).
203 irrelevant_preference(unsat_core_algorithm).
204
205 irrelevant_preference(deterministic_trace_replay).
206 irrelevant_preference(dot_use_ps_viewer).
207 %irrelevant_preference(double_evaluation_when_analysing).% not used when computing constants or events
208 irrelevant_preference(generate_minimal_nr_of_testcases).
209 irrelevant_preference(ltl_to_ba_tool).
210 irrelevant_preference(path_to_atb_krt).
211 irrelevant_preference(path_to_bcomp).
212 irrelevant_preference(path_to_clingo).
213 irrelevant_preference(path_to_cspm).
214 irrelevant_preference(path_to_csp_typechecker).
215 irrelevant_preference(path_to_dot).
216 irrelevant_preference(path_to_dotty).
217 irrelevant_preference(path_to_fdr).
218 irrelevant_preference(path_to_fuzz). %% ??
219 irrelevant_preference(path_to_latex).
220 irrelevant_preference(path_to_ltsmin).
221 irrelevant_preference(path_to_probe).
222 irrelevant_preference(path_to_ps_viewer).
223 irrelevant_preference(path_to_spin).
224 irrelevant_preference(path_to_text_editor).
225 irrelevant_preference(path_to_text_editor_launch).
226 irrelevant_preference(repl_cache_parsing).
227 irrelevant_preference(show_bvisual_formula_explanations).
228 irrelevant_preference(show_bvisual_formula_functor_from).
229 irrelevant_preference(show_bvisual_proof_info_icons).
230 irrelevant_preference(show_function_tuples_in_property).
231 irrelevant_preference(symbolic_mc_try_other_solvers).
232 irrelevant_preference(use_scope_predicate).
233
234 irrelevant_preference(path_to_java).
235 irrelevant_preference(translate_print_all_sequences).
236 irrelevant_preference(translate_print_cs_style_sequences).
237 irrelevant_preference(view_probcli_errors_using_bbresults).
238 irrelevant_preference(trace_upon_error).
239 irrelevant_preference(error_log_file).
240 irrelevant_preference(tk_custom_state_viewer_padding).
241 irrelevant_preference(tk_custom_state_viewer_str_padding).
242 irrelevant_preference(tk_custom_state_viewer_font_name).
243 irrelevant_preference(tk_custom_state_viewer_font_size).
244 irrelevant_preference(use_tk_custom_state_viewer).
245 irrelevant_preference(translate_suppress_rodin_positions_flag).
246 irrelevant_preference(translate_ids_to_parseable_format).
247 irrelevant_preference(translate_print_frozen_infos).
248 irrelevant_preference(translate_print_typing_infos).
249 irrelevant_preference(translate_force_all_typing_infos).
250 irrelevant_preference(prob_lastchangedate_info). % what about prob_revision_info ?
251 irrelevant_preference(X) :- preference_category(X,Cat), irrelevant_category(Cat).
252
253 irrelevant_category(alloy2b).
254 irrelevant_category(cbc_commands). %cbc_provide_explanations
255 irrelevant_category(distb).
256 irrelevant_category(dot).
257 irrelevant_category(dot_definitions).
258 irrelevant_category(dot_event_hierarchy).
259 irrelevant_category(dot_formula_tree).
260 irrelevant_category(dot_machine_hierarchy).
261 irrelevant_category(dot_graph_generator).
262 irrelevant_category(dot_projection).
263 irrelevant_category(dot_state_graph).
264 irrelevant_category(dot_state_space).
265 irrelevant_category(dot_variable_modification).
266 irrelevant_category(gui_prefs).
267 irrelevant_category(latex).
268 irrelevant_category(mc_dc_commands).
269 irrelevant_category(smtlib2b).
270 irrelevant_category(state_as_graph).
271 irrelevant_category(syntax_highlighting).
272 irrelevant_category(table_commands).
273 irrelevant_category(trace_generator).
274 irrelevant_category(visb).
275 irrelevant_category(wd_commands).
276 % alternate categories already covered by dot category:
277 %irrelevant_category(state_as_graph).
278 %irrelevant_category(dot_graph_generator).
279 %irrelevant_category(dot_state_space).
280
281 compute_constants_signature(Name,constsig(Name,PropHash,Sublist)) :-
282 properties_hash(Name,PropHash),
283 findall(Sig,
284 ( referenced_machine_with_constants_or_properties(Name,RefName),
285 compute_constants_signature(RefName,Sig)),
286 SubSigs),
287 sort(SubSigs,Sublist).
288
289 referenced_machine_with_constants_or_properties(OrigName,RefName) :-
290 referenced_machine(OrigName,RefName,_,_),
291 machine_has_constants_or_properties_trans(RefName).
292
293 machine_has_constants_or_properties_trans(Name) :-
294 machine_has_constants_or_properties(Name),!.
295 machine_has_constants_or_properties_trans(Name) :-
296 referenced_machine(Name,Ref,_,_),
297 machine_has_constants_or_properties_trans(Ref),!.
298 machine_has_constants_or_properties(Name) :-
299 machine_identifiers(Name,_Params,Sets,_AVars,_CVars,AConsts,CConsts),
300 ( Sets=[_|_] ; AConsts==[_|_] ; CConsts=[_|_]),!.
301
302 referenced_machine(SrcName,DstName,Type,Prefix) :-
303 machine_references(SrcName,Refs),
304 member(ref(Type,DstName,Prefix),Refs).
305
306 /**********************************************************************/
307 /* saving values of constants */
308 /**********************************************************************/
309 :- use_module(state_packing).
310
311 save_constants(MaxReached) :-
312 cache_is_applicable,
313 main_machine_name(Name), % this fails e.g. in Z mode
314 \+ constants_loaded_from_file(Name), % we have just loaded the constants from file; no need to re-write them
315 !,
316 save_constants1(Name,MaxReached).
317 %(machine_name(MName), save_constants1(MName,MaxReached), fail ; true). % this would save all constants; not just the one's from the main machine; but we should probably only save the constants whose value is already deterministic in the original included machine
318 save_constants(_MaxReached).
319
320 save_constants1(Name,MaxReached) :-
321 (save_constants2(Name,MaxReached) -> true ; add_error(value_persistance,'Storing constants failed for:',Name)).
322
323 save_constants2(Name,MaxReached) :-
324 statistics(runtime,[Start,_]),
325 statistics(walltime,[WStart,_]),
326 save_constants_for_machine(Name,MaxReached),
327 statistics(runtime,[Stop,_]), Time is Stop - Start,
328 statistics(walltime,[WStop,_]), WTime is WStop - WStart,
329 %% tools:print_memory_used_wo_gc,
330 formatinfo('value caching: storing constants for ~w (max_reached: ~w) (~w [~w] ms).',
331 [Name,MaxReached,Time,WTime]).
332
333 save_constants_for_machine(Name,MaxReached) :-
334 find_constants(Name,Constants), % At the moment this only returns top-level constants and is ignored!
335 Constants = [_|_], % at least one constant exists, check before computing findall !
336 find_constants_stores(Stores), % find all concrete_constants(_) nodes in state_space
337 is_usable_data(Name,Constants,Stores),!,
338 save_constants_stores(Name,MaxReached,Constants,Stores).
339 save_constants_for_machine(Name,_MaxReached) :-
340 formatinfo('value caching: no constants stored for ~w',[Name]).
341
342 % called by add_new_transition_to_cache_from_expanded_state:
343 save_constants_from_expanded_state(SingleState) :-
344 cache_is_applicable_for_constants,
345 main_machine_name(Name),
346 \+ constants_loaded_from_file(Name), % we have just loaded the constants from file; no need to re-write them
347 SingleState = concrete_constants(Store),
348 length(Store,Len), formatinfo('value caching: saving ~w constants from expanded state',[Len]),
349 find_constants(Name,Constants),
350 !,
351 MaxReached=true, % we do not know if there are more constants states
352 save_constants_stores(Name,MaxReached,Constants,[Store]).
353 save_constants_from_expanded_state(_) :-
354 (cache_is_applicable,main_machine_name(Name)
355 -> formatinfo('value caching: no constants stored for ~w',[Name]) ; true).
356
357 % TODO: at the moment memoisation closures will not work and Memo id info also need to be stored and re-loaded
358 save_constants_stores(Name,MaxReached,Constants,Stores) :-
359 debug_println(9,saving_constants(Name)),
360 maplist(generate_bindings(Constants),Stores,ConstantBindings), % first arg. (Constants) currently not used
361 collect_computation_parameters(Name,CompParams),
362 length(ConstantBindings,Len),formatinfo('value caching: saving ~w constant solutions of machine ~w to file.',[Len,Name]),
363 export_memo_state(MemoState),
364 bb_inc_by(value_persistance_stored_constants,Len),
365 save_constants_values_into_file(Name,CompParams,ConstantBindings,MemoState,MaxReached).
366
367 find_main_constants(Constants) :- b_get_machine_constants(C),
368 sort(C,Constants).
369 find_constants(Name,Constants) :-
370 machine_identifiers(Name,Params,_Sets,_AVars,_CVars,AbstractConstants,ConcreteConstants),
371 ( Params=[_|_]
372 -> add_warning(value_persistance,'Parameters not yet supported.'), % ok to just issue warning ?? or should we generate error ?
373 fail
374 ; true),
375 append(AbstractConstants,ConcreteConstants,RawConstants),
376 maplist(get_raw_identifier,RawConstants,Unsorted),
377 sort(Unsorted,Constants).
378 get_raw_identifier(identifier(_Pos,Id),Id).
379 get_raw_identifier(description(_Pos,_Desc,Raw),Id) :- get_raw_identifier(Raw,Id).
380
381 /* Returns the stores of values in the state space that contain values for contants */
382 find_constants_stores(Stores) :-
383 findall(S,
384 ( transition(root,Trans,I),
385 functor(Trans,'$setup_constants',_),
386 visited_expression(I,concrete_constants(S))
387 ),
388 Stores).
389
390 /* is_usable_data/2 succeeds if there are constants that are ready to store */
391 is_usable_data(MachName,Constants,Stores) :-
392 % at least one constant exists
393 Constants = [_|_],
394 % at least one state with computed constants was generated
395 Stores = [_|_],
396 % all constants have been computed
397 (not_all_transitions_added(root)
398 -> formatwarn('value caching: not storing constants for ~w as not all transitions computed.',[MachName]), fail
399 ; true),
400 % no time-out in the root node
401 (time_out_for_node(root)
402 -> formatwarn('value caching: not storing constants for ~w as TIME_OUT occured.',[MachName]), fail
403 ; true).
404
405 %generate_bindings(Constants,Store,ConstantsBinding) :-
406 % maplist(generate_binding2(Store),Constants,ConstantsBinding).
407 %generate_binding2(Store,Constant,bind(Constant,Value)) :-
408 % lookup_value(Constant,Store,Value).
409 generate_bindings(_Constants,Store,ConstantsBinding) :-
410 % TODO: review this
411 Store = ConstantsBinding.
412
413 save_constants_values_into_file(Name,CompParams,ConstantBindings,MemoState,MaxReached) :-
414 storage_file_name(constants,Name,Filename),
415 open(Filename,write,S,[type(binary)]),
416 call_cleanup(save_values_into_file2(S,CompParams,ConstantBindings,MemoState,MaxReached),
417 my_close(S)).
418 save_values_into_file2(S,CompParams,ConstantBindings,MemoState,MaxReached) :-
419 fast_write(S,comp_parameters(CompParams)),
420 fast_write(S,maximum_reached(MaxReached)),
421 fast_write(S,memo_state(MemoState)),
422 maplist(write_bind(S,constants),ConstantBindings),
423 fast_write(S,end_of_file).
424 write_bind(S,Type,Store) :-
425 preferences:get_preference(use_state_packing,PREF),
426 preferences:set_preference(use_state_packing,false),
427 state_packing:pack_values(Store,PS), % does not seem to bring major performance benefit; but reduces file size
428 % print(packed(Store,PS)),nl,
429 preferences:set_preference(use_state_packing,PREF),
430 fast_write(S,values(Type,PS)).
431 % fast_write(S,values(Type)), fast_write_list(PS,S). % should we do something like this to reduce memory consumption ?
432
433 %fast_write_list([],S) :- fast_write(S,end_of_list).
434 %fast_write_list('$bind_var'(Var,Val,T),S) :- fast_write(S,bind(Var,Val)), fast_write_list(T,S).
435
436 /* compute the full file name for the stored constants for the machine
437 the predicate uses the specified directory where constants values
438 should be stored */
439 storage_file_name(Type,MachineName,FullName) :-
440 cache_file_suffix(Type,Suffix),!,
441 storage_directory(Directory),
442 atom_concat(MachineName,Suffix,Name),
443 atom_concat(Directory,Name,FullName).
444 storage_file_name(Type,MachineName,_) :-
445 add_internal_error('Illegal cache file type: ',storage_file_name(Type,MachineName,_)),fail.
446
447 cache_file_suffix(constants,'.probcst').
448 cache_file_suffix(operations_index,'.probops').
449 cache_file_suffix(operations_data,'.opdata').
450
451 cache_file_type(constants).
452 cache_file_type(operations_index).
453
454 /**********************************************************************/
455 /* load constants */
456 /**********************************************************************/
457
458 % a predicate to see which constant values have been saved
459 tcltk_load_constants(list(CS)) :-
460 load_constants(ConstantsStores,_),
461 maplist(translate:translate_bstate,ConstantsStores,CS).
462
463
464 /* load_constants/2 returns a list of stores if the constants have been
465 saved before for the same computation parameters.
466 The predicate fails if no constants can be loaded.
467 MaxReached is 'true' if the maximum number of computed solutions was reached
468 or 'false' otherwise.
469 */
470
471 :- dynamic constants_loaded_from_file/1.
472 :- volatile constants_loaded_from_file/1.
473 % load constants for main machine
474 load_constants(ConstantStores,MaxReached) :-
475 cache_is_applicable_for_constants, % check if storing/re-using constants is activated
476 main_machine_name(Name),
477 machine_constants_cache_file_exists(Name,FullName),
478 open(FullName,read,S,[type(binary)]),
479 call_cleanup(load_constants2(S,Name,ConstantStores,MaxReached),
480 my_close(S)),!.
481 load_constants2(S,Name,ConstantStores,MaxReached) :-
482 load_parameters(S,StoredParameters), % if the relevant computation parameters
483 collect_computation_parameters(Name,CurrentParameters), % are different, we cannot re-use the
484 (compare_computation_parameters(StoredParameters,CurrentParameters) % values stored in the file
485 -> true
486 ; formatinfo('value caching: parameters changed; not reusing previously computed constants for ~w.',[Name]),
487 fail
488 ),
489 load_max_reached(S,MaxReached),
490 load_constant_values(S,ConstantStores),
491 bb_inc(value_persistance_constants_loaded),
492 (debug_mode(off)
493 -> formatgood('value caching: re-using stored solutions for constants for ~w.', [Name])
494 ; length(ConstantStores,Len),
495 get_ids(ConstantStores,CstNames),
496 formatgood('value caching: re-using ~w stored solutions for constants ~w for ~w.',
497 [Len,CstNames,Name])
498 ),
499 assert_once( constants_loaded_from_file(Name) ).
500
501
502 machine_constants_cache_file_exists(Name,FullName) :-
503 cache_file_exists(constants,Name,FullName).
504 cache_file_exists(Type,Name,FullName) :-
505 storage_file_name(Type,Name,FullName),
506 (file_exists(FullName)
507 -> debug_format(19,'value caching: ~w cache file ~w exists for ~w.~n',[Type, FullName, Name])
508 ; get_tail_filename(FullName,Tail),
509 formatinfo('value caching: ~w cache file ~w does not yet exist for ~w.',[Type, Tail, Name]),
510 fail
511 ).
512
513 load_parameters(S,StoredParameters) :-
514 safe_constants_read(S,comp_parameters(StoredParameters)).
515
516 load_max_reached(S,MR) :-
517 safe_constants_read(S,maximum_reached(MR)).
518
519
520 load_constant_values(S,Stores) :-
521 safe_constants_read(S,memo_state(MS)),
522 import_memo_state(MS),
523 load_constant_values2(S,Stores).
524 load_constant_values2(S,Stores) :-
525 safe_constants_read(S,Term),
526 ( Term = end_of_file ->
527 Stores = []
528 ; Term = values(constants,Store) ->
529 unpack_constants(Store,UPS),
530 Stores = [UPS|Rest],
531 load_constant_values2(S,Rest)).
532
533 unpack_constants(Store,UPS) :-
534 preferences:get_preference(use_state_packing,PREF),
535 preferences:set_preference(use_state_packing,false),
536 state_packing:unpack_values(Store,UPS),
537 % print(unpacked(Store,UPS)),nl,
538 preferences:set_preference(use_state_packing,PREF).
539
540 safe_constants_read(S,Term) :-
541 read_syntax_safe(S,T,Error),
542 ( Error==true ->
543 write('Invalid cache file content. File skipped.\n'),
544 fail
545 ;
546 Term = T).
547
548 % load constant solutions from subsidiary referenced machines
549 load_partial_constants(ConstantsBindings,InProperties,OutProperties) :-
550 % TODO: - check if parameters / constraints have been used (what are the implications?)
551 cache_is_applicable_for_constants, % check if storing/re-using constants is activated
552 main_machine_name(Name),
553 findall( partial(MName,NewBindings),
554 try_to_reuse_referenced_machine(Name,MName,NewBindings),
555 PSol),
556 PSol = [_|_],!,
557 remove_evaluated_properties(PSol,InProperties,OutProperties),
558 select_and_apply_binding(PSol,ConstantsBindings).
559 load_partial_constants(_ConstantsBindings,Properties,Properties).
560
561 /**********************************************************************/
562
563 :- meta_predicate open_cache_file(+,+,-,0).
564 open_cache_file(Type,Name,Stream,Call) :-
565 cache_file_exists(Type,Name,FullName),
566 my_open(FullName,read,Stream,[type(binary)]),
567 debug_format(19,'Opened cache file ~w~n',[FullName]),
568 call_cleanup( (call(Call),!),my_close(Stream)).
569
570 /**********************************************************************/
571
572 :- dynamic referenced_machine/1.
573
574 :- mode try_to_reuse_referenced_machine(+,-,-).
575 try_to_reuse_referenced_machine(OrigName,Name,Bindings) :-
576 retractall(referenced_machine(_)),
577 try_to_reuse_referenced_machine1(OrigName,Name,Bindings).
578 try_to_reuse_referenced_machine1(OrigName,Name,Bindings) :-
579 referenced_machine_with_constants_or_properties(OrigName,RefName),
580 (referenced_machine(RefName) -> fail ; true), % we have already processed it
581 assert(referenced_machine(RefName)),
582 try_to_reuse_referenced_machine2(OrigName,RefName,Name,Bindings).
583 try_to_reuse_referenced_machine2(OrigName,RefName,Name,Bindings) :-
584 % try to re-use values of a machine directly referenced by OrigName that
585 % contains constants
586 open_cache_file(constants,RefName,S,try_load_ref_values2(RefName,OrigName,S,Bindings1)),
587 !,
588 RefName = Name,
589 Bindings1 = Bindings.
590 try_to_reuse_referenced_machine2(_,RefName,Name,Bindings) :-
591 % using the directly referenced machine failed, using a machine
592 % that is referenced by the referenced machine
593 try_to_reuse_referenced_machine1(RefName,Name,Bindings).
594
595 try_load_ref_values2(RefName,OrigName,S,Bindings) :-
596 check_if_machine_has_no_parameters(RefName),
597 load_parameters(S,StoredParameters),
598 check_if_all_constants_computed(RefName,S),
599 collect_computation_parameters(RefName,CurrentParameters),
600 compare_computation_parameters(StoredParameters,CurrentParameters),
601 load_constant_values(S,Bindings),
602 bb_inc(value_persistance_ref_constants_loaded),
603 (debug_mode(off)
604 -> formatgood('value caching: re-using stored solutions for constants for referenced machine ~w.', [RefName])
605 ; length(Bindings,Len),
606 get_ids(Bindings,CstNames),
607 formatgood('value caching: re-using ~w previously computed solutions for constants ~w of referenced machine ~w within ~w.',[Len,CstNames,RefName,OrigName])
608 % TODO: show names of constants ...
609 ).
610
611 get_name(bind(ID,_),ID) :- !.
612 get_name(X,X).
613
614 get_ids([Binding|_],Names) :- maplist(get_name,Binding,Names).
615
616 check_if_machine_has_no_parameters(RefName) :-
617 machine_identifiers(RefName,Params,_Sets,_AVars,_CVars,_AConsts,_CConsts),
618 ( Params=[] -> true
619 ;
620 formatwarn('value caching: constants of referenced machine ~w are not used because it uses parameters',[Params]),
621 fail).
622
623 compare_computation_parameters([],[]) :- !.
624 compare_computation_parameters([CH|CT],[SH|ST]) :-
625 !,compare_computation_parameters(CH,SH),
626 compare_computation_parameters(CT,ST).
627 compare_computation_parameters(op_comp_parameters(C),op_comp_parameters(S)) :- !,
628 compare_computation_parameters(C,S).
629 compare_computation_parameters(C,C) :- !.
630 compare_computation_parameters(C,S) :-
631 formatwarn('value caching: parameter difference:~ncurrent is ~w,~n stored is ~w.',[C,S]),
632 fail.
633
634 check_if_all_constants_computed(_RefName,S) :-
635 % make sure that all solutions have been generated
636 load_max_reached(S,false),!.
637 check_if_all_constants_computed(RefName,_S) :-
638 formatwarn('value caching: constants for referenced machine ~w not used because not all solutions were computed.',[RefName]),
639 fail.
640
641 select_and_apply_binding(Solutions,Store) :-
642 maplist(select_solutions,Solutions,Bindings),
643 maplist(select_and_apply_binding2(Store),Bindings).
644 select_and_apply_binding2(Store,Binding) :-
645 maplist(apply_binding(Store),Binding).
646 apply_binding(Store,bind(Id,Value)) :-
647 lookup_value(Id,Store,SValue),
648 equal_object(SValue,Value).
649 select_solutions(partial(_Name,Bindings),Binding) :-
650 member(Binding,Bindings).
651
652 :- use_module(bmachine,[get_machine_file_number/4]).
653 machine_file_number(Name,Nr) :-
654 get_machine_file_number(Name,Ext,Nr,_),
655 Ext \= 'def',!.
656 machine_file_number(Name,Nr) :-
657 add_error(value_persistance,'Could not find machine name:',Name),
658 bmachine:portray_filenumbers,
659 Nr = -99.
660
661 :- use_module(tools_positions, [get_position_filenumber/2]).
662 % remove the properties from those machines whose constants have already been set from file
663 remove_evaluated_properties(PSol,InProperties,OutProperties) :-
664 findall(Name,member(partial(Name,_),PSol),UnsortedNames),
665 sort(UnsortedNames,Names),
666 maplist(machine_file_number,Names,FileNumbers),
667 debug_println(9,filtering(Names,FileNumbers)),
668 conjunction_to_list(InProperties,InAsList),
669 % exclude all properties who are in one of the files for which we have restored (all) constant values
670 exclude(belongs_to_file(FileNumbers),InAsList,OutAsList), % this is exclude/3 from library(lists)
671 conjunct_predicates(OutAsList,OutProperties).
672 belongs_to_file(FileNumbers,TPred) :-
673 get_texpr_info(TPred,Info),
674 memberchk(nodeid(Pos),Info),
675 get_position_filenumber(Pos,FilePos),
676 memberchk(FilePos,FileNumbers).
677
678 /**********************************************************************/
679
680 :- dynamic loadable_operation/5, storable_operation/4, stored_transition/4, operation_has_stored_transition/1,
681 operations_index_file_opened/2.
682 :- volatile loadable_operation/5, storable_operation/4, stored_transition/4, operation_has_stored_transition/1,
683 operations_index_file_opened/2.
684
685 initialise_operation_caching :-
686 clear_applicable_flag,
687 cache_is_applicable_for_transitions,
688 main_machine_name(MachName), % if we have no machine name, fail silently (for default machine)
689 !,
690 % check wich operations are cachable and prepare information for them
691 debug_println(9,initialise_operation_caching(MachName)),
692 retract_all_op_cache_data,
693 try_to_load_operations_cache_for_all_machines,
694 %initialise_op_cache_for_machine(MachName),
695 find_loadable_machines(LoadableMachines),
696 formatinfo('value caching: loadable machines: ~w',[LoadableMachines]),
697 maplist(initialise_op_cache_for_machine,LoadableMachines).
698 initialise_operation_caching :-
699 retract_all_op_cache_data.
700
701 initialise_op_cache_for_machine(loadable(_,MachName)) :-
702 bb_inc(value_persistance_op_cache_machines),
703 get_operation_names(MachName,OperationNames),
704 maplist(init_operation_cache(MachName),OperationNames),
705 save_operations_index_cache(MachName,OperationNames),
706 open_data_file(MachName).
707
708 :- use_module(eventhandling,[register_event_listener/3]).
709 :- register_event_listener(specification_initialised,initialise_operation_caching,
710 'Initialise operation caching info.').
711
712
713 retract_all_op_cache_data :-
714 retractall(constants_loaded_from_file(_)),
715 retractall(loadable_operation(_,_,_,_,_)),
716 retractall(storable_operation(_,_,_,_)),
717 retractall(stored_transition(_,_,_,_)),
718 retractall(operation_has_stored_transition(_)),
719 retractall(cst_id_to_hash(_,_)),
720 retractall(constant_pre_hash_cache_active),
721 reset_operations_index_file_opened.
722
723 % operations_index_file_opened(Stream) contains a possibly open stream for the operations (probops) file
724 reset_operations_index_file_opened :-
725 ( operations_index_file_opened(M,S) ->
726 my_close(S),retractall(operations_index_file_opened(M,_)),
727 reset_operations_index_file_opened
728 ; true).
729
730 get_operation_names(MachName,OperationNames) :-
731 if(machine_operations(MachName,RawOperationNames),
732 maplist(get_raw_identifier,RawOperationNames,OperationNames),
733 add_error_fail(value_persistance,'Cannot find machine:',MachName)).
734
735 try_to_load_operations_cache_for_all_machines :-
736 find_loadable_machines(LoadableMachines),
737 maplist(try_to_load_operations_cache,LoadableMachines).
738
739 try_to_load_operations_cache(loadable(Type,MachName)) :-
740 formatinfo('value caching: try loading cached operations for machine ~w (~w)',[MachName,Type]),
741 get_operations_computation_parameters(MachName,OpParams),
742 open_cache_file(operations_index,MachName,S,read_cached_operations(S,MachName,OpParams,Error)),!,
743 ( Error==true ->
744 formatwarn('value caching: corrupted index file for machine ~w, deleting file.',[MachName]),
745 delete_cache_file(MachName)
746 ; true).
747 try_to_load_operations_cache(loadable(main,MachName)) :-
748 % delete the data file if one exists -- only for main machine
749 delete_cache_file(MachName),!.
750 try_to_load_operations_cache(_Loadable).
751
752 delete_cache_file(MachName) :-
753 cache_file_exists(operations_data,MachName,Filename),!,
754 formatinfo('value caching: deleting opdata cache file of machine ~w: ~w',[MachName,Filename]),
755 delete_file(Filename).
756
757 read_cached_operations(S,MachName,CurrentOpParams,SyntaxError) :-
758 read_syntax_safe(S,StoredOpParams,SyntaxError),
759 ( SyntaxError==true -> true
760 ; compare_computation_parameters(StoredOpParams,CurrentOpParams) ->
761 formatgood('value caching: parameters unchanged, re-use of stored operations possible for ~w',[MachName]),
762 read_cached_operations2(S,MachName,SyntaxError)
763 ;
764 formatwarn('value caching: general computations parameters have changed, no re-use of stored operations',[]),
765 debug_params(CurrentOpParams,StoredOpParams),
766 fail).
767 read_cached_operations2(S,MachName,SyntaxError) :-
768 read_syntax_safe(S,Term,SyntaxError),
769 ( SyntaxError==true -> true
770 ; Term == end_of_file -> true
771 ; read_cached_operations3(Term,MachName) ->
772 read_cached_operations2(S,MachName,SyntaxError)
773 ;
774 functor(Term,F,A),
775 formatwarn('value caching: unrecognised entry in cache file for ~w: ~w/~w~n',[MachName,F,A]),
776 fail
777 ).
778 debug_params(op_comp_parameters(A),op_comp_parameters(B)) :- !,
779 debug_params(A,B).
780 debug_params(preference(P,A),preference(P,B)) :- !,
781 (A=B -> true ; print(P), print(':'), print(A/B), print(' ')).
782 debug_params([],[]) :- !,nl.
783 debug_params([preference(P1,A)|CT],[preference(P2,B)|ST]) :- !,
784 (P1=P2 -> (A=B -> true ; format('Difference in preference ~w : current = ~w, stored = ~w~n',[P1,A,B])),
785 debug_params(CT,ST)
786 ; P1 @< P2 -> format('New preference ~w = ~w (not stored)~n',[P1,A]), debug_params(CT,[preference(P2,B)|ST])
787 ; format('Stored preference removed ~w = ~w~n',[P2,B]), debug_params([preference(P1,A)|CT],ST)
788 ).
789 debug_params([Cur|CT],[Stored|ST]) :- !,
790 debug_params(Cur,Stored),
791 debug_params(CT,ST).
792 debug_params(A,B) :- (A=B -> true ; print(A/B),nl).
793
794 % -----------------
795
796 % a way to clean/delete all cache files for current machine; useful for tests
797 delete_cache_files :-
798 reset_operations_index_file_opened, % to ensure we can delete the files
799 find_loadable_machines(LoadableMachines),
800 maplist(delete_cache_files_for_machine(_),LoadableMachines).
801
802 % delete a single cache file only
803 delete_cache_files_for_machine(Machine) :-
804 reset_operations_index_file_opened, % to ensure we can delete the files
805 delete_cache_files_for_machine(_,loadable(main,Machine)).
806
807 delete_cache_files_for_machine(ExpectedType,loadable(_MType,MachName)) :-
808 cache_file_suffix(Type,_), % backtracks and also matches operations_data
809 (var(ExpectedType) -> true ; ExpectedType=Type),
810 (cache_file_exists(Type,MachName,FullName)
811 -> get_tail_filename(FullName,FF),
812 format_with_colour_nl(user_output,[blue],'Deleting ~w cache file for machine ~w: ~w',[Type,MachName,FF]),
813 delete_file(FullName)
814 ; format_with_colour_nl(user_output,[blue],'No cache file of type ~w found for machine ~w',[Type,MachName])
815 ),fail.
816 delete_cache_files_for_machine(_,_).
817
818 :- meta_predicate show_cache_file_contents_for_machine(-,0,-,-).
819 % a small utility to print out the contents of the cache files:
820
821 % called by -show_cache and -show_cache_verbose commands of probcli
822 show_cache_file_contents(Verbose) :-
823 (storage_directory(Dir) -> true ; Dir='?'),
824 format_with_colour_nl(user_output,[blue],'Cache contents (directory: ~w)',[Dir]),
825 reset_operations_index_file_opened, % otherwise on Windows we are not able to open the probobs file as it is already open
826 show_cache_file_operations(Verbose).
827
828
829 show_cache_file_operations(Verbose) :-
830 reset_operations_index_file_opened, % otherwise on Windows we are not able to open the probobs file as it is already open
831 find_loadable_machines(LoadableMachines),
832 maplist(show_cache_file_contents_for_machine(_,show_facts(S,Verbose),S),LoadableMachines).
833
834 cache_applicable(operations) :- !, cache_is_applicable_for_transitions.
835 cache_applicable(constants) :- !, cache_is_applicable_for_constants.
836 cache_applicable(_) :- cache_is_applicable.
837
838 :- use_module(tools,[get_tail_filename/2]).
839 show_cache_file_contents_for_machine(ExpectedType,Call,Stream,loadable(_MType,MachName)) :-
840 cache_file_type(Type), % backtracks
841 (var(ExpectedType) -> true ; ExpectedType=Type),
842 (cache_file_exists(Type,MachName,FullName) ->
843 get_tail_filename(FullName,FF),
844 format_with_colour_nl(user_output,[blue],'Contents of ~w cache file for machine ~w: ~w',[Type,MachName,FF]),
845 (cache_applicable(Type) -> true
846 ; format_with_colour_nl(user_output,[blue],' (Cache not applicable for ~w)',[Type])),
847 (open_cache_file(Type,MachName,Stream,Call)
848 -> format_with_colour_nl(user_output,[blue],'End of contents (~w)',[FF])
849 ; format_with_colour_nl(user_error,[red],'Failed to show cache contents of ~w.',[FF])
850 )
851 ; \+ cache_applicable(Type) -> true
852 ; Type=operations_index, machine_operations(MachName,_)
853 -> format_with_colour_nl(user_output,[blue],'No cache file of type ~w for machine with operations ~w.~n',[Type,MachName])
854 ; Type=constants, machine_has_constants(MachName)
855 -> format_with_colour_nl(user_output,[blue],'No cache file of type ~w for machine with constants ~w.~n',[Type,MachName])
856 ; debug_format(19,'No cache file of type ~w for machine ~w.~n',[Type,MachName]) % TODO: check if MachName has constants,...
857 ),
858 fail.
859 show_cache_file_contents_for_machine(_,_,_,_).
860
861 show_facts(S,Verbose) :- read_syntax_safe(S,Term,Error),
862 (nonvar(Error)
863 -> add_error(value_persistance,'Error occured reading cache stream: ',S)
864 ; Term = end_of_file -> reset_and_show_stats
865 ; portray_content_fact(Term,Verbose),
866 show_facts(S,Verbose)).
867
868 :- use_module(tools_strings,[get_hex_bytes/2]).
869 :- use_module(translate,[print_bstate/1]).
870 % operations:
871 portray_content_fact(op_comp_parameters(OpParams),Verbose) :- OpParams=[H|_], !,
872 format_verbose(Verbose,' op_comp_parameters([~w,...]).~n',[H]).
873 portray_content_fact(operation(OpName,Hash),_) :- get_hex_bytes(Hash,Hex), !,
874 format(' operation(~w,~s).~n',[OpName,Hex]).
875 portray_content_fact(trans_index(OpName,Hash,Index),Verbose) :- get_hex_bytes(Hash,Hex), !,
876 format_verbose(Verbose,' transition(~w,~s,~w).~n',[OpName,Hex,Index]),
877 inc_counter(OpName).
878 % constants:
879 portray_content_fact(comp_parameters(OpParams),Verbose) :- OpParams=[H|_], !,
880 format_verbose(Verbose,' comp_parameters([~w,...]).~n',[H]).
881 portray_content_fact(maximum_reached(MaxReached),Verbose) :- !,
882 format_verbose(Verbose,' maximum_reached(~w).~n',[MaxReached]),
883 (MaxReached=true -> inc_counter(maximum_reached) ; true).
884 portray_content_fact(values(constants,Store),_Verbose) :- !,
885 unpack_constants(Store,UPS),
886 print_bstate(UPS),nl.
887 portray_content_fact(Term,_) :- portray_clause(Term).
888
889 format_verbose(verbose,Str,A) :- !, format(Str,A).
890 format_verbose(_,_,_).
891
892
893 :- dynamic counter/2.
894 reset_and_show_stats :- retract(counter(C,Nr)), format(' # of ~w : ~w~n',[C,Nr]),fail.
895 reset_and_show_stats.
896
897 inc_counter(C) :- (retract(counter(C,Nr)) -> N1 is Nr+1 ; N1 = 1),
898 assertz(counter(C,N1)).
899
900 :- use_module(error_manager).
901 % variation of tools_fastread:fastrw_read/3
902 read_syntax_safe(S,Term,Error) :-
903 catch( fast_read(S,Term1), % from library fastrw
904 error(E,_),
905 ( E=syntax_error(_) -> Error = true
906 ; E=permission_error(_,_,_) -> Term1 = end_of_file
907 ; E=consistency_error(_,_,_)
908 -> add_error(value_persistance,'Consistency error when reading from stream: ',E),
909 Error = true
910 ;
911 add_error(value_persistance,'Unknown error when reading from stream: ',E),
912 throw(E))
913 ),
914 Term1 = Term.
915
916
917 read_cached_operations3(operation(OpName,StoredHash),MachName) :-
918 ( operation_hash(MachName,OpName,CurrentHash) ->
919 ( CurrentHash = StoredHash % we can reuse operation; the hash includes DEFINITIONS and called operations
920 ->
921 formatgood('value caching: operation ~w unchanged for ~w.',[OpName,MachName]),
922 %TODO: what if the machine has parameters? Can we reuse the transitions from the generic machine?
923 find_matching_operations(OpName,MachName,PrefixedOpNames), % find includes with renaming, ...
924 ( PrefixedOpNames = [] ->
925 formatwarn('value caching: no operation found for ~w in ~w', [OpName,MachName])
926 ;
927 (PrefixedOpNames = [OpName] -> true
928 ; formatinfo('value caching: (composed/renamed) operations ~w found for ~w in ~w',
929 [PrefixedOpNames,OpName,MachName])
930 ),
931 maplist(store_loadable_operation(OpName,MachName),PrefixedOpNames) )
932 ;
933 get_hex_bytes(CurrentHash,CH), get_hex_bytes(StoredHash,SH),
934 formatwarn('value caching: operation ~w has changed (~s, was ~s).',[OpName, CH, SH])
935 )
936 ;
937 formatwarn('value caching: unrecognised operation ~w.',[OpName])
938 ).
939 read_cached_operations3(trans_index(OpName,Hash,Index),MachName) :-
940 ( loadable_operation(_,OpName,MachName,_InputPattern,_OutputPattern) ->
941 compute_short_hash(Hash,Short),
942 formatinfo('value caching: loading stored_transition ~w (~w) : hash ~w',[OpName,Index,Short]),
943 assert_stored_transition(Short,Hash,OpName,Index)
944 ;
945 % ignore
946 true
947 ).
948
949 store_loadable_operation(_OpName,_MachName,PrefixedOpName) :-
950 loadable_operation(PrefixedOpName,_,_,_,_),!.
951 store_loadable_operation(OpName,MachName,PrefixedOpName) :-
952 (find_operation_input_output(PrefixedOpName,Input,Output) ->
953 create_output_pattern(Output,OutputPattern),
954 lookup_pattern(Input,InputPattern)),
955 !,
956 bb_inc(value_persistance_loadable_operations),
957 formatinfo('value caching: register loadable_operation from cache: ~w in ~w',[OpName,MachName]),
958 assertz( loadable_operation(PrefixedOpName,OpName,MachName,InputPattern,OutputPattern) ).
959 store_loadable_operation(_OpName,_MachName,PrefixedOpName) :-
960 formatwarn('value caching: unable to generate input/output pattern for operation ~w.',
961 [PrefixedOpName]).
962
963 find_matching_operations(Operation,MachName,FullNames) :-
964 findall(O, is_matching_operation(Operation,MachName,O), FullNames).
965
966 is_matching_operation(Operation,MachName,Operation) :-
967 % there is an operation with exactly the same name
968 operation_with_machine(Operation,MachName).
969 is_matching_operation(Operation,MachName,FullName) :-
970 atom_concat('.',Operation,DottedOp),
971 operation_with_machine(FullName,MachName),
972 atom_concat(_,DottedOp,FullName).
973
974 operation_with_machine(OpName,MachName) :-
975 get_operation_info(OpName,Infos),
976 ( memberchk(origin(Origin),Infos), % for c1.Inc the origin will be the included machine
977 last(Origin,_/MachName) -> true
978 ; main_machine_name(MachName)
979 ).
980
981 create_output_pattern(Ids,Values/Bindings) :-
982 maplist(create_output_pattern2,Ids,Values,Bindings).
983 create_output_pattern2(Id,Value,bind(Id,Value)).
984
985 init_operation_cache(MachName,OpName) :-
986 storable_operation(OpName,MachName,_InputPattern,_Output),!. % ignore, already registered
987 init_operation_cache(MachName,OpName) :-
988 \+ b_top_level_operation(OpName), !,
989 % only store top-level operations for which we compute all solutions at the moment
990 % for subsidiary operations we do a call by predicate; much more difficult to cache/store
991 formatinfo('value caching: Not storing subsidiary operation ~w in machine ~w',[OpName,MachName]).
992 init_operation_cache(MachName,OpName) :-
993 ( find_operation_input_output(OpName,Input,Output) ->
994 lookup_pattern(Input,InputPattern),
995 debug_println(9,find_operation_input_output(OpName,Input,Output)),
996 formatinfo('value caching: Storable operation ~w in machine ~w',[OpName,MachName]),
997 bb_inc(value_persistance_storeable_operations),
998 assertz( storable_operation(OpName,MachName,InputPattern,Output) ),
999 % Operations of the main machine are never prefixed
1000 create_output_pattern(Output,OutputPattern),
1001 (loadable_operation(OpName,_,_,_,_) -> true
1002 ; bb_inc(value_persistance_loadable_operations), % see also store_loadable_operation
1003 assertz( loadable_operation(OpName,OpName,MachName,InputPattern,OutputPattern) )
1004 )
1005 ;
1006 formatwarn('value caching: unable to generate input/output pattern for operation ~w.~n',[OpName])
1007 ).
1008
1009
1010 get_operations_computation_parameters(Name,op_comp_parameters(OpParams)) :-
1011 find_relevant_preferences(Prefs),
1012 get_revision_info(Revision),
1013 OpParams = [machine_name(Name),prob_revision(Revision)|Prefs].
1014
1015 lookup_cached_transitions(PrefixedOpName,InState,Info,OutputBindings) :-
1016 cache_is_applicable_for_transitions,
1017 loadable_operation(PrefixedOpName,OpName,MachName,InputPattern,OutputPattern),
1018 operation_has_stored_transition(OpName), % otherwise no use in computing hash here
1019 sort(InState,SortedInState),
1020 % tools:start_ms_timer(T1),
1021 hash_input_values(OpName,MachName,InputPattern,SortedInState,ShortHash,InputHash),
1022 % tools:stop_ms_walltimer_with_msg(T1,hash_input(OpName)),
1023 (stored_transition(ShortHash,InputHash,OpName,Index) -> true
1024 ; %formatwarn('value caching: no cached operation transition found ~w (~w -> ...).',[OpName,ShortHash]),
1025 fail
1026 ), !,
1027 formatgood('value caching: re-using values for operation ~w (~w -> ~w).',[OpName,ShortHash,Index]),
1028 %formatdetails('value caching: state=~w',[SortedInState]),
1029 start_profile(OpName,T1),
1030 ( load_solutions(MachName,Index,Info,Solutions) -> true
1031 %length(Solutions,Sn),
1032 %format('value caching: re-using ~w solutions for operation ~w of machine ~w.~n',
1033 % [Sn,OpName,MachName])
1034 ;
1035 formatwarn('value caching: re-using values for operation ~w failed.',[OpName]),
1036 fail),
1037 %print(solution(Solutions)),nl, print(pattern(OutputPattern)),nl,
1038 % OutputPattern is of the form [V1,...]/[bind(v1,V1),...]
1039 bb_inc(value_persistance_reused_transitions),
1040 maplist(create_output_binding(OutputPattern),Solutions,OutputBindings),
1041 %tools:stop_ms_walltimer_with_msg(T1,time_caching(OpName)),
1042 stop_profile(OpName,cache_load_transitions,unknown,T1).
1043 load_solutions(MachName,Index,Info,Solutions) :-
1044 storage_file_name(operations_data,MachName,FilenameData),
1045 catch(load_sol_aux(FilenameData,Index,ReadSolutions),
1046 Exc,
1047 (ajoin(['Corrupt opdata cache file for ',MachName,':'],Msg),
1048 add_error_fail(value_persistance,Msg,Exc))
1049 ),
1050 (ReadSolutions = trans_info(II,S) -> Solutions=S, Info=II ; Solutions=ReadSolutions, Info=[]).
1051 load_sol_aux(FilenameData,Index,Solutions) :-
1052 open(FilenameData,read,S,[type(binary),reposition(true)]),
1053 call_cleanup((seek(S,Index,bof,_),
1054 fast_read(S,Solutions)), % read list of transition terms
1055 my_close(S)).
1056
1057 create_output_binding(Pattern,trans_cached(Param,Result,New,Info),
1058 trans_cached(Param,Result,Update,Info)) :-
1059 copy_term(Pattern,New/Update).
1060
1061 select_values(Ids,State,Values) :- sort(State,SState),
1062 select_values_sorted(Ids,SState,Values).
1063 % Note: as Identifiers are sorted then we can avoid quadratic complexity here and scan State only once for all Ids
1064 select_values_sorted(Ids,SState,Values) :-
1065 (select_values_sorted_aux(Ids,SState,Values) -> true
1066 ; print('Lookup: '),print(Ids), nl,
1067 print('State: '), maplist(get_bind_id,SState,SIds), print(SIds),nl,fail).
1068 select_values_sorted_aux([],_,[]).
1069 select_values_sorted_aux([Id|Irest],State,[Value|Vrest]) :-
1070 ( ordered_select(State,Id,StoredValue,RestState) ->
1071 Value=StoredValue,
1072 select_values_sorted_aux(Irest,RestState,Vrest)
1073 ;
1074 ajoin(['Looking up "', Id, '" failed.'], Msg),
1075 (maplist(get_bind_id,State,Ids) -> true ; Ids = '<<cannot print state ids>>'),
1076 add_error(value_persistance,Msg,Ids),
1077 fail
1078 ).
1079 ordered_select([bind(Id,Value)|T],Id,Value,T).
1080 ordered_select([_|T],Id,Value,R) :- ordered_select(T,Id,Value,R).
1081 get_bind_id(bind(Id,_),Id).
1082
1083 hash_input_values(OpName,MachName,InputPattern,SortedInState,Short,Long) :-
1084 % tools:start_ms_timer(T1),
1085 % write(hash(OpName,MachName,InputPattern,SortedInState)),nl,
1086 ( hash_input_values2(OpName,MachName,InputPattern,SortedInState,Short,Long) ->
1087 true
1088 %,tools:stop_ms_walltimer_with_msg(T1,time_hashing(OpName,MachName))
1089 % tools:print_memory_used_wo_gc,
1090 ; add_failed_call_error(hash_input_values2(OpName,MachName,InputPattern,SortedInState,Short,Long)),
1091 fail).
1092
1093 hash_input_values2(OpName,MachName,InputPattern,SortedInState,Short,Long) :-
1094 start_profile(OpName,T1),
1095 copy_term(InputPattern,lookup_pattern(SortedVars,SortedInputValues,InputVarsAndCsts,InputValues)),
1096 select_values_sorted(SortedVars,SortedInState,SortedInputValues),
1097 l_pre_hash(InputVarsAndCsts,InputValues,PreHashedInputValues),
1098 % terms:term_size(PreHashedInputValues,Sz), write(hash(OpName,SortedVars,Sz)),nl,
1099 % tools_printing:print_term_summary(raw_sha_hash(OpName,PreHashedInputValues)),nl,
1100 raw_sha_hash(OpName/MachName/PreHashedInputValues,Long),
1101 compute_short_hash(Long,Short),
1102 stop_profile(OpName,cache_hashing_input_values,unknown,T1).
1103 compute_short_hash([A,B,C,D|_],Short) :-
1104 Short is A<<24 + B<<16 + C<<8 + D.
1105
1106 % pre-hash certain potentially large values, so that we do not have to send them to raw_sha_hash every time
1107 l_pre_hash([],[],[]).
1108 l_pre_hash([ID|T],[Val|TV],[PreHashVal|PT]) :-
1109 pre_hash(Val,ID,PreHashVal),
1110 l_pre_hash(T,TV,PT).
1111
1112 :- dynamic constant_pre_hash_cache_active/0.
1113
1114 :- dynamic cst_id_to_hash/2.
1115 :- use_module(probsrc(memoization),[is_memoization_closure/2]).
1116 %pre_hash(Val,_ID,PreHashVal) :-
1117 % is_memoization_closure(Val,MemoID),!, %write(memo(ID,MemoID)),nl,
1118 % PreHashVal = '$MEMO'(MemoID).
1119 pre_hash(Val,CstId,PreHashVal) :- bmachine:b_is_constant(CstId),
1120 value_can_be_large(Val),!,
1121 (constant_pre_hash_cache_active
1122 -> (cst_id_to_hash(CstId,StoredHash)
1123 -> PreHashVal = StoredHash % used stored value
1124 ; raw_sha_hash(Val,Hash),
1125 assert(cst_id_to_hash(CstId,Hash)),
1126 debug_println(4,storing_cache_hash_for_constant(CstId)),
1127 PreHashVal = Hash
1128 )
1129 ; raw_sha_hash(Val,PreHashVal) % there can be multiple constant values active
1130 ).
1131 pre_hash(V,_,V).
1132
1133 :- use_module(probsrc(avl_tools),[avl_height_less_than/2]).
1134 value_can_be_large(avl_set(A)) :- \+ avl_height_less_than(A,7).
1135 value_can_be_large(closure(_,_,_)).
1136 value_can_be_large((A,B)) :- value_can_be_large(A) -> true ; value_can_be_large(B).
1137 value_can_be_large(rec(Fields)) :- (member(field(_,V),Fields), value_can_be_large(V) -> true).
1138
1139 % TODO: separate constants from variables? or do full incremental hashing; by hashing all large sets first
1140 % we also could detect memoization closures and just store their id? or pre-compute their hash and store it?
1141
1142 % save operations_index file for machine
1143 save_operations_index_cache(MachName,OperationNames) :-
1144 get_operations_computation_parameters(MachName,OpParams),
1145 storage_file_name(operations_index,MachName,FileName),
1146 my_open(FileName,write,S,[type(binary)]),
1147 fast_write(S,OpParams),
1148 get_tail_filename(FileName,TailFileName),
1149 save_operation_info(S,TailFileName,MachName,OperationNames),
1150 my_close(S).
1151
1152 % is this really required: it seems to re-write already loaded information to the file; at least in some cases
1153 save_operation_info(S,FileName,MachName,OperationNames) :-
1154 member(OpName,OperationNames),
1155 storable_operation(OpName,MachName,_InputPattern,_Output),
1156 operation_hash(MachName,OpName,OpHash),
1157 fast_write(S,operation(OpName,OpHash)),
1158 stored_transition(_Short,InputHash,OpName,Index),
1159 formatinfo('value caching: storing/refreshing transition for ~w (index ~w) from ~w to ~w',[OpName,Index,MachName,FileName]),
1160 fast_write(S,trans_index(OpName,InputHash,Index)),
1161 bb_inc(value_persistance_refresh_transitions),
1162 fail.
1163 save_operation_info(_S,_F,_MachName,_OperationNames).
1164
1165 find_operation_input_output(OpName,Input,Output) :-
1166 get_operation_info(OpName,Info),
1167 memberchk(reads(Input1),Info),
1168 % remove references to global sets and their elements
1169 get_all_sets_and_enum_ids(SEIds),
1170 remove_all(Input1,SEIds,Input),
1171 memberchk(modifies(Output),Info).
1172
1173 get_all_sets_and_enum_ids(SEIds) :-
1174 findall(Id,
1175 ( is_b_global_constant(_,_,Id)
1176 ; b_global_set(Id)),
1177 SEIds).
1178
1179
1180
1181 % add new transitions from the state space
1182 add_new_transitions_to_cache(InStateId) :-
1183 cache_is_applicable_for_transitions,
1184 visited_expression(InStateId,InState1),
1185 state_corresponds_to_initialised_b_machine(InState1,InState),
1186 !,
1187 add_new_transitions_to_cache1(InStateId,InState).
1188 add_new_transitions_to_cache(_InStateId).
1189
1190 get_all_max_reached_operations(MaxReachedList) :-
1191 findall(OpName, max_reached(OpName), MaxReached),
1192 sort(MaxReached,MaxReachedList).
1193
1194 :- use_module(library(ordsets),[ord_member/2]).
1195
1196 add_new_transitions_to_cache1(InStateId,InState) :-
1197 get_all_max_reached_operations(MaxReachedList),
1198 %main_machine_name(MachName),
1199 storable_operation(OpName,MachName,InputPattern,Output),
1200 \+ time_out_for_node(InStateId,OpName,_),
1201 (ord_member(OpName,MaxReachedList) -> MaxReached=true ; MaxReached=false),
1202 sort(InState,SortedInState),
1203 add_new_transitions_to_cache2(InStateId,SortedInState,OpName,InputPattern,Output,MaxReached,MachName),
1204 fail.
1205 add_new_transitions_to_cache1(_InStateId,_) :-
1206 flush_data.
1207
1208 add_new_transitions_to_cache2(InStateId,SortedInState,OpName,InputPattern,Output,MaxReached,MachName) :-
1209 hash_input_values(OpName,MachName,InputPattern,SortedInState,ShortHash,InputHash),
1210 \+ stored_transition(ShortHash,InputHash,_,_), % Is there already a cache entry?
1211 find_all_transitions(InStateId,OpName,Output,Transitions),
1212 length(Transitions,Length),
1213 %format('value caching: storing ~w transitions for operation ~w in state ~w.~n',
1214 % [Length,OpName,InStateId]),
1215 %print(Transitions),nl,
1216 statistics(runtime,[Start,_]),
1217 statistics(walltime,[WStart,_]),
1218 store_transition_into_cache(OpName,ShortHash,InputHash,Transitions,MaxReached,MachName),
1219 statistics(runtime,[Stop,_]), Time is Stop - Start,
1220 statistics(walltime,[WStop,_]), WTime is WStop - WStart,
1221 %%tools:print_memory_used_wo_gc,
1222 bb_inc_by(value_persistance_stored_transitions,Length),
1223 formatinfo('value caching: storing ~w transitions for operation ~w in state ~w (~w, state ~w, [~w] ms).',
1224 [Length,OpName,InStateId,ShortHash,Time,WTime]).
1225
1226 store_transition_into_cache(OpName,ShortHash,Hash,Transitions,MaxReached,MachName) :-
1227 start_profile(OpName,T1),
1228 storage_file_name(operations_data,MachName,FilenameData),
1229 my_open(FilenameData,read,SR,[type(binary),reposition(true)]),
1230 call_cleanup(seek(SR,0,eof,Index), % gets the end of file
1231 my_close(SR)),
1232 %formatdetails('storing ~w (~w), EOF index is ~w for file ~w~n',[OpName,ShortHash,Index,FilenameData]),
1233 my_open(FilenameData,append,SW,[type(binary)]),
1234 (MaxReached = true -> Term = trans_info([max_reached],Transitions) ; Term=Transitions),
1235 call_cleanup(fast_write(SW,Term),
1236 my_close(SW)),
1237 assert_stored_transition(ShortHash,Hash,OpName,Index),
1238 get_operations_index_file(MachName,OI),
1239 fast_write(OI,trans_index(OpName,Hash,Index)),
1240 stop_profile(OpName,cache_store_transitions,unknown,T1).
1241
1242 assert_stored_transition(ShortHash,Hash,OpName,Index) :- store_operation_has_stored_transition(OpName),
1243 assertz( stored_transition(ShortHash,Hash,OpName,Index) ).
1244
1245 store_operation_has_stored_transition(X) :- operation_has_stored_transition(X),!.
1246 store_operation_has_stored_transition(X) :- assertz( operation_has_stored_transition(X) ).
1247
1248 find_all_transitions(InStateId,OpName,Output,Transitions) :-
1249 findall( trans_cached(ParaValues,ResultValues,Updates,TransInfo),
1250 find_transition(InStateId,OpName,Output,ParaValues,ResultValues,Updates,TransInfo),
1251 Transitions).
1252 find_transition(InStateId,OpName,Output,ParaValues,ResultValues,Updates,TransInfo) :-
1253 transition(InStateId,Operation,TransId,OutStateId),
1254 operation_name(Operation,OpName,ParaValues,ResultValues),
1255 findall(TI,transition_info(TransId,TI),TransInfo),
1256 visited_expression(OutStateId,OutState1), % we could use packed_visited_expression here ?
1257 state_corresponds_to_initialised_b_machine(OutState1,OutState),
1258 select_values(Output,OutState,Updates).
1259 operation_name('-->'(Operation,ResultValues),OpName,ParaValues,ResultValues) :-
1260 !,operation_name(Operation,OpName,ParaValues,_).
1261 operation_name(Operation,OpName,ParaValues,[]) :-
1262 Operation =.. [OpName|ParaValues].
1263
1264
1265 % add a single new transition, found by execute by predicate or -execute
1266 add_new_transition_to_cache_from_expanded_state(root,_OpTerm,OutState,_CacheInfo) :-
1267 OutState = concrete_constants(_),!,
1268 save_constants_from_expanded_state(OutState).
1269 add_new_transition_to_cache_from_expanded_state(InState,OpTerm,OutState,CacheInfo) :-
1270 cache_is_applicable_for_transitions,
1271 main_machine_name(MachName),
1272 operation_name(OpTerm,OpName,ParaValues,ResultValues),
1273 storable_operation(OpName,MachName,InputPattern,Output),
1274 \+ new_transition_not_worthwhile(CacheInfo,OpName),
1275 sort(InState,SortedInState),
1276 hash_input_values(OpName,MachName,InputPattern,SortedInState,ShortHash,InputHash), % can be expensive
1277 \+ stored_transition(ShortHash,InputHash,_,_), % Is there already a cache entry?
1278 !,
1279 MaxReached=true, % TODO: should we check that MAX_OPERATIONS is set to exactly 1
1280 TransInfo = [], % TODO: preference(eventtrace,true), preference(store_event_transinfo,true)
1281 Transitions = [trans_cached(ParaValues,ResultValues,Updates,TransInfo)],
1282 select_values(Output,OutState,Updates),
1283 bb_inc(value_persistance_stored_transitions),
1284 store_transition_into_cache(OpName,ShortHash,InputHash,Transitions,MaxReached,MachName),
1285 formatinfo('value caching: storing single transition for operation ~w in execute mode (~w).', [OpName,ShortHash]),
1286 flush_data.
1287 add_new_transition_to_cache_from_expanded_state(_,_,_,_).
1288
1289 % add_deadlock_to_cache_from_expanded_state(InState,OpName) % TODO: worthwhile to store failure info
1290
1291 start_cache_execute_modus(cache_info(StartRuntime,Counter)) :-
1292 statistics(runtime,[StartRuntime,_]),
1293 bb_safe_get(value_persistance_reused_transitions,Counter),
1294 (constant_pre_hash_cache_active -> true
1295 ; assert(constant_pre_hash_cache_active)).
1296
1297 stop_cache_execute_modus :-
1298 retractall(constant_pre_hash_cache_active).
1299
1300 new_transition_not_worthwhile(cache_info(_,OldCounter),OpName) :-
1301 bb_safe_get(value_persistance_reused_transitions,Counter),
1302 Counter > OldCounter, % we cannot reuse subsidiary operation calls, so this must be the main operation itself
1303 formatinfo('value caching: not storing transition for ~w; it has been extracted from cache itself',[OpName]).
1304 new_transition_not_worthwhile(cache_info(StartRuntime,_),OpName) :-
1305 get_preference(cache_operations_runtime_limit,Limit), Limit>0,
1306 statistics(runtime,[CurrentTime,_]), Delta is CurrentTime-StartRuntime,
1307 Delta < Limit,
1308 bb_inc(value_persistance_not_worth_transitions),
1309 formatinfo('value caching: not storing transition for ~w, runtime (ms) ~w smaller than limit ~w',
1310 [OpName,Delta,Limit]).
1311
1312
1313
1314 % --------------------
1315
1316 open_data_file(Name) :-
1317 storage_file_name(operations_index,Name,FilenameIndex),
1318 my_open(FilenameIndex,append,FI,[type(binary)]),
1319 assertz(operations_index_file_opened(Name,FI)),
1320 storage_file_name(operations_data,Name,FilenameData),
1321 ( file_exists(FilenameData) -> true
1322 ;
1323 my_open(FilenameData,write,SD,[type(binary)]),
1324 my_close(SD)).
1325
1326 flush_data :-
1327 findall(M,(operations_index_file_opened(M,S),flush_output(S)),L),
1328 (L=[] -> add_internal_error('No index file opened',flush_data) ; true).
1329
1330 get_operations_index_file(Machine,OI) :-
1331 operations_index_file_opened(Machine,F),!,OI=F.
1332 get_operations_index_file(Machine,OI) :-
1333 add_internal_error('No operations_index file opened',get_operations_index_file(Machine,OI)),fail.
1334
1335 find_loadable_machines(Solutions) :-
1336 findall(loadable(Type,Machine),
1337 find_loadable_machines2(Type,Machine),
1338 Solutions).
1339 find_loadable_machines2(Type,Machine) :-
1340 main_machine_name(Main),
1341 find_loadable_machines_sees_includes(Main,Type,Machine).
1342 find_loadable_machines_sees_includes(Main,main,Main).
1343 find_loadable_machines_sees_includes(Main,sub,Seen) :-
1344 machine_sees(Main,Seen).
1345 find_loadable_machines_sees_includes(Start,sub,Included) :-
1346 find_loadable_machines_includes(Start,Included).
1347 find_loadable_machines_includes(Start,Included) :-
1348 machine_includes(Start,_Prefix1,M),
1349 ( Included=M
1350 ; find_loadable_machines_includes(M,Included)).
1351
1352 machine_sees(MachA,MachB) :-
1353 machine_references(MachA,References),
1354 member(ref(Type,MachB,''),References),
1355 memberchk(Type,[sees,uses]).
1356 machine_includes(MachA,Prefix,MachB) :-
1357 machine_references(MachA,References),
1358 member(ref(Type,MachB,Prefix),References),
1359 memberchk(Type,[includes,extends]).
1360
1361 % lookup_pattern/2:
1362 % To enable a fast lookup of values in a state, we have to sort the variables.
1363 % On the other hand, we must not sort the variables when storing them, their order
1364 % is significant.
1365 % This predicate generates a "lookup_pattern" that sorts the variables and their
1366 % corresponding values and enables to map the sorted values to the original order
1367 % by a simple unification.
1368 lookup_pattern(Variables,lookup_pattern(SortedVariables,SortedValues,Variables,Values)) :-
1369 maplist(variable_value_pair,Variables,VarValues,Values),
1370 sort(VarValues,SortedVarValues),
1371 maplist(variable_value_pair,SortedVariables,SortedVarValues,SortedValues).
1372 variable_value_pair(I,I/V,V).
1373
1374
1375 % utility for statistics:
1376
1377 reset_counters :-
1378 ? (is_counter(C), bb_reset(C), fail ; true).
1379
1380 print_value_persistance_stats :-
1381 format_with_colour_nl(user_output,[blue],'ProB Value Persistance Caching Statistics',[]),
1382 (storage_directory(Dir)
1383 -> format_with_colour_nl(user_output,[blue],'* Cache storage directory: ~w',[Dir])
1384 ; format_with_colour_nl(user_output,[orange],'* No cache storage directory set!',[])
1385 ),
1386 format_with_colour_nl(user_output,[blue],'ProB Value Persistance Caching Statistics',[]),
1387 bb_safe_get(value_persistance_constants_loaded,C),
1388 format_with_colour_nl(user_output,[blue],' * Nr. of machines for which stored constants were reused: ~w',[C]),
1389 bb_safe_get(value_persistance_ref_constants_loaded,RC),
1390 format_with_colour_nl(user_output,[blue],' * Nr. of referenced machines for which stored constants were reused: ~w',[RC]),
1391 bb_safe_get(value_persistance_stored_constants,StCs),
1392 format_with_colour_nl(user_output,[blue],' * Nr. of solutions for constants stored: ~w',[StCs]),
1393 bb_safe_get(value_persistance_op_cache_machines,OCM),
1394 format_with_colour_nl(user_output,[blue],' * Nr. of machines for which operations can be reused/stored: ~w',[OCM]),
1395 bb_safe_get(value_persistance_loadable_operations,LO),
1396 format_with_colour_nl(user_output,[blue],' * Nr. of stored operations which can be re-used: ~w',[LO]),
1397 bb_safe_get(value_persistance_storeable_operations,SO),
1398 format_with_colour_nl(user_output,[blue],' * Nr. of operations which can be stored: ~w',[SO]),
1399 bb_safe_get(value_persistance_reused_transitions,R),
1400 format_with_colour_nl(user_output,[blue],' * Nr. of stored operation calls reused: ~w',[R]),
1401 bb_safe_get(value_persistance_stored_transitions,S),
1402 format_with_colour_nl(user_output,[blue],' * Nr. of operation calls *not* reused and stored: ~w',[S]),
1403 bb_safe_get(value_persistance_not_worth_transitions,WW),
1404 format_with_colour_nl(user_output,[blue],' * Nr. of operation calls *not* reused and *not* stored: ~w',[WW]),
1405 bb_safe_get(value_persistance_refresh_transitions,RF),
1406 format_with_colour_nl(user_output,[blue],' * Nr. of operation calls refreshed: ~w',[RF]).
1407
1408 get_value_persistance_stats(List) :-
1409 findall(Counter-Value,(is_counter(Counter),bb_safe_get(Counter,Value)),List).
1410
1411 is_counter(value_persistance_constants_loaded).
1412 is_counter(value_persistance_ref_constants_loaded).
1413 is_counter(value_persistance_loadable_operations).
1414 is_counter(value_persistance_op_cache_machines).
1415 is_counter(value_persistance_loadable_operations).
1416 is_counter(value_persistance_storeable_operations).
1417 is_counter(value_persistance_reused_transitions).
1418 is_counter(value_persistance_stored_transitions).
1419 is_counter(value_persistance_not_worth_transitions).
1420 is_counter(value_persistance_refresh_transitions).
1421
1422 bb_reset(Counter) :- bb_put(Counter,0).
1423
1424
1425 % utility for debugging:
1426
1427 formatwarn(Format,Args) :-
1428 format_with_colour_nl(user_output,[orange],Format,Args).
1429
1430 formatinfo(_Format,_Args) :- silent_mode(on),!.
1431 formatinfo(Format,Args) :-
1432 format_with_colour_nl(user_output,[grey],Format,Args).
1433
1434 formatdetails(_Format,_Args) :- silent_mode(on), debug_mode(on),
1435 !.
1436 formatdetails(Format,Args) :-
1437 format_with_colour_nl(user_output,[grey],Format,Args).
1438
1439 formatgood(_Format,_Args) :- silent_mode(on),!.
1440 formatgood(Format,Args) :-
1441 format_with_colour_nl(user_output,[green],Format,Args).
1442
1443 :- use_module(tools_io,[safe_open_file/4]).
1444 my_open(File,Mode,St,Opt) :- !, safe_open_file(File,Mode,St,Opt).
1445 my_open(File,Mode,St,Opt) :-
1446 safe_open_file(File,Mode,St,Opt),
1447 formatinfo('Opened file (~w) ~w -> ~w',[Mode,File,St]).
1448
1449 my_close(Stream) :- !, close(Stream).
1450 my_close(Stream) :- stream_property(Stream,file_name(F)),!,
1451 formatinfo('Closing ~w -> ~w',[F, Stream]),
1452 close(Stream).
1453 my_close(Stream) :-
1454 formatinfo('Closing -> ~w',[Stream]),
1455 close(Stream).