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