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