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