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