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 %:- set_prolog_flag(source_info,on).
6 % comment in if you want source location, e.g., for exceptions,...
7 % you can also comment in a line in remove_debugging_calls in debugging_calls_te.pl to see location of nl/0
8 % (and ensure debugging_calls.pl is loaded below and in term_expansion hook is set in debugging_calls_te.pl)
9 % with ?- trace, leash(off). one can creep without entering return in the debugger; with leash([redo]) the debugger only stops at the Redo-Port. Use @<RETURN> to enter Prolog commands in the debugger.
10 % leash(exception) also useful
11 % Note: to run probcli from source for ProB2 change change probcli.sh: PROBCOMMAND=probproxy and start probsli -s 8888
12
13 :- module(prob_cli, [go_cli/0,
14 run_probcli/2, run_probcli_with_argv_string/1,
15 reset_cli/0, recognised_cli_option/4, recognised_option/2, go_proxy/0,
16 print_version/1, cli_print_statistics/1]).
17
18 :- set_prolog_flag(double_quotes, codes).
19
20 :- if(predicate_property(expects_dialect(_), _)).
21 :- expects_dialect(sicstus4).
22 :- endif.
23
24 :- multifile user:portray_message/2.
25 user:portray_message(informational, imported(_Nr,_M1,_M2)) :- !.
26 user:portray_message(informational, loading(_Nr,_,_File)) :- !.
27 %user:portray_message(informational, loaded(_Nr,compiled,_File,M,MS,_)) :- !, format('~w ms for ~w~n',[MS,M]).
28 user:portray_message(informational, loaded(_Nr,_CompiledLoaded,_File,_Module,_TimeMS,_Bytes)) :- !.
29 user:portray_message(informational, foreign_resource(_Nr,_Status,_File,_Mod)) :- !.
30 user:portray_message(informational, chr_banner) :- !.
31 %user:portray_message(informational, halt) :- !.
32 %user:portray_message(informational, prompt(off,0,user,off,off,off)) :- !.
33 %user:portray_message(informational, M) :- !, write(M),nl,nl.
34
35
36 :- meta_predicate if_option_set(-,0).
37 :- meta_predicate if_option_set(-,0,0).
38 :- meta_predicate if_options_set(-,0).
39 :- meta_predicate if_option_set_loaded(-,-,0).
40 :- meta_predicate ifm_option_set(-,0).
41 :- meta_predicate ifm_option_set(-,-,0).
42 :- meta_predicate ifm_option_set_loaded(-,-,0).
43
44
45 % patch for SICStus 4.3.3 performance issue
46 % sprm_14972_patch.pl BEGIN
47 :- if((current_prolog_flag(dialect, sicstus),
48 current_prolog_flag(version_data, sicstus(4,3,3,_,_)))).
49 prolog:wf_call_like_arg(A, B, C, D, E, F, G, H, I, _) :-
50 prolog:wellformed_body_iso(A, B, C, D, E, F, G, H, I, quiet),
51 !.
52 prolog:wf_call_like_arg(A, B, C, A, D, _, E, _, _, _) :-
53 F=E:A,
54 prolog:condense_layout(B, G),
55 prolog:comp_layout2(B, G, B, H),
56 C=call(F),
57 prolog:comp_layout1(B, H, D).
58 :- endif.
59 % sprm_14972_patch.pl END
60
61
62 %:- include('self_check_off.pl').
63
64 :- use_module(module_information).
65 :- module_info(group,cli).
66 :- module_info(description,'ProB start file in cli mode.').
67
68 %:- use_module(debugging_calls).
69 %:- register_debugging_calls([pp_mnf(*), pp_cll(*), mnf(*), mnf(-,*), det_call(*)]).
70 %:- disable_debugging_calls.
71
72 :- use_module(prob_startup, [startup_prob/0]).
73 %:- use_module(pathes,[set_search_pathes/0]). % called first to set_compile_time_search_pathes
74 :- use_module(tools,[string_concatenate/3,arg_is_number/2, print_memory_used_wo_gc/1, print_memory_used_wo_gc/0,
75 split_atom/3, get_options/5,
76 start_ms_timer/1, stop_ms_timer/1, stop_ms_timer/2, stop_ms_timer_with_msg/2]).
77 :- use_module(tools_printing,[print_error/1,format_with_colour/4, format_with_colour_nl/4]).
78 :- use_module(tools_strings,[atom_split/4,convert_atom_to_number/2]).
79 :- use_module(tools_meta,[safe_time_out/3]).
80 :- use_module(tools_lists,[count_occurences/2]).
81
82 :- use_module(preferences).
83 :- set_prob_application_type(probcli). %
84
85 :- use_module(library(lists)).
86 :- use_module(library(file_systems),[file_exists/1]).
87 :- use_module(library(system)).
88 :- use_module(library(codesio)).
89 :- use_module(library(between),[between/3]).
90 :- use_module(library(terms),[term_hash/2]).
91 :- use_module(library(random),[random/3, setrand/1]).
92
93 :- use_module(self_check,[disable_interaction_on_errors/0,
94 perform_self_check/2,turn_off_run_time_type_checks/0,turn_on_run_time_type_checks/0]).
95 :- use_module(debug).
96 :- use_module(error_manager).
97 :- use_module(translate,[pretty_type/2]).
98 :- use_module(tools,[safe_absolute_file_name/2, safe_absolute_file_name/3, convert_ms_time_to_string/2]).
99 :- use_module(extension('counter/counter'),
100 [counter_init/0, new_counter/1, get_counter/2, inc_counter/1, inc_counter/2, reset_counter/1]).
101 :- use_module(state_space,[current_expression/2]).
102
103
104 :- dynamic junit_mode/1.
105 :- use_module(junit_tests,[set_junit_dir/1, create_and_print_junit_result/4]).
106
107 :- use_module(b_trace_checking,[check_default_trace_for_specfile/1, tcltk_check_state_sequence_from_file/1,
108 tcltk_check_sequence_from_file/3, get_default_trace_file/3,
109 tcltk_save_history_as_trace_file/2]).
110 :- use_module(eventhandling,[store_virtual_event/1]).
111 :- use_module(bmachine,[b_set_initial_machine/0]).
112 :- use_module(specfile).
113 :- use_module(test_typechecker,[run_typecheck_testcase/2]).
114 :- use_module(basic_unit_tests). % basic unit tests
115 :- use_module(bsyntaxtree,[size_of_conjunction/2, get_texpr_id/2, get_texpr_description/2,
116 conjunction_to_list/2,
117 get_texpr_label/2, predicate_components/2, get_texpr_pos/2]).
118 :- use_module(bmachine,[b_write_machine_representation_to_file/3,
119 full_b_machine/1, b_write_eventb_machine_to_classicalb_to_file/1]).
120 :- use_module(state_space,[current_state_id/1, get_state_space_stats/4, compute_full_state_space_hash/1]).
121 :- use_module(xtl_interface,[set_cspm_main_process/1]).
122 :- use_module(extrasrc(meta_interface),[is_dot_command/1, call_dot_command_with_engine/4,
123 is_dot_command_for_expr/1,call_dot_command_with_engine_for_expr/5,
124 is_plantuml_command/1, is_plantuml_command_for_expr/1,
125 is_table_command/1, is_table_command_for_expr/1,
126 call_plantuml_command/2, call_plantuml_command_for_expr/4,
127 call_command/5, is_table_command/6, write_table_to_csv_file/3,
128 command_description/3]).
129 :- use_module(kodkodsrc(kodkod_test),[test_kodkod/1, compare_kodkod_performance/2]).
130 :- use_module(kodkodsrc(predicate_analysis),[test_predicate_analysis/0]).
131 :- use_module(b_show_history,[write_history_to_file/2,write_values_to_file/1,
132 write_all_values_to_dir/1,write_history_to_user_output/1]).
133 :- use_module(cbcsrc(sap), [write_all_deadlocking_paths_to_xml/1, test_generation_by_xml_description/1]).
134 :- use_module(smtlib_solver(smtlib2_cli),[smtlib2_file/2]).
135 :- use_module(disproversrc(disprover_test_runner), [run_disprover_on_all_pos/1,
136 load_po_file/1,print_disprover_stats/0, set_disprover_timeout/1,
137 set_disprover_options/1, reset_disprover_timeout/0]).
138 :- use_module(extrasrc(latex_processor), [process_latex_file/2]).
139 :- use_module(probltlsrc(ltl),[ltl_check_assertions/2,ltl_model_check/4]).
140 :- use_module(probltlsrc(ctl),[ctl_model_check/4]).
141
142 :- use_module(logger).
143 :- use_module(extension('zmq/master/master'),[start_master/8]).
144 :- use_module(extension('zmq/worker/worker'),[start_worker/5]).
145 :- use_module(extension('ltsmin/ltsmin'),
146 [start_ltsmin/4,ltsmin_init/3,ltsmin_loop/1,ltsmin_teardown/2,ltsmin_generate_ltlfile/2]).
147 :- use_module(extrasrc(coverage_statistics),[compute_the_coverage/5]).
148 :- use_module(value_persistance, [set_storage_directory/1]).
149 :- use_module(prob_socketserver,[start_prob_socketserver/2]).
150 :- use_module(tcltk_interface).
151 %:- compile(gui_tcltk).
152 :- use_module(eclipse_interface).
153 :- use_module(prob2_interface,[start_animation/0, is_initialised_state/1, reset_animator/0,
154 set_eclipse_preference/2, update_preferences_from_spec/1,
155 load_cspm_spec_from_cspm_file/1, load_xtl_spec_from_prolog_file/1]).
156
157 start_probcli_timer(timer(T1,WT1)) :-
158 statistics(runtime,[T1,_]),
159 statistics(walltime,[WT1,_]).
160 stop_probcli_debug_timer(Timer,Msg) :- (debug_mode(on) -> stop_probcli_timer(Timer,Msg) ; true).
161 stop_probcli_timer(timer(T1,WT1),Msg) :- stop_probcli_timer(timer(T1,WT1),Msg,_).
162 stop_probcli_timer(timer(T1,WT1),Msg,WTotTime) :-
163 statistics(runtime,[T2,_]), TotTime is T2-T1,
164 statistics(walltime,[WT2,_]), WTotTime is WT2-WT1,
165 convert_ms_time_to_string(WT2,WTString),
166 format('~w ~w ms walltime (~w ms runtime), since start: ~w~n',[Msg,WTotTime,TotTime,WTString]),
167 !.
168 stop_probcli_timer(Timer,Msg,_) :- add_internal_error('Illegal timer call: ',stop_probcli_timer(Timer,Msg)).
169 print_total_probcli_timer :-
170 statistics(runtime,[T2,_]),
171 statistics(walltime,[WT2,_]),
172 format('Since start of probcli: ~w ms walltime (~w ms runtime)~n',[WT2,T2]).
173 get_probcli_elapsed_walltime(timer(_,WT1),WTotTime) :-
174 statistics(walltime,[WT2,_]), WTotTime is WT2-WT1.
175 get_probcli_elapsed_runtime(timer(RT1,_),RTotTime) :-
176 statistics(runtime,[RT2,_]), RTotTime is RT2-RT1.
177
178 :- meta_predicate timeout_call(0,-,-).
179 timeout_call(Call,NOW,PP) :- option(timeout(TO)),!,
180 statistics(runtime,[T1,_]),
181 safe_time_out(Call,TO,Res),
182 statistics(runtime,[T2,_]), Runtime is T2-T1,
183 formatsilent('Runtime for ~w: ~w ms~n',[PP,Runtime]),
184 (Res=time_out -> print('*** Timeout occurred: '), print(TO),nl,
185 print('*** Call: '), print(Call),nl,
186 nl,
187 writeln_log(timeout_occurred(NOW,Call))
188 ; true).
189 timeout_call(Call,_NOW,PP) :-
190 statistics(runtime,[T1,_]),
191 call(Call),
192 statistics(runtime,[T2,_]), Runtime is T2-T1,
193 formatsilent('Runtime for ~w: ~w ms~n',[PP,Runtime]).
194
195 set_junit_mode(X) :-
196 set_junit_dir(X),
197 retractall(junit_mode(_)),
198 statistics(runtime,[Start,_]),
199 assertz(junit_mode(Start)).
200
201 go_proxy :-
202 catch( run_probcli(['-s','8888'],[proxy]), halt(ExitCode),
203 ( nl,write('CLI halt prevented, exit code '),write(ExitCode),nl) ).
204
205 go_cli :-
206 % set_prob_application_type(probcli) is already done at compile_time
207 current_prolog_flag(argv,ArgV),
208 run_probcli_with_junit_check(ArgV).
209
210 initialise_cli :- counter_init,
211 new_counter(cli_execute_inits),
212 new_counter(cli_errors), new_counter(cli_warnings),
213 new_counter(cli_expected_errors).
214
215 % called from test_runner.pl:
216 reset_cli :-
217 announce_event(clear_specification),
218 announce_event(reset_prob),
219 reset_expected_error_occurred,
220 reset_optional_errors_or_warnings,
221 reset_counter(cli_errors), reset_counter(cli_warnings),
222 reset_counter(cli_expected_errors),
223 % now done via event handling: clear_dynamic_predicates_for_POR,
224 % retractall(refinement_checker: generated_predeterministic_refinement(_,_,_)),
225 % retractall(refinement_checker: determinism_check_div_found(_)),
226 % reset_cspm_main_process,
227 retractall(accumulated_infos(_,_,_)),
228 retractall(merged_individual_file_infos(_,_,_)),
229 retractall(individual_file_infos(_,_,_)),
230 (file_loaded(_)
231 -> clear_loaded_machines, % TODO: also treat by reset_prob eventhandling?
232 retractall(file_loaded(_,_)),
233 retractall(loaded_main_file(_,_))
234 ; true).
235
236 run_probcli_with_junit_check(ArgV) :-
237 catch( run_probcli(ArgV,[junit]),
238 halt(ExitCode),
239 ( ExitCode = 0 ->
240 true
241 ; ( junit_mode(S) ->
242 statistics(runtime,[E,_]), T is E - S,
243 create_and_print_junit_result(['Integration Tests'],ArgV,T,error([ExitCode]))
244 ; true),
245 throw(halt(ExitCode)))).
246
247 % a useful entry point for Jupyter to mimic probcli execution in notebooks
248 run_probcli_with_argv_string(ArgVAtom) :- split_argv_string(ArgVAtom,Atoms),
249 (Atoms = [probcli|Atoms2] -> true ; Atoms2=Atoms),
250 run_probcli(Atoms2,[run_probcli_with_argv_string]).
251
252 split_argv_string(ArgVAtom,Atoms) :- split_atom(ArgVAtom,[' '],Atoms). % TODO: treat quoting
253
254 run_probcli(ArgV,Context) :- % format(user_output,'~n* Starting probcli with argv: ~w~n~n',[ArgV]),
255 (catch(
256 run_probcli2(ArgV),
257 Exc,
258 process_exception(Exc,Context)
259 )
260 -> true
261 ; flush_output,
262 print_error('INTERNAL ERROR OCCURRED (run_probcli failed) !'),nl,
263 error_occurred(internal_error),
264 halt_exception(1)
265 ).
266
267 :- use_module(translate,[translate_error_term/2]).
268 %process_exception(Exception,_) :- write('Exception: '),write(Exception),nl,fail. % for debugging
269 process_exception(halt(A),_) :- !, throw(halt(A)).
270 process_exception('$aborted',_) :- !, throw('$aborted'). % thrown by SWI-Prolog on abort by user
271 process_exception(user_interrupt_signal,Context) :- !,
272 %add_error(probcli,'probcli interrupted by user (CTRL-C)').
273 statistics(walltime,[WStart,_]),
274 format_with_colour_nl(user_error,[red],'~nprobcli interrupted by user (CTRL-C), total walltime ~w ms',[WStart]),
275 (member(test_runner,Context)
276 -> throw(user_interrupt_signal) % will be caught by test_runner
277 ; error_occurred_with_msg(user_interrupt_signal,'probcli interrupted by user (CTRL-C)')
278 ).
279 process_exception(Exc,_) :-
280 (translate_error_term(Exc,S)
281 -> format_error_with_nl('Uncaught exception in probcli: ~w',[S])
282 ; true),
283 error_occurred(internal_error(exception(Exc))),fail.
284
285 no_command_issued :- \+ command_option(_).
286 command_option(X) :- option(X), \+ not_command_option(X).
287 not_command_option(verbose).
288 not_command_option(very_verbose).
289 not_command_option(profiling_on).
290 not_command_option(set_pref(_,_)).
291 not_command_option(set_preference_group(_,_)).
292 not_command_option(set_card(_,_)).
293 not_command_option(set_argv(_)).
294 not_command_option(silent).
295 not_command_option(strict_raise_error).
296 not_command_option(no_color).
297
298 probcli_startup :-
299 %print_total_probcli_timer,
300 startup_prob, % % startup_prob will already call init_preferences
301 %myheap_init,
302 initialise_cli.
303
304 :- load_files(library(system), [when(compile_time), imports([environ/2])]).
305 :- if(environ(prob_logging_mode,true)).
306 cli_set_options(ArgV,RemArgV) :-
307 cli_init_options(['-ll'|ArgV],RemArgV). %% adds -ll to have an automatically logging probcli to /tmp/prob_cli_debug.log
308 :- else.
309 cli_set_options(ArgV,RemArgV) :- cli_init_options(ArgV,RemArgV).
310 :- endif.
311
312 %:- use_module(extension('myheap/myheap')).
313 run_probcli2(ArgV) :- %print(probcli_startup),nl_time,
314 probcli_startup,
315 external_functions:reset_argv,
316 cli_set_options(ArgV,RemArgV), % recognise command-line options
317 %% cli_set_options(['-vv','-version'|ArgV],RemArgV), %% comment in to have an automatically verbose probcli
318 maplist(prob_cli:check_atom_looks_like_file,RemArgV),
319 (option(prolog_trace) -> error_manager:safe_trace ; true),
320 !,
321 run_probcli3(ArgV,RemArgV).
322
323 run_probcli3(ArgV,RemArgV) :-
324 ( RemArgV=[File],no_command_issued,
325 get_filename_extension(File,Ext),
326 \+ do_not_execute_automatically(Ext)
327 % then assume we want to do -execute_all:
328 -> assert_option(execute(2147483647,false,current_state(1)))
329 ; true),
330 if_option_set(set_application_type(PAT),set_prob_application_type(PAT)),
331 if_option_set(test_mode,set_random_seed_to_deterministic_start_seed, set_new_random_seed),
332 if_option_set(verbose,
333 verbose, %% set_verbose_mode -> does tcltk_turn_debugging_on(19),
334 tcltk_turn_debugging_off),
335 if_option_set(very_verbose,
336 very_verbose), %tcltk_turn_debugging_on(5)),
337 if_option_set(profiling_on,profiling_on),
338 debug_print(9,'Command Line Arguments: '),debug_println(9,ArgV),
339 if_option_set(very_verbose,
340 print_options),
341 debug_print(6,'Command Line File Args: '),debug_println(6,RemArgV),
342 if_option_set(cache_storage(StorageDir), set_storage_directory(StorageDir)),
343 if_option_set(parsercp(ParserLoc),
344 (add_message(parsercp,'Command -parcercp PATH deprecated, use -p JAVA_PARSER_PATH PATH',''),
345 set_preference(path_to_java_parser,ParserLoc))
346 ),
347 if_option_set(parserport(ParserPort),
348 connect_to_external_console_parser_on_port(ParserPort)),
349 generate_time_stamp(Datime,NOW),
350 if_option_set(log(LogF,Mode),
351 cli_start_logging(LogF,Mode,NOW,Datime,RemArgV)),
352 if_option_set(runtimechecking,
353 turn_on_run_time_type_checks,
354 turn_off_run_time_type_checks),
355 if_option_set(junit(JUX),
356 set_junit_mode(JUX)),
357 set_prefs,
358 (option_verbose, (option(set_prefs_from_file(_)) ; option(set_preference_group(_,_))),
359 get_non_default_preferences(list(NDPrefs))
360 -> format('Non-default preferences:~n',[]),print_list(NDPrefs),nl ; true),
361 set_optional_errors,
362 check_unavailable_options,
363 cli_show_help(ArgV,RemArgV),
364 if_option_set(set_argv(ArgVStr),
365 set_argv(ArgVStr)),
366 if_option_set(selfcheck(_,_),
367 cli_start_selfcheck),
368 if_option_set(typechecker_test(Filename),
369 (run_typecheck_testcase(Filename,typesok) -> halt_prob(NOW,0); halt_prob(NOW,1))),
370 if_option_set(install_prob_lib(LIBTOINSTALL,INSTALLOPTS), install_prob_lib(LIBTOINSTALL,INSTALLOPTS)),
371 if_options_set(print_version(VERSIONKIND), print_version(VERSIONKIND)),
372 if_option_set(check_java_version, check_java_version),
373 if_option_set(very_verbose,
374 preferences:print_preferences),
375 if_option_set(zmq_worker(Identifier), zmq_start_worker(Identifier, NOW)),
376 %if_option_set(zmq_worker2(MasterIP, Port, ProxyID, Logfile), zmq_start_worker(MasterIP,Port,ProxyID,Logfile,NOW)),
377 % process remaining arguments as files to load
378 debug_println(6,processing(RemArgV)),
379 cli_load_files(RemArgV,NOW), % all CLI arguments which are not understood are supposed to be files to be treated
380 debug_println(19,finished_loading(RemArgV)),
381 if_option_set(socket(Port,Loopback),
382 cli_start_socketserver(Port,Loopback)),
383 % check_all_expected_errors_occurred(NOW), % is now checked for each file; socket_server should not generate errors ?
384 debug_println(20,'% probcli execution finished'),
385 cli_print_junit_results(ArgV),
386 debug_println(20,'% Stored Junit results'),
387 stop_xml_probcli_run(NOW),
388 debug_println(20,'% ProB Finished').
389
390 % finish logxml file by writing total number of errors and warnings
391 stop_xml_probcli_run(NOW) :-
392 get_counter(cli_errors,CErrs), get_counter(cli_warnings,CWarns), get_counter(cli_expected_errors,EErrs),
393 writeln_log_time(prob_finished(NOW,CErrs,CWarns)),
394 (EErrs>0
395 -> write_xml_element_to_log('probcli-errors',[errors/CErrs,warnings/CWarns,expected_errors/EErrs])
396 ; write_xml_element_to_log('probcli-errors',[errors/CErrs,warnings/CWarns])
397 ),
398 ((CErrs>0 ; CWarns>0) -> format(user_error,'! Total Errors: ~w, Warnings:~w~n',[CErrs,CWarns]) ; true),
399 stop_xml_group_in_log('probcli-run'). % Generating this tag means probcli ran to completion without segfault,...
400
401 % check if a cli argument looks like a proper filename
402 :- public check_file_arg/2. % is actually called when parsing options
403 check_file_arg(File,Command) :- normalise_option_atom(File,NF),
404 recognised_option(NF,_,_,_),!,
405 ajoin(['Command-line file argument for ', Command, ' looks like another probcli command: '],Msg),
406 add_warning(probcli,Msg,File).
407 check_file_arg(File,Command) :-
408 tools:check_filename_arg(File,Command).
409
410 % check if a remaining argument looks suspicious (e.g., like an unknown command)
411 check_atom_looks_like_file(Number) :- number(Number),!,
412 add_warning(probcli,'Command-line argument is a number (expected file name or probcli command): ',Number).
413 check_atom_looks_like_file(File) :- atom_codes(File,Codes),
414 check_codes_look_like_file(Codes,File).
415 check_codes_look_like_file(Codes,Arg) :-
416 check_codes_resembles_command(Codes,Arg),!.
417 check_codes_look_like_file([D|T],Arg) :- D >= 0'0, D =< 0'9,
418 nonmember(0'/,T), % detect things like 01_Jan/a.mch
419 !,
420 add_message(probcli,'Command-line argument looks like a number: ',Arg).
421 check_codes_look_like_file(_,_).
422
423 check_codes_resembles_command([45|_],Arg) :- !,
424 (get_possible_fuzzy_match_options(Arg,FuzzyMatches),
425 FuzzyMatches \= []
426 -> (FuzzyMatches=[FM]
427 -> ajoin(['Command-line argument ', Arg, ' looks like a probcli command! Did you mean: '],Msg),
428 add_warning(probcli,Msg,FM)
429 ; ajoin(['Command-line argument ', Arg, ' looks like a probcli command! Did you mean any of: '],Msg),
430 add_warning(probcli,Msg,FuzzyMatches)
431 )
432 ; get_possible_options_completion_msg(Arg,Completions)
433 -> ajoin(['Command-line argument ', Arg, ' looks like a probcli command! Did you mean: '],Msg),
434 add_warning(probcli,Msg,Completions)
435 ; add_message(probcli,'Command-line argument looks like an unknown probcli command: ',Arg)).
436
437 :- use_module(extrasrc(refinement_checker),[valid_failures_model/2]).
438 check_failures_mode(Shortcut,FailuresModel) :- valid_failures_model(FailuresModel,Shortcut),!.
439 check_failures_mode(Shortcut,trace) :-
440 add_warning(probcli,'Unrecognised refinement model flag (must be F, FD, T, R, RD, V, VD; using default trace model T): ',Shortcut).
441
442 % ----------
443
444 cli_init_options(ArgV,RemArgV) :- %print(argv(ArgV)),nl,
445 append(ProBArgV,['--'|BArgV],ArgV),!, % pass arguments after -- to B via external_functions
446 cli_init_options2(ProBArgV,RemArgV),
447 debug_println(20,set_argv_from_list(BArgV)),
448 external_functions:set_argv_from_list(BArgV).
449 cli_init_options(ArgV,RemArgV) :- cli_init_options2(ArgV,RemArgV).
450 cli_init_options2(ArgV,RemArgV) :-
451 reset_options,
452 %%assertz(option(log('/tmp/ProBLog.log'))), print('LOGGING'),nl, %% coment in to build a version of probcli that automatically logs
453 ( get_options(ArgV,recognised_cli_option,Options,RemArgV,throw(halt(1))) ->
454 assert_all_options(Options)
455 ;
456 print_error(get_options_failed(ArgV)),definite_error_occurred).
457 cli_show_help(ArgV,RemArgV) :-
458 ( (option(help) ; ArgV=[]) ->
459 print_help, (RemArgV=[] -> halt_exception ; true)
460 ; true).
461 cli_start_logging(F,Mode,NOW,Datime,RemArgV) :-
462 debug_print(20,'%logging to: '), debug_println(20,F),
463 set_log_file(F), set_logging_mode(Mode),
464 start_xml_group_in_log('probcli-run'),
465 writeln_log(start_logging(NOW,F)),
466 version(V1,V2,V3,Suffix), revision(Rev), lastchangeddate(LCD),
467 writeln_log(version(NOW,V1,V2,V3,Suffix,Rev,LCD)), % still used by log_analyser
468 current_prolog_flag(version,PV),
469 write_xml_element_to_log(version,[major/V1,minor/V2,patch/V3,suffix/Suffix,revision/Rev,lastchanged/LCD,prolog/PV]),
470 findall(Opt, option(Opt), Options),
471 write_prolog_term_as_xml_to_log(options(NOW,Options)),
472 write_prolog_term_as_xml_to_log(files(NOW,RemArgV)), %
473 datime(Datime,DateRecord),
474 writeln_log(date(NOW,DateRecord)),
475 (DateRecord=datime(Yr,Mon,Day,Hr,Min,Sec)
476 -> write_xml_element_to_log(date,[year/Yr,month/Mon,day/Day,hour/Hr,minutes/Min,seconds/Sec]) ; true).
477
478 cli_start_selfcheck :-
479 %clear_loaded_machines_wo_errors,
480 b_set_initial_machine,
481 set_animation_mode(b),
482 store_virtual_event(clear_specification), % TO DO: try and get rid of the need for this
483 start_animation,
484 option(selfcheck(ModuleCombo,Opts)),
485 (atom(ModuleCombo),
486 atom_split(Module,':',TestNrA,ModuleCombo)
487 -> convert_atom_to_number(TestNrA,TestNr),
488 Opts2=[run_only_nr(TestNr)|Opts]
489 ; Module=ModuleCombo, Opts2=Opts
490 ),
491 (option(silent) -> Opts3=[silent|Opts2] ; option(verbose) -> Opts3=[verbose|Opts2] ; Opts3=Opts2),
492 (perform_self_check(Module,Opts3) -> true ; error_occurred(selfcheck)),
493 fail.
494 cli_start_selfcheck.
495
496
497 :- dynamic file_loaded/2.
498 file_loaded(Status) :- file_loaded(Status,_File).
499
500
501 cli_load_files([],NOW) :- % no files are provided
502 !,
503 ( options_allow_start_without_file
504 -> debug_format(19,'Using empty machine to process probcli command~n',[]),
505 cli_set_empty_machine
506 ; we_did_something -> true
507 ; print('No file to process'),nl),
508 writeln_log_time(start_processing_empty_machine(NOW)),
509 start_xml_feature(process_file,filename,'$EMPTY_MACHINE',FINFO),
510 cli_process_loaded_file(NOW,'$EMPTY_MACHINE'),
511 check_all_expected_errors_occurred(NOW), % check that all expected errors occurred; below they will be checked for each file
512 stop_xml_feature(process_file,FINFO),
513 (option(benchmark_info_csv_output(_,_)) -> print_accumulated_infos(0) ; true).
514 cli_load_files(RemArgV,NOW) :-
515 cli_load_files2(RemArgV,NOW,0).
516
517
518 cli_set_empty_machine :- % TO DO: do this more properly here and for initialise_required
519 % announce_event(clear_specification),
520 set_animation_mode(b),
521 % announce_event(start_initialising_specification),
522 bmachine:b_set_empty_machine,
523 assertz(file_loaded(true,'$$empty_machine')).
524 %announce_event(specification_initialised).
525
526 empty_machine_loaded :- file_loaded(true,'$$empty_machine').
527
528
529 options_allow_start_without_file :- option(run_benchmark(_,_,_)).
530 options_allow_start_without_file :- option(eval_repl(_)).
531 options_allow_start_without_file :- option(eval_string_or_file(_,_,_,_,_)).
532 options_allow_start_without_file :- option(check_log(_)).
533 options_allow_start_without_file :- option(process_latex_file(_,_)).
534 options_allow_start_without_file :- option(socket(_,_)).
535
536 we_did_something :- option(print_version(_)).
537 we_did_something :- option(check_java_version).
538 we_did_something :- option(check_parser_version).
539 we_did_something :- option(install_prob_lib(_,_)).
540
541 option_only_works_for_single_file(zmq_assertion(_Identifier)).
542 option_only_works_for_single_file(zmq_master(_Identifier)).
543
544 clear_loaded_files :-
545 (file_loaded(_) -> clear_loaded_machines_wo_errors ; true).
546
547 % called if we have at least one file
548 cli_load_files2([],_,NrFilesProcessed) :- !,
549 debug_println(19,finished_procesing_all_files(NrFilesProcessed)),
550 print_accumulated_infos(NrFilesProcessed). % print summary of all runs for different files
551 cli_load_files2([F1,F2|T],NOW,_NrFilesProcessed) :-
552 option(Option),
553 option_only_works_for_single_file(Option),!,
554 add_error(probcli,'The following option can only be used for a single file: ',Option),
555 add_error(probcli,'Multiple files provided: ',[F1,F2|T]),
556 halt_prob(NOW,0).
557 cli_load_files2(RemArgV,NOW,NrFilesProcessed) :-
558 %print_total_probcli_timer,
559 clear_loaded_files,
560 retractall(file_loaded(_,_)),
561 RemArgV = [MainFile0|Rest],!,
562 N1 is NrFilesProcessed+1,
563 cli_load_files3(MainFile0,Rest,NOW,N1).
564 cli_load_files3(MainFile0,Rest,NOW,NrOfFile) :-
565 safe_absolute_file_name(MainFile0,MainFile,[access(none)]), % converts Windows slash into Unix slash,...
566 if_option_set(file_info,print_file_info(MainFile)),
567 ((Rest=[_|_] ; NrOfFile>1)
568 -> length(Rest,RLen), Tot is NrOfFile+RLen,
569 format('~n~n% Processing file ~w/~w: ~w~n',[NrOfFile,Tot,MainFile]) % was formatsilent
570 ; true),
571 start_xml_feature(process_file,filename,MainFile,FINFO),
572 ( file_exists(MainFile) ->
573 debug_println(6,file_exists(MainFile)),
574 ( load_main_file(MainFile,NOW,Already_FullyProcessed) ->
575 (Already_FullyProcessed==true
576 -> true
577 ; assertz(file_loaded(true,MainFile)),
578 trimcore_if_useful(Rest),
579 writeln_log_time(start_processing(NOW)),
580 start_probcli_timer(Timer),
581 catch((cli_process_loaded_file(NOW,MainFile)
582 -> stop_probcli_debug_timer(Timer,'% Finished processing file after')
583 ; print_error('Processing or loading file failed: '), print_error(MainFile),
584 start_repl_even_after_failure
585 ),
586 user_interrupt_signal, % catch CTRL-C by user but give chance to enter REPL
587 start_repl_even_after_failure
588 ),
589 writeln_log_time(finished_processing(NOW))
590 )
591 ;
592 assertz(file_loaded(error,MainFile)),
593 print_error('Loading Specification Failed'),
594 writeln_log_time(loading_failed(NOW,MainFile)),
595 error_occurred(load_main_file)
596 %start_repl_even_after_failure : TODO: fix issues with bmachine not precompiled and counter extension
597 ),
598 nls,
599 ifm_option_set(pretty_print_prolog_file(PPFILE0),
600 pretty_print_prolog_file(PPFILE0))
601 ; % not file_exists
602 nl, assertz(file_loaded(error,MainFile)),
603 (number(MainFile0)
604 -> add_error(load_main_file,'Command-line argument is a number which is not associated with a command and does not exist as file: ',MainFile0)
605 ; atom_codes(MainFile0,[45|_]) % starts with a dash - : probably an illegal command-line option
606 -> add_error(load_main_file,'Specified option or file does not exist: ',MainFile0)
607 ; get_filename_extension(MainFile,Ext), \+ known_spec_file_extension(Ext,_)
608 -> (Ext = '' -> EMsg = 'Specified file does not exist and has no file extension:'
609 ; ajoin(['Specified file does not exist and has an unrecognised file extension ".',Ext,'" :'], EMsg)
610 ),
611 add_error(load_main_file,EMsg,MainFile)
612 ; add_error(load_main_file,'Specified file does not exist:',MainFile)
613 )
614 ),
615 check_all_expected_errors_occurred(NOW),
616 stop_xml_feature(process_file,FINFO),
617
618 debug_println(19,reset_expected_error_occurred),
619 reset_expected_error_occurred, % reset for next file
620 debug_println(19,resetting_errors),
621 reset_errors,
622 debug_println(19,update_time_stamp),
623 NOW1 is NOW+1,
624 update_time_stamp(NOW1),
625 debug_println(19,remaining_files_to_process(Rest)),
626 cli_load_files2(Rest,NOW1,NrOfFile).
627
628 start_repl_even_after_failure :-
629 (option(eval_repl([]))
630 -> format_with_colour_nl(user_output,[blue],'Starting REPL, but ignoring any other commands',[]),
631 % TODO: check if setup_constants_fails and then suggest e.g. :core @PROPERTIES command
632 start_repl_if_required % can be useful to debug properties, e.g, one can fix an error and reload
633 ; true
634 ).
635
636 print_file_info(F) :-
637 print('Specification_File('), print(F), print(')'),nl.
638
639 :- use_module(probsrc(tools),[statistics_memory_used/1]).
640 trimcore_if_useful(_) :- option(release_java_parser),!, prob_trimcore.
641 % if user wants to release java parser, this is an indication that the .prob files are big and it can be good to free memory
642 trimcore_if_useful([]) :- % try and reduce Prologs memory consumption, see also PROLOGKEEPSIZE parameter
643 % a lot of memory can be consumed loading .prob file and doing machine construction
644 !,
645 (option(X), memory_intensive_option(X)
646 -> debug_format(9,'Not trimming memory usage because of memory intensive option: ~w~n',[X])
647 ; statistics_memory_used(M), M< 300000000 % less than 300 MB used
648 -> debug_format(9,'Not trimming memory usage because of memory used is already low: ~w~n',[M])
649 ; prob_trimcore
650 ).
651 trimcore_if_useful(_) :- debug_println(9,'Not trimming memory usage as there are still files to process').
652
653 prob_trimcore :- (option(verbose) ; option(release_java_parser)),!,prob_trimcore_verbose.
654 prob_trimcore :- prob_trimcore_silent.
655
656 prob_trimcore_verbose :-
657 print('Memory used before trimming: '),print_memory_used_wo_gc,flush_output, nl_time,
658 prob_trimcore_silent,
659 print('Memory used after trimming : '),print_memory_used_wo_gc,flush_output, nl_time.
660 prob_trimcore_silent :-
661 garbage_collect, % is important, otherwise trimming may achieve very little
662 trimcore.
663
664 memory_intensive_option(cli_mc(_)).
665 memory_intensive_option(ltl_formula_model_check(_,_)).
666 memory_intensive_option(ctl_formula_model_check(_,_)).
667 memory_intensive_option(refinement_check(_,_,_)).
668 memory_intensive_option(generate_all_traces_until(_,_,_)).
669
670 % ---------------------
671
672 % process all the commands for a loaded file:
673 cli_process_loaded_file(NOW,MainFile) :-
674 (real_error_occurred -> print_error('% *** Errors occurred while loading ! ***'),nl,nl ; true),
675 get_errors, reset_errors,
676 if_option_set(kodkod_performance(KPFile,Iterations),
677 compare_kodkod_performance1(KPFile,Iterations,NOW)),
678 if_option_set(kodkod_comparision(MaxResiduePreds),
679 test_kodkod_and_exit(MaxResiduePreds,NOW)),
680 % if_option_set(add_csp_guide(CspGuide), tcltk_add_csp_file(CspGuide)), %% moved to later to ensure B machine is precompiled; allows e.g. type_check_csp_and_b to run
681
682 if_option_set(csp_main(MAINPROC),
683 set_cspm_main_process(MAINPROC)),
684
685 if_option_set(zmq_master(Identifier), zmq_start_master(invariant,Identifier)),
686 %if_option_set(zmq_master(IP, Logfile), zmq_start_master(invariant,200,-1,5000,0,IP,Logfile)),
687
688 ifm_option_set(check_machine_file_sha(FileToCheck,ExpectedSha1Hash),
689 check_machine_file_sha(FileToCheck,ExpectedSha1Hash)),
690
691 % STARTING ANIMATION/MODEL CHECKING
692 cli_start_animation(NOW),
693
694 if_option_set_loaded(cli_core_properties(MaxCoreSize),cli_core_properties,
695 cli_core_properties(MaxCoreSize)),
696
697 if_option_set_loaded(default_trace_check,default_trace_check,
698 cli_start_default_trace_check(MainFile)),
699 if_option_set_loaded(trace_check(TrStyle,TraceFile,ChkMode),trace_check,
700 cli_start_trace_check(TrStyle,TraceFile,ChkMode)),
701
702 cli_process_loaded_file_afer_start_animation(NOW).
703
704 cli_process_loaded_file_afer_start_animation(NOW) :-
705 ifm_option_set(cli_print_machine_info(IKind),
706 cli_print_machine_info(IKind)),
707 ifm_option_set(pretty_print_internal_rep(PPFILE1,MachName1,TYPES1,ASCII1),
708 pretty_print_internal_rep(PPFILE1,MachName1,TYPES1,ASCII1)),
709 ifm_option_set(pretty_print_internal_rep_to_B(PPFILE3),
710 b_write_eventb_machine_to_classicalb_to_file(PPFILE3)),
711
712 if_option_set_loaded(state_trace(TraceFile),state_trace,
713 cli_start_trace_state_check(TraceFile)),
714
715 if_option_set(evaldot(EvalDotF),
716 set_eval_dot_file(EvalDotF)),
717
718 (initialise_required
719 -> check_loaded(initialise),
720 cli_start_initialisation(NOW),
721 writeln_log_time(initialised(NOW))
722 ; true),
723 if_option_set(check_abstract_constants,
724 check_abstract_constants),
725
726 if_option_set(zmq_assertion(Identifier),
727 zmq_start_master(assertion,Identifier)),
728
729 if_option_set(cli_lint,cli_lint(_)),
730 ifm_option_set_loaded(cli_lint(LintCheck),cli_lint,cli_lint(LintCheck)),
731 if_option_set(cli_wd_check(Disch,TotPos),cli_wd_check(Disch,TotPos)),
732 if_option_set(cli_wd_inv_proof(UnchangedNr,ProvenNr,TotPOsNr),cli_wd_inv_proof(UnchangedNr,ProvenNr,TotPOsNr)),
733 if_option_set(cli_start_mc_with_tlc,cli_start_mc_with_tlc),
734 if_option_set(cli_start_sym_mc_with_lts(LType),cli_start_sym_mc_with_lts(LType)),
735
736 if_option_set(cli_symbolic_model_check(Algorithm),cli_symbolic_model_check(Algorithm)),
737
738 if_option_set_loaded(cli_check_properties,check_properties,
739 cli_check_properties(NOW)),
740 ifm_option_set_loaded(cli_check_assertions(ALL,ReqInfos),check_assertions,
741 cli_check_assertions(ALL,ReqInfos,NOW)),
742 if_option_set(set_goal(GOAL),
743 cli_set_goal(GOAL)),
744 if_option_set(set_searchscope(SCOPE),
745 cli_set_searchscope(SCOPE)),
746 ifm_option_set_loaded(cli_mc(Nr,MCOpts),model_check,
747 cli_start_model_check(Nr,NOW,MCOpts)),
748 ifm_option_set_loaded(cli_random_animate(Steps,ErrOnDeadlock),animate,
749 cli_random_animate(NOW,Steps,ErrOnDeadlock)),
750 ifm_option_set_loaded(execute(ESteps,ErrOnDeadlock,From),execute,
751 cli_execute(ESteps,ErrOnDeadlock,From)),
752 if_option_set_loaded(pa_check,predicate_analysis,
753 test_predicate_analysis),
754
755 cbc_check(NOW),
756
757 ifm_option_set_loaded(logxml_write_ids(Prefix,IDScope),logxml_write_ids,
758 logxml_write_ids(Prefix,IDScope)),
759
760 if_options_set(generate_read_write_matrix_csv(RWCsvFile),
761 generate_read_write_matrix(RWCsvFile)),
762 if_options_set(feasibility_analysis_csv(TimeOut,EnablingCsvFile),
763 do_feasibility_analysis(TimeOut,EnablingCsvFile)),
764 ifm_option_set_loaded(mcm_tests(ADepth1,AMaxS,ATarget1,Output1),mcm_test_cases,
765 mcm_test_case_generation(ADepth1,AMaxS,ATarget1,Output1)),
766 ifm_option_set_loaded(all_deadlocking_paths(File),all_deadlocking_paths,
767 write_all_deadlocking_paths_to_xml(File)),
768 ifm_option_set_loaded(cbc_tests(ADepth2,ATarget2,Output2),cb_test_cases,
769 cbc_test_case_generation(ADepth2,ATarget2,Output2)),
770 ifm_option_set_loaded(test_description(TestDescFile),cb_test_cases,
771 test_generation_by_xml_description(TestDescFile)),
772 if_options_set(csp_in_situ_refinement_check(RP,RType,RQ),
773 cli_csp_in_situ_refinement_check(RP,RType,RQ,NOW)),
774 if_options_set(csp_checkAssertion(Proc,Model,AssertionType),
775 cli_checkAssertion(Proc,Model,AssertionType,NOW)),
776 if_options_set(check_csp_assertion(Assertion),
777 cli_check_csp_assertion(Assertion,NOW)),
778 if_options_set(refinement_check(RefFile,PerformSingleFailures,RefNrNodes),
779 cli_start_refinement_check(RefFile,PerformSingleFailures,RefNrNodes,NOW)),
780 if_options_set(ctl_formula_model_check(Formula,Expected),cli_ctl_model_check(Formula,init,Expected,_)),
781 % TO DO print ctl/ltl statistics
782 if_options_set(csp_get_assertions,cli_csp_get_assertions),
783 if_options_set(eval_csp_expression(CspExpr),cli_eval_csp_expression(CspExpr)),
784 if_options_set(csp_translate_to_file(PlFile),cli_csp_translate_to_file(PlFile)),
785 if_options_set(get_coverage_information(CovFileName),cli_get_coverage_information(CovFileName)), %% TODO: replace
786 if_options_set(vacuity_check,cli_vacuity_check),
787 if_option_set_loaded(check_goal,check_goal,cli_check_goal),
788 if_option_set_loaded(animate,animate,
789 (interactive_animate_machine -> true ; true)),
790 if_option_set(ltsmin, start_ltsmin_srv('/tmp/ltsmin.probz', NOW)),
791 if_option_set(ltsmin2(EndpointPath), start_ltsmin_srv(EndpointPath, NOW)),
792 if_option_set(ltsmin_ltl_output(Path), ltsmin_ltl_output(Path, NOW)),
793 if_options_set(run_benchmark(Kind,Option,Path), run_benchmark(Kind,Option,Path)),
794 evaluate_from_commandline,
795 if_option_set_loaded(ltl_assertions,check_ltl_assertions,
796 (timeout_call(ltl_check_assertions,NOW,check_ltl_assertions) -> true; true)),
797 ifm_option_set_loaded(ltl_formula_model_check(Formula,Expected),check_ltl_assertions,
798 (option(cli_start_sym_mc_with_lts(_))-> true % we request LTSMin, do not start prob model check
799 ; timeout_call(cli_ltl_model_check(Formula,init,Expected,_),NOW,check_ltl_assertions)
800 -> true; true)),
801 ifm_option_set_loaded(ltl_file(LtlFilename),check_ltl_file,
802 (ltl_check_file(LtlFilename) -> true; true)),
803 ifm_option_set_loaded(visb_history(VJSONFile,VHTMLFile,Options),visb,
804 cli_visb_history(VJSONFile,VHTMLFile,Options)),
805 ifm_option_set_loaded(history(HistoryFilename),history,
806 cli_print_history(HistoryFilename)),
807 ifm_option_set_loaded(print_values(ValuesFilename),sptxt,
808 cli_print_values(ValuesFilename)),
809 ifm_option_set_loaded(print_all_values(ValuesDirname),print_all_values,
810 cli_print_all_values(ValuesDirname)),
811 ifm_option_set_loaded(generate_all_traces_until(LTL_Stop_AsAtom,FilePrefix),generate_all_traces_until,
812 cli_generate_all_traces_until(LTL_Stop_AsAtom,FilePrefix)),
813 if_options_set(save_state_for_refinement(SaveRefF),
814 tcltk_save_specification_state_for_refinement(SaveRefF)),
815 if_options_set(dot_command(DCommand1,DotFile1,DotEngine1),
816 dot_command(DCommand1,DotFile1,DotEngine1)),
817 if_options_set(dot_command_for_expr(DECommand,Expr,DotFile,Opts,DotEngine),
818 dot_command_for_expr(DECommand,Expr,DotFile,Opts,DotEngine)),
819 if_options_set(plantuml_command(PCommand1,UmlFile1),
820 plantuml_command(PCommand1,UmlFile1)),
821 if_options_set(plantuml_command_for_expr(PECommand,Expr,UmlFile,Opts),
822 plantuml_command_for_expr(PECommand,Expr,UmlFile,Opts)),
823 if_options_set(csv_table_command(TECommand,TableFormulas,TableOptions,TableCSVFile),
824 csv_table_command(TECommand,TableFormulas,TableOptions,TableCSVFile)),
825 if_options_set(evaluate_expression_over_history_to_csv_file(HistExpr,HistDotFile),
826 tcltk_interface:evaluate_expression_over_history_to_csv_file(HistExpr,HistDotFile)),
827 if_options_set(enabling_analysis_csv(EnablingCsvFile),
828 do_enabling_analysis_csv(EnablingCsvFile,NOW)),
829 if_options_set(process_latex_file(LatexF1,LatexF2),
830 process_latex_file(LatexF1,LatexF2)),
831 ifm_option_set(coverage(Nodes,Operations,ShowEnabledInfo),
832 cli_show_coverage(Nodes,Operations,ShowEnabledInfo,NOW)),
833 ifm_option_set(check_statespace_hash(ExpectedHash,Kind),
834 cli_check_statespace_hash(ExpectedHash,Kind)),
835 ifm_option_set(check_op_cache(ExpectedC),
836 cli_check_op_cache(ExpectedC)),
837 ifm_option_set(coverage(ShowEnabledInfo),
838 cli_show_coverage(ShowEnabledInfo,NOW)),
839 if_option_set(save_state_space(StateFile),
840 save_state_space(StateFile)),
841 ifm_option_set(cli_print_statistics(SPARA),
842 cli_print_statistics(SPARA)),
843 if_option_set(show_cache,
844 show_cache),
845 if_option_set(check_complete, check_complete),
846 if_option_set(check_complete_operation_coverage, check_complete_operation_coverage),
847 if_option_set(check_scc_for_ltl_formula(LtlFormula,SCC),cli_check_scc_for_ltl_formula(LtlFormula,SCC)).
848
849 % what needs to be done for files like .po files, where all processing is already done:
850 cli_process_options_for_alrady_fully_processed_file(_MainFile) :-
851 ifm_option_set(cli_print_statistics(SPARA),
852 cli_print_statistics(SPARA)).
853
854 :- use_module(value_persistance,[show_cache_file_contents/1]).
855 show_cache :- option(verbose),!,show_cache(verbose).
856 show_cache :- show_cache(normal).
857
858 show_cache(Verbose) :-
859 show_cache_file_contents(Verbose),nl.
860
861 % new profiler
862 %:- use_module('../extensions/profiler/profiler.pl').
863 %cli_print_statistics :- pen,nl,garbage_collect,statistics,nl,state_space:state_space_initialise_with_stats.
864
865 :- use_module(runtime_profiler,[print_runtime_profile/0]).
866 :- use_module(source_profiler,[print_source_profile/0]).
867 :- use_module(memoization,[print_memo_profile/0]).
868 :- use_module(state_packing,[print_state_packing_profile/0]).
869 :- use_module(external_functions,[print_external_function_instantiation_profile/0]).
870
871 % old profiler
872 :- use_module(covsrc(hit_profiler),[print_hit_profile_statistics/0]).
873 :- use_module(extrasrc(b_operation_cache),[print_op_cache_profile/0, reset_b_operation_cache_with_statistics/0]).
874 :- use_module(memoization,[reset_memo_with_statistics/0]).
875 :- use_module(disproversrc(disprover),[print_prover_result_stats/0]).
876 :- use_module(probsrc(tools),[print_mb/1]).
877 cli_print_statistics(memory) :- !,
878 print_memory_statistics(user_output).
879 cli_print_statistics(sicstus_profile) :- !,
880 format('SICStus Prolog PROFILE STATISTICS~n',[]),
881 sicstus_profile_statistics.
882 cli_print_statistics(disprover_profile) :- !,
883 print_prover_result_stats.
884 cli_print_statistics(prob_profile) :- !,
885 statistics(walltime,[WT,_]),
886 statistics(runtime,[RT,_]),
887 format('--------------------------~nPROB PROFILING INFORMATION after ~w ms walltime (~w ms runtime) ',[WT,RT]),
888 statistics_memory_used(M), print_mb(M),nl,
889 print_source_profile,
890 print_runtime_profile,
891 print_memo_profile,
892 print_state_packing_profile,
893 print_external_function_instantiation_profile,
894 (get_preference(try_operation_reuse,false) -> true ; print_op_cache_profile).
895 cli_print_statistics(hit_profile) :- !,
896 (print_hit_profile_statistics -> true ; true). % mainly used by external functions
897 cli_print_statistics(op_cache_profile) :- !,
898 get_preference(try_operation_reuse,OR),
899 format('PROB OPERATION_REUSE (value:~w) STATISTICS~n',[OR]),
900 print_op_cache_profile.
901 cli_print_statistics(full) :- format('PROB FULL STATISTICS~n',[]),
902 sicstus_profile_statistics,
903 garbage_collect,
904 statistics,
905 nl,
906 (get_preference(try_operation_reuse,false) -> true ; print_op_cache_profile),
907 print_prover_result_stats,
908 state_space:state_space_initialise_with_stats,
909 reset_memo_with_statistics,
910 reset_b_operation_cache_with_statistics.
911
912 print_memory_statistics(Stream) :-
913 garbage_collect,
914 write(Stream,'ProB memory used: '),
915 print_memory_used_wo_gc(Stream), nl(Stream), flush_output(Stream).
916
917 sicstus_profile_statistics :-
918 %(hit_profiler:print_hit_profile_statistics -> true ; true), % only used by external functions
919 (option(profiling_on)
920 -> catch(print_profile,
921 error(existence_error(_,_),_),
922 print_red('SICStus Prolog Profiler can only be used when running from source'))
923 ; true).
924
925
926 :- use_module(state_space,[not_all_transitions_added/1, not_invariant_checked/1,
927 not_interesting/1, get_operation_name_coverage_infos/4]).
928 check_complete :-
929 (tcltk_find_max_reached_node(Node1) ->
930 add_error(check_complete,'Maximum number of transitions reached for at least one state: ',Node1) ; true),
931 (not_all_transitions_added(Node2) ->
932 add_error(check_complete,'At least one state was not examined: ',Node2) ; true),
933 (not_invariant_checked(Node3) ->
934 add_error(check_complete,'The invariant was not checked for at least one state: ',Node3) ; true),
935 (not_interesting(Node4) ->
936 add_message(check_complete,'At least one state was ignored (not satisfying the SCOPE predicate): ',Node4) ; true).
937
938 check_complete_operation_coverage :-
939 (state_space: operation_name_not_yet_covered(OpName) ->
940 add_error(check_complete_operation_coverage,'At least one operation is not covered: ', OpName)
941 ; true).
942
943 show_operation_coverage_summary(NOW) :-
944 get_operation_name_coverage_infos(PossibleNr,FeasibleNr,UncovNr,UncoveredList),
945 writeln_log(uncovered_info(NOW,PossibleNr,UncoveredList)),
946 (UncovNr=0 -> format(' All ~w possible operations have been covered',[PossibleNr]),nl
947 ; (FeasibleNr=PossibleNr
948 -> format(' The following ~w operations (out of ~w) were not covered:~n ~w~n',
949 [UncovNr, PossibleNr,UncoveredList])
950 ; INr is PossibleNr-FeasibleNr,
951 format(' The following ~w operations (out of ~w with ~w infeasible) were not covered:~n ~w~n',
952 [UncovNr, PossibleNr, INr,UncoveredList])
953 )).
954 show_initialisation_summary(NOW) :-
955 findall(ID,state_space:is_concrete_constants_state_id(ID),L),
956 length(L,Nr), N1 is Nr+1, % for root
957 writeln_log(uninitialised_states(NOW,N1)),
958 format(' Uninitialised states: ~w (root and constants only)~n',[N1]).
959
960 % ---------------------
961
962 animation_mode_does_not_support_animation(File) :-
963 loaded_main_file(smt2,File).
964 cli_start_animation(NOW) :-
965 file_loaded(true,LoadedFile),
966 \+ animation_mode_does_not_support_animation(LoadedFile),
967 !,
968 debug_println(20,'% Starting Animation'),
969 writeln_log_time(start_animation(NOW)),
970 start_probcli_timer(Timer1),
971 start_animation_without_computing,
972 stop_probcli_debug_timer(Timer1,'% Finished Starting Animation'),
973 if_option_set(add_csp_guide(CspGuide), tcltk_add_csp_file(CspGuide)),
974
975 xml_log_machine_statistics,
976 getAllOperations(Ops),
977 debug_print(20,'Operations: '), debug_println(20,Ops),
978
979 (we_need_only_static_assertions(ALL)
980 -> debug_println(20,'% Projecting on static ASSERTIONS'),
981 b_interpreter:set_projection_on_static_assertions(ALL) ; true),
982
983 (option(load_state(File))
984 -> debug_println(20,'% Loading stored state from file'),
985 state_space:tcltk_load_state(File)
986 ; computeOperations_for_root_required ->
987 debug_println(20,'% Searching for valid initial states'),
988 start_probcli_timer(Timer2),
989 cli_computeOperations(EO),
990 stop_probcli_debug_timer(Timer2,'% Finished searching for valid initial states'),
991 debug_println(10,EO)
992 ; debug_println(20,'% No initialisation required')
993 ).
994 cli_start_animation(_NOW).
995
996 start_animation_without_computing :-
997 update_preferences_from_spec(ListOfPrefs),
998 (ListOfPrefs=[] -> true ; write_prolog_term_as_xml_to_log(b_machine_preferences(ListOfPrefs))),
999 set_prefs, % override SET_PREF in DEFINITIONS with values from command-line;
1000 start_animation,
1001 ifm_option_set(add_additional_property(PROP),
1002 cli_add_additional_property(PROP)),
1003 get_errors.
1004
1005 % an execution engine with minimal overhead: states are not stored in visited_expression database, only first enabled operation is taken
1006 cli_execute(Steps,ErrorOnDeadlock,FromWhere) :-
1007 temporary_set_preference(try_operation_reuse,false,ChangeOccured),
1008 (ChangeOccured=true % operation reuse not compatible with cut used below after solution found
1009 -> add_message(execute_model,'Disabling OPERATION_REUSE preference for -execute ',Steps) ; true),
1010 call_cleanup(cli_execute2(Steps,ErrorOnDeadlock,FromWhere),
1011 reset_temporary_preference(ChangeOccured)).
1012 cli_execute2(Steps,ErrorOnDeadlock,FromWhere) :-
1013 FromWhere=from_all_initial_states,!,
1014 % try out all initial states and from each of those perform deterministic execution
1015 start_ms_timer(Start),
1016 format('Running execute from all initial states~n',[]),
1017 reset_counter(cli_execute_inits),
1018 findall(Result,
1019 (cli_trans(root,Action,CurState,0,'$NO_OPERATION'), %print(Action),nl,
1020 (\+ functor(Action,'$setup_constants',_)
1021 -> inc_counter(cli_execute_inits,Nr),
1022 format('~nExecuting model from initial state ~w~n',[Nr]),
1023 (option(animate_stats) -> print_state_silent(CurState) ; true),
1024 (cli_execute_from(CurState,Steps,ErrorOnDeadlock,1,Result) -> true)
1025 ; format('~nInitialising state~n',[]), % we need to execute initialise_machine
1026 cli_trans(CurState,_ActionName,NewState,0,'$NO_OPERATION'),
1027 inc_counter(cli_execute_inits,Nr),
1028 format('~nExecuting model from initial state ~w with constants~n',[Nr]),
1029 (option(animate_stats) -> print_state_silent(NewState) ; true),
1030 (cli_execute_from(NewState,Steps,ErrorOnDeadlock,2,Result) -> true)
1031 )), Results),
1032 get_counter(cli_execute_inits,Nr),
1033 format('---------~nTotal runtime for all ~w executions:',[Nr]),nl,
1034 stop_ms_timer(Start),
1035 count_occurences(Results,Occs), format('Results: ~w~n',[Occs]).
1036 cli_execute2(Steps,ErrorOnDeadlock,current_state(Repetitions)) :-
1037 current_expression(ID,CurState),
1038 start_xml_feature(execute,max_steps,Steps,FINFO),
1039 start_ms_timer(Start),
1040 (between(1,Repetitions,RepNr),
1041 % with -strict option we will stop after first error found
1042 % for repetitions you should probably set RANDOMISE_OPERATION_ORDER and RANDOMISE_ENUMERATION_ORDER to TRUE
1043 debug_format(19,'Starting execute (~w/~w) from state ~w with maximum number of steps ~w~n',[RepNr,Repetitions,ID,Steps]),
1044 (cli_execute_from(CurState,Steps,ErrorOnDeadlock,1,_Result) -> fail ; fail)
1045 ; Repetitions>1 -> stop_ms_timer_with_msg(Start,'-execute-repeat')
1046 ; true),
1047 stop_xml_feature(execute,FINFO).
1048
1049 :- use_module(bmachine,[b_top_level_operation/1]).
1050 allow_filter_unused_constants :-
1051 b_or_z_mode,
1052 b_top_level_operation(_), % we can filter out unused constants, unless there are no operations in which case the user probably wants to see the constant values
1053 \+ options_can_eval_any_cst.
1054
1055 options_can_eval_any_cst :- option(eval_repl(_)).
1056 options_can_eval_any_cst :- option(eval_string_or_file(_,_,_,_,_)).
1057 options_can_eval_any_cst :- option(dot_command(_,_,_)).
1058 options_can_eval_any_cst :- option(dot_command_for_expr(_,_,_,_,_)).
1059 options_can_eval_any_cst :- option(process_latex_file(_,_)).
1060 options_can_eval_any_cst :- option(logxml_write_ids(all,_)). % the user writes out constants (not just variables) to file: also do not filter
1061
1062 :- dynamic execute_timeout_occurred/0.
1063
1064 cli_execute_from(CurState,Steps,ErrorOnDeadlock,FirstStepNr,Result) :-
1065 retractall(max_walltime(_,_,_)),
1066 retractall(execute_timeout_occurred),
1067 start_ms_timer(Start),
1068 (allow_filter_unused_constants -> temporary_set_preference(filter_unused_constants,true,CHNG) ; true),
1069 cli_execute_aux(FirstStepNr,Steps,CurState,_MEMO,ErrorOnDeadlock,'$NO_OPERATION',Result),
1070 (allow_filter_unused_constants -> reset_temporary_preference(filter_unused_constants,CHNG) ; true),
1071 (option(silent) -> true ; stop_ms_timer_with_msg(Start,'-execute')),
1072 print_max_walltime.
1073
1074 :- use_module(tools_strings,[ajoin/2, ajoin_with_sep/3]).
1075 :- use_module(external_functions,[reset_side_effect_occurred/0, side_effect_occurred/1]).
1076 cli_execute_aux(Nr,Steps,CurState,_,_ErrorOnDeadlock,_LastActionName,Result) :- Nr>Steps,!,
1077 formatsilent('Stopping execution after ~w steps~n',[Steps]), Result = stopped,
1078 print_state_silent(CurState),
1079 cli_execute_add_virtual_transition(Steps,CurState,Result).
1080 cli_execute_aux(Nr,Steps,CurState0,MEMO,ErrorOnDeadlock,LastActionName,Result) :-
1081 (Nr mod 5000 =:= 0, \+option(animate_stats), \+option(silent)
1082 -> (var(LastActionName) -> format('Step ~w~n',[Nr])
1083 ; format('Step ~w (after ~w)~n',[Nr,LastActionName])),
1084 (option(verbose) -> print_state_silent(CurState0) ; true),
1085 %copy_term(CurState0,CurState), tools_printing:print_term_summary((CurState0)),nl,
1086 !,
1087 garbage_collect,
1088 !,
1089 print('Memory used: '),print_memory_used_wo_gc,flush_output,nl %nl_time
1090 ; true),
1091 prepare_state_for_specfile_trans(CurState0,unknown,MEMO,CurState), % ensure we memoize expanded constants in MEMO
1092 % avoid re-expanding constants in every state !
1093 % relevant e.g. for probcli -execute 20001 DataValidationTestSmallStep.mch -init
1094 (cli_invariant_ko(CurState,LastActionName,InvStatus,CliErr) -> % also recognises no_inv command
1095 N1 is Nr-1,
1096 ajoin(['INVARIANT ',InvStatus,' after ',N1,' steps (after ',LastActionName,').'],ErrMsg),
1097 format('~w~n',[ErrMsg]),!,
1098 print_state_silent(CurState),
1099 error_occurred_with_msg(CliErr,ErrMsg),
1100 Result=CliErr,
1101 cli_execute_add_virtual_transition(N1,CurState,Result,NewID),
1102 %(option_verbose -> b_interpreter:analyse_invariant_for_state(NewID) ; true)
1103 b_interpreter:analyse_invariant_for_state(NewID)
1104 ; \+ cli_assertions_ok(CurState,LastActionName) -> % also recognises no_inv command
1105 N1 is Nr-1,
1106 format('ASSERTION VIOLATED after ~w steps (after ~w).~n',[N1,LastActionName]),!,
1107 print_state_silent(CurState),
1108 error_occurred(assertion_violation), Result=assertion_violation,
1109 cli_execute_add_virtual_transition(N1,CurState,Result)
1110 ; cli_goal_found(CurState) -> % also recognizes no_goal command
1111 N1 is Nr-1,
1112 format('GOAL FOUND after ~w steps (after ~w).~n',[N1,LastActionName]),!,
1113 print_state_silent(CurState), Result=goal_found,
1114 cli_execute_add_virtual_transition(N1,CurState,Result)
1115 ; reset_side_effect_occurred,
1116 cli_trans(CurState,ActionName,NewState,Nr,LastActionName), % Compute new transition
1117 !,
1118 N1 is Nr+1,
1119 (NewState=CurState0, % could be expensive for large states; states are expanded ! % TO DO: look only at written variables ?!
1120 \+ side_effect_occurred(file)
1121 -> formatsilent('Infinite loop reached after ~w steps (looping on ~w).~n',[N1,ActionName]),
1122 Result=loop,
1123 cli_execute_add_virtual_transition(N1,CurState,Result)
1124 ; cli_execute_aux(N1,Steps,NewState,MEMO,ErrorOnDeadlock,ActionName,Result))
1125 ).
1126 cli_execute_aux(Nr,_Steps,CurState,_,_ErrorOnDeadlock,LastActionName,Result) :- execute_timeout_occurred,!,
1127 N1 is Nr-1,
1128 formatsilent('Timeout occurred after ~w steps (after ~w).~n',[N1,LastActionName]),
1129 Result=time_out,
1130 print_state_silent(CurState),
1131 cli_execute_add_virtual_transition(N1,CurState,Result).
1132 cli_execute_aux(Nr,_Steps,CurState,_,ErrorOnDeadlock,LastActionName,Result) :- N1 is Nr-1,
1133 formatsilent('Deadlock reached after ~w steps (after ~w).~n',[N1,LastActionName]),
1134 Result=deadlock,
1135 (ErrorOnDeadlock=true,\+ option(no_deadlocks) -> error_occurred(deadlock) ; true),
1136 print_state_silent(CurState),
1137 cli_execute_add_virtual_transition(N1,CurState,Result).
1138
1139 check_nr_of_steps(Steps) :- option(execute_expect_steps(ExpSteps)),
1140 (Steps = ExpSteps -> formatsilent('The expected number of steps were executed: ~w~n',[Steps]),fail
1141 ; true),
1142 !,
1143 ajoin(['Unexpected number of steps ',Steps,', expected:'],Msg),
1144 add_error(cli_execute,Msg,ExpSteps).
1145 check_nr_of_steps(_).
1146
1147 cli_execute_add_virtual_transition(Steps,CurState,Result) :-
1148 cli_execute_add_virtual_transition(Steps,CurState,Result,_).
1149 cli_execute_add_virtual_transition(Steps,CurState,Result,ToID) :-
1150 current_state_id(CurID),
1151 write_xml_element_to_log(executed,[steps/Steps,result/Result]),
1152 (Steps>0 -> tcltk_interface:tcltk_add_new_transition(CurID,'$execute'(Steps),ToID,CurState,[]),
1153 debug_format(19,'Added virtual transtion ~w -> ~w for ~w steps~n',[CurID,ToID,Steps]),
1154 tcltk_goto_state('$execute'(Steps),ToID)
1155 ; true),
1156 check_nr_of_steps(Steps).
1157
1158 :- dynamic max_walltime/3.
1159 print_max_walltime :- (max_walltime(Action,Nr,WT),option_verbose
1160 -> format('% Maximum walltime ~w ms at step ~w for ~w.~n',[WT,Nr,Action]) ; true).
1161
1162 % will be used to compute a single successor
1163 % b_operation_cannot_modify_state
1164 cli_trans(CurState,ActionName,NewState,Nr,LastActionName) :-
1165 option(animate_stats),!, % provide statistics about the animation
1166 start_probcli_timer(Timer),
1167 cli_trans_aux(CurState,ActionName,Act,NewState,Nr,LastActionName),
1168 (option_verbose -> translate:translate_event(Act,TStr)
1169 ; translate:translate_event_with_limit(Act,100,TStr)),
1170 format('~w~5|: ~w~n',[Nr,TStr]),
1171 format(' ~5|',[]),stop_probcli_timer(Timer,' '),
1172 (option_verbose -> format(' ~5|',[]),print_memory_used_wo_gc,nl ; true),
1173 flush_output,
1174 get_probcli_elapsed_walltime(Timer,WallTime),
1175 get_probcli_elapsed_runtime(Timer,RunTime),
1176 accumulate_infos(animate_stats,[step-1,step_nr-Nr,runtime-RunTime,walltime-WallTime]),
1177 (max_walltime(_,_,MWT), MWT >= WallTime -> true
1178 ; retractall(max_walltime(_,_,_)),
1179 assertz(max_walltime(ActionName,Nr,WallTime))).
1180 cli_trans(CurState,ActionName,NewState,Nr,LastActionName) :-
1181 cli_trans_aux(CurState,ActionName,_,NewState,Nr,LastActionName).
1182
1183 cli_trans_aux(CurState,ActionName,Act,NewState,Nr,LastActionName) :-
1184 option(timeout(TO)),!,
1185 safe_time_out(cli_trans_aux2(CurState,ActionName,Act,NewState,LastActionName),TO,Res),
1186 (Res=time_out -> format_error_with_nl('! Timeout occurred while performing step ~w of execute: ~w ms',[Nr,TO]),
1187 % TO DO: try and obtain operation name in which time-out occured
1188 error_occurred(time_out,execute),
1189 assertz(execute_timeout_occurred),
1190 fail
1191 ; true).
1192 cli_trans_aux(CurState,ActionName,Act,NewState,_Nr,LastActionName) :-
1193 cli_trans_aux2(CurState,ActionName,Act,NewState,LastActionName).
1194
1195 cli_trans_aux2(CurState,ActionName,Act,NewState,LastActionName) :-
1196 catch_enumeration_warning_exceptions(
1197 (throw_enumeration_warnings_in_current_scope,
1198 cli_execute_trans(CurState,ActionName,Act,NewState,LastActionName), % no time-out !
1199 (error_occurred_in_error_scope -> ErrorEvent=true ; ErrorEvent=false)
1200 ),
1201 (error_occurred(virtual_time_out_execute),
1202 ActionName = '*** VIRTUAL_TIME_OUT ***', Act=ActionName,
1203 CurState=NewState) % this forces loop detection above; not very elegant way of signalling
1204 ),
1205 (ErrorEvent==true,option(strict_raise_error)
1206 -> print('*** ERROR OCCURED DURING EXECUTE ***'),nl, error_occurred(execute),fail
1207 ; true).
1208
1209 :- use_module(runtime_profiler,[profile_single_call/3]).
1210 :- use_module(specfile,[get_specification_description/2]).
1211 cli_execute_trans(CurState,ActionName,Act,NewState,LastActionName) :-
1212 statistics(runtime,[StartExecuteForState,_]),
1213 get_possible_next_operation_for_execute(CurState,LastActionName,ActionName),
1214 start_check_disabled(ActionName,StartActionTime),
1215 catch(
1216 profile_single_call(ActionName,
1217 unknown, % state Unknown
1218 specfile_trans_with_check(CurState,ActionName,Act,NewState,Residue) % no time-out !
1219 ),
1220 EXC,
1221 (translate_exception(EXC,EMSG),
1222 (nonvar(ActionName)
1223 -> get_specification_description(operation,OP),
1224 format_with_colour_nl(user_error,[red,bold],'~n*** ~w while executing ~w "~w"~n',[EMSG,OP,ActionName])
1225 ; get_specification_description(operations,OP),
1226 format_with_colour_nl(user_error,[red,bold],'~n*** ~w while computing ~w~n',[EMSG,OP])
1227 ),
1228 perform_feedback_options_after_exception,
1229 throw(EXC))),
1230 (Residue=[]
1231 -> check_trans_time(StartExecuteForState,StartActionTime,ActionName)
1232 ; error_occurred(cli_execute_residue(ActionName,Residue,Act))).
1233
1234 :- use_module(probsrc(static_enabling_analysis),[static_cannot_enable/2]).
1235 % compute all possible next operations to try out in -execute, based on LastActionName
1236 % the predicate makes use of the fact that operations are tried in order
1237 get_possible_next_operation_for_execute(CurState,LastActionName,ActionName) :-
1238 get_preference(randomise_operation_order,false),
1239 get_preference(use_po,true), % PROOF_INFO: should we use a proper preference for use_po_for_execute ?
1240 b_or_z_mode,
1241 b_top_level_operation(LastActionName),
1242 % prevent trying ActionName which we know is infeasible according to previous LastActionName
1243 % we rely on the fact that execute tries the operations in order
1244 findall(AN,specfile_possible_trans_name_for_successors(CurState,AN),ANS),
1245 !,
1246 member_with_last(ActionName,ANS,LastActionName,FoundLast),
1247 (var(FoundLast)
1248 -> % ActionName occurs before LastActionName, this means
1249 % we did try this ActionName at the last execution step and it was not possible
1250 % format('Checking operation ~w against ~w~n',[ActionName,LastActionName]),debug:nl_time,
1251 %Note: we could use result of cbc enabling analysis if it was performed
1252 (static_cannot_enable(LastActionName,ActionName)
1253 -> %format('Operation ~w : ~w cannot be enabled by ~w : ~w~n',[Nr2,ActionName,Nr1,LastActionName]),
1254 %print('- '),
1255 fail
1256 ; true
1257 )
1258 ; true % we did not try this ActionName at the last execution step
1259 ).
1260 get_possible_next_operation_for_execute(CurState,_LastActionName,ActionName) :-
1261 specfile_possible_trans_name_for_successors(CurState,ActionName).
1262
1263 % like member but instantiate FoundLast when we pass the element Last
1264 member_with_last(X,[H|T],Last,FoundLast) :-
1265 (H=Last -> !,FoundLast=true, member(X,[H|T]) ; X=H).
1266 member_with_last(X,[_|T],Last,FoundLast) :- member_with_last(X,T,Last,FoundLast).
1267
1268 % also checks whether a setup_constants_inconsistent error should be raised:
1269 specfile_trans_with_check(CurState,ActionName,Act,NewState,Residue) :-
1270 if(specfile_trans_or_partial_trans(CurState,ActionName,Act,NewState,_TransInfo,Residue,Partial), % no time-out !
1271 check_partial_trans(Partial,ActionName),
1272 check_deadlock_fail(ActionName)
1273 ).
1274
1275 % check whether we should raise errors on deadlock in -execute:
1276 check_deadlock_fail('$setup_constants') :- !, error_occurred(setup_constants_inconsistent),fail.
1277
1278 % check whether we should raise errors due to partial transitions in -execute:
1279 check_partial_trans(true,'$setup_constants') :- !, error_occurred(setup_constants_inconsistent).
1280 check_partial_trans(true,ActionName) :- !,format('Unknown partial transition: ~w~n',[ActionName]),
1281 error_occurred(setup_constants_inconsistent).
1282 check_partial_trans(_,_).
1283
1284 % check if we did not spend too much time on disabled operations and print warning if we do
1285 check_trans_time(StartExecuteForState,StartActionTime,ActionName) :-
1286 option(execute_monitoring),
1287 statistics(runtime,[CurrentTime,_]),
1288 Delta1 is StartActionTime-StartExecuteForState,
1289 Delta2 is CurrentTime-StartActionTime,
1290 Delta1 > 100, Delta1 > Delta2,
1291 !,
1292 format_with_colour(user_output,[blue],'~n ~5|: WARNING from -execute_monitor: ~w ms for disabled operations and ~w ms for operation ~w itself~n',[Delta1,Delta2,ActionName]).
1293 check_trans_time(_,_,_).
1294
1295 % check if we did not spend too much time on a single disabled operations and print warning if we do
1296 start_check_disabled(ActionName,StartActionTime) :- option(execute_monitoring),!,
1297 statistics(runtime,[StartActionTime,_]),
1298 (true
1299 ; statistics(runtime,[EndActionTime,_]),
1300 Delta is EndActionTime - StartActionTime,
1301 Delta > 50,
1302 format_with_colour(user_output,[blue],'~n ~5|: WARNING from -execute_monitor: ~w ms for disabled operation ~w~n',[Delta,ActionName]),
1303 fail
1304 ).
1305 start_check_disabled(_,0).
1306
1307 translate_exception(user_interrupt_signal,'User-Interrupt (CTRL-C)').
1308 translate_exception(enumeration_warning(_,_,_,_,_),'Enumeration Warning').
1309 translate_exception(E,E).
1310
1311 :- use_module(bmachine,[b_machine_has_constants/0]).
1312 print_state_silent(_) :- option(silent),!.
1313 print_state_silent(CurState) :- (option(verbose);\+ b_machine_has_constants),!,
1314 translate:print_bstate_limited(CurState,1000,-1),nl.
1315 print_state_silent(CurState) :- remove_constants(CurState,VarState),
1316 % only print variables
1317 format('VARIABLES (use -v to see constants or -silent to suppress output):~n',[]),
1318 translate:print_bstate_limited(VarState,1000,-1),nl.
1319
1320 :- use_module(bmachine,[b_is_constant/1]).
1321 is_constant_binding(bind(C,_)) :- b_is_constant(C).
1322 remove_constants(const_and_vars(_,Vars),Res) :- !,Res=Vars.
1323 remove_constants([H|T],Res) :- !,exclude(prob_cli:is_constant_binding,[H|T],Res).
1324 remove_constants(root,Res) :- !,Res=[].
1325 remove_constants(concrete_constants(_),Res) :- !, Res=[].
1326 remove_constants(X,X).
1327
1328 % write vars to xml log file if they start with a given prefix
1329 logxml_write_ids(variables,Prefix) :- !,
1330 current_expression(_,CurState),
1331 remove_constants(CurState,VarState),
1332 % TO DO: store also final state in xml_log
1333 write_bstate_to_log(VarState,Prefix).
1334 logxml_write_ids(_,Prefix) :- !,
1335 current_expression(_,CurState),
1336 expand_const_and_vars_to_full_store(CurState,EState),
1337 write_bstate_to_log(EState,Prefix).
1338
1339 :- use_module(bmachine,[b_get_invariant_from_machine/1, b_specialized_invariant_for_op/2, b_machine_has_constants/0]).
1340 cli_invariant_ko(_,_,_,_) :- option(no_invariant_violations),!,fail. % user asks not to check it
1341 cli_invariant_ko(_,_,_,_) :- get_preference(do_invariant_checking,false),!,fail. % user asks not to check it via preference
1342 cli_invariant_ko(CurState,LastActionName,ResInvStatus,CliError) :-
1343 profile_single_call('INVARIANT',unknown,cli_invariant_ko2(CurState,LastActionName,ResInvStatus,CliError)).
1344 cli_invariant_ko2(CurState,LastActionName,ResInvStatus,CliError) :-
1345 state_corresponds_to_initialised_b_machine(CurState,BState),!,
1346 start_probcli_timer(InvTimer),
1347 (b_specialized_invariant_for_op(LastActionName,Invariant) -> true
1348 %, print('Specialized invariant: '),translate:print_bexpr(Invariant),nl
1349 ; b_get_invariant_from_machine(Invariant)),
1350 cli_test_pred(BState,'INVARIANT',Invariant,ResInvStatus),
1351 stop_probcli_debug_timer(InvTimer,'Finished Invariant Checking'),
1352 ResInvStatus \= 'TRUE',
1353 (ResInvStatus == 'FALSE' -> CliError = invariant_violation
1354 ; ResInvStatus == 'UNKNOWN' -> CliError = invariant_unknown
1355 ; format_error_with_nl('Unexpected invariant status: ~w',[ResInvStatus]),
1356 CliError= invariant_unknown).
1357 %cli_invariant_ko(_,_,_,_) :- fail. % not yet initialised
1358
1359 :- use_module(b_interpreter,[b_test_boolean_expression_for_ground_state/4]).
1360 cli_test_pred(BState,PredKind,Pred) :- cli_test_pred(BState,PredKind,Pred,'TRUE').
1361 cli_test_pred(BState,PredKind,Pred,Res) :-
1362 % currently does not do a time-out: % b_interpreter calls: time_out_with_enum_warning_one_solution_no_new_error_scope
1363 catch(
1364 on_enumeration_warning(b_test_boolean_expression_for_ground_state(Pred,[],BState,PredKind ), (
1365 add_error(cli_test_pred,'Enumeration warning while testing',PredKind,Pred),
1366 cli_print_pred_info(Pred),
1367 Res='UNKNOWN')
1368 ),
1369 E,
1370 (
1371 string_concatenate('VIRTUAL TIME-OUT while testing ',PredKind,Msg),
1372 add_error(cli_test_pred,Msg,E,Pred),
1373 cli_print_pred_info(Pred),
1374 Res='UNKNOWN'
1375 )
1376 ),
1377 !,
1378 (var(Res) -> Res = 'TRUE' ; true).
1379 cli_test_pred(_BState,_PredKind,_Pred,'FALSE').
1380
1381 cli_print_pred_info(Pred) :- get_texpr_label(Pred,Label),
1382 format('Label = ~w~n',[Label]),fail.
1383 cli_print_pred_info(Pred) :- get_texpr_description(Pred,Desc),
1384 format('Description = ~w~n',[Desc]),fail.
1385 %cli_print_pred_info(Pred) :- bsyntaxtree:get_texpr_pos(Pred,Pos), Pos \= none, translate_span(Pos,Str),
1386 % format('Location = ~w~n',[Str]),fail.
1387 cli_print_pred_info(_).
1388
1389 :- use_module(bmachine,[get_assertions_from_machine/2]).
1390 % TO DO: also check static assertions
1391 cli_assertions_ok(_,_) :- option(no_assertion_violations),!. % user asks not to check it
1392 cli_assertions_ok(CurState,_LastActionName) :-
1393 state_corresponds_to_initialised_b_machine(CurState,BState),
1394 get_assertions_from_machine(dynamic,Assertions), % TO DO: do something similar to b_specialized_invariant_for_op
1395 !,
1396 profile_single_call('ASSERTIONS',unknown,cli_assertions_ok2(BState,Assertions)).
1397 cli_assertions_ok(_,_). % not yet initialised or no assertions
1398
1399 cli_assertions_ok2(BState,Assertions) :-
1400 start_probcli_timer(AssTimer),
1401 %nl,nl,print(check),nl,maplist(translate:print_bexpr,Assertions),nl,
1402 maplist(prob_cli:cli_test_pred(BState,'ASSERTION'),Assertions),
1403 stop_probcli_debug_timer(AssTimer,'Finished Checking Assertions').
1404
1405
1406 :- use_module(bmachine,[b_get_machine_goal/1]).
1407 cli_goal_found(_):- option(no_goal),!,fail.
1408 cli_goal_found(CurState) :-
1409 b_get_machine_goal(Goal),
1410 state_corresponds_to_initialised_b_machine(CurState,BState),
1411 profile_single_call('GOAL',unknown,cli_goal_found2(Goal,BState)).
1412 cli_goal_found2(Goal,BState) :-
1413 b_test_boolean_expression_for_ground_state(Goal,[],BState,'GOAL').
1414
1415
1416 % random animation
1417 :- public cli_random_animate/2. % for repl to use -animate command
1418 cli_random_animate(Steps,Err) :- probcli_time_stamp(NOW),
1419 cli_random_animate(NOW,Steps,Err).
1420 cli_random_animate(_NOW,Steps,ErrorOnDeadlock) :-
1421 start_xml_feature(random_animate,max_steps,Steps,FINFO),
1422 start_ms_timer(Start),
1423 perform_random_steps(Steps,ErrorOnDeadlock),
1424 (option(silent) -> true ; stop_ms_timer_with_msg(Start,'-animate')),
1425 %tcltk_save_history_as_trace_file(prolog,user),
1426 stop_xml_feature(random_animate,FINFO).
1427
1428 :- use_module(bmachine,[b_get_assertions/3]).
1429 we_need_only_static_assertions(ALL) :- specfile:b_or_z_mode,
1430 (option(cli_check_assertions(main,_)) -> ALL=main
1431 ; option(cli_check_assertions(ALL,_))),
1432 % we do an assertion check
1433 \+ ((option(A), option_requires_all_properties(A))),
1434 b_get_assertions(ALL,dynamic,[]). % the assertions do not reference variables
1435
1436 % do we need all properties/constants of the machine, or only certain ones (e.g., static)
1437 option_requires_all_properties(cli_mc(_,_)).
1438 option_requires_all_properties(cli_check_properties). % we may want to check all properties
1439 option_requires_all_properties(cli_core_properties(_)).
1440 option_requires_all_properties(cli_random_animate(_)).
1441 option_requires_all_properties(default_trace_check).
1442 option_requires_all_properties(trace_check(_,_,_)).
1443 option_requires_all_properties(state_trace(_)).
1444 option_requires_all_properties(mcm_tests(_,_,_,_)).
1445 option_requires_all_properties(cbc_tests(_,_,_)).
1446 option_requires_all_properties(animate).
1447 option_requires_all_properties(initialise). % INITIALISATION may access constants
1448 option_requires_all_properties(eval_repl(_)).
1449 option_requires_all_properties(eval_string_or_file(_,_,_,_,_)).
1450 option_requires_all_properties(ltl_assertions).
1451 option_requires_all_properties(ltl_file(_)).
1452 option_requires_all_properties(refinement_check(_,_,_)).
1453 option_requires_all_properties(cli_start_mc_with_tlc).
1454 option_requires_all_properties(cli_symbolic_model_check(_)).
1455 option_requires_all_properties(process_latex_file(_,_)).
1456 option_requires_all_properties(cli_wd_check(_,_)).
1457 option_requires_all_properties(cli_lint(_)).
1458 option_requires_all_properties(visb_history(_,_,_)).
1459
1460 :- use_module(b_intelligent_trace_replay,[replay_json_trace_file/2]).
1461 :- public default_trace_check/0.
1462 default_trace_check :- loaded_main_file(_,MainFile),
1463 cli_start_default_trace_check(MainFile).
1464 cli_start_default_trace_check(MainFile) :-
1465 debug_println(20,'% Starting Default Trace Check: '),
1466 (check_default_trace_for_specfile(MainFile) -> true ; error_occurred(trace_check)).
1467
1468 default_json_trace_save :-
1469 loaded_main_file(_,MainFile),
1470 get_default_trace_file(MainFile,'.prob2trace',HistFile),
1471 format('Saving history to JSON ProB2-UI default trace file: ~w~n',[HistFile]),
1472 tcltk_save_history_as_trace_file(json,HistFile).
1473 cli_start_trace_check(json,File,default_trace_replay) :- !,
1474 replay_json_trace_file(File,Status),
1475 (Status=perfect -> true
1476 ; Status = imperfect(_) -> add_warning(trace_replay,'Imperfect JSON trace replay:',Status)
1477 ; add_error(trace_replay,'Failed JSON trace replay:',Status)
1478 ).
1479 cli_start_trace_check(Style,File,Mode) :-
1480 debug_format(20,'% Starting Trace Check (~w:~w): ~w~n',[Style,Mode,File]),
1481 (tcltk_check_sequence_from_file(Style,File,Mode) -> true ; error_occurred(trace_check)).
1482 cli_start_trace_state_check(File) :-
1483 debug_println(20,'% Starting Trace Check: '),
1484 (tcltk_check_state_sequence_from_file(File) -> true ; error_occurred(state_trace)).
1485
1486 % is it necessary to compute enabled operations for root state
1487 computeOperations_for_root_required :- initialise_required.
1488 computeOperations_for_root_required :- option(default_trace_check).
1489 computeOperations_for_root_required :- option(trace_check(_,_,_)).
1490 computeOperations_for_root_required :- option(state_trace(_)).
1491 computeOperations_for_root_required :- option(ltl_assertions).
1492 computeOperations_for_root_required :- option(cli_random_animate(_,_)).
1493 computeOperations_for_root_required :- option(socket(_,_)).
1494 computeOperations_for_root_required :- option(cli_mc(_,_)).
1495 computeOperations_for_root_required :- option(ltl_file(_)).
1496 computeOperations_for_root_required :- option(ltl_formula_model_check(_,_)).
1497 computeOperations_for_root_required :- option(ctl_formula_model_check(_,_)).
1498 computeOperations_for_root_required :- option(refinement_check(_,_,_)).
1499 computeOperations_for_root_required :- option(csp_in_situ_refinement_check(_,_)).
1500 computeOperations_for_root_required :- option(csp_checkAssertion(_,_)).
1501 computeOperations_for_root_required :- option(mcm_tests(_,_,_,_)).
1502 computeOperations_for_root_required :- option(mcm_cover(_)).
1503
1504 % is an initialisation mandatory:
1505 initialise_required :- option(initialise), \+ empty_machine_loaded.
1506 initialise_required :- \+ option(default_trace_check), \+ option(trace_check(_,_,_)), \+ option(state_trace(_)),
1507 \+ option(load_state(_)),
1508 \+ empty_machine_loaded,
1509 \+ (option(execute(Nr,_,_)), Nr>=2), % execute will also initialise machine
1510 init_req2.
1511 init_req2 :- option(cli_check_properties).
1512 init_req2 :- option(zmq_assertion(_,_,_)).
1513 init_req2 :- option(cli_check_assertions(_,_)).
1514 init_req2 :- option(process_latex_file(_,_)).
1515 init_req2 :- option(eval_string_or_file(_,_,_,_,_)). % ensure that we initialise/precompile empty machine in case no main file specified; currently no longer required
1516 init_req2 :- option(check_abstract_constants).
1517 init_req2 :- option(visb_click(_)).
1518 init_req2 :- option(dot_command_for_expr(Cat,_,_,_,_)),
1519 nonmember(Cat,[transition_diagram,expression_coverage]). % see test 1033, option also works with empty state space
1520 %init_req2 :- option(csv_table_command(Cat,_,_,_)), ...
1521
1522 :- public initialise/0. % for REPL
1523 initialise :- probcli_time_stamp(NOW),cli_start_initialisation(NOW).
1524
1525 cli_start_initialisation(NOW) :-
1526 debug_println(20,'% Performing INITIALISATION: '),
1527 (perform_random_initialisation -> true ;
1528 writeln_log_time(cli_start_initialisation_failed(NOW)),
1529 fail).
1530
1531 :- use_module(wdsrc(well_def_analyser),[analyse_wd_for_machine/4]).
1532 :- public cli_wd_check/2. % for REPL
1533 cli_wd_check(ExpectedDis,ExpectedTot) :-
1534 (option(timeout(TO)) -> true ; TO=5000), % this is global_time_out option
1535 (option(silent) -> Opts=[discharge_po,ignore_wd_infos,reorder_conjuncts]
1536 ; Opts=[create_not_discharged_msg(warning),discharge_po,ignore_wd_infos,reorder_conjuncts]),
1537 statistics(walltime,[W1,_]),
1538 safe_time_out(analyse_wd_for_machine(NrDischarged,NrTot,_Res,Opts),TO,Res),
1539 statistics(walltime,[W2,_]), WT is W2-W1,
1540 (Res=time_out -> accumulate_infos(wd_check,[timeout-1,walltime-WT]), % discharged and total are unknown
1541 add_error(cli_wd_check,'TIME-OUT in WD Analysis (use -global_time_out X to increase it)')
1542 ; format(user_output,'WD Analysis Result: discharged ~w / ~w',[NrDischarged,NrTot]),
1543 (NrTot >0
1544 -> Perc is 100*NrDischarged/NrTot,
1545 (NrDischarged=NrTot -> Col=[green,bold] ; Col=[red])
1546 ; Perc = 100, Col=[]),
1547 format_with_colour(user_output,Col,' (~2f %)~n',[Perc]),
1548 WDInfos = [discharged-NrDischarged,timeout-0,total-NrTot,walltime-WT],
1549 accumulate_infos(wd_check,WDInfos),
1550 (ExpectedDis==ExpectedTot, ExpectedTot = NrTot -> true ; true), % for -wd-check-all: bind ExpectedDis
1551 check_required_infos([discharged-ExpectedDis,total-ExpectedTot],WDInfos,cli_wd_check)
1552 ).
1553 :- use_module(wdsrc(well_def_analyser),[analyse_invariants_for_machine/5]).
1554 cli_wd_inv_proof(UnchangedNr,ProvenNr,TotPOsNr) :-
1555 (option(timeout(TO)) -> true ; TO=5000),
1556 Options=[],
1557 statistics(walltime,[W1,_]),
1558 safe_time_out(analyse_invariants_for_machine(UnchangedNr,ProvenNr,UnProvenNr,TotPOsNr,Options),TO,Res),
1559 statistics(walltime,[W2,_]), WT is W2-W1,
1560 (Res=time_out -> accumulate_infos(wd_inv_proof,[timeout-1,walltime-WT]), % discharged and total are unknown
1561 add_error(cli_wd_check,'TIME-OUT in WD Invariant Proving (use -global_time_out X to increase it)')
1562 ;
1563 (TotPOsNr>0 -> Perc is (UnchangedNr+ProvenNr)*100/ TotPOsNr ; Perc = 100.0),
1564 format('Proof summary for ~w Invariant POs (~2f % discharged): ~w unchanged, ~w proven, ~w unproven~n',
1565 [TotPOsNr,Perc,UnchangedNr,ProvenNr,UnProvenNr]),
1566 WDInfos = [proven-ProvenNr,timeout-0,total-TotPOsNr,unchanged-UnchangedNr,unproven-UnProvenNr,walltime-WT],
1567 accumulate_infos(wd_inv_proof,WDInfos)
1568 ).
1569
1570
1571 :- use_module(bmachine_static_checks,[extended_static_check_machine/1]).
1572 :- use_module(visbsrc(visb_visualiser),[extended_static_check_default_visb_file/0]).
1573 % perform some additional static checks
1574 :- public cli_lint/0. % for REPL
1575 cli_lint(Check) :-
1576 extended_static_check_machine(Check),
1577 (unavailable_extension(visb_extension,_) -> true
1578 ; Check=visb -> extended_static_check_default_visb_file
1579 ; true).
1580 cli_lint :- cli_lint(_).
1581
1582
1583 :- use_module(extrasrc(predicate_debugger),[tcltk_debug_properties/3]).
1584 :- use_module(state_space,[current_state_corresponds_to_setup_constants_b_machine/0]).
1585 :- public cli_check_properties/0. % for REPL
1586 cli_check_properties :- probcli_time_stamp(NOW),
1587 cli_check_properties(NOW).
1588 cli_check_properties(NOW) :-
1589 printsilent('% Checking PROPERTIES: '),nls,
1590 writeln_log_time(starting_check_properties(NOW)),
1591 ( current_state_corresponds_to_setup_constants_b_machine ->
1592 set_analyse_hook('_P'),
1593 predicate_evaluator:tcltk_analyse_properties(_PROPRES,PROPInfos),
1594 unset_analyse_hook,
1595 printsilent(PROPInfos),nls, % ex: [total/33,true/29,false/0,unknown/4,timeout/4,runtime/49950]
1596 accumulate_infos(properties,PROPInfos),
1597 write_important_xml_element_to_log(check_properties,PROPInfos),
1598 (predicate_evaluator:check_summary_all_true(PROPInfos) -> true
1599 ; print_error('Not all PROPERTIES true'), error_occurred(check_properties))
1600 ;
1601 (tcltk_debug_properties(list(PROPRES),false,Satisfiable)
1602 -> printsilent(PROPRES),nls,
1603 printsilent(Satisfiable),nls
1604 ; error_occurred(debug_properties_failed))
1605 ),
1606 writeln_log_time(finished_check_properties(NOW,PROPInfos)),
1607 loaded_root_filename(RootName),
1608 formatsilent('% Finished checking PROPERTIES of ~w~n',[RootName]).
1609
1610 % TODO: provide argument so that we run it only if necessary; e.g., when ProB has not already found a solution
1611
1612 cli_core_properties(Algorithm) :-
1613 format('% Checking CONSISTENCY of PROPERTIES by finding UNSAT CORE (using ~w)~n',[Algorithm]),
1614 b_get_properties_from_machine(Properties),!,
1615 size_of_conjunction(Properties,NrOfConjuncts),
1616 statistics(walltime,[W1,_]),
1617 (find_core(Algorithm,Properties,Core,Result)
1618 -> statistics(walltime,[W2,_]), WTime is W2-W1,
1619 length(Core,Len),
1620 accumulate_infos(properties_core,[contradiction_found-1,core_length-Len,
1621 properties-NrOfConjuncts,walltime-WTime]),
1622 format('UNSAT CORE of length ~w found, PROPERTIES are inconsistent! (~w, ~w ms walltime using ~w)~n',[Len,Result,WTime,Algorithm]),
1623 translate:nested_print_bexpr_as_classicalb(Core),
1624 format('% END OF UNSAT CORE (~w conjuncts)~n',[Len])
1625 % TODO: raise setup_constants_fails and avoid trying to solve properties later
1626 ; statistics(walltime,[W2,_]), WTime is W2-W1,
1627 accumulate_infos(properties_core,[contradiction_found-0,core_length-0,
1628 properties-NrOfConjuncts,walltime-WTime]),
1629 format('No small UNSAT CORE found, PROPERTIES may be consistent (~w ms walltime).~n',[WTime])
1630 ).
1631
1632 :- use_module(extrasrc(unsat_cores),[quick_bup_core_up_to/4]).
1633 :- use_module(wdsrc(well_def_analyser),[find_inconsistent_axiom/3]).
1634 find_core(wd_prover,_,Core,Result) :-
1635 find_inconsistent_axiom([],Axiom,NecHyps),
1636 Core = [Axiom|NecHyps], Result = contradiction_found.
1637 find_core(z3_bup(MaxSize),Properties,Core,Result) :-
1638 (var(MaxSize) -> MaxSize=2 ; true),
1639 quick_bup_core_up_to(Properties,MaxSize,Core,Result).
1640
1641
1642 % -----------------------
1643
1644 :- public cli_check_assertions/2. % for REPL
1645 cli_check_assertions(ALL,RI) :-
1646 probcli_time_stamp(NOW),
1647 cli_check_assertions(ALL,RI,NOW).
1648 cli_check_assertions(ALL,ReqInfos,NOW) :-
1649 printsilent('% Checking ASSERTIONS: '),nls,
1650 writeln_log_time(starting_check_assertions(NOW)),
1651 set_analyse_hook('_A'), % for dot output, in case users wants to generate dot files for assertions
1652 predicate_evaluator:tcltk_analyse_assertions(ALL,_ASSRES,Infos), % also checks CSP assertions
1653 unset_analyse_hook,
1654 printsilent(Infos),nls,
1655 accumulate_infos(assertions,Infos),
1656 write_important_xml_element_to_log(check_assertions,Infos),
1657 check_required_infos(ReqInfos,Infos,check_assertions),
1658 writeln_log_time(finished_check_assertions(NOW,Infos)),
1659 loaded_root_filename(RootName),
1660 formatsilent('% Finished checking ASSERTIONS of ~w~n',[RootName]),!.
1661 cli_check_assertions(ALL,ReqInfos,NOW) :-
1662 add_internal_error('Analyse ASSERTIONS unexpectedly failed',cli_check_assertions(ALL,ReqInfos,NOW)),
1663 error_occurred(internal_error).
1664 cli_set_goal(GOAL) :-
1665 debug_println(20,set_goal(GOAL)), %print(set_goal(GOAL)), nl,
1666 (bmachine:b_set_machine_goal(GOAL) -> true
1667 ; add_error(scope,'Setting GOAL predicate failed:',GOAL)).
1668 cli_add_additional_property(PROP) :-
1669 debug_println(20,add_additional_property(PROP)),
1670 (bmachine:add_additional_property(PROP,'command line -property') -> true
1671 ; add_error(scope,'Adding additional predicate to PROPERTIES failed:',PROP)).
1672 cli_set_searchscope(GOAL) :-
1673 debug_println(20,set_searchscope(GOAL)),
1674 format('Setting SCOPE for verification: ~w~n (Only states satsifying this predicate will be examined)~n',[GOAL]),
1675 (bmachine:b_set_machine_searchscope(GOAL) -> true
1676 ; add_error(scope,'Setting model checking search SCOPE failed:',GOAL)).
1677 cli_check_goal :- \+ b_get_machine_goal(_),!,
1678 add_error(cli_check_goal,'No GOAL DEFINITION found'),
1679 error_occurred(cli_check_goal).
1680 cli_check_goal :-
1681 printsilent('% Checking GOAL predicate: '),nls,
1682 tcltk_analyse_goal(_List,Summary),
1683 debug_println(20,Summary),
1684 accumulate_infos(check_goal,Summary),
1685 write_important_xml_element_to_log(check_goal,Summary),
1686 check_required_infos([false/0,unknown/0],Summary,check_goal).
1687 :- public cli_mc/2. % for REPL
1688 cli_mc(Nr,Opts) :- probcli_time_stamp(NOW), cli_start_model_check(Nr,NOW,Opts).
1689 cli_start_model_check(Nr,NOW,Options) :-
1690 (member(reset_state_space,Options)
1691 -> formatsilent('Resetting state space for benchmarking model checking (limit:~w, options:~w)~n',[Nr, Options]),
1692 announce_event(reset_specification) % for benchmarking purposes
1693 %,state_space:portray_state_space,nl
1694 ; true),
1695 start_xml_feature(model_check,max_states,Nr,FINFO),
1696 regular_safety_model_check_now(Nr,Time,WallTime,MCRes,NOW),
1697 %nl,
1698 stop_xml_feature(model_check,FINFO),
1699 get_state_space_stats(TS,TT,PT,IgnT),
1700 statistics_memory_used(Mem),
1701 (MCRes=time_out -> TInfos=[timeout/1] ; TInfos=[]),
1702 accumulate_infos(model_check,[runtime-Time,walltime-WallTime, % mc only runtime, and total wall time
1703 processed_states/PT,total_states/TS,total_transitions/TT,
1704 ignored_states/IgnT, memory_used/Mem|TInfos]), %for bench_csv output
1705 writeln_log_time(model_check(NOW,Nr,Time,WallTime,MCRes)),
1706 (select(repeat(RepNr),Options,RestOptions)
1707 -> (RepNr>1
1708 -> N1 is RepNr-1,
1709 cli_start_model_check(Nr,NOW,[repeat(N1)|RestOptions])
1710 ; merge_accumulated_infos(model_check)
1711 )
1712 ; true
1713 ).
1714
1715 cli_start_mc_with_tlc :-
1716 (animation_mode(b), \+ animation_minor_mode(eventb) -> true
1717 ; error_manager: add_error_and_fail(mc_with_tlc,'TLC4B tool can be used only for classical B models.')),
1718 % TO DO: use b_write_eventb_machine_to_classicalb_to_file to do conversion
1719 catch(
1720 safe_absolute_file_name(prob_lib('TLC4B.jar'),TLC4BTool),
1721 error(E,_),
1722 error_manager:add_error_fail(get_tlc_command,'Could not find TLC4B.jar file.',E)),
1723 start_xml_feature(model_check_with_tlc,tlc4bjar,TLC4BTool,FINFO),
1724 construct_and_execute_tlc_command(TLC4BTool),
1725 stop_xml_feature(model_check_with_tlc,FINFO).
1726
1727 :- use_module(system_call,[system_call/4]).
1728 construct_and_execute_tlc_command(TLC4BTool) :-
1729 parsercall: get_java_command_path(JavaCmd),
1730 loaded_main_file(File),
1731 % determine extra arguments:
1732 (get_preference(tlc_number_of_workers,TLCWorkers), TLCWorkers>1
1733 -> number_codes(TLCWorkers,CC), atom_codes(TLAWA,CC), WW = ['-workers',TLAWA]
1734 ; WW=[]),
1735 (option(no_assertion_violations) -> WA = ['-noass'] ; WA=[]),
1736 (option(no_deadlocks) -> WD = ['-nodead'] ; WD=[]),
1737 (option(no_invariant_violations) -> WI = ['-noinv'] ; WI=[]),
1738 (option(no_goal) -> WG = ['-nogoal'] ; WG=[]),
1739 (option(no_ltl) -> WL = ['-noltl'] ; WL=[]),
1740 (option(verbose) -> WV = ['-verbose'] ; WV=[]),
1741 (option(silent) -> WS = ['-silent'] ; WS=[]),
1742 (option(logtlc(Log)) -> WLG = ['-log',Log] ; WLG=[]),
1743 (get_preference(tlc_use_prob_constant_setup,true),
1744 get_preference(maxNrOfEnablingsPerOperation,MaxO),
1745 tcltk_get_constants_predicate(DNF_Pred,MaxO)
1746 -> WCS = ['-constantssetup', DNF_Pred]
1747 ; WCS=[]),
1748 append([WW,WA,WD,WI,WG,WL,WCS,WV,WS,WLG,[File]],TLCArgs),
1749 debug_println(19,tlc_args(TLCArgs)),
1750 statistics(walltime,[W1,_]),
1751 % we could call get_jvm_options: '-Xss5m' is useful e.g. for Generated1000.mch
1752 system_call(JavaCmd, ['-Xss5m', '-jar', TLC4BTool | TLCArgs], Text,JExit),
1753 statistics(walltime,[W2,_]),
1754 WTime is W2-W1,
1755 formatsilent('exit : ~w walltime: ~w ms~n',[JExit,WTime]),
1756 (JExit=exit(0)
1757 -> accumulate_infos(mc_with_tlc,[walltime-WTime,model_check_ok-1])
1758 ; accumulate_infos(mc_with_tlc,[walltime-WTime,model_check_error-1]),
1759 add_error(construct_and_execute_tlc_command,'Error while model checking with TLC: ',TLC4BTool/File),
1760 atom_codes(T,Text),
1761 add_error_fail(construct_and_execute_tlc_command,'Std error: ',T)
1762 ).
1763
1764 % SymbolicOrSequential = symbolic or sequential
1765 cli_start_sym_mc_with_lts(SymbolicOrSequential) :-
1766 (option(no_deadlocks) -> NoDead = true ; NoDead = false),
1767 (option(no_invariant_violations) -> NoInv = true ; NoInv = false), % does LTSMin support goal checking
1768 findall(Option,option(ltsmin_option(Option)),MoreFlags1),
1769 findall(ltl_formula(LTLF),option(ltl_formula_model_check(LTLF,_)),MoreFlags2),
1770 append(MoreFlags1,MoreFlags2,MoreFlags),
1771 (NoDead = false, NoInv = false ->
1772 print_error('ERROR: cannot start LTSmin with both deadlock and invariant checking'),
1773 print_error(' use either the -noinv or -nodead flag'),
1774 flush_output(user_error)
1775 ; true),
1776 formatsilent('starting prob2lts-sym/seq (flags nodead=~w, noinv=~w, moreflags=~w)~n',[NoDead,NoInv,MoreFlags]),
1777 statistics(walltime,[W1,_]),
1778 start_ltsmin(SymbolicOrSequential, [NoDead, NoInv], MoreFlags,Result),
1779 process_ltsmin_result(Result,AccInfos),
1780 statistics(walltime,[W2,_]), WT is W2-W1,
1781 accumulate_infos(mc_with_lts_min(SymbolicOrSequential),[walltime-WT|AccInfos]).
1782 % TO DO: start lts-sym + start start_ltsmin_srv('/tmp/ltsmin.probz', NOW) + print output
1783
1784 :- use_module(extension('ltsmin/ltsmin_trace'),[csv_to_trace/3]).
1785 process_ltsmin_result(ltsmin_model_checking_ok,[model_check_ok-1]) :-
1786 print_green('LTSMin found no counter example\n').
1787 process_ltsmin_result(ltsmin_model_checking_aborted,[model_check_aborted-1]) :-
1788 add_warning(ltsmin_model_checking_aborted,'LTSMin was aborted (e.g., by CTRL-C)').
1789 process_ltsmin_result(ltsmin_counter_example_found(CsvFile),[model_check_counter_example-1]) :-
1790 add_error(ltsmin_counter_example_found,'LTSMin found a counter example, written to:',CsvFile),
1791 (option(silent) -> true
1792 ; csv_to_trace(CsvFile,_States,Transitions) ->
1793 print('*** TRACE: '),nl,print_list(Transitions) % ,print(_States),nl
1794 ; add_error(ltsmin,'Could not extract trace information from LTSmin file: ',CsvFile)
1795 ).
1796
1797 :- use_module(symbolic_model_checker(ic3), [ic3_symbolic_model_check/1]).
1798 :- use_module(symbolic_model_checker(ctigar), [ctigar_symbolic_model_check/1]).
1799 :- use_module(symbolic_model_checker(kinduction), [kinduction_symbolic_model_check/1,
1800 tinduction_symbolic_model_check/1]).
1801 :- use_module(symbolic_model_checker(bmc), [bmc_symbolic_model_check/1]).
1802 cli_symbolic_model_check(Algorithm) :-
1803 debug_format(20,'% Starting Symbolic Model Check. Using ~w Algorithm', [Algorithm]),
1804 start_xml_feature(model_check,algorithm,Algorithm,FINFO),
1805 (animation_mode(b)
1806 -> true
1807 ; error_manager:add_error_and_fail(cli_symbolic_model_check,'Symbolic Model Checking is currently only available for B and Event-B.')),
1808 perform_symbolic_model_checking(Algorithm,Result),
1809 handle_symbolic_model_check_result(Result),
1810 stop_xml_feature(model_check,FINFO).
1811
1812 perform_symbolic_model_checking(ic3,Result) :- !, ic3_symbolic_model_check(Result).
1813 perform_symbolic_model_checking(ctigar,Result) :- !, ctigar_symbolic_model_check(Result).
1814 perform_symbolic_model_checking(kinduction,Result) :- !, kinduction_symbolic_model_check(Result).
1815 perform_symbolic_model_checking(tinduction,Result) :- !, tinduction_symbolic_model_check(Result).
1816 perform_symbolic_model_checking(bmc,Result) :- !, bmc_symbolic_model_check(Result).
1817 perform_symbolic_model_checking(Alg,_) :- add_error_fail(cli_symbolic_model_check,'Invalid symbolic model checking algorithm: ',Alg).
1818
1819 handle_symbolic_model_check_result(counterexample_found) :- !, error_occurred(invariant_violation).
1820 handle_symbolic_model_check_result(property_holds) :- !,
1821 format('Model checking complete, invariant holds~n',[]).
1822 handle_symbolic_model_check_result(solver_and_provers_too_weak) :- !,
1823 format('Model checking incomplete because a constraint could not be solved in time~n',[]),
1824 error_occurred(model_check_incomplete).
1825 handle_symbolic_model_check_result(limit_reached) :- !,
1826 format('Model checking incomplete because an iteration limit was reached~n',[]),
1827 error_occurred(model_check_incomplete).
1828
1829 zmq_start_master(invariant,Identifier) :-
1830 start_animation_without_computing,
1831 zmq_get_initialisation_term(InitTerm),
1832 (option(strict_raise_error) -> Strict = 1 ; Strict = 0),
1833 get_preference(port, PortStart),
1834 get_preference(max_states, Max),
1835 get_preference(ip, IP),
1836 get_preference(logdir, LogDir),
1837 get_preference(tmpdir, TmpDir),
1838 get_preference(hash_cycle, HashCycle),
1839 atom_concat(LogDir, '/distb-', ATmp),
1840 atom_concat(ATmp, Identifier, Logfile),
1841 atom_concat(TmpDir, '/db-distb-', TTmp),
1842 atom_concat(TTmp, Identifier, TmpDir2),
1843 start_master(InitTerm,Max,PortStart,Strict,IP,Logfile,TmpDir2,HashCycle),
1844 halt.
1845 zmq_start_master(assertion,Identifier) :-
1846 get_preference(port, PortStart),
1847 get_preference(logdir, LogDir),
1848 get_preference(ip, IP),
1849 get_preference(tmpdir, TmpDir),
1850 get_preference(hash_cycle, HashCycle),
1851 atom_concat(LogDir, '/distb-', ATmp),
1852 atom_concat(ATmp, Identifier, Logfile),
1853 atom_concat(TmpDir, '/db-distb-', TTmp),
1854 atom_concat(TTmp, Identifier, TmpDir2),
1855 current_state_corresponds_to_setup_constants_b_machine,
1856 animation_mode(b),
1857 full_b_machine(Machine),
1858 b_get_assertions(_,static,SAss),
1859 b_get_assertions(_,dynamic,DAss),
1860 append(SAss,DAss,Ass),
1861 count_assertions(Ass,0,N),
1862 assertz(master:assertion_count(N)),
1863 current_expression(_,State1),
1864 specfile:state_corresponds_to_set_up_constants(State1,State),
1865 zmq_get_important_options(Options),
1866 (option(strict_raise_error) -> Strict = 1 ; Strict = 0),
1867 %start_master(assertions(classical_b(Machine,Options),State,Ass),2,-1,PortStart,0,Strict,IP,Logfile,TmpDir2),
1868 start_master(assertions(classical_b(Machine,Options),State,Ass),2,PortStart,Strict,IP,Logfile,TmpDir2,HashCycle),
1869 halt.
1870
1871 zmq_get_initialisation_term(Term) :-
1872 (animation_mode(b) ; animation_mode(csp_and_b)), % CSP file not yet added when ZMQ master starts working
1873 \+ animation_minor_mode(eventb),
1874 option(add_csp_guide(CspGuide)),
1875 !, % Classical B + CSP
1876 debug_println(20,'ZMQ: Transferring CSP || B model'),
1877 full_b_machine(Machine),
1878 % TO DO: extract CSP Term rather than file name: will not work for distribution on other file-systems
1879 zmq_get_important_options(Options),
1880 Term = classical_b_with_csp(Machine,CspGuide,Options).
1881 zmq_get_initialisation_term(Term) :-
1882 debug_println(20,'Generating ZMQ Worker Initialisation'),
1883 animation_mode(b), \+ animation_minor_mode(eventb), !, % Classical B
1884 debug_println(20,'ZMQ: Transferring Classical-B model'),
1885 full_b_machine(Machine),
1886 zmq_get_important_options(Options),
1887 Term = classical_b(Machine,Options).
1888 zmq_get_initialisation_term(Term) :-
1889 animation_mode(b), animation_minor_mode(eventb), !, % Event-B
1890 debug_println(20,'ZMQ: Transferring Event-B model'),
1891 full_b_machine(Machine),
1892 zmq_get_important_options(Options),
1893 Term = eventb(Machine,Options).
1894 zmq_get_initialisation_term(Term) :-
1895 animation_mode(cspm),
1896 loaded_main_file(MainCSPFile),!, % TO DO: pass CSP Prolog term rather than file name (for distribution)
1897 zmq_get_important_options(Options),
1898 debug_println(20,'ZMQ: Transferring CSP specification'),
1899 Term = csp_specification(MainCSPFile,Options).
1900 zmq_get_initialisation_term(_Term) :-
1901 \+ real_error_occurred, % otherwise error occured while loading
1902 animation_mode(Mode),
1903 add_internal_error('Unsupported formalism for ZMQ', Mode),
1904 fail.
1905
1906 zmq_get_initialisation_term(filename(FN)) :-
1907 loaded_main_file(FN).
1908
1909 % get important command-line options to be transmitted to probcli worker
1910 zmq_get_important_options(Options) :- findall(O, (option(O), zmq_important_option(O)), Options),
1911 debug_println(20,transferring_zmq_options_to_workers(Options)).
1912 zmq_important_option(coverage(_)).
1913 zmq_important_option(expect_error(_)).
1914 zmq_important_option(optional_error(_)).
1915 zmq_important_option(file_info).
1916 zmq_important_option(log(_)).
1917 zmq_important_option(print_version(_)).
1918 zmq_important_option(profiling_on).
1919 zmq_important_option(set_card(_,_)).
1920 zmq_important_option(set_pref(_,_)).
1921 zmq_important_option(set_preference_group(_,_)).
1922 zmq_important_option(verbose).
1923 zmq_important_option(statistics).
1924 zmq_important_option(csv_table_command(_,_,_,_)).
1925 zmq_important_option(very_verbose).
1926 zmq_important_option(set_searchscope(_)).
1927 zmq_important_option(no_invariant_violations).
1928 %zmq_important_option(no_deadlocks).
1929 %zmq_important_option(no_goal).
1930 % we could consider also supporting: -argv, -cache, -prefs FILE csp_main(ProcessName) profiling_on prob_profile runtimechecking
1931
1932 % set options received by a zmq worker
1933 :- use_module(b_global_sets, [set_user_defined_scope/2]).
1934 :- use_module(tools_strings, [convert_cli_arg/2]).
1935 zmq_set_important_options(Options) :- debug_println(20,setting_zmq_options(Options)),
1936 maplist(prob_cli:zmq_set_option,Options).
1937 zmq_set_option(file_info) :- !, file_info.
1938 zmq_set_option(log(F)) :- !,
1939 generate_time_stamp(Datime,NOW),
1940 cli_start_logging(F,ascii,NOW,Datime,[zmq_worker]).
1941 zmq_set_option(print_version(V)) :- !, print_version(V).
1942 zmq_set_option(profiling_on) :- !, profiling_on.
1943 zmq_set_option(set_card(Set,V)) :- !,
1944 convert_cli_arg(V,Value),
1945 set_user_defined_scope(Set,Value).
1946 zmq_set_option(set_pref(P,V)) :- !, set_pref(P,V).
1947 zmq_set_option(set_preference_group(P,V)) :- !, set_preference_group(P,V).
1948 zmq_set_option(verbose) :- !, verbose.
1949 zmq_set_option(very_verbose) :- !, very_verbose.
1950 zmq_set_option(O) :- zmq_delayed_option(O),!, assert_option(O). % DO IT LATER
1951 zmq_set_option(O) :- add_internal_error('Unsupported option for ZMQ worker: ',zmq_set_option(O)).
1952
1953 zmq_delayed_option(coverage(_)).
1954 zmq_delayed_option(expect_error(_)).
1955 zmq_delayed_option(expect_error_pos(_,_,_)).
1956 zmq_delayed_option(optional_error(_)).
1957 zmq_delayed_option(statistics).
1958 zmq_delayed_option(set_searchscope(_)).
1959 zmq_delayed_option(no_invariant_violations). % not supported yet
1960
1961 ltsmin_ltl_output(Filename, NOW) :-
1962 if_option_set(ltl_formula_model_check(Formula, _),true),
1963 ltsmin_generate_ltlfile(Formula, Filename),
1964 halt_prob(NOW,0). % if we additionally specify -ltsformula, we do not want to model check it
1965
1966
1967 start_ltsmin_srv(X, NOW) :-
1968 nls,println_silent('Starting LTSMin Server...'),
1969 if_option_set(ltl_formula_model_check(Formula, _),true),
1970 ltsmin_init(X, Zocket, Formula),
1971 ltsmin_loop(Zocket),
1972 ltsmin_teardown(Zocket, X),
1973 nls,println_silent('Stopped LTSMin Server.'),
1974 halt_prob(NOW,0). % if we additionally specify -ltsformula, we do not want to model check it
1975
1976 zmq_start_worker(Identifier, NOW) :-
1977 get_preference(port, Port),
1978 get_preference(logdir, LogDir),
1979 get_preference(tmpdir, TmpDir),
1980 get_preference(proxynumber, ProxyNumber),
1981 /* TODO: ensure directory exists (pk, 09.01.2018) */
1982 atom_concat(LogDir, '/worker-', ATmp),
1983 atom_concat(ATmp, Identifier, Logfile),
1984 % TODO: tmp dir currently not used
1985 atom_concat(TmpDir, '/db-worker-', TTmp),
1986 atom_concat(TTmp, Identifier, TmpDir2),
1987 start_worker(Port,ProxyNumber,Logfile,TmpDir2,zmq_worker_load_model),
1988 formatsilent('ZMQ worker finished (Port:~w)~n',[Port]),
1989 cli_process_loaded_file_afer_start_animation(NOW),
1990 println_silent('Exiting probcli worker'),
1991 halt_prob(NOW,0).
1992
1993 zmq_start_animation :-
1994 prob2_interface:start_animation,
1995 if_option_set(set_goal(GOAL),
1996 cli_set_goal(GOAL)), % not used yet
1997 if_option_set(set_searchscope(SCOPE),
1998 cli_set_searchscope(SCOPE)),
1999 cli_computeOperations(_).
2000 zmq_worker_load_model(classical_b(Machine,Options)) :- !,
2001 debug_println(20,'ZMQ WORKER: Loading classical B model'),
2002 zmq_set_important_options(Options),
2003 bmachine:b_machine_reset, bmachine:assert_main_machine(Machine),
2004 set_animation_mode(b),
2005 zmq_start_animation.
2006 zmq_worker_load_model(classical_b_with_csp(Machine,CspGuide,Options)) :- !,
2007 debug_println(20,'ZMQ WORKER: Loading CSP || B model'),
2008 zmq_set_important_options(Options),
2009 bmachine:b_machine_reset, bmachine:assert_main_machine(Machine),
2010 set_animation_mode(b),
2011 prob2_interface:start_animation,
2012 tcltk_add_csp_file(CspGuide), % TO DO: use CSP Prolog term rather than filename <----------------
2013 zmq_start_animation.
2014 zmq_worker_load_model(eventb(Machine,Options)) :- !,
2015 print(loading_eventb(Options)),nl,
2016 zmq_set_important_options(Options),
2017 bmachine:b_machine_reset, bmachine:assert_main_machine(Machine),
2018 set_animation_mode(b), set_animation_minor_mode(eventb),
2019 zmq_start_animation.
2020 zmq_worker_load_model(csp_specification(CSPFile,Options)) :-
2021 zmq_set_important_options(Options),
2022 load_cspm_spec_from_cspm_file(CSPFile), % TO DO: pass CSP Prolog term rather than filename
2023 zmq_start_animation.
2024 zmq_worker_load_model(filename(FN)) :- !,
2025 printsilent('loading file by filename\n'),flush_output,
2026 ( is_eventb_b(FN) ->
2027 eclipse_interface:load_eventb_file(FN)
2028 ;
2029 bmachine:b_load_machine_probfile(FN)),
2030 zmq_start_animation.
2031 zmq_worker_load_model(assertions(Machine,State,Assertions)) :- !,
2032 assertz(assertion_counter(-1)),
2033 println_silent(loaded_model_for_assertion_checking),
2034 zmq_worker_load_model(Machine),
2035 assertz(worker:assertion_state(State)),
2036 make_assertionwps(Assertions).
2037 % assert current state
2038 zmq_worker_load_model(Other) :-
2039 add_internal_error('ZMQ worker: Unexpected machine description', zmq_worker_load_model(Other)),
2040 fail.
2041
2042
2043 :-dynamic assertion_counter/1.
2044
2045 count_assertions([],A,A).
2046 count_assertions([H|T],A,R) :- size_of_conjunction(H,N1),
2047 NN is A + N1,
2048 count_assertions(T,NN,R).
2049
2050 make_assertionwps([]).
2051 make_assertionwps([H|T]) :- conjunction_to_list(H,HL),
2052 sort_assertions(HL,SL),
2053 append_assertion(SL),
2054 make_assertionwps(T).
2055
2056 append_assertion([]).
2057 append_assertion([H|T]) :- assertion_counter(N),
2058 retractall(assertion_counter(_)),
2059 N1 is N + 1,
2060 assertz(assertion_counter(N1)),
2061 assertz(worker:assertion_task(N1,H)),
2062 append_assertion(T).
2063
2064 %assertions_order(A,B) :- term_size(A,NA),term_size(B,NB), NA > NB.
2065 sort_assertions(X,X).
2066 % :- samsort(assertions_order,X,Y).
2067
2068
2069
2070 is_eventb_b(FN) :- append(_,FN,".eventb").
2071 % load_model(Initialisation)
2072
2073
2074 :- use_module(predicate_evaluator).
2075 :- use_module(bmachine,[b_machine_name/1]).
2076 set_analyse_hook(AddPrefix) :- % set a hook to write false/unknown expressions into a dot file
2077 reset_dot_file_number,
2078 if_options_set(dot_analyse_output_prefix(_Path),
2079 (set_dot_file_prefix_if_option_set(AddPrefix),
2080 register_conjunct_error_hook(prob_cli:pred_eval_hook))).
2081 unset_analyse_hook :- predicate_evaluator:reset_conjunct_error_hook.
2082
2083 :- use_module(tools,[get_modulename_filename/2]).
2084 loaded_root_filename(RootName) :- loaded_main_file(MainFile),
2085 get_modulename_filename(MainFile,RootName).
2086
2087 set_dot_file_prefix_if_option_set(AddPrefix) :-
2088 if_options_set(dot_analyse_output_prefix(Path),
2089 (loaded_root_filename(RootName),
2090 % we could also use b_machine_hierarchy:main_machine_name(RootName)
2091 string_concatenate(Path,RootName,P1),
2092 string_concatenate(P1,AddPrefix,FullPath),
2093 set_dot_file_prefix(FullPath),
2094 debug_println(9,dot_file_prefix(FullPath)))).
2095
2096 % Status: true, false, unknown
2097 :- public pred_eval_hook/5.
2098 pred_eval_hook(_Conjunct,true,_EnumWarning,_IsExpanded, _CS) :-
2099 \+ option(dot_generate_for_all_formulas),!. % don't generate .dot for true formulas, unless explicitly requested
2100 pred_eval_hook(Conjunct,Status,_EnumWarning,_IsExpanded, CS) :-
2101 printsilent('Generating dotfile for: '),printsilent(CS),nls,
2102 (write_dot_graph_to_new_file(Status,Conjunct) -> true
2103 ; add_error(dot_output,'Writing dot to file failed: ',CS)).
2104
2105
2106 :- dynamic dot_file_prefix/1.
2107 :- dynamic dot_file_number/1.
2108
2109 dot_file_prefix('~/Desktop/dot').
2110 set_dot_file_prefix(F) :- retractall(dot_file_prefix(_)), assertz(dot_file_prefix(F)).
2111 dot_file_number(0).
2112 reset_dot_file_number :- retractall(dot_file_number(_)), assertz(dot_file_number(0)).
2113 get_next_nr(GNr) :- retract(dot_file_number(Nr)), N1 is Nr+1,
2114 assertz(dot_file_number(N1)), GNr = Nr.
2115 write_dot_graph_to_new_file(Status,BExpr) :-
2116 dot_file_prefix(Dir),get_next_nr(Nr),
2117 string_concatenate('_',Status,Str1),
2118 string_concatenate(Nr,Str1,NS),
2119 string_concatenate(Dir,NS,F1),
2120 atom_concat(F1,'.dot',FileName),
2121 tcltk_interface:write_dot_file_for_pred_expr(BExpr,FileName).
2122
2123 % get dot file name if dot_output has been set
2124 get_dot_file(Type,FileName) :- option(dot_analyse_output_prefix(_)),
2125 set_dot_file_prefix_if_option_set(Type),
2126 dot_file_prefix(Dir),
2127 string_concatenate('_',Type,Str1),
2128 string_concatenate(Dir,Str1,F1),
2129 atom_concat(F1,'.dot',FileName).
2130
2131 :- use_module(extrasrc(refinement_checker),
2132 [tcltk_refinement_search/3, tcltk_load_refine_spec_file/1, tcltk_save_specification_state_for_refinement/1]).
2133 cli_csp_in_situ_refinement_check(P,Type,Q,NOW) :-
2134 debug_println(20,'% Starting CSP Refinement Check'),
2135 loaded_main_file(CSPFile),
2136 ajoin_with_sep(['assert',P,Type,Q], ' ',Assertion),
2137 start_xml_feature(csp_refinement_check,assertion,Assertion,FINFO),
2138 ( timeout_call(tcltk_interface:tcltk_check_csp_assertion(Assertion,CSPFile,'False',_PlTerm,RefTrace),NOW,'cspref')
2139 -> check_ref_result(RefTrace)
2140 ; true),
2141 stop_xml_feature(csp_refinement_check,FINFO).
2142 cli_start_refinement_check(RefFile,PerformSingleFailures,RefNrNodes,NOW) :-
2143 start_xml_feature(refinement_check,file,RefFile,FINFO),
2144 tcltk_load_refine_spec_file(RefFile),
2145 ( timeout_call(tcltk_refinement_search(RefTrace,PerformSingleFailures,RefNrNodes),NOW,refinement_check)
2146 -> check_ref_result(RefTrace)
2147 ; true),
2148 stop_xml_feature(refinement_check,FINFO).
2149 check_ref_result(RefTrace) :-
2150 ( RefTrace==no_counter_example ->
2151 print('==> Refinement Check Successful'),nl
2152 ; RefTrace==no_counter_example_found ->
2153 print('==> Refinement Check did not find Counter-Example but is incomplete'),nl,
2154 error_occurred(refinement_check_incomplete)
2155 ;
2156 print('*** Refinement Check Counter-Example: ***'),nl, print(RefTrace),nl,
2157 print('*** Refinement Check Failed ***'),nl,
2158 error_occurred(refinement_check_fails)).
2159 cli_checkAssertion(Proc,Model,AssertionType,_NOW) :-
2160 loaded_main_file(CSPFile),
2161 ajoin(['assert ',Proc,' :[ ',AssertionType,'[',Model,']',' ]'],Assertion),
2162 start_xml_feature(csp_deadlock_check,assertion,Assertion,FINFO),
2163 ( /*timeout_call(*/tcltk_interface:tcltk_check_csp_assertion(Assertion,CSPFile,'False',_PlTerm,ResTrace)/*,NOW,a)*/
2164 -> check_model_result(Assertion,ResTrace)
2165 ; true),
2166 stop_xml_feature(csp_deadlock_check,FINFO).
2167 cli_check_csp_assertion(Assertion,NOW) :-
2168 start_xml_feature(csp_assertion_check,assertion,Assertion,FINFO),
2169 loaded_main_file(CSPFile),
2170 ajoin(['assert ',Assertion],AssertionFull),
2171 ( timeout_call(tcltk_interface:tcltk_check_csp_assertion(AssertionFull,CSPFile,_Negated,PlTerm,ResTrace),NOW,csp_assertion_check)
2172 -> check_model_result(PlTerm,ResTrace)
2173 ; true),
2174 stop_xml_feature(csp_assertion_check,FINFO).
2175
2176
2177
2178 check_model_result(AssertionPlTerm,ResTrace) :-
2179 ( ResTrace==no_counter_example ->
2180 printsilent('==> Model Check Successful'),nls
2181 ;
2182 (functor(AssertionPlTerm,assertRef,_Arity) ->
2183 print('*** Refinement Check Counter-Example: ***'),nl, print(ResTrace),nl,
2184 print('*** Refinement Check Failed ***'),nl,
2185 error_occurred(refinement_check_fails)
2186 ;
2187 print('*** Model Check Counterexample: ***'),nl,print(ResTrace),nl,
2188 print('*** Model Check Failed ***'),nl,
2189 error_occurred(model_check_fails))
2190 ).
2191 :- use_module(probcspsrc(haskell_csp),[get_csp_assertions_as_string/2,
2192 parse_and_load_cspm_file_into_specific_pl_file/2,
2193 evaluate_csp_expression/2, evaluate_csp_expression/3]).
2194 cli_csp_get_assertions :-
2195 loaded_main_file(CSPFile),
2196 get_csp_assertions_as_string(CSPFile,String),
2197 print('*** Assertions in File (separated by $) ***'),nl,print(String),nl.
2198 cli_eval_csp_expression(E) :-
2199 (loaded_main_file(CSPFile) ->
2200 evaluate_csp_expression(E, CSPFile, Res)
2201 ; evaluate_csp_expression(E,Res)
2202 ), print('Evaluated Expression: '),nl,print(Res),nl.
2203 cli_csp_translate_to_file(PlFile) :-
2204 loaded_main_file(CSPFile),
2205 parse_and_load_cspm_file_into_specific_pl_file(CSPFile,PlFile).
2206 :- use_module(probltlsrc(ltl_fairness),[check_scc_ce/2]).
2207 cli_check_scc_for_ltl_formula(LtlFormula,SCC) :-
2208 check_scc_ce(LtlFormula,SCC).
2209
2210 :- use_module(extrasrc(coverage_statistics),[pretty_print_coverage_information_to_file/1]).
2211 cli_get_coverage_information(FileName) :-
2212 pretty_print_coverage_information_to_file(FileName).
2213 cli_vacuity_check :-
2214 eclipse_interface:get_vacuous_invariants(L),
2215 (L=[] -> print('No vacuous invariants'),nl
2216 ; maplist(prob_cli:add_vacuous_invariant,L)).
2217 add_vacuous_invariant(Inv) :-
2218 translate:translate_bexpression(Inv,TI),
2219 add_error(vacuity_check,'Vacuous invariant: ',TI).
2220 cli_start_socketserver(Port,Loopback) :-
2221 printsilent('Starting Socket Server'),nls,
2222 safe_absolute_file_name(prob_home('.'),AppDir),
2223 printsilent('Application Path: '),printsilent(AppDir),nls,
2224 disable_interaction_on_errors,
2225 ( start_prob_socketserver(Port,Loopback) -> true
2226 ;
2227 print('Starting socket server failed, Port: '), print(Port),nl),
2228 printsilent('Finished Socket Server'),nls.
2229 :- use_module(tools_platform, [platform_is_64_bit/0]).
2230 cli_check_statespace_hash(Expected,Kind) :-
2231 printsilent('Computing hash of entire statespace: '),
2232 compute_full_state_space_hash(Hash),
2233 printsilent(Hash),nls, % TO DO: maybe also compute hash for transitions and check that
2234 (Hash=Expected -> true
2235 ; Kind=='64bit', \+ platform_is_64_bit -> format('Hash does not match ~w (but was computed on 64-bit system)~n',[Expected])
2236 ; Kind=='32bit', platform_is_64_bit -> format('Hash does not match ~w (but was computed on 32-bit system)~n',[Expected])
2237 ; add_error(hash,'Expected Statespace Hash to be: ',Expected)).
2238 :- use_module(extrasrc(b_operation_cache),[get_op_cache_stats/1]).
2239 cli_check_op_cache(ReqInfos) :-
2240 get_op_cache_stats(Stats),
2241 (ReqInfos=[] -> format('Operation caching statistics: ~w~n',[Stats])
2242 ; formatsilent('Operation caching statistics: ~w~n',[Stats])),
2243 accumulate_infos(op_cache,Stats),
2244 check_required_infos(ReqInfos,Stats,op_cache_stats).
2245 cli_show_coverage(ShowEnabledInfo,NOW) :-
2246 cli_show_coverage(_Nodes,_Operations,ShowEnabledInfo,NOW).
2247 cli_show_coverage(Nodes,Operations,ShowEnabledInfo,NOW) :-
2248 ShowEnabledInfo == just_check_stats,!, % no printing of individual transition coverage
2249 get_state_space_stats(TotalNodeSum,TotalTransSum,_ProcessedTotal,_), % no computation overhead
2250 writeln_log(computed_coverage(NOW,TotalNodeSum,TotalTransSum)),
2251 check_totals(Nodes,Operations,TotalNodeSum,TotalTransSum).
2252 cli_show_coverage(Nodes,Operations,ShowEnabledInfo,NOW) :-
2253 ShowEnabledInfo == just_summary,
2254 !, % no printing of detailed transition coverage (avoid traversing state space)
2255 get_state_space_stats(TotalNodeSum,TotalTransSum,ProcessedTotal,Ignored), % no computation overhead
2256 writeln_log(computed_coverage(NOW,TotalNodeSum,TotalTransSum)),
2257 format('Coverage:~n States: ~w (~w processed, ~w ignored)~n Transitions: ~w~n',
2258 [TotalNodeSum,ProcessedTotal,Ignored,TotalTransSum]),
2259 show_initialisation_summary(NOW),
2260 show_operation_coverage_summary(NOW),
2261 (invariant_violated(ID) -> format('At least one state violates the invariant (~w) ~n',[ID]) ; true),
2262 check_totals(Nodes,Operations,TotalNodeSum,TotalTransSum).
2263 cli_show_coverage(Nodes,Operations,ShowEnabledInfo,NOW) :-
2264 print('Coverage:'),nl,
2265 compute_the_coverage(Res,TotalNodeSum,TotalTransSum,ShowEnabledInfo,false),
2266 writeln_log(computed_coverage(NOW,TotalNodeSum,TotalTransSum)),
2267 print(Res),nl,
2268 check_totals(Nodes,Operations,TotalNodeSum,TotalTransSum).
2269 check_totals(Nodes,Operations,TotalNodeSum,TotalTransSum) :-
2270 ( Nodes=TotalNodeSum -> true
2271 ;
2272 add_error(probcli,'Unexpected number of nodes: ',TotalNodeSum),
2273 add_error(probcli,'Expected: ',Nodes),error_occurred(coverage)),
2274 ( Operations=TotalTransSum -> true
2275 ;
2276 add_error(probcli,'Unexpected number of transitions: ',TotalTransSum),
2277 add_error(probcli,'Expected: ',Operations),error_occurred(coverage)).
2278
2279
2280 :- use_module(bmachine,[b_machine_statistics/2, b_get_main_filename/1, b_get_all_used_filenames/1,get_full_b_machine_sha_hash/1]).
2281 :- use_module(tools_strings,[get_hex_bytes/2]).
2282 cli_print_machine_info(statistics) :-
2283 b_machine_name(Name),
2284 %(b_get_main_filename(File) -> true ; File=unknown),
2285 format('Machine statistics for ~w:~n',[Name]),
2286 findall(Key/Nr,b_machine_statistics(Key,Nr),L),
2287 maplist(prob_cli:print_keynr,L),!.
2288 cli_print_machine_info(files(WithSha)) :-
2289 b_machine_name(Name),
2290 (WithSha = with_sha -> Msg2='and SHA1 ' ; Msg2=''),
2291 format('Files ~wused for machine ~w:~n',[Msg2,Name]),
2292 b_get_all_used_filenames(Files),
2293 maplist(prob_cli:print_individual_file(WithSha),Files),!.
2294 cli_print_machine_info(hash(Expected)) :-
2295 b_machine_name(MainName), % to do: findall machines and hashes
2296 get_full_b_machine_sha_hash(HashBytes),
2297 get_hex_bytes(HashBytes,Hash),
2298 format('SHA hash for machine ~w = ~s~n',[MainName,Hash]),!,
2299 write_xml_element_to_log(machine_hash,[hash/Hash]),
2300 (var(Expected) -> true
2301 ; atom_codes(Expected,Hash)
2302 -> format_with_colour_nl(user_output,[green],'Machine hash for ~w matches provided hash.',[MainName])
2303 ; add_error(machine_hash_check,'Unexpected machine hash, expected: ',Expected)).
2304 cli_print_machine_info(Kind) :- add_error(machine_stats,'Could not obtain machine information:',Kind).
2305 print_keynr(Key/Nr) :- format(' ~w : ~w~n',[Key,Nr]).
2306 :- use_module(extension('probhash/probhash'),[raw_sha_hash_file/3]).
2307 :- use_module(tools_strings,[get_hex_bytes/2]).
2308 print_individual_file(with_sha,File) :- Span = machine_info,
2309 raw_sha_hash_file(File,Term,Span),
2310 get_hex_bytes(Term,SHAHexCodes),
2311 format(' ~w, ~s~n',[File,SHAHexCodes]).
2312 print_individual_file(_,File) :- format(' ~w~n',[File]).
2313
2314 check_machine_file_sha(File,ExpectedHash) :- Span = check_machine_file_sha,
2315 get_full_machine_file_path(File,AbsFile),
2316 raw_sha_hash_file(AbsFile,Term,Span),
2317 get_hex_bytes(Term,SHAHexCodes), atom_codes(ExpectedHash,ExpectedShaCodes),
2318 (SHAHexCodes=ExpectedShaCodes
2319 -> format_with_colour_nl(user_output,[green],'Checked SHA1 hash for file ~w is ~s',[AbsFile,SHAHexCodes])
2320 ; add_error(check_machine_file_sha,'Unexpected SHA1 hash of file:',AbsFile),
2321 format_with_colour_nl(user_error,[orange],'! Expected: ~w~n! Actual : ~s',[ExpectedHash,SHAHexCodes])
2322 ).
2323
2324 :- use_module(bmachine,[get_machine_file_number/4, b_absolute_file_name_relative_to_main_machine/2]).
2325 :- use_module(probsrc(tools), [get_parent_directory/2]).
2326 get_full_machine_file_path(File,AbsFile) :-
2327 get_modulename_filename(File,Name), get_filename_extension(File,ExtF),
2328 (get_machine_file_number(Name,ExtF,_Nr,AbsFile)
2329 -> get_parent_directory(File,Parent),
2330 (Parent='' -> true % no path provided
2331 ; File=AbsFile -> true % full path provided
2332 ; b_absolute_file_name_relative_to_main_machine(File,AbsFile) -> true % consistent partial path provided
2333 ; add_error(check_machine_file_sha,'File path is inconsistent with used file:',File),
2334 format_with_colour_nl(user_error,[orange],'! File actually used in B specification:~n ~w',[AbsFile])
2335 )
2336 ; add_error(check_machine_file_sha,'Could not locate the file for:',File),
2337 b_absolute_file_name_relative_to_main_machine(File,AbsFile)
2338 ).
2339
2340 :- use_module(tools,[get_tail_filename/2]).
2341 xml_log_machine_statistics :-
2342 animation_mode(Major),
2343 (animation_minor_mode(Minor) -> true ; Minor=none),
2344 write_xml_element_to_log(animation_mode,[major/Major,minor/Minor]),
2345 (b_or_z_mode, b_machine_name(Main)
2346 -> findall(Key/Nr,b_machine_statistics(Key,Nr),BMachStats),
2347 (b_get_main_filename(MainFile) -> get_tail_filename(MainFile,TailFile) ; TailFile = unknown),
2348 write_xml_element_to_log(b_machine_statistics,[machine_name/Main, tail_filename/TailFile|BMachStats])
2349 ; true).
2350
2351 cli_print_junit_results(ArgV) :-
2352 junit_mode(S),!,
2353 statistics(runtime,[E,_]),
2354 T is E - S,
2355 create_and_print_junit_result(['Integration Tests'],ArgV,T,pass).
2356 cli_print_junit_results(_).
2357
2358 :- use_module(visbsrc(visb_visualiser),[load_visb_file/1,
2359 tcltk_perform_visb_click_event/1, generate_visb_html_for_history/2]).
2360 cli_visb_history(JSONFile,HTMLFile,Options) :-
2361 (load_visb_file(JSONFile)
2362 -> ifm_option_set(visb_click(SVGID),tcltk_perform_visb_click_event(SVGID)), % simulate clicks if requested
2363 generate_visb_html_for_history(HTMLFile,Options)
2364 ; true). % errors already reported
2365
2366 cli_print_history(HistFile) :-
2367 findall( O, option(history_option(O)), Options),
2368 debug_println(9,writing_history_to_file(HistFile)),
2369 (Options=[trace_file] -> tcltk_save_history_as_trace_file(prolog,HistFile) % save as Prolog trace file for replay with -t
2370 ; Options=[json] -> tcltk_save_history_as_trace_file(json,HistFile) % save for replay with ProB2 UI
2371 ; write_history_to_file(HistFile,Options) -> true
2372 ; add_error(history,'Writing history to file failed: ',HistFile)).
2373
2374 cli_print_values(ValuesFilename) :-
2375 (write_values_to_file(ValuesFilename) -> true ; add_error(sptxt,'Writing values to file failed: ',ValuesFilename)).
2376 cli_print_all_values(ValuesDirname) :-
2377 (write_all_values_to_dir(ValuesDirname) -> true ; add_error(sstxt,'Writing all values to directory failed: ',ValuesDirname)).
2378
2379 :- use_module(probltlsrc(trace_generator),[generate_all_traces_until/4]).
2380
2381 cli_generate_all_traces_until(LTL_Stop_AsAtom,FilePrefix) :-
2382 generate_all_traces_until(LTL_Stop_AsAtom,FilePrefix,Result,NrTracesGenerated),
2383 format_with_colour_nl(user_error,[blue],'Generated ~w traces, result=~w~n',[NrTracesGenerated,Result]).
2384
2385 :- dynamic probcli_time_stamp/1.
2386 generate_time_stamp(NOW,TS) :- retractall(probcli_time_stamp(_)),
2387 now(NOW),
2388 current_prolog_flag(argv,ArgV),term_hash(ArgV,Hash),
2389 Rnd is Hash mod 1000,
2390 % random(0,1000,Rnd), always returns 216 % TO DO: try to get milliseconds from some library function
2391 TS is (NOW*1000)+Rnd,
2392 assertz(probcli_time_stamp(TS)).
2393 update_time_stamp(NOW1) :- retractall(probcli_time_stamp(_)),
2394 assertz(probcli_time_stamp(NOW1)).
2395
2396 %get_errors :- \+ real_error_occurred,!, (get_error(_Source,_Msg) -> print('*** Warnings occurred'),nl ; true), reset_errors.
2397 get_errors :-
2398 (get_preference(view_probcli_errors_using_bbresults,true)
2399 -> tools_commands:show_errors_with_bb_results([current]) ; true),
2400 get_error_sources.
2401
2402 get_error_sources :- get_error_with_span(ErrSource,Msg,Span), !,
2403 error_occurred_with_msg(ErrSource,Msg,Span),
2404 findall(1,get_error(ErrSource,_),L), length(L,Nr),
2405 (Nr>0 -> N1 is Nr+1, get_error_category_and_type(ErrSource,Cat,Type),
2406 (Type=error -> print_error('*** Occurences of this error: ')
2407 ; print_error('*** Occurences of this warning: ')),
2408 print_error(N1),
2409 write_xml_element_to_log(multiple_errors_occurred,[category/Cat,(type)/Type,number/N1])
2410 ; true),
2411 get_error_sources.
2412 get_error_sources.
2413
2414 :- use_module(state_space,[state_error/3, invariant_violated/1, time_out_for_invariant/1, time_out_for_assertions/1, time_out_for_node/3]).
2415 ?get_state_space_errors :- option(strict_raise_error),
2416 !,
2417 (\+ option(no_invariant_violations),invariant_violated(ID)
2418 -> (option_verbose ->
2419 format('Invariant violation in state with id = ~w~n',[ID]),
2420 b_interpreter:analyse_invariant_for_state(ID) % caused issue for test 1076
2421 ; format('Invariant violation in state with id = ~w (use -v to print more details)~n',[ID])
2422 ),
2423 error_occurred(invariant_violation)
2424 ; true),
2425 (state_error(_,_,abort_error(TYPE,Msg,_,Span)) -> error_occurred(TYPE,error,Span,Msg) ; true),
2426 get_state_errors(_).
2427 get_state_space_errors.
2428
2429 get_state_errors(ID) :- state_error(ID,_,X), X\=invariant_violated, X\=abort_error(_,_,_,_),
2430 create_state_error_description(X,Msg),error_occurred(Msg),fail.
2431 get_state_errors(ID) :- time_out_for_invariant(ID),error_occurred(time_out_for_invariant),fail.
2432 get_state_errors(ID) :- time_out_for_assertions(ID),error_occurred(time_out_for_assertions),fail.
2433 get_state_errors(ID) :- time_out_for_node(ID,_,time_out),error_occurred(time_out),fail.
2434 get_state_errors(ID) :-
2435 time_out_for_node(ID,_,virtual_time_out(_)), %print(virtual_time_out_for_node(ID)),nl,
2436 error_occurred(virtual_time_out),fail.
2437 get_state_errors(_).
2438
2439
2440 create_state_error_description(eventerror(Event,Error,_),Description) :- !,
2441 functor(Error,Functor,_),
2442 ajoin(['event_error:',Event,':',Functor],Description).
2443 create_state_error_description(StateError,Description) :-
2444 functor(StateError,Functor,_),
2445 atom_concat('state_error:',Functor,Description).
2446
2447 % require a real machine to be loaded
2448 check_loaded_not_empty(Action) :-
2449 file_loaded(true,'$$empty_machine'),!,
2450 add_error(probcli,'No file specified; cannot perform command: ',Action),
2451 error_occurred(loading),fail.
2452 check_loaded_not_empty(Action) :- check_loaded(Action).
2453
2454 check_loaded(Action) :-
2455 ( file_loaded(true) -> true
2456 ; file_loaded(error) -> fail /* we have already generated error message */
2457 ;
2458 add_error(probcli,'No file specified; cannot perform action: ',Action),
2459 error_occurred(loading),fail).
2460
2461 :- dynamic loaded_main_file/2.
2462 loaded_main_file(File) :- loaded_main_file(_Ext,File).
2463
2464 :- use_module(tools,[get_filename_extension/2]).
2465 load_main_file(MainFile,NOW,Already_FullyProcessed) :- retractall(loaded_main_file(_,_)),
2466 debug_print(20,'% Loading: '), debug_println(20,MainFile),
2467 writeln_log_time(loading(NOW,MainFile)),
2468 get_filename_extension(MainFile,Ext),
2469 debug_println(6,file_extension(Ext)),
2470 file_extension_can_be_loaded(Ext,MainFile),
2471 start_probcli_timer(Timer),
2472 load_spec_file(Ext,MainFile,Already_FullyProcessed),
2473 stop_probcli_debug_timer(Timer,'% Finished loading'),
2474 (Already_FullyProcessed==true -> true
2475 ; assertz(loaded_main_file(Ext,MainFile))).
2476
2477 known_spec_file_extension('P',xtl).
2478 known_spec_file_extension(als,alloy).
2479 known_spec_file_extension(csp,csp).
2480 known_spec_file_extension(cspm,csp).
2481 known_spec_file_extension(def,b).
2482 known_spec_file_extension(eval,b_eval).
2483 known_spec_file_extension(eventb,eventb).
2484 known_spec_file_extension(fuzz,z).
2485 known_spec_file_extension(imp,b).
2486 known_spec_file_extension(mch,b).
2487 known_spec_file_extension(pb,b).
2488 known_spec_file_extension(pla,alloy). % Prolog AST of Alloy translation
2489 known_spec_file_extension(prob,b).
2490 known_spec_file_extension(ref,b).
2491 known_spec_file_extension(rmch,b_rules).
2492 known_spec_file_extension(smt,smt).
2493 known_spec_file_extension(smt2,smt).
2494 known_spec_file_extension(sys,b).
2495 known_spec_file_extension(tex,z).
2496 known_spec_file_extension(tla,tla).
2497 known_spec_file_extension(zed,z).
2498
2499 :- use_module(pathes_extensions_db, [load_spec_file_requires_extension/2]).
2500 :- use_module(pathes_lib, [available_extension/1, unavailable_extension/2]).
2501 % check if we can load the file extension given available ProB extensions
2502 file_extension_can_be_loaded(FileExt,_) :- known_spec_file_extension(FileExt,Mode),
2503 load_spec_file_requires_extension(Mode,ProBExtension),
2504 unavailable_extension(ProBExtension,Reason),!,
2505 ajoin(['File with ending .', FileExt,' cannot be loaded because extension not available (',Reason,'):'],Msg),
2506 add_error(probcli,Msg,ProBExtension),
2507 fail.
2508 file_extension_can_be_loaded(_,_). % assume ok; if unrecognized we will load as B machine
2509
2510 %load_spec_file('pl',MainFile) :- !, load_cspm_spec_from_pl_file(MainFile). % no longer needed ?
2511 load_spec_file('csp',MainFile) :- !, load_cspm_spec_from_cspm_file(MainFile).
2512 load_spec_file('cspm',MainFile) :- !, load_cspm_spec_from_cspm_file(MainFile).
2513 load_spec_file('P',MainFile) :- !, load_xtl_spec_from_prolog_file(MainFile).
2514 load_spec_file('p',MainFile) :- !, load_xtl_spec_from_prolog_file(MainFile). % sometimes windows is confused about the upper case letter....
2515 load_spec_file('eventb',MainFile) :- !, load_eventb_file(MainFile).
2516 load_spec_file('v',MainFile) :- !,
2517 print('Warning: .v proof rule file format no longer supported, use -eval_rule_file FILE'),nl,
2518 % but even that may not work; some older rule files required predicate variables
2519 load_b_file_with_options(MainFile). % Siemens Rule File; now use -eval_rule_file
2520 load_spec_file('prob',MainFile) :- !,load_prob_file_with_options(MainFile). % .prob files
2521 load_spec_file('mch',MainFile) :- !,load_b_file_with_options(MainFile).
2522 load_spec_file('sys',MainFile) :- !,load_b_file_with_options(MainFile).
2523 load_spec_file('ref',MainFile) :- !,load_b_file_with_options(MainFile).
2524 load_spec_file('imp',MainFile) :- !,load_b_file_with_options(MainFile).
2525 load_spec_file('rmch',MainFile) :- !,load_b_file_with_options(MainFile).
2526 load_spec_file('def',MainFile) :- !,load_b_file_with_options(MainFile). % .def DEFINITIONS file
2527 load_spec_file('fuzz',MainFile) :- !,tcltk_open_z_file(MainFile).
2528 load_spec_file('tex',MainFile) :- !,tcltk_open_z_tex_file(MainFile).
2529 load_spec_file('zed',MainFile) :- !,tcltk_open_z_tex_file(MainFile). % proz .zed file
2530 load_spec_file('als',MainFile) :- !,tcltk_open_alloy_file(MainFile).
2531 load_spec_file('pla',MainFile) :- !,tcltk_open_alloy_prolog_ast_file(MainFile). % maybe we should detect .als.pl
2532 load_spec_file('tla',MainFile) :- !, load_tla_file(MainFile).
2533 load_spec_file('eval',File) :- !, % .eval file
2534 cli_set_empty_machine,
2535 assertz(option(eval_string_or_file(file(default),File,exists,_,norecheck))).
2536 load_spec_file('pb',File) :- !, cli_set_empty_machine, % .pb file
2537 cli_set_empty_machine,
2538 assertz(option(eval_string_or_file(file(default),File,exists,_,norecheck))).
2539 %load_spec_file('pml',MainFile) :- !,parsercall:call_promela_parser(MainFile),
2540 % parsercall:promela_prolog_filename(MainFile,PrologFile),
2541 % println_silent(consulting(PrologFile)),
2542 % tcltk_open_promela_file(PrologFile).
2543 load_spec_file(EXT,MainFile) :- print_error('Unknown file extension, assuming B machine:'),
2544 print_error(EXT),
2545 load_b_file_with_options(MainFile).
2546
2547 load_spec_file('pl',MainFile, Already_FullyProcessed) :- !, Already_FullyProcessed=true,
2548 printsilent('Processing PO file: '),printsilent(MainFile),nls,
2549 load_po_file(MainFile),
2550 (option(timeout(TO)) -> set_disprover_timeout(TO) ; reset_disprover_timeout),
2551 (option(disprover_options(L)) -> set_disprover_options(L) ; set_disprover_options([])),
2552 println_silent('Running ProB Disprover'),
2553 run_disprover_on_all_pos(Summary),
2554 print_disprover_stats,
2555 accumulate_infos(disprover,[po_files-1|Summary]),
2556 get_errors,
2557 (option(cli_check_disprover_result(Infos)) -> check_required_infos(Infos,Summary,load_po_file)
2558 ; option(strict_raise_error) -> check_required_infos([false-0,unknown-0,failure-0],Summary,load_po_file)
2559 % TO DO: provide way for user to specify expected info
2560 ; true),
2561 cli_process_options_for_alrady_fully_processed_file(MainFile),
2562 clear_loaded_machines.
2563 load_spec_file(EXT,MainFile,Already_FullyProcessed) :- (EXT='smt2' ; EXT= 'smt'), !,
2564 Already_FullyProcessed=true,
2565 printsilent('Processing SMT file: '),printsilent(MainFile),nls,
2566 (option(eval_repl([])) -> Opts = [repl] ; Opts=[]),
2567 smtlib2_file(MainFile,Opts).
2568 load_spec_file(EXT,F,false) :- load_spec_file(EXT,F).
2569
2570 load_prob_file_with_options(File) :-
2571 (option(release_java_parser) -> Options = [use_fastread] ; Options = []),
2572 load_prob_file(File,Options).
2573 load_b_file_with_options(File) :-
2574 (option(release_java_parser) -> Options = [release_java_parser,use_fastread]
2575 ; option(fast_read_prob) -> Options = [use_fastread] % use fastread for large .prob files
2576 ; Options = []),
2577 % TO DO: automatically release if no option requires parsing and no more file uses it; or print warning if release will affect other options like -repl (DEFINITIONS not available,...)
2578 load_b_file(File,Options).
2579
2580 % do not perform -execute_all if no parameters provided
2581 do_not_execute_automatically('pl').
2582 do_not_execute_automatically('smt2').
2583
2584 test_kodkod_and_exit(MaxResiduePreds,NOW) :-
2585 start_animation_without_computing,
2586 test_kodkod(MaxResiduePreds),
2587 halt_prob(NOW,0).
2588
2589 compare_kodkod_performance1(KPFile,Iterations,NOW) :-
2590 start_animation_without_computing,
2591 compare_kodkod_performance(KPFile,Iterations),
2592 halt_prob(NOW,0).
2593
2594 :- use_module(parsercall,[check_java_version/2,get_parser_version/1, ensure_console_parser_launched/0,
2595 connect_to_external_console_parser_on_port/1]).
2596 check_java_version :- check_java_version(V,Result),
2597 format('Result of checking Java version:~n ~w~n',[V]),
2598 (Result=compatible -> check_parser_version
2599 ; add_error(check_java_version,V)).
2600
2601 check_parser_version :- get_parser_version(PV),!,
2602 format(' ProB B Java Parser available in version: ~w.~n',[PV]). % will also launch parser
2603 check_parser_version :- add_error(check_parser_version,'Cannot start Java B Parser to obtain version number').
2604
2605 :- use_module(pathes_lib,[install_lib_component/2]).
2606 install_prob_lib(Lib,Opts) :- install_lib_component(Lib,Opts).
2607
2608 print_version(Kind) :- print_version(Kind,user_output).
2609
2610 print_version(short,Stream) :- print_short_version(Stream).
2611 print_version(cpp,Stream) :- print_cpp_version(Stream).
2612 print_version(java,Stream) :- print_java_version(Stream).
2613 print_version(full,Stream) :- print_full_version(Stream).
2614 print_version(full_verbose,Stream) :- print_full_version(Stream,verbose).
2615 print_version(host,Stream) :- print_host_version(Stream).
2616 print_version(lib,Stream) :- check_lib_contents(Stream,verbose).
2617
2618 :- use_module(version).
2619 print_short_version(Stream) :-
2620 version(V1,V2,V3,Suffix),revision(Rev),
2621 format(Stream,'VERSION ~p.~p.~p-~p (~p)~N',[V1,V2,V3,Suffix,Rev]).
2622
2623 :- use_module(parsercall,[get_parser_version/1, get_java_command_path/1, get_java_fullversion/1]).
2624 :- use_module(pathes_lib,[check_lib_contents/2]).
2625 print_full_version(Stream) :-
2626 (option_verbose ->
2627 (option(very_verbose)
2628 -> print_full_version(Stream,very_verbose)
2629 ; print_full_version(Stream,verbose)
2630 )
2631 ; print_full_version(Stream,normal)
2632 ).
2633 print_full_version(Stream,Verbose) :-
2634 format(Stream,'ProB Command Line Interface~n',[]),
2635 print_probcli_version(Stream),
2636 ( Verbose=normal -> true
2637 ;
2638 current_prolog_flag(system_type,SysType),
2639 format(Stream,' Prolog System Type: ~p~N', [SysType]), % development or runtime
2640 safe_absolute_file_name(prob_home('.'),AppDir),
2641 format(Stream,' Application Path: ~p~N', [AppDir]),
2642 print_host_version(Stream),
2643 print_java_version(Stream),
2644 print_cpp_version(Stream),
2645 (Verbose = very_verbose
2646 -> print_prolog_flags(Stream), print_extensions(Stream), print_modules(Stream),
2647 check_lib_contents(Stream,verbose)
2648 ; check_lib_contents(Stream,silent)
2649 )
2650 ), print_compile_time_flags.
2651
2652 print_java_version(Stream) :-
2653 (get_java_command_path(JavaPath)
2654 -> format(Stream,' Java Runtime: ~p~N', [JavaPath]),
2655 (get_java_fullversion(JavaVersion)
2656 -> format(Stream,' Java Version: ~s~N', [JavaVersion])
2657 ; format(Stream,' Java Version: *** not available ***~N',[])
2658 ),
2659 (get_parser_version(ParserVersion)
2660 -> format(Stream,' Java Parser: ~p~N', [ParserVersion])
2661 ; format(Stream,' Java Parser: *** not available ***~N',[])
2662 )
2663 ; format(Stream,' Java Runtime: *** not available ***~N',[])
2664 ).
2665
2666 :- use_module(tools_platform, [host_platform/1, host_processor/1]).
2667 print_host_version(Stream) :-
2668 host_platform(HP),
2669 host_processor(Proc),
2670 (platform_is_64_bit -> Bits=64 ; Bits=32),
2671 format(Stream,' Host Processor: ~w (~w bits)~n Host Operating System: ~w~n',[Proc,Bits,HP]).
2672
2673
2674 print_probcli_version(Stream) :-
2675 full_version_str(VersStr),
2676 revision(Rev), lastchangeddate(LCD),
2677 current_prolog_flag(dialect, Dialect),
2678 (Dialect= swi, current_prolog_flag(version_git,PV) -> true
2679 ; current_prolog_flag(version,PV)
2680 ),
2681 format(Stream,' VERSION ~w (~p)~N ~p~N Prolog (~w): ~p~N',
2682 [VersStr,Rev,LCD,Dialect, PV]).
2683
2684
2685 :- use_module(compile_time_flags,[compile_time_flags/1, relevant_prolog_flags/1]).
2686 :- use_module(extension('regexp/regexp'),[get_cpp_version/1]).
2687 print_compile_time_flags :-
2688 compile_time_flags(list(Flags)),
2689 (Flags=[], \+ option_verbose -> true ; format(' COMPILE TIME FLAGS: ~w~N',[Flags])).
2690 print_prolog_flags(Stream) :-
2691 relevant_prolog_flags(Flags),
2692 format(Stream,' PROLOG FLAGS: ~w~N',[Flags]).
2693 print_extensions(Stream) :- findall(E,available_extension(E),Es),
2694 format(Stream,' EXTENSIONS: ~w~N',[Es]).
2695 print_cpp_version(Stream) :-
2696 available_extension(regexp_extension),!,
2697 get_cpp_version(V),
2698 format(Stream,' C++ Version for extensions: ~w~n',[V]).
2699 print_cpp_version(_).
2700 print_modules(Stream) :- findall(M,current_module(M),Ms), sort(Ms,SMs),
2701 format(Stream,' PROLOG MODULES: ~w~N',[SMs]).
2702
2703 print_logo :-
2704 % should be improved considerably; doesn't look very nice yet on macOS terminal due to line separation
2705 % â–„â–„â–„â–„ â–„â–„â–„â–„
2706 % â–ˆ â–ˆ â–ˆ â–ˆ
2707 % █▀▀▀ ▄ ▄▄▄ █▀▀▀▄
2708 % █ █ █▄█ █▄▄▄▀
2709 format_with_colour_nl(user_output,[blue],' ~s',[[9604,9604,9604,9604,32,32,32,32,32,32,32,9604,9604,9604,9604]]),
2710 format_with_colour_nl(user_output,[blue],' ~s',[[9608,32,32,32,9608,32,32,32,32,32,32,9608,32,32,32,9608]]),
2711 format_with_colour_nl(user_output,[blue],' ~s',[[9608,9600,9600,9600,32,9604,32,9604,9604,9604,32,9608,9600,9600,9600,9604]]),
2712 format_with_colour_nl(user_output,[blue],' ~s',[[9608,32,32,32,9608,32,32,9608,9604,9608,32,9608,9604,9604,9604,9600]]).
2713
2714 print_help :-
2715 print_version(full),
2716 print('Usage: probcli FILE [OPTIONS]'),nl,
2717 print(' OPTIONS are: '),nl,
2718 print(' -mc Nr model check; checking at most Nr states'),nl,
2719 print(' -model_check model check without limit on states explored'),nl,
2720 ( \+ option_verbose ->
2721 print(' -noXXX XXX=dead,inv,goal,ass (for model check)'),nl % -nodead, -noinv, -nogoal, -noass
2722 ;
2723 print(' -nodead do not look for deadlocks (for model check, animate, execute)'),nl,
2724 print(' -noinv do not look for invariant violations (for model check, animate, execute)'),nl,
2725 print(' -nogoal do not look for GOAL predicate (for model check, execute)'),nl,
2726 print(' -noass do not look for ASSERTION violations (for model check, execute)'),nl
2727 ),
2728 print(' -bf proceed breadth-first (default is mixed bf/df)'),nl,
2729 print(' -df proceed depth-first'),nl,
2730 print(' -mc_mode M M=hash,heuristic,random,dlk,breadth-first,depth-first,mixed,size'),nl, % dlk stands for out_degree_hash
2731 print(' -global_time_out N total timeout in ms for model/refinement checking and'),nl,
2732 print(' and execute steps and disprover checks'),nl,
2733 print(' -disable_timeout disable timeouts for operations, invariants,....'),nl, % speeds up mc
2734 print(' -t trace check (associated .trace file must exist)'),nl,
2735 print(' -init initialise specification'),nl,
2736 print(' -cbc OPNAME constraint-based invariant checking for an operation'),nl,
2737 print(' (you can also use OPNAME=all)'),nl,
2738 print(' -cbc_deadlock constraint-based deadlock checking'),nl,
2739 ( \+ option_verbose -> true ;
2740 print(' -cbc_deadlock_pred PRED as above but with additional predicate'),nl
2741 ),
2742 print(' -cbc_assertions constraint-based static assertion checking'),nl,
2743 print(' -cbc_refinement constraint-based static refinement checking'),nl,
2744 print(' -cbc_sequence S constraint-based search for sequence of operations'),nl,
2745 print(' -strict raise error if model-checking finds counter example'),nl,
2746 print(' or trace checking fails or any error state found'),nl,
2747 print(' -expcterr ERR expect error to occur (ERR=cbc,mc,ltl,...)'),nl,
2748 print(' -animate Nr random animation (max. Nr steps)'),nl,
2749 print(' -animate_all random animation until a deadlock is reached'),nl,
2750 print(' -animate_stats provide feedback which operations are animated or executed'),nl,
2751 print(' -execute Nr execute specification (maximally Nr steps)'),nl,
2752 print(' in contrast to -animate: stops at first operation found, is deterministic,'),nl,
2753 print(' does not store intermediate states and does not use TIME_OUT preference'),nl,
2754 print(' -execute_all execute until a deadlock, direct loop, goal or error is reached'),nl,
2755 print(' -execute_monitor monitor performance of execute'),nl,
2756 print(' -his File write history to File'),nl,
2757 print(' -his_option O additional option when writing a history (show_init,show_states,json,trace_file)'),nl,
2758 print(' -sptxt File save constants and variable values of last discovered state to File'),nl,
2759 print(' -sstxt Dir save constants and variable values of all discovered states to files in Dir'),nl,
2760 print(' -cache Directory automatically save constants to files and avoid recomputation'),nl,
2761 print(' -det_check check if animation steps are deterministic'),nl,
2762 print(' -det_constants only check if SETUP_CONSTANTS step is deterministic'),nl,
2763 ( \+ option_verbose -> true ;
2764 print(' -i interactive animation. Only for interactive sessions,'),nl,
2765 print(' the output can arbitrarily change in future versions. '),nl,
2766 print(' Do not build automatic tools using the interactive mode'),nl
2767 ),
2768 print(' -repl start interactive read-eval-loop'),nl,
2769 print(' -eval "E" evaluate expression or predicate'),nl,
2770 print(' -eval_file FILE evaluate expression or predicate from file'),nl,
2771 print(' -c print coverage statistics'),nl,
2772 print(' -cc Nr Nr print and check coverage statistics'),nl,
2773 print(' -vacuity_check look for vacuous implications in invariant'),nl,
2774 print(' -cbc_redundant_invariants Nr find redundant invariants, expecting Nr'),nl, % Nr exepcted
2775 print(' -statistics print memory and other statistics at the end'),nl,
2776 print(' -p PREF Val set preference to value'),nl,
2777 print(' -prefs FILE set preferences from Prolog file'),nl,
2778 print(' -pref_group G S set group G of preferences to predefined value set S'),nl,
2779 print(' -card GS Val set cardinality (aka scope) of B deferred set'),nl,
2780 print(' -goal "PRED" set GOAL predicate for model checker'),nl,
2781 print(' -check_goal check GOAL (after -mc, -t, or -animate)'),nl,
2782 print(' -scope "PRED" set scope predicate for model checker'),nl,
2783 print(' (only states satsifying this predicate will be examined)'),nl,
2784 print(' -property "PRED" virtually add predicate to PROPERTIES'),nl,
2785 print(' -s Port start socket server on given port'),nl,
2786 print(' -ss start socket server on port 9000'),nl,
2787 print(' -sf start socket server on some free port'),nl,
2788 print(' -l LogFile log activities in LogFile'),nl,
2789 print(' -ll log activities in /tmp/prob_cli_debug.log'),nl,
2790 print(' -logxml LogFile log activities in XML LogFile'),nl,
2791 print(' -logxml_write_ids P write variables/constants starting with P to XML LogFile'),nl,
2792 print(' -pp FILE pretty-print internal representation to file (or user_output)'), nl,
2793 print(' -ppf FILE like -pp, but force printing of all type infos'),nl,
2794 print(' -ppAB FILE like -ppf, but make output readable by Atelier-B'),nl,
2795 print(' -ppB FILE pretty-print Event-B model to file in valid B syntax'),nl,
2796 print(' -v verbose'),nl,
2797 ( \+ option_verbose -> true ;
2798 print(' -vv very verbose'),nl
2799 ),
2800 print(' -mc_with_tlc model check using TLC (see also TLC_WORKERS preference)'),nl,
2801 print(' -mc_with_lts_sym model check using LTSmin (symbolic)'),nl,
2802 print(' -mc_with_lts_seq model check using LTSmin (sequential)'),nl,
2803
2804 ( \+ option_verbose -> true ;
2805 print(' -ltsmin_option OPT set option for LTSmin (e.g, por)'),nl,
2806 print(' -ltsmin_ltl_output FILE set output file for LTSMin'),nl,
2807 print(' -symbolic_model_check ALGO ALGO is bmc, kinduction, ctigar, ic3'),nl,
2808 print(' -enabling_analysis_csv FILE perform operation enabling analysis'),nl,
2809 print(' -feasibility_analysis perform operation feasibility analysis'),nl,
2810 print(' -feasibility_analysis_csv FILE write feasibility result to file'),nl,
2811 print(' -read_write_matrix show read/write matrix for operations'),nl
2812 ),
2813 print(' -version print version information (-svers for short info)'),nl,
2814 print(' -check_java_version check that Java version compatible with ProB parser'),nl,
2815 print(' -assertions check ASSERTIONS'),nl,
2816 print(' -main_assertions check ASSERTIONS from main file only'),nl,
2817 print(' -properties check PROPERTIES'),nl,
2818 print(' -cache Dir use directory "Dir" to cache constants and variables'),nl,
2819 print(' -ltlfile F check LTL formulas in file F'),nl,
2820 print(' -ltlassertions check LTL assertions (in DEFINITIONS)'),nl,
2821 print(' -ltllimit L explore at most L states when model-checking LTL or CTL'),nl,
2822 print(' -ltlformula \"F\" check the LTL formula F'),nl,
2823 print(' -ctlformula \"F\" check the CTL formula F'),nl,
2824 print(' -save File save state space for later refinement check'),nl,
2825 print(' -refchk File refinement check against previous saved state space'),nl,
2826 print(' -mcm_tests Depth MaxStates EndPredicate File'),nl,
2827 print(' generate test cases with maximum length Depth, explore'),nl,
2828 print(' maximally MaxStates, the last state satisfies EndPredicate'),nl,
2829 print(' and the test cases are written to File'),nl,
2830 print(' -mcm_cover Operation'),nl,
2831 print(' when generating MCM test cases, Operation should be covered'),nl,
2832 print(' -cbc_tests Depth EndPredicate File'),nl,
2833 print(' generate test cases by constraint solving with maximum'),nl,
2834 print(' length Depth, the last state satisfies EndPredicate'),nl,
2835 print(' and the test cases are written to File'),nl,
2836 print(' -cbc_cover Operation'),nl,
2837 print(' when generating CBC test cases, Operation should be covered'),nl,
2838 % print(' -cbc_cover_all try and cover all operations'),nl, % is now default if no cbc_cover provided
2839 print(' -test_description File'),nl,
2840 print(' read information for test generation from File'),nl,
2841 print(' -dot CMD File write a graph to a dot file, with CMD being one of:'),nl,
2842 (is_dot_command(Cmd),command_description(Cmd,_,Desc),
2843 format(' ~w : ~w~n',[Cmd,Desc]),fail
2844 ; true),
2845 print(' -dotexpr CMD Expr File write a graph for Expr to a dot file, with CMD:'),nl,
2846 (is_dot_command_for_expr(Cmd),command_description(Cmd,_,Desc),
2847 format(' ~w : ~w~n',[Cmd,Desc]),fail
2848 ; true),
2849 print(' -puml CMD File write a graph to a plantuml file, with CMD being one of:'),nl,
2850 (is_plantuml_command(Cmd),command_description(Cmd,_,Desc),
2851 format(' ~w : ~w~n',[Cmd,Desc]),fail
2852 ; true),
2853 print(' -pumlexpr CMD Expr File write a graph for Expr to a plantuml file, with CMD:'),nl,
2854 (is_plantuml_command_for_expr(Cmd),command_description(Cmd,_,Desc),
2855 format(' ~w : ~w~n',[Cmd,Desc]),fail
2856 ; true),
2857 print(' -csv CMD File write a table to a CSV file, with CMD being one of:'),nl,
2858 (is_table_command(Cmd),command_description(Cmd,_,Desc),
2859 format(' ~w : ~w~n',[Cmd,Desc]),fail
2860 ; true),
2861 print(' -csvexpr CMD Expr File write a table for Expr to a CSV file, with CMD:'),nl,
2862 (is_table_command_for_expr(Cmd),command_description(Cmd,_,Desc),
2863 format(' ~w : ~w~n',[Cmd,Desc]),fail
2864 ; true),
2865 print(' -dot_output Path generate dot files for false assertions/properties'),nl,
2866 print(' -dot_all also generate dot files for true assertions/properties'),nl,
2867 print(' -csvhist E File evaluate expression over history and generate CSV file.'),nl,
2868 print(' -load_state File load state of ProB from a saved state space (generated by ProB Tcl/Tk or -save_state)'),nl,
2869 % For Eclipse Version only
2870 %% print(' -parsercp CP class path of the B Parser, this has to be a valid Java class path'),nl,
2871 %% print(' -cspm load CSP-M .csp file rather than B Machine .mch/.ref/.imp File'),nl,
2872 %% print(' -csp load CSP-M .pl file rather than B Machine File'),nl,
2873
2874 /* Options -cspref, -cspdeadlock, -cspdeterministic, and -csplivelock are deprecated, should be excluded in favor of -csp_assertion */
2875 print(' -cspref Spec [m= Impl File'),nl,
2876 print(' checks a refinement statement,'),nl,
2877 print(' where Spec and Impl are processes from File, and \'m\' the type of the refinement:'),nl,
2878 print(' \'T\' for traces, \'F\' for failures, or \'FD\' for failures-divergences.'),nl,
2879 print(' -cspdeadlock P m File'),nl,
2880 print(' checks a process for deadlock,'),nl,
2881 print(' where \'P\' is a process from File, and \'m\' the type of the model:'),nl,
2882 print(' \'F\' for failures and \'FD\' for failures-divergences.'),nl,
2883 print(' -cspdeterministic P m File'),nl,
2884 print(' checks a process for determinism,'),nl,
2885 print(' where \'P\' is a process from File, and \'m\' the type of the model:'),nl,
2886 print(' \'F\' for failures and \'FD\' for failures-divergences.'),nl,
2887 print(' -csplivelock P File'),nl,
2888 print(' checks a process for divergence,'),nl,
2889 print(' where \'P\' is a process from File.'),nl,
2890 /* Options -cspref, -cspdeadlock, -cspdeterministic, and -csplivelock are deprecated, should be excluded in favor of -csp_assertion */
2891
2892 print(' -csp_assertion \"A\" File'),nl,
2893 print(' checks the CSP assertion \'A\' on file \'File\''),nl,
2894 print(' -csp_eval "E" evaluate CSP-M expression.'),nl,
2895 print(' -csp-guide File CSP||B: Use the CSP File to control the B machine'),nl,
2896 print(' '),nl,
2897 ( \+ option_verbose -> true
2898 ;
2899 print(' -test_mode set random seed to the Prolog\'s current random state'),nl,
2900 print(' -rc runtime checking of types/pre-/post-conditions'),nl,
2901 print(' -state_trace File read a file of B predicates (one per line) and try find a matching trace.'),nl
2902
2903 ),
2904 print(' FILE extensions are: '),nl,
2905 print(' .mch for B abstract machines'),nl,
2906 print(' .ref for B refinement machines'),nl,
2907 print(' .imp for B implementation machines'),nl,
2908 print(' .sys for Event-B abstract machines'),nl,
2909 print(' .rmch for B Rule DSL machines'),nl,
2910 print(' .csp, .cspm for CSP-M files, same format as FDR'),nl,
2911 print(' .eventb for Event-B packages exported from Rodin ProB Plugin'),nl,
2912 print(' .tex, .zed for Z models'),nl,
2913 print(' .tla for TLA+ models'),nl,
2914 print(' .als for Alloy models'),nl,
2915 print(' .P for Prolog XTL models'),nl,
2916 ( option_verbose ->
2917 print(' Preferences PREF are: '),nl,
2918 print_eclipse_prefs
2919 ;
2920 print(' Use --help -v to print available preferences PREF'),nl
2921 ),
2922 print(' Set NO_COLOR environment variable to disable terminal colors'),nl,
2923 print(' More info at: https://prob.hhu.de/w/index.php/ProB_Cli'),nl,
2924 nl.
2925
2926
2927 set_argv(V) :-
2928 debug_println(20,set_argv(V)),
2929 external_functions:set_argv_from_atom(V).
2930
2931 :- use_module(b_global_sets, [set_user_defined_scope/2]).
2932 :- use_module(state_space_exploration_modes,[set_depth_breadth_first_mode/1, get_current_breadth_first_level/1]).
2933 :- use_module(tools_strings, [convert_cli_arg/2]).
2934 set_prefs :-
2935 if_option_set(socket(_,_), % then we may need the event(.) transition_info for the Java API
2936 preferences:set_preference(store_event_transinfo,true)),
2937 option(set_prefs_from_file(File)),
2938 debug_println(20,load_preferences(File)),
2939 preferences:load_preferences(File),
2940 fail.
2941 set_prefs :-
2942 option(set_preference_group(P,V)),
2943 debug_println(20,set_preference_group(P,V)),
2944 set_preference_group(P,V),
2945 fail.
2946 % eclipse preference or 'normal preference'
2947 set_prefs :-
2948 ? option(set_pref(P,V)),
2949 set_pref(P,V),
2950 fail.
2951 set_prefs :- option(set_card(Set,V)),
2952 debug_println(20,set_card(Set,V)),
2953 convert_cli_arg(V,Value),
2954 set_user_defined_scope(Set,Value),
2955 fail.
2956 set_prefs :-
2957 ( option(breadth_first) -> set_depth_breadth_first_mode(breadth_first)
2958 ; option(depth_first) -> set_depth_breadth_first_mode(depth_first)
2959 ; option(depth_breadth_first_mode(M)) -> set_depth_breadth_first_mode(M)
2960 ; true
2961 ).
2962 :- use_module(tools_matching,[get_possible_preferences_matches_msg/2]).
2963 set_pref(P,V) :-
2964 debug_println(20,set_pref(P,V)),
2965 ? ( eclipse_preference(P,_)
2966 -> set_eclipse_preference(P,V)
2967 ; deprecated_eclipse_preference(P,_,_,_) -> set_eclipse_preference(P,V)
2968 ; obsolete_eclipse_preference(P) -> probcli_add_light_warning('Obsolete preference: ',P)
2969 ; obsolete_preference(P) -> probcli_add_light_warning('Obsolete preference: ',P)
2970 ; % might be a term if its a plugin preference
2971 atom_codes(P,Codes),
2972 append(Codes,".",Codes2), % to make term readable by read_from_codes
2973 read_from_codes(Codes2,Preference),
2974 (nonvar(Preference),preference_val_type(Preference,_)
2975 -> convert_cli_arg(V,Value),
2976 set_preference(Preference,Value)
2977 ; P=timeout ->
2978 add_error(probcli,'Unknown preference timeout. Either set preference TIME_OUT or use -gobal_time_out command','')
2979 ; get_possible_preferences_matches_msg(P,FuzzyMsg) ->
2980 ajoin(['Unknown preference: ',P,'. Did you mean:'],Msg),
2981 add_error(probcli,Msg,FuzzyMsg)
2982 ; get_possible_fuzzy_match_options(P,FuzzyMatches),
2983 % will only give perfect matches as P usually does not have the hyphen in front
2984 FuzzyMatches = [FMC|_] ->
2985 ajoin(['Unknown preference ', P, ' which looks like a probcli command! Did you want to call:'],Msg),
2986 add_error(probcli,Msg,FMC)
2987 ;
2988 add_error(probcli,'Unknown preference:',P)
2989 )
2990 ).
2991
2992 % add non severe warning:
2993 probcli_add_light_warning(Msg,Term) :- option(strict_raise_error),!,
2994 add_warning(probcli,Msg,Term). % does not write on user_error
2995 probcli_add_light_warning(Msg,Term) :- add_message(probcli,Msg,Term).
2996
2997 set_optional_errors :- % register optional/expected errors in the error_manager; avoid printing on stderr
2998 reset_optional_errors_or_warnings,
2999 (option(optional_error(Type)) ; option(expect_error(Type)) ; option(expect_error_pos(Type,_Line,_Col))),
3000 register_optional_error_or_warning(Type),
3001 fail.
3002 set_optional_errors.
3003
3004 % explicit state model checking, without LTL/CTL
3005 regular_safety_model_check_now(Nr,Runtime,WallTime,MCRes,NOW) :-
3006 statistics(runtime,[T1,_]),
3007 statistics(walltime,[W1,_]),
3008 (option(timeout(TO)) -> safe_time_out(regular_safety_model_check(Nr,Time,MCRes),TO,Res)
3009 ; regular_safety_model_check(Nr,Time,MCRes), Res=success
3010 ),
3011 statistics(runtime,[T2,_]),
3012 statistics(walltime,[W2,_]),
3013 WallTime is W2-W1,
3014 Runtime is T2-T1,
3015 (Res=time_out
3016 -> add_warning(model_check_incomplete,'Not all states examined due to -global_time_out option set by user: ',TO),
3017 writeln_log(timeout_occurred(NOW,model_check(Nr,Time,MCRes))),
3018 coverage(just_summary),
3019 MCRes=time_out
3020 ; true).
3021
3022 :- use_module(model_checker,[model_checking_is_incomplete/6]).
3023
3024 % TO DO: check for ignored states
3025 % code somewhat redundant also with model_check_incomplete below
3026 add_model_checking_warnings(FindInvViolations,FindDeadlocks,FindGoal,FindAssViolations) :-
3027 %print(check(model_checking_is_incomplete(FindInvViolations,FindDeadlocks,FindGoal,FindAssViolations,Msg,Term))),nl,
3028 model_checking_is_incomplete(FindInvViolations,FindDeadlocks,FindGoal,FindAssViolations,Msg,Term),
3029 add_warning(model_check_incomplete,Msg,Term),
3030 % TO DO: store for accumulate_infos
3031 fail.
3032 add_model_checking_warnings(_,_,_,_).
3033
3034 :- use_module(state_space,[current_state_id/1]).
3035 regular_safety_model_check(Nr,Time,ErrRes) :-
3036 statistics(runtime,[T1,_]),
3037 statistics(walltime,[W1,_]),
3038 catch(model_check_aux(Nr,T1,W1,Time,ErrRes), user_interrupt_signal, (
3039 statistics(walltime,[W2,_]), TotalWT is W2-W1,
3040 format_with_colour_nl(user_error,[red],'~nmodel checking interrupted after ~w ms by user (CTRL-C)',[TotalWT]),
3041 coverage(just_summary),
3042 perform_feedback_options_after_exception,
3043 throw(user_interrupt_signal)
3044 )).
3045
3046 % perform some important options for user feedback after CTRL-C interrupts model checking, execute, ...
3047 perform_feedback_options_after_exception :-
3048 (option(check_op_cache(_)) -> cli_check_op_cache([]) ; true),
3049 if_options_set(csv_table_command(TECommand,TableFormulas,TableOptions,TableCSVFile),
3050 csv_table_command(TECommand,TableFormulas,TableOptions,TableCSVFile)),
3051 (option(get_coverage_information(FCC)) -> pretty_print_coverage_information_to_file(FCC) ; true),
3052 (option(cli_print_statistics(X)), (cli_print_statistics(X) -> fail) ; true).
3053
3054 model_check_aux(Nr,T1,W1,Time,ErrRes) :-
3055 (option(no_deadlocks) -> FindDeadlocks=0 ; FindDeadlocks=1),
3056 (option(no_invariant_violations) -> FindInvViolations=0 ; FindInvViolations=1),
3057 (option(no_goal) -> FindGoal=0 ; FindGoal=1),
3058 (option(no_state_errors) -> FindStateErrors=0 ; FindStateErrors=1),
3059 (option(no_assertion_violations)
3060 -> FindAssViolations=0
3061 ; FindAssViolations=1
3062 ),
3063 get_preference(por,POR),
3064 get_preference(pge,PGE),
3065 StopAtFullCoverage=0,
3066 %STOPMCAFTER = 86400000, /* 86400000 = 1 day timeout */
3067 STOPMCAFTER = 1152921504606846975, /* equals 13,343,998,895 days */
3068 InspectExistingNodes = 1,
3069 write_xml_element_to_log(model_checking_options,[find_deadlocks/FindDeadlocks,
3070 find_invariant_violations/FindInvViolations, find_goal/FindGoal,
3071 find_assertion_violations/FindAssViolations,
3072 find_state_errors/FindStateErrors,
3073 partial_order_reduction/POR,
3074 partial_guard_evaluation/PGE,
3075 inspect_existing_nodes/InspectExistingNodes]),
3076 (tcltk_interface:do_model_check(Nr,NodesAnalysed,STOPMCAFTER,ErrRes,
3077 FindDeadlocks,FindInvViolations,FindGoal,
3078 FindAssViolations,FindStateErrors,StopAtFullCoverage,POR,PGE, InspectExistingNodes)
3079 -> (statistics(runtime,[T2,_]), statistics(walltime,[W2,_]),
3080 Time1 is T2-T1, WTime is W2-W1,
3081 (model_checker: expired_static_analysis_time(AnalysisTime) ->
3082 Time is Time1 - AnalysisTime
3083 ; Time = Time1, AnalysisTime=0),
3084 formatsilent('Model checking time: ~w ms (~w ms walltime)~n',[Time,WTime]),
3085 formatsilent('States analysed: ~w~n',[NodesAnalysed]),
3086 get_state_space_stats(_,NrTransitions,_,_),
3087 printsilent('Transitions fired: '),printsilent(NrTransitions),nls,
3088 (get_current_breadth_first_level(Level)
3089 -> formatsilent('Breadth-first levels: ~w~n',[Level]) % is this the equivalent of TLC's diameter?
3090 ; true),
3091 write_xml_element_to_log(model_checking_statistics,
3092 [result/ErrRes,runtime/Time,walltime/WTime,
3093 states/NodesAnalysed,transitions/NrTransitions,staticAnalysisTime/AnalysisTime]),
3094 (ErrRes = no
3095 -> print('No counter example Found, not all states visited'),nl,
3096 add_warning(model_check_incomplete,'Not all states examined due to limit set by user: ',Nr)
3097 ; ErrRes=all
3098 -> (tcltk_find_max_reached_node
3099 -> (not_interesting(_)
3100 -> print('No counter example found. However, not all transitions were computed (and some states not satisfying SCOPE predicate were ignored) !')
3101 ; print('No counter example found. However, not all transitions were computed !')
3102 )
3103 ; not_interesting(_)
3104 -> print_green('No counter example found. ALL states (satisfying SCOPE predicate) visited.')
3105 % b_get_machine_searchscope(Scope)
3106 ; print_green('No counter example found. ALL states visited.')
3107 ),nl,
3108 add_model_checking_warnings(FindInvViolations,FindDeadlocks,FindGoal,FindAssViolations)
3109 ; % ErrRes is not no or all
3110 print_red('*** COUNTER EXAMPLE FOUND ***'),nl,
3111 debug_println(20,ErrRes),nl,
3112 tcltk_interface:translate_error_for_tclk(ErrRes,TclTkRes),
3113 print(TclTkRes),nl,
3114 (option(silent) -> true
3115 ; option(no_counter_examples) -> true % -nocounter
3116 ; tcltk_interface:tcltk_get_history(list(Hist)),
3117 length(Hist,Len),
3118 format('*** TRACE (length=~w):~n',[Len]),
3119 reverse(Hist,Trace),
3120 print_nr_list(Trace),
3121 (silent_mode(off),
3122 current_state_id(ID),invariant_violated(ID)
3123 -> b_interpreter:analyse_invariant_for_state(ID)
3124 ; true)
3125 ),
3126 error_occurred(TclTkRes)
3127 ),nl
3128 )
3129 ; % do_model_check failed
3130 statistics(runtime,[T2,_]), Time1 is T2-T1,
3131 (model_checker: expired_static_analysis_time(AnalysisTime) -> Time is Time1 - AnalysisTime
3132 ; Time = Time1),
3133 printsilent('Model checking time: '), printsilent(Time), printsilent(' ms'),nls,
3134 print_error('*** Model checking FAILED '),nl,
3135 ErrRes=fail,
3136 definite_error_occurred
3137 ).
3138
3139 % perform all cbc checks on current machine
3140 cbc_check(_NOW) :-
3141 option(cbc_deadlock_check(DeadlockGoalPred)),
3142 cbc_deadlock_check(DeadlockGoalPred),
3143 fail.
3144 cbc_check(_NOW) :-
3145 option(constraint_based_check(OpName)),
3146 constraint_based_check(OpName),
3147 fail.
3148 cbc_check(_NOW) :- option(cbc_assertions(AllowEnumWarning,Options)),
3149 cbc_assertions(AllowEnumWarning,Options),
3150 fail.
3151 %cbc_check(NOW) :-
3152 % option(cbc_pred(TargetPredString)),
3153 % check_loaded(cbc_pred),
3154 % print('% Starting Constraint-Based Check for Predicate: '), print(TargetPredString),nl,
3155 % b_set_up_valid_state_with_pred(NormalisedState,Pred) TO DO: add this feature
3156 cbc_check(_NOW) :- option(cbc_sequence(Sequence,TargetPredString,Findall)),
3157 cbc_sequence(Sequence,TargetPredString,Findall),
3158 fail.
3159 cbc_check(_NOW) :- option(cbc_refinement),
3160 cbc_refinement,
3161 fail.
3162 cbc_check(_NOW) :- option(cbc_redundant_invariants(NrExpected)),
3163 cbc_redundant_invariants(NrExpected),
3164 fail.
3165 cbc_check(_).
3166
3167 :- use_module(tcltk_interface,[tcltk_constraint_based_check/2,
3168 tcltk_constraint_based_check_with_timeout/2,
3169 tcltk_constraint_find_deadlock_state_with_goal/3,
3170 tcltk_cbc_find_trace/4,
3171 tcltk_cbc_refinement_check/2]).
3172 :- use_module(probsrc(bmachine),[b_is_operation_name/1]).
3173
3174 constraint_based_check(all) :-
3175 check_loaded_not_empty(constraint_based_check),
3176 print_repl_prompt_s('% Starting Constraint-Based Check for all Operations: '),nl,
3177 start_xml_feature(cbc_operation_check,all_operations,true,FINFO),
3178 (tcltk_constraint_based_check(list(Result),ErrorsWereFound)
3179 -> print('% Constraint-Based Check Result: '),nl,
3180 print(Result),nl,
3181 write_result_to_file(Result),
3182 (ErrorsWereFound=true
3183 -> print_red('*** CONSTRAINT-BASED CHECK FOUND ERRORS ***'),nl, error_occurred(cbc)
3184 ; (ErrorsWereFound=false -> print_green('NO ERRORS FOUND'),nl)
3185 ; print_red('*** TIMEOUT OCCURRED ***'),nl,error_occurred(cbc)
3186 )
3187 ; write_result_to_file(cbc_check_failed), Result=internal_error, ErrorsWereFound=false,
3188 add_internal_error('ConstraintBasedCheck unexpectedly failed. ',cbc_check(all)),definite_error_occurred
3189 ),nl,
3190 write_cbc_check_result(Result,ErrorsWereFound),
3191 stop_xml_feature(cbc_operation_check,FINFO).
3192 constraint_based_check(OpName) :- OpName\=all, % -cbc OpName
3193 check_loaded_not_empty(constraint_based_check),
3194 print_repl_prompt_s('% Starting Constraint-Based Check for Operation: '), print(OpName),nl,
3195 start_xml_feature(cbc_operation_check,operation,OpName,FINFO),
3196 (tcltk_constraint_based_check_with_timeout(OpName,Result)
3197 -> print('% Constraint-Based Check Result: '),nl, print(Result),nl,
3198 write_result_to_file(Result),
3199 (Result=time_out
3200 -> print_red('*** TIMEOUT OCCURRED ***'),nl, error_occurred(cbc)
3201 ; (Result=ok -> print_green('NO ERRORS FOUND'),nl)
3202 ; print_red('*** CONSTRAINT-BASED CHECK FOUND ERRORS ***'),nl,error_occurred(cbc) )
3203 ; write_result_to_file(constraint_based_check_failed), Result=internal_error,
3204 add_error(probcli,'ConstraintBasedCheck unexpectedly failed'),
3205 (b_is_operation_name(OpName) -> true
3206 ; add_error(probcli,'Unknown Operation Name: ',OpName)),
3207 definite_error_occurred
3208 ),nl,
3209 write_cbc_check_result(Result),
3210 stop_xml_feature(cbc_operation_check,FINFO).
3211
3212 write_cbc_check_result(Result) :-
3213 functor(Result,F,_), % example result: no_counterexample_exists(Ids,Prd,Other)
3214 write_xml_element_to_log(cbc_check_result,[result/F]).
3215 write_cbc_check_result(Result,ErrorsWereFound) :- functor(Result,F,_),
3216 write_xml_element_to_log(cbc_check_result,[result/F,errors_were_found/ErrorsWereFound]).
3217
3218 cbc_deadlock_check(DeadlockGoalPred) :-
3219 print_repl_prompt_s('% Starting Constraint-Based DEADLOCK check '),nl,
3220 start_xml_feature(cbc_deadlock_check,FINFO),
3221 (tcltk_constraint_find_deadlock_state_with_goal(DeadlockGoalPred,false,Res)
3222 -> write_result_to_file(Res),
3223 (Res=time_out ->
3224 print_red('*** TIME_OUT occurred ***'),nl,
3225 error_occurred(cbc_deadlock_check_time_out)
3226 ; print_red('*** DEADLOCK state found ***'),nl,
3227 error_occurred(cbc_deadlock_check),
3228 (silent_mode(on) -> true
3229 ; print('*** STATE = '),nl,
3230 current_b_expression(DBState), translate:print_bstate(DBState),nl,
3231 print('*** END DEADLOCKING STATE '),nl
3232 )
3233 )
3234 ; write_result_to_file(no_deadlock_found), Res=no_deadlock_found,
3235 print_green('No DEADLOCK state found'),nl
3236 ),
3237 write_cbc_check_result(Res),
3238 stop_xml_feature(cbc_deadlock_check,FINFO).
3239 cbc_assertions(AllowEnumWarning,Options) :-
3240 findall(OPT,option(cbc_option(OPT)),FullOptions,Options),
3241 check_loaded_not_empty(cbc_assertions),
3242 print_repl_prompt_s('% Starting Constraint-Based static ASSERTIONS check '),nl,
3243 start_xml_feature(cbc_assertion_check,allow_enumeration_warning,AllowEnumWarning,FINFO),
3244 write_prolog_term_as_xml_to_log(options(Options)),
3245 (cbc_constraint_find_static_assertion_violation(Res,FullOptions)
3246 -> process_cbc_assertion_result(Res,AllowEnumWarning)
3247 ; write_result_to_file(cbc_assertions_failed), Res=internal_error,
3248 print_red('CBC Check failed'),nl,
3249 error_occurred(cbc_assertions_failure)
3250 ),
3251 write_cbc_check_result(Res),
3252 stop_xml_feature(cbc_assertion_check,FINFO).
3253 cbc_sequence(Sequence,TargetPredString,Findall) :-
3254 check_loaded_not_empty(cbc_sequence),
3255 print_repl_prompt_s('% Starting Constraint-Based Check for Sequence: '), print_repl_prompt_s(Sequence),
3256 start_xml_feature(cbc_sequence_check,sequence,Sequence,FINFO),
3257 (TargetPredString='' -> true ; print(' with target: '), print(TargetPredString)),
3258 nl,
3259 write_xml_element_to_log(options,[target_predicate/TargetPredString]),
3260 (tcltk_cbc_find_trace(Sequence,TargetPredString,Findall,Res)
3261 -> (Res=ok -> print_green('Sequence found and executed'),nl
3262 ; Res=time_out -> error_occurred(cbc_sequence_time_out)
3263 ; Res=no_solution_found -> print_red('*** NO SOLUTION FOUND '),error_occurred(cbc_sequence_no_solution_found)
3264 ; Res=nr_cbc_sols(NrSols) -> print('*** # SOLUTIONS FOUND: '),print(NrSols),nl
3265 ; print_red('*** Unknown result: '), print(Res),nl,
3266 error_occurred(cbc_sequence)
3267 )
3268 ; print('*** Internal error: Check failed '), error_occurred(cbc_sequence), Res=internal_error
3269 ),
3270 write_cbc_check_result(Res),
3271 stop_xml_feature(cbc_sequence_check,FINFO).
3272 cbc_refinement :-
3273 check_loaded_not_empty(cbc_refinement),
3274 print_repl_prompt_s('% Starting Constraint-Based static refinement check '),nl,
3275 start_xml_feature(cbc_refinement_check,FINFO),
3276 tcltk_cbc_refinement_check(list(Result),ErrorsWereFound),
3277 print('% Constraint-Based Refinement Check Result: '),nl,print(Result),nl,
3278 (ErrorsWereFound = time_out -> print_red('*** TIME_OUT occurred ***'),nl,error_occurred(cbc_refinement_time_out) ;
3279 ErrorsWereFound = true -> print_red('*** Refinement Violation found ***'),nl,error_occurred(cbc_refinement) ;
3280 print_green('No static Refinement Violation found'),nl
3281 ),
3282 write_xml_element_to_log(cbc_check_result,[errors_were_found/ErrorsWereFound]),
3283 stop_xml_feature(cbc_refinement_check,FINFO).
3284 :- use_module(b_state_model_check,[cbc_find_redundant_invariants/2]).
3285 cbc_redundant_invariants(NrExpected) :-
3286 check_loaded_not_empty(cbc_redundant_invariants),
3287 print_repl_prompt_s('% Starting Constraint-Based invariant redundancy check'),nl,
3288 start_xml_feature(cbc_redundant_invariants,FINFO),
3289 cbc_find_redundant_invariants(Res,TimeoutOccured),
3290 length(Res,NrInvs),
3291 (Res = [] -> print_green('No redundant invariants found'),nl
3292 ; format('*** REDUNDANT INVARIANTS (~w) ***~n',[NrInvs]),
3293 prnt(1,Res), nl
3294 ),
3295 (NrExpected = NrInvs -> true
3296 ; format_with_colour_nl(user_error,[red],'*** Expected ~w redundant invariants (instead of ~w).',[NrExpected,NrInvs]),
3297 error_occurred(cbc_redundant_invariants)),
3298 write_xml_element_to_log(cbc_redundant_invariants,[redundant_invariants/NrInvs, timeout_occured/TimeoutOccured]),
3299 stop_xml_feature(cbc_redundant_invariants,FINFO).
3300
3301 prnt(_,[]).
3302 prnt(N,[H|T]) :- format(' ~w : ~w~n',[N,H]), N1 is N+1, prnt(N1,T).
3303
3304 :- use_module(solver_interface,[predicate_uses_unfixed_deferred_set/2, unfixed_typed_id_in_list/3]).
3305 process_cbc_assertion_result(time_out,_) :- !,
3306 write_result_to_file(no_counterexample_found('"TIME_OUT"')),
3307 print_red('*** TIME_OUT occurred ***'),nl,
3308 error_occurred(cbc_assertions_time_out).
3309 process_cbc_assertion_result(no_counterexample_exists(Constants,TotPredicate,OtherInfo),AllowEnumWarning) :- !,
3310 print_green('No counter-example to ASSERTION exists '),(OtherInfo=[] -> true ; print(OtherInfo)),nl,
3311 (unfixed_typed_id_in_list(TID,CType,Constants) % TO DO: look only at component
3312 -> write_deferred_set_used(AllowEnumWarning),
3313 get_texpr_id(TID,CID),pretty_type(CType,CTypeS),
3314 format('Warning: Some constants use deferred sets (e.g., ~w:~w) which have only been checked for a single cardinality!~n',[CID,CTypeS])
3315 ; predicate_uses_unfixed_deferred_set(TotPredicate,CType)
3316 -> write_deferred_set_used(AllowEnumWarning),pretty_type(CType,CTypeS),
3317 format('Warning: Some quantified variables use deferred sets (e.g., ~w) which have only been checked for a single cardinality!~n',[CTypeS]) % happens for tests 1173, 1174
3318 ; write_result_to_file(no_counterexample_exists)
3319 %,print('Computing unsat core: '),nl,unsat_cores:unsat_core(TotPredicate,Core),print('CORE: '),translate:print_bexpr(Core),nl
3320 ). % WE HAVE A PROOF
3321 process_cbc_assertion_result(no_counterexample_found,AllowEnumWarning) :- !,
3322 write_result_to_file(no_counterexample_found('"Enumeration Warning"')),
3323 print('No counter-example for ASSERTION found (*enumeration warning occured*)'),nl,
3324 (AllowEnumWarning=true -> true ; error_occurred(cbc_assertions_enumeration_warning)).
3325 process_cbc_assertion_result(counterexample_found,_) :- !,
3326 write_result_to_file(counterexample_found),
3327 print_red('*** Counter-example for ASSERTION found ***'),nl,
3328 error_occurred(cbc_assertions),
3329 (silent_mode(on) -> true
3330 ; print('*** STATE = '),nl,
3331 current_b_expression(DBState), translate:print_bstate(DBState),nl,
3332 print('*** END ASSERTION counter-example STATE '),nl
3333 ),
3334 (get_dot_file('cbc_assertions',DFile) -> generate_dot_from_assertions(DFile) ; true).
3335 process_cbc_assertion_result(Res,A) :-
3336 write_result_to_file(Res),
3337 add_internal_error('Unknown: ',process_cbc_assertion_result(Res,A)).
3338
3339
3340 write_deferred_set_used(AllowEnumWarning) :-
3341 write_result_to_file(no_counterexample_found('"Deferred Sets Used"')),
3342 (AllowEnumWarning=true -> true ; error_occurred(cbc_assertions_enumeration_warning)).
3343
3344 :- use_module(tools_io,[safe_open_file/4]).
3345 write_result_to_file(Result) :- option(cbc_result_file(FILE)),
3346 safe_open_file(FILE,write,Stream,[encoding(utf8)]),
3347 !,
3348 write(Stream,Result),
3349 close(Stream).
3350 write_result_to_file(_).
3351
3352
3353
3354 if_option_set(Option,Call) :-
3355 if_option_set(Option,Call,true).
3356 if_option_set(Option,Then,Else) :-
3357 (option(Option) -> call_for_option(Then) ; call_for_option(Else)).
3358 ifm_option_set(Option,Call) :-
3359 ifm_option_set(Option,Call,true).
3360 ifm_option_set(Option,Then,Else) :- % can perform multiple options
3361 findall(Then,option(Option),As),
3362 (As=[] -> call_for_option(Else) ; perform(As)).
3363 perform([]).
3364 perform([A|T]) :-
3365 call_for_option(A),
3366 perform(T).
3367 call_for_option(Call) :- (call(Call) -> true ; add_internal_error('probcli option call failed: ',Call)).
3368 if_option_set_loaded(Option,Action,Call) :-
3369 ( option(Option),check_loaded_not_empty(Action) ->
3370 call_for_option(Call)
3371 ; true).
3372 ifm_option_set_loaded(Option,Action,Call) :- % can perform multiple options
3373 findall(Call,(option(Option),check_loaded_not_empty(Action)),As),
3374 perform(As).
3375
3376
3377
3378 if_options_set(Option,Call) :- % allow multiple solutions for Option
3379 option(Option),call(Call),fail.
3380 if_options_set(_,_).
3381
3382 print_options :- print('CLI OPTIONS: '),nl,
3383 option(Option), print(Option), nl, fail.
3384 print_options :- nl.
3385
3386 :- use_module(cbcsrc(enabling_analysis),[infeasible_operation_cache/1]).
3387 :- use_module(cbcsrc(sap),[explore_and_generate_testcases/7,cbc_gen_test_cases_from_string/5, tcl_get_stored_test_cases/1]).
3388 :- use_module(translate,[print_bexpr/1]).
3389
3390 mcm_test_case_generation(ADepth,AMaxStates,ATarget,Output) :-
3391 arg_is_number(ADepth,MaxDepth),
3392 arg_is_number(AMaxStates,MaxStates),
3393 bmachine:b_parse_machine_predicate(ATarget,Target),!,
3394 get_comma_or_space_separated_options(mcm_cover,Events),
3395 (option(silent) -> true
3396 ; print('mcm test case generation, maximum search depth: '),print(MaxDepth),nl,
3397 print('mcm test case generation, maximum number of states: '),print(MaxStates),nl,
3398 print('mcm test case generation, target state predicate: '),print_bexpr(Target),nl,
3399 print('mcm test case generation, output file: '),print(Output),nl,
3400 print('mcm test case generation, events to cover: '),print_list(Events),nl
3401 ),
3402 explore_and_generate_testcases(Events,Target,MaxDepth,MaxStates,Output,NumTests,Uncovered),
3403 printsilent('mcm test case generation, generated test cases: '),printsilent(NumTests),nls,
3404 print_uncovered('mcm test case generation, ',Uncovered).
3405 mcm_test_case_generation(_ADepth,_AMaxStates,_ATarget,_Output) :-
3406 print_error('MCM Test Case Generation failed'),
3407 error_occurred(mcm_tests).
3408
3409 cbc_test_case_generation(ADepth,TargetString,Output) :-
3410 arg_is_number(ADepth,MaxDepth),
3411 ( option(cbc_cover_all) -> Events=all
3412 ; (get_comma_or_space_separated_options(cbc_cover,Events), Events \= []) -> true
3413 ; Events=all ),
3414 (\+ option(cbc_cover_final) -> FEvents = Events
3415 ; Events=all -> FEvents=all,
3416 add_error(cbc_cover_final,'Option cbc_cover_final not compatible with trying to cover all events')
3417 ; FEvents = final(Events),
3418 println_silent('constraint based test case generation, target events considered final')),
3419 printsilent('constraint based test case generation, maximum search depth: '),printsilent(MaxDepth),nls,
3420 printsilent('constraint based test case generation, target state predicate: '),printsilent(TargetString),nls,
3421 printsilent('constraint based test case generation, output file: '),printsilent(Output),nls,
3422 (TargetString = '#not_invariant' -> BMC=invariant_violation
3423 ; TargetString = '#deadlock' -> BMC=deadlock
3424 ; BMC = 'none'),
3425 (BMC \= 'none' ->
3426 printsilent('constraint based test case generation, performing bounded model checking'),nls
3427 ; option(silent) -> true
3428 ; print('constraint based test case generation, events to cover: '),print_list(Events),nl),
3429 cbc_gen_test_cases_from_string(FEvents,TargetString,MaxDepth,Output,Uncovered),
3430 !,
3431 format('constraint based test case generation finished~n',[]),
3432 (BMC \= 'none'
3433 -> tcl_get_stored_test_cases(list(Tests)), %print(tests(Tests)),nl,
3434 (Tests=[] -> print_green('No counterexample found'),nl
3435 ; Tests = [_|_], BMC=deadlock -> add_error(deadlock,'Deadlock found by bmc')
3436 ; Tests = [_|_] -> add_error(invariant_violation,'Invariant violation found by bmc')
3437 ; add_internal_error('Unexpected bmc result: ',Tests)
3438 )
3439 ; Uncovered=[_|_],option(strict_raise_error)
3440 -> add_error(cbc_tests,'Uncovered events: ',Uncovered)
3441 ; print_uncovered('constraint based test case generation, ',Uncovered)
3442 ).
3443 cbc_test_case_generation(_ADepth,_ATarget,_Output) :-
3444 print_error('Constraint based test case generation failed!'),
3445 error_occurred(cbc_tests).
3446
3447 print_uncovered(Msg,Uncovered) :-
3448 include(enabling_analysis:infeasible_operation_cache,Uncovered,Infeasible),
3449 (Infeasible=[]
3450 -> format('~wuncovered events: ',[Msg]),print_list(Uncovered),nl
3451 ; format('~winfeasible uncovered events: ',[Msg]),print_list(Infeasible),nl,
3452 exclude(enabling_analysis:infeasible_operation_cache,Uncovered,Feasible),
3453 format('~wuncovered events: ',[Msg]),print_list(Feasible),nl
3454 ).
3455
3456 print_list(all) :- print('** all **').
3457 print_list(list(L)) :- print_list(L). % possibly not used
3458 print_list([]) :- print('** none **').
3459 print_list([H|T]) :- length([H|T],Len), format('(~w) ',[Len]),
3460 print(H),print(' '),print_list2(T).
3461 print_list2([]).
3462 print_list2([H|T]) :- print(H),print(' '),print_list2(T).
3463
3464 get_comma_or_space_separated_options(Option,Selection) :-
3465 functor(O,Option,1),
3466 findall(E, (option(O),arg(1,O,CommaSep),
3467 split_by_seperator(CommaSep,Es),
3468 member(E,Es)),
3469 Selection).
3470
3471 split_by_seperator(NonAtomic,Res) :- \+ atomic(NonAtomic),!, Res=[NonAtomic].
3472 split_by_seperator(String,Strings) :-
3473 atom_chars(String,Chars),
3474 split_by_seperator2(Chars,Strings).
3475 split_by_seperator2(Chars,Result) :-
3476 append(AChars,[X|B],Chars),seperator(X),!,
3477 (AChars=[] -> Result=Rest ; atom_chars(A,AChars), Result=[A|Rest]),
3478 split_by_seperator2(B,Rest).
3479 split_by_seperator2(Chars,[String]) :- atom_chars(String,Chars).
3480
3481 seperator(',').
3482 seperator(' ').
3483 seperator(';').
3484
3485 ltl_check_assertions :-
3486 (option(ltl_limit(Limit)) -> true; Limit= -1), % -1 means no limit
3487 formatsilent('Model checking LTL assertions~n',[]),
3488 ltl_check_assertions(Limit,Outcome),!,
3489 ( Outcome = pass -> print_green('LTL check passed'),nl
3490 ; Outcome = fail -> print_red('*** LTL check failed'),nl,error_occurred(ltl)
3491 ; Outcome = no_tests -> print_red('*** No LTL assertions found, test failed'),nl,definite_error_occurred
3492 ; print_red('*** An error occurred in the LTL assertion test'),nl,
3493 definite_error_occurred).
3494 ltl_check_assertions :-
3495 add_internal_error('Call failed:',ltl_check_assertions),definite_error_occurred.
3496
3497 :- use_module(probltlsrc(ltl),[parse_ltlfile/2]).
3498 ltl_check_file(Filename) :-
3499 (option(ltl_limit(Limit)) -> true; Limit= -1), % -1 means no limit
3500 ajoin(['Model checking LTL assertions from file ',Filename],Msg),
3501 print_repl_prompt_s(Msg),nl,
3502 ( parse_ltlfile(Filename, Formulas)
3503 -> ltl_check_formulas(Formulas,Limit)
3504 ; print_red('An error occurred while parsing the LTL file.\n'),
3505 definite_error_occurred
3506 ).
3507
3508 :- use_module(probltlsrc(ltl),[ltl_model_check2/4]).
3509 ltl_check_formulas([],_) :-
3510 print_green('All LTL formulas checked.\n').
3511 ltl_check_formulas([formula(Name,F)|Rest],Limit) :-
3512 print('Checking formula '),print(Name),print(':\n'),
3513 ltl_model_check2(F,Limit,init,Status),
3514 ( Status == no ->
3515 print_red('Counter-example found for formula \"'),print_red(Name),
3516 print_red('\", saving trace file.\n'),
3517 ajoin(['ltlce_', Name, '.trace'], Tracefile),
3518 tcltk_save_history_as_trace_file(prolog,Tracefile),
3519 add_error(ltl_counterexample,'Counter-example was found')
3520 ; Status == ok ->
3521 ltl_check_formulas(Rest,Limit)
3522 ; Status == incomplete ->
3523 ajoin(['Model was not completly model-checked, aborted after ',Limit,' new states'],
3524 Msg),
3525 add_error(ltl,Msg)
3526 ;
3527 ajoin(['Model checker returns unexpected result (',Status,')'],Msg),
3528 add_error(ltl,Msg)).
3529
3530 % Mode = init or specific_node(ID) or starthere
3531 cli_ltl_model_check(Formula,Mode,ExpectedStatus,Status) :-
3532 (option(ltl_limit(Max)) -> true; Max = -1), % -1 means no limit
3533 start_xml_feature(ltl_model_check,formula,Formula,FINFO),
3534 ltl_model_check(Formula,Max,Mode,Status),
3535 write_xml_element_to_log(model_check_result,[status/Status,expected_status/ExpectedStatus,(mode)/Mode]),
3536 check_status(Status,ExpectedStatus,Formula,ltl),
3537 stop_xml_feature(ltl_model_check,FINFO).
3538
3539 % Mode = init or specific_node(ID) or starthere
3540 cli_ctl_model_check(Formula,Mode,ExpectedStatus,Status) :-
3541 (option(ltl_limit(Max)) -> true; Max = -1), % -1 means no limit
3542 start_xml_feature(ctl_model_check,formula,Formula,FINFO),
3543 ctl_model_check(Formula,Max,Mode,Status),
3544 write_xml_element_to_log(model_check_result,[status/Status,expected_status/ExpectedStatus,(mode)/Mode]),
3545 check_status(Status,ExpectedStatus,Formula,ctl),
3546 stop_xml_feature(ctl_model_check,FINFO).
3547
3548 check_expected(St,Exp,Mode) :-
3549 (St=Exp -> true
3550 ; ajoin(['Unexpected ',Mode,' model checking result ',St,', expected: '],Msg),
3551 add_error(Mode,Msg,Exp)).
3552
3553 check_status(ok,Expected,Formula,ltl) :- !, % TO DO: make uniform ? CTL returns true; LTL returns ok
3554 format_with_colour_nl(user_output,[green],'LTL Formula TRUE.~nNo counter example found for ~w.',[Formula]),
3555 flush_output(user_output),
3556 check_expected(true,Expected,ltl).
3557 check_status(true,Expected,Formula,ctl) :- !,
3558 format_with_colour_nl(user_output,[green],'CTL Formula TRUE.~nNo counter example found for ~w.',[Formula]),
3559 flush_output(user_output),
3560 check_expected(true,Expected,ctl).
3561 check_status(incomplete,Expected,Formula,LTLorCTL) :- !,
3562 incomplete_warning(LTLorCTL,Warning),
3563 add_warning(Warning, 'Warning: Model Check incomplete for: ', Formula),nl,
3564 format('No counter example found so far for ~w.~n',[Formula]),
3565 check_expected(incomplete,Expected,LTLorCTL).
3566 check_status(NO,Expected,Formula,LTLorCTL) :- (NO=no ; NO=false),!, % TO DO: make uniform
3567 (Expected==false
3568 -> format_with_colour_nl(user_error,[red],'Model Check Counterexample found for: ~w',[Formula])
3569 ; add_error(LTLorCTL, 'Model Check Counterexample found for: ', Formula),nl
3570 ),
3571 print('Formula '), print('FALSE.'),nl,
3572 debug_format(19,'Use -his FILE -his_option show_states to display counterexample~n',[]),
3573 nl,
3574 check_expected(false,Expected,LTLorCTL).
3575 check_status(Status,Expected,Formula,LTLorCTL) :-
3576 add_internal_error('Unknown status: ', check_status(Status,Expected,Formula,LTLorCTL)).
3577
3578 incomplete_warning(ltl,ltl_incomplete) :- !.
3579 incomplete_warning(ctl,ctl_incomplete) :- !.
3580 incomplete_warning(X,X).
3581
3582 :- if(environ(prob_release,true)).
3583
3584 run_benchmark(_, _, _) :-
3585 add_message(probcli, 'Command-line argument for benchmarking is not available in release mode.').
3586
3587 :- else.
3588
3589 :- use_module('../tests/smt_solver_benchmarks/alloy2b_benchmarks').
3590 :- use_module('../tests/smt_solver_benchmarks/smt_solver_benchmarks').
3591 run_benchmark(alloy, CmdName, AlloyFilePath) :-
3592 alloy2b_benchmarks:benchmark_alloy_command(CmdName, AlloyFilePath).
3593 run_benchmark(smt, bmc, Path) :-
3594 smt_solver_benchmarks:run_additional_bmc_benchmarks(false, [Path]), halt.
3595 run_benchmark(smt, cbc_deadlock, Path) :-
3596 smt_solver_benchmarks:run_additional_deadlock_benchmarks(false, [Path]), halt.
3597 run_benchmark(smt, cbc_inv, Path) :-
3598 smt_solver_benchmarks:run_additional_inductive_inv_benchmarks(false, [Path]), halt.
3599
3600 :- endif.
3601
3602 evaluate_from_commandline :-
3603 retractall(eval_result(_,_)),
3604 option(eval_string_or_file(A,B,Q,E,Rchk)), %print(eval(A,B,Q,E)),nl,
3605 % treat eval_string and eval_file together to ensure proper order of evaluation
3606 % (only possible side-effect at the moment: formula can add new machine_string facts)
3607 eval_string_or_file(A,B,Q,E,Rchk),
3608 fail.
3609 evaluate_from_commandline :- print_eval_results,
3610 % treat -repl option or -replay File option
3611 (option(eval_repl([File1|TF]))
3612 -> (repl_evaluate_expressions([File1|TF]) -> true ; true)
3613 ; start_repl_if_required).
3614 start_repl_if_required :-
3615 (option(eval_repl([]))
3616 -> (repl_evaluate_expressions([]) -> true ; true)
3617 ; true).
3618
3619 :- dynamic eval_result/2.
3620 add_eval_result(R) :- retract(eval_result(R,N)),!,
3621 N1 is N+1, assertz(eval_result(R,N1)).
3622 add_eval_result(R) :- assertz(eval_result(R,1)).
3623 print_eval_results :- findall(R/N, eval_result(R,N), L), sort(L,SL),
3624 (SL=[] -> true ; format('Evaluation results: ~w~n',[SL])).
3625
3626 :- use_module(tools_printing,[print_error/1, format_error_with_nl/2]).
3627 %eval_string_or_file(string,_String,_,'FALSE',_Recheck) :- !. % comment in to skip evalf
3628 eval_string_or_file(string,String,_,Expected,Recheck) :-
3629 set_current_probcli_command(eval_string(String)),
3630 (option(silent),nonvar(Expected) -> true
3631 ; nonvar(Expected) -> format('eval(~w): ~w~n',[Expected,String])
3632 ; format('eval: ~w~n',[String])
3633 ),
3634 reset_error_spans, % avoid underlining previous errors in eval_string
3635 (eval_string_with_time_out(String,StringResult,EnumWarning,_LS) -> true
3636 ; print_error('Eval string failed: '), print_error(String),
3637 error_occurred(eval_string)
3638 ),
3639 add_eval_result(StringResult),
3640 eval_check_result(StringResult,Expected,EnumWarning,eval_string,String),
3641 (Recheck=recheck(Mode) -> recheck_pp_of_last_expression(Mode,_,_) ; true),
3642 unset_current_probcli_command.
3643 eval_string_or_file(file(bench),File,Quantifier,Expected,Recheck) :- !,
3644 ( member(Solver,[prob,kodkod,sat,'sat-z3','z3', 'cdclt']),
3645 (eval_string_or_file(file(Solver),File,Quantifier,Expected,Recheck) -> fail)
3646 ; true).
3647 eval_string_or_file(file(Solver),File,Quantifier,Expected,_) :-
3648 % evaluate a single formula stored in a file
3649 set_current_probcli_command(eval_file(Solver,File)),
3650 turn_show_error_source_off, % reduce clutter in user feedback; eval_file used in ProB Logic Calculator for example
3651 formatsilent('~nEvaluating file: ~w~n',[File]),
3652 error_manager:reset_error_scopes, % TO DO: avoid that exceptions mess up error scopes in eval_string/file
3653 statistics(runtime,[Start,_]),
3654 statistics(walltime,[W1,_]),
3655 (Expected=='TRUE' -> TypeInfo=predicate(_) % avoids parsing as expression
3656 ; true),
3657 (eval_file(Solver,File,Quantifier,Result,EnumWarning,TypeInfo)
3658 -> statistics(walltime,[W2,_]), WT is W2-W1,
3659 translate_solver_result(Result,Infos),
3660 accumulate_file_infos(File,Solver,[walltime-WT|Infos]),
3661 add_eval_result(Result),
3662 eval_check_result(Result,Expected,EnumWarning,eval_file,File)
3663 ; statistics(walltime,[W2,_]), WT is W2-W1,
3664 accumulate_file_infos(File,Solver,[failure-1,false-0,true-0,unknown-1,walltime-WT]),
3665 add_eval_result(eval_file_failed),
3666 print_error('Eval from file failed: '), print_error(File),
3667 error_occurred(eval_file)
3668 ),
3669 statistics(runtime,[Stop,_]), Time is Stop - Start,
3670 debug_format(19,'Time for ~w : ~w ms (~w ms walltime)~n',[File,Time,WT]),
3671 turn_show_error_source_on,
3672 unset_current_probcli_command.
3673
3674 translate_solver_result('TRUE',I) :- !, I=[false-0,true-1,unknown-0].
3675 translate_solver_result('FALSE',I) :- !, I=[false-1,true-0,unknown-0].
3676 translate_solver_result('UNKNOWN',I) :- !,I=[false-0,true-0,unknown-1].
3677 translate_solver_result('**** TIME-OUT ****',I) :- !,I=[false-0,true-0,unknown-1].
3678 translate_solver_result(_,[false-0,true-0,unknown-1]). % we could record this as error
3679
3680 eval_check_result(StringResult,Expected,_,Origin,File) :- Expected\=StringResult,!,
3681 format_error_with_nl('! Evaluation error, expected result to be: ~w (but was ~w) in ~w',[Expected,StringResult,File]),
3682 error_occurred(Origin).
3683 eval_check_result('NOT-WELL-DEFINED',Expected,_,Origin,File) :- var(Expected),!,
3684 format_error_with_nl('! Evaluation NOT-WELL-DEFINED in ~w',[File]),
3685 error_occurred(Origin).
3686 eval_check_result(_,_,EnumWarning,_,_) :- eval_gen_enum_warning(EnumWarning).
3687
3688 eval_gen_enum_warning(false) :- !.
3689 eval_gen_enum_warning(time_out) :- !,error_occurred(eval_string_time_out).
3690 eval_gen_enum_warning(_) :- print_error('Enumeration warning occurred'),
3691 error_occurred(eval_string_enum_warning,warning).
3692 %repl :- repl_evaluate_expressions([]).
3693 :- use_module(parsercall,[ensure_console_parser_launched/0]).
3694 repl_evaluate_expressions(StartFiles) :-
3695 get_errors, % first clear any errors from earlier commands
3696 nl,
3697 print('ProB Interactive Expression and Predicate Evaluator '), nl,
3698 print('Type ":help" for more information.'),nl,
3699 turn_show_error_source_off, % reduce clutter in user feedback
3700 (option(evaldot(File))
3701 -> print('Solutions written to dot file: '), print(File),nl
3702 ; true
3703 ),
3704 (ensure_console_parser_launched
3705 -> maplist(prob_cli:set_repl_input_file(verbose),StartFiles),
3706 top_level_eval
3707 ; print('>>> ABORTING REPL'),nl),
3708 turn_show_error_source_on.
3709
3710 :- use_module(user_interrupts,[interruptable_call/1]).
3711 top_level_eval :-
3712 catch(top_level_eval1, halt(0), (format('~s', ["Bye."]), nl)).
3713
3714 :- use_module(tools_printing,[reset_terminal_colour/1, print_red/1, print_green/1]).
3715 print_repl_prompt :- reset_terminal_colour(user_output), write('>>> ').
3716 print_repl_prompt_s(_) :- option(silent),!.
3717 print_repl_prompt_s(P) :- print_repl_prompt(P).
3718 print_repl_prompt(P) :- reset_terminal_colour(user_output), write(P).
3719 %print_repl_prompt(P) :- tools_printing:start_terminal_colour(dark_gray,user_output), write(P), reset_terminal_colour(user_output).
3720
3721 top_level_eval1 :-
3722 (interruptable_call(eval1) -> true
3723 ; print_red('Evaluation failed or interrupted'),nl,
3724 print_repl_prompt('Use :q to quit REPL'),nl),
3725 reset_errors,
3726 top_level_eval1.
3727 eval0 :- store_last_error_location_for_repl,
3728 reset_errors, % get_errors prints errors again and quits in -strict mode
3729 % However, reset_errors means that in subsequent REPL runs errors are not printed again!!
3730 garbage_collect, eval1.
3731 eval1 :- repl_multi_read_line(Expr), eval_probcli_repl_line(Expr).
3732
3733 :- dynamic last_repl_error/2.
3734 store_last_error_location_for_repl :-
3735 retractall(last_repl_error(_,_)),
3736 check_error_span_file_linecol(_,File,Line,_,_,_),!,
3737 assertz(last_repl_error(File,Line)).
3738 store_last_error_location_for_repl.
3739
3740 :- dynamic current_repl_input_stream/2.
3741 close_repl_input_stream(file_closed) :- retract(current_repl_input_stream(X,File)),!,
3742 format(":replayed ~w~n",[File]),
3743 close(X).
3744 close_repl_input_stream(no_file).
3745 :- use_module(tools_io,[safe_open_file/4]).
3746 set_repl_input_file(_,File) :- current_repl_input_stream(_,File),!,
3747 add_error(set_repl_input_file,'Cyclic file replay: ',File).
3748 set_repl_input_file(Verbose,File) :-
3749 % close_repl_input_stream, % this way we allow one REPL file to call another
3750 safe_open_file(File,read,Stream,[encoding(utf8)]),!,
3751 (Verbose=verbose -> format('Replaying REPL commands in file: ~w~n',[File]) ; true),
3752 asserta(current_repl_input_stream(Stream,File)).
3753 set_repl_input_file(_,_).
3754
3755 repl_multi_read_line(Line) :-
3756 (current_repl_input_stream(Stream,_)
3757 -> repl_multi_read_line(Stream,Line),
3758 format(user_output,'~s~n',[Line])
3759 ; repl_multi_read_line(user_input,Line)
3760 ).
3761 repl_multi_read_line(Stream,Line) :- repl_multi_read_line_aux(Stream,'>>> ',[],Line).
3762 repl_multi_read_line_aux(Stream,Prompt,SoFar,Line) :-
3763 prompt(OldPrompt,Prompt),
3764 call_cleanup(read_line(Stream,L), prompt(_,OldPrompt)),
3765 (L=end_of_file -> close_repl_input_stream(FileC),
3766 (SoFar=[], FileC = file_closed
3767 -> repl_multi_read_line(Line) % last line of file empty; do not process
3768 ; FileC = file_closed -> Line=SoFar
3769 ; Line=end_of_file) % user pressed CTRL-D
3770 ; append(LFront,[92],L) % line ends with slash \
3771 -> append(LFront,[10],LFront2), % insert newline instead;
3772 % note cleanup_newlines in parsercall transforms this into 8232 \x2028 Unicode
3773 append(SoFar,LFront2,NewSoFar),
3774 repl_multi_read_line_aux(Stream,'... ',NewSoFar,Line)
3775 ; append(SoFar,L,Line)).
3776
3777 :- use_module(eval_strings).
3778 :- dynamic trace_eval/0.
3779
3780 generate_atom_list([],[],R) :- !, R=[].
3781 generate_atom_list([],Last,[NewAtom]) :-
3782 reverse(Last,RL),
3783 atom_codes(NewAtom,RL).
3784 generate_atom_list([39|X],[],[QuotedAtom|T]) :- !,
3785 get_quoted_atom(X,[],QuotedAtom,Rest),
3786 strip_leading_ws(Rest,X2),
3787 generate_atom_list(X2,[],T).
3788 generate_atom_list([32|X],Last,[NewAtom|T]) :- !,
3789 reverse(Last,RL),
3790 atom_codes(NewAtom,RL),
3791 strip_leading_ws(X,X2),
3792 generate_atom_list(X2,[],T).
3793 generate_atom_list([H|X],Last,Res) :- generate_atom_list(X,[H|Last],Res).
3794
3795 get_quoted_atom([],Acc,QuotedAtom,[]) :- reverse(Acc,R), atom_codes(QuotedAtom,R).
3796 get_quoted_atom([39|T],Acc,QuotedAtom,T) :- !, reverse(Acc,R), atom_codes(QuotedAtom,R).
3797 get_quoted_atom([H|T],Acc,QuotedAtom,Rest) :- get_quoted_atom(T,[H|Acc],QuotedAtom,Rest).
3798
3799
3800 strip_leading_ws([32|X],R) :- !, strip_leading_ws(X,R).
3801 strip_leading_ws(X,X).
3802
3803 :- meta_predicate call_probcli_option(0).
3804 call_probcli_option(_:Option) :- just_assert_option(Option), !,
3805 (option(Option) -> true ; assert_option(Option)).
3806 call_probcli_option(_:statistics) :- !, % avoid calling SICS version
3807 cli_print_statistics(full).
3808 call_probcli_option(Option) :-
3809 catch(call(Option), error(existence_error(A,B),E), (
3810 treat_existence_error(A,B,E,Option),
3811 nl % ensure that next prompt is printed
3812 )).
3813
3814 % commands that require no execution; just asserting option(.)
3815 just_assert_option(depth_first).
3816 just_assert_option(breadth_first).
3817 just_assert_option(strict_raise_error).
3818 just_assert_option(no_deadlocks).
3819 just_assert_option(no_invariant_violations).
3820 just_assert_option(no_goal).
3821 just_assert_option(no_ltl).
3822 just_assert_option(no_assertion_violations).
3823 just_assert_option(no_state_errors).
3824 just_assert_option(no_counter_examples).
3825
3826 treat_existence_error(source_sink,File,E,Option) :- !,
3827 format_with_colour_nl(user_error,[red],
3828 '* Could not find file ~w~n* for probcli command ~w~n* Detailed error: ~w',[File,Option,E]).
3829 treat_existence_error(_,_,E,Option) :-
3830 format_with_colour_nl(user_error,[red],
3831 '* probcli command not yet supported in REPL: ~w~n* Error: ~w',[Option,E]).
3832
3833 reload_mainfile :-
3834 file_loaded(_,MainFile),
3835 reset_errors,
3836 print_repl_prompt_s('Reloading and initialising file: '), print_repl_prompt_s(MainFile),nl,
3837 clear_loaded_files,
3838 load_main_file(MainFile,0,_),
3839 get_errors,
3840 cli_start_animation(0),
3841 cli_start_initialisation(0).
3842
3843 % REPL EVAL LOOP:
3844 eval_probcli_repl_line(end_of_file) :- !, eval_line(end_of_file).
3845 eval_probcli_repl_line(Line) :- strip_ws(Line,SLine),
3846 catch(eval_line(SLine), E, (
3847 E=halt(_) -> throw(E) % e.g., coming from :quit; will be caught above
3848 ; E='$aborted' -> throw(E) % thrown by SWI-Prolog on abort by user
3849 ; add_error(repl,'Uncaught Exception in REPL: ',E),
3850 nl % ensure that next prompt is printed
3851 )).
3852
3853 % strip whitespace at end and beginning
3854 strip_ws([H|T],Res) :- is_ws(H),!, strip_ws(T,Res).
3855 strip_ws(C,Res) :- reverse(C,CR), strip_ws2(CR,SCR), reverse(SCR,Res).
3856 strip_ws2([H|T],Res) :- is_ws(H),!, strip_ws2(T,Res).
3857 strip_ws2(R,R).
3858
3859 is_ws(32).
3860
3861 :- use_module(performance_messages,[toggle_perfmessages/0]).
3862 eval_line([]) :- !, print_repl_prompt('Type :q or :quit to quit.'),nl,eval0.
3863 eval_line(end_of_file) :- !, halt_exception(0).
3864 % Haskell GHCI like syntax
3865 eval_line(":r") :- !, eval_line("--reload").
3866 eval_line(":reload") :- !, eval_line("--reload").
3867 eval_line("--reload") :- !,
3868 (reload_mainfile -> true ; get_errors,print_repl_prompt('Error(s) occured during reload (use :e to jump to first error)'),nl),
3869 eval0.
3870 % TO DO: other Haskell commands :info E :l FILE , let pattern = expression
3871 eval_line(":prefs") :- !,print_eclipse_prefs, eval0.
3872 eval_line([45|Command]) :- % -command
3873 generate_atom_list([45|Command],[],ArgV),
3874 %print(argv(ArgV)),nl,
3875 % try and parse like commands passed to probcli
3876 get_options(ArgV,recognised_cli_option,Options,[],fail),
3877 print_repl_prompt('Executing probcli command: '),print_repl_prompt(Options),nl,!,
3878 (maplist(prob_cli:call_probcli_option,Options) -> true
3879 ; print_red('Failed to execute probcli arguments'),nl),
3880 eval0.
3881 eval_line("+") :- !, add_last_expression_to_unit_tests, eval0.
3882 eval_line("$+") :- !, preferences:temporary_set_preference(expand_avl_upto,-1,CHNG),
3883 print_last_value,preferences:reset_temporary_preference(expand_avl_upto,CHNG),
3884 eval0.
3885 %eval_line("$$") :- !, print_last_expression, eval0. % now in eval_strings
3886 eval_line("$$$") :- !, % $$0 - $$9 commands to print last expression with indentation
3887 indent_print_last_expression, eval0.
3888 %eval_line("$") :- !, print_last_info, eval0. % now in eval_strings
3889 eval_line("!trace") :- !, eval_line("^").
3890 eval_line("^") :- !,
3891 (retract(trace_eval) -> print_repl_prompt('TRACING OFF'),nl
3892 ; assertz(trace_eval), print_repl_prompt('TRACING ON'),nl), eval0.
3893 eval_line("!observe") :- !, toggle_observe_evaluation.
3894 eval_line("!v") :- !, tcltk_turn_debugging_off.
3895 eval_line("!p") :- !, toggle_perfmessages.
3896 eval_line("!perf") :- !, toggle_perfmessages.
3897 eval_line("!profile") :- !, eval_line("%").
3898 eval_line("!print_profile") :- !, eval_line("%%").
3899 eval_line("%") :- !, print_repl_prompt('PROFILING : '), %spy([avl:avl_size/2]),
3900 (current_prolog_flag(profiling,on)
3901 -> set_prolog_flag(profiling,off), print('OFF') ;
3902 set_prolog_flag(profiling,on), print('ON')),
3903 nl,print_repl_prompt('USE %% to print profile info'),nl,eval0.
3904 eval_line("%%") :- !, nl,print_repl_prompt('PROLOG PROFILE INFORMATION:'), nl,
3905 catch(print_profile,
3906 error(existence_error(_,_),_),
3907 print_red('CAN ONLY BE USED WHEN RUNNING PROB FROM SOURCE')),
3908 nl,
3909 debug:timer_statistics,
3910 eval0.
3911 eval_line("!print_coverage") :- !, nl,print_repl_prompt('PROLOG COVERAGE INFORMATION:'), nl,
3912 (current_prolog_flag(source_info,on) -> true ; print_red('Only useful when current_prolog_flag(source_info,on)!'),nl),
3913 catch(print_coverage,
3914 error(existence_error(_,_),_),
3915 print_red('CAN ONLY BE USED WHEN RUNNING PROB FROM SOURCE')),
3916 nl,
3917 eval0.
3918 eval_line("!profile_reset") :- !, nl,print_repl_prompt('RESETTING PROLOG PROFILE INFORMATION'), nl,
3919 catch(profile_reset,
3920 error(existence_error(_,_),_),
3921 print_red('CAN ONLY BE USED WHEN RUNNING PROB FROM SOURCE')),
3922 eval0.
3923 eval_line("%%%") :- !, nl,print('PROFILE INFORMATION (Starting TK Viewer):'), nl,
3924 catch(
3925 (use_module(library(gauge)), gauge:view),
3926 error(existence_error(_,_),_),
3927 print_red('CAN ONLY BE USED WHEN RUNNING PROB FROM SOURCE')),
3928 nl,
3929 eval0.
3930 eval_line("!debug") :- !,
3931 print_repl_prompt('ENTERING PROLOG DEBUG MODE:'),
3932 catch(
3933 debug,
3934 error(existence_error(_,_),_),
3935 print_red('CAN ONLY BE USED WHEN RUNNING PROB FROM SOURCE')),
3936 nl,
3937 eval0.
3938 eval_line("@") :- !, get_preference(find_abort_values,OldVal),
3939 print_repl_prompt('Try more aggressively to detect ill-defined expressions: '),
3940 (OldVal=true -> Val=false ; Val=true), print(Val),nl,
3941 temporary_set_preference(find_abort_values,Val) , eval0.
3942 eval_line("!") :- !, toggle_eval_det,eval0.
3943 eval_line("!norm") :- !, toggle_normalising,eval0.
3944 eval_line(Codes) :- parse_eval_command(Codes,CommandName,Argument),!,
3945 debug_println(9,executing_eval_command(CommandName,Argument)),
3946 (exec_eval_command(CommandName,Argument) -> eval0
3947 ; format_with_colour_nl(user_error,[red,bold],'Command ~w failed',[CommandName]),
3948 eval0).
3949 eval_line(ExpressionOrPredicate) :- (trace_eval -> trace ; true),
3950 (eval_codes(ExpressionOrPredicate,exists,_,_,_,_)
3951 -> eval0
3952 ; print_red('Evaluation failed'),nl,eval0).
3953
3954 parse_eval_command([C|Rest],CommandName,Argument) :- [C]=":",
3955 eval_command(Cmd,CommandName),
3956 append(Cmd,RestArg,Rest),
3957 (RestArg = [Letter1|_] -> is_ws(Letter1) /* otherwise command name continues */ ; true),
3958 strip_ws(RestArg,Argument),
3959 (eval_command_help(CommandName,[],_), Argument = [_|_]
3960 -> format_with_colour_nl(user_error,[red],'WARNING: Command ~w does not take arguments!',[CommandName])
3961 ; eval_command_help(CommandName,[_|_],_), Argument = []
3962 -> format_with_colour_nl(user_error,[red],'WARNING: Command ~w requires arguments!',[CommandName])
3963 ; true).
3964
3965 % TO DO: some of these commands should also be made available in the Tcl/Tk Console
3966 eval_command("q",quit).
3967 eval_command("quit",quit).
3968 eval_command("halt",quit).
3969 eval_command("x",exit).
3970 eval_command("exit",exit).
3971 eval_command("f",find).
3972 eval_command("find",find).
3973 eval_command("*",apropos).
3974 eval_command("apropos",apropos).
3975 eval_command("help",help).
3976 eval_command("h",help).
3977 eval_command("?",help).
3978 eval_command("ctl",ctl). % :ctl
3979 eval_command("ctlh",ctl_starthere). % :ctlh
3980 eval_command("ltl",ltl). % :ltl
3981 eval_command("ltlh",ltl_starthere). % :ltlh
3982 eval_command("reset",reset_animator(hard)). % :reset
3983 eval_command("reset-history",reset_animator(history_only)). % :reset
3984 eval_command("statistics",statistics).
3985 eval_command("stats",statistics). % :stats
3986 eval_command("states",state_space_stats). % :states
3987 eval_command("state",show_state_info(2000)). % :state
3988 eval_command("statespace",state_space_display). % :statespace
3989 eval_command("u",unsat_core).
3990 %eval_command("core",unsat_core).
3991 eval_command("show",show_last_as_table). % :show
3992 eval_command("dot",show_last_as_dot(no_dot_viewing)). % :dot
3993 eval_command("dotty",show_last_as_dot(dotty)).
3994 eval_command("dotpdf",show_last_as_dot(dot)).
3995 eval_command("sfdp",show_last_as_dot(sfdp)).
3996 eval_command("browse",browse). % :browse
3997 eval_command("abstract_constants",check_abstract_constants). % :abstract_constants
3998 eval_command("det_check_constants",det_check_constants). % :det_check_constants
3999 eval_command("b",browse).
4000 eval_command("hbrowse",hbrowse). % :hbrowse
4001 eval_command("comp",show_components). % :comp
4002 eval_command("replay",replay_repl_file). % :replay
4003 eval_command("trim",trimcore). % :trim
4004 eval_command("src",show_source). %:src
4005 eval_command("source",show_source). %:source
4006 eval_command("origin",show_origin). %:origin
4007 eval_command("edit",edit_main_file).
4008 eval_command("e",edit_main_file). % :e
4009 eval_command("comment",comment).
4010 eval_command("machine",show_machine_info(statistics)). %:machine
4011 eval_command("machine-stats",show_machine_info(statistics)). %:machine
4012 eval_command("files",show_machine_info(files)). %:files
4013 eval_command("syntax",syntax_help). % :syntax
4014 eval_command("open",open_file). % :open
4015
4016 available_commands(SLC) :-
4017 findall(Cmd,(eval_command(Cs,_),atom_codes(Cmd,[58|Cs])), LC),
4018 sort(LC,SLC).
4019
4020 eval_command_help(exit,[],'Exit ProB').
4021 eval_command_help(find,['P'],'Find state in state-space which makes LTL atomic proposition P true; LTL Propositions: {B-Pred}, e(Op), [Op], true, false, sink').
4022 eval_command_help(ltl,['F'],'Check LTL formula F; LTL Operators: G,F,X,U,W,R,not,&,or,=>; LTL Propositions: {B-Pred}, e(Op), [Op], true, false, sink; Past-LTL Operators: Y,H,O,S,T (dual to X,G,F,U,R)').
4023 eval_command_help(ltl_starthere,['F'],'Check LTL formula F starting from current state').
4024 eval_command_help(ctl,['F'],'Check CTL formula F in all initial states; CTL Syntax: ExUy,EXx,AXx,EFx,AGx,EX[Op]x,e(Op),{B-Pred}').
4025 eval_command_help(ctl_starthere,['F'],'Check CTL formula F starting from current state').
4026 eval_command_help(browse,opt('PAT'),'Browse available constants, variables, sets and lets introduced in REPL').
4027 eval_command_help(apropos,['PAT'],'Find constant or variable whose names contains PAT').
4028 eval_command_help(hbrowse,['PAT'],'Browse machine hierarchy for all identifiers whose names contains PAT').
4029 eval_command_help(show_components,[],'Show components of PROPERTIES').
4030 eval_command_help(abstract_constants,[],'Show ABSTRACT_CONSTANTS and check if can be fully evaluated').
4031 eval_command_help(det_check_constants,[],'Check if values of CONSTANTS are forced and explain if they are').
4032 eval_command_help(show_last_as_table,[],'Show last evaluated expression in tabular form').
4033 eval_command_help(show_last_as_dot(_),['F'],'Show expression or predicate F as dot graph').
4034 eval_command_help(unsat_core,[],'Compute Unsatisfiable Core of last evaluated predicate').
4035 eval_command_help(help,opt('CMD'),'Provide help about REPL command CMD').
4036 eval_command_help(replay_repl_file,['FILE'],'Replay FILE of REPL commands').
4037 eval_command_help(reset_animator(_),[],'Reset history and statespace of animator').
4038 eval_command_help(show_source,['ID'],'Show origin and source code definition of identifier ID').
4039 eval_command_help(show_origin,['ID'],'Show origin of identifier ID and try opening in EDITOR').
4040 eval_command_help(show_machine_info(_),[],'Show statistics about loaded machine and files').
4041 eval_command_help(state_space_stats,[],'Show statistics about state space').
4042 eval_command_help(state_space_display,[],'Show complete state space transitions (could be very big !)').
4043 eval_command_help(show_state_info(_),[],'Show current state').
4044 eval_command_help(statistics,[],'Show statistics about last evaluation').
4045 % -machine_stats : cli_print_machine_info(statistics) -machine_files : cli_print_machine_info(files)
4046 eval_command_help(trim,[],'Trim memory usage of probcli (try and give memory back to the OS)').
4047 % implemented in eval_strings:
4048 eval_command_help(type,['E'],'Show type of expression E').
4049 eval_command_help(cvc4,['P'],'Solve predicate P using CVC4 solver').
4050 eval_command_help(kodkod,['P'],'Solve predicate P using SAT solver via Kodkod').
4051 eval_command_help(z3,['P'],'Solve predicate P using Z3 solver').
4052 eval_command_help('z3-free',['P'],'Solve predicate P using Z3 solver (ignoring current state)').
4053 eval_command_help('z3-file',['F'],'Solve predicate in File F using Z3 solver').
4054 eval_command_help('z3-free-file',['F'],'Solve predicate in File F using Z3 solver (ignoring current state)').
4055 eval_command_help(cdclt,['P'],'Solve predicate P using Prolog CDCL(T) solver').
4056 eval_command_help(cdclt-free,['P'],'Solve predicate P using Prolog CDCL(T) solver (ignoring current state)').
4057 eval_command_help(prob,['P'],'Solve predicate P using ProB solver (ignoring current state)').
4058 eval_command_help('prob-file',['F'],'Solve predicate in File F using ProB solver (ignoring current state)').
4059 eval_command_help(edit_main_file,opt('ID'),'Edit main file (or origin of identifier ID) using EDITOR (path_to_text_editor preference)').
4060 eval_command_help(comment,['STRING'],'provide STRING as a comment (mainly useful for :replay files)').
4061 eval_command_help(syntax_help,[],'Show a summary of the B syntax accepted by the REPL').
4062 eval_command_help(open_file,['FILE'],'Open FILE in preferred application.').
4063
4064 print_eval_command_help(Codes) :-
4065 eval_command(Codes,Cmd),
4066 eval_command_help(Cmd,Args,Descr),
4067 (Args = []
4068 -> format('Command ~w~n Syntax :~s~n ~w~n',[Cmd,Codes,Descr])
4069 ; Args=[Arg] -> format('Command ~w~n Syntax :~s ~w~n ~w~n',[Cmd,Codes,Arg,Descr])
4070 ; Args=opt(Arg) -> format('Command ~w~n Syntax :~s [~w]~n ~w~n',[Cmd,Codes,Arg,Descr])
4071 ; format('Command ~w~n Syntax :~s ~w~n ~w~n',[Cmd,Codes,Args,Descr])).
4072
4073 :- use_module(tools_commands,[show_dot_file/1, show_pdf_file/1, gen_dot_output/4]).
4074 :- use_module(state_space,[transition/4]).
4075 exec_eval_command(quit,_) :- !, halt_exception(0).
4076 exec_eval_command(exit,_) :- !,halt.
4077 exec_eval_command(browse,CodesToMatch) :- !,
4078 (CodesToMatch=[] -> browse % maybe merge with apropos functionality
4079 ; exec_eval_command(apropos,CodesToMatch)).
4080 exec_eval_command(find,FORMULA) :-
4081 atom_codes(APF,FORMULA),cli_find_ltl_ap(APF).
4082 exec_eval_command(apropos,CodesToMatch) :- /* :* Pattern (apropos command) */
4083 browse_machine(CodesToMatch).
4084 exec_eval_command(hbrowse,CodesToMatch) :- /* :* Pattern (apropos command) */
4085 browse_all_machines(CodesToMatch).
4086 exec_eval_command(show_components,_) :-
4087 print_property_partitions.
4088 exec_eval_command(check_abstract_constants,_) :-
4089 check_abstract_constants.
4090 exec_eval_command(det_check_constants,_) :-
4091 det_check_constants.
4092 exec_eval_command(help,Arg) :-
4093 (Arg=[] -> eval_help
4094 ; print_eval_command_help(Arg) -> true
4095 ; (Arg=[58|RA],print_eval_command_help(RA)) -> true % remove : at front
4096 ; format('Cannot provide help about ~s~n',[Arg]),
4097 available_commands(LC), format('Available commands: ~w~n',[LC])
4098 ).
4099 exec_eval_command(ctl,FORMULA) :- % :ctl
4100 atom_codes(F,FORMULA),
4101 (cli_ctl_model_check(F,init,_,Status)
4102 -> (Status=false -> write_history_to_user_output([show_init,show_states]) ; true)
4103 ; print('CTL Syntax: ExUy,EXx,AXx,EFx,AGx,EX[Op]x,e(Op),{B-Pred}'),nl).
4104 exec_eval_command(ctl_starthere,FORMULA) :- % :ctlh for ctl here
4105 atom_codes(F,FORMULA),
4106 (cli_ctl_model_check(F,starthere,_,Status)
4107 -> (Status=false -> write_history_to_user_output([show_init,show_states]) ; true)
4108 ; print('CTL Syntax: ExUy,EXx,AXx,EFx,AGx,EX[Op]x,e(Op),{B-Pred}'),nl).
4109 exec_eval_command(ltl,FORMULA) :- % :ltl
4110 atom_codes(F,FORMULA),
4111 (cli_ltl_model_check(F,init,_,Status)
4112 -> (Status=no -> write_history_to_user_output([show_init,show_states]) ; true)
4113 ; print('LTL Operators: G,F,X,U,W,R,not,&,or,=>,<=>'),nl,
4114 print('LTL Propositions: {B-Pred}, e(Op), [Op], true, false, sink'),nl,
4115 print('Past-LTL Operators: Y,H,O,S,T (dual to X,G,F,U,R)'),nl
4116 ).
4117 exec_eval_command(ltl_starthere,FORMULA) :- % :ltl
4118 atom_codes(F,FORMULA),
4119 (cli_ltl_model_check(F,starthere,_,Status)
4120 -> (Status=no -> write_history_to_user_output([show_init,show_states]) ; true)
4121 ; print('LTL Operators: G,F,X,U,W,R,not,&,or,=>,<=>'),nl,
4122 print('LTL Propositions: {B-Pred}, e(Op), [Op], true, false, sink'),nl,
4123 print('Past-LTL Operators: Y,H,O,S,T (dual to X,G,F,U,R)'),nl
4124 ).
4125 exec_eval_command(reset_animator(Hard),_) :- !,
4126 get_state_space_stats(TotalNodeSum,TotalTransSum,_,_),
4127 (Hard=hard ->
4128 format('Resetting statespace (~w states, ~w transitions)~n',[TotalNodeSum,TotalTransSum]),
4129 reset_animator
4130 ; format('Resetting animation history (keeping statespace: ~w states, ~w transitions)~n',[TotalNodeSum,TotalTransSum]),
4131 tcltk_reset % only resets animation history,...
4132 ).
4133 exec_eval_command(statistics,_) :- !, print_last_info.
4134 exec_eval_command(state_space_stats,_) :- !, % :states
4135 get_state_space_stats(TotalNodeSum,TotalTransSum,Processed,Ignored),
4136 (Ignored>0
4137 -> format('Statespace: ~w states (~w processed, ~w ignored) and ~w transitions.~n',
4138 [TotalNodeSum,Processed,Ignored,TotalTransSum])
4139 ; format('Statespace: ~w states (~w processed) and ~w transitions.~n',[TotalNodeSum,Processed,TotalTransSum])).
4140 exec_eval_command(state_space_display,_) :- !, % :statespace
4141 ( visited_expression(ID,State),
4142 functor(State,F,N),
4143 format('State ID ~w (~w/~w)~n',[ID,F,N]),
4144 transition(ID,OperationTerm,_OpID,ToID),
4145 functor(OperationTerm,F2,N2),
4146 format(' -> ~w (~w/~w)~n',[ToID,F2,N2]),
4147 fail
4148 ;
4149 current_state_id(ID),
4150 format('Current State ID ~w~n',[ID])
4151 ).
4152 exec_eval_command(show_state_info(Limit),_) :- !, % :state
4153 current_expression(ID,CurState),
4154 expand_const_and_vars_to_full_store(CurState,EState),
4155 format('Current state id ~w : ~n',[ID]), % MAX_DISPLAY_SET
4156 translate:print_bstate_limited(EState,Limit,-1),nl.
4157 exec_eval_command(unsat_core,_) :- !, % :core :u
4158 unsat_core_last_expression.
4159 exec_eval_command(trimcore,_) :- !, % :trim
4160 prob_trimcore_verbose.
4161 exec_eval_command(show_last_as_table,_) :- !, % :show
4162 show_last_expression_as_table.
4163 exec_eval_command(syntax_help,_) :- !, % :syntax
4164 syntax_help.
4165 exec_eval_command(show_last_as_dot(Show),Arg) :- !,
4166 (Arg = [] -> print('*** :dot requires an expression or predicate as argument.'),nl
4167 ; safe_absolute_file_name('~/probcli_repl.dot',AFile),
4168 set_eval_dot_file(AFile),
4169 format('Displaying evaluation result in: ~w~n',[AFile]),
4170 (eval_codes(Arg,exists,_,_,_,_) -> true ; true), unset_eval_dot_file,
4171 ( Show=no_dot_viewing -> true
4172 ; Show=dotty -> show_dot_file(AFile)
4173 ; safe_absolute_file_name('~/probcli_repl.pdf',PDFFile),
4174 gen_dot_output(AFile,Show,pdf,PDFFile),
4175 show_pdf_file(PDFFile)
4176 )).
4177 exec_eval_command(replay_repl_file,FILEC) :- !, % :replay
4178 atom_codes(File,FILEC),
4179 set_repl_input_file(not_verbose,File).
4180 exec_eval_command(show_source,IDC) :- !, % :src
4181 atom_codes(ID,IDC),
4182 show_source(ID).
4183 exec_eval_command(show_origin,IDC) :- !, % :origin
4184 atom_codes(ID,IDC),
4185 show_origin(ID).
4186 exec_eval_command(show_machine_info(X),_) :- !, % :machine
4187 cli_print_machine_info(X).
4188 exec_eval_command(edit_main_file,Arg) :- !, % :e
4189 (Arg=[] -> edit_main_file
4190 ; trim_quotes(Arg,FC), atom_codes(File,FC), file_exists(File) -> edit_file(File,unknown)
4191 ; exec_eval_command(show_origin,Arg)).
4192 exec_eval_command(open_file,FILEC) :- !, % :open
4193 (FILEC=[] -> open_file('.')
4194 ; atom_codes(File,FILEC),
4195 open_file(File)
4196 ).
4197 exec_eval_command(comment,_Arg) :- !. % do nothing; argument was a comment; mainly useful for :replay files
4198
4199 trim_quotes([34|T],Res) :- append(Res,[34],T),!. % double quotes
4200 trim_quotes([39|T],Res) :- append(Res,[39],T),!. % single quotes
4201 trim_quotes(R,R).
4202
4203 :- use_module(tools_commands,[edit_file/2, open_file/1]).
4204 edit_main_file :- last_repl_error(File,Line),
4205 \+ functor(File,unknown,_), % File \= unknown(_),
4206 !,
4207 format('Showing first error from last command~n',[]),
4208 edit_file(File,Line).
4209 % Note: for the bbedit command we can also specify line numbers bbedit +LINE FILE
4210 edit_main_file :- file_loaded(_,MainFile), \+ empty_machine_loaded,
4211 !,edit_file(MainFile,unknown).
4212 edit_main_file :- format_with_colour_nl(user_error,[red],'No file loaded, cannot open EDITOR!',[]).
4213
4214
4215
4216 :- use_module(probsrc(error_manager),[extract_file_line_col/6]).
4217 open_file_at_position(OriginTerm) :-
4218 extract_file_line_col(OriginTerm,FILE,LINE,_COL,_Erow,_Ecol),
4219 edit_file(FILE,LINE).
4220
4221
4222 :- use_module(probsrc(bmachine),[source_code_for_identifier/6]).
4223 show_source(ID) :- source_code_for_identifier(ID,Kind,_Type,OriginStr,OriginTerm,Source),!,
4224 translate:translate_subst_or_bexpr(Source,PPS),
4225 %format('~w: ~w (Type: ~w)~norigin: ~w~nsource: ~w~n',[Kind,ID,_Type,Origin,PPS]).
4226 format('~w: ~w~norigin: ~w~nsource: ~w~n',[Kind,ID,OriginStr,PPS]),
4227 (OriginTerm=b(_,_,_),get_texpr_description(OriginTerm,Description)
4228 -> format('description: ~w~n',[Description]) ; true).
4229 show_source(ID) :- format_error_with_nl('! Could not find source for ~w',[ID]).
4230
4231 show_origin('') :- last_repl_error(_,_),!, % error occured: show error in editor like :e would
4232 edit_main_file.
4233 show_origin('') :- !,format_error_with_nl('! You need to provided an identifier',[]).
4234 show_origin(ID) :- source_code_for_identifier(ID,Kind,_Type,OriginStr,OriginTerm,_Source),!,
4235 format('~w: ~w~norigin: ~w~n',[Kind,ID,OriginStr]),
4236 open_file_at_position(OriginTerm).
4237 show_origin(ID) :- format_error_with_nl('! Could not find origin for ~w',[ID]).
4238
4239 profiling_on :- set_prolog_flag(profiling,on), print('% PROFILING ON'),nl.
4240
4241 % find a state satisfying LTL atomic property
4242 cli_find_ltl_ap(APF) :-
4243 if(ltl:find_atomic_property_formula(APF,ID),
4244 (format('Found state (id = ~w) satisfying LTL atomic property.~n',[ID]),
4245 tcltk_goto_state('LTL FIND',ID)),
4246 format('No explored state satsifies LTL atomic property.~n',[])).
4247
4248 eval_help :-
4249 print('ProB Interactive Expression and Predicate Evaluator '), nl,
4250 print('Type a valid B expressions or predicates, followed by RETURN or ENTER.'),nl,
4251 print('You can spread input over multiple lines by ending lines with "\\".'),nl,
4252 browse_machine([]),
4253 print('You can also type one of the following commands: '),nl,
4254 (option_verbose ->
4255 print(' + to save last expression to ProB unit tests.'),nl,
4256 print(' ! to go to deterministic propagation only mode.'),nl,
4257 print(' $ to print evaluation time for last expression.'),nl,
4258 print(' $$ to pretty-print last expression and its type.'),nl,
4259 print(' $$$ to pretty-print last expression in nested fashion.'),nl,
4260 print(' !p to toggle performance messages.'),nl,
4261 print(' !norm to toggle normalisation of results.'),nl,
4262 print(' :col to toggle colorizing of results.'),nl
4263 ; true),
4264 print(' :let x = E to define a new local variable x'),nl, % : optional for let
4265 print(' :b or :b Prefix to browse the available identifiers'),nl,
4266 print(' :t E to get the type of an expression and :r to reload the machine'),nl,
4267 print(' :show to display the last result as a table (if possible)'),nl,
4268 print(' :list CAT to display information with CAT : {files,variables,help,...}'),nl,
4269 print(' :* P to display constants/variables containing pattern P'),nl,
4270 print(' :core Pred to compute the unsat core for Pred'),nl,
4271 print(' :u to compute the unsat core for last evaulated result'),nl,
4272 print(' :stats to print the type and evaluation time for last query'),nl,
4273 print(' -PROBCLIARGS to pass command-line probcli arguments to the REPL'),nl,
4274 print(' :ctl F or :ltl F to check a CTL or LTL formula.'),nl,
4275 print(' :f F to find a state satisfying LTL atomic property.'),nl,
4276 print(' :exec S to execute an operation or substitution S.'),nl,
4277 print(' :replay FILE to replay a file of commands.'),nl,
4278 print(' :z3 P, :cvc4 P, :kodkod P to solve predicate P using alternate solver'),nl,
4279 print(' :forall P to prove predicate P as universally quantified with default solver'),nl,
4280 (option_verbose ->
4281 print(' :krt P, :pp P, :ml P to prove predicate P using Atelier-B provers if installed'),nl
4282 ; true),
4283 print(' :print P to pretty print predicate in a nested fashion'),nl,
4284 print(' :min P, :max P to find a minimal/maximal model for predicate P or %x.(P|E)'),nl,
4285 print(' :prefs to print current value of preferences'),nl,
4286 print(' :reset to reset the state space of the animator.'),nl, % :reset-history only resets history
4287 print(' :help CMD to obtain more help about a command.'),nl,
4288 print(' :state, :statespace, :states,'),nl,
4289 print(' :machine, :files, :source, :orgin,'),nl,
4290 print(' :dot, :dotty, :sfdp, :trim, :comp - use :help CMD for more info'),nl,
4291 print(' :syntax to show a summary of the B syntax accepted by the REPL'),nl,
4292 print(' :q to exit.'),nl.
4293
4294 :- use_module(tools,[read_atom_from_file/3]).
4295 :- dynamic prob_summary/1.
4296
4297 :- read_atom_from_file(tclsrc('prob_summary.txt'),utf8,T), assertz(prob_summary(T)).
4298 % TODO: we could just include a shorter version with predicates and expressions
4299 % TODO: provide :syntax LTL or :syntax CTL help commands
4300 syntax_help :- prob_summary(S),
4301 format(user_output,'~w',S).
4302
4303
4304 browse :- browse_machine([]), browse_repl_lets.
4305
4306 :- use_module(bmachine,[get_machine_identifiers/2]).
4307 % the CodesToMatch parameters mimics the apropos command of the Clojure-REPL
4308 browse_machine(CodesToMatch) :-
4309 get_machine_identifiers(machines,MN), display_match('MACHINES',CodesToMatch,MN),
4310 (CodesToMatch =[] -> print_sets
4311 ; get_machine_identifiers(sets,SN), display_match('SETS',CodesToMatch,SN),
4312 get_machine_identifiers(set_constants,SCN), display_match('SETS-ELEMENTS',CodesToMatch,SCN)
4313 ),
4314 get_machine_identifiers(definition_files,DFN),
4315 (DFN=[] -> true ; display_match('DEFINITIONS FILES',CodesToMatch,DFN)),
4316 get_machine_identifiers(definitions,DN),
4317 (DN=[] -> true ; display_match('DEFINITIONS',CodesToMatch,DN)),
4318 get_machine_identifiers(constants,CN),
4319 display_match('CONSTANTS',CodesToMatch,CN),
4320 get_machine_identifiers(variables,VN),
4321 display_match('VARIABLES',CodesToMatch,VN),
4322 get_machine_identifiers(operations,Ops),
4323 display_match('OPERATIONS',CodesToMatch,Ops).
4324
4325 display_match(KIND,CodesToMatch,Ids) :- display_match(KIND,CodesToMatch,Ids,show_empty).
4326 display_match(KIND,CodesToMatch,Ids,ShowEmpty) :-
4327 include(prob_cli:atom_contains_codes(CodesToMatch),Ids,MatchingIds),
4328 length(MatchingIds,LenMIds),
4329 (LenMIds=0, ShowEmpty=show_only_if_match -> true
4330 ; sort(MatchingIds,SMatchingIds),
4331 (CodesToMatch=[]
4332 -> format(' ~w: ~w ~w~n',[KIND,LenMIds,SMatchingIds])
4333 ; length(Ids,LenIds),
4334 format('Matching ~w: ~w/~w ~w~n',[KIND,LenMIds,LenIds,SMatchingIds]))
4335 ).
4336
4337 % check if an atom contains a list of codes in its name
4338 atom_contains_codes([],_) :- !.
4339 atom_contains_codes(Codes,Name) :- atom_codes(Name,NC),
4340 append([_,Codes,_],NC).
4341
4342 :- use_module(b_global_sets,[b_global_set/1]).
4343 print_sets :- print('Available SETS: '), b_global_set(GS), print_set(GS),fail.
4344 print_sets :- nl.
4345
4346 :- use_module(probsrc(b_global_sets),[is_b_global_constant/3]).
4347 print_set(GS) :- print(GS), \+ is_b_global_constant(GS,_,_),!, print(' ').
4348 print_set(GS) :- print(' = {'), is_b_global_constant(GS,_,Cst), print(Cst), print(' '),fail.
4349 print_set(_) :- print(' } ').
4350
4351 :- use_module(b_machine_hierarchy,[get_machine_identifier_names/7]).
4352 % browse all machines, shows identifiers maybe not visible at top-level
4353 browse_all_machines(CodesToMatch) :-
4354 format('Searching machine hierarchy for identifiers matching ~s~n',[CodesToMatch]),
4355 get_machine_identifier_names(Name,Params,Sets,AVars,CVars,AConsts,CConsts),
4356 format('~nMACHINE ~w~n',[Name]),
4357 display_match('PARAMS',CodesToMatch,Params,show_only_if_match),
4358 display_match('SETS',CodesToMatch,Sets,show_only_if_match),
4359 display_match('ABSTRACT_VARIABLES',CodesToMatch,AVars,show_only_if_match),
4360 display_match('CONCRETE_VARIABLES',CodesToMatch,CVars,show_only_if_match),
4361 display_match('ABSTRACT_CONSTANTS',CodesToMatch,AConsts,show_only_if_match),
4362 display_match('CONCRETE_CONSTANTS',CodesToMatch,CConsts,show_only_if_match),
4363 fail.
4364 browse_all_machines(_).
4365
4366
4367 :- use_module(bmachine,[b_get_properties_from_machine/1]).
4368 print_property_partitions :- print('PARTITIONS OF PROPERTIES'),nl,
4369 b_get_properties_from_machine(Properties),
4370 predicate_components(Properties,Comp),
4371 length(Comp,Len), print(Len), print(' components found in PROPERTIES'),nl,
4372 nth1(Nr,Comp,component(P,Vars)),
4373 format('~n& // Component ~w/~w over identifiers ~w~n',[Nr,Len,Vars]),
4374 translate:print_bexpr(P),nl,fail.
4375 print_property_partitions :- nl, print(' ============== '),nl.
4376
4377 :- use_module(store,[lookup_value_for_existing_id/3]).
4378 :- use_module(b_machine_hierarchy,[abstract_constant/2]).
4379 check_abstract_constants :-
4380 format('Checking whether abstract constants can be expanded:~n',[]),
4381 current_expression(_ID,CurState),
4382 expand_const_and_vars_to_full_store(CurState,EState),
4383 abstract_constant(AID,_),
4384 lookup_value_for_existing_id(AID,EState,Val),
4385 get_value_type(Val,VF),
4386 format(user_output,'~n*** Evaluating ABSTRACT_CONSTANT (stored value: ~w):~n',[VF]),
4387 format_with_colour_nl(user_output,[blue],' ~w',[AID]),
4388 (debug_mode(off) -> true
4389 ; translate:translate_bvalue(Val,VS), format_with_colour_nl(user_output,[blue],' Stored value = ~w',[VS])),
4390 atom_codes(AID,C),
4391 % TO DO: provide info if value symbolic and can be expanded fully + add timing
4392 % term_size, unique in state space
4393 % this command is deprecated compared to -csv constants_analysis (i.e., tcltk_analyse_constants)
4394 eval_codes(C,exists,_,_EnumWarning,_LS,_),nl, % TO DO: call try_expand_and_convert_to_avl_with_check(Val)
4395 fail.
4396 check_abstract_constants.
4397
4398 :- use_module(probsrc(custom_explicit_sets),[is_interval_closure/3]).
4399 get_value_type(CS, Res) :- is_interval_closure(CS,_,_),!, Res = 'interval closure'.
4400 get_value_type(closure(_,_,_),Res) :- !, Res= 'symbolic closure'.
4401 get_value_type(avl_set(_), Res) :- !, Res= 'explicit AVL set'.
4402 get_value_type(Val,VF) :- functor(Val,VF,_).
4403
4404 :- use_module(b_state_model_check,[cbc_constants_det_check/1]).
4405 det_check_constants :- \+ current_state_corresponds_to_setup_constants_b_machine, !,
4406 format_with_colour_nl(user_error,[red],'This command requires to setup the constants first!',[]).
4407 det_check_constants :-
4408 current_state_id(ID),
4409 %format('Checking whether constants are forced in state ~w:~n',[ID]),
4410 cbc_constants_det_check(ID).
4411
4412 % showing relations as tables:
4413
4414 :- use_module(extrasrc(table_tools),[print_value_as_table/2]).
4415 show_last_expression_as_table :- \+ last_expression(_,_Expr),!,
4416 print_red('Please evaluate an expression or predicate first.'),nl.
4417 show_last_expression_as_table :-
4418 get_last_result_value(Expr,_,Value),
4419 print_value_as_table(Expr,Value).
4420
4421
4422 % a few definitions so that probcli commands work in REPL:
4423 :- use_module(translate,[set_unicode_mode/0, unset_unicode_mode/0, set_atelierb_mode/1, unset_atelierb_mode/0]).
4424 :- public pretty_print_internal_rep/4, pretty_print_internal_rep_to_B/1.
4425 pretty_print_internal_rep(PPFILE,MachName,TYPES,unicode) :- !,
4426 set_unicode_mode,
4427 call_cleanup(b_write_machine_representation_to_file(MachName,TYPES,PPFILE),unset_unicode_mode).
4428 pretty_print_internal_rep(PPFILE,'$auto',_TYPES,atelierb) :- animation_minor_mode(eventb),!,
4429 b_write_eventb_machine_to_classicalb_to_file(PPFILE). % old -ppB option:
4430 pretty_print_internal_rep(PPFILE,MachName,TYPES,atelierb) :- !,
4431 set_atelierb_mode(native),
4432 call_cleanup(b_write_machine_representation_to_file(MachName,TYPES,PPFILE),unset_atelierb_mode).
4433 pretty_print_internal_rep(PPFILE,MachName,TYPES,_) :- b_write_machine_representation_to_file(MachName,TYPES,PPFILE).
4434
4435 % -ppB option:
4436 pretty_print_internal_rep_to_B(PPFILE) :- b_write_eventb_machine_to_classicalb_to_file(PPFILE).
4437
4438 :- use_module(tools_printing,[tcltk_nested_read_prolog_file_as_codes/2]).
4439 % -pppl option: internal developer utility to pretty-print a Prolog file in nested fashion
4440 % can be useful to inspecting .prob AST files or .P XTL files
4441 pretty_print_prolog_file(PPFILE) :-
4442 file_loaded(_,MainFile), % TODO: check if main file is really Prolog file
4443 (loaded_main_file(Ext,_), \+( (Ext='P' ; Ext='prob' ; Ext= 'pl') )
4444 -> add_warning(probcli,'The -pppl command is designed to work with Prolog files (.P, .prob or .pl), not with: ',Ext) ; true),
4445 format('Pretty-Printing Prolog file ~w to ~w~n',[MainFile,PPFILE]),
4446 tcltk_nested_read_prolog_file_as_codes(MainFile,list(Codes)),
4447 safe_intelligent_open_file(PPFILE,write,Stream),
4448 format(Stream,'~s~n',[Codes]),
4449 close(Stream).
4450
4451
4452 % Simple Animator
4453
4454 interactive_animate_machine :-
4455 nl,print('IMPORTANT: Do not use this mode for automatic tools.'),nl,
4456 print('The output format can change arbitrarily in future versions.'),nl,
4457 print('Please terminate your input with a dot (.) and then type return.'),nl,nl,
4458 animate_machine2.
4459 animate_machine2 :-
4460 print_current_state,
4461 cli_computeOperations(Ops),
4462 length(Ops,Max),
4463 print('Enabled Operations: '),nl,
4464 print_options(Ops,1),
4465 print(' ==> '),!,
4466 read(Nr),
4467 (number(Nr),Nr>0,Nr=<Max
4468 -> cli_animateOperationNr(Nr,Ops,0)
4469 ; fail
4470 ),!,
4471 animate_machine2.
4472 animate_machine2.
4473
4474 print_current_state :- current_state_id(CurID), print('ID ==> '), print(CurID),nl,
4475 getStateValues(CurID,State),
4476 print_bindings(State),
4477 (specfile:b_or_z_mode,\+is_initialised_state(CurID)
4478 -> print_red(' Not yet initialised.'),print_mode_info, debug_println(10,state(State)) ; nl).
4479
4480 print_mode_info :- animation_mode(M), (animation_minor_mode(MM) -> true ; MM=''),
4481 format('Animation Mode = ~w [~w]~n',[M,MM]).
4482
4483 cli_computeOperations(Ops) :- option(animate_stats),!, % provide statistics about the animation
4484 nl,
4485 start_probcli_timer(Timer),
4486 tcltk_get_options(list(Ops)),
4487 stop_probcli_timer(Timer,'Time to compute operations: ').
4488 cli_computeOperations(Ops) :- tcltk_get_options(list(Ops)).
4489
4490 cli_animateOperationNr(Nr,Options,StepNr) :-
4491 (option(animate_stats)
4492 -> nth1(Nr,Options,Action),
4493 truncate_animate_action(Action,TA),
4494 (StepNr>1 -> format('performing step ~w : ~w~n',[StepNr,TA])
4495 ; format('performing ~w~n',[TA]))
4496 ; true),
4497 tcltk_perform_nr(Nr).
4498
4499 :- use_module(tools_strings,[truncate_atom/3]).
4500 % optionally truncate animation action atom for printing:
4501 truncate_animate_action(Action,TA) :-
4502 (option_verbose -> TA = Action
4503 ; \+ atom(Action) -> TA = Action
4504 ; truncate_atom(Action,100,TA)).
4505
4506 perform_random_step(StepNr) :- perform_random_step(_Ops,_Len,_RanChoice,StepNr).
4507 perform_random_step(Ops,Len,RanChoice,StepNr) :-
4508 cli_computeOperations(Ops),
4509 current_state_id(CurID), check_for_errors(CurID,StepNr),
4510 length(Ops,Len), Len>0,
4511 debug_println(20,perform_random_step(Len,StepNr)),
4512 L1 is Len+1,
4513 (do_det_checking, Len>1
4514 -> print_error('Non-deterministic step in animate or init'),
4515 print_error('State:'),
4516 print_current_state, print_error('Enabled Operations: '), print_options(Ops,1),
4517 error_occurred(det_check)
4518 ; true),
4519 random(1,L1,RanChoice),
4520 debug_println(20,random(L1,RanChoice)),
4521 cli_animateOperationNr(RanChoice,Ops,StepNr).
4522
4523 :- use_module(state_space,[visited_expression/2]).
4524 check_for_errors(CurID,StepNr) :- invariant_violated(CurID),
4525 \+ option(no_invariant_violations),
4526 get_preference(do_invariant_checking,true),
4527 ajoin(['INVARIANT VIOLATED after ',StepNr,' steps (state id ',CurID,').'],ErrMsg),
4528 format('~w~n',[ErrMsg]),
4529 visited_expression(CurID,CurState), print_state_silent(CurState),
4530 error_occurred_with_msg(invariant_violation,ErrMsg),
4531 fail.
4532 check_for_errors(CurID,_) :- get_state_errors(CurID).
4533 % TO DO: also check for assertion errors, goal, state_errors with abort
4534
4535 :- use_module(bmachine,[b_machine_has_constants_or_properties/0]).
4536 do_det_checking :- option(det_check),!.
4537 do_det_checking :- option(det_constants_check),current_state_id(root),
4538 b_or_z_mode, b_machine_has_constants_or_properties.
4539
4540 perform_random_steps(Nr,_) :- \+ number(Nr),!,
4541 print_error('Argument to animate not a number'), print_error(Nr),error_occurred(animate).
4542 perform_random_steps(Nr,_) :- Nr<0, !,
4543 print_error('Argument to animate is a negative number'), print_error(Nr),error_occurred(animate).
4544 perform_random_steps(0,_) :- !.
4545 perform_random_steps(Nr,ErrorOnDeadlock) :-
4546 (perform_random_initialisation_if_necessary(Steps) % if Nr=1 we currently will also execute the INITIALISATION ! TO DO: fix
4547 -> perform_random_steps_aux(Steps,Nr,ErrorOnDeadlock)
4548 ; % we have setup_constants_fails or initialisation_fails
4549 print_error('Could not initialise model for animation')
4550 ).
4551
4552 perform_random_steps_aux(Nr,Max,_) :- Nr >= Max,!, debug_println(9,performed_random_steps(Nr)).
4553 perform_random_steps_aux(Nr,Max,ErrorOnDeadlock) :-
4554 N1 is Nr+1,
4555 (perform_random_step(N1)
4556 -> perform_random_steps_aux(N1,Max,ErrorOnDeadlock)
4557 ; /* deadlock */
4558 write_xml_element_to_log(deadlock_found,[step/Nr]),
4559 (ErrorOnDeadlock=true, \+ option(no_deadlocks)) ->
4560 print_error('Deadlock occurred during -animate, at step number:'), print_error(Nr),
4561 error_occurred(animate)
4562 ; print('% Deadlock occurred during -animate, at step number:'), print(Nr),nl
4563 ).
4564
4565 perform_random_initialisation_if_necessary(Steps) :-
4566 b_or_z_mode, current_state_id(State), State=root,!, perform_random_initialisation(Steps).
4567 perform_random_initialisation_if_necessary(0).
4568
4569 perform_random_initialisation :- perform_random_initialisation(_).
4570 perform_random_initialisation(Steps) :- current_state_id(State), State \= root, !,
4571 print_error('init can only be used in initial state'), print_error(State),error_occurred(initialisation),
4572 Steps=0.
4573 perform_random_initialisation(Steps) :- b_mode, b_machine_has_constants_or_properties,!,
4574 (perform_random_step(Ops,_Len,RanChoice,1)
4575 -> nth1(RanChoice,Ops,Choice), %print(Choice),nl,
4576 (Choice = 'PARTIAL_SETUP_CONSTANTS'
4577 -> error_occurred(setup_constants_inconsistent)
4578 ; true)
4579 ; error_occurred(setup_constants_fails),fail), % $setup_constants TODO: properties unknown or unsat
4580 perform_random_init_after_setup_constants, Steps=2. % $initialise_machine
4581 perform_random_initialisation(Steps) :- (perform_random_step(1) -> Steps=1 ; error_occurred(initialisation_fails),fail).
4582
4583
4584 perform_random_init_after_setup_constants :- \+ option(initialise), we_need_only_static_assertions(_),!,
4585 printsilent('% NOT INITIALISING MACHINE (not required)'),nls.
4586 % debug_println(20,'% NOT INITIALISING MACHINE (not required)').
4587 perform_random_init_after_setup_constants :-
4588 (perform_random_step(2) % 2 is the step nr not the number of steps
4589 -> true
4590 ; error_occurred(initialisation_fails),
4591 fail).
4592
4593 :- use_module(cbcsrc(enabling_analysis),[tcltk_cbc_enabling_analysis/1, print_enable_table/1, is_timeout_enabling_result/1]).
4594 do_enabling_analysis_csv(EnablingCsvFile,NOW) :-
4595 start_probcli_timer(Timer1),
4596 start_xml_feature(enabling_analysis,file,EnablingCsvFile,FINFO),
4597 tcltk_cbc_enabling_analysis(list(R)),
4598 stop_probcli_timer(Timer1,'% Finished CBC Enabling Analysis',_TotWallTime),
4599 print_cbc_stats(R,NOW),
4600 debug_println(9,writing_to_file(EnablingCsvFile)),
4601 my_tell(EnablingCsvFile),
4602 print_enable_table(R),
4603 told,!,
4604 stop_xml_feature(enabling_analysis,FINFO).
4605 do_enabling_analysis_csv(EnablingCsvFile,_) :-
4606 add_error(enabling_analysis,'Enabling analysis failed',EnablingCsvFile),
4607 stop_xml_group_in_log(enabling_analysis).
4608
4609 print_cbc_stats(Res,_NOW) :- length(Res,Len), Ops is Len-2, % Header + Init
4610 CBC_Calls is Ops*(Ops+1), % +1 for INITIALISATION
4611 findall(TO,(member(list([_|T]),Res), member(TO,T),is_timeout_enabling_result(TO)),TOS),
4612 length(TOS,NrTOS),
4613 format('% CBC Enabling Stats:~n% Nr of events: ~w~n% Nr of cbc calls: ~w, Timeout results: ~w~n',[Ops,CBC_Calls,NrTOS]),
4614 write_xml_element_to_log(cbc_enabling_stats,[nr_events/Ops,cbc_calls/CBC_Calls,nr_timeouts/NrTOS]).
4615
4616
4617 :- use_module(cbcsrc(enabling_analysis),[feasible_operation_with_timeout/3]).
4618 do_feasibility_analysis(ATimeOut,EnablingCsvFile) :-
4619 arg_is_number(ATimeOut,TimeOut),
4620 start_xml_feature(feasibility_analysis,file,EnablingCsvFile,FINFO),
4621 findall(list([Op,Res]),feasible_operation_with_timeout(Op,TimeOut,Res),R),
4622 debug_println(9,writing_to_file(EnablingCsvFile)),
4623 my_tell(EnablingCsvFile),
4624 print_enable_table([list(['Event','Feasibility'])|R]),
4625 told,!,
4626 stop_xml_feature(feasibility_analysis,FINFO).
4627 do_feasibility_analysis(_,EnablingCsvFile) :-
4628 add_error(feasibility_analysis,'Feasibility analysis failed',EnablingCsvFile),
4629 stop_xml_group_in_log(feasibility_analysis).
4630
4631 :- use_module(b_read_write_info,[tcltk_read_write_matrix/1]).
4632 generate_read_write_matrix(CsvFile) :-
4633 tcltk_read_write_matrix(list(Matrix)),
4634 my_tell(CsvFile),
4635 print_enable_table(Matrix),
4636 told,!.
4637 generate_read_write_matrix(CsvFile) :-
4638 add_error(read_write_matrix,'Generating Read-Write-Matrix failed',CsvFile).
4639
4640
4641 my_tell(File) :-
4642 catch(
4643 tell(File),
4644 error(_E,_), % existence_error(_,_)
4645 add_error_fail(tell,'File cannot be written to: ',File)).
4646
4647 print_options([],_).
4648 print_options([H|T],N) :-
4649 print(' '), print(N), print(':'), print(H),nl,
4650 N1 is N+1,
4651 print_options(T,N1).
4652
4653 print_nr_list(List) :- print_nr_list(List,0,1,no_repeats).
4654
4655 print_nr_list([],NM1,_,Repeats) :- !, print_repeats(NM1,Repeats).
4656 print_nr_list([H|T],_,N,repeated(H,SinceN)) :- !, N1 is N+1,
4657 print_nr_list(T,N,N1,repeated(H,SinceN)).
4658 print_nr_list([H|T],NM1,N,Repeats) :- !,
4659 print_repeats(NM1,Repeats),
4660 N1 is N+1,
4661 print_nr_list(T,N,N1,repeated(H,N)).
4662 print_nr_list(X,_,_,_) :- print('### not a list: '), print(X),nl.
4663
4664 print_repeats(N,repeated(H,N)) :- !,
4665 format(' ~w: ~w~n',[N,H]).
4666 print_repeats(N,repeated(H,Since)) :- !, Repeats is 1+N-Since,
4667 format(' ~w - ~w: ~w (~w repetitions)~n',[Since,N,H,Repeats]).
4668 print_repeats(_,_).
4669
4670 print_bindings([]) :- !.
4671 print_bindings([binding(Var,_,PPV)|T]) :- !, print(Var),print('='),print(PPV),
4672 (T=[] -> true ; print(', '), print_bindings(T)).
4673 print_bindings([binding(Var,_,PPV,_Tag)|T]) :- !, print(Var),print('='),print(PPV),
4674 (T=[] -> true ; print(', '), print_bindings(T)).
4675 print_bindings(X) :- print('### Internal Error: illegal binding list: '), print(X),nl.
4676
4677 :- dynamic expected_error_occurred/1.
4678 :- dynamic error_did_not_occur/1.
4679 reset_expected_error_occurred :- retractall(expected_error_occurred(_)).
4680 check_all_expected_errors_occurred(NOW) :-
4681 %error_manager:display_error_statistics,
4682 get_errors, get_state_space_errors,
4683 retractall(error_did_not_occur(_)),
4684 expected_error(Type),
4685 \+ expected_error_occurred(Type),
4686 print('*** Expected Error of following type to occur: '), print(Type),nl,
4687 writeln_log_time(expected_error_did_not_occur(NOW,Type)),
4688 assertz(error_did_not_occur(Type)),
4689 (option(strict_raise_error) -> definite_error_occurred ; fail).
4690 check_all_expected_errors_occurred(_NOW) :-
4691 (expected_error(_)
4692 -> (error_did_not_occur(_) -> print('*** Some expected errors did NOT occur !')
4693 ; print('All expected errors occurred.')),nl
4694 ; true).
4695
4696 expected_error(Type) :- option(expect_error(Type)).
4697 expected_error(Type) :- option(expect_error_pos(Type,_Line,_Col)).
4698
4699 error_occurred(warning(Type)) :- !, error_occurred(Type,warning).
4700 error_occurred(Type) :- error_occurred(Type,error).
4701
4702 get_error_category_and_type(warning(Cat),Category,Type) :- !, Category=Cat,Type=warning.
4703 get_error_category_and_type(C,C,error).
4704
4705 error_occurred_with_msg(Type,Msg) :- error_occurred_with_msg(Type,Msg,not_yet_extracted).
4706 error_occurred_with_msg(warning(Type),Msg,Span) :- !, error_occurred(Type,warning,Span,Msg).
4707 error_occurred_with_msg(Type,Msg,Span) :- error_occurred(Type,error,Span,Msg).
4708
4709 error_occurred(Type,ErrOrWarn) :- error_occurred(Type,ErrOrWarn,not_yet_extracted,'').
4710
4711 error_occurred(Type,ErrOrWarning,ExtractedSpan,Msg) :-
4712 option(expect_error_pos(Type,Line,Col)),!,
4713 write_xml_element_to_log(expected_error_occurred,[category/Type, (type)/ErrOrWarning, message/Msg]),
4714 assertz(expected_error_occurred(Type)),
4715 (get_error_or_warning_span(ExtractedSpan,Type,EL,EC)
4716 -> (option(expect_error_pos(Type,EL,EC))
4717 -> debug_println(9,expect_error_pos_ok(Type,EL,EC))
4718 ; format('*** Unexpected line ~w and column ~w for error ~w!~n*** Expected line ~w and column ~w.~n',[EL,EC,Type,Line,Col]),
4719 definite_error_occurred
4720 )
4721 ; format('*** Could not obtain position information for error ~w! Expected line ~w and column ~w.~n',[Type,Line,Col]),
4722 %display_error_statistics,
4723 definite_error_occurred).
4724 error_occurred(Type,ErrOrWarning,ExtractedSpan,Msg) :-
4725 option(expect_error(Type)),!,
4726 inc_counter(cli_expected_errors),
4727 get_xml_span(ExtractedSpan,XML),
4728 write_xml_element_to_log(expected_error_occurred,[category/Type, (type)/ErrOrWarning, message/Msg|XML]),
4729 assertz(expected_error_occurred(Type)).
4730 error_occurred(Type,ErrOrWarning,ExtractedSpan,Msg) :-
4731 (probcli_time_stamp(NOW) -> true ; NOW=unknown),
4732 writeln_log(error_occurred(NOW,Type)),
4733 get_xml_span(ExtractedSpan,XML),
4734 (option(optional_error(Type)) ->
4735 write_xml_element_to_log(optional_error_occurred,[category/Type, (type)/ErrOrWarning, message/Msg|XML]),
4736 formatsilent('% Optional error occured: ~w~n',[Type])
4737 ;
4738 write_xml_element_to_log(error_occurred,[category/Type, (type)/ErrOrWarning, message/Msg|XML]),
4739 (ErrOrWarning = warning -> safe_inc_counter(cli_warnings) ; safe_inc_counter(cli_errors)),
4740 flush_output, % ensure we can later associate position of error message
4741 (option(strict_raise_error) ->
4742 print_error('*** Unexpected error occurred ***'),
4743 print_error(Type),
4744 findall(Err,option(expect_error(Err)),Ls), (Ls=[] -> true ; print_error(expected(Ls))),
4745 definite_error_occurred
4746 ; ErrOrWarning=error,serious_error(Type)
4747 -> print_error('*** Serious error occurred ***'),
4748 print_error(Type),
4749 definite_error_occurred
4750 ; print_probcli_error_non_strict(Type,ErrOrWarning)
4751 )
4752 ).
4753
4754 safe_inc_counter(Counter) :-
4755 catch(inc_counter(Counter), E,
4756 format(user_error,'~n*** Exception in counter library, probably not yet initialized: ~w.~n~n',[E])).
4757
4758
4759 get_xml_span(Span,XML) :- extract_file_line_col(Span,FullFilename,Line,Col,EndLine,EndCol),!,
4760 XML = [file/FullFilename,start_line/Line,end_line/EndLine,start_col/Col,end_col/EndCol|XT],
4761 get_xml_add_description(Span,XT).
4762 get_xml_span(Span,XML) :- get_xml_add_description(Span,XML).
4763
4764 get_xml_add_description(Span,XML) :-
4765 extract_additional_description(Span,Msg),!,
4766 XML = [additional_description/Msg].
4767 get_xml_add_description(_,[]).
4768
4769 get_error_or_warning_span(not_yet_extracted,Type,EL,EC) :- check_error_span_file_linecol(Type,_File,EL,EC,_,_).
4770 get_error_or_warning_span(not_yet_extracted,Type,EL,EC) :- check_error_span_file_linecol(warning(Type),_File,EL,EC,_,_).
4771 get_error_or_warning_span(Span,_,EL,EC) :- Span \= not_yet_extracted, extract_line_col(Span,EL,EC,_,_).
4772
4773
4774 % a list of serious errors: if these occur; then return code different from 0 even in non-strict mode
4775 serious_error(get_java_command_path).
4776 serious_error(internal_error(_)).
4777
4778 print_probcli_error_non_strict(parse_machine_predicate_error,_) :-
4779 !. % have already been reported
4780 print_probcli_error_non_strict(Type,ErrOrWarning) :-
4781 (ErrOrWarning=warning -> print_error('*** warning occurred ***')
4782 ; print_error('*** error occurred ***')),
4783 print_error(Type).
4784
4785 definite_error_occurred :- print_error('*** Abnormal termination of probcli !'),
4786 (file_loaded(_,File) -> print_error('*** for_file'(File)) ; true),
4787 (current_probcli_command(Cmd) -> print_error('*** for_command'(Cmd)) ; true),
4788 (probcli_time_stamp(NOW) -> halt_prob(NOW,1)
4789 ; writeln_log(halt(1)),
4790 halt_exception(1)
4791 ).
4792
4793 :- dynamic current_probcli_command/1.
4794 set_current_probcli_command(X) :- retractall(current_probcli_command(_)),
4795 assertz(current_probcli_command(X)).
4796 unset_current_probcli_command :- retractall(current_probcli_command(_)).
4797
4798 halt_prob(ExitCode) :-
4799 (probcli_time_stamp(NOW) -> halt_prob(NOW,ExitCode) ; halt_prob(0,ExitCode)).
4800 halt_prob(NOW,ExitCode) :-
4801 write_xml_element_to_log(probcli_halted_prematurely,[now/NOW]),
4802 close_all_xml_groups_in_log_until('probcli-run'),
4803 stop_xml_probcli_run(NOW),
4804 halt_exception(ExitCode).
4805
4806
4807 :- dynamic accumulated_infos/3, individual_file_infos/3, merged_individual_file_infos/3.
4808 accumulate_infos(Context,Infos) :- option(benchmark_info_csv_output(_,_)), % -bench_csv
4809 file_loaded(_,File),
4810 get_additional_infos(Infos,Infos2), % additional infos if -machine_stats provided
4811 sort(Infos2,SInfos), % infos is a list of the form Info-Value
4812 debug_println(19,assert_file_infos(File,Context,SInfos)),
4813 assertz(individual_file_infos(File,Context,SInfos)), % store for later csv summary printing
4814 fail.
4815 accumulate_infos(Context,Infos) :- accumulate_infos_2(Context,Infos).
4816
4817 % useful if this is not related to a loaded file, like -eval_file:
4818 accumulate_file_infos(File,Context,Infos) :-
4819 get_additional_stats(Infos,Infos2),
4820 sort(Infos2,SInfos), % infos is a list of the form Info-Value
4821 assertz(individual_file_infos(File,Context,SInfos)).
4822
4823 % join/merge accumulated infos for multiple runs (benchmarking) for a particular context/category
4824 % currently we support this for model-checking
4825 merge_accumulated_infos(Context) :- individual_file_infos(File,Context,_),!,
4826 findall(Infos,individual_file_infos(File,Context,Infos),[Infos1|RestInfos]),
4827 merge_acc(Infos1,RestInfos,1,Result),
4828 assertz(merged_individual_file_infos(File,Context,Result)).
4829
4830 merge_acc(Cur,[],_,Cur).
4831 merge_acc(Cur,[Next|T],Nr,Res) :-
4832 N1 is Nr+1,
4833 merge_acc_infos(Cur,Next,N1,NextCur),
4834 merge_acc(NextCur,T,N1,Res).
4835
4836 % merge two accumulated infos lists
4837 merge_acc_infos([],S,_,Res) :- !, Res=S.
4838 merge_acc_infos(S,[],_,Res) :- !, Res=S.
4839 merge_acc_infos([C1|T1],[C2|T2],Nr,[Cat-ResVal|MT]) :-
4840 get_info(C1,Cat,Val1), get_info(C2,Cat,Val2),
4841 merge_value(Cat,Val1,Val2,Nr,ResVal),!,
4842 merge_acc_infos(T1,T2,Nr,MT).
4843 merge_acc_infos([C1|T1],T2,Nr,[C1|MT]) :-
4844 add_warning(merge_acc_infos,'Missing value: ',C1),
4845 merge_acc_infos(T1,T2,Nr,MT).
4846
4847 % merge individual values
4848 merge_value(Cat,Val1,_Val2,_,ResVal) :- keep_first_value(Cat),!, ResVal=Val1.
4849 merge_value(_,Val,Val,_,ResVal) :- !, ResVal=Val.
4850 merge_value(Cat,Val1,Val2,Nr,ResVal) :- compute_average(Cat),!, ResVal is (Val1*(Nr-1)/Nr) + (Val2 / Nr).
4851 merge_value(Cat,Val1,Val2,Nr,ResVal) :-
4852 add_warning(merge_value,'Differing values: ',val(Cat,Val1,Val2)),
4853 ResVal is (Val1*(Nr-1)/Nr) + (Val2 / Nr).
4854
4855 compute_average(runtime).
4856 compute_average(total_runtime).
4857 compute_average(walltime).
4858
4859 keep_first_value(memory_used). % memory consumption of the first run is relevant
4860
4861
4862 % also store additional infos if -machine_stats provided; useful for benchmarking/articles
4863 :- use_module(covsrc(hit_profiler),[retract_profile_stats/2]).
4864 get_additional_infos(I,Res) :- option(cli_print_machine_info(statistics)),!,
4865 findall(Key-Nr,b_machine_statistics(Key,Nr),I2,I),
4866 get_additional_stats(I2,Res).
4867 get_additional_infos(I,Res) :- get_additional_stats(I,Res).
4868 get_additional_stats(I,Res) :-
4869 findall(Key-Nr,retract_profile_stats(Key,Nr),Res,I). % include additional profiling stats and retract/reset them
4870
4871 accumulate_infos_2(_,[]).
4872 accumulate_infos_2(Context,[Info|T]) :- get_info(Info,FF,Nr),
4873 (number(Nr) -> Nr>0 ; add_internal_error('Can only accumulate numbers:',FF-Nr),fail), !,
4874 (retract(accumulated_infos(Context,FF,OldNr)) ->true ; OldNr=0),
4875 N1 is OldNr+Nr,
4876 assertz(accumulated_infos(Context,FF,N1)),
4877 accumulate_infos_2(Context,T).
4878 accumulate_infos_2(Context,[_|T]) :- accumulate_infos_2(Context,T).
4879 get_info(FF-Nr,FF,Nr).
4880 get_info(FF/Nr,FF,Nr).
4881
4882 :- use_module(tools_io,[safe_intelligent_open_file/3]).
4883 print_accumulated_infos(NrFilesProcessed) :-
4884 (option(benchmark_info_csv_output(File,FileMode))
4885 -> safe_intelligent_open_file(File,FileMode,Stream) % FileMode is write or append
4886 ; Stream=user_output),
4887 call_cleanup(pr_acc_infos_aux(Stream,NrFilesProcessed,FileMode),
4888 close(Stream)), !.
4889 print_accumulated_infos(NrFilesProcessed) :-
4890 add_internal_error('Call failed:',print_accumulated_infos(NrFilesProcessed)).
4891
4892 %:- use_module(library(system),[ datime/1]).
4893 pr_acc_infos_aux(Stream,NrFilesProcessed,FileMode) :-
4894 (NrFilesProcessed>1,accumulated_infos(_,_,_) -> true ; option(benchmark_info_csv_output(_,_))),!,
4895 print_individual_file_infos_csv(Stream,FileMode),
4896 start_xml_group_in_log(summary,files_processed,NrFilesProcessed),
4897 ((FileMode = append ; NrFilesProcessed = 1)
4898 -> true % do not print accumulated info line
4899 ; format(Stream,'Analysis summary (~w files processed): ',[NrFilesProcessed]),
4900 findall(Context-F-Nr,accumulated_infos(Context,F,Nr),L), sort(L,SL),
4901 maplist(prob_cli:pracc(Stream),SL),nl(Stream)
4902 ),
4903 % TO DO: write infos to XML log
4904 (option(print_version(VERSIONKIND)) ->
4905 datime(datime(Year,Month,Day,Hour,Min,_Sec)),
4906 format(Stream,'CSV file generated at ~w:~w on the date ~w/~w/~w using probcli:~n',[Hour,Min,Year,Month,Day]),
4907 print_version(VERSIONKIND,Stream),
4908 print_csv_prefs(Stream)
4909 ; true),
4910 (option(cli_print_statistics(memory)) -> print_memory_statistics(Stream) ; true),
4911 stop_xml_group_in_log_no_statistics(summary).
4912 pr_acc_infos_aux(_,_NrFilesProcessed,_Mode).
4913
4914 print_csv_prefs(Stream) :- \+ \+ option(set_preference_group(_,_)),
4915 format(Stream,'PREFERENCE GROUP,Setting~n',[]),
4916 option(set_preference_group(P,V)),
4917 format(Stream,'~w,~w~n',[P,V]),
4918 fail.
4919 print_csv_prefs(Stream) :- \+ \+ option(set_pref(_,_)),
4920 format(Stream,'PREFERENCE,Value~n',[]),
4921 option(set_pref(P,V)),
4922 format(Stream,'~w,~w~n',[P,V]),
4923 fail.
4924 print_csv_prefs(_).
4925
4926 pracc(Stream,Context-F-Nr) :- format(Stream,'~w:~w:~w ',[Context,F,Nr]).
4927 :- use_module(probsrc(tools),[gen_relative_path_to_cur_dir/2]).
4928 % print CSV summary of run
4929 print_individual_file_infos_csv(Stream,FileMode) :-
4930 findall(C,individual_file_infos(_,C,_),All), sort(All,AllContexts),
4931 member(Context,AllContexts), % iterate over all Contexts
4932 (individual_file_infos(_,Context,HInfos) -> true), % pick one as header
4933 (FileMode=append
4934 -> true % do not print header line, we append to an existing table
4935 ; format(Stream,'~nFILE,ANALYSIS,',[]),
4936 print_titles(HInfos,Stream),nl(Stream)
4937 ),
4938 % TO DO: ensure Infos and SHInfos identical, else add 0 for missing categories
4939 (merged_individual_file_infos(File,Context,Infos)
4940 -> true % just print averages
4941 ; individual_file_infos(File,Context,Infos)
4942 ),
4943 gen_relative_path_to_cur_dir(File,RelFile),
4944 format(Stream,'~w,~w,',[RelFile,Context]),
4945 print_vals(Infos,HInfos,Stream),nl(Stream),
4946 fail.
4947 print_individual_file_infos_csv(_,_).
4948
4949
4950
4951 print_vals(_,[],_) :- !.
4952 print_vals([H|T],[Header|HT],Stream) :- get_info(Header,Title,_),
4953 get_info(H,Title,Nr), !,
4954 write(Stream,Nr),
4955 (T=[] -> true ; write(Stream,','), print_vals(T,HT,Stream)).
4956 print_vals(Vals,[_|HT],Stream) :- % a value is missing for this file
4957 write(Stream,'-'),
4958 (HT=[] -> true ; write(Stream,','), print_vals(Vals,HT,Stream)).
4959 print_titles([],_).
4960 print_titles([H|T],Stream) :- get_info(H,FF,_), write(Stream,FF),
4961 (T=[] -> true ; write(Stream,','), print_titles(T,Stream)).
4962
4963 write_important_xml_element_to_log(Category,Infos) :-
4964 include(prob_cli:important_info,Infos,II),
4965 write_xml_element_to_log(Category,II).
4966 important_info(FF/Nr) :-
4967 \+ irrelevant_xml_info(FF),
4968 (Nr=0 -> \+ irrelevant_xml_if_zero(FF) ; true).
4969 irrelevant_xml_info(true_after_expansion).
4970 irrelevant_xml_info(false_after_expansion).
4971 irrelevant_xml_info(unknown_after_expansion).
4972 irrelevant_xml_info(total_after_expansion).
4973 irrelevant_xml_if_zero(timeout).
4974 irrelevant_xml_if_zero(enum_warning).
4975
4976 check_required_infos([],_,_).
4977 check_required_infos([H|T],Infos,ErrType) :-
4978 (check_single_info(H,Infos)
4979 -> check_required_infos(T,Infos,ErrType)
4980 ; translate_err_type(ErrType,ES),
4981 format_with_colour_nl(user_error,[red],
4982 '*** Unexpected result while checking: ~w~n*** expected : ~w~n*** in : ~w',
4983 [ES,H,Infos]),
4984 error_occurred(ErrType)).
4985 translate_err_type(check_assertions,'ASSERTIONS') :- !.
4986 translate_err_type(cli_check_assertions,'ASSERTIONS') :- !.
4987 translate_err_type(check_goal,'GOAL') :- !.
4988 translate_err_type(load_po_file,'PROOF OBLIGATIONS') :- !.
4989 translate_err_type(cli_wd_check,'WD PROOF OBLIGATIONS') :- !.
4990 translate_err_type(X,X).
4991
4992 check_single_info(Label-Nr,Infos) :- !, member(Label-ActualNr,Infos),
4993 match_info(Nr,ActualNr).
4994 check_single_info(H,List) :- member(H,List).
4995 match_info(X,X).
4996 match_info(comparison_operator(Comp,Nr),ActualNr) :-
4997 number(Nr), number(ActualNr),call(Comp,ActualNr,Nr).
4998
4999 :- use_module(tools_platform, [max_tagged_integer/1]).
5000 :- public mc_ok_arg/2.
5001 mc_ok_arg(Arg,X) :- Arg==all,!,max_tagged_integer(X).
5002 mc_ok_arg(Arg,N) :- arg_is_number(Arg,N).
5003
5004
5005 :- dynamic option/1.
5006 assert_all_options([]).
5007 assert_all_options([Opt|T]) :- assert_option(Opt),
5008 assert_all_options(T).
5009
5010 :- use_module(pathes_extensions_db,[probcli_command_requires_extension/2]).
5011 cli_option_not_available(Opt,ProBExtension,Reason) :-
5012 probcli_command_requires_extension(Opt,ProBExtension),
5013 unavailable_extension(ProBExtension,Reason).
5014
5015 check_unavailable_options :-
5016 ? option(Opt),
5017 cli_option_not_available(Opt,ProBExtension,Reason),
5018 (recognised_option(Name,Opt,_,_) -> true ; Name=Opt),
5019 ajoin(['probcli command ', Name,' cannot be performed because extension not available (',Reason,'):'],Msg),
5020 add_error(probcli,Msg,ProBExtension),
5021 fail.
5022 check_unavailable_options.
5023
5024 assert_option(silent) :- option(force_no_silent),!. % ignoring silent flag
5025 assert_option(Opt) :- assertz(option(Opt)), treat_option(Opt).
5026
5027 :- use_module(tools_printing,[set_no_color/1, reset_no_color_to_default/0]).
5028 treat_option(silent) :- !, set_silent_mode(on),set_error_manager_silent_mode(on).
5029 treat_option(force_no_silent) :- !, set_silent_mode(off),set_error_manager_silent_mode(off).
5030 treat_option(no_color) :- !, set_no_color(true).
5031 treat_option(_).
5032
5033 reset_options :- retractall(option(_)),
5034 set_silent_mode(off), set_error_manager_silent_mode(off),
5035 reset_no_color_to_default.
5036
5037 % replace a leading double-dash -- by a single dash and replace inner dashes by underscores
5038 normalise_option_atom(X,RX) :- atom(X),!,
5039 atom_codes(X,CodesX),
5040 % remove leading dash
5041 (CodesX=[45,45,H|T], H\=45 % Double dash --Option
5042 -> maplist(prob_cli:convert_dash_to_underscore,[H|T],HT2),
5043 RXCodes=[45|HT2]
5044 ; CodesX = [Dash|T], is_dash(Dash) % single dash
5045 -> maplist(prob_cli:convert_dash_to_underscore,T,T2),
5046 RXCodes=[45|T2]
5047 ; maplist(prob_cli:convert_dash_to_underscore,CodesX,RXCodes)
5048 ),
5049 atom_codes(RX,RXCodes).
5050 normalise_option_atom(T,T).
5051
5052 is_dash(45). % regular dash
5053 is_dash(8212). % Unicode double dash; sometimes automatically generated from -- by e.g., macOS Mail program
5054
5055 :- public normalise_pref_name/2. % called via recognised_option
5056 % replace dashes by underscores
5057 normalise_pref_name(X,RX) :- atom(X),!,
5058 atom_codes(X,CodesX),
5059 maplist(prob_cli:convert_dash_to_underscore,CodesX,C2),
5060 atom_codes(RX,C2).
5061 normalise_pref_name(T,T).
5062
5063 convert_dash_to_underscore(45,R) :- !, R=95.
5064 convert_dash_to_underscore(X,X).
5065
5066 recognised_cli_option(X,Opt,Args,Condition) :- normalise_option_atom(X,RX),
5067 ? recognised_option(RX,Opt,Args,Condition).
5068
5069 % get a list of all options
5070 get_all_options(SOpts) :-
5071 findall(O, recognised_option(O,_,_,_), Opts),
5072 sort(Opts,SOpts).
5073
5074 :- use_module(tools_matching,[fuzzy_match_codes_lower_case/2]).
5075 % compute a set of possible fuzzy matches
5076 get_possible_fuzzy_match_options(Option,FuzzyMatches) :-
5077 normalise_option_atom(Option,RX),
5078 atom_codes(RX,OCodes),
5079 get_all_options(SOpts),
5080 findall(Target,(member(Target,SOpts),atom_codes(Target,TargetCodes),
5081 fuzzy_match_codes_lower_case(OCodes,TargetCodes)),FuzzyMatches).
5082
5083 :- use_module(tools_matching,[get_possible_completions_msg/3]).
5084 get_possible_options_completion_msg(Option,Msg) :-
5085 normalise_option_atom(Option,RX),
5086 get_all_options(SOpts),
5087 get_possible_completions_msg(RX,SOpts,Msg).
5088
5089 recognised_option(X,Opt,[],true) :- recognised_option(X,Opt). % options without arguments
5090 recognised_option(X,Opt,Args,true) :- recognised_option(X,Opt,Args). % options with arguments but no code needed to check arguments
5091
5092 recognised_option('-mc',cli_mc(N,[]),[Arg],prob_cli:mc_ok_arg(Arg,N)).
5093 recognised_option('-bench_model_check',cli_mc(LimitNr,[reset_state_space,repeat(Rep)]),[Arg],tools:arg_is_number(Arg,Rep)) :- max_tagged_integer(LimitNr).
5094 recognised_option('-model_check',cli_mc(LimitNr,[]),[],true) :- max_tagged_integer(LimitNr).
5095 recognised_option('-timeout',timeout(N),[Arg],tools:arg_is_number(Arg,N)). % for model checking, refinement checking and for disprover per PO
5096 recognised_option('-time_out',timeout(N),[Arg],tools:arg_is_number(Arg,N)).
5097 recognised_option('-global_time_out',timeout(N),[Arg],tools:arg_is_number(Arg,N)). % better name, to avoid conflict with -p timeout N which also works
5098 recognised_option('-s',socket(S,true),[Arg],tools:arg_is_number(Arg,S)).
5099 recognised_option('-cc',coverage(N,N2,just_check_stats),[Arg,Arg2],
5100 (arg_is_number_or_wildcard(Arg,N),arg_is_number_or_wildcard(Arg2,N2))).
5101 recognised_option('-csp_guide',add_csp_guide(File),[File],
5102 prob_cli:check_file_arg(File,'csp_guide')).
5103 recognised_option('-prologOut',csp_translate_to_file(PlFile),[PlFile],
5104 prob_cli:check_file_arg(PlFile,'prologOut')).
5105 recognised_option('-load_state',load_state(Filename),[Filename],
5106 prob_cli:check_file_arg(Filename,'load_state')).
5107 recognised_option('-refchk',refinement_check(Filename,trace,100000),[Filename],
5108 prob_cli:check_file_arg(Filename,'refchk')).
5109 recognised_option('-ref_check',refinement_check(Filename,FailuresModel,100000),[Shortcut,Filename],
5110 (prob_cli:check_file_arg(Filename,'ref_check'),
5111 prob_cli:check_failures_mode(Shortcut,FailuresModel))).
5112 recognised_option('-refinement_check',Option,Args,Code) :- recognised_option('-refchk',Option,Args,Code).
5113 recognised_option('-hash',check_statespace_hash(H,_),[Arg],tools:arg_is_number(Arg,H)).
5114 recognised_option('-hash64',check_statespace_hash(H,'64bit'),[Arg],tools:arg_is_number(Arg,H)).
5115 recognised_option('-hash32',check_statespace_hash(H,'32bit'),[Arg],tools:arg_is_number(Arg,H)).
5116 recognised_option('-check_op_cache_stats',
5117 check_op_cache([next_state_calls-H1,inv_check_calls-H2,
5118 operations_cached-H3,invariants_cached-H4]),[Arg1,Arg2,Arg3,Arg4],
5119 (tools:arg_is_number_or_wildcard(Arg1,H1), tools:arg_is_number_or_wildcard(Arg2,H2),
5120 tools:arg_is_number_or_wildcard(Arg3,H3), tools:arg_is_number_or_wildcard(Arg4,H4))).
5121 recognised_option('-ltllimit',ltl_limit(Nr),[Arg], tools:arg_is_number(Arg,Nr)).
5122 recognised_option('-ltlfile',ltl_file(Filename),[Filename],
5123 prob_cli:check_file_arg(Filename,'ltlfile')).
5124 recognised_option('-check_disprover_result',cli_check_disprover_result([true-TNr,false-FNr,unknown-UNr,failure-0]),[T,F,U],
5125 (arg_is_number_or_wildcard(T,TNr),arg_is_number_or_wildcard(F,FNr),arg_is_number_or_wildcard(U,UNr))).
5126 recognised_option('-aa',cli_check_assertions(all,[true/TNr,false/FNr,unknown/UNr]),[T,F,U],
5127 (arg_is_number_or_wildcard(T,TNr),arg_is_number_or_wildcard(F,FNr),arg_is_number_or_wildcard(U,UNr))).
5128 recognised_option('-ma',cli_check_assertions(main,[true/TNr,false/FNr,unknown/UNr]),[T,F,U],
5129 (arg_is_number_or_wildcard(T,TNr),arg_is_number_or_wildcard(F,FNr),arg_is_number_or_wildcard(U,UNr))).
5130 recognised_option('-wd',cli_wd_check(DNr,TNr),[D,T],
5131 (arg_is_number_or_wildcard(T,TNr),arg_is_number_or_wildcard(D,DNr))).
5132 recognised_option('-kodkod_comparision',kodkod_comparision(Nr),[Arg],tools:arg_is_number(Arg,Nr)).
5133 recognised_option('-kodkod_performance',kodkod_performance(File,Nr),[File,Arg],tools:arg_is_number(Arg,Nr)).
5134 recognised_option('-animate',cli_random_animate(N,true),[Steps],tools:arg_is_number(Steps,N)).
5135 recognised_option('-execute',execute(N,true,current_state(1)),[Steps],tools:arg_is_number(Steps,N)).
5136 recognised_option('-execute_repeat',execute(N,true,current_state(R)),[Steps,Rep],
5137 (tools:arg_is_number(Steps,N),tools:arg_is_number(Rep,R))).
5138 recognised_option('-execute_expect_steps',execute_expect_steps(N),[Steps],tools:arg_is_number(Steps,N)).
5139 recognised_option('-logxml_write_vars',logxml_write_ids(variables,Prefix),[Prefix],true).
5140 recognised_option('-logxml_write_ids',logxml_write_ids(all,Prefix),[Prefix],true).
5141 recognised_option('-zmq_master',zmq_master(Identifier),[Identifier], true).
5142 recognised_option('-cbc_tests', cbc_tests(Depth,EndPred,Output),[Depth,EndPred,Output],
5143 prob_cli:check_file_arg(Output,'cbc_tests')).
5144 recognised_option('-mcm_tests', mcm_tests(Depth,MaxStates,EndPred,Output),[Depth,MaxStates,EndPred,Output],
5145 prob_cli:check_file_arg(Output,'mcm_tests')).
5146 recognised_option('-test_description', test_description(File), [File],
5147 prob_cli:check_file_arg(File,'test_description')).
5148 recognised_option('-all_paths', all_deadlocking_paths(File), [File],
5149 prob_cli:check_file_arg(File,'all_paths')).
5150 recognised_option('-dot',dot_command(Category,File,default),[Category,File],
5151 prob_cli:check_file_arg(File,'dot')).
5152 recognised_option('-spdot',dot_command(state_space,File,default),[File], prob_cli:check_file_arg(File,'spdot')). % we keep this : it is shown in Wiki
5153 % recognised_option('-spmdot',dot_command(signature_merge,File,default),[File], prob_cli:check_file_arg(File,'spmdot')).
5154 % recognised_option('-spddot',dot_command(dfa_merge,File,default),[File], prob_cli:check_file_arg(File,'spddot')).
5155 % recognised_option('-sgdot',dot_command(state_as_graph,File,default),[File], prob_cli:check_file_arg(File,'sgdot')).
5156 recognised_option('-dotexpr',dot_command_for_expr(Category,Expr,File,[],default),[Category,Expr,File],
5157 prob_cli:check_file_arg(File,'dotexpr')).
5158 recognised_option('-dot_expr',Opt,Args,Call) :- recognised_option('-dotexpr',Opt,Args,Call).
5159 %recognised_option('-sgedot',dot_command_for_expr(expr_as_graph,Expr,File,[],default),[Expr,File], prob_cli:check_file_arg(File,'sgedot')).
5160 % recognised_option('-sptdot',dot_command_for_expr(transition_diagram,Expr,File,[],default),[Expr,File],prob_cli:check_file_arg(File,'sptdot')).
5161 %recognised_option('-invdot',dot_command(invariant,File,default),[File], prob_cli:check_file_arg(File,'invdot')).
5162 %recognised_option('-propdot',dot_command(properties,File,default),[File], prob_cli:check_file_arg(File,'propdot')).
5163 %recognised_option('-assdot',dot_command(assertions,File,default),[File], prob_cli:check_file_arg(File,'assdot')).
5164 %recognised_option('-deaddot',dot_command(deadlock,File,default)(File),[File], prob_cli:check_file_arg(File,'deaddot')).
5165 recognised_option('-puml',plantuml_command(Category,File),[Category,File],
5166 prob_cli:check_file_arg(File,'plantuml')).
5167 recognised_option('-pumlexpr',plantuml_command(Category,File,[Expr]),[Category,Expr,File],
5168 prob_cli:check_file_arg(File,'plantuml')).
5169 recognised_option('-puml_expr',Opt,Args,Call) :- recognised_option('-pumlexpr',Opt,Args,Call).
5170 recognised_option('-csv',csv_table_command(Category,[],[],File),[Category,File],
5171 prob_cli:check_file_arg(File,'csv')).
5172 recognised_option('-csvexpr',csv_table_command(Category,[Expr],[],File),[Category,Expr,File],
5173 prob_cli:check_file_arg(File,'csvexpr')).
5174 recognised_option('-csv_expr',Opt,Args,Call) :- recognised_option('-csvexpr',Opt,Args,Call).
5175 recognised_option('-csv_hist',Opt,Args,Call) :- recognised_option('-csvhist',Opt,Args,Call).
5176 recognised_option('-csvhist',evaluate_expression_over_history_to_csv_file(Expr,File),[Expr,File],
5177 prob_cli:check_file_arg(File,'csvhist')).
5178 %recognised_option('-get_min_max_coverage',csv_table_command(minmax_table,[],[text_output],File),[File]). % deprecated
5179 recognised_option('-min_max_coverage',csv_table_command(minmax_table,[],[text_output],File),[File],
5180 prob_cli:check_file_arg(File,'min_max_coverage')).
5181 recognised_option('-get_coverage_information',get_coverage_information(File),[File],
5182 prob_cli:check_file_arg(File,'get_coverage_information')).
5183 %recognised_option('-vc',csv_table_command(minmax_table,[],[text_output],user_output)).
5184 recognised_option('-read_write_matrix_csv',generate_read_write_matrix_csv(CsvFile),
5185 [CsvFile],
5186 prob_cli:check_file_arg(CsvFile,'read_write_matrix_csv')).
5187 recognised_option('-feasibility_analysis_csv',feasibility_analysis_csv(TimeOut,EnablingCsvFile),
5188 [TimeOut,EnablingCsvFile],
5189 prob_cli:check_file_arg(EnablingCsvFile,'feasibility_analysis_csv')).
5190 recognised_option('-l',log(Log,prolog),[Log],
5191 prob_cli:check_file_arg(Log,'l')).
5192 recognised_option('-log',log(Log,prolog),[Log],
5193 prob_cli:check_file_arg(Log,'log')).
5194 recognised_option('-logxml',log(Log,xml),[Log],
5195 prob_cli:check_file_arg(Log,'logxml')).
5196 recognised_option('-logtlc',logtlc(Log),[Log],
5197 prob_cli:check_file_arg(Log,'logtlc')).
5198 recognised_option('-pp',pretty_print_internal_rep(File,'$auto',needed,ascii),[File],
5199 prob_cli:check_file_arg(File,'pp')).
5200 recognised_option('-ppunicode',pretty_print_internal_rep(File,'$auto',needed,unicode),[File],
5201 prob_cli:check_file_arg(File,'pp')).
5202 recognised_option('-ppf',pretty_print_internal_rep(File,'$auto',all,ascii),[File],
5203 prob_cli:check_file_arg(File,'ppf')).
5204 recognised_option('-ppAB',pretty_print_internal_rep(File,'$auto',all,atelierb),[File],
5205 prob_cli:check_file_arg(File,'ppAB')).
5206 recognised_option('-pp_with_name',pretty_print_internal_rep(File,MachName,all,ascii),[MachName,File],
5207 prob_cli:check_file_arg(File,'pp_with_name')). % provide explicit machine name
5208 recognised_option('-ppB',pretty_print_internal_rep_to_B(File),[File],
5209 prob_cli:check_file_arg(File,'ppB')). % deprecated; is now superseded by ppAB for Event-B machines
5210 recognised_option('-pppl',pretty_print_prolog_file(File),[File],
5211 prob_cli:check_file_arg(File,'pppl')).
5212 recognised_option('-save_state',save_state_space(Filename),[Filename],
5213 prob_cli:check_file_arg(Filename,'save_state')). % possibly save_state_space would be a better name
5214 recognised_option('-save',save_state_for_refinement(Filename),[Filename],
5215 prob_cli:check_file_arg(Filename,'save')).
5216 recognised_option('-sptxt',print_values(Filename),[Filename],
5217 prob_cli:check_file_arg(Filename,'sptxt')).
5218 recognised_option('-sstxt',print_all_values(Dirname),[Dirname],
5219 prob_cli:check_file_arg(Dirname,'sstxt')).
5220 recognised_option('-latex',process_latex_file(In,Out),[In,Out],
5221 (prob_cli:check_file_arg(In,'latex'),prob_cli:check_file_arg(Out,'latex'))).
5222 recognised_option('-bench_csv',benchmark_info_csv_output(File,write),[File],prob_cli:check_file_arg(File,'bench_csv')).
5223 recognised_option('-bench_csv_append',benchmark_info_csv_output(File,append),[File],prob_cli:check_file_arg(File,'bench_csv')).
5224 recognised_option('-trace_replay',trace_check(Style,File,default_trace_replay),[Style,File],prob_cli:check_file_arg(File,'trace_replay')). % can be json, ..
5225 recognised_option('-det_trace_replay',trace_check(Style,File,deterministic_trace_replay),[Style,File],prob_cli:check_file_arg(File,'det_trace_replay')).
5226 recognised_option('-replay',eval_repl([File]),[File],prob_cli:check_file_arg(File,'replay')). % used to be -eval
5227 recognised_option('-state_trace',state_trace(File),[File],prob_cli:check_file_arg(File,'state_trace')).
5228 recognised_option('-typecheckertest',typechecker_test(File),[File],prob_cli:check_file_arg(File,'typecheckertest')).
5229 recognised_option('-enabling_analysis_csv',enabling_analysis_csv(EnablingCsvFile),[EnablingCsvFile],
5230 prob_cli:check_file_arg(EnablingCsvFile,'enabling_analysis_csv')).
5231 recognised_option('-dot_output',dot_analyse_output_prefix(Path),[Path],prob_cli:check_file_arg(Path,'dot_output')).
5232 recognised_option('-evaldot',evaldot(File),[File],prob_cli:check_file_arg(File,'evaldot')).
5233 recognised_option('-his',history(File),[File],prob_cli:check_file_arg(File,'his')).
5234 recognised_option('-visb_click',visb_click(SVGID),[SVGID],true).
5235 recognised_option('-visb',visb_history(JSONFile,HTMLFile,[]),[JSONFile,HTMLFile],
5236 (prob_cli:check_file_arg(JSONFile,'visb'),prob_cli:check_file_arg(HTMLFile,'visb'))).
5237 recognised_option('-visb_with_vars',
5238 visb_history(JSONFile,HTMLFile,[show_constants(all),show_sets(all),show_variables(all)]),
5239 [JSONFile,HTMLFile],
5240 (prob_cli:check_file_arg(JSONFile,'visb_with_vars'),prob_cli:check_file_arg(HTMLFile,'visb_with_vars'))).
5241 recognised_option('-bench_alloy_cmd',run_benchmark(alloy,CmdNames,AlloyFilePath),[CmdNames,AlloyFilePath],prob_cli:check_file_arg(AlloyFilePath,'bench_alloy_cmd')).
5242 recognised_option('-bench_smt_cbc_inv',run_benchmark(smt,cbc_inv,Folder),[Folder],prob_cli:check_file_arg(Folder,'bench_smt_cbc_inv')).
5243 recognised_option('-bench_smt_cbc_deadlock',run_benchmark(smt,cbc_deadlock,Folder),[Folder],prob_cli:check_file_arg(Folder,'bench_smt_cbc_deadlock')).
5244 recognised_option('-bench_smt_bmc',run_benchmark(smt,bmc,Folder),[Folder],prob_cli:check_file_arg(Folder,'bench_smt_bmc')).
5245 recognised_option('-eval_file',eval_string_or_file(file(default),F,exists,_ANY,norecheck),[F],prob_cli:check_file_arg(F,'eval_file')).
5246 recognised_option('-evalt_file',eval_string_or_file(file(default),F,exists,'TRUE',norecheck),[F],prob_cli:check_file_arg(F,'evalt_file')).
5247 recognised_option('-eval_rule_file',eval_string_or_file(file(default),F,forall,_ANY,norecheck),[F],prob_cli:check_file_arg(F,'eval_rule_file')).
5248 recognised_option('-solve_file',eval_string_or_file(file(Solver),F,exists,_ANY,norecheck),[Solver,F],prob_cli:check_file_arg(F,'eval_file')).
5249
5250 recognised_option('-zmq_assertions',zmq_assertion(Identifier),[Identifier],true).
5251 recognised_option('-zmq_worker',zmq_worker(Identifier),[Identifier], true).
5252 %recognised_option('-zmq_worker2',zmq_worker2(MasterIP, Port, ProxyID, Logfile),[MasterIP, SPort, SProxyID, Logfile],
5253 % tools:(arg_is_number(SPort,Port), arg_is_number(SProxyID, ProxyID))).
5254 recognised_option('-p',set_pref(NPREF,PREFVAL),[PREF,PREFVAL],prob_cli:normalise_pref_name(PREF,NPREF)).
5255 recognised_option('-pref',set_pref(NPREF,PREFVAL),[PREF,PREFVAL],prob_cli:normalise_pref_name(PREF,NPREF)).
5256 recognised_option('-prob_application_type',set_application_type(T),[T],true).
5257 recognised_option('-cbc_redundant_invariants',cbc_redundant_invariants(Nr),[X],tools:arg_is_number(X,Nr)).
5258 recognised_option('-expcterrpos',expect_error_pos(Type,LNr,CNr),[Type,Line,Col],
5259 (tools:arg_is_number(Line,LNr),tools:arg_is_number(Col,CNr))).
5260 recognised_option('-pref_group',set_preference_group(NGroup,Val),[Group,Val],
5261 (prob_cli:normalise_option_atom(Group,NGroup))).
5262 recognised_option('-save_all_traces_until',generate_all_traces_until(Formula,FilePrefix),
5263 [Formula,FilePrefix],
5264 true). % we could check LTL formula and FilePrefix
5265 recognised_option('-check_machine_file_sha',check_machine_file_sha(FILE,SHA1),[FILE,SHA1],
5266 prob_cli:check_file_arg(FILE,'check_machine_file_sha')).
5267 recognised_option('-sha1sum',Command,Args,Call) :-
5268 recognised_option('-check_machine_file_sha',Command,Args,Call).
5269
5270 % recognised_option/3
5271 recognised_option('-prefs',set_prefs_from_file(PREFFILE),[PREFFILE]).
5272 %recognised_option('-plugin',plugin(Plugin), [Plugin]).
5273 recognised_option('-card',set_card(SET,SCOPE),[SET,SCOPE]).
5274 recognised_option('-argv',set_argv(ARGV),[ARGV]).
5275 recognised_option('-goal',set_goal(GOAL),[GOAL]).
5276 recognised_option('-property',add_additional_property(PRED),[PRED]).
5277 recognised_option('-scope',set_searchscope(GOAL),[GOAL]).
5278 recognised_option('-searchscope',set_searchscope(GOAL),[GOAL]).
5279 recognised_option('-search_scope',set_searchscope(GOAL),[GOAL]).
5280 recognised_option('-eval',eval_string_or_file(string,E,exists,_,norecheck),[E]).
5281 recognised_option('-evalt',eval_string_or_file(string,E,exists,'TRUE',norecheck),[E]).
5282 recognised_option('-evalf',eval_string_or_file(string,E,exists,'FALSE',norecheck),[E]).
5283 recognised_option('-evalt_rc',eval_string_or_file(string,E,exists,'TRUE',recheck(ascii)),[E]).
5284 recognised_option('-evalf_rc',eval_string_or_file(string,E,exists,'FALSE',recheck(ascii)),[E]).
5285 recognised_option('-evalu',eval_string_or_file(string,E,exists,'UNKNOWN',norecheck),[E]).
5286 recognised_option('-evalnwd',eval_string_or_file(string,E,exists,'NOT-WELL-DEFINED',norecheck),[E]).
5287 recognised_option('-parsercp',parsercp(L),[L]). % deprecated
5288 recognised_option('-parserport',parserport(L),[L]).
5289 recognised_option('-expcterr',expect_error(Type),[Type]).
5290 recognised_option('-expecterr',expect_error(Type),[Type]).
5291 recognised_option('-expect',expect_error(Type),[Type]).
5292 recognised_option('-opterr',optional_error(Type),[Type]).
5293 recognised_option('-his_option',history_option(Option),[Option]). % trace_file, json, show_init, show_states
5294 recognised_option('-cache',cache_storage(D),[D]).
5295 recognised_option('-show_cache',show_cache,[]).
5296
5297 recognised_option('-MAIN',csp_main(ProcessName),[ProcessName]).
5298
5299 recognised_option('-ltlformula',ltl_formula_model_check(Formula,_),[Formula]).
5300 recognised_option('-ltlformulat',ltl_formula_model_check(Formula,true),[Formula]).
5301 recognised_option('-ltlformulaf',ltl_formula_model_check(Formula,false),[Formula]).
5302 recognised_option('-ctlformula',ctl_formula_model_check(Formula,_),[Formula]).
5303 recognised_option('-ctlformulat',ctl_formula_model_check(Formula,true),[Formula]).
5304 recognised_option('-ctlformulaf',ctl_formula_model_check(Formula,false),[Formula]).
5305
5306
5307 %recognised_option('-cspref',csp_in_situ_refinement_check(assertRef('False',val_of(AbsP1,no_loc_info_available),Type,val_of(ImplP2,no_loc_info_available),no_loc_info_available),'False'),[AbsP1,Type,ImplP2]).
5308 recognised_option('-cspref',csp_in_situ_refinement_check(AbsP1,Type,ImplP2),[AbsP1,Type,ImplP2]).
5309 % -cspref R [F= Q
5310 recognised_option('-cspdeadlock',csp_checkAssertion(Proc,Model,'deadlock free'),[Proc,Model]).
5311 % -cspdeadlock R F
5312 recognised_option('-cspdeterministic',csp_checkAssertion(Proc,Model,'deterministic'),[Proc,Model]).
5313 % -cspdeterministic R F
5314 recognised_option('-csplivelock',csp_checkAssertion(Proc,'FD','livelock free'),[Proc]).
5315 % -csplivelock R
5316 % -csp_assertion "P [F= Q"
5317 recognised_option('-csp_assertion',check_csp_assertion(Assertion),[Assertion]).
5318 recognised_option('-csp_eval', eval_csp_expression(Expr),[Expr]).
5319 recognised_option('-get_csp_assertions_as_string',csp_get_assertions,[]).
5320
5321 recognised_option('-variable_coverage',csv_table_command(variable_coverage,[],[text_output],user_output),[]).
5322 recognised_option('-vacuity_check',vacuity_check,[]).
5323 recognised_option('-wd_check',cli_wd_check(_,_),[]).
5324 recognised_option('-wd_check_all',cli_wd_check(X,X),[]).
5325 recognised_option('-well_definedness_check',cli_wd_check(_,_),[]).
5326 recognised_option('-wd_inv_proof',cli_wd_inv_proof(_,_,_),[]).
5327 recognised_option('-lint',cli_lint,[]). % extended static check (ESC, esc)
5328 recognised_option('-lint_operations',cli_lint(operations),[]).
5329 recognised_option('-lint_variables',cli_lint(variables),[]).
5330 recognised_option('-cbc',constraint_based_check(OpName),[OpName]). % cbc invariant checking
5331 recognised_option('-cbc_invariant',constraint_based_check(OpName),[OpName]).
5332 recognised_option('-cbc_deadlock',cbc_deadlock_check(true),[]).
5333 recognised_option('-cbc_assertions',cbc_assertions(true,[]),[]).
5334 recognised_option('-cbc_main_assertions',cbc_assertions(true,[main_assertions]),[]).
5335 recognised_option('-cbc_assertions_proof',cbc_assertions(false,[]),[]). % do not allow enumeration warnings
5336 recognised_option('-cbc_assertions_tautology_proof',cbc_assertions(false,[tautology_check]),[]). % do not allow enumeration warnings + disregard PROPERTIES, used for Atelier-B proof/disproof; TO DO: also call WD prover
5337 recognised_option('-cbc_assertions_tautology_proof_check',cbc_assertions(false,[tautology_check,contradiction_check]),[]).
5338 recognised_option('-cbc_option',cbc_option(OPT),[OPT]). % should be tautology_check,contradiction_check, unsat_core
5339 recognised_option('-cbc_result_file',cbc_result_file(FILE),[FILE]). % write result to FILE
5340 recognised_option('-cbc_refinement',cbc_refinement,[]).
5341 recognised_option('-cbc_deadlock_pred',cbc_deadlock_check(GoalPred),[GoalPred]).
5342 recognised_option('-cbc_sequence',cbc_sequence(OpSequence,'',single_solution),[OpSequence]).
5343 recognised_option('-cbc_sequence_all',cbc_sequence(OpSequence,'',findall),[OpSequence]).
5344 recognised_option('-cbc_sequence_with_target',cbc_sequence(OpSequence,TargetPredString,single_solution),[OpSequence,TargetPredString]).
5345 recognised_option('-cbc_sequence_with_target_all',cbc_sequence(OpSequence,TargetPredString,findall),[OpSequence,TargetPredString]).
5346 recognised_option('-comment',comment(UserComment),[UserComment]). % not processed by tool, but will be stored in log-file and used by log_analyser
5347 recognised_option('-junit',junit(Dir),[Dir]).
5348 recognised_option('-mcm_cover', mcm_cover(Event),[Event]).
5349 recognised_option('-cbc_cover', cbc_cover(Event),[Event]).
5350 recognised_option('-cbc_cover_match', cbc_cover(match_event(Event)),[Event]). % find events which have Event String occuring somewhere in name
5351 recognised_option('-cbc_cover_all', cbc_cover_all,[]). % is now default if no cbc_cover provided
5352 recognised_option('-cbc_cover_final', cbc_cover_final,[]).
5353 recognised_option('-bmc', cbc_tests(Depth,'#not_invariant',''),[Depth]).
5354 recognised_option('-bdc', cbc_tests(Depth,'#deadlock',''),[Depth]).
5355 recognised_option('-enabling_analysis',enabling_analysis_csv(user_output),[]).
5356 recognised_option('-feasibility_analysis',feasibility_analysis_csv(1000,user_output),[]).
5357 recognised_option('-read_write_matrix',generate_read_write_matrix_csv(user_output),[]).
5358 recognised_option('-scc_trace',check_scc_for_ltl_formula(LtlFormula,SCC),[LtlFormula,SCC]).
5359 recognised_option('-selfcheck_module',selfcheck(M,[]),[M]).
5360 recognised_option('-mc_mode',depth_breadth_first_mode(M),[M]). % can be mixed, hash, heuristic
5361 recognised_option('-assertion',cli_check_assertions(specific(X),[false/0,unknown/0]),[X]).
5362 recognised_option('-cbc_assertion',cbc_assertions(true,[specific(X)]),[X]). % check only a specific assertion
5363 recognised_option('-symbolic_model_check', cli_symbolic_model_check(Algorithm), [Algorithm]).
5364 recognised_option('-ltsmin2',ltsmin2(EndpointPath), [EndpointPath]).
5365 recognised_option('-ltsmin_ltl_output',ltsmin_ltl_output(Path), [Path]).
5366 recognised_option('-ltsmin_option', ltsmin_option(X),[X]).
5367 recognised_option('-machine_hash_check',cli_print_machine_info(hash(X)),[X]).
5368 recognised_option('-install',install_prob_lib(X,[]),[X]).
5369 recognised_option('-install_dry_run',install_prob_lib(X,[dryrun]),[X]).
5370
5371
5372 recognised_option('-dot_all',dot_generate_for_all_formulas). % generate dot also for true formulas
5373 recognised_option('-animate_all',cli_random_animate(2147483647,false)).
5374 recognised_option('-execute_all',execute(2147483647,false,current_state(1))).
5375 recognised_option('-execute_all_inits',execute(2147483647,false,from_all_initial_states)).
5376 recognised_option('-animate_stats',animate_stats).
5377 recognised_option('-execute_monitor',execute_monitoring).
5378 recognised_option('-check_goal',check_goal).
5379 recognised_option('-ltlassertions',ltl_assertions).
5380 recognised_option('-assertions',cli_check_assertions(all,[false/0,unknown/0])).
5381 recognised_option('-main_assertions',cli_check_assertions(main,[false/0,unknown/0])).
5382 recognised_option('-properties',cli_check_properties).
5383 recognised_option('-properties_core',cli_core_properties(_)). % variable as arg: try various algorithms in order
5384 recognised_option('-properties_core_wd',cli_core_properties(wd_prover)).
5385 recognised_option('-properties_core_z2',cli_core_properties(z3_bup(2))).
5386 recognised_option('-properties_core_z3',cli_core_properties(z3_bup(3))).
5387 recognised_option('-selfcheck',selfcheck(_,[])).
5388 recognised_option('-pacheck',pa_check). % predicate analysis for Kodkod
5389 recognised_option('-det_check',det_check). % check if animation is deterministic
5390 recognised_option('-det_constants',det_constants_check). % check if animation for setup_constants is deterministic
5391 recognised_option('-bf',breadth_first).
5392 recognised_option('-breadth',breadth_first).
5393 recognised_option('-df',depth_first).
5394 recognised_option('-depth',depth_first).
5395 recognised_option('-strict',strict_raise_error).
5396 recognised_option('-silent',silent).
5397 recognised_option('-quiet',silent).
5398 recognised_option('-q',silent).
5399 recognised_option('-force_no_silent',force_no_silent). % override provided silent flag; useful for gitlab test debugging
5400 recognised_option('-statistics',cli_print_statistics(full)).
5401 recognised_option('-stats',cli_print_statistics(full)).
5402 recognised_option('-memory_stats',cli_print_statistics(memory)).
5403 recognised_option('-memory_statistics',cli_print_statistics(memory)).
5404 recognised_option('-memory',cli_print_statistics(memory)).
5405 recognised_option('-profile_stats',cli_print_statistics(sicstus_profile)).
5406 recognised_option('-profile_statistics',cli_print_statistics(sicstus_profile)).
5407 recognised_option('-op_cache_profile',cli_print_statistics(op_cache_profile)).
5408 recognised_option('-hit_profile',cli_print_statistics(hit_profile)). % mainly for ProB developers
5409 recognised_option('-reset_profile_statistics',reset_profiler). % mainly for use in REPL
5410 recognised_option('-nodead',no_deadlocks).
5411 recognised_option('-no_deadlocks',no_deadlocks).
5412 recognised_option('-noinv',no_invariant_violations).
5413 recognised_option('-no_invariant_violations',no_invariant_violations).
5414 recognised_option('-nogoal',no_goal).
5415 recognised_option('-no_goal',no_goal).
5416 recognised_option('-noltl',no_ltl). % just used for TLC at the moment
5417 recognised_option('-noass',no_assertion_violations).
5418 recognised_option('-no_assertion_violations',no_assertion_violations).
5419 recognised_option('-no_state_errors',no_state_errors). % disable checking for general_errors and transition related state_errors
5420 recognised_option('-nocounter',no_counter_examples).
5421 recognised_option('-no_counter_examples',no_counter_examples).
5422 recognised_option('-nocolor',no_color).
5423 recognised_option('-no_color',no_color).
5424 recognised_option('-no_colour',no_color).
5425 recognised_option('-disable_time_out',set_preference_group(time_out,disable_time_out)).
5426 recognised_option('-disable_timeout',set_preference_group(time_out,disable_time_out)).
5427 %recognised_option('-POR',with_reduction).
5428 recognised_option('-i',animate).
5429 recognised_option('-repl',eval_repl([])). % used to be -eval
5430 recognised_option('-c',coverage(false)).
5431 recognised_option('-cs',coverage(just_summary)).
5432 recognised_option('-coverage',coverage(false)).
5433 recognised_option('-coverage_summary',coverage(just_summary)).
5434 recognised_option('-machine_stats',cli_print_machine_info(statistics)).
5435 recognised_option('-machine_statistics',cli_print_machine_info(statistics)).
5436 recognised_option('-machine_files',cli_print_machine_info(files(no_sha))).
5437 recognised_option('-machine_files_sha',cli_print_machine_info(files(with_sha))).
5438 recognised_option('-machine_hash',cli_print_machine_info(hash(_))).
5439 recognised_option('-check_abstract_constants',check_abstract_constants).
5440 recognised_option('-op_cache_stats',check_op_cache([])).
5441 recognised_option('-op_cache_statistics',check_op_cache([])).
5442 recognised_option('-cv',coverage(true)).
5443 recognised_option('-v',verbose).
5444 recognised_option('-vv',very_verbose).
5445 recognised_option('-verbose',verbose).
5446 recognised_option('-debug',verbose).
5447 recognised_option('-verbose_off',verbose_off). % mainly useful in REPL
5448 recognised_option('-voff',verbose_off). % mainly useful in REPL
5449 recognised_option('-very_verbose',very_verbose).
5450 recognised_option('-profiling_on',profiling_on). % Prolog profiling
5451 recognised_option('-profile',cli_print_statistics(prob_profile)). % ProB Operation profiling
5452 recognised_option('-prob_profile',cli_print_statistics(prob_profile)). % ProB Operation profiling
5453 recognised_option('-version',print_version(full)).
5454 recognised_option('-cpp_version',print_version(cpp)).
5455 recognised_option('-V',print_version(full)).
5456 recognised_option('-svers',print_version(short)).
5457 recognised_option('-short_version',print_version(short)).
5458 recognised_option('-check_lib',print_version(lib)).
5459 recognised_option('-check_java_version',check_java_version).
5460 recognised_option('-java_version',print_version(java)).
5461 recognised_option('-release_java_parser',release_java_parser).
5462 recognised_option('-fast_read_prob',fast_read_prob).
5463 recognised_option('-file_info',file_info).
5464 recognised_option('-t',default_trace_check).
5465 recognised_option('-init',initialise).
5466 recognised_option('-initialise',initialise).
5467 recognised_option('-ll',log('/tmp/prob_cli_debug.log',prolog)).
5468 recognised_option('-ss',socket(9000,true)). % standard socket 9000
5469 recognised_option('-sf',socket(_,true)). % free socket
5470 recognised_option('-local_socketserver',socket(_,true)). % do not allow remote socket connections
5471 recognised_option('-remote_socketserver',socket(_,false)). % allow remote socket connections
5472 recognised_option('-help',help).
5473 recognised_option('-h',help).
5474 recognised_option('-rc',runtimechecking).
5475 recognised_option('-test_mode',test_mode).
5476 recognised_option('-check_complete',check_complete).
5477 recognised_option('-check_complete_operation_coverage', check_complete_operation_coverage).
5478 recognised_option('-mc_with_tlc', cli_start_mc_with_tlc).
5479 recognised_option('-mc_with_lts_sym', cli_start_sym_mc_with_lts(symbolic)).
5480 recognised_option('-mc_with_lts_seq', cli_start_sym_mc_with_lts(sequential)).
5481 recognised_option('-core',disprover_options([disprover_option(unsat_core),unsat_core_algorithm/linear])).
5482 recognised_option('-export_po',disprover_options([disprover_option(export_po_as_machine(user_output))])).
5483 recognised_option('-ltsmin',ltsmin).
5484 recognised_option('-trace',prolog_trace). % enter Prolog debugger on development system after starting up ProB
5485
5486 % some utilities to be able to call the above options directly from repl:
5487 :- public silent/0, coverage/1, help/0.
5488 % predicate to set_verbose_mode
5489 verbose :- tcltk_turn_debugging_on(19).
5490 very_verbose :- tcltk_turn_debugging_on(5).
5491 verbose_off :- tcltk_turn_debugging_off.
5492 file_info :- file_loaded(true,MainFile), print_file_info(MainFile).
5493 coverage(ShowEnabledInfo) :- probcli_time_stamp(NOW), cli_show_coverage(ShowEnabledInfo,NOW).
5494
5495 silent :- (option(silent) -> true ; assert_option(silent)).
5496 help :- eval_help.
5497 dot_command(DCommand,DotFile,DotEngine) :- call_dot_command_with_engine(DCommand,DotFile,[],DotEngine).
5498 dot_command_for_expr(DECommand,Expr,DotFile,Opts,DotEngine) :-
5499 call_dot_command_with_engine_for_expr(DECommand,Expr,DotFile,Opts,DotEngine).
5500
5501 plantuml_command(PCommand,UmlFile) :- call_plantuml_command(PCommand,UmlFile).
5502 plantuml_command_for_expr(PECommand,Expr,UmlFile,Opts) :-
5503 call_plantuml_command_for_expr(PECommand,Expr,UmlFile,Opts).
5504
5505 :- use_module(tools_io,[safe_intelligent_open_file/3]).
5506 csv_table_command(TCommand,Formulas,Options,CSVFile) :-
5507 append(Formulas,[TableResult],ActualArgs),
5508 OptionalArgs=[],
5509 format_with_colour_nl(user_output,[blue],'Calling table command ~w',[TCommand]),
5510 call_command(table,TCommand,_,ActualArgs,OptionalArgs),
5511 write_table_to_csv_file(CSVFile,Options,TableResult),
5512 format_with_colour_nl(user_output,[blue],'Finished exporting ~w to ~w',[TCommand,CSVFile]).
5513
5514
5515 save_state_space(StateFile) :- debug_println(20,'% Saving state space to file'),
5516 state_space:tcltk_save_state_space(StateFile).
5517 :- public load_state/1. % for REPL
5518 load_state(StateFile) :- debug_println(20,'% Loading state space from file'),
5519 state_space:tcltk_load_state(StateFile).
5520 :- public execute/3. % for REPL
5521 execute(ESteps,ErrOnDeadlock,From) :- cli_execute(ESteps,ErrOnDeadlock,From).
5522
5523 option_verbose :- (option(verbose) -> true ; option(very_verbose)).
5524
5525
5526 set_random_seed_to_deterministic_start_seed :-
5527 % in test_mode we do not change the random number generator's initial seed
5528 true. %getrand(CurrState),setrand(CurrState). % this seems to be a no-op
5529
5530 :- if(predicate_property(set_random(_), _)).
5531 % SWI-Prolog's native API for reinitializing the RNG state.
5532 % The equivalent of this call is also performed automatically by SWI
5533 % when a random number is requested for the first time.
5534 set_new_random_seed :- set_random(seed(random)).
5535 :- else.
5536 % SICStus way of (re)initializing the RNG state.
5537 % Note that on SICStus, the initial RNG state after startup is always the same,
5538 % so it *must* be manually reinitialized like this to get actually random results!
5539 %:- use_module(library(random),[setrand/1]).
5540 set_new_random_seed :-
5541 now(TimeStamp), % getting the unix time
5542 setrand(TimeStamp). % setting new random seed by every execution of probcli
5543 :- endif.
5544
5545 halt_exception :- halt_exception(0).
5546 halt_exception(Code) :- throw(halt(Code)).
5547
5548 % -----------------
5549
5550 start_xml_feature(FeatureName,[CErrs1,CWarns1,CEErrs1]) :-
5551 debug_format(20,'% Starting ~w~n',[FeatureName]),
5552 get_counter(cli_errors,CErrs1), get_counter(cli_warnings,CWarns1), get_counter(cli_expected_errors,CEErrs1),
5553 start_xml_group_in_log(FeatureName).
5554
5555 start_xml_feature(FeatureName,Attr,Value,[CErrs1,CWarns1,CEErrs1]) :-
5556 debug_format(20,'% Starting ~w (~w=~w)~n',[FeatureName,Attr,Value]),
5557 get_counter(cli_errors,CErrs1), get_counter(cli_warnings,CWarns1), get_counter(cli_expected_errors,CEErrs1),
5558 start_xml_group_in_log(FeatureName,Attr,Value).
5559
5560 stop_xml_feature(FeatureName,[CErrs1,CWarns1,CEErrs1]) :-
5561 get_counter(cli_errors,CErrs2), get_counter(cli_warnings,CWarns2), get_counter(cli_expected_errors,CEErrs2),
5562 CErrs is CErrs2-CErrs1, CWarns is CWarns2-CWarns1, CEErrs is CEErrs2-CEErrs1,
5563 (CEErrs>0
5564 -> write_xml_element_to_log('probcli-errors',[errors/CErrs,warnings/CWarns,expected_errors/CEErrs])
5565 ; write_xml_element_to_log('probcli-errors',[errors/CErrs,warnings/CWarns])
5566 ),
5567 debug_format(20,'% Finished ~w (errors=~w, warnings=~w, expected_errors=~w)~n',[FeatureName,CErrs,CWarns,CEErrs]),
5568 stop_xml_group_in_log(FeatureName),
5569 !.
5570 stop_xml_feature(FeatureName,L) :-
5571 add_internal_error('Illegal or failed call:',stop_xml_feature(FeatureName,L)).
5572
5573 %(CErrs>0 -> (file_loaded(_,MainFile) -> true ; MainFile=unknown), Time=unknown, % TO DO: determine time
5574 % create_and_print_junit_result(['Feature',MainFile], FeatureName, Time, error) ; true).
5575 % Note: call stop_xml_group_in_log if the feature stops unexpectedly and you do not have the Info list available
5576
5577 % -----------------
5578
5579 :- public user:runtime_entry/1.
5580 user:runtime_entry(start) :- go_cli.
5581
5582 %save :- save_program('probcli.sav').
5583
5584 :- use_module(eventhandling,[announce_event/1]).
5585 :- announce_event(compile_prob).