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