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