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