1 % (c) 2009-2019 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 %:- prolog_flag(source_info,_,on). % comment in if you want source location, e.g., for exceptions,...
6
7 portray_message(informational, _).
8
9 % patch for SICStus 4.3.3 performance issue
10 % sprm_14972_patch.pl BEGIN
11 :- if((current_prolog_flag(dialect, sicstus),
12 current_prolog_flag(version_data, sicstus(4,3,3,_,_)))).
13 prolog:wf_call_like_arg(A, B, C, D, E, F, G, H, I, _) :-
14 prolog:wellformed_body_iso(A, B, C, D, E, F, G, H, I, quiet),
15 !.
16 prolog:wf_call_like_arg(A, B, C, A, D, _, E, _, _, _) :-
17 F=E:A,
18 prolog:condense_layout(B, G),
19 prolog:comp_layout2(B, G, B, H),
20 C=call(F),
21 prolog:comp_layout1(B, H, D).
22 :- endif.
23 % sprm_14972_patch.pl END
24
25 %% sp_4_1_3_nested_exception_patch.pl BEGIN
26 %% Compile this to patch a bug in 4.1.3 affecting nested exception handlers.
27 %% This source code is a no-op on other versions of sicstus than 4.1.3.
28 :- if(current_prolog_flag(dialect,sicstus)).
29 :- if(current_prolog_flag(version_data,sicstus(4,1,3,0,_))).
30
31 prolog:(matching_exception(internal, Ball, Templ) :- !,
32 Templ = Ball).
33 prolog:(matching_exception(prolog, '$reserved'(_), _) :- !,
34 fail).
35 prolog:(matching_exception(prolog, time_out, _) :- !,
36 fail).
37 prolog:(matching_exception(_, Ball, Template) :-
38 compound(Ball),
39 sysball_iso_equiv(Ball,Iso1Exc), !,
40 Template = error(Iso1Exc, Ball)).
41 prolog:(matching_exception(_, Ball, Ball)).
42
43 :- endif. % sicstus 4.1.3
44 :- endif. % sicstus
45 %% sp_4_1_3_nested_exception_patch.pl END
46
47 %:- include('self_check_off.pl').
48
49 % use module_info/3 because we are not in a module here
50 :- use_module(module_information).
51 :- module_info(prob_cli,group,infrastructure).
52 :- module_info(prob_cli,description,'ProB start file in cli mode.').
53
54 :- use_module(debugging_calls).
55 :- register_debugging_call pp_mnf(*), pp_cll(*), mnf(*), mnf(-,*), det_call(*).
56 :- disable_debugging_calls.
57
58 :- use_module(prob_startup, [startup_prob/0]).
59 %:- use_module(pathes,[set_search_pathes/0]). % called first to set_compile_time_search_pathes
60 :- use_module(tools,[string_concatenate/3,arg_is_number/2]).
61 :- use_module(tools_printing,[print_error/1]).
62
63
64 % :- use_module(extension('timer/assert_profiler.pl')).
65
66
67 :- compile(tcltk_interface).
68 %:- compile(gui_tcltk).
69
70 :- use_module(eclipse_interface).
71 :- use_module(prob2_interface,[start_animation/0, is_initialised_state/1,
72 set_eclipse_preference/2, update_preferences_from_spec/1,
73 load_cspm_spec_from_cspm_file/1]).
74
75
76 :- use_module(prob_socketserver).
77
78 :- use_module(coverage_statistics,[compute_the_coverage/5]).
79 :- use_module(value_persistance, [set_storage_directory/1,unset_storage_directory/0]).
80
81 do_one_gui_event.
82 tk_do_all_events.
83
84 :- dynamic junit_mode/1.
85
86 :- use_module(b_trace_checking,[check_default_trace_for_specfile/1, tcltk_check_state_sequence_from_file/1,
87 tcltk_save_history_as_trace_file/2]).
88 %:- use_module(cspParserHs,'cia/haskell/java_api/cspParserHs.pl',
89 % [initCspParser/0]).
90
91 :- use_module(library(file_systems),[file_exists/1, make_directory/1]).
92 :- use_module(debug).
93 :- use_module(preferences).
94 :- use_module(probltlsrc(ltl),[ltl_check_assertions/2,ltl_model_check/4]).
95 :- use_module(probltlsrc(ctl),[ctl_model_check/4]).
96 :- use_module(test_typechecker,[run_typecheck_testcase/2]).
97
98 :- use_module(basic_unit_tests). % basic unit tests
99 :- use_module(self_check,[disable_interaction_on_errors/0]).
100 :- use_module(error_manager).
101
102 :- use_module(extension('zmq/master/master')).
103 :- use_module(extension('zmq/worker/worker')).
104 :- use_module(extension('ltsmin/ltsmin')).
105
106 :- use_module(self_check,[perform_self_check/1,turn_off_run_time_type_checks/0,turn_on_run_time_type_checks/0]).
107
108 :- use_module(library(system)).
109 :- use_module(library(codesio)).
110
111 :- use_module(logger).
112 %:- use_module(log_analyser, [analyse_log/3, check_log/0]).
113 :- use_module(specfile).
114 :- use_module(bmachine,[b_write_machine_representation_to_file/2,full_b_machine/1, b_write_eventb_machine_to_classicalb_to_file/1]).
115
116 :- use_module(xtl_interface,[set_cspm_main_process/1]).
117 :- use_module(meta_interface,[is_dot_command/1, call_dot_command/3,
118 is_dot_command_for_expr/1,call_dot_command_for_expr/4,
119 command_description/3]).
120 :- use_module('kodkod/kodkod_test').
121 :- use_module(predicate_analysis,[test_predicate_analysis/0]).
122 :- use_module(b_show_history,[write_history_to_file/2,write_values_to_file/1,write_all_values_to_dir/1,write_history_to_user_output/1]).
123 :- use_module(sap, [write_all_deadlocking_paths_to_xml/1, test_generation_by_xml_description/1]).
124
125 :- use_module(smtlib_solver(smtlib2_cli)).
126 :- use_module(disprover_test_runner, [run_disprover_on_all_pos/1, load_po_file/1,print_disprover_stats/0, set_disprover_timeout/1, set_disprover_options/1, reset_disprover_timeout/0]).
127 :- use_module(latex_processor, [process_latex_file/2]).
128
129 :- meta_predicate if_option_set(-,0).
130 :- meta_predicate if_option_set(-,0,0).
131 :- meta_predicate if_options_set(-,0).
132 :- meta_predicate if_option_set_loaded(-,-,0).
133 :- meta_predicate ifm_option_set(-,0).
134 :- meta_predicate ifm_option_set_loaded(-,-,0).
135
136 start_probcli_timer(timer(T1,WT1)) :-
137 statistics(runtime,[T1,_]),
138 statistics(walltime,[WT1,_]).
139 stop_probcli_debug_timer(Timer,Msg) :- (debug_mode(on) -> stop_probcli_timer(Timer,Msg) ; true).
140 stop_probcli_timer(timer(T1,WT1),Msg) :- stop_probcli_timer(timer(T1,WT1),Msg,_).
141 stop_probcli_timer(timer(T1,WT1),Msg,WTotTime) :-
142 statistics(runtime,[T2,_]), TotTime is T2-T1,
143 statistics(walltime,[WT2,_]), WTotTime is WT2-WT1,
144 format('~w ~w ms walltime (~w ms runtime), since start: ~w ms~n',[Msg,WTotTime,TotTime,WT2]),
145 !.
146 stop_probcli_timer(Timer,Msg,_) :- add_internal_error('Illegal timer call: ',stop_probcli_timer(Timer,Msg)).
147 print_total_probcli_timer :-
148 statistics(runtime,[T2,_]),
149 statistics(walltime,[WT2,_]),
150 format('Since start of probcli: ~w ms walltime (~w ms runtime)~n',[WT2,T2]).
151 get_probcli_elapsed_walltime(timer(_,WT1),WTotTime) :-
152 statistics(walltime,[WT2,_]), WTotTime is WT2-WT1.
153
154 :- use_module(tools_meta,[safe_time_out/3]).
155 :- meta_predicate timeout_call(0,-).
156 timeout_call(Call,NOW) :- option(timeout(TO)),!,
157 statistics(runtime,[T1,_]),
158 safe_time_out(Call,TO,Res),
159 statistics(runtime,[T2,_]), Runtime is T2-T1,
160 printsilent('Runtime: '), printsilent(Runtime), printsilent(' ms'),nls,
161 (Res=time_out -> print('*** Timeout occurred: '), print(TO),nl,
162 print('*** Call: '), print(Call),nl,
163 nl,
164 writeln_log(timeout_occurred(NOW,Call))
165 ; true).
166 timeout_call(Call,_NOW) :-
167 statistics(runtime,[T1,_]),
168 call(Call),
169 statistics(runtime,[T2,_]), Runtime is T2-T1,
170 printsilent('Runtime: '), printsilent(Runtime), printsilent(' ms'),nls.
171
172 :- use_module(junit_tests,[set_junit_dir/1, print_junit/2, create_junit_result/6]).
173 set_junit_mode(X) :- set_junit_dir(X), statistics(runtime,[Start,_]), assert(junit_mode(Start)).
174
175
176 go_proxy :-
177 catch( go_cli(['-s','8888']), halt(ExitCode),
178 ( nl,write('CLI halt prevented, exit code '),write(ExitCode),nl) ).
179
180 go_cli :-
181 prolog_flag(argv,ArgV),
182 go_cli_with_junit_check(ArgV).
183
184 initialise_cli :- counter_init,
185 new_counter(cli_execute_inits),
186 new_counter(cli_errors), new_counter(cli_warnings),
187 new_counter(cli_expected_errors).
188 reset_cli :-
189 tcltk_turn_debugging_off,
190 reset_errors,
191 reset_expected_error_occurred,
192 reset_optional_errors,
193 reset_counter(cli_errors), reset_counter(cli_warnings),
194 reset_counter(cli_expected_errors),
195 preferences:reset_to_defaults,
196 reset_logger,
197 unset_storage_directory,
198 % now done via event handling: clear_dynamic_predicates_for_POR,
199 % retractall(refinement_checker: generated_predeterministic_refinement(_,_,_)),
200 % retractall(refinement_checker: determinism_check_div_found(_)),
201 % reset_cspm_main_process,
202 retractall(accumulated_infos(_,_,_)),
203 (file_loaded(_)
204 -> clear_loaded_machines,
205 retractall(file_loaded(_,_)),
206 retractall(loaded_main_file(_,_))
207 ; true).
208
209 go_cli_with_junit_check(ArgV) :-
210 catch( go_cli(ArgV),
211 halt(ExitCode),
212 ( ExitCode = 0 ->
213 true
214 ; junit_mode(S) ->
215 statistics(runtime,[E,_]), T is E - S,
216 create_junit_result(ArgV,'Integration Tests','Integration_Test',T,error([ExitCode]),Result),
217 print_junit([Result],'Integration_Test')
218 ; throw(halt(ExitCode)))).
219
220 go_cli(ArgV) :-
221 (go_cli2(ArgV) -> true
222 ; print_error('INTERNAL ERROR OCCURRED !'),nl,
223 print_error(' (go_cli failed)'),nl, halt_exception(1)).
224
225 ?no_command_issued :- \+ command_option(_).
226 ?command_option(X) :- option(X), \+ not_command_option(X).
227 not_command_option(verbose).
228 not_command_option(very_verbose).
229 not_command_option(profiling_on).
230 not_command_option(set_pref(_,_)).
231 not_command_option(set_card(_,_)).
232 not_command_option(set_argv(_)).
233 not_command_option(silent).
234
235 probcli_startup :-
236 %print_total_probcli_timer,
237 startup_prob,
238 %myheap_init,
239 initialise_cli,
240 init_eclipse_preferences. % startup_prob will already call init_preferences; TO DO: simplify
241
242 :- load_files(library(system), [when(compile_time), imports([environ/2])]).
243 :- if(environ(prob_logging_mode,true)).
244 cli_set_options(ArgV,RemArgV) :-
245 cli_init_options(['-ll'|ArgV],RemArgV). %% adds -ll to have an automatically logging probcli to /tmp/prob_cli_debug.log
246 :- else.
247 cli_set_options(ArgV,RemArgV) :- cli_init_options(ArgV,RemArgV).
248 :- endif.
249
250 %:- use_module(extension('myheap/myheap')).
251 go_cli2(ArgV) :- %print(probcli_startup),nl_time,
252 probcli_startup,
253 external_functions:reset_argv,
254 cli_set_options(ArgV,RemArgV),
255 %% cli_set_options(['-vv','-version'|ArgV],RemArgV), %% comment in to have an automatically verbose probcli
256 !,
257 ( RemArgV=[File],no_command_issued,
258 get_filename_extension(File,Ext),
259 \+ do_not_execute_automatically(Ext)
260 % then assume we want to do -execute_all:
261 -> assert_option(execute(2147483647,false,current_state))
262 ; true),
263 if_option_set(test_mode,set_random_seed_to_deterministic_start_seed, set_new_random_seed),
264 if_option_set(verbose,
265 verbose, %tcltk_turn_debugging_on(19),
266 tcltk_turn_debugging_off),
267 if_option_set(very_verbose,
268 very_verbose), %tcltk_turn_debugging_on(5)),
269 if_option_set(profiling_on,profiling_on),
270 debug_print(9,'Command Line Arguments: '),debug_println(9,ArgV),
271 if_option_set(very_verbose,
272 print_options),
273 debug_print(6,'Command Line File Args: '),debug_println(6,RemArgV),
274 if_option_set(cache_storage(StorageDir), set_storage_directory(StorageDir)),
275 if_option_set(parsercp(ParserLoc),
276 assert(parsercall:parser_location(ParserLoc))),
277 generate_time_stamp(Datime,NOW),
278 if_option_set(log(LogF,Mode),
279 cli_start_logging(LogF,Mode,NOW,Datime,RemArgV)),
280 if_option_set(runtimechecking,
281 turn_on_run_time_type_checks,
282 turn_off_run_time_type_checks),
283 if_option_set(junit(JUX),
284 set_junit_mode(JUX)),
285 set_prefs,
286 set_optional_errors,
287 cli_show_help(ArgV,RemArgV),
288 if_option_set(set_argv(ArgVStr),
289 set_argv(ArgVStr)),
290 if_option_set(selfcheck(_),
291 cli_start_selfcheck),
292 if_option_set(typechecker_test(Filename),
293 (run_typecheck_testcase(Filename,typesok) -> halt_prob(NOW); halt1_prob(NOW))),
294 if_option_set(print_version, print_version),
295 if_option_set(print_short_version, print_short_version),
296 if_option_set(check_java_version, check_java_version),
297 if_option_set(very_verbose,
298 preferences:print_preferences),
299 if_option_set(zmq_worker(Identifier), zmq_start_worker(Identifier, NOW)),
300 %if_option_set(zmq_worker2(MasterIP, Port, ProxyID, Logfile), zmq_start_worker(MasterIP,Port,ProxyID,Logfile,NOW)),
301 debug_println(6,loading(RemArgV)),
302 cli_load_files(RemArgV,NOW), % all CLI arguments which are not understood are supposed to be files to be treated
303 debug_println(6,finished_loading(RemArgV)),
304 %if_options_set(analyse_log(LF,RowID,ForGnu),
305 % analyse_log(LF,RowID,ForGnu)),
306 %if_options_set(check_log(LF),
307 % check_log(LF)),
308 if_option_set(socket(Port),
309 cli_start_socketserver(Port)),
310 % check_all_expected_errors_occurred(NOW), % is now checked for each file; socket_server should not generate errors ?
311 debug_println(20,'% ProB Finished'),
312 cli_print_junit_results(ArgV),
313 get_counter(cli_errors,CErrs), get_counter(cli_warnings,CWarns), get_counter(cli_expected_errors,EErrs),
314 writeln_log_time(prob_finished(NOW,CErrs,CWarns)),
315 (EErrs>0 -> write_xml_element_to_log('probcli-errors',[errors/CErrs,warnings/CWarns,expected_errors/EErrs])
316 ; write_xml_element_to_log('probcli-errors',[errors/CErrs,warnings/CWarns])
317 ),
318 ((CErrs>0 ; CWarns>0) -> format(user_error,'! Total Errors: ~w, Warnings:~w~n',[CErrs,CWarns]) ; true),
319 stop_xml_group_in_log('probcli-run'). % Generating this tag means probcli ran to completion without segfault,...
320
321 cli_init_options(ArgV,RemArgV) :- %print(argv(ArgV)),nl,
322 append(ProBArgV,['--'|BArgV],ArgV),!, % pass arguments after -- to B via external_functions
323 cli_init_options2(ProBArgV,RemArgV),
324 debug_println(20,set_argv_from_list(BArgV)),
325 external_functions:set_argv_from_list(BArgV).
326 cli_init_options(ArgV,RemArgV) :- cli_init_options2(ArgV,RemArgV).
327 cli_init_options2(ArgV,RemArgV) :-
328 reset_options,
329 %%assert(option(log('/tmp/ProBLog.log'))), print('LOGGING'),nl, %% coment in to build a version of probcli that automatically logs
330 ( get_options(ArgV,recognised_cli_option,Options,RemArgV) ->
331 assert_all_options(Options)
332 ; otherwise ->
333 print_error(get_options_failed(ArgV)),definite_error_occurred).
334 cli_show_help(ArgV,RemArgV) :-
335 ( (option(help) ; ArgV=[]) ->
336 print_help, (RemArgV=[] -> halt_exception ; true)
337 ; true).
338 cli_start_logging(F,Mode,NOW,Datime,RemArgV) :-
339 debug_print(20,'%logging to: '), debug_println(20,F),
340 set_log_file(F), set_logging_mode(Mode),
341 start_xml_group_in_log('probcli-run'),
342 writeln_log(start_logging(NOW,F)),
343 version(V1,V2,V3,Suffix), revision(Rev), lastchangeddate(LCD),
344 writeln_log(version(NOW,V1,V2,V3,Suffix,Rev,LCD)), % still used by log_analyser
345 prolog_flag(version,PV),
346 write_xml_element_to_log(version,[major/V1,minor/V2,patch/V3,suffix/Suffix,revision/Rev,lastchanged/LCD,prolog/PV]),
347 findall(Opt, option(Opt), Options),
348 write_prolog_term_as_xml_to_log(options(NOW,Options)),
349 write_prolog_term_as_xml_to_log(files(NOW,RemArgV)),
350 datime(Datime,DateRecord),
351 writeln_log(date(NOW,DateRecord)),
352 (DateRecord=datime(Yr,Mon,Day,Hr,Min,Sec)
353 -> write_xml_element_to_log(date,[year/Yr,month/Mon,day/Day,hour/Hr,minutes/Min,seconds/Sec]) ; true).
354
355 :- use_module(eventhandling,[store_virtual_event/1]).
356 cli_start_selfcheck :-
357 %clear_loaded_machines_wo_errors,
358 b_set_initial_machine,
359 set_animation_mode(b),
360 store_virtual_event(clear_specification), % TO DO: try and get rid of the need for this
361 start_animation,
362 option(selfcheck(Module)),
363 (perform_self_check(Module) -> true ; true),
364 (test_error_occurred(_) -> error_occurred(selfcheck) ; true),
365 fail.
366 cli_start_selfcheck.
367
368
369 :- dynamic file_loaded/2.
370 file_loaded(Status) :- file_loaded(Status,_File).
371
372 %cli_load_files(RemArgV,NOW) :-
373 % if_options_set(l_cspm_pl_file(PlFile),cli_l_cspm_pl_file(PlFile)),!,
374 % assert(file_loaded(true,PlFile)),
375 % cli_process_loaded_file(NOW,PlFile),
376 %(RemArgV=[] -> true ; cli_load_files2(RemArgV,NOW)).
377 cli_load_files([],NOW) :- % no files are provided
378 !,
379 ? ( options_allow_start_without_file -> cli_set_empty_machine
380 ; we_did_something -> true
381 ; otherwise -> print('No file to process'),nl),
382 writeln_log_time(start_processing_empty_machine(NOW)),
383 cli_process_loaded_file(NOW,'$EMPTY_MACHINE'),
384 check_all_expected_errors_occurred(NOW). % check that all expected errors occurred; below they will be checked for each file
385 cli_load_files(RemArgV,NOW) :- cli_load_files2(RemArgV,NOW,0).
386
387
388 cli_set_empty_machine :- % TO DO: do this more properly here and for initialise_required
389 % announce_event(clear_specification),
390 set_animation_mode(b),
391 % announce_event(start_initialising_specification),
392 bmachine:b_set_empty_machine,
393 assert(file_loaded(true,empty_machine)).
394 %announce_event(specification_initialised).
395
396
397 options_allow_start_without_file :- option(eval_repl(_)).
398 options_allow_start_without_file :- option(eval_string_or_file(_,_,_,_)).
399 options_allow_start_without_file :- option(check_log(_)).
400 options_allow_start_without_file :- option(process_latex_file(_,_)).
401
402 we_did_something :- option(print_version).
403 we_did_something :- option(print_short_version).
404 we_did_something :- option(check_java_version).
405
406 option_only_works_for_single_file(zmq_assertion(_Identifier)).
407 option_only_works_for_single_file(zmq_master(_Identifier)).
408
409 clear_loaded_files :-
410 (file_loaded(_) -> clear_loaded_machines_wo_errors ; true).
411 cli_load_files2([],_,NrFilesProcessed) :- !, print_accumulated_infos(NrFilesProcessed).
412 cli_load_files2([F1,F2|T],NOW,_NrFilesProcessed) :-
413 ? option(Option),
414 option_only_works_for_single_file(Option),!,
415 add_error(probcli,'The following option can only be used for a single file: ',Option),
416 add_error(probcli,'Multiple files provided: ',[F1,F2|T]),
417 halt_prob(NOW).
418 cli_load_files2(RemArgV,NOW,NrFilesProcessed) :-
419 %print_total_probcli_timer,
420 clear_loaded_files,
421 retractall(file_loaded(_,_)),
422 RemArgV = [MainFile0|Rest],!,
423 N1 is NrFilesProcessed+1,
424 cli_load_files3(MainFile0,Rest,NOW,N1).
425 cli_load_files3(MainFile0,Rest,NOW,NrOfFile) :-
426 safe_absolute_file_name(MainFile0,MainFile,[access(none)]), % converts Windows slash into Unix slash,...
427 if_option_set(file_info,print_file_info(MainFile)),
428 ? ((Rest=[_|_] ; NrOfFile>1)
429 -> length(Rest,RLen), Tot is NrOfFile+RLen,
430 format('~n~n% Processing file ~w/~w: ~w~n',[NrOfFile,Tot,MainFile]) % was formatsilent
431 ; true),
432 start_xml_feature(process_file,filename,MainFile,FINFO),
433 ( file_exists(MainFile) ->
434 debug_println(6,file_exists(MainFile)),
435 ( load_main_file(MainFile,NOW,Already_FullyProcessed) ->
436 (Already_FullyProcessed==true -> true
437 ; assert(file_loaded(true,MainFile)),
438 writeln_log_time(start_processing(NOW)),
439 start_probcli_timer(Timer),
440 (cli_process_loaded_file(NOW,MainFile)
441 -> stop_probcli_debug_timer(Timer,'% Finished processing file after')
442 ; print_error('### Processing or loading file failed: '), print_error(MainFile)
443 ),
444 writeln_log_time(finished_processing(NOW))
445 )
446 ; otherwise ->
447 assert(file_loaded(error,MainFile)),
448 print_error('### Loading Machine Failed'),
449 writeln_log_time(loading_failed(NOW,MainFile)),
450 error_occurred(load_main_file)
451 ),nl
452 ; otherwise ->
453 nl, assert(file_loaded(error,MainFile)),
454 (number(MainFile0)
455 -> 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)
456 ; atom_codes(MainFile0,[45|_]) % starts with a dash - : probably an illegal command-line option
457 -> add_error(load_main_file,'Specified Option or File does not exist: ',MainFile0)
458 ; add_error(load_main_file,'Specified File does not exist: ',MainFile)
459 )
460 ),
461 check_all_expected_errors_occurred(NOW),
462 stop_xml_feature(process_file,FINFO),
463
464 reset_expected_error_occurred, % reset for next file
465 reset_errors,
466 NOW1 is NOW+1, update_time_stamp(NOW1),
467 cli_load_files2(Rest,NOW1,NrOfFile).
468
469 print_file_info(F) :-
470 print('Specification_File('), print(F), print(')'),nl.
471
472 % ---------------------
473
474 % process all the commands for a loaded file:
475 cli_process_loaded_file(NOW,MainFile) :-
476 (real_error_occurred -> print_error('% *** Errors occurred while loading ! ***'),nl,nl ; true),
477 get_errors, reset_errors,
478 if_option_set(kodkod_performance(KPFile,Iterations),
479 compare_kodkod_performance1(KPFile,Iterations,NOW)),
480 if_option_set(kodkod_comparision(MaxResiduePreds),
481 test_kodkod_and_exit(MaxResiduePreds,NOW)),
482 % 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
483
484 if_option_set(csp_main(MAINPROC),
485 set_cspm_main_process(MAINPROC)),
486
487 if_option_set(zmq_master(Identifier), zmq_start_master(invariant,Identifier)),
488 %if_option_set(zmq_master(IP, Logfile), zmq_start_master(invariant,200,-1,5000,0,IP,Logfile)),
489
490 % STARTING ANIMATION/MODEL CHECKING
491 cli_start_animation(NOW),
492
493
494 if_option_set_loaded(trace_check,trace_check,
495 cli_start_trace_check(MainFile)),
496
497 cli_process_loaded_file_afer_start_animation(NOW).
498
499 cli_process_loaded_file_afer_start_animation(NOW) :-
500 ifm_option_set(cli_print_machine_statistics,
501 cli_print_machine_statistics),
502 ifm_option_set(pretty_print_internal_rep(PPFILE1,TYPES,ASCII),
503 pretty_print_internal_rep(PPFILE1,TYPES,ASCII)),
504 ifm_option_set(pretty_print_internal_rep_to_B(PPFILE3),
505 b_write_eventb_machine_to_classicalb_to_file(PPFILE3)),
506
507 if_option_set_loaded(state_trace(TraceFile),state_trace,
508 cli_start_trace_state_check(TraceFile)),
509
510 if_option_set(evaldot(EvalDotF),
511 set_eval_dot_file(EvalDotF)),
512
513 ? (initialise_required
514 -> check_loaded(initialise),
515 cli_start_initialisation(NOW),
516 writeln_log_time(initialised(NOW))
517 ; true),
518
519 if_option_set(zmq_assertion(Identifier),
520 zmq_start_master(assertion,Identifier)),
521
522 if_option_set(cli_start_mc_with_tlc,cli_start_mc_with_tlc),
523 if_option_set(cli_start_sym_mc_with_lts(LType),cli_start_sym_mc_with_lts(LType)),
524
525 if_option_set(cli_symbolic_model_check(Algorithm),cli_symbolic_model_check(Algorithm)),
526
527 if_option_set_loaded(cli_check_properties,check_properties,
528 cli_check_properties(NOW)),
529 ifm_option_set_loaded(cli_check_assertions(ALL,ReqInfos),check_assertions,
530 cli_check_assertions(ALL,ReqInfos,NOW)),
531 if_option_set(set_goal(GOAL),
532 cli_set_goal(GOAL)),
533 if_option_set(set_searchscope(SCOPE),
534 cli_set_searchscope(SCOPE)),
535 ifm_option_set_loaded(cli_mc(Nr),model_check,
536 cli_start_model_check(Nr,NOW)),
537 ifm_option_set_loaded(cli_random_animate(Steps,ErrOnDeadlock),animate,
538 cli_random_animate(NOW,Steps,ErrOnDeadlock)),
539 ifm_option_set_loaded(execute(ESteps,ErrOnDeadlock,From),execute,
540 cli_execute(ESteps,ErrOnDeadlock,From)),
541 ifm_option_set_loaded(logxml_write_vars(Prefix),logxml_write_vars,
542 logxml_write_vars(Prefix)),
543 if_option_set_loaded(pa_check,predicate_analysis,
544 test_predicate_analysis),
545
546 cbc_check(NOW),
547 if_options_set(generate_read_write_matrix_csv(RWCsvFile),
548 generate_read_write_matrix(RWCsvFile)),
549 if_options_set(feasibility_analysis_csv(TimeOut,EnablingCsvFile),
550 do_feasibility_analysis(TimeOut,EnablingCsvFile)),
551 ifm_option_set_loaded(mcm_tests(ADepth1,AMaxS,ATarget1,Output1),mcm_test_cases,
552 mcm_test_case_generation(ADepth1,AMaxS,ATarget1,Output1)),
553 ifm_option_set_loaded(all_deadlocking_paths(File),all_deadlocking_paths,
554 write_all_deadlocking_paths_to_xml(File)),
555 ifm_option_set_loaded(cbc_tests(ADepth2,ATarget2,Output2),cb_test_cases,
556 cbc_test_case_generation(ADepth2,ATarget2,Output2)),
557 ifm_option_set_loaded(test_description(TestDescFile),cb_test_cases,
558 test_generation_by_xml_description(TestDescFile)),
559 if_options_set(csp_in_situ_refinement_check(RP,RType,RQ),
560 cli_csp_in_situ_refinement_check(RP,RType,RQ,NOW)),
561 if_options_set(csp_checkAssertion(Proc,Model,AssertionType),
562 cli_checkAssertion(Proc,Model,AssertionType,NOW)),
563 if_options_set(check_csp_assertion(Assertion),
564 cli_check_csp_assertion(Assertion,NOW)),
565 if_options_set(refinement_check(RefFile,PerformSingleFailures,RefNrNodes),
566 cli_start_refinement_check(RefFile,PerformSingleFailures,RefNrNodes,NOW)),
567 if_options_set(ctl_forumla_model_check(Formula,Expected),cli_ctl_model_check(Formula,Expected,_)),
568 % TO DO print ctl/ltl statistics
569 if_options_set(csp_get_assertions,cli_csp_get_assertions),
570 if_options_set(eval_csp_expression(CspExpr),cli_eval_csp_expression(CspExpr)),
571 if_options_set(csp_translate_to_file(PlFile),cli_csp_translate_to_file(PlFile)),
572 if_options_set(get_min_max_coverage(MinMxFileName),cli_get_min_max_coverage(MinMxFileName)),
573 if_options_set(get_coverage_information(CovFileName),cli_get_coverage_information(CovFileName)),
574 if_options_set(vacuity_check,cli_vacuity_check),
575 if_option_set_loaded(check_goal,check_goal,cli_check_goal),
576 if_option_set_loaded(animate,animate,
577 (animate_machine -> true ; true)),
578 if_option_set(ltsmin, start_ltsmin_srv('/tmp/ltsmin.probz', NOW)),
579 if_option_set(ltsmin2(EndpointPath), start_ltsmin_srv(EndpointPath, NOW)),
580 if_option_set(ltsmin_ltl_output(Path), ltsmin_ltl_output(Path, NOW)),
581 evaluate_from_commandline,
582 if_option_set_loaded(ltl_assertions,check_ltl_assertions,
583 (timeout_call(ltl_check_assertions,NOW) -> true; true)),
584 ifm_option_set_loaded(ltl_formula_model_check(Formula,Expected),check_ltl_assertions,
585 (option(cli_start_sym_mc_with_lts(_))-> true % we request LTSMin, do not start prob model check
586 ; timeout_call(cli_ltl_model_check(Formula,Expected,_),NOW) -> true; true)),
587 ifm_option_set_loaded(ltl_file(LtlFilename),check_ltl_file,
588 (ltl_check_file(LtlFilename) -> true; true)),
589 ifm_option_set_loaded(history(HistoryFilename),history,
590 cli_print_history(HistoryFilename)),
591 ifm_option_set_loaded(print_values(ValuesFilename),values,
592 cli_print_values(ValuesFilename)),
593 ifm_option_set_loaded(print_all_values(ValuesDirname),values,
594 cli_print_all_values(ValuesDirname)),
595 if_options_set(save_state_for_refinement(SaveRefF),
596 refinement_checker:tcltk_save_specification_state_for_refinement(SaveRefF)),
597 if_options_set(dot_command(DCommand,DotFile),
598 dot_command(DCommand,DotFile)),
599 if_options_set(dot_command_for_expr(DECommand,Expr,DotFile,Opts),
600 dot_command_for_expr(DECommand,Expr,DotFile,Opts)),
601 if_options_set(evaluate_expression_over_history_to_csv_file(HistExpr,HistDotFile),
602 user:evaluate_expression_over_history_to_csv_file(HistExpr,HistDotFile)),
603 if_options_set(enabling_analysis_csv(EnablingCsvFile),
604 do_enabling_analysis_csv(EnablingCsvFile,NOW)),
605 if_options_set(process_latex_file(LatexF1,LatexF2),
606 process_latex_file(LatexF1,LatexF2)),
607 ifm_option_set(coverage(Nodes,Operations,ShowEnabledInfo),
608 cli_show_coverage(Nodes,Operations,ShowEnabledInfo,NOW)),
609 ifm_option_set(check_statespace_hash(ExpectedHash,Kind),
610 cli_check_statespace_hash(ExpectedHash,Kind)),
611 ifm_option_set(variable_coverage,
612 cli_show_variable_coverage(NOW)),
613 ifm_option_set(coverage(ShowEnabledInfo),
614 cli_show_coverage(ShowEnabledInfo,NOW)),
615 if_option_set(save_state(StateFile),
616 save_state(StateFile)),
617 if_option_set(prob_profile,
618 prob_profile),
619 if_option_set(statistics,
620 cli_print_statistics),
621 if_option_set(profile_statistics,
622 profile_statistics),
623 if_option_set(show_cache,
624 show_cache),
625 if_option_set(check_complete, check_complete),
626 if_option_set(check_complete_operation_coverage, check_complete_operation_coverage),
627 if_option_set(check_scc_for_ltl_formula(LtlFormula,SCC),cli_check_scc_for_ltl_formula(LtlFormula,SCC)).
628
629 :- use_module(value_persistance,[show_cache_file_contents/0,show_cache_file_constants/0]).
630 show_cache :- option(verbose),!,show_cache_file_contents,nl.
631 show_cache :- show_cache_file_constants,nl.
632
633 % new profiler
634 %:- use_module('../extensions/profiler/profiler.pl').
635 %cli_print_statistics :- pen,nl,garbage_collect,statistics,nl,state_space:state_space_initialise_with_stats.
636
637 % old profiler
638 :- use_module(hit_profiler).
639 :- use_module(b_operation_cache,[print_op_cache/0]).
640 :- use_module(memoization,[reset_memo_with_statistics/0]).
641 cli_print_statistics :- profile_statistics,
642 nl,garbage_collect,statistics,nl,
643 print_op_cache,
644 state_space:state_space_initialise_with_stats,
645 reset_memo_with_statistics.
646
647 profile_statistics :-
648 print_hit_profile_statistics,
649 (option(profiling_on)
650 -> on_exception(error(existence_error(_,_),_),print_profile,
651 print_red('SICStus Prolog Profiler can only be used when running from source'))
652 ; true).
653
654
655 :- use_module(state_space,[not_all_transitions_added/1, not_invariant_checked/1]).
656 check_complete :-
657 (tcltk_find_max_reached_node(Node1) ->
658 add_error(check_complete,'Maximum number of transitions reached for at least one state: ',Node1) ; true),
659 (not_all_transitions_added(Node2) ->
660 add_error(check_complete,'At least one state was not examined: ',Node2) ; true),
661 (not_invariant_checked(Node3) ->
662 add_error(check_complete,'The invariant was not checked for at least one state: ',Node3) ; true).
663
664 check_complete_operation_coverage :-
665 (state_space: operation_name_not_yet_covered(OpName) ->
666 add_error(check_complete_operation_coverage,'At least one operation is not covered: ', OpName)
667 ; true).
668
669 show_operation_coverage_summary(NOW) :-
670 findall(ON, specfile:get_possible_event(ON), Possible), length(Possible,Nr),
671 findall(OpName, state_space: operation_name_not_yet_covered(OpName), Uncovered),
672 writeln_log(uncovered_info(NOW,Nr,Uncovered)),
673 (Uncovered=[] -> format(' All ~w possible operations have been covered',[Nr]),nl
674 ; format(' The following operations (out of ~w) were not covered:~n ~w~n',[Nr,Uncovered])).
675 show_initialisation_summary(NOW) :-
676 findall(ID,state_space:is_concrete_constants_state_id(ID),L),
677 length(L,Nr), N1 is Nr+1, % for root
678 writeln_log(uninitialised_states(NOW,N1)),
679 format(' Uninitialised states: ~w (root and constants only)~n',[N1]).
680
681 % ---------------------
682
683 animation_mode_does_not_support_animation(File) :-
684 loaded_main_file(smt2,File).
685 cli_start_animation(NOW) :-
686 file_loaded(true,LoadedFile),
687 \+ animation_mode_does_not_support_animation(LoadedFile),
688 !,
689 debug_println(20,'% Starting Animation'),
690 writeln_log_time(start_animation(NOW)),
691 start_probcli_timer(Timer1),
692 start_animation_without_computing,
693 stop_probcli_debug_timer(Timer1,'% Finished Starting Animation'),
694 if_option_set(add_csp_guide(CspGuide), tcltk_add_csp_file(CspGuide)),
695
696 xml_log_machine_statistics,
697 getAllOperations(Ops),
698 debug_print(20,'Operations: '), debug_println(20,Ops),
699
700 (we_need_only_static_assertions(ALL)
701 -> debug_println(20,'% Projecting on static ASSERTIONS'),
702 b_interpreter:set_projection_on_static_assertions(ALL) ; true),
703
704 (option(load_state(File))
705 -> debug_println(20,'% Loading stored state from file'),
706 state_space:tcltk_load_state(File)
707 ? ; computeOperations_for_root_required ->
708 debug_println(20,'% Searching for valid initial states'),
709 start_probcli_timer(Timer2),
710 cli_computeOperations(EO),
711 stop_probcli_debug_timer(Timer2,'% Finished searching for valid initial states'),
712 debug_println(10,EO)
713 ; debug_println(20,'% No initialisation required')
714 ).
715 cli_start_animation(_NOW).
716
717 start_animation_without_computing :-
718 update_preferences_from_spec(ListOfPrefs),
719 (ListOfPrefs=[] -> true ; write_prolog_term_as_xml_to_log(b_machine_preferences(ListOfPrefs))),
720 set_prefs, % override SET_PREF in DEFINITIONS with values from command-line;
721 start_animation,
722 ifm_option_set(add_additional_property(PROP),
723 cli_add_additional_property(PROP)),
724 get_errors.
725
726 :- use_module(state_space,[current_expression/2]).
727 :- use_module(extension('counter/counter')).
728 :- use_module(tools_lists,[count_occurences/2]).
729 % an execution engine with minimal overhead: states are not stored in visited_expression database, only first enabled operation is taken
730 cli_execute(Steps,ErrorOnDeadlock,FromWhere) :-
731 FromWhere=from_all_initial_states,!,
732 % try out all initial states and from each of those perform deterministic execution
733 start_ms_timer(Start),
734 format('Running execute from all initial states~n',[]),
735 reset_counter(cli_execute_inits),
736 findall(Result,
737 (cli_trans(root,Action,CurState,0), %print(Action),nl,
738 (\+ functor(Action,'$setup_constants',_)
739 -> inc_counter(cli_execute_inits,Nr),
740 format('~nExecuting model from initial state ~w~n',[Nr]),
741 (option(animate_stats) -> print_state_silent(CurState) ; true),
742 (cli_execute_from(CurState,Steps,ErrorOnDeadlock,1,Result) -> true)
743 ; format('~nInitialising state~n',[]), % we need to execute initialise_machine
744 cli_trans(CurState,_ActionName,NewState,0),
745 inc_counter(cli_execute_inits,Nr),
746 format('~nExecuting model from initial state ~w with constants~n',[Nr]),
747 (option(animate_stats) -> print_state_silent(NewState) ; true),
748 (cli_execute_from(NewState,Steps,ErrorOnDeadlock,2,Result) -> true)
749 )), Results),
750 get_counter(cli_execute_inits,Nr),
751 format('---------~nTotal runtime for all ~w executions:',[Nr]),nl,
752 stop_ms_timer(Start),
753 count_occurences(Results,Occs), format('Results: ~w~n',[Occs]).
754 cli_execute(Steps,ErrorOnDeadlock,_) :-
755 current_expression(_ID,CurState),
756 start_xml_feature(execute,max_steps,Steps,FINFO),
757 cli_execute_from(CurState,Steps,ErrorOnDeadlock,1,_Result),
758 stop_xml_feature(execute,FINFO).
759 % TO DO: add transition from root to executed state ?
760
761 cli_execute_from(CurState,Steps,ErrorOnDeadlock,FirstStepNr,Result) :-
762 retractall(max_walltime(_,_,_)),
763 start_ms_timer(Start),
764 (b_mode,b_top_level_operation(_) -> temporary_set_preference(filter_unused_constants,true,CHNG) ; true), % we can filter out unused constants, unless there are no operations in which case the user probably wants to see the constant values
765 cli_execute_aux(FirstStepNr,Steps,CurState,ErrorOnDeadlock,'$NO_OPERATION',Result),
766 (b_mode,b_top_level_operation(_) -> reset_temporary_preference(filter_unused_constants,CHNG) ; true),
767 (option(silent) -> true ; stop_ms_timer_with_msg(Start,'-execute')),
768 print_max_walltime.
769
770 :- use_module(external_functions,[reset_side_effect_occurred/0, side_effect_occurred/1]).
771 cli_execute_aux(Nr,Steps,CurState,_ErrorOnDeadlock,_LastActionName,Result) :- Nr>Steps,!,
772 formatsilent('Stopping execution after ~w steps~n',[Steps]), Result = stopped,
773 print_state_silent(CurState),
774 cli_execute_add_virtual_transition(Steps,CurState,Result).
775 cli_execute_aux(Nr,Steps,CurState,ErrorOnDeadlock,LastActionName,Result) :-
776 ((Nr mod 50000 =:= 0,\+option(animate_stats),\+option(silent))
777 -> (var(LastActionName) -> format('Step ~w~n',[Nr])
778 ; format('Step ~w (after ~w)~n',[Nr,LastActionName])),
779 (option(verbose) -> print_state_silent(CurState) ; true),
780 print('Memory used: '),tools:print_memory_used_wo_gc,flush_output,nl ; true),
781 (cli_invariant_ko(CurState,LastActionName,InvStatus) -> % also recognises no_inv command
782 N1 is Nr-1,
783 tools:ajoin(['INVARIANT ',InvStatus,' after ',N1,' steps (after ',LastActionName,').'],ErrMsg),
784 format('~w~n',[ErrMsg]),!,
785 print_state_silent(CurState),
786 error_occurred_with_msg(invariant_violation,ErrMsg),
787 Result=invariant_violation,
788 cli_execute_add_virtual_transition(N1,CurState,Result)
789 ; \+ cli_assertions_ok(CurState,LastActionName) -> % also recognises no_inv command
790 N1 is Nr-1,
791 format('ASSERTION VIOLATED after ~w steps (after ~w).~n',[N1,LastActionName]),!,
792 print_state_silent(CurState),
793 error_occurred(assertion_violation), Result=assertion_violation,
794 cli_execute_add_virtual_transition(N1,CurState,Result)
795 ; cli_goal_found(CurState) -> % also recognizes no_goal command
796 N1 is Nr-1,
797 format('GOAL FOUND after ~w steps (after ~w).~n',[N1,LastActionName]),!,
798 print_state_silent(CurState), Result=goal_found,
799 cli_execute_add_virtual_transition(N1,CurState,Result)
800 ; reset_side_effect_occurred,
801 cli_trans(CurState,ActionName,NewState,Nr),
802 !,
803 N1 is Nr+1,
804 (NewState=CurState, \+ side_effect_occurred(file)
805 -> formatsilent('Infinite loop reached after ~w steps (looping on ~w).~n',[N1,ActionName]),
806 Result=loop,
807 cli_execute_add_virtual_transition(N1,CurState,Result)
808 ; cli_execute_aux(N1,Steps,NewState,ErrorOnDeadlock,ActionName,Result))
809 ).
810 cli_execute_aux(Nr,_Steps,CurState,ErrorOnDeadlock,LastActionName,Result) :- N1 is Nr-1,
811 formatsilent('Deadlock reached after ~w steps (after ~w).~n',[N1,LastActionName]),
812 Result=deadlock,
813 ((ErrorOnDeadlock=true,\+ option(no_deadlocks) ) -> error_occurred(deadlock) ; true),
814 print_state_silent(CurState),
815 cli_execute_add_virtual_transition(N1,CurState,Result).
816
817 cli_execute_add_virtual_transition(Steps,CurState,Result) :-
818 getCurrentStateID(CurID),
819 write_xml_element_to_log(executed,[steps/Steps,result/Result]),
820 (Steps>0 -> user:tcltk_add_new_transition(CurID,'$execute'(Steps),ToID,CurState,[]),
821 debug_println(added_transition_for_execute(Steps,ToID)),
822 tcltk_goto_state('$execute'(Steps),ToID)
823 ; true).
824
825 :- dynamic max_walltime/3.
826 print_max_walltime :- (max_walltime(Action,Nr,WT),option_verbose
827 -> format('% Maximum walltime ~w ms at step ~w for ~w.~n',[WT,Nr,Action]) ; true).
828
829 % will be used to compute a single successor
830 % b_operation_cannot_modify_state
831 cli_trans(CurState,ActionName,NewState,Nr) :- option(animate_stats),!, % provide statistics about the animation
832 start_probcli_timer(Timer),
833 cli_trans_aux(CurState,ActionName,Act,NewState),
834 (option_verbose -> translate:translate_event(Act,TStr)
835 ; translate:translate_event_with_limit(Act,100,TStr)),
836 format('~w~5|: ~w~n',[Nr,TStr]),
837 format(' ~5|',[]),stop_probcli_timer(Timer,' '),
838 get_probcli_elapsed_walltime(Timer,WallTime),
839 (max_walltime(_,_,MWT), MWT >= WallTime -> true
840 ; retractall(max_walltime(_,_,_)),
841 assert(max_walltime(ActionName,Nr,WallTime))).
842 cli_trans(CurState,ActionName,NewState,_Nr) :-
843 cli_trans_aux(CurState,ActionName,_,NewState).
844
845 cli_trans_aux(CurState,ActionName,Act,NewState) :-
846 catch_enumeration_warning_exceptions(
847 (throw_enumeration_warnings_in_current_scope,
848 cli_execute_trans(CurState,ActionName,Act,NewState), % no time-out !
849 (error_occurred_in_error_scope -> ErrorEvent=true ; ErrorEvent=false)
850 ),
851 (error_occurred(virtual_time_out_execute),
852 ActionName = '*** VIRTUAL_TIME_OUT ***', Act=ActionName,
853 CurState=NewState) % this forces loop detection above; not very elegant way of signalling
854 ),
855 (ErrorEvent==true,option(strict_raise_error)
856 -> print('*** ERROR OCCURED DURING EXECUTE ***'),nl, error_occurred(execute),fail
857 ; true).
858
859 cli_execute_trans(CurState,ActionName,Act,NewState) :-
860 specfile_possible_trans_name_for_successors(CurState,ActionName), % to provide feedback
861 on_exception(EXC,
862 specfile_trans_or_partial_trans(CurState,ActionName,Act,NewState,_TransInfo,Residue), % no time-out !
863 (translate_exception(EXC,EMSG),
864 format_with_colour(user_error,[red,bold],'~n*** ~w while executing operation "~w"~n~n',[EMSG,ActionName]),
865 throw(EXC))),
866 (Residue=[] -> true ; error_occurred(cli_execute_residue(ActionName,Residue,Act))).
867
868 translate_exception(user_interrupt_signal,'User-Interrupt (CTRL-C)').
869 translate_exception(enumeration_warning(_,_,_,_,_),'Enumeration Warning').
870 translate_exception(E,E).
871
872 print_state_silent(_) :- option(silent),!.
873 print_state_silent(CurState) :- (option(verbose);\+ b_machine_has_constants),!,
874 translate:print_state(CurState),nl.
875 print_state_silent(CurState) :- remove_constants(CurState,VarState),
876 % only print variables
877 format('VARIABLES (use -v to see constants or -silent to suppress output):~n',[]),
878 translate:print_state(VarState),nl.
879
880 is_constant_binding(bind(C,_)) :- b_is_constant(C).
881 remove_constants(const_and_vars(_,Vars),Res) :- !,Res=Vars.
882 remove_constants([H|T],Res) :- !,exclude(is_constant_binding,[H|T],Res).
883 remove_constants(root,Res) :- !,Res=[].
884 remove_constants(X,X).
885
886 % write vars to xml log file if they start with a given prefix
887 logxml_write_vars(Prefix) :- current_expression(_,CurState),
888 remove_constants(CurState,VarState),
889 % TO DO: store also final state in xml_log
890 write_bstate_to_log(VarState,Prefix).
891
892 cli_invariant_ko(_,_,_) :- option(no_invariant_violations),!,fail. % user asks not to check it
893 cli_invariant_ko(_,_,_) :- get_preference(do_invariant_checking,false),!,fail. % user asks not to check it via preference
894 cli_invariant_ko(CurState,LastActionName,Res) :-
895 state_corresponds_to_initialised_b_machine(CurState,BState),!,
896 start_probcli_timer(InvTimer),
897 (b_specialized_invariant_for_op(LastActionName,Invariant) -> true
898 %, print('Specialized invariant: '),translate:print_bexpr(Invariant),nl
899 ; b_get_invariant_from_machine(Invariant)),
900 cli_test_pred(BState,'INVARIANT',Invariant,Res),
901 stop_probcli_debug_timer(InvTimer,'Finished Invariant Checking'),
902 Res \= 'TRUE'.
903 %cli_invariant_ko(_,_,_) :- fail. % not yet initialised
904
905 cli_test_pred(BState,PredKind,Pred) :- cli_test_pred(BState,PredKind,Pred,'TRUE').
906 cli_test_pred(BState,PredKind,Pred,Res) :-
907 % currently does not do a time-out: % b_interpreter calls: time_out_with_enum_warning_one_solution_no_new_error_scope
908 on_exception(E,
909 on_enumeration_warning(b_interpreter:b_test_boolean_expression_for_ground_state(Pred,[],BState ),
910 (add_error(cli_test_pred,'Enumeration warning while testing',PredKind,Pred),
911 cli_print_pred_info(Pred),
912 Res='UNKNOWN')),
913 (string_concatenate('VIRTUAL TIME-OUT while testing ',PredKind,Msg),
914 add_error(cli_test_pred,Msg,E,Pred),
915 cli_print_pred_info(Pred),
916 Res='UNKNOWN')),
917 !,
918 (var(Res) -> Res = 'TRUE' ; true).
919 cli_test_pred(_BState,_PredKind,_Pred,'FALSE').
920
921 cli_print_pred_info(Pred) :- bsyntaxtree:get_texpr_label(Pred,Label),
922 format('Label = ~w~n',[Label]),fail.
923 cli_print_pred_info(Pred) :- bsyntaxtree:get_texpr_description(Pred,Desc),
924 format('Description = ~w~n',[Desc]),fail.
925 %cli_print_pred_info(Pred) :- bsyntaxtree:get_texpr_pos(Pred,Pos), Pos \= none, translate_span(Pos,Str),
926 % format('Location = ~w~n',[Str]),fail.
927 cli_print_pred_info(_).
928
929 :- use_module(bmachine,[get_assertions_from_machine/2]).
930 % TO DO: also check static assertions
931 cli_assertions_ok(_,_) :- option(no_assertion_violations),!. % user asks not to check it
932 cli_assertions_ok(CurState,_LastActionName) :-
933 state_corresponds_to_initialised_b_machine(CurState,BState),
934 get_assertions_from_machine(dynamic,Assertions), % TO DO: do something similar to b_specialized_invariant_for_op
935 !,
936 start_probcli_timer(AssTimer),
937 %nl,nl,print(check),nl,maplist(translate:print_bexpr,Assertions),nl,
938 maplist(cli_test_pred(BState,'ASSERTION'),Assertions),
939 stop_probcli_debug_timer(AssTimer,'Finished Checking Assertions').
940 cli_assertions_ok(_,_). % not yet initialised or no assertions
941
942
943 cli_goal_found(_):- option(no_goal),!,fail.
944 cli_goal_found(CurState) :-
945 b_get_machine_goal(Goal),
946 state_corresponds_to_initialised_b_machine(CurState,BState),
947 b_interpreter:b_test_boolean_expression_for_ground_state(Goal,[],BState ).
948
949
950 % random animation
951 :- public cli_random_animate/2. % for repl to use -animate command
952 cli_random_animate(Steps,Err) :- probcli_time_stamp(NOW),
953 cli_random_animate(NOW,Steps,Err).
954 cli_random_animate(_NOW,Steps,ErrorOnDeadlock) :-
955 start_xml_feature(random_animate,max_steps,Steps,FINFO),
956 start_ms_timer(S),
957 perform_random_steps(Steps,ErrorOnDeadlock),
958 stop_ms_timer(S,Res),
959 %tcltk_save_history_as_trace_file(prolog,user),
960 printsilent(finished_random_animate(Steps,Res)),nls,
961 stop_xml_feature(random_animate,FINFO).
962
963 we_need_only_static_assertions(ALL) :- specfile:b_or_z_mode,
964 (option(cli_check_assertions(main,_)) -> ALL=main
965 ; option(cli_check_assertions(ALL,_))),
966 % we do an assertion check
967 ? \+ ((option(A), option_requires_all_properties(A))),
968 b_get_assertions(ALL,dynamic,[]). % the assertions do not reference variables
969
970 % do we need all properties/constants of the machine, or only certain ones (e.g., static)
971 option_requires_all_properties(cli_mc(_)).
972 option_requires_all_properties(cli_check_properties(_)). % we may want to check all properties
973 option_requires_all_properties(cli_random_animate(_)).
974 option_requires_all_properties(trace_check).
975 option_requires_all_properties(state_trace(_)).
976 option_requires_all_properties(mcm_tests(_,_,_,_)).
977 option_requires_all_properties(cbc_tests(_,_,_)).
978 option_requires_all_properties(animate).
979 option_requires_all_properties(initialise). % INITIALISATION may access constants
980 option_requires_all_properties(eval_repl(_)).
981 option_requires_all_properties(eval_string_or_file(_,_,_,_)).
982 option_requires_all_properties(ltl_assertions).
983 option_requires_all_properties(ltl_file(_)).
984 option_requires_all_properties(refinement_check(_,_,_)).
985 option_requires_all_properties(cli_start_mc_with_tlc).
986 option_requires_all_properties(cli_symbolic_model_check(_)).
987 option_requires_all_properties(process_latex_file(_,_)).
988
989 :- public trace_check/0.
990 trace_check :- loaded_main_file(_,MainFile),
991 cli_start_trace_check(MainFile).
992 cli_start_trace_check(MainFile) :-
993 debug_println(20,'% Starting Trace Check: '),
994 ( check_default_trace_for_specfile(MainFile) -> true
995 ; otherwise -> error_occurred(trace_check)).
996 cli_start_trace_state_check(File) :-
997 debug_println(20,'% Starting Trace Check: '),
998 ( tcltk_check_state_sequence_from_file(File) -> true
999 ; otherwise -> error_occurred(state_trace)).
1000
1001 % is it necessary to compute enabled operations for root state
1002 ?computeOperations_for_root_required :- initialise_required.
1003 computeOperations_for_root_required :- option(trace_check).
1004 computeOperations_for_root_required :- option(state_trace(_)).
1005 computeOperations_for_root_required :- option(ltl_assertions).
1006 computeOperations_for_root_required :- option(cli_random_animate(_,_)).
1007 computeOperations_for_root_required :- option(socket(_)).
1008 computeOperations_for_root_required :- option(cli_mc(_)).
1009 computeOperations_for_root_required :- option(ltl_file(_)).
1010 computeOperations_for_root_required :- option(ltl_formula_model_check(_,_)).
1011 computeOperations_for_root_required :- option(ctl_forumla_model_check(_,_)).
1012 computeOperations_for_root_required :- option(refinement_check(_,_,_)).
1013 computeOperations_for_root_required :- option(csp_in_situ_refinement_check(_,_)).
1014 computeOperations_for_root_required :- option(csp_checkAssertion(_,_)).
1015 computeOperations_for_root_required :- option(mcm_tests(_,_,_,_)).
1016 computeOperations_for_root_required :- option(mcm_cover(_)).
1017
1018 % is an initialisation mandatory:
1019 initialise_required :- option(initialise), \+ file_loaded(true,empty_machine).
1020 ?initialise_required :- \+ option(trace_check), \+ option(state_trace(_)),
1021 ? \+ option(load_state(_)),
1022 ? \+ file_loaded(true,empty_machine), init_req2.
1023 init_req2 :- option(cli_check_properties).
1024 init_req2 :- option(zmq_assertion(_,_,_)).
1025 init_req2 :- option(cli_check_assertions(_,_)).
1026 init_req2 :- option(process_latex_file(_,_)).
1027 init_req2 :- option(eval_string_or_file(_,_,_,_)). % ensure that we initialise/precompile empty machine in case no main file specified; currently no longer required
1028
1029 initialise :- probcli_time_stamp(NOW),cli_start_initialisation(NOW). % for REPL
1030
1031 cli_start_initialisation(NOW) :-
1032 debug_println(20,'% Performing INITIALISATION: '),
1033 (perform_random_initialisation -> true ;
1034 writeln_log_time(cli_start_initialisation_failed(NOW)),
1035 fail).
1036
1037 :- use_module(state_space,[current_state_corresponds_to_setup_constants_b_machine/0]).
1038 :- public cli_check_properties/0. % for REPL
1039 cli_check_properties :- probcli_time_stamp(NOW),
1040 cli_check_properties(NOW).
1041 cli_check_properties(NOW) :-
1042 printsilent('% Checking PROPERTIES: '),nls,
1043 writeln_log_time(starting_check_properties(NOW)),
1044 ( current_state_corresponds_to_setup_constants_b_machine ->
1045 set_analyse_hook('_P'),
1046 predicate_evaluator:tcltk_analyse_properties(_PROPRES,PROPInfos),
1047 unset_analyse_hook,
1048 printsilent(PROPInfos),nls, % ex: [total/33,true/29,false/0,unknown/4,timeout/4,runtime/49950]
1049 accumulate_infos(properties,PROPInfos),
1050 write_important_xml_element_to_log(check_properties,PROPInfos),
1051 (predicate_evaluator:check_summary_all_true(PROPInfos) -> true
1052 ; print_error('### Not all PROPERTIES true'), error_occurred(check_properties))
1053 ; otherwise ->
1054 (tcltk_debug_properties(list(PROPRES),false,Satisfiable) ->
1055 printsilent(PROPRES),nls,
1056 printsilent(Satisfiable),nls
1057 ; error_occurred(debug_properties_failed))
1058 ),
1059 writeln_log_time(finished_check_properties(NOW,PROPInfos)),
1060 loaded_root_filename(RootName),
1061 formatsilent('% Finished checking PROPERTIES of ~w~n',[RootName]).
1062 :- public cli_check_assertions/2. % for REPL
1063 cli_check_assertions(ALL,RI) :-
1064 probcli_time_stamp(NOW),
1065 cli_check_assertions(ALL,RI,NOW).
1066 cli_check_assertions(ALL,ReqInfos,NOW) :-
1067 printsilent('% Checking ASSERTIONS: '),nls,
1068 writeln_log_time(starting_check_assertions(NOW)),
1069 set_analyse_hook('_A'), % for dot output, in case users wants to generate dot files for assertions
1070 ? predicate_evaluator:tcltk_analyse_assertions(ALL,_ASSRES,Infos),
1071 unset_analyse_hook,
1072 printsilent(Infos),nls,
1073 accumulate_infos(assertions,Infos),
1074 write_important_xml_element_to_log(check_assertions,Infos),
1075 check_required_infos(ReqInfos,Infos,check_assertions),
1076 writeln_log_time(finished_check_assertions(NOW,Infos)),
1077 loaded_root_filename(RootName),
1078 formatsilent('% Finished checking ASSERTIONS of ~w~n',[RootName]),!.
1079 cli_check_assertions(ALL,ReqInfos,NOW) :-
1080 add_internal_error('Analyse ASSERTIONS unexpectedly failed',cli_check_assertions(ALL,ReqInfos,NOW)),
1081 error_occurred(internal_error).
1082 cli_set_goal(GOAL) :-
1083 debug_println(20,set_goal(GOAL)), %print(set_goal(GOAL)), nl,
1084 bmachine:b_set_machine_goal(GOAL).
1085 cli_add_additional_property(PROP) :-
1086 debug_println(20,add_additional_property(PROP)),
1087 bmachine:add_additional_property(PROP).
1088 cli_set_searchscope(GOAL) :-
1089 debug_println(20,set_searchscope(GOAL)),
1090 format('Setting SCOPE for verification: ~w~n (Only states satsifying this predicate will be examined)~n',[GOAL]),
1091 bmachine:b_set_machine_searchscope(GOAL).
1092 cli_check_goal :- \+ b_get_machine_goal(_),!,
1093 add_error(cli_check_goal,'No GOAL DEFINITION found'),
1094 error_occurred(cli_check_goal).
1095 cli_check_goal :-
1096 printsilent('% Checking GOAL predicate: '),nls,
1097 tcltk_analyse_goal(_List,Summary),
1098 debug_println(20,Summary),
1099 accumulate_infos(check_goal,Summary),
1100 write_important_xml_element_to_log(check_goal,Summary),
1101 check_required_infos([false/0,unknown/0],Summary,check_goal).
1102 :- public cli_mc/1. % for REPL
1103 cli_mc(Nr) :- probcli_time_stamp(NOW), cli_start_model_check(Nr,NOW).
1104 cli_start_model_check(Nr,NOW) :-
1105 start_xml_feature(model_check,max_states,Nr,FINFO),
1106 model_check(Nr,Time,MCRes,NOW),
1107 %nl,
1108 stop_xml_feature(model_check,FINFO),
1109 writeln_log_time(model_check(NOW,Nr,Time,MCRes)).
1110 cli_start_mc_with_tlc :-
1111 (animation_mode(b), \+ animation_minor_mode(eventb) -> true; error_manager: add_error_and_fail(mc_with_tlc,'TLC4B tool can be used only for classical B models.')),
1112 % TO DO: use b_write_eventb_machine_to_classicalb_to_file to do conversion
1113 on_exception(error(E,_),
1114 safe_absolute_file_name(prob_lib('TLC4B.jar'),TLC4BTool),
1115 error_manager: add_error_fail(get_tlc_command,'Could not find TLC4B.jar file.',E)),
1116 start_xml_feature(model_check_with_tlc,tlc4bjar,TLC4BTool,FINFO),
1117 construct_and_execute_tlc_command(TLC4BTool),
1118 stop_xml_feature(model_check_with_tlc,FINFO).
1119
1120 :- use_module(system_call,[system_call/4]).
1121 construct_and_execute_tlc_command(TLC4BTool) :-
1122 parsercall: get_java_command_path(JavaCmd),
1123 loaded_main_file(File),
1124 ((get_preference(tlc_number_of_workers,TLCWorkers), TLCWorkers>1)
1125 -> number_codes(TLCWorkers,CC), atom_codes(TLAWA,CC), WW = ['-workers',TLAWA]
1126 ; WW=[]),
1127 (option(no_assertion_violations) -> WA = ['-noass'] ; WA=[]),
1128 (option(no_deadlocks) -> WD = ['-nodead'] ; WD=[]),
1129 (option(no_invariant_violations) -> WI = ['-noinv'] ; WI=[]),
1130 (option(no_goal) -> WG = ['-nogoal'] ; WG=[]),
1131 (option(no_ltl) -> WL = ['-noltl'] ; WL=[]),
1132 append([WW,WA,WD,WI,WG,WL],XtraTLCArgs),
1133 append(XtraTLCArgs,[File],TLCArgs),
1134 print(tlc_args(TLCArgs)),nl,
1135 statistics(walltime,[W1,_]),
1136 system_call: system_call(JavaCmd, ['-jar', TLC4BTool | TLCArgs], Text,JExit),
1137 statistics(walltime,[W2,_]),
1138 WTime is W2-W1,
1139 format('exit : ~w walltime: ~w ms~n',[JExit,WTime]),
1140 (JExit=exit(0)
1141 -> true
1142 ; error_manager: add_error(construct_and_execute_tlc_command,'Error while model checking with TLC: ',TLC4BTool/File),
1143 atom_codes(T,Text),
1144 error_manager: add_error_fail(construct_and_execute_tlc_command,'Std error: ',T)
1145 ).
1146
1147 % SymbolicOrSequential = symbolic or sequential
1148 cli_start_sym_mc_with_lts(SymbolicOrSequential) :-
1149 (option(no_deadlocks) -> NoDead = true ; NoDead = false),
1150 (option(no_invariant_violations) -> NoInv = true ; NoInv = false), % does LTSMin support goal checking
1151 findall(Option,option(ltsmin_option(Option)),MoreFlags1),
1152 findall(ltl_formula(LTLF),option(ltl_formula_model_check(LTLF,_)),MoreFlags2),
1153 append(MoreFlags1,MoreFlags2,MoreFlags),
1154 (NoDead = false, NoInv = false ->
1155 print_error('ERROR: cannot start LTSmin with both deadlock and invariant checking'),
1156 print_error(' use either the -noinv or -nodead flag'),
1157 flush_output(user_error)
1158 ; true),
1159 formatsilent('starting prob2lts-sym/seq (flags nodead=~w, noinv=~w, moreflags=~w)~n',[NoDead,NoInv,MoreFlags]),
1160 start_ltsmin(SymbolicOrSequential, [NoDead, NoInv], MoreFlags,Result),
1161 process_ltsmin_result(Result).
1162 % TO DO: start lts-sym + start start_ltsmin_srv('/tmp/ltsmin.probz', NOW) + print output
1163
1164 :- use_module(extension('ltsmin/ltsmin_trace'),[csv_to_trace/3]).
1165 process_ltsmin_result(ltsmin_model_checking_ok) :-
1166 print_green('LTSMin found no counter example\n').
1167 process_ltsmin_result(ltsmin_counter_example_found(CsvFile)) :-
1168 add_error(ltsmin,'LTSMin found a counter example, written to:',CsvFile),
1169 (option(silent) -> true
1170 ; csv_to_trace(CsvFile,_States,Transitions),
1171 print('*** TRACE: '),nl,print_list(Transitions) % ,print(_States),nl
1172 ).
1173
1174 :- use_module(symbolic_model_checker(ic3), [ic3_symbolic_model_check/1]).
1175 :- use_module(symbolic_model_checker(ctigar), [ctigar_symbolic_model_check/1]).
1176 :- use_module(symbolic_model_checker(kinduction), [kinduction_symbolic_model_check/1,
1177 tinduction_symbolic_model_check/1]).
1178 :- use_module(symbolic_model_checker(bmc), [bmc_symbolic_model_check/1]).
1179 cli_symbolic_model_check(Algorithm) :-
1180 debug_format(20,'% Starting Symbolic Model Check. Using ~w Algorithm', [Algorithm]),
1181 start_xml_feature(model_check,algorithm,Algorithm,FINFO),
1182 (animation_mode(b)
1183 -> true
1184 ; error_manager:add_error_and_fail(cli_symbolic_model_check,'Symbolic Model Checking is currently only available for B and Event-B.')),
1185 perform_symbolic_model_checking(Algorithm,Result),
1186 handle_symbolic_model_check_result(Result),
1187 stop_xml_feature(model_check,FINFO).
1188
1189 perform_symbolic_model_checking(ic3,Result) :- !, ic3:ic3_symbolic_model_check(Result).
1190 perform_symbolic_model_checking(ctigar,Result) :- !, ctigar:ctigar_symbolic_model_check(Result).
1191 perform_symbolic_model_checking(kinduction,Result) :- !, kinduction:kinduction_symbolic_model_check(Result).
1192 perform_symbolic_model_checking(tinduction,Result) :- !, kinduction:tinduction_symbolic_model_check(Result).
1193 perform_symbolic_model_checking(bmc,Result) :- !, bmc:bmc_symbolic_model_check(Result).
1194 perform_symbolic_model_checking(Alg,_) :- add_error_fail(cli_symbolic_model_check,'Invalid symbolic model checking algorithm: ',Alg).
1195
1196 handle_symbolic_model_check_result(counterexample_found) :- !, error_occurred(invariant_violation).
1197 handle_symbolic_model_check_result(property_holds) :- !,
1198 format('Model checking complete, invariant holds~n',[]).
1199 handle_symbolic_model_check_result(solver_and_provers_too_weak) :- !,
1200 format('Model checking incomplete because a constraint could not be solved in time~n',[]),
1201 error_occurred(model_check_incomplete).
1202 handle_symbolic_model_check_result(limit_reached) :- !,
1203 format('Model checking incomplete because an iteration limit was reached~n',[]),
1204 error_occurred(model_check_incomplete).
1205
1206 zmq_start_master(invariant,Identifier) :-
1207 start_animation_without_computing,
1208 zmq_get_initialisation_term(InitTerm),
1209 (option(strict_raise_error) -> Strict = 1 ; Strict = 0),
1210 get_preference(port, PortStart),
1211 get_preference(max_states, Max),
1212 get_preference(ip, IP),
1213 get_preference(logdir, LogDir),
1214 get_preference(tmpdir, TmpDir),
1215 get_preference(hash_cycle, HashCycle),
1216 atom_concat(LogDir, '/distb-', ATmp),
1217 atom_concat(ATmp, Identifier, Logfile),
1218 atom_concat(TmpDir, '/db-distb-', TTmp),
1219 atom_concat(TTmp, Identifier, TmpDir2),
1220 start_master(InitTerm,Max,PortStart,Strict,IP,Logfile,TmpDir2,HashCycle),
1221 halt.
1222 zmq_start_master(assertion,Identifier) :-
1223 get_preference(port, PortStart),
1224 get_preference(logdir, LogDir),
1225 get_preference(ip, IP),
1226 get_preference(tmpdir, TmpDir),
1227 get_preference(hash_cycle, HashCycle),
1228 atom_concat(LogDir, '/distb-', ATmp),
1229 atom_concat(ATmp, Identifier, Logfile),
1230 atom_concat(TmpDir, '/db-distb-', TTmp),
1231 atom_concat(TTmp, Identifier, TmpDir2),
1232 current_state_corresponds_to_setup_constants_b_machine,
1233 animation_mode(b),
1234 full_b_machine(Machine),
1235 b_get_assertions(_,static,SAss),
1236 b_get_assertions(_,dynamic,DAss),
1237 append(SAss,DAss,Ass),
1238 count_assertions(Ass,0,N),
1239 assert(master:assertion_count(N)),
1240 current_expression(_,State1),
1241 specfile:state_corresponds_to_set_up_constants(State1,State),
1242 zmq_get_important_options(Options),
1243 (option(strict_raise_error) -> Strict = 1 ; Strict = 0),
1244 %start_master(assertions(classical_b(Machine,Options),State,Ass),2,-1,PortStart,0,Strict,IP,Logfile,TmpDir2),
1245 start_master(assertions(classical_b(Machine,Options),State,Ass),2,PortStart,Strict,IP,Logfile,TmpDir2,HashCycle),
1246 halt.
1247
1248 zmq_get_initialisation_term(Term) :-
1249 (animation_mode(b) ; animation_mode(csp_and_b)), % CSP file not yet added when ZMQ master starts working
1250 \+ animation_minor_mode(eventb),
1251 option(add_csp_guide(CspGuide)),
1252 !, % Classical B + CSP
1253 debug_println(20,'ZMQ: Transferring CSP || B model'),
1254 full_b_machine(Machine),
1255 % TO DO: extract CSP Term rather than file name: will not work for distribution on other file-systems
1256 zmq_get_important_options(Options),
1257 Term = classical_b_with_csp(Machine,CspGuide,Options).
1258 zmq_get_initialisation_term(Term) :-
1259 debug_println(20,'Generating ZMQ Worker Initialisation'),
1260 animation_mode(b), \+ animation_minor_mode(eventb), !, % Classical B
1261 debug_println(20,'ZMQ: Transferring Classical-B model'),
1262 full_b_machine(Machine),
1263 zmq_get_important_options(Options),
1264 Term = classical_b(Machine,Options).
1265 zmq_get_initialisation_term(Term) :-
1266 animation_mode(b), animation_minor_mode(eventb), !, % Event-B
1267 debug_println(20,'ZMQ: Transferring Event-B model'),
1268 full_b_machine(Machine),
1269 zmq_get_important_options(Options),
1270 Term = eventb(Machine,Options).
1271 zmq_get_initialisation_term(Term) :-
1272 animation_mode(cspm),
1273 loaded_main_file(MainCSPFile),!, % TO DO: pass CSP Prolog term rather than file name (for distribution)
1274 zmq_get_important_options(Options),
1275 debug_println(20,'ZMQ: Transferring CSP specification'),
1276 Term = csp_specification(MainCSPFile,Options).
1277 zmq_get_initialisation_term(_Term) :-
1278 \+ real_error_occurred, % otherwise error occured while loading
1279 animation_mode(Mode),
1280 add_internal_error('Unsupported formalism for ZMQ', Mode),
1281 fail.
1282
1283 zmq_get_initialisation_term(filename(FN)) :-
1284 loaded_main_file(FN).
1285
1286 % get important command-line options to be transmitted to probcli worker
1287 zmq_get_important_options(Options) :- findall(O, (option(O), zmq_important_option(O)), Options),
1288 debug_println(20,transferring_zmq_options_to_workers(Options)).
1289 zmq_important_option(coverage(_)).
1290 zmq_important_option(expect_error(_)).
1291 zmq_important_option(optional_error(_)).
1292 zmq_important_option(file_info).
1293 zmq_important_option(log(_)).
1294 zmq_important_option(print_version).
1295 zmq_important_option(print_short_version).
1296 zmq_important_option(profiling_on).
1297 zmq_important_option(set_card(_,_)).
1298 zmq_important_option(set_pref(_,_)).
1299 zmq_important_option(set_preference_group(_,_)).
1300 zmq_important_option(verbose).
1301 zmq_important_option(statistics).
1302 zmq_important_option(variable_coverage).
1303 zmq_important_option(very_verbose).
1304 % we could consider also supporting: -argv, -cache, -prefs FILE csp_main(ProcessName) profiling_on prob_profile runtimechecking
1305
1306 % set options received by a zmq worker
1307 zmq_set_important_options(Options) :- debug_println(20,setting_zmq_options(Options)),
1308 maplist(zmq_set_option,Options).
1309 zmq_set_option(file_info) :- !, file_info.
1310 zmq_set_option(log(F)) :- !,
1311 generate_time_stamp(Datime,NOW),
1312 cli_start_logging(F,ascii,NOW,Datime,[zmq_worker]).
1313 zmq_set_option(print_version) :- !, print_version.
1314 zmq_set_option(print_short_version) :- !, print_short_version.
1315 zmq_set_option(profiling_on) :- !, profiling_on.
1316 zmq_set_option(set_card(P,V)) :- !, set_eclipse_card(P,V).
1317 zmq_set_option(set_pref(P,V)) :- !, set_pref(P,V).
1318 zmq_set_option(set_preference_group(P,V)) :- !, set_preference_group(P,V).
1319 zmq_set_option(verbose) :- !, verbose.
1320 zmq_set_option(very_verbose) :- !, very_verbose.
1321 zmq_set_option(O) :- zmq_delayed_option(O),!, assert_option(O). % DO IT LATER
1322 zmq_set_option(O) :- add_internal_error('Unsupported option for ZMQ worker: ',zmq_set_option(O)).
1323
1324 zmq_delayed_option(coverage(_)).
1325 zmq_delayed_option(expect_error(_)).
1326 zmq_delayed_option(expect_error_pos(_,_,_)).
1327 zmq_delayed_option(optional_error(_)).
1328 zmq_delayed_option(statistics).
1329 zmq_delayed_option(variable_coverage).
1330
1331 ltsmin_ltl_output(Filename, NOW) :-
1332 if_option_set(ltl_formula_model_check(Formula, _),true),
1333 ltsmin:ltsmin_generate_ltlfile(Formula, Filename),
1334 halt_prob(NOW). % if we additionally specify -ltsformula, we do not want to model check it
1335
1336
1337 start_ltsmin_srv(X, NOW) :-
1338 nls,println_silent('Starting LTSMin Server...'),
1339 if_option_set(ltl_formula_model_check(Formula, _),true),
1340 ltsmin:ltsmin_init(X, Zocket, Formula),
1341 ltsmin:ltsmin_loop(Zocket),
1342 ltsmin:ltsmin_teardown(Zocket, X),
1343 nls,println_silent('Stopped LTSMin Server.'),
1344 halt_prob(NOW). % if we additionally specify -ltsformula, we do not want to model check it
1345
1346 zmq_start_worker(Identifier, NOW) :-
1347 get_preference(port, Port),
1348 get_preference(logdir, LogDir),
1349 get_preference(tmpdir, TmpDir),
1350 get_preference(proxynumber, ProxyNumber),
1351 /* TODO: ensure directory exists (pk, 09.01.2018) */
1352 atom_concat(LogDir, '/worker-', ATmp),
1353 atom_concat(ATmp, Identifier, Logfile),
1354 % TODO: tmp dir currently not used
1355 atom_concat(TmpDir, '/db-worker-', TTmp),
1356 atom_concat(TTmp, Identifier, TmpDir2),
1357 start_worker(Port,ProxyNumber,Logfile,TmpDir2,zmq_worker_load_model),
1358 formatsilent('ZMQ worker finished (Port:~w)~n',[Port]),
1359 cli_process_loaded_file_afer_start_animation(NOW),
1360 println_silent('Exiting probcli worker'),
1361 halt_prob(NOW).
1362
1363 zmq_worker_load_model(classical_b(Machine,Options)) :- !,
1364 debug_println(20,'ZMQ WORKER: Loading classical B model'),
1365 zmq_set_important_options(Options),
1366 bmachine:b_machine_reset, bmachine:assert_main_machine(Machine),
1367 set_animation_mode(b),
1368 prob2_interface:start_animation, cli_computeOperations(_)
1369 .
1370 zmq_worker_load_model(classical_b_with_csp(Machine,CspGuide,Options)) :- !,
1371 debug_println(20,'ZMQ WORKER: Loading CSP || B model'),
1372 zmq_set_important_options(Options),
1373 bmachine:b_machine_reset, bmachine:assert_main_machine(Machine),
1374 set_animation_mode(b),
1375 prob2_interface:start_animation,
1376 tcltk_add_csp_file(CspGuide), % TO DO: use CSP Prolog term rather than filename <----------------
1377 prob2_interface:start_animation,
1378 cli_computeOperations(_)
1379 .
1380 zmq_worker_load_model(eventb(Machine,Options)) :- !,
1381 zmq_set_important_options(Options),
1382 bmachine:b_machine_reset, bmachine:assert_main_machine(Machine),
1383 set_animation_mode(b), set_animation_minor_mode(eventb),
1384 prob2_interface:start_animation, cli_computeOperations(_).
1385 zmq_worker_load_model(csp_specification(CSPFile,Options)) :-
1386 zmq_set_important_options(Options),
1387 load_cspm_spec_from_cspm_file(CSPFile), % TO DO: pass CSP Prolog term rather than filename
1388 prob2_interface:start_animation, cli_computeOperations(_).
1389 zmq_worker_load_model(filename(FN)) :- !,
1390 printsilent('loading file by filename\n'),flush_output,
1391 ( is_eventb_b(FN) ->
1392 eclipse_interface:load_eventb_file(FN)
1393 ; otherwise ->
1394 bmachine:b_load_machine_probfile(FN)),
1395 prob2_interface:start_animation.
1396 zmq_worker_load_model(assertions(Machine,State,Assertions)) :- !,
1397 assert(assertion_counter(-1)),
1398 println_silent(loaded_model_for_assertion_checking),
1399 zmq_worker_load_model(Machine),
1400 assert(worker:assertion_state(State)),
1401 make_assertionwps(Assertions).
1402 % assert current state
1403 zmq_worker_load_model(Other) :-
1404 add_internal_error('ZMQ worker: Unexpected machine description', zmq_worker_load_model(Other)),
1405 fail.
1406
1407
1408 :-dynamic assertion_counter/1.
1409
1410 count_assertions([],A,A).
1411 count_assertions([H|T],A,R) :- bsyntaxtree:conjunction_to_list(H,HL),
1412 length(HL,N1),
1413 NN is A + N1,
1414 count_assertions(T,NN,R).
1415
1416 make_assertionwps([]).
1417 make_assertionwps([H|T]) :- bsyntaxtree:conjunction_to_list(H,HL),
1418 sort_assertions(HL,SL),
1419 append_assertion(SL),
1420 make_assertionwps(T).
1421
1422 append_assertion([]).
1423 append_assertion([H|T]) :- assertion_counter(N),
1424 retractall(assertion_counter(_)),
1425 N1 is N + 1,
1426 assert(assertion_counter(N1)),
1427 assert(worker:assertion_task(N1,H)),
1428 append_assertion(T).
1429
1430 %assertions_order(A,B) :- term_size(A,NA),term_size(B,NB), NA > NB.
1431 sort_assertions(X,X).
1432 % :- samsort(assertions_order,X,Y).
1433
1434
1435
1436 is_eventb_b(FN) :- append(_,FN,".eventb").
1437 % load_model(Initialisation)
1438
1439
1440 load_model(classical_b(M)) :- !,eclipse_interface:load_classical_b(M).
1441 load_model(load_event_b_project(A,B,C,D)) :- !, prob2_interface:load_event_b_project(A,B,C,D), start_animation.
1442 load_model(X) :- print('*** Unknown model: '), print(X),nl.
1443
1444
1445 :- use_module(predicate_evaluator).
1446 :- use_module(bmachine,[b_machine_name/1]).
1447 set_analyse_hook(AddPrefix) :- % set a hook to write false/unknown expressions into a dot file
1448 reset_dot_file_number,
1449 if_options_set(dot_analyse_output_prefix(_Path),
1450 (set_dot_file_prefix_if_option_set(AddPrefix),
1451 register_conjunct_error_hook(user:pred_eval_hook))).
1452 unset_analyse_hook :- predicate_evaluator:reset_conjunct_error_hook.
1453
1454 loaded_root_filename(RootName) :- loaded_main_file(MainFile),
1455 get_modulename_filename(MainFile,RootName).
1456
1457 set_dot_file_prefix_if_option_set(AddPrefix) :-
1458 if_options_set(dot_analyse_output_prefix(Path),
1459 (loaded_root_filename(RootName),
1460 % we could also use b_machine_hierarchy:main_machine_name(RootName)
1461 string_concatenate(Path,RootName,P1),
1462 string_concatenate(P1,AddPrefix,FullPath),
1463 set_dot_file_prefix(FullPath),
1464 debug_println(9,dot_file_prefix(FullPath)))).
1465
1466 % Status: true, false, unknown
1467 pred_eval_hook(_Conjunct,true,_EnumWarning,_IsExpanded, _CS) :-
1468 \+ option(dot_generate_for_all_formulas),!. % don't generate .dot for true formulas, unless explicitly requested
1469 pred_eval_hook(Conjunct,Status,_EnumWarning,_IsExpanded, CS) :-
1470 printsilent('Generating dotfile for: '),printsilent(CS),nls,
1471 (write_dot_graph_to_new_file(Status,Conjunct) -> true
1472 ; add_error(dot_output,'Writing dot to file failed: ',CS)).
1473
1474
1475 :- dynamic dot_file_prefix/1.
1476 :- dynamic dot_file_number/1.
1477
1478 dot_file_prefix('~/Desktop/dot').
1479 set_dot_file_prefix(F) :- retractall(dot_file_prefix(_)), assert(dot_file_prefix(F)).
1480 dot_file_number(0).
1481 reset_dot_file_number :- retractall(dot_file_number(_)), assert(dot_file_number(0)).
1482 get_next_nr(GNr) :- retract(dot_file_number(Nr)), N1 is Nr+1,
1483 assert(dot_file_number(N1)), GNr = Nr.
1484 write_dot_graph_to_new_file(Status,BExpr) :-
1485 dot_file_prefix(Dir),get_next_nr(Nr),
1486 string_concatenate('_',Status,Str1),
1487 string_concatenate(Nr,Str1,NS),
1488 string_concatenate(Dir,NS,F1),
1489 atom_concat(F1,'.dot',FileName),
1490 user:write_dot_file_for_pred_expr(BExpr,FileName).
1491
1492 % get dot file name if dot_output has been set
1493 get_dot_file(Type,FileName) :- option(dot_analyse_output_prefix(_)),
1494 set_dot_file_prefix_if_option_set(Type),
1495 dot_file_prefix(Dir),
1496 string_concatenate('_',Type,Str1),
1497 string_concatenate(Dir,Str1,F1),
1498 atom_concat(F1,'.dot',FileName).
1499
1500 :- use_module(refinement_checker).
1501 cli_csp_in_situ_refinement_check(P,Type,Q,NOW) :-
1502 debug_println(20,'% Starting CSP Refinement Check'),
1503 loaded_main_file(CSPFile),
1504 ajoin_with_sep(['assert',P,Type,Q], ' ',Assertion),
1505 start_xml_feature(csp_refinement_check,assertion,Assertion,FINFO),
1506 ( timeout_call(user:tcltk_check_csp_assertion(Assertion,CSPFile,'False',_PlTerm,RefTrace),NOW)
1507 -> check_ref_result(RefTrace)
1508 ; otherwise -> true),
1509 stop_xml_feature(csp_refinement_check,FINFO).
1510 cli_start_refinement_check(RefFile,PerformSingleFailures,RefNrNodes,NOW) :-
1511 start_xml_feature(refinement_check,file,RefFile,FINFO),
1512 refinement_checker:tcltk_load_refine_spec_file(RefFile),
1513 ( timeout_call(tcltk_refinement_search(RefTrace,PerformSingleFailures,RefNrNodes),NOW)
1514 -> check_ref_result(RefTrace)
1515 ; otherwise -> true),
1516 stop_xml_feature(refinement_check,FINFO).
1517 check_ref_result(RefTrace) :-
1518 ( RefTrace==no_counter_example ->
1519 print('==> Refinement Check Successful'),nl
1520 ; otherwise ->
1521 print('*** Refinement Check Counter-Example: ***'),nl, print(RefTrace),nl,
1522 print('*** Refinement Check Failed ***'),nl,
1523 error_occurred(refinement_check_fails)).
1524 cli_checkAssertion(Proc,Model,AssertionType,_NOW) :-
1525 loaded_main_file(CSPFile),
1526 ajoin(['assert ',Proc,' :[ ',AssertionType,'[',Model,']',' ]'],Assertion),
1527 start_xml_feature(csp_deadlock_check,assertion,Assertion,FINFO),
1528 ( /*timeout_call(*/user:tcltk_check_csp_assertion(Assertion,CSPFile,'False',_PlTerm,ResTrace)/*,NOW)*/
1529 -> check_model_result(Assertion,ResTrace)
1530 ; otherwise -> true),
1531 stop_xml_feature(csp_deadlock_check,FINFO).
1532 cli_check_csp_assertion(Assertion,NOW) :-
1533 start_xml_feature(csp_assertion_check,assertion,Assertion,FINFO),
1534 loaded_main_file(CSPFile),
1535 ajoin(['assert ',Assertion],AssertionFull),
1536 ( timeout_call(user:tcltk_check_csp_assertion(AssertionFull,CSPFile,_Negated,PlTerm,ResTrace),NOW)
1537 -> check_model_result(PlTerm,ResTrace)
1538 ; otherwise -> true),
1539 stop_xml_feature(csp_assertion_check,FINFO).
1540
1541
1542
1543 check_model_result(AssertionPlTerm,ResTrace) :-
1544 ( ResTrace==no_counter_example ->
1545 print('==> Model Check Successful'),nl
1546 ;otherwise ->
1547 (functor(AssertionPlTerm,assertRef,_Arity) ->
1548 print('*** Refinement Check Counter-Example: ***'),nl, print(ResTrace),nl,
1549 print('*** Refinement Check Failed ***'),nl,
1550 error_occurred(refinement_check_fails)
1551 ; otherwise ->
1552 print('*** Model Check Counter-Example: ***'),nl,print(ResTrace),nl,
1553 print('*** Model Check Failed ***'),nl,
1554 error_occurred(model_check_fails))
1555 ).
1556 cli_csp_get_assertions :-
1557 loaded_main_file(CSPFile),
1558 get_csp_assertions_as_string(CSPFile,String),
1559 print('*** Assertions in File (separated by $) ***'),nl,print(String),nl.
1560 cli_eval_csp_expression(E) :-
1561 (loaded_main_file(CSPFile) ->
1562 haskell_csp: evaluate_csp_expression(E, CSPFile, Res)
1563 ; haskell_csp: evaluate_csp_expression(E,Res)
1564 ), print('Evaluated Expression: '),nl,print(Res),nl.
1565 cli_csp_translate_to_file(PlFile) :-
1566 loaded_main_file(CSPFile),parse_and_load_cspm_file_into_specific_pl_file(CSPFile,PlFile).
1567 cli_check_scc_for_ltl_formula(LtlFormula,SCC) :-
1568 ltl_fairness: check_scc_ce(LtlFormula,SCC).
1569 :- use_module(tools_files,[write_lines_to_file/2]).
1570 cli_get_min_max_coverage(Filename) :-
1571 coverage_statistics:tcltk_compute_min_max(list(R)),
1572 tools:filter(tools: is_a_comment('/*','*/'),R,_Comments,Res),
1573 write_lines_to_file(Filename,Res).
1574 % pretty_print_min_max_coverage_to_file(FileName).
1575 :- use_module(coverage_statistics,[pretty_print_coverage_information_to_file/1]).
1576 cli_get_coverage_information(FileName) :-
1577 pretty_print_coverage_information_to_file(FileName).
1578 cli_vacuity_check :-
1579 eclipse_interface:get_vacuous_invariants(L),
1580 (L=[] -> print('No vacuous invariants'),nl
1581 ; maplist(add_vacuous_invariant,L)).
1582 add_vacuous_invariant(Inv) :-
1583 translate:translate_bexpression(Inv,TI),
1584 add_error(vacuity_check,'Vacuous invariant: ',TI).
1585 cli_start_socketserver(Port) :-
1586 printsilent('Starting Socket Server'),nls,
1587 safe_absolute_file_name(prob_home('.'),AppDir),
1588 printsilent('Application Path: '),printsilent(AppDir),nls,
1589 disable_interaction_on_errors,
1590 ( start(Port) -> true
1591 ; otherwise ->
1592 print('Starting socket server failed, Port: '), print(Port),nl),
1593 printsilent('Finished Socket Server'),nls.
1594 cli_check_statespace_hash(Expected,Kind) :-
1595 print('Computing hash of entire statespace: '),
1596 state_space:compute_full_state_space_hash(Hash),
1597 print(Hash),nl, % TO DO: maybe also compute hash for transitions and check that
1598 (Hash=Expected -> true
1599 ; Kind=='64bit', \+ platform_is_64_bit -> format('Hash does not match ~w (but was computed on 64-bit system)~n',[Expected])
1600 ; Kind=='32bit', platform_is_64_bit -> format('Hash does not match ~w (but was computed on 32-bit system)~n',[Expected])
1601 ; add_error(hash,'Expected Statespace Hash to be: ',Expected)).
1602 cli_show_coverage(ShowEnabledInfo,NOW) :-
1603 cli_show_coverage(_Nodes,_Operations,ShowEnabledInfo,NOW).
1604 cli_show_coverage(Nodes,Operations,ShowEnabledInfo,NOW) :-
1605 ShowEnabledInfo==just_check_stats,!, % no printing of individual transition coverage
1606 state_space:get_state_space_stats(TotalNodeSum,TotalTransSum,_ProcessedTotal), % no computation overhead
1607 writeln_log(computed_coverage(NOW,TotalNodeSum,TotalTransSum)),
1608 check_totals(Nodes,Operations,TotalNodeSum,TotalTransSum).
1609 cli_show_coverage(Nodes,Operations,ShowEnabledInfo,NOW) :-
1610 ShowEnabledInfo== just_summary,
1611 !, % no printing of detailed transition coverage (avoid traversing state space)
1612 state_space:get_state_space_stats(TotalNodeSum,TotalTransSum,_ProcessedTotal), % no computation overhead
1613 writeln_log(computed_coverage(NOW,TotalNodeSum,TotalTransSum)),
1614 format('Coverage:~n States: ~w~n Transitions: ~w~n',[TotalNodeSum,TotalTransSum]),
1615 show_initialisation_summary(NOW),
1616 show_operation_coverage_summary(NOW),
1617 check_totals(Nodes,Operations,TotalNodeSum,TotalTransSum).
1618 cli_show_coverage(Nodes,Operations,ShowEnabledInfo,NOW) :-
1619 print('Coverage:'),nl,
1620 compute_the_coverage(Res,TotalNodeSum,TotalTransSum,ShowEnabledInfo,false),
1621 writeln_log(computed_coverage(NOW,TotalNodeSum,TotalTransSum)),
1622 print(Res),nl,
1623 check_totals(Nodes,Operations,TotalNodeSum,TotalTransSum).
1624 check_totals(Nodes,Operations,TotalNodeSum,TotalTransSum) :-
1625 ( Nodes=TotalNodeSum -> true
1626 ; otherwise ->
1627 add_error(probcli,'Unexpected number of nodes: ',TotalNodeSum),
1628 add_error(probcli,'Expected: ',Nodes),error_occurred(coverage)),
1629 ( Operations=TotalTransSum -> true
1630 ; otherwise ->
1631 add_error(probcli,'Unexpected number of transitions: ',TotalTransSum),
1632 add_error(probcli,'Expected: ',Operations),error_occurred(coverage)).
1633 cli_show_variable_coverage(NOW) :-
1634 print('Variable (min/max) coverage: '),nl,
1635 coverage_statistics:tcltk_compute_min_max(list(R)),
1636 print_list(R),nl,
1637 writeln_log(computed_variable_coverage(NOW,R)).
1638
1639 cli_print_machine_statistics :-
1640 b_machine_name(Name),
1641 %(b_get_main_filename(File) -> true ; File=unknown),
1642 format('Machine statistics for ~w~n',[Name]),
1643 findall(Key/Nr,b_machine_statistics(Key,Nr),L),
1644 maplist(print_keynr,L),!.
1645 cli_print_machine_statistics :- add_error(machine_stats,'Could not obtain machine statistics').
1646 print_keynr(Key/Nr) :- format(' ~w : ~w~n',[Key,Nr]).
1647
1648 xml_log_machine_statistics :-
1649 animation_mode(Major),
1650 (animation_minor_mode(Minor) -> true ; Minor=none),
1651 write_xml_element_to_log(animation_mode,[major/Major,minor/Minor]),
1652 ((b_or_z_mode, b_machine_name(Main))
1653 -> findall(Key/Nr,b_machine_statistics(Key,Nr),BMachStats),
1654 (b_get_main_filename(MainFile) -> get_tail_filename(MainFile,TailFile) ; TailFile = unknown),
1655 write_xml_element_to_log(b_machine_statistics,[machine_name/Main, tail_filename/TailFile|BMachStats])
1656 ; true).
1657
1658 cli_print_junit_results(ArgV) :-
1659 ? junit_mode(S),!,
1660 statistics(runtime,[E,_]),
1661 T is E - S,
1662 create_junit_result(ArgV,'Integration Tests','Integration_Test',T,pass,Result),
1663 print_junit([Result],'Integration_Test').
1664 cli_print_junit_results(_).
1665
1666 cli_print_history(HistFile) :-
1667 findall( O, option(history_option(O)), Options),
1668 debug_println(9,writing_history_to_file(HistFile)),
1669 (Options=[trace_file] -> tcltk_save_history_as_trace_file(prolog,HistFile) % save as Prolog trace file for replay with -t
1670 ; Options=[json] -> tcltk_save_history_as_trace_file(json,HistFile) % save for replay with ProB2 UI
1671 ; write_history_to_file(HistFile,Options) -> true
1672 ; add_error(history,'Writing history to file failed: ',HistFile)).
1673
1674 cli_print_values(ValuesFilename) :-
1675 (write_values_to_file(ValuesFilename) -> true ; add_error(sptxt,'Writing values to file failed: ',ValuesFilename)).
1676 cli_print_all_values(ValuesDirname) :-
1677 (write_all_values_to_dir(ValuesDirname) -> true ; add_error(sstxt,'Writing all values to directory failed: ',ValuesDirname)).
1678
1679 :- use_module(library(terms),[term_hash/2]).
1680 :- dynamic probcli_time_stamp/1.
1681 generate_time_stamp(NOW,TS) :- retractall(probcli_time_stamp(_)),
1682 now(NOW),
1683 prolog_flag(argv,ArgV),term_hash(ArgV,Hash),
1684 Rnd is Hash mod 1000,
1685 % random(0,1000,Rnd), always returns 216 % TO DO: try to get milliseconds from some library function
1686 TS is (NOW*1000)+Rnd,
1687 assert(probcli_time_stamp(TS)).
1688 update_time_stamp(NOW1) :- retractall(probcli_time_stamp(_)),
1689 assert(probcli_time_stamp(NOW1)).
1690
1691 %get_errors :- \+ real_error_occurred,!, (get_error(_Source,_Msg) -> print('*** Warnings occurred'),nl ; true), reset_errors.
1692 get_errors :-
1693 (get_preference(view_probcli_errors_using_bbresults,true)
1694 -> tools_commands:show_errors_with_bb_results([current]) ; true),
1695 get_error_sources.
1696
1697 ?get_error_sources :- get_error_with_span(ErrSource,Msg,Span), !,
1698 error_occurred_with_msg(ErrSource,Msg,Span),
1699 findall(1,get_error(ErrSource,_),L), length(L,Nr),
1700 (Nr>0 -> N1 is Nr+1, get_error_category_and_type(ErrSource,Cat,Type),
1701 (Type=error -> print_error('*** Occurences of this error: ')
1702 ; print_error('*** Occurences of this warning: ')),
1703 print_error(N1),
1704 write_xml_element_to_log(multiple_errors_occurred,[category/Cat,type/Type,number/N1])
1705 ; true),
1706 get_error_sources.
1707 get_error_sources.
1708
1709 :- 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]).
1710 ?get_state_space_errors :- option(strict_raise_error),
1711 !,
1712 ? (\+ option(no_invariant_violations),invariant_violated(ID)
1713 -> (option_verbose ->
1714 format('Invariant violation in state with id = ~w~n',[ID]),
1715 b_interpreter:analyse_invariant_for_state(ID) % caused issue for test 1076
1716 ; format('Invariant violation in state with id = ~w (use -v to print more details)~n',[ID])
1717 ),
1718 error_occurred(invariant_violation)
1719 ; true),
1720 (state_error(_,_,abort_error(TYPE,Msg,_,Span)) -> error_occurred(TYPE,error,Span,Msg) ; true),
1721 get_state_errors(_).
1722 get_state_space_errors.
1723
1724 ?get_state_errors(ID) :- state_error(ID,_,X), X\=invariant_violated, X\=abort_error(_,_,_,_),
1725 create_state_error_description(X,Msg),error_occurred(Msg),fail.
1726 get_state_errors(ID) :- time_out_for_invariant(ID),error_occurred(time_out_for_invariant),fail.
1727 get_state_errors(ID) :- time_out_for_assertions(ID),error_occurred(time_out_for_assertions),fail.
1728 get_state_errors(ID) :- time_out_for_node(ID,_,time_out),error_occurred(time_out),fail.
1729 get_state_errors(ID) :-
1730 time_out_for_node(ID,_,virtual_time_out(_)), %print(virtual_time_out_for_node(ID)),nl,
1731 error_occurred(virtual_time_out),fail.
1732 get_state_errors(_).
1733
1734
1735 create_state_error_description(eventerror(Event,Error,_),Description) :- !,
1736 functor(Error,Functor,_),
1737 ajoin(['event_error:',Event,':',Functor],Description).
1738 create_state_error_description(StateError,Description) :-
1739 functor(StateError,Functor,_),
1740 atom_concat('state_error:',Functor,Description).
1741
1742 check_loaded(Action) :-
1743 ( file_loaded(true) -> true
1744 ; file_loaded(error) -> fail /* we have already generated error message */
1745 ; otherwise ->
1746 add_error(probcli,'No file specified; cannot perform action: ',Action),
1747 error_occurred(loading),fail).
1748
1749 :- dynamic loaded_main_file/2.
1750 loaded_main_file(File) :- loaded_main_file(_Ext,File).
1751
1752 load_main_file(MainFile,NOW,Already_FullyProcessed) :- retractall(loaded_main_file(_,_)),
1753 debug_print(20,'% Loading: '), debug_println(20,MainFile),
1754 writeln_log_time(loading(NOW,MainFile)),
1755 get_filename_extension(MainFile,Ext),
1756 debug_println(6,file_extension(Ext)),
1757 start_probcli_timer(Timer),
1758 load_spec_file(Ext,MainFile,Already_FullyProcessed),
1759 stop_probcli_debug_timer(Timer,'% Finished loading'),
1760 (Already_FullyProcessed==true -> true
1761 ; assert(loaded_main_file(Ext,MainFile))).
1762 %load_spec_file('pl',MainFile) :- !, load_cspm_spec_from_pl_file(MainFile). % no longer needed ?
1763 load_spec_file('csp',MainFile) :- !, load_cspm_spec_from_cspm_file(MainFile).
1764 load_spec_file('cspm',MainFile) :- !, load_cspm_spec_from_cspm_file(MainFile).
1765 load_spec_file('P',MainFile) :- !, load_xtl_file(MainFile).
1766 load_spec_file('p',MainFile) :- !, load_xtl_file(MainFile). % sometimes windows is confused about the upper case letter....
1767 load_spec_file('eventb',MainFile) :- !, load_eventb_file(MainFile).
1768 load_spec_file('v',MainFile) :- !,
1769 print('---------------------------------'),nl,
1770 print('Loading: '),print(MainFile),nl,
1771 load_b_file(MainFile). % Siemens Rule File; maybe in future use -eval_rule_file
1772 load_spec_file('prob',MainFile) :- !,load_prob_file(MainFile).
1773 load_spec_file('mch',MainFile) :- !,load_b_file(MainFile).
1774 load_spec_file('sys',MainFile) :- !,load_b_file(MainFile).
1775 load_spec_file('ref',MainFile) :- !,load_b_file(MainFile).
1776 load_spec_file('imp',MainFile) :- !,load_b_file(MainFile).
1777 load_spec_file('rmch',MainFile) :- !,load_b_file(MainFile).
1778 load_spec_file('fuzz',MainFile) :- !,tcltk_open_z_file(MainFile).
1779 load_spec_file('tex',MainFile) :- !,tcltk_open_z_tex_file(MainFile).
1780 load_spec_file('zed',MainFile) :- !,tcltk_open_z_tex_file(MainFile).
1781 load_spec_file('als',MainFile) :- !,tcltk_open_alloy_file(MainFile).
1782 load_spec_file('tla',MainFile) :- !, load_tla_file(MainFile).
1783 load_spec_file('eval',File) :- !, cli_set_empty_machine, cli_start_animation(eval_file), eval_string_or_file(file,File,exists,_).
1784 load_spec_file('pb',File) :- !, cli_set_empty_machine, cli_start_animation(pb_file), eval_string_or_file(file,File,exists,_).
1785 %load_spec_file('pml',MainFile) :- !,parsercall:call_promela_parser(MainFile),
1786 % parsercall:promela_prolog_filename(MainFile,PrologFile),
1787 % println_silent(consulting(PrologFile)),
1788 % tcltk_open_promela_file(PrologFile).
1789 load_spec_file(EXT,MainFile) :- print_error('### Unknown file extension, assuming B machine:'),
1790 print_error(EXT),
1791 load_b_file(MainFile).
1792
1793 load_spec_file('pl',MainFile, Already_FullyProcessed) :- !, Already_FullyProcessed=true,
1794 printsilent('Processing PO file: '),printsilent(MainFile),nls,
1795 load_po_file(MainFile),
1796 (option(timeout(TO)) -> set_disprover_timeout(TO) ; reset_disprover_timeout),
1797 (option(disprover_options(L)) -> set_disprover_options(L) ; set_disprover_options([])),
1798 println_silent('Running ProB Disprover'),
1799 run_disprover_on_all_pos(Summary),
1800 print_disprover_stats,
1801 accumulate_infos(disprover,[po_files-1|Summary]),
1802 get_errors,
1803 (option(cli_check_disprover_result(Infos)) -> check_required_infos(Infos,Summary,load_po_file)
1804 ; option(strict_raise_error) -> check_required_infos([false-0,unknown-0,failure-0],Summary,load_po_file)
1805 % TO DO: provide way for user to specify expected info
1806 ; true),
1807 clear_loaded_machines.
1808 load_spec_file('smt2',MainFile,Already_FullyProcessed) :- !, Already_FullyProcessed=true,
1809 printsilent('Processing SMT file: '),printsilent(MainFile),nls,
1810 smtlib2_file(MainFile).
1811 load_spec_file(EXT,F,false) :- load_spec_file(EXT,F).
1812
1813
1814 % do not perform -execute_all if no parameters provided
1815 do_not_execute_automatically('pl').
1816 do_not_execute_automatically('smt2').
1817
1818 test_kodkod_and_exit(MaxResiduePreds,NOW) :-
1819 start_animation_without_computing,
1820 test_kodkod(MaxResiduePreds),
1821 halt_prob(NOW).
1822
1823 compare_kodkod_performance1(KPFile,Iterations,NOW) :-
1824 start_animation_without_computing,
1825 compare_kodkod_performance(KPFile,Iterations),
1826 halt_prob(NOW).
1827
1828 :- use_module(parsercall,[check_java_version/2,get_parser_version/1, ensure_console_parser_launched/0]).
1829 check_java_version :- check_java_version(V,Result),
1830 format('Result of checking Java version:~n ~w~n',[V]),
1831 (Result=compatible -> check_parser_version
1832 ; add_error(check_java_version,V)).
1833
1834 check_parser_version :- get_parser_version(PV),!,
1835 format(' ProB B Java Parser available in version: ~w.~n ',[PV]). % will also launch parser
1836 check_parser_version :- add_error(check_parser_version,'Cannot start Java B Parser to obtain version number').
1837
1838 :- use_module(version).
1839 print_short_version :-
1840 version(V1,V2,V3,Suffix),revision(Rev),
1841 format('VERSION ~p.~p.~p-~p (~p)~N',[V1,V2,V3,Suffix,Rev]).
1842
1843 :- use_module(parsercall,[get_parser_version/1, get_java_command_path/1, get_java_fullversion/1]).
1844 print_version :-
1845 print('ProB Command Line Interface'),nl,
1846 version(V1,V2,V3,Suffix),
1847 revision(Rev), lastchangeddate(LCD), prolog_flag(version,PV),
1848 format(' VERSION ~p.~p.~p-~p (~p)~N ~p~N Prolog: ~p~N',
1849 [V1,V2,V3,Suffix,Rev,LCD,PV]),
1850 ( option_verbose ->
1851 safe_absolute_file_name(prob_home('.'),AppDir),
1852 format(' Application Path: ~p~N', [AppDir]),
1853 (get_java_command_path(JavaPath)
1854 -> format(' Java Runtime: ~p~N', [JavaPath]),
1855 (get_java_fullversion(JavaVersion)
1856 -> format(' Java Version: ~s~N', [JavaVersion])
1857 ; format(' Java Version: *** not available ***~N',[])
1858 ),
1859 (get_parser_version(ParserVersion)
1860 -> format(' Java Parser: ~p~N', [ParserVersion])
1861 ; format(' Java Parser: *** not available ***~N',[])
1862 )
1863 ; format(' Java Runtime: *** not available ***~N',[])
1864 ),
1865 (option(very_verbose) -> print_prolog_flags ; true)
1866 ; true
1867 ), print_compile_time_flags.
1868
1869
1870 :- use_module(compile_time_flags,[compile_time_flags/1, relevant_prolog_flags/1]).
1871 print_compile_time_flags :-
1872 compile_time_flags(list(Flags)),
1873 (Flags=[], \+ option_verbose -> true ; format(' COMPILE TIME FLAGS: ~w~N',[Flags])).
1874 print_prolog_flags :-
1875 relevant_prolog_flags(Flags),
1876 format(' PROLOG FLAGS: ~w~N',[Flags]).
1877
1878 print_help :-
1879 print_version,
1880 print('Usage: probcli FILE [OPTIONS]'),nl,
1881 print(' OPTIONS are: '),nl,
1882 print(' -mc Nr model check; checking at most Nr states'),nl,
1883 print(' -model_check model check without limit on states explored'),nl,
1884 ( \+ option_verbose ->
1885 print(' -noXXX XXX=dead,inv,goal,ass (for model check)'),nl % -nodead, -noinv, -nogoal, -noass
1886 ;
1887 print(' -nodead do not look for deadlocks (for model check, animate, execute)'),nl,
1888 print(' -noinv do not look for invariant violations (for model check, animate, execute)'),nl,
1889 print(' -nogoal do not look for GOAL predicate (for model check, execute)'),nl,
1890 print(' -noass do not look for ASSERTION violations (for model check, execute)'),nl
1891 ),
1892 print(' -bf proceed breadth-first'),nl,
1893 print(' -df proceed depth-first'),nl,
1894 print(' -mc_mode M M=hash,heuristic,random,breadth-first,depth-first,mixed'),nl,
1895 print(' -timeout N total timeout in ms for model and refinement checking'),nl, % also for disprover
1896 print(' -disable_timeout disable timeouts for operations, invariants,....'),nl, % speeds up mc
1897 print(' -t trace check (associated .trace file must exist)'),nl,
1898 print(' -init initialise specification'),nl,
1899 print(' -cbc OPNAME constraint-based invariant checking for an operation'),nl,
1900 print(' (you can also use OPNAME=all)'),nl,
1901 print(' -cbc_deadlock constraint-based deadlock checking'),nl,
1902 ( \+ option_verbose -> true ;
1903 print(' -cbc_deadlock_pred PRED as above but with additional predicate'),nl
1904 ),
1905 print(' -cbc_assertions constraint-based static assertion checking'),nl,
1906 print(' -cbc_refinement constraint-based static refinement checking'),nl,
1907 print(' -cbc_sequence S constraint-based search for sequence of operations'),nl,
1908 print(' -strict raise error if model-checking finds counter example'),nl,
1909 print(' or trace checking fails or any error state found'),nl,
1910 print(' -expcterr ERR expect error to occur (ERR=cbc,mc,ltl,...)'),nl,
1911 print(' -animate Nr random animation (max. Nr steps)'),nl,
1912 print(' -animate_all random animation until a deadlock is reached'),nl,
1913 print(' -animate_stats provide feedback which operations are executed'),nl,
1914 print(' -execute Nr execute first operation found without storing states (max. Nr steps)'),nl,
1915 print(' -execute_all execute first operation found until a deadlock is reached'),nl,
1916 print(' -his File write history to File'),nl,
1917 print(' -his_option O additional option when writing a history (show_init,show_states,json,trace_file)'),nl,
1918 print(' -sptxt File save constants and variable values of last discovered state to File'),nl,
1919 print(' -sstxt Dir save constants and variable values of all discovered states to files in Dir'),nl,
1920 print(' -cache Directory automatically save constants to files and avoid recomputation'),nl,
1921 print(' -det_check check if animation steps are deterministic'),nl,
1922 print(' -det_constants only check if SETUP_CONSTANTS step is deterministic'),nl,
1923 ( \+ option_verbose -> true ;
1924 print(' -i interactive animation. Only for interactive sessions,'),nl,
1925 print(' the output can arbitrarily change in future versions. '),nl,
1926 print(' Do not build automatic tools using the interactive mode'),nl
1927 ),
1928 print(' -repl start interactive read-eval-loop'),nl,
1929 print(' -eval "E" evaluate expression or predicate'),nl,
1930 print(' -eval_file FILE evaluate expression or predicate from file'),nl,
1931 print(' -c print coverage statistics'),nl,
1932 print(' -cc Nr Nr print and check coverage statistics'),nl,
1933 print(' -vacuity_check look for vacuous implications in invariant'),nl,
1934 print(' -cbc_redundant_invariants Nr find redundant invariants, expecting Nr'),nl, % Nr exepcted
1935 print(' -statistics print memory and other statistics at the end'),nl,
1936 print(' -p PREF Val set preference to value'),nl,
1937 print(' -prefs FILE set preferences from Prolog file'),nl,
1938 print(' -pref_group GROUP SETTING set group of preferences to predefined values'),nl,
1939 print(' -card GS Val set scope of B deferred set'),nl,
1940 print(' -goal "PRED" set GOAL predicate for model checker'),nl,
1941 print(' -check_goal check GOAL (after -mc, -t, or -animate)'),nl,
1942 print(' -scope "PRED"set scope predicate for model checker'),nl,
1943 print(' -s Port start socket server on given port'),nl,
1944 print(' -ss start socket server on port 9000'),nl,
1945 print(' -sf start socket server on some free port'),nl,
1946 print(' -l LogFile log activities in LogFile'),nl,
1947 print(' -ll log activities in /tmp/prob_cli_debug.log'),nl,
1948 print(' -lg LogFile analyse logfile using gnuplot'),nl,
1949 print(' -pp FILE pretty-print internal representation to file (or user_output)'), nl,
1950 print(' -ppf FILE like -pp, but force printing of all type infos'),nl,
1951 print(' -ppB FILE pretty-print Event-B model to file in valid B syntax'),nl,
1952 print(' -v verbose'),nl,
1953 print(' -mc_with_tlc model check using the model checker TLC'),nl,
1954 print(' -mc_with_lts_sym model check using the model checker LTSmin (symbolic)'),nl,
1955 print(' -mc_with_lts_seq model check using the model checker LTSmin (sequential)'),nl,
1956 %% print(' -vv very verbose'),nl, % no effect when debugging calls disabled
1957
1958 ( \+ option_verbose -> true ;
1959 print(' -ltsmin_option OPT set option for LTSmin (e.g, por)'),nl,
1960 print(' -ltsmin_ltl_output FILE set output file for LTSMin'),nl,
1961 print(' -symbolic_model_check ALGO ALGO is bmc, kinduction, ctigar, ic3'),nl
1962 ),
1963 print(' -version print version information (-svers for short info)'),nl,
1964 print(' -check_java_version check that Java version compatible with ProB parser'),nl,
1965 print(' -assertions check ASSERTIONS'),nl,
1966 print(' -main_assertions check ASSERTIONS from main file only'),nl,
1967 print(' -properties check PROPERTIES'),nl,
1968 print(' -cache Dir use directory "Dir" to cache constants and variables'),nl,
1969 print(' -ltlfile F check LTL formulas in file F'),nl,
1970 print(' -ltlassertions check LTL assertions (in DEFINITIONS)'),nl,
1971 print(' -ltllimit L explore at most L states when model-checking LTL or CTL'),nl,
1972 print(' -ltlformula \"F\" check the LTL formula F'),nl,
1973 print(' -ctlformula \"F\" check the CTL formula F'),nl,
1974 print(' -save File save state space for later refinement check'),nl,
1975 print(' -refchk File refinement check against previous saved state space'),nl,
1976 print(' -mcm_tests Depth MaxStates EndPredicate File'),nl,
1977 print(' generate test cases with maximum length Depth, explore'),nl,
1978 print(' maximally MaxStates, the last state satisfies EndPredicate'),nl,
1979 print(' and the test cases are written to File'),nl,
1980 print(' -mcm_cover Operation'),nl,
1981 print(' when generating MCM test cases, Operation should be covered'),nl,
1982 print(' -cbc_tests Depth EndPredicate File'),nl,
1983 print(' generate test cases by constraint solving with maximum'),nl,
1984 print(' length Depth, the last state satisfies EndPredicate'),nl,
1985 print(' and the test cases are written to File'),nl,
1986 print(' -cbc_cover Operation'),nl,
1987 print(' when generating CBC test cases, Operation should be covered'),nl,
1988 % print(' -cbc_cover_all try and cover all operations'),nl, % is now default if no cbc_cover provided
1989 print(' -test_description File'),nl,
1990 print(' read information for test generation from File'),nl,
1991 print(' -dot CMD File write a graph to a dot file, with CMD being one of:'),nl,
1992 (is_dot_command(Cmd),command_description(Cmd,_,Desc),
1993 format(' ~w : ~w~n',[Cmd,Desc]),fail
1994 ; true),
1995 print(' -dotexpr CMD Expr File write a graph for Expr to a dot file, with CMD:'),nl,
1996 (is_dot_command_for_expr(Cmd),command_description(Cmd,_,Desc),
1997 format(' ~w : ~w~n',[Cmd,Desc]),fail
1998 ; true),
1999 print(' -dot_output Path generate dot files for false assertions/properties'),nl,
2000 print(' -dot_all also generate dot files for true assertions/properties'),nl,
2001 print(' -csvhist E File evaluate expression over history and generate CSV file.'),nl,
2002 print(' -load_state File load state from a saved state (generated by PrB Tcl/Tk or -save_state)'),nl,
2003 % For Eclipse Version only
2004 %% print(' -parsercp CP class path of the B Parser, this has to be a valid Java class path'),nl,
2005 %% print(' -cspm load CSP-M .csp file rather than B Machine .mch/.ref/.imp File'),nl,
2006 %% print(' -csp load CSP-M .pl file rather than B Machine File'),nl,
2007
2008 /* Options -cspref, -cspdeadlock, -cspdeterministic, and -csplivelock are deprecated, should be excluded in favor of -csp_assertion */
2009 print(' -cspref Spec [m= Impl File'),nl,
2010 print(' checks a refinement statement,'),nl,
2011 print(' where Spec and Impl are processes from File, and \'m\' the type of the refinement:'),nl,
2012 print(' \'T\' for traces, \'F\' for failures, or \'FD\' for failures-divergences.'),nl,
2013 print(' -cspdeadlock P m File'),nl,
2014 print(' checks a process for deadlock,'),nl,
2015 print(' where \'P\' is a process from File, and \'m\' the type of the model:'),nl,
2016 print(' \'F\' for failures and \'FD\' for failures-divergences.'),nl,
2017 print(' -cspdeterministic P m File'),nl,
2018 print(' checks a process for determinism,'),nl,
2019 print(' where \'P\' is a process from File, and \'m\' the type of the model:'),nl,
2020 print(' \'F\' for failures and \'FD\' for failures-divergences.'),nl,
2021 print(' -csplivelock P File'),nl,
2022 print(' checks a process for divergence,'),nl,
2023 print(' where \'P\' is a process from File.'),nl,
2024 /* Options -cspref, -cspdeadlock, -cspdeterministic, and -csplivelock are deprecated, should be excluded in favor of -csp_assertion */
2025
2026 print(' -csp_assertion \"A\" File'),nl,
2027 print(' checks the CSP assertion \'A\' on file \'File\''),nl,
2028 print(' -csp_eval "E" evaluate CSP-M expression.'),nl,
2029 print(' -csp-guide File CSP||B: Use the CSP File to control the B machine'),nl,
2030 print(' '),nl,
2031 ( \+ option_verbose -> true
2032 ;
2033 print(' -test_mode set random seed to the Prolog\'s current random state'),nl,
2034 print(' -rc runtime checking of types/pre-/post-conditions'),nl,
2035 print(' -state_trace File read a file of B predicates (one per line) and try find a matching trace.'),nl
2036
2037 ),
2038 print(' FILE extensions are: '),nl,
2039 print(' .mch for B abstract machines'),nl,
2040 print(' .ref for B refinement machines'),nl,
2041 print(' .imp for B implementation machines'),nl,
2042 print(' .csp, .cspm for CSP-M files, same format as FDR'),nl,
2043 print(' .eventb for Event-B packages exported from Rodin ProB Plugin'),nl,
2044 print(' .tla for TLA+ models'),nl,
2045 ( option_verbose ->
2046 print(' Preferences PREF are: '),nl,
2047 print_eclipse_prefs
2048 ; otherwise ->
2049 print(' Use --help -v to print available preferences PREF'),nl
2050 ),
2051 print(' Set NO_COLOR environment variable to disable terminal colors'),nl,
2052 print(' More info at: http://www.stups.hhu.de/ProB/'),nl,
2053 print(' and at: http://www.prob2.de/probcli/'),nl,
2054 % http://www.stups.hhu.de/ProB/index.php5/Using_the_Command-Line_Version_of_ProB
2055 nl.
2056
2057
2058 set_argv(V) :-
2059 debug_println(20,set_argv(V)),
2060 external_functions:set_argv_from_atom(V).
2061
2062 :- use_module(state_space_exploration_modes,[set_depth_breadth_first_mode/1]).
2063 set_prefs :-
2064 if_option_set(socket(_), % then we may need the event(.) transition_info for the Java API
2065 preferences:set_preference(store_event_transinfo,true)),
2066 option(set_prefs_from_file(File)),
2067 debug_println(20,load_preferences(File)),
2068 preferences:load_preferences(File),
2069 fail.
2070 set_prefs :-
2071 option(set_preference_group(P,V)),
2072 debug_println(20,set_preference_group(P,V)),
2073 set_preference_group(P,V),
2074 fail.
2075 % eclipse preference or 'normal preference'
2076 set_prefs :-
2077 ? option(set_pref(P,V)),
2078 set_pref(P,V),
2079 fail.
2080 set_prefs :- option(set_card(P,V)),
2081 debug_println(20,set_card(P,V)),
2082 set_eclipse_card(P,V),
2083 fail.
2084 set_prefs :-
2085 ( option(breadth_first) -> set_depth_breadth_first_mode(breadth_first)
2086 ; option(depth_first) -> set_depth_breadth_first_mode(depth_first)
2087 ; option(depth_breadth_first_mode(M)) -> set_depth_breadth_first_mode(M)
2088 ; otherwise -> true
2089 ).
2090 :- use_module(tools_strings, [convert_cli_arg/2]).
2091 set_pref(P,V) :-
2092 debug_println(20,set_pref(P,V)),
2093 ? ( eclipse_preference(P,_)
2094 -> set_eclipse_preference(P,V)
2095 ; obsolete_eclipse_preference(P) -> probcli_add_light_warning('Obsolete preference: ',P)
2096 ; obsolete_preference(P) -> probcli_add_light_warning('Obsolete preference: ',P)
2097 ; % might be a term if its a plugin preference
2098 atom_codes(P,Codes),
2099 append(Codes,".",Codes2), % to make term readable by read_from_codes
2100 read_from_codes(Codes2,Preference),
2101 (nonvar(Preference),preference_val_type(Preference,_)
2102 -> convert_cli_arg(V,Value),
2103 set_preference(Preference,Value)
2104 ; add_error(probcli,'Illegal preference:',P)
2105 )
2106 ).
2107
2108 % add non severe warning:
2109 probcli_add_light_warning(Msg,Term) :- option(strict_raise_error),!,
2110 add_warning(probcli,Msg,Term). % does not write on user_error
2111 probcli_add_light_warning(Msg,Term) :- add_message(probcli,Msg,Term).
2112
2113 set_optional_errors :- % register optional/expected errors in the error_manager; avoid printing on stderr
2114 reset_optional_errors,
2115 ? (option(optional_error(Type)) ; option(expect_error(Type)) ; option(expect_error_pos(Type,_Line,_Col))),
2116 register_optional_error(Type),
2117 fail.
2118 set_optional_errors.
2119
2120 model_check(Nr,Time,ErrRes,NOW) :-
2121 option(timeout(TO)),!,
2122 safe_time_out(model_check(Nr,Time,ErrRes),TO,Res),
2123 (Res=time_out -> print('*** Timeout occurred while model checking: '), print(TO),nl,nl,
2124 writeln_log(timeout_occurred(NOW,model_check(Nr,Time,ErrRes))),
2125 Time=time_out(TO), ErrRes=time_out
2126 ; true).
2127 model_check(Nr,Time,ErrRes,_NOW) :- model_check(Nr,Time,ErrRes).
2128
2129 :- use_module(model_checker,[model_checking_is_incomplete/6]).
2130
2131 add_model_checking_warnings(FindInvViolations,FindDeadlocks,FindGoal,FindAssViolations) :-
2132 %print(check(model_checking_is_incomplete(FindInvViolations,FindDeadlocks,FindGoal,FindAssViolations,Msg,Term))),nl,
2133 model_checking_is_incomplete(FindInvViolations,FindDeadlocks,FindGoal,FindAssViolations,Msg,Term),
2134 nl,
2135 add_warning(model_check_incomplete,Msg,Term),
2136 fail.
2137 add_model_checking_warnings(_,_,_,_).
2138
2139 model_check(Nr,Time,ErrRes) :-
2140 statistics(runtime,[T1,_]),
2141 statistics(walltime,[W1,_]),
2142 (option(no_deadlocks) -> FindDeadlocks=0 ; FindDeadlocks=1),
2143 (option(no_invariant_violations) -> FindInvViolations=0 ; FindInvViolations=1),
2144 (option(no_goal) -> FindGoal=0 ; FindGoal=1),
2145 (option(no_assertion_violations)
2146 -> FindAssViolations=0
2147 ; FindAssViolations=1
2148 ),
2149 get_preference(por,POR),
2150 get_preference(pge,PGE),
2151 StopAtFullCoverage=0,
2152 %STOPMCAFTER = 86400000, /* 86400000 = 1 day timeout */
2153 STOPMCAFTER = 1152921504606846975, /* equals 13,343,998,895 days */
2154 InspectExistingNodes = 1,
2155 write_xml_element_to_log(model_checking_options,[find_deadlocks/FindDeadlocks,
2156 find_invariant_violations/FindInvViolations, find_goal/FindGoal,
2157 find_assertion_violations/FindAssViolations,
2158 partial_order_reduction/POR,
2159 partial_guard_evaluation/PGE,
2160 inspect_existing_nodes/InspectExistingNodes]),
2161 (user:do_model_check(Nr,NodesAnalysed,STOPMCAFTER,ErrRes,FindDeadlocks,FindInvViolations,FindGoal,FindAssViolations,StopAtFullCoverage,POR,PGE, InspectExistingNodes)
2162 -> (statistics(runtime,[T2,_]), statistics(walltime,[W2,_]),
2163 Time1 is T2-T1, WTime is W2-W1,
2164 (model_checker: expired_static_analysis_time(AnalysisTime) ->
2165 Time is Time1 - AnalysisTime
2166 ; Time = Time1),
2167 formatsilent('Model checking time: ~w ms (~w ms walltime)~n',[Time,WTime]),
2168 formatsilent('States analysed: ~w~n',[NodesAnalysed]),
2169 state_space: get_state_space_stats(_,NrTransitions,_),
2170 printsilent('Transitions fired: '),printsilent(NrTransitions),nls,
2171 write_xml_element_to_log(model_checking_statistics,
2172 [result/ErrRes,runtime/Time,walltime/WTime,states/NodesAnalysed,transitions/NrTransitions]),
2173 (ErrRes = no
2174 -> print('No counter example Found, not all nodes visited'),nl,
2175 add_warning(model_check_incomplete,'Not all nodes examined due to limit set by user: ',Nr)
2176 ; (ErrRes=all
2177 -> (tcltk_find_max_reached_node
2178 -> print('No counter example found. However, not all transitions were computed !')
2179 ; print_green('No counter example found. ALL nodes visited.')
2180 ),
2181 add_model_checking_warnings(FindInvViolations,FindDeadlocks,FindGoal,FindAssViolations)
2182 ; print_red('*** COUNTER EXAMPLE FOUND ***'),nl,
2183 debug_println(20,ErrRes),nl,
2184 user:translate_error_for_tclk(ErrRes,TclTkRes),
2185 print(TclTkRes),nl,
2186 (option(silent) -> true
2187 ; option(no_counter_examples) -> true
2188 ; user:tcltk_get_history(list(Hist)),
2189 length(Hist,Len),
2190 format('*** TRACE (length=~w):~n',[Len]),
2191 reverse(Hist,Trace),
2192 print_nr_list(Trace)
2193 ),
2194 error_occurred(TclTkRes)
2195 )
2196 ),nl
2197 )
2198 ; ( statistics(runtime,[T2,_]),
2199 Time1 is T2-T1,
2200 (model_checker: expired_static_analysis_time(AnalysisTime) ->
2201 Time is Time1 - AnalysisTime
2202 ; Time = Time1),
2203 printsilent('Model checking time: '), printsilent(Time), printsilent(' ms'),nls,
2204 print_error('*** Model checking FAILED '),nl,
2205 ErrRes=fail,
2206 definite_error_occurred)
2207 ).
2208
2209 % perform all cbc checks on current machine
2210 cbc_check(_NOW) :-
2211 option(cbc_deadlock_check(DeadlockGoalPred)),
2212 cbc_deadlock_check(DeadlockGoalPred),
2213 fail.
2214 cbc_check(_NOW) :-
2215 option(constraint_based_check(OpName)),
2216 constraint_based_check(OpName),
2217 fail.
2218 cbc_check(_NOW) :- option(cbc_assertions(AllowEnumWarning,Options)),
2219 cbc_assertions(AllowEnumWarning,Options),
2220 fail.
2221 %cbc_check(NOW) :-
2222 % option(cbc_pred(TargetPredString)),
2223 % check_loaded(cbc_pred),
2224 % print('% Starting Constraint-Based Check for Predicate: '), print(TargetPredString),nl,
2225 % b_set_up_valid_state_with_pred(NormalisedState,Pred) TO DO: add this feature
2226 cbc_check(_NOW) :- option(cbc_sequence(Sequence,TargetPredString,Findall)),
2227 cbc_sequence(Sequence,TargetPredString,Findall),
2228 fail.
2229 cbc_check(_NOW) :- option(cbc_refinement),
2230 cbc_refinement,
2231 fail.
2232 cbc_check(_NOW) :- option(cbc_redundant_invariants(NrExpected)),
2233 cbc_redundant_invariants(NrExpected),
2234 fail.
2235 cbc_check(_).
2236
2237 constraint_based_check(all) :-
2238 check_loaded(constraint_based_check),
2239 print_repl_prompt('% Starting Constraint-Based Check for all Operations: '),nl,
2240 start_xml_feature(cbc_operation_check,all_operations,true,FINFO),
2241 (tcltk_constraint_based_check(list(Result),ErrorsWereFound)
2242 -> print('% Constraint-Based Check Result: '),nl,
2243 print(Result),nl,
2244 write_result_to_file(Result),
2245 (ErrorsWereFound=true
2246 -> print_red('*** CONSTRAINT-BASED CHECK FOUND ERRORS ***'),nl, error_occurred(cbc)
2247 ; (ErrorsWereFound=false -> print_green('NO ERRORS FOUND'),nl)
2248 ; print_red('*** TIMEOUT OCCURRED ***'),nl,error_occurred(cbc)
2249 )
2250 ; write_result_to_file(cbc_check_failed), Result=internal_error, ErrorsWereFound=false,
2251 add_internal_error('ConstraintBasedCheck unexpectedly failed. ',cbc_check(all)),definite_error_occurred
2252 ),nl,
2253 write_xml_element_to_log(cbc_check_result,[result/Result,errors_were_found/ErrorsWereFound]),
2254 stop_xml_feature(cbc_operation_check,FINFO).
2255 constraint_based_check(OpName) :- OpName\=all, % -cbc OpName
2256 check_loaded(constraint_based_check),
2257 print_repl_prompt('% Starting Constraint-Based Check for Operation: '), print(OpName),nl,
2258 start_xml_feature(cbc_operation_check,operation,OpName,FINFO),
2259 (tcltk_constraint_based_check_with_timeout(OpName,Result)
2260 -> print('% Constraint-Based Check Result: '),nl, print(Result),nl,
2261 write_result_to_file(Result),
2262 (Result=time_out
2263 -> print_red('*** TIMEOUT OCCURRED ***'),nl, error_occurred(cbc)
2264 ; (Result=ok -> print_green('NO ERRORS FOUND'),nl)
2265 ; print_red('*** CONSTRAINT-BASED CHECK FOUND ERRORS ***'),nl,error_occurred(cbc) )
2266 ; write_result_to_file(constraint_based_check_failed), Result=internal_error,
2267 add_error(probcli,'ConstraintBasedCheck unexpectedly failed'),
2268 (b_is_operation_name(OpName) -> true
2269 ; add_error(probcli,'Unknown Operation Name: ',OpName)),
2270 definite_error_occurred
2271 ),nl,
2272 write_xml_element_to_log(cbc_check_result,[result/Result]),
2273 stop_xml_feature(cbc_operation_check,FINFO).
2274 cbc_deadlock_check(DeadlockGoalPred) :-
2275 print_repl_prompt('% Starting Constraint-Based DEADLOCK check '),nl,
2276 start_xml_feature(cbc_deadlock_check,FINFO),
2277 (tcltk_constraint_find_deadlock_state_with_goal(DeadlockGoalPred,false,Res)
2278 -> write_result_to_file(Res),
2279 (Res=time_out ->
2280 print_red('*** TIME_OUT occurred ***'),nl,
2281 error_occurred(cbc_deadlock_check_time_out)
2282 ; print_red('*** DEADLOCK state found ***'),nl,
2283 error_occurred(cbc_deadlock_check),
2284 (silent_mode(on) -> true
2285 ; print('*** STATE = '),nl,
2286 current_b_expression(DBState), translate:print_bstate(DBState),nl,
2287 print('*** END DEADLOCKING STATE '),nl
2288 )
2289 )
2290 ; write_result_to_file(no_deadlock_found), Res=no_deadlock_found,
2291 print_green('No DEADLOCK state found'),nl
2292 ),
2293 write_xml_element_to_log(cbc_check_result,[result/Res]),
2294 stop_xml_feature(cbc_deadlock_check,FINFO).
2295 cbc_assertions(AllowEnumWarning,Options) :-
2296 findall(OPT,option(cbc_option(OPT)),FullOptions,Options),
2297 check_loaded(cbc_assertions),
2298 print_repl_prompt('% Starting Constraint-Based static ASSERTIONS check '),nl,
2299 start_xml_feature(cbc_assertion_check,allow_enumeration_warning,AllowEnumWarning,FINFO),
2300 write_prolog_term_as_xml_to_log(options(Options)),
2301 (cbc_constraint_find_static_assertion_violation(Res,FullOptions)
2302 -> process_cbc_assertion_result(Res,AllowEnumWarning)
2303 ; write_result_to_file(cbc_assertions_failed), Res=internal_error,
2304 print_red('CBC Check failed'),nl,
2305 error_occurred(cbc_assertions_failure)
2306 ),
2307 write_xml_element_to_log(cbc_check_result,[result/Res]),
2308 stop_xml_feature(cbc_assertion_check,FINFO).
2309 cbc_sequence(Sequence,TargetPredString,Findall) :-
2310 check_loaded(cbc_sequence),
2311 print_repl_prompt('% Starting Constraint-Based Check for Sequence: '), print_repl_prompt(Sequence),
2312 start_xml_feature(cbc_sequence_check,sequence,Sequence,FINFO),
2313 (TargetPredString='' -> true ; print(' with target: '), print(TargetPredString)),
2314 nl,
2315 write_xml_element_to_log(options,[target_predicate/TargetPredString]),
2316 (tcltk_cbc_find_trace(Sequence,TargetPredString,Findall,Res)
2317 -> (Res=ok -> print_green('Sequence found and executed'),nl
2318 ; Res=time_out -> error_occurred(cbc_sequence_time_out)
2319 ; Res=no_solution_found -> print_red('*** NO SOLUTION FOUND '),error_occurred(cbc_sequence_no_solution_found)
2320 ; Res=nr_cbc_sols(NrSols) -> print('*** # SOLUTIONS FOUND: '),print(NrSols),nl
2321 ; print_red('*** Unknown result: '), print(Res),nl,
2322 error_occurred(cbc_sequence)
2323 )
2324 ; print('*** Internal error: Check failed '), error_occurred(cbc_sequence), Res=internal_error
2325 ),
2326 write_xml_element_to_log(cbc_check_result,[result/Res]),
2327 stop_xml_feature(cbc_sequence_check,FINFO).
2328 cbc_refinement :-
2329 check_loaded(cbc_refinement),
2330 print_repl_prompt('% Starting Constraint-Based static refinement check '),nl,
2331 start_xml_feature(cbc_refinement_check,FINFO),
2332 tcltk_cbc_refinement_check(list(Result),ErrorsWereFound),
2333 print('% Constraint-Based Refinement Check Result: '),nl,print(Result),nl,
2334 (ErrorsWereFound = time_out -> print_red('*** TIME_OUT occurred ***'),nl,error_occurred(cbc_refinement_time_out) ;
2335 ErrorsWereFound = true -> print_red('*** Refinement Violation found ***'),nl,error_occurred(cbc_refinement) ;
2336 otherwise -> print_green('No static Refinement Violation found'),nl
2337 ),
2338 write_xml_element_to_log(cbc_check_result,[errors_were_found/ErrorsWereFound]),
2339 stop_xml_feature(cbc_refinement_check,FINFO).
2340 cbc_redundant_invariants(NrExpected) :-
2341 check_loaded(cbc_redundant_invariants),
2342 print_repl_prompt('% Starting Constraint-Based invariant redundancy check'),nl,
2343 start_xml_feature(cbc_redundant_invariants,FINFO),
2344 cbc_find_redundant_invariants(Res,TimeoutOccured),
2345 length(Res,NrInvs),
2346 (Res = [] -> print_green('No redundant invariants found'),nl
2347 ; format('*** REDUNDANT INVARIANTS (~w) ***~n',[NrInvs]),
2348 prnt(1,Res), nl
2349 ),
2350 (NrExpected = NrInvs -> true
2351 ; format_with_colour(user_error,[red],'*** Expected ~w redundant invariants (instead of ~w).~n',[NrExpected,NrInvs]),
2352 error_occurred(cbc_redundant_invariants)),
2353 write_xml_element_to_log(cbc_redundant_invariants,[redundant_invariants/NrInvs, timeout_occured/TimeoutOccured]),
2354 stop_xml_feature(cbc_redundant_invariants,FINFO).
2355
2356 prnt(_,[]).
2357 prnt(N,[H|T]) :- format(' ~w : ~w~n',[N,H]), N1 is N+1, prnt(N1,T).
2358
2359 :- use_module(solver_interface,[predicate_uses_unfixed_deferred_set/2, unfixed_typed_id_in_list/3]).
2360 :- use_module(bsyntaxtree,[get_texpr_id/2]).
2361 process_cbc_assertion_result(time_out,_) :- !,
2362 write_result_to_file(no_counterexample_found('"TIME_OUT"')),
2363 print_red('*** TIME_OUT occurred ***'),nl,
2364 error_occurred(cbc_assertions_time_out).
2365 process_cbc_assertion_result(no_counterexample_exists(Constants,TotPredicate,OtherInfo),AllowEnumWarning) :- !,
2366 print_green('No counter-example to ASSERTION exists '),(OtherInfo=[] -> true ; print(OtherInfo)),nl,
2367 (unfixed_typed_id_in_list(TID,CType,Constants) % TO DO: look only at component
2368 -> write_deferred_set_used(AllowEnumWarning),
2369 get_texpr_id(TID,CID),pretty_type(CType,CTypeS),
2370 format('Warning: Some constants use deferred sets (e.g., ~w:~w) which have only been checked for a single cardinality!~n',[CID,CTypeS])
2371 ; predicate_uses_unfixed_deferred_set(TotPredicate,CType)
2372 -> write_deferred_set_used(AllowEnumWarning),pretty_type(CType,CTypeS),
2373 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
2374 ; write_result_to_file(no_counterexample_exists)
2375 %,print('Computing unsat core: '),nl,unsat_cores:unsat_core(TotPredicate,Core),print('CORE: '),translate:print_bexpr(Core),nl
2376 ). % WE HAVE A PROOF
2377 process_cbc_assertion_result(no_counterexample_found,AllowEnumWarning) :- !,
2378 write_result_to_file(no_counterexample_found('"Enumeration Warning"')),
2379 print('No counter-example for ASSERTION found (*enumeration warning occured*)'),nl,
2380 (AllowEnumWarning=true -> true ; error_occurred(cbc_assertions_enumeration_warning)).
2381 process_cbc_assertion_result(counterexample_found,_) :- !,
2382 write_result_to_file(counterexample_found),
2383 print_red('*** Counter-example for ASSERTION found ***'),nl,
2384 error_occurred(cbc_assertions),
2385 (silent_mode(on) -> true
2386 ; print('*** STATE = '),nl,
2387 current_b_expression(DBState), translate:print_bstate(DBState),nl,
2388 print('*** END ASSERTION counter-example STATE '),nl
2389 ),
2390 (get_dot_file('cbc_assertions',DFile) -> generate_dot_from_assertions(DFile) ; true).
2391 process_cbc_assertion_result(Res,A) :-
2392 write_result_to_file(Res),
2393 add_internal_error('Unknown: ',process_cbc_assertion_result(Res,A)).
2394
2395
2396 write_deferred_set_used(AllowEnumWarning) :-
2397 write_result_to_file(no_counterexample_found('"Deferred Sets Used"')),
2398 (AllowEnumWarning=true -> true ; error_occurred(cbc_assertions_enumeration_warning)).
2399
2400 :- use_module(tools_io,[safe_open_file/4]).
2401 write_result_to_file(Result) :- option(cbc_result_file(FILE)),
2402 safe_open_file(FILE,write,Stream,[]),
2403 !,
2404 write(Stream,Result),
2405 close(Stream).
2406 write_result_to_file(_).
2407
2408
2409
2410 if_option_set(Option,Call) :-
2411 if_option_set(Option,Call,true).
2412 if_option_set(Option,Then,Else) :-
2413 ( option(Option) -> call(Then)
2414 ; otherwise -> call(Else)).
2415 ifm_option_set(Option,Call) :-
2416 ifm_option_set(Option,Call,true).
2417 ifm_option_set(Option,Then,Else) :- % can perform multiple options
2418 findall(Then,option(Option),As),
2419 (As=[] -> call(Else) ; perform(As)).
2420 perform([]).
2421 perform([A|T]) :- call(A), perform(T).
2422 if_option_set_loaded(Option,Action,Call) :-
2423 ( (option(Option),check_loaded(Action)) ->
2424 call(Call)
2425 ; otherwise -> true).
2426 ifm_option_set_loaded(Option,Action,Call) :- % can perform multiple options
2427 findall(Call,(option(Option),check_loaded(Action)),As), perform(As).
2428
2429
2430
2431 if_options_set(Option,Call) :- % allow multiple solutions for Option
2432 option(Option),call(Call),fail.
2433 if_options_set(_,_).
2434
2435 print_options :- print('CLI OPTIONS: '),nl,
2436 option(Option), print(Option), nl, fail.
2437 print_options :- nl.
2438
2439 :- use_module(enabling_analysis,[infeasible_operation_cache/1]).
2440 :- use_module(sap,[explore_and_generate_testcases/7,cbc_gen_test_cases_from_string/5, tcl_get_stored_test_cases/1]).
2441
2442 mcm_test_case_generation(ADepth,AMaxStates,ATarget,Output) :-
2443 arg_is_number(ADepth,MaxDepth),
2444 arg_is_number(AMaxStates,MaxStates),
2445 bmachine:b_parse_machine_predicate(ATarget,Target),!,
2446 get_comma_or_space_separated_options(mcm_cover,Events),
2447 (option(silent) -> true
2448 ; print('mcm test case generation, maximum search depth: '),print(MaxDepth),nl,
2449 print('mcm test case generation, maximum number of states: '),print(MaxStates),nl,
2450 print('mcm test case generation, target state predicate: '),print_bexpr(Target),nl,
2451 print('mcm test case generation, output file: '),print(Output),nl,
2452 print('mcm test case generation, events to cover: '),print_list(Events),nl
2453 ),
2454 explore_and_generate_testcases(Events,Target,MaxDepth,MaxStates,Output,NumTests,Uncovered),
2455 printsilent('mcm test case generation, generated test cases: '),printsilent(NumTests),nls,
2456 print_uncovered('mcm test case generation, ',Uncovered).
2457 mcm_test_case_generation(_ADepth,_AMaxStates,_ATarget,_Output) :-
2458 print_error('### MCM Test Case Generation failed'),
2459 error_occurred(mcm_tests).
2460
2461 cbc_test_case_generation(ADepth,TargetString,Output) :-
2462 arg_is_number(ADepth,MaxDepth),
2463 ( option(cbc_cover_all) -> Events=all
2464 ; (get_comma_or_space_separated_options(cbc_cover,Events), Events \= []) -> true
2465 ; Events=all ),
2466 (\+ option(cbc_cover_final) -> FEvents = Events
2467 ; Events=all -> FEvents=all,
2468 add_error(cbc_cover_final,'Option cbc_cover_final not compatible with trying to cover all events')
2469 ; FEvents = final(Events),
2470 println_silent('constraint based test case generation, target events considered final')),
2471 printsilent('constraint based test case generation, maximum search depth: '),printsilent(MaxDepth),nls,
2472 printsilent('constraint based test case generation, target state predicate: '),printsilent(TargetString),nls,
2473 printsilent('constraint based test case generation, output file: '),printsilent(Output),nls,
2474 (TargetString = '#not_invariant' ->
2475 printsilent('constraint based test case generation, performing bounded model checking'),nls
2476 ; option(silent) -> true
2477 ; print('constraint based test case generation, events to cover: '),print_list(Events),nl),
2478 cbc_gen_test_cases_from_string(FEvents,TargetString,MaxDepth,Output,Uncovered),
2479 !,
2480 %print('mcm test case generation, generated test cases: '),print(NumTests),nl,
2481 (TargetString = '#not_invariant'
2482 -> tcl_get_stored_test_cases(list(Tests)), %print(tests(Tests)),nl,
2483 (Tests=[] -> print_green('No counterexample found'),nl
2484 ; Tests = [_|_] -> add_error(invariant_violation,'Invariant violation found by bmc')
2485 ; add_internal_error('Unexpected bmc result: ',Tests))
2486 ; (Uncovered=[_|_],option(strict_raise_error))
2487 -> add_error(cbc_tests,'Uncovered events: ',Uncovered)
2488 ; print_uncovered('constraint based test case generation, ',Uncovered)
2489 ).
2490 cbc_test_case_generation(_ADepth,_ATarget,_Output) :-
2491 print_error('### CBC Test Case Generation failed'),
2492 error_occurred(cbc_tests).
2493
2494 print_uncovered(Msg,Uncovered) :-
2495 include(infeasible_operation_cache,Uncovered,Infeasible),
2496 (Infeasible=[]
2497 -> format('~wuncovered events: ',[Msg]),print_list(Uncovered),nl
2498 ; format('~winfeasible uncovered events: ',[Msg]),print_list(Infeasible),nl,
2499 exclude(infeasible_operation_cache,Uncovered,Feasible),
2500 format('~wuncovered events: ',[Msg]),print_list(Feasible),nl
2501 ).
2502
2503 print_list(all) :- print('** all **').
2504 print_list(list(L)) :- print_list(L). % possibly not used
2505 print_list([]) :- print('** none **').
2506 print_list([H|T]) :- length([H|T],Len), format('(~w) ',[Len]),
2507 print(H),print(' '),print_list2(T).
2508 print_list2([]).
2509 print_list2([H|T]) :- print(H),print(' '),print_list2(T).
2510
2511 get_comma_or_space_separated_options(Option,Selection) :-
2512 functor(O,Option,1),
2513 findall(E, (option(O),arg(1,O,CommaSep),
2514 split_by_seperator(CommaSep,Es),
2515 member(E,Es)),
2516 Selection).
2517
2518 split_by_seperator(NonAtomic,Res) :- \+ atomic(NonAtomic),!, Res=[NonAtomic].
2519 split_by_seperator(String,Strings) :-
2520 atom_chars(String,Chars),
2521 split_by_seperator2(Chars,Strings).
2522 split_by_seperator2(Chars,Result) :-
2523 append(AChars,[X|B],Chars),seperator(X),!,
2524 (AChars=[] -> Result=Rest ; atom_chars(A,AChars), Result=[A|Rest]),
2525 split_by_seperator2(B,Rest).
2526 split_by_seperator2(Chars,[String]) :- atom_chars(String,Chars).
2527
2528 seperator(',').
2529 seperator(' ').
2530 seperator(';').
2531
2532 ltl_check_assertions :-
2533 (option(ltl_limit(Limit)) -> true; Limit= -1), % -1 means no limit
2534 print('LTL Model checking assertions'),nl,
2535 ltl_check_assertions(Limit,Outcome),
2536 ( Outcome = pass -> print_green('LTL check passed'),nl
2537 ; Outcome = fail -> print_red('*** LTL check failed'),nl,error_occurred(ltl)
2538 ; Outcome = no_tests -> print_red('*** No LTL assertions found, test failed'),nl,definite_error_occurred
2539 ; otherwise -> print_red('*** An error occurred in the LTL assertion test'),nl,
2540 definite_error_occurred).
2541
2542 :- use_module(probltlsrc(ltl),[parse_ltlfile/2]).
2543 ltl_check_file(Filename) :-
2544 (option(ltl_limit(Limit)) -> true; Limit= -1), % -1 means no limit
2545 print_repl_prompt('LTL Model checking assertions'),nl,
2546 parse_ltlfile(Filename, Formulas),
2547 ( real_error_occurred ->
2548 print_red('An error occurred while parsing the LTL file.\n'), fail
2549 ; otherwise ->
2550 ltl_check_formulas(Formulas,Limit)).
2551
2552 :- use_module(probltlsrc(ltl),[ltl_model_check2/4]).
2553 ltl_check_formulas([],_) :-
2554 print_green('All LTL formulas checked.\n').
2555 ltl_check_formulas([formula(Name,F)|Rest],Limit) :-
2556 print('Checking formula '),print(Name),print(':\n'),
2557 ltl_model_check2(F,Limit,init,Status),
2558 ( Status == no ->
2559 print_red('Counter-example found for formula \"'),print_red(Name),
2560 print_red('\", saving trace file.\n'),
2561 ajoin(['ltlce_', Name, '.trace'], Tracefile),
2562 tcltk_save_history_as_trace_file(prolog,Tracefile),
2563 add_error(ltl_counterexample,'Counter-example was found')
2564 ; Status == ok ->
2565 ltl_check_formulas(Rest,Limit)
2566 ; Status == incomplete ->
2567 ajoin(['Model was not completly model-checked, aborted after ',Limit,' new states'],
2568 Msg),
2569 add_error(ltl,Msg)
2570 ; otherwise ->
2571 ajoin(['Model checker returns unexpected result (',Status,')'],Msg),
2572 add_error(ltl,Msg)).
2573
2574 cli_ltl_model_check(Formula,ExpectedStatus,Status) :-
2575 (option(ltl_limit(Max)) -> true; Max = -1), % -1 means no limit
2576 start_xml_feature(ltl_model_check,formula,Formula,FINFO),
2577 ltl_model_check(Formula,Max,init,Status),
2578 write_xml_element_to_log(model_check_result,[status/Status,expected_status/ExpectedStatus]),
2579 check_status(Status,ExpectedStatus,Formula,ltl),
2580 stop_xml_feature(ltl_model_check,FINFO).
2581
2582 cli_ctl_model_check(Formula,ExpectedStatus,Status) :-
2583 (option(ltl_limit(Max)) -> true; Max = -1), % -1 means no limit
2584 start_xml_feature(ctl_model_check,formula,Formula,FINFO),
2585 ctl_model_check(Formula,Max,init,Status),
2586 write_xml_element_to_log(model_check_result,[status/Status,expected_status/ExpectedStatus]),
2587 check_status(Status,ExpectedStatus,Formula,ctl),
2588 stop_xml_feature(ctl_model_check,FINFO).
2589
2590 check_expected(St,Exp,Mode) :-
2591 (St=Exp -> true ; add_error(Mode,'Unexpected model checking result: ',Mode:St)).
2592
2593 check_status(ok,Expected,Formula,ltl) :- !, % TO DO: make uniform ? CTL returns true; LTL returns ok
2594 format_with_colour(user_output,[green],'LTL Formula TRUE.~nNo counter example found for ~w.~n',[Formula]),
2595 flush_output(user_output),
2596 check_expected(true,Expected,ltl).
2597 check_status(true,Expected,Formula,ctl) :- !,
2598 format_with_colour(user_output,[green],'CTL Formula TRUE.~nNo counter example found for ~w.~n',[Formula]),
2599 flush_output(user_output),
2600 check_expected(true,Expected,ctl).
2601 check_status(incomplete,Expected,Formula,LTLorCTL) :- !,
2602 incomplete_warning(LTLorCTL,Warning),
2603 add_warning(Warning, 'Warning: Model Check incomplete for: ', Formula),nl,
2604 format('No counter example found so far for ~w.~n',[Formula]),
2605 check_expected(incomplete,Expected,LTLorCTL).
2606 check_status(NO,Expected,Formula,LTLorCTL) :- (NO=no ; NO=false),!, % TO DO: make uniform
2607 (Expected==false -> format_with_colour(user_error,[red],'Model Check Counter-Example found for: ~w~n',[Formula])
2608 ; add_error(LTLorCTL, 'Model Check Counter-Example found for: ', Formula),nl
2609 ),
2610 print('Formula '), print('FALSE.'),nl,
2611 %print('Counter example found for '),print(Formula),print('.'),nl,
2612 nl,
2613 check_expected(false,Expected,LTLorCTL).
2614 check_status(Status,Expected,Formula,LTLorCTL) :-
2615 add_internal_error('Unknown status: ', check_status(Status,Expected,Formula,LTLorCTL)).
2616
2617 incomplete_warning(ltl,ltl_incomplete) :- !.
2618 incomplete_warning(ctl,ctl_incomplete) :- !.
2619 incomplete_warning(X,X).
2620
2621 evaluate_from_commandline :-
2622 retractall(eval_result(_,_)),
2623 option(eval_string_or_file(A,B,Q,E)), %print(eval(A,B,Q,E)),nl,
2624 % treat eval_string and eval_file together to ensure proper order of evaluation
2625 % (only possible side-effect at the moment: formula can add new machine_string facts)
2626 eval_string_or_file(A,B,Q,E),
2627 fail.
2628 evaluate_from_commandline :- print_eval_results,
2629 % treat -repl option or -replay File option
2630 (option(eval_repl([File1|TF]))
2631 -> (evaluate_expressions([File1|TF]) -> true ; true)
2632 ; option(eval_repl([]))
2633 -> (evaluate_expressions([]) -> true ; true)
2634 ; true).
2635
2636 :- dynamic eval_result/2.
2637 add_eval_result(R) :- retract(eval_result(R,N)),!,
2638 N1 is N+1, assert(eval_result(R,N1)).
2639 add_eval_result(R) :- assert(eval_result(R,1)).
2640 print_eval_results :- findall(R/N, eval_result(R,N), L), sort(L,SL),
2641 (SL=[] -> true ; format('Evaluation results: ~w~n',[SL])).
2642
2643 :- use_module(tools_printing,[print_error/1, format_error/2]).
2644 eval_string_or_file(string,String,_,Expected) :-
2645 set_current_probcli_command(eval_string(String)),
2646 print('eval: '), print(String),nl,
2647 reset_error_spans, % avoid underlining previous errors in eval_string
2648 eval_string_with_time_out(String,StringResult,EnumWarning,_LS),
2649 % print(enumwarning(EnumWarning,Expected)),nl,
2650 add_eval_result(StringResult),
2651 (Expected\=StringResult
2652 -> format_error('### Evaluation error, expected result to be: ~w (but was ~w)~n',[Expected,StringResult]),
2653 error_occurred(eval_string)
2654 ; EnumWarning = false -> true
2655 ; gen_enum_warning(Expected) % now also generate enum warnings when Expected not set (eval instead of evalt/evalf)
2656 ),
2657 unset_current_probcli_command.
2658 eval_string_or_file(file,File,Quantifier,Expected0) :-
2659 % evaluate a single formula stored in a file
2660 set_current_probcli_command(eval_file(File)),
2661 turn_show_error_source_off, % reduce clutter in user feedback; eval_file used in ProB Logic Calculator for example
2662 (Expected0 == print_file -> formatsilent('~nEvaluating file: ~w~n',[File])
2663 ; Expected = Expected0, debug_println(10,eval_file(File,Quantifier,Expected)),nl
2664 ),
2665 error_manager:reset_error_scopes, % TO DO: avoid that exceptions mess up error scopes in eval_string/file
2666 statistics(runtime,[Start,_]),nl,
2667 (Expected=='TRUE' -> TypeInfo=predicate(_) % avoids parsing as expression
2668 ; true),
2669 (eval_file(File,Quantifier,Result,EnumWarning,TypeInfo)
2670 -> add_eval_result(Result),
2671 (EnumWarning = false -> true ; gen_enum_warning(EnumWarning)),
2672 (Result\=Expected -> print_error('### Error, expected result to be: '),
2673 print_error(Expected),
2674 print_error('### File: '), print_error(File),
2675 error_occurred(eval_file)
2676 ; true)
2677 ; add_eval_result(eval_file_failed),
2678 print_error('### Eval from file failed: '), print_error(File),
2679 error_occurred(eval_file)
2680 ),
2681 (debug_mode(on) -> statistics(runtime,[Stop,_]), Time is Stop - Start,
2682 print(File),print(' time: '), print(Time), print(' ms'),nl
2683 ; true),
2684 turn_show_error_source_on,
2685 unset_current_probcli_command.
2686
2687 gen_enum_warning(time_out) :- !,error_occurred(eval_string_time_out).
2688 gen_enum_warning(_) :- print_error('### Enumeration warning occurred'),
2689 error_occurred(eval_string_enum_warning,warning).
2690 repl :- evaluate_expressions([]).
2691 :- use_module(parsercall,[ensure_console_parser_launched/0]).
2692 evaluate_expressions(StartFiles) :- nl,
2693 print('ProB Interactive Expression and Predicate Evaluator '), nl,
2694 print('Type ":help" for more information.'),nl,
2695 turn_show_error_source_off, % reduce clutter in user feedback
2696 (option(evaldot(File))
2697 -> print('Solutions written to dot file: '), print(File),nl
2698 ; true
2699 ),
2700 print_repl_prompt, % >>>
2701 (ensure_console_parser_launched
2702 -> maplist(set_repl_input_file(verbose),StartFiles),
2703 top_level_eval
2704 ; print('>>> ABORTING REPL'),nl),
2705 turn_show_error_source_on.
2706
2707 :- use_module(user_interrupts,[interruptable_call/1]).
2708 top_level_eval :-
2709 catch(top_level_eval1, halt(0), (format('~s', ["Bye."]), nl)).
2710
2711 :- use_module(tools_printing,[start_terminal_colour/2, reset_terminal_colour/1, print_red/1, print_green/1]).
2712 print_repl_prompt :- print_repl_prompt('>>> ').
2713 print_repl_prompt(P) :- reset_terminal_colour(user_output), write(P).
2714 %print_repl_prompt(P) :- start_terminal_colour(dark_gray,user_output), write(P), reset_terminal_colour(user_output).
2715
2716 top_level_eval1 :-
2717 (interruptable_call(eval1) -> true
2718 ; print_red('Evaluation failed or interrupted'),nl,
2719 print_repl_prompt('Use :q to quit REPL'),nl),
2720 print_repl_prompt, % >>>
2721 top_level_eval1.
2722 eval :- store_last_error_location_for_repl,
2723 reset_errors, % get_errors prints errors again and quits in -strict mode
2724 print_repl_prompt, % >>>
2725 garbage_collect, eval1.
2726 eval1 :- repl_multi_read_line(Expr), eval_probcli_repl_line(Expr).
2727
2728 :- dynamic last_repl_error/2.
2729 store_last_error_location_for_repl :-
2730 retractall(last_repl_error(_,_)),
2731 check_error_span_file_linecol(_,File,Line,_,_,_),!,
2732 assert(last_repl_error(File,Line)).
2733 store_last_error_location_for_repl.
2734
2735 :- dynamic current_repl_input_stream/2.
2736 close_repl_input_stream(file_closed) :- retract(current_repl_input_stream(X,File)),!,
2737 format(":replayed ~w~n",[File]),
2738 close(X).
2739 close_repl_input_stream(no_file).
2740 :- use_module(tools_io,[safe_open_file/4]).
2741 set_repl_input_file(_,File) :- current_repl_input_stream(_,File),!,
2742 add_error(set_repl_input_file,'Cyclic file replay: ',File).
2743 set_repl_input_file(Verbose,File) :-
2744 % close_repl_input_stream, % this way we allow one REPL file to call another
2745 safe_open_file(File,read,Stream,[]),!,
2746 (Verbose=verbose -> format('Replaying REPL commands in file: ~w~n',[File]) ; true),
2747 asserta(current_repl_input_stream(Stream,File)).
2748 set_repl_input_file(_,_).
2749
2750 repl_multi_read_line(Line) :-
2751 (current_repl_input_stream(Stream,_)
2752 -> repl_multi_read_line_aux(Stream,[],Line),
2753 format('~s~n',[Line])
2754 ; repl_multi_read_line_aux(user_input,[],Line)
2755 ).
2756 repl_multi_read_line_aux(Stream,SoFar,Line) :-
2757 read_line(Stream,L),
2758 (L=end_of_file -> close_repl_input_stream(FileC),
2759 ((SoFar=[], FileC = file_closed)
2760 -> print_repl_prompt, % >>>
2761 repl_multi_read_line(Line) % last line of file empty; do not process
2762 ; FileC = file_closed -> Line=SoFar
2763 ; Line=end_of_file) % user pressed CTRL-D
2764 ; append(LFront,[92],L) % line ends with slash
2765 -> append(SoFar,LFront,NewSoFar), print_repl_prompt('... '),
2766 repl_multi_read_line_aux(Stream,NewSoFar,Line)
2767 ; append(SoFar,L,Line)).
2768
2769 :- use_module(eval_strings).
2770 :- dynamic trace_eval/0.
2771
2772 generate_atom_list([],[],R) :- !, R=[].
2773 generate_atom_list([],Last,[NewAtom]) :-
2774 reverse(Last,RL),
2775 atom_codes(NewAtom,RL).
2776 generate_atom_list([39|X],[],[QuotedAtom|T]) :- !,
2777 get_quoted_atom(X,[],QuotedAtom,Rest),
2778 strip_leading_ws(Rest,X2),
2779 generate_atom_list(X2,[],T).
2780 generate_atom_list([32|X],Last,[NewAtom|T]) :- !,
2781 reverse(Last,RL),
2782 atom_codes(NewAtom,RL),
2783 strip_leading_ws(X,X2),
2784 generate_atom_list(X2,[],T).
2785 generate_atom_list([H|X],Last,Res) :- generate_atom_list(X,[H|Last],Res).
2786
2787 get_quoted_atom([],Acc,QuotedAtom,[]) :- reverse(Acc,R), atom_codes(QuotedAtom,R).
2788 get_quoted_atom([39|T],Acc,QuotedAtom,T) :- !, reverse(Acc,R), atom_codes(QuotedAtom,R).
2789 get_quoted_atom([H|T],Acc,QuotedAtom,Rest) :- get_quoted_atom(T,[H|Acc],QuotedAtom,Rest).
2790
2791
2792 strip_leading_ws([32|X],R) :- !, strip_leading_ws(X,R).
2793 strip_leading_ws(X,X).
2794
2795 :- meta_predicate call_probcli_option(0).
2796 call_probcli_option(_:Option) :- just_assert_option(Option), !,
2797 (option(Option) -> true ; assert_option(Option)).
2798 call_probcli_option(_:statistics) :- !, % avoid calling SICS version
2799 cli_print_statistics.
2800 call_probcli_option(Option) :-
2801 on_exception(error(existence_error(A,B),E),
2802 call(Option),treat_existence_error(A,B,E,Option)).
2803
2804 % commands that require no execution; just asserting option(.)
2805 just_assert_option(depth_first).
2806 just_assert_option(breadth_first).
2807 just_assert_option(strict_raise_error).
2808 just_assert_option(no_deadlocks).
2809 just_assert_option(no_invariant_violations).
2810 just_assert_option(no_goal).
2811 just_assert_option(no_ltl).
2812 just_assert_option(no_assertion_violations).
2813 just_assert_option(no_counter_examples).
2814
2815 :- use_module(tools_printing,[format_with_colour/4]).
2816 treat_existence_error(source_sink,File,E,Option) :- !,
2817 format_with_colour(user_error,[red],
2818 '* Could not find file ~w~n* for probcli command ~w~n* Detailed error: ~w~n',[File,Option,E]).
2819 treat_existence_error(_,_,E,Option) :-
2820 format_with_colour(user_error,[red],
2821 '* probcli command not yet supported in REPL: ~w~n* Error: ~w~n',[Option,E]).
2822
2823 reload_mainfile :- file_loaded(_,MainFile),
2824 reset_errors,
2825 print_repl_prompt('Reloading and initialising file: '), print_repl_prompt(MainFile),nl,
2826 clear_loaded_files,
2827 load_main_file(MainFile,0,_),
2828 get_errors,
2829 cli_start_animation(0),
2830 cli_start_initialisation(0).
2831
2832 % REPL EVAL LOOP:
2833 eval_probcli_repl_line(end_of_file) :- !, eval_line(end_of_file).
2834 eval_probcli_repl_line(Line) :- strip_ws(Line,SLine),
2835 on_exception(E,eval_line(SLine),
2836 (E=halt(_) -> throw(E) % e.g., coming from :quit; will be caught above
2837 ; add_error(repl,'Uncaught Exception in REPL: ',E))).
2838
2839 % strip whitespace at end and beginning
2840 strip_ws([H|T],Res) :- is_ws(H),!, strip_ws(T,Res).
2841 strip_ws(C,Res) :- reverse(C,CR), strip_ws2(CR,SCR), reverse(SCR,Res).
2842 strip_ws2([H|T],Res) :- is_ws(H),!, strip_ws2(T,Res).
2843 strip_ws2(R,R).
2844
2845 is_ws(32).
2846
2847 :- use_module(performance_messages,[toggle_perfmessages/0]).
2848 eval_line([]) :- !, print_repl_prompt('Type :q or :quit to quit.'),nl,eval.
2849 eval_line(end_of_file) :- !, halt_exception(0).
2850 % Haskell GHCI like syntax
2851 eval_line(":r") :- !, eval_line("--reload").
2852 eval_line(":reload") :- !, eval_line("--reload").
2853 eval_line("--reload") :- !,
2854 (reload_mainfile -> true ; get_errors,print_repl_prompt('### Error(s) occured during reload (use :e to jump to first error)'),nl),
2855 eval.
2856 % TO DO: other Haskell commands :info E :l FILE , let pattern = expression
2857 eval_line(":prefs") :- !,print_eclipse_prefs, eval.
2858 eval_line([45|Command]) :- % -command
2859 generate_atom_list([45|Command],[],ArgV),
2860 %print(argv(ArgV)),nl,
2861 % try and parse like commands passed to probcli
2862 get_options(ArgV,recognised_cli_option,Options,[],fail),
2863 print_repl_prompt('Executing probcli command: '),print_repl_prompt(Options),nl,!,
2864 (maplist(call_probcli_option,Options) -> true
2865 ; print_red('Failed to execute probcli arguments'),nl),
2866 eval.
2867 eval_line("+") :- !, add_last_expression_to_unit_tests, eval.
2868 eval_line("$+") :- !, preferences:temporary_set_preference(expand_avl_upto,-1,CHNG),
2869 print_last_value,preferences:reset_temporary_preference(expand_avl_upto,CHNG),
2870 eval.
2871 %eval_line("$$") :- !, print_last_expression, eval. % now in eval_strings
2872 eval_line("$$$") :- !, % $$0 - $$9 commands to print last expression with indentation
2873 indent_print_last_expression, eval.
2874 %eval_line("$") :- !, print_last_info, eval. % now in eval_strings
2875 eval_line("!trace") :- !, eval_line("^").
2876 eval_line("^") :- !,
2877 (retract(trace_eval) -> print_repl_prompt('TRACING OFF'),nl
2878 ; assert(trace_eval), print_repl_prompt('TRACING ON'),nl), eval.
2879 eval_line("!observe") :- !, toggle_observe_evaluation.
2880 eval_line("!v") :- !, tcltk_turn_debugging_off.
2881 eval_line("!p") :- !, toggle_perfmessages.
2882 eval_line("!perf") :- !, toggle_perfmessages.
2883 eval_line("!profile") :- !, eval_line("%").
2884 eval_line("%") :- !, print_repl_prompt('PROFILING : '), %spy([avl:avl_size/2]),
2885 (current_prolog_flag(profiling,on)
2886 -> set_prolog_flag(profiling,off), print('OFF') ;
2887 set_prolog_flag(profiling,on), print('ON')),
2888 nl,print_repl_prompt('USE %% to print profile info'),nl,eval.
2889 eval_line("%%") :- !, nl,print_repl_prompt('PROFILE INFORMATION:'), nl,
2890 on_exception(error(existence_error(_,_),_),print_profile, print_red('CAN ONLY BE USED WHEN RUNNING PROB FROM SOURCE')),
2891 nl, debug:timer_statistics,
2892 eval.
2893 eval_line("%%%") :- !, nl,print('PROFILE INFORMATION (Starting TK Viewer):'), nl,
2894 on_exception(error(existence_error(_,_),_),
2895 (use_module(library(gauge)),gauge:view), print_red('CAN ONLY BE USED WHEN RUNNING PROB FROM SOURCE')),
2896 nl,eval.
2897 eval_line("!debug") :- !, nl,print_repl_prompt('ENTERING PROLOG DEBUG MODE:'),
2898 on_exception(error(existence_error(_,_),_),debug, print_red('CAN ONLY BE USED WHEN RUNNING PROB FROM SOURCE')),
2899 nl,
2900 eval.
2901 eval_line("@") :- !, get_preference(find_abort_values,OldVal),
2902 print_repl_prompt('Try more aggressively to detect ill-defined expressions: '),
2903 (OldVal=true -> Val=false ; Val=true), print(Val),nl,
2904 temporary_set_preference(find_abort_values,Val) , eval.
2905 eval_line("!") :- !, toggle_eval_det,eval.
2906 eval_line("!norm") :- !, toggle_normalising,eval.
2907 eval_line(Codes) :- parse_eval_command(Codes,CommandName,Argument),!,
2908 debug_println(9,executing_eval_command(CommandName,Argument)),
2909 (exec_eval_command(CommandName,Argument) -> eval
2910 ; format_with_colour(user_error,[red,bold],'Command ~w failed~n',[CommandName]), eval).
2911 eval_line(ExpressionOrPredicate) :- (trace_eval -> trace ; true),
2912 (eval_codes(ExpressionOrPredicate,exists,_,_,_,_)
2913 -> eval ; print_red('Evaluation failed'),nl,eval).
2914
2915 parse_eval_command([C|Rest],CommandName,Argument) :- [C]=":",
2916 eval_command(Cmd,CommandName),
2917 append(Cmd,RestArg,Rest),
2918 (RestArg = [Letter1|_] -> is_ws(Letter1) /* otherwise command name continues */ ; true),
2919 strip_ws(RestArg,Argument),
2920 (eval_command_help(CommandName,[],_), Argument = [_|_]
2921 -> format_with_colour(user_error,[red],'WARNING: Command ~w does not take arguments!~n',[CommandName])
2922 ; eval_command_help(CommandName,[_|_],_), Argument = []
2923 -> format_with_colour(user_error,[red],'WARNING: Command ~w requires arguments!~n',[CommandName])
2924 ; true).
2925
2926 % TO DO: some of these commands should also be made available in the Tcl/Tk Console
2927 eval_command("q",quit).
2928 eval_command("quit",quit).
2929 eval_command("halt",quit).
2930 eval_command("x",exit).
2931 eval_command("exit",exit).
2932 eval_command("f",find).
2933 eval_command("find",find).
2934 eval_command("*",apropos).
2935 eval_command("apropos",apropos).
2936 eval_command("help",help).
2937 eval_command("h",help).
2938 eval_command("?",help).
2939 eval_command("ctl",ctl).
2940 eval_command("ltl",ltl).
2941 eval_command("statistics",statistics).
2942 eval_command("stats",statistics).
2943 eval_command("states",state_space_stats).
2944 eval_command("state",show_state_info).
2945 eval_command("u",unsat_core).
2946 eval_command("core",unsat_core).
2947 eval_command("show",show_last_as_table). % :show
2948 eval_command("dot",show_last_as_dot(no_dot_viewing)). % :dot
2949 eval_command("dotty",show_last_as_dot(dotty)).
2950 eval_command("dotpdf",show_last_as_dot(dot)).
2951 eval_command("sfdp",show_last_as_dot(sfdp)).
2952 eval_command("browse",browse). % :browse
2953 eval_command("b",browse).
2954 eval_command("hbrowse",hbrowse). % :hbrowse
2955 eval_command("replay",replay_repl_file). % :replay
2956 eval_command("src",show_source).
2957 eval_command("source",show_source).
2958 eval_command("origin",show_origin).
2959 eval_command("edit",edit_main_file).
2960 eval_command("e",edit_main_file). % :e
2961 eval_command("comment",comment).
2962
2963 available_commands(SLC) :-
2964 findall(Cmd,(eval_command(Cs,_),atom_codes(Cmd,[58|Cs])), LC),
2965 sort(LC,SLC).
2966
2967 eval_command_help(exit,[],'Exit ProB').
2968 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').
2969 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)').
2970 eval_command_help(ctl,['F'],'Check CTL formula F; CTL Syntax: ExUy,EXx,AXx,EFx,AGx,EX[Op]x,e(Op),{B-Pred}').
2971 eval_command_help(browse,opt('PAT'),'Browse available constants, variables, sets and lets introduced in REPL').
2972 eval_command_help(apropos,['PAT'],'Find constant or variable whose names contains PAT').
2973 eval_command_help(hbrowse,['PAT'],'Browse machine hierarchy for all identifiers whose names contains PAT').
2974 eval_command_help(show_last_as_table,[],'Show last evaluated expression in tabular form').
2975 eval_command_help(show_last_as_dot(_),['F'],'Show expression or predicate F as dot graph').
2976 eval_command_help(unsat_core,[],'Compute Unsatisfiable Core of last evaluated predicate').
2977 eval_command_help(help,opt('CMD'),'Provide help about REPL command CMD').
2978 eval_command_help(replay_repl_file,['FILE'],'Replay FILE of REPL commands').
2979 eval_command_help(show_source,['ID'],'Show origin and source code definition of identifier ID').
2980 eval_command_help(show_origin,['ID'],'Show origin of identifier ID and try opening in EDITOR').
2981 eval_command_help(state_space_stats,[],'Show statistics about state space').
2982 eval_command_help(show_state_info,[],'Show current state').
2983 eval_command_help(statistics,[],'Show statistics about last evaluation').
2984 % implemented in eval_strings:
2985 eval_command_help(type,['E'],'Show type of expression E').
2986 eval_command_help(cvc4,['P'],'Solve predicate P using CVC4 solver').
2987 eval_command_help(kodkod,['P'],'Solve predicate P using SAT solver via Kodkod').
2988 eval_command_help(z3,['P'],'Solve predicate P using Z3 solver').
2989 eval_command_help(edit_main_file,opt('ID'),'Edit main file (or origin of identifier ID) using EDITOR (path_to_text_editor preference)').
2990 eval_command_help(comment,['STRING'],'provide STRING as a comment (mainly useful for :replay files)').
2991
2992 print_eval_command_help(Codes) :-
2993 eval_command(Codes,Cmd),
2994 eval_command_help(Cmd,Args,Descr),
2995 (Args = []
2996 -> format('Command ~w~n Syntax :~s~n ~w~n',[Cmd,Codes,Descr])
2997 ; Args=[Arg] -> format('Command ~w~n Syntax :~s ~w~n ~w~n',[Cmd,Codes,Arg,Descr])
2998 ; Args=opt(Arg) -> format('Command ~w~n Syntax :~s [~w]~n ~w~n',[Cmd,Codes,Arg,Descr])
2999 ; format('Command ~w~n Syntax :~s ~w~n ~w~n',[Cmd,Codes,Args,Descr])).
3000
3001 :- use_module(tools_commands,[show_dot_file/1, show_ps_file/1, gen_dot_output/4]).
3002 exec_eval_command(quit,_) :- !, halt_exception(0).
3003 exec_eval_command(exit,_) :- !,halt.
3004 exec_eval_command(browse,CodesToMatch) :- !,
3005 (CodesToMatch=[] -> browse % maybe merge with apropos functionality
3006 ; exec_eval_command(apropos,CodesToMatch)).
3007 exec_eval_command(find,FORMULA) :-
3008 atom_codes(APF,FORMULA),cli_find_ltl_ap(APF).
3009 exec_eval_command(apropos,CodesToMatch) :- /* :* Pattern (apropos command) */
3010 browse_machine(CodesToMatch).
3011 exec_eval_command(hbrowse,CodesToMatch) :- /* :* Pattern (apropos command) */
3012 browse_all_machines(CodesToMatch).
3013 exec_eval_command(help,Arg) :-
3014 (Arg=[] -> eval_help
3015 ; print_eval_command_help(Arg) -> true
3016 ; (Arg=[58|RA],print_eval_command_help(RA)) -> true % remove : at front
3017 ; format('Cannot provide help about ~s~n',[Arg]),
3018 available_commands(LC), format('Available commands: ~w~n',[LC])
3019 ).
3020 exec_eval_command(ctl,FORMULA) :-
3021 atom_codes(F,FORMULA),
3022 (cli_ctl_model_check(F,_,Status)
3023 -> (Status=false -> write_history_to_user_output([show_init,show_states]) ; true)
3024 ; print('CTL Syntax: ExUy,EXx,AXx,EFx,AGx,EX[Op]x,e(Op),{B-Pred}'),nl).
3025 exec_eval_command(ltl,FORMULA) :-
3026 atom_codes(F,FORMULA),
3027 (cli_ltl_model_check(F,_,Status)
3028 -> (Status=no -> write_history_to_user_output([show_init,show_states]) ; true)
3029 ; print('LTL Operators: G,F,X,U,W,R,not,&,or,=>'),nl,
3030 print('LTL Propositions: {B-Pred}, e(Op), [Op], true, false, sink'),nl,
3031 print('Past-LTL Operators: Y,H,O,S,T (dual to X,G,F,U,R)'),nl
3032 ).
3033 exec_eval_command(statistics,_) :- !, print_last_info.
3034 exec_eval_command(state_space_stats,_) :- !, state_space:get_state_space_stats(TotalNodeSum,TotalTransSum,ProcessedTotal),
3035 format('Statespace: ~w states (~w processed) and ~w transitions.~n',[TotalNodeSum,ProcessedTotal,TotalTransSum]).
3036 exec_eval_command(show_state_info,_) :- !,
3037 current_expression(ID,CurState),
3038 format('Current state ~w : ',[ID]),translate:print_bstate(CurState),nl.
3039 exec_eval_command(unsat_core,_) :- !, % :core
3040 unsat_core_last_expression.
3041 exec_eval_command(show_last_as_table,_) :- !, % :show
3042 show_last_expression_as_table.
3043 exec_eval_command(show_last_as_dot(Show),Arg) :- !,
3044 (Arg = [] -> print('*** :dot requires an expression or predicate as argument.'),nl
3045 ; safe_absolute_file_name('~/probcli_repl.dot',AFile),
3046 set_eval_dot_file(AFile),
3047 format('Displaying evaluation result in: ~w~n',[AFile]),
3048 (eval_codes(Arg,exists,_,_,_,_) -> true ; true), unset_eval_dot_file,
3049 ( Show=no_dot_viewing -> true
3050 ; Show=dotty -> show_dot_file(AFile)
3051 ; safe_absolute_file_name('~/probcli_repl.pdf',PDFFile),
3052 gen_dot_output(AFile,Show,pdf,PDFFile),
3053 show_ps_file(PDFFile) % we assume psviewer can also open pdf
3054 )).
3055 exec_eval_command(replay_repl_file,FILEC) :- !,
3056 atom_codes(File,FILEC),
3057 set_repl_input_file(not_verbose,File).
3058 exec_eval_command(show_source,IDC) :- !,
3059 atom_codes(ID,IDC),
3060 show_source(ID).
3061 exec_eval_command(show_origin,IDC) :- !,
3062 atom_codes(ID,IDC),
3063 show_origin(ID).
3064 exec_eval_command(edit_main_file,Arg) :- !,
3065 (Arg=[] -> edit_main_file ; exec_eval_command(show_origin,Arg)).
3066 exec_eval_command(comment,_Arg) :- !. % do nothing; argument was a comment; mainly useful for :replay files
3067
3068 :- use_module(tools_commands,[edit_file/2]).
3069 edit_main_file :- last_repl_error(File,Line),!,
3070 format('Showing first error from last command~n',[]),
3071 edit_file(File,Line).
3072 edit_main_file :- file_loaded(true,MainFile),!,edit_file(MainFile,unknown).
3073 % Note: for the bbedit command we can also specify line numbers bbedit +LINE FILE
3074 edit_main_file :- format_with_colour(user_error,[red],'No file loaded, cannot open EDITOR!~n',[]).
3075
3076
3077
3078 :- use_module(probsrc(error_manager),[extract_file_line_col/6]).
3079 open_file_at_position(OriginTerm) :-
3080 extract_file_line_col(OriginTerm,FILE,LINE,_COL,_Erow,_Ecol),
3081 edit_file(FILE,LINE).
3082
3083
3084 show_source(ID) :- source_code_for_identifier(ID,Kind,_Type,OriginStr,OriginTerm,Source),!,
3085 translate:translate_subst_or_bexpr(Source,PPS),
3086 %format('~w: ~w (Type: ~w)~norigin: ~w~nsource: ~w~n',[Kind,ID,_Type,Origin,PPS]).
3087 format('~w: ~w~norigin: ~w~nsource: ~w~n',[Kind,ID,OriginStr,PPS]),
3088 (OriginTerm=b(_,_,_),bsyntaxtree:get_texpr_description(OriginTerm,Description)
3089 -> format('description: ~w~n',[Description]) ; true).
3090 show_source(ID) :- format('### Could not find source for ~w~n',[ID]).
3091
3092 show_origin('') :- last_repl_error(_,_),!, % error occured: show error in editor like :e would
3093 edit_main_file.
3094 show_origin('') :- !,format('### You need to provided an identifier~n',[]).
3095 show_origin(ID) :- source_code_for_identifier(ID,Kind,_Type,OriginStr,OriginTerm,_Source),!,
3096 format('~w: ~w~norigin: ~w~n',[Kind,ID,OriginStr]),
3097 open_file_at_position(OriginTerm).
3098 show_origin(ID) :- format('### Could not find origin for ~w~n',[ID]).
3099
3100 profiling_on :- set_prolog_flag(profiling,on), print('% PROFILING ON'),nl.
3101
3102 % find a state satisfying LTL atomic property
3103 cli_find_ltl_ap(APF) :-
3104 if(ltl:find_atomic_property_formula(APF,ID),
3105 (format('Found state (id = ~w) satisfying LTL atomic property.~n',[ID]),
3106 user:tcltk_goto_state('LTL FIND',ID)),
3107 format('No explored state satsifies LTL atomic property.~n',[])).
3108
3109 eval_help :-
3110 print('ProB Interactive Expression and Predicate Evaluator '), nl,
3111 print('Type a valid B expressions or predicates, followed by RETURN or ENTER.'),nl,
3112 print('You can spread input over multiple lines by ending lines with "\\".'),nl,
3113 browse_machine([]),
3114 print('You can also type one of the following commands: '),nl,
3115 (option_verbose ->
3116 print(' + to save last expression to ProB unit tests.'),nl,
3117 print(' ! to go to deterministic propagation only mode.'),nl
3118 ; true),
3119 print(' let x = E to define a new local variable x and :b to browse the variables'),nl,
3120 print(' :t E to get the type of an expression and :r to reload the machine'),nl,
3121 print(' :show to display the last result as a table (if possible)'),nl,
3122 print(' :list CAT to display information with CAT : {files,variables,help,...}'),nl,
3123 print(' :* P to display constants/variables containing pattern P'),nl,
3124 print(' :core to compute the unsat core for last result'),nl,
3125 print(' :stats to print the type and evaluation time for last query'),nl,
3126 print(' -PROBCLIARGS to pass command-line probcli arguments to the REPL'),nl,
3127 print(' :ctl F or :ltl F to check a CTL or LTL formula.'),nl,
3128 print(' :f F to find a state satisfying LTL atomic property.'),nl,
3129 print(' :exec S to execute an operation or substitution S.'),nl,
3130 print(' :help CMD to obtain more help about a command.'),nl,
3131 print(' :replay FILE to replay a file of commands.'),nl,
3132 print(' :z3 P, :cvc4 P, :kodkod P to solve predicate P using alternate solver'),nl,
3133 print(' :states, :source, :orgin, :dot, :dotty, :sfdp - use :help for more info'),nl,
3134 print(' :q to exit.'),nl.
3135
3136
3137 browse :- browse_machine([]), browse_repl_lets.
3138
3139 :- use_module(prob2_interface,[get_machine_identifiers/2]).
3140 % the CodesToMatch parameters mimics the apropos command of the Clojure-REPL
3141 browse_machine(CodesToMatch) :-
3142 get_machine_identifiers(machines,MN), display_match('MACHINES',CodesToMatch,MN),
3143 (CodesToMatch =[] -> print_sets
3144 ; get_machine_identifiers(sets,SN), display_match('SETS',CodesToMatch,SN),
3145 get_machine_identifiers(set_constants,SCN), display_match('SETS-ELEMENTS',CodesToMatch,SCN)
3146 ),
3147 get_machine_identifiers(definition_files,DFN),
3148 (DFN=[] -> true ; display_match('DEFINITIONS FILES',CodesToMatch,DFN)),
3149 get_machine_identifiers(definitions,DN),
3150 (DN=[] -> true ; display_match('DEFINITIONS',CodesToMatch,DN)),
3151 get_machine_identifiers(constants,CN),
3152 display_match('CONSTANTS',CodesToMatch,CN),
3153 get_machine_identifiers(variables,VN),
3154 display_match('VARIABLES',CodesToMatch,VN),
3155 get_machine_identifiers(operations,Ops),
3156 display_match('OPERATIONS',CodesToMatch,Ops).
3157
3158 display_match(KIND,CodesToMatch,Ids) :- display_match(KIND,CodesToMatch,Ids,show_empty).
3159 display_match(KIND,CodesToMatch,Ids,ShowEmpty) :-
3160 include(atom_contains_codes(CodesToMatch),Ids,MatchingIds),
3161 length(MatchingIds,LenMIds),
3162 (LenMIds=0, ShowEmpty=show_only_if_match -> true
3163 ; sort(MatchingIds,SMatchingIds),
3164 (CodesToMatch=[]
3165 -> format(' ~w: ~w ~w~n',[KIND,LenMIds,SMatchingIds])
3166 ; length(Ids,LenIds),
3167 format('Matching ~w: ~w/~w ~w~n',[KIND,LenMIds,LenIds,SMatchingIds]))
3168 ).
3169
3170 % check if an atom contains a list of codes in its name
3171 atom_contains_codes([],_) :- !.
3172 atom_contains_codes(Codes,Name) :- atom_codes(Name,NC), append(Codes,_,C),
3173 append(_,C,NC).
3174
3175 print_sets :- print('Available SETS: '), b_global_set(GS), print_set(GS),fail.
3176 print_sets :- nl.
3177
3178 print_set(GS) :- print(GS), \+ is_b_global_constant(GS,_,_),!, print(' ').
3179 print_set(GS) :- print(' = {'), is_b_global_constant(GS,_,Cst), print(Cst), print(' '),fail.
3180 print_set(_) :- print(' } ').
3181
3182 :- use_module(b_machine_hierarchy,[get_machine_identifier_names/7]).
3183 % browse all machines, shows identifiers maybe not visible at top-level
3184 browse_all_machines(CodesToMatch) :-
3185 format('Searching machine hierarchy for identifiers matching ~s~n',[CodesToMatch]),
3186 get_machine_identifier_names(Name,Params,Sets,AVars,CVars,AConsts,CConsts),
3187 format('~nMACHINE ~w~n',[Name]),
3188 display_match('PARAMS',CodesToMatch,Params,show_only_if_match),
3189 display_match('SETS',CodesToMatch,Sets,show_only_if_match),
3190 display_match('ABSTRACT_VARIABLES',CodesToMatch,AVars,show_only_if_match),
3191 display_match('CONCRETE_VARIABLES',CodesToMatch,CVars,show_only_if_match),
3192 display_match('ABSTRACT_CONSTANTS',CodesToMatch,AConsts,show_only_if_match),
3193 display_match('CONCRETE_CONSTANTS',CodesToMatch,CConsts,show_only_if_match),
3194 fail.
3195 browse_all_machines(_).
3196
3197
3198 % showing relations as tables:
3199
3200 :- use_module(table_tools).
3201 show_last_expression_as_table :- \+ last_expression(_,_Expr,_Value),!,
3202 print_red('Please evaluate an expression or predicate first.'),nl.
3203 show_last_expression_as_table :-
3204 get_last_result_value(Expr,_,Value),
3205 print_value_as_table(Expr,Value).
3206
3207
3208 % a few definitions so that probcli commands work in REPL:
3209
3210 :- public pretty_print_internal_rep/3, pretty_print_internal_rep_to_B/1.
3211 pretty_print_internal_rep(PPFILE,TYPES,unicode) :- !,
3212 set_unicode_mode, b_write_machine_representation_to_file(TYPES,PPFILE),unset_unicode_mode.
3213 pretty_print_internal_rep(PPFILE,TYPES,_) :- b_write_machine_representation_to_file(TYPES,PPFILE).
3214
3215 pretty_print_internal_rep_to_B(PPFILE) :- b_write_eventb_machine_to_classicalb_to_file(PPFILE).
3216
3217
3218 % Simple Animator
3219
3220 animate_machine :- nl,print('IMPORTANT: Do not use this mode for automatic tools.'),nl,
3221 print('The output format can change arbitrarily in future versions.'),nl,
3222 print('Please terminate your input with a dot (.) and then type return.'),nl,nl,
3223 animate_machine2.
3224
3225 animate_machine2 :-
3226 print_current_state,
3227 cli_computeOperations(Ops),
3228 length(Ops,Max),
3229 print('Enabled Operations: '),nl,
3230 print_options(Ops,1),
3231 print(' ==> '),!,
3232 read(Nr),
3233 ((number(Nr),Nr>0,Nr=<Max)
3234 -> cli_animateOperationNr(Nr,Ops,0)
3235 ; fail
3236 ),!,
3237 animate_machine2.
3238 animate_machine2.
3239
3240 print_current_state :- getCurrentStateID(CurID), print('ID ==> '), print(CurID),nl,
3241 getStateValues(CurID,State),
3242 print_bindings(State),
3243 ((specfile:b_or_z_mode,\+is_initialised_state(CurID))
3244 -> print_red(' Not yet initialised.'),print_mode_info, debug_println(10,state(State)) ; nl).
3245
3246 print_mode_info :- animation_mode(M), (animation_minor_mode(MM) -> true ; MM=''),
3247 format('Animation Mode = ~w [~w]~n',[M,MM]).
3248
3249 cli_computeOperations(Ops) :- option(animate_stats),!, % provide statistics about the animation
3250 nl,
3251 start_probcli_timer(Timer),
3252 computeOperations(Ops),
3253 stop_probcli_timer(Timer,'Time: ').
3254 cli_computeOperations(Ops) :- computeOperations(Ops).
3255
3256 cli_animateOperationNr(Nr,Options,StepNr) :-
3257 (option(animate_stats)
3258 -> nth1(Nr,Options,Action),
3259 truncate_animate_action(Action,TA),
3260 (StepNr>1 -> format('performing step ~w : ~w~n',[StepNr,TA])
3261 ; format('performing ~w~n',[TA]))
3262 ; true),
3263 executeOperationNr_on_computed_node(Nr).
3264
3265 % optionally truncate animation action atom for printing:
3266 truncate_animate_action(Action,TA) :-
3267 (option_verbose -> TA = Action
3268 ; \+ atom(Action) -> TA = Action
3269 ; truncate_atom(Action,100,TA)).
3270
3271 perform_random_step(StepNr) :- perform_random_step(_Ops,_Len,_RanChoice,StepNr).
3272 perform_random_step(Ops,Len,RanChoice,StepNr) :-
3273 cli_computeOperations(Ops),
3274 getCurrentStateID(CurID), check_for_errors(CurID,StepNr),
3275 length(Ops,Len), Len>0,
3276 debug_println(20,perform_random_step(Len,StepNr)),
3277 L1 is Len+1,
3278 ((do_det_checking, Len>1)
3279 -> print_error('### Non-deterministic step in animate or init'),
3280 print_error('### State:'),
3281 print_current_state, print_error('### Enabled Operations: '), print_options(Ops,1),
3282 error_occurred(det_check)
3283 ; true),
3284 random(1,L1,RanChoice),
3285 debug_println(20,random(L1,RanChoice)),
3286 cli_animateOperationNr(RanChoice,Ops,StepNr).
3287
3288 :- use_module(state_space,[visited_expression/2]).
3289 check_for_errors(CurID,StepNr) :- invariant_violated(CurID),
3290 \+ option(no_invariant_violations),
3291 get_preference(do_invariant_checking,true),
3292 tools:ajoin(['INVARIANT VIOLATED after ',StepNr,' steps (state id ',CurID,').'],ErrMsg),
3293 format('~w~n',[ErrMsg]),
3294 visited_expression(CurID,CurState), print_state_silent(CurState),
3295 error_occurred_with_msg(invariant_violation,ErrMsg),
3296 fail.
3297 check_for_errors(CurID,_) :- get_state_errors(CurID).
3298 % TO DO: also check for assertion errors, goal, state_errors with abort
3299
3300 do_det_checking :- option(det_check),!.
3301 do_det_checking :- option(det_constants_check),getCurrentStateID(root),
3302 b_mode, b_machine_has_constants_or_properties.
3303
3304 perform_random_steps(Nr,_) :- \+ number(Nr),!,
3305 print_error('### Argument to animate not a number'), print_error(Nr),error_occurred(animate).
3306 perform_random_steps(Nr,_) :- Nr<0, !,
3307 print_error('### Argument to animate is a negative number'), print_error(Nr),error_occurred(animate).
3308 perform_random_steps(0,_) :- !.
3309 perform_random_steps(Nr,ErrorOnDeadlock) :-
3310 perform_random_initialisation_if_necessary(Steps), % if Nr=1 we currently will also execute the INITIALISATION ! TO DO: fix
3311 perform_random_steps_aux(Steps,Nr,ErrorOnDeadlock).
3312
3313 perform_random_steps_aux(Nr,Max,_) :- Nr >= Max,!, debug_println(9,performed_random_steps(Nr)).
3314 perform_random_steps_aux(Nr,Max,ErrorOnDeadlock) :-
3315 N1 is Nr+1,
3316 (perform_random_step(N1)
3317 -> perform_random_steps_aux(N1,Max,ErrorOnDeadlock)
3318 ; /* deadlock */
3319 write_xml_element_to_log(deadlock_found,[step/Nr]),
3320 (ErrorOnDeadlock=true, \+ option(no_deadlocks)) ->
3321 print_error('### Deadlock occurred during -animate, at step number:'), print_error(Nr),
3322 error_occurred(animate)
3323 ; print('% Deadlock occurred during -animate, at step number:'), print(Nr),nl
3324 ).
3325
3326 perform_random_initialisation_if_necessary(Steps) :-
3327 ? b_mode, getCurrentStateID(State), State=root,!, perform_random_initialisation(Steps).
3328 perform_random_initialisation_if_necessary(0).
3329
3330 perform_random_initialisation :- perform_random_initialisation(_).
3331 perform_random_initialisation(Steps) :- getCurrentStateID(State), State \= root, !,
3332 print_error('### init can only be used in initial state'), print_error(State),error_occurred(initialisation),
3333 Steps=0.
3334 ?perform_random_initialisation(Steps) :- b_mode, b_machine_has_constants_or_properties,!,
3335 (perform_random_step(Ops,_Len,RanChoice,1)
3336 -> nth1(RanChoice,Ops,Choice), %print(Choice),nl,
3337 (Choice = 'PARTIAL_SETUP_CONSTANTS'
3338 -> error_occurred(setup_constants_inconsistent)
3339 ; true)
3340 ; error_occurred(setup_constants_fails),fail), % $setup_constants
3341 perform_random_init_after_setup_constants, Steps=2. % $initialise_machine
3342 perform_random_initialisation(Steps) :- (perform_random_step(1) -> Steps=1 ; error_occurred(initialisation_fails),fail).
3343
3344
3345 perform_random_init_after_setup_constants :- \+ option(initialise), we_need_only_static_assertions(_),!,
3346 print('% NOT INITIALISING MACHINE (not required)'),nl.
3347 % debug_println(20,'% NOT INITIALISING MACHINE (not required)').
3348 perform_random_init_after_setup_constants :-
3349 (perform_random_step(2) % 2 is the step nr not the number of steps
3350 -> true ; error_occurred(initialisation_fails),fail).
3351
3352 :- use_module(enabling_analysis,[tcltk_cbc_enabling_analysis/1, print_enable_table/1, is_timeout_enabling_result/1]).
3353 do_enabling_analysis_csv(EnablingCsvFile,NOW) :-
3354 start_probcli_timer(Timer1),
3355 start_xml_feature(enabling_analysis,file,EnablingCsvFile,FINFO),
3356 tcltk_cbc_enabling_analysis(list(R)),
3357 stop_probcli_timer(Timer1,'% Finished CBC Enabling Analysis',_TotWallTime),
3358 print_cbc_stats(R,NOW),
3359 debug_println(9,writing_to_file(EnablingCsvFile)),
3360 my_tell(EnablingCsvFile),
3361 print_enable_table(R),
3362 told,!,
3363 stop_xml_feature(enabling_analysis,FINFO).
3364 do_enabling_analysis_csv(EnablingCsvFile,_) :-
3365 add_error(enabling_analysis,'Enabling analysis failed',EnablingCsvFile),
3366 stop_xml_group_in_log(enabling_analysis).
3367
3368 print_cbc_stats(Res,_NOW) :- length(Res,Len), Ops is Len-2, % Header + Init
3369 CBC_Calls is Ops*(Ops+1), % +1 for INITIALISATION
3370 findall(TO,(member(list([_|T]),Res), member(TO,T),is_timeout_enabling_result(TO)),TOS),
3371 length(TOS,NrTOS),
3372 format('% CBC Enabling Stats:~n% Nr of events: ~w~n% Nr of cbc calls: ~w, Timeout results: ~w~n',[Ops,CBC_Calls,NrTOS]),
3373 write_xml_element_to_log(cbc_enabling_stats,[nr_events/Ops,cbc_calls/CBC_Calls,nr_timeouts/NrTOS]).
3374
3375
3376 :- use_module(enabling_analysis,[feasible_operation_with_timeout/3]).
3377 do_feasibility_analysis(ATimeOut,EnablingCsvFile) :-
3378 arg_is_number(ATimeOut,TimeOut),
3379 start_xml_feature(feasibility_analysis,file,EnablingCsvFile,FINFO),
3380 findall(list([Op,Res]),feasible_operation_with_timeout(Op,TimeOut,Res),R),
3381 debug_println(9,writing_to_file(EnablingCsvFile)),
3382 my_tell(EnablingCsvFile),
3383 print_enable_table([list(['Event','Feasibility'])|R]),
3384 told,!,
3385 stop_xml_feature(feasibility_analysis,FINFO).
3386 do_feasibility_analysis(_,EnablingCsvFile) :-
3387 add_error(feasibility_analysis,'Feasibility analysis failed',EnablingCsvFile),
3388 stop_xml_group_in_log(feasibility_analysis).
3389
3390 :- use_module(b_read_write_info,[tcltk_read_write_matrix/1]).
3391 generate_read_write_matrix(CsvFile) :-
3392 tcltk_read_write_matrix(list(Matrix)),
3393 my_tell(CsvFile),
3394 print_enable_table(Matrix),
3395 told,!.
3396 generate_read_write_matrix(CsvFile) :-
3397 add_error(read_write_matrix,'Generating Read-Write-Matrix failed',CsvFile).
3398
3399
3400 my_tell(File) :- on_exception(error(_E,_), % existence_error(_,_)
3401 tell(File), add_error_fail(tell,'File cannot be written to: ',File)).
3402
3403 print_options([],_).
3404 print_options([H|T],N) :-
3405 print(' '), print(N), print(':'), print(H),nl,
3406 N1 is N+1,
3407 print_options(T,N1).
3408
3409 print_nr_list(List) :- print_nr_list(List,0,1,no_repeats).
3410
3411 print_nr_list([],NM1,_,Repeats) :- !, print_repeats(NM1,Repeats).
3412 print_nr_list([H|T],_,N,repeated(H,SinceN)) :- !, N1 is N+1,
3413 print_nr_list(T,N,N1,repeated(H,SinceN)).
3414 print_nr_list([H|T],NM1,N,Repeats) :- !,
3415 print_repeats(NM1,Repeats),
3416 N1 is N+1,
3417 print_nr_list(T,N,N1,repeated(H,N)).
3418 print_nr_list(X,_,_,_) :- print('### not a list: '), print(X),nl.
3419
3420 print_repeats(N,repeated(H,N)) :- !,
3421 format(' ~w: ~w~n',[N,H]).
3422 print_repeats(N,repeated(H,Since)) :- !, Repeats is 1+N-Since,
3423 format(' ~w - ~w: ~w (~w repetitions)~n',[Since,N,H,Repeats]).
3424 print_repeats(_,_).
3425
3426 print_bindings([]) :- !.
3427 print_bindings([binding(Var,_,PPV)|T]) :- !, print(Var),print('='),print(PPV),
3428 (T=[] -> true ; print(', '), print_bindings(T)).
3429 print_bindings([binding(Var,_,PPV,_Tag)|T]) :- !, print(Var),print('='),print(PPV),
3430 (T=[] -> true ; print(', '), print_bindings(T)).
3431 print_bindings(X) :- print('### Internal Error: illegal binding list: '), print(X),nl.
3432
3433 :- dynamic expected_error_occurred/1.
3434 :- dynamic error_did_not_occur/1.
3435 reset_expected_error_occurred :- retractall(expected_error_occurred(_)).
3436 check_all_expected_errors_occurred(NOW) :-
3437 %error_manager:display_error_statistics,
3438 get_errors, get_state_space_errors,
3439 retractall(error_did_not_occur(_)),
3440 ? expected_error(Type),
3441 ? \+ expected_error_occurred(Type),
3442 print('*** Expected Error of following type to occur: '), print(Type),nl,
3443 writeln_log_time(expected_error_did_not_occur(NOW,Type)),
3444 assert(error_did_not_occur(Type)),
3445 (option(strict_raise_error) -> definite_error_occurred ; fail).
3446 check_all_expected_errors_occurred(_NOW) :-
3447 ? (expected_error(_)
3448 -> (error_did_not_occur(_) -> print('*** Some expected errors did NOT occur !')
3449 ; print('All expected errors occurred.')),nl
3450 ; true).
3451
3452 ?expected_error(Type) :- option(expect_error(Type)).
3453 expected_error(Type) :- option(expect_error_pos(Type,_Line,_Col)).
3454
3455 error_occurred(warning(Type)) :- !, error_occurred(Type,warning).
3456 error_occurred(Type) :- error_occurred(Type,error).
3457
3458 get_error_category_and_type(warning(Cat),Category,Type) :- !, Category=Cat,Type=warning.
3459 get_error_category_and_type(C,C,error).
3460
3461 error_occurred_with_msg(Type,Msg) :- error_occurred_with_msg(Type,Msg,not_yet_extracted).
3462 error_occurred_with_msg(warning(Type),Msg,Span) :- !, error_occurred(Type,warning,Span,Msg).
3463 error_occurred_with_msg(Type,Msg,Span) :- error_occurred(Type,error,Span,Msg).
3464
3465 error_occurred(Type,ErrOrWarn) :- error_occurred(Type,ErrOrWarn,not_yet_extracted,'').
3466
3467 error_occurred(Type,ErrOrWarning,ExtractedSpan,Msg) :- option(expect_error_pos(Type,Line,Col)),!,
3468 write_xml_element_to_log(expected_error_occurred,[category/Type, type/ErrOrWarning, message/Msg]),
3469 assert(expected_error_occurred(Type)),
3470 (get_error_or_warning_span(ExtractedSpan,Type,EL,EC)
3471 -> ((EL,EC)=(Line,Col) -> debug_println(9,expect_error_pos_ok(Type,EL,EC))
3472 ; format('Unexpected line ~w and column ~w for error ~w! Expected line ~w and column ~w.~n',[EL,EC,Type,Line,Col]),
3473 definite_error_occurred
3474 )
3475 ; format('*** Could not obtain position information for error ~w! Expected line ~w and column ~w.~n',[Type,Line,Col]),
3476 %display_error_statistics,
3477 definite_error_occurred).
3478 error_occurred(Type,ErrOrWarning,ExtractedSpan,Msg) :-
3479 ? option(expect_error(Type)),!,
3480 inc_counter(cli_expected_errors),
3481 get_xml_span(ExtractedSpan,XML),
3482 write_xml_element_to_log(expected_error_occurred,[category/Type, type/ErrOrWarning, message/Msg|XML]),
3483 assert(expected_error_occurred(Type)).
3484 error_occurred(Type,ErrOrWarning,ExtractedSpan,Msg) :-
3485 (probcli_time_stamp(NOW) -> true ; NOW=unknown),
3486 writeln_log(error_occurred(NOW,Type)),
3487 get_xml_span(ExtractedSpan,XML),
3488 (option(optional_error(Type)) ->
3489 write_xml_element_to_log(optional_error_occurred,[category/Type, type/ErrOrWarning, message/Msg|XML]),
3490 format(user_output,'% Optional error occured: ~w~n',[Type])
3491 ;
3492 write_xml_element_to_log(error_occurred,[category/Type, type/ErrOrWarning, message/Msg|XML]),
3493 (ErrOrWarning = warning -> inc_counter(cli_warnings) ; inc_counter(cli_errors)),
3494 (option(strict_raise_error) ->
3495 print_error('*** Unexpected error occurred ***'),
3496 print_error(Type),
3497 findall(Err,option(expect_error(Err)),Ls), (Ls=[] -> true ; print_error(expected(Ls))),
3498 definite_error_occurred
3499 ; ErrOrWarning=error,serious_error(Type)
3500 -> print_error('*** Serious error occurred ***'),
3501 print_error(Type),
3502 definite_error_occurred
3503 ; print_probcli_error_non_strict(Type,ErrOrWarning)
3504 )
3505 ).
3506
3507 get_xml_span(Span,XML) :- extract_file_line_col(Span,FullFilename,Line,Col,EndLine,EndCol),!,
3508 XML = [file/FullFilename,start_line/Line,end_line/EndLine,start_col/Col,end_col/EndCol].
3509 get_xml_span(_,[]).
3510
3511 get_error_or_warning_span(not_yet_extracted,Type,EL,EC) :- check_error_span_file_linecol(Type,_File,EL,EC,_,_).
3512 get_error_or_warning_span(not_yet_extracted,Type,EL,EC) :- check_error_span_file_linecol(warning(Type),_File,EL,EC,_,_).
3513 get_error_or_warning_span(Span,_,EL,EC) :- Span \= not_yet_extracted, extract_line_col(Span,EL,EC,_,_).
3514
3515
3516 % a list of serious errors: if these occur; then return code different from 0 even in non-strict mode
3517 serious_error(get_java_command_path).
3518 serious_error(internal_error(_)).
3519
3520 print_probcli_error_non_strict(parse_machine_predicate_error,_) :-
3521 !. % have already been reported
3522 print_probcli_error_non_strict(Type,ErrOrWarning) :-
3523 (ErrOrWarning=warning -> print_error('*** warning occurred ***')
3524 ; print_error('*** error occurred ***')),
3525 print_error(Type).
3526
3527 definite_error_occurred :- print_error('*** Abnormal termination of probcli !'),
3528 (file_loaded(_,File) -> print_error('*** for_file'(File)) ; true),
3529 (current_probcli_command(Cmd) -> print_error('*** for_command'(Cmd)) ; true),
3530 (probcli_time_stamp(NOW) -> halt1_prob(NOW)
3531 ; writeln_log(halt(1)),
3532 halt_exception(1)
3533 ).
3534
3535 :- dynamic current_probcli_command/1.
3536 set_current_probcli_command(X) :- retractall(current_probcli_command(_)),
3537 assert(current_probcli_command(X)).
3538 unset_current_probcli_command :- retractall(current_probcli_command(_)).
3539
3540 halt_prob(NOW) :-
3541 write_xml_element_to_log(probcli_halted_prematurely,[now/NOW]),
3542 check_all_expected_errors_occurred(NOW),
3543 close_all_xml_groups_in_log,
3544 halt_exception.
3545 halt1_prob(NOW) :-
3546 write_xml_element_to_log(probcli_halted_prematurely,[now/NOW]),
3547 close_all_xml_groups_in_log,
3548 halt_exception(1).
3549
3550
3551 :- dynamic accumulated_infos/3.
3552 accumulate_infos(_,[]).
3553 accumulate_infos(Context,[Info|T]) :- get_info(Info,FF,Nr),Nr>0,!,
3554 (retract(accumulated_infos(Context,FF,OldNr))->true ; OldNr=0),
3555 N1 is OldNr+Nr,
3556 assert(accumulated_infos(Context,FF,N1)),
3557 accumulate_infos(Context,T).
3558 accumulate_infos(Context,[_|T]) :- accumulate_infos(Context,T).
3559 get_info(FF-Nr,FF,Nr).
3560 get_info(FF/Nr,FF,Nr).
3561 ?print_accumulated_infos(NrFilesProcessed) :- NrFilesProcessed>1, accumulated_infos(_,_,_),!,
3562 format('Analysis summary (~w files processed): ',[NrFilesProcessed]),
3563 start_xml_group_in_log(summary,files_processed,NrFilesProcessed),
3564 findall(Context-F-Nr,accumulated_infos(Context,F,Nr),L), sort(L,SL),
3565 maplist(pracc,SL),nl,
3566 % TO DO: write infos to XML log
3567 stop_xml_group_in_log_no_statistics(summary).
3568 print_accumulated_infos(_NrFilesProcessed).
3569 pracc(Context-F-Nr) :- format('~w:~w:~w ',[Context,F,Nr]).
3570
3571 write_important_xml_element_to_log(Category,Infos) :-
3572 include(important_info,Infos,II),
3573 write_xml_element_to_log(Category,II).
3574 important_info(FF/Nr) :- Nr \= 0, \+ irrelevant_xml_info(FF).
3575 irrelevant_xml_info(true_after_expansion).
3576 irrelevant_xml_info(false_after_expansion).
3577 irrelevant_xml_info(unknown_after_expansion).
3578 irrelevant_xml_info(total_after_expansion).
3579
3580 check_required_infos([],_,_).
3581 check_required_infos([H|T],Infos,ErrType) :-
3582 ? (member(H,Infos) -> check_required_infos(T,Infos,ErrType)
3583 ; print('*** Unexpected result while checking: '),
3584 translate_err_type(ErrType,ES), print(ES),nl,
3585 print('*** expected : '), print(H),nl,
3586 print('*** in : '), print(Infos),nl,
3587 error_occurred(ErrType)).
3588 translate_err_type(check_assertions,'ASSERTIONS') :- !.
3589 translate_err_type(cli_check_assertions,'ASSERTIONS') :- !.
3590 translate_err_type(check_goal,'GOAL') :- !.
3591 translate_err_type(load_po_file,'PROOF OBLIGATIONS') :- !.
3592 translate_err_type(X,X).
3593
3594 :- public mc_ok_arg/2.
3595 mc_ok_arg(Arg,X) :- Arg==all,!,prolog_flag(max_tagged_integer,X).
3596 mc_ok_arg(Arg,N) :- tools:arg_is_number(Arg,N).
3597
3598
3599 :- dynamic option/1.
3600 assert_all_options([]).
3601 assert_all_options([Opt|T]) :- assert_option(Opt),
3602 assert_all_options(T).
3603
3604 assert_option(Opt) :- assert(option(Opt)),
3605 (Opt=silent -> set_silent_mode(on) ; true).
3606
3607 reset_options :- retractall(option(_)), set_silent_mode(off).
3608
3609 % replace a leading double-dash -- by a single dash and replace inner dashes by underscores
3610 normalise_option_atom(X,RX) :- atom(X),!,
3611 atom_codes(X,CodesX),
3612 % remove leading dash
3613 (CodesX=[45,45,H|T], H\=45
3614 -> maplist(convert_dash_to_underscore,[H|T],HT2),
3615 RXCodes=[45|HT2]
3616 ; CodesX = [45|T]
3617 -> maplist(convert_dash_to_underscore,T,T2),
3618 RXCodes=[45|T2]
3619 ; maplist(convert_dash_to_underscore,CodesX,RXCodes)
3620 ),
3621 atom_codes(RX,RXCodes).
3622 normalise_option_atom(T,T).
3623
3624 :- public normalise_pref_name/2. % called via recognised_option
3625 % replace dashes by underscores
3626 normalise_pref_name(X,RX) :- atom(X),!,
3627 atom_codes(X,CodesX),
3628 maplist(convert_dash_to_underscore,CodesX,C2),
3629 atom_codes(RX,C2).
3630 normalise_pref_name(T,T).
3631
3632 convert_dash_to_underscore(45,R) :- !, R=95.
3633 convert_dash_to_underscore(X,X).
3634
3635 ?recognised_cli_option(X,Opt,Args,Condition) :- normalise_option_atom(X,RX),
3636 ? recognised_option(RX,Opt,Args,Condition).
3637
3638 recognised_option(X,Opt,[],true) :- recognised_option(X,Opt). % options without arguments
3639 recognised_option(X,Opt,Args,true) :- recognised_option(X,Opt,Args). % options with arguments but no code needed to check arguments
3640
3641 recognised_option('-mc',cli_mc(N),[Arg],user:mc_ok_arg(Arg,N)).
3642 recognised_option('-model_check',cli_mc(LimitNr),[],true) :- max_tagged_integer(LimitNr).
3643 recognised_option('-timeout',timeout(N),[Arg],tools:arg_is_number(Arg,N)). % for model checking, refinement checking and for disprover per PO
3644 recognised_option('-time_out',timeout(N),[Arg],tools:arg_is_number(Arg,N)).
3645 recognised_option('-s',socket(S),[Arg],tools:arg_is_number(Arg,S)).
3646 recognised_option('-cc',coverage(N,N2,just_check_stats),[Arg,Arg2],
3647 (arg_is_number_or_wildcard(Arg,N),arg_is_number_or_wildcard(Arg2,N2))).
3648 recognised_option('-hash',check_statespace_hash(H,_),[Arg],tools:arg_is_number(Arg,H)).
3649 recognised_option('-hash64',check_statespace_hash(H,'64bit'),[Arg],tools:arg_is_number(Arg,H)).
3650 recognised_option('-hash32',check_statespace_hash(H,'32bit'),[Arg],tools:arg_is_number(Arg,H)).
3651 recognised_option('-ltllimit',ltl_limit(Nr),[Arg], tools:arg_is_number(Arg,Nr)).
3652 recognised_option('-check_disprover_result',cli_check_disprover_result([true-TNr,false-FNr,unknown-UNr,failure-0]),[T,F,U],
3653 (arg_is_number_or_wildcard(T,TNr),arg_is_number_or_wildcard(F,FNr),arg_is_number_or_wildcard(U,UNr))).
3654 recognised_option('-aa',cli_check_assertions(all,[true/TNr,false/FNr,unknown/UNr]),[T,F,U],
3655 (arg_is_number_or_wildcard(T,TNr),arg_is_number_or_wildcard(F,FNr),arg_is_number_or_wildcard(U,UNr))).
3656 recognised_option('-ma',cli_check_assertions(main,[true/TNr,false/FNr,unknown/UNr]),[T,F,U],
3657 (arg_is_number_or_wildcard(T,TNr),arg_is_number_or_wildcard(F,FNr),arg_is_number_or_wildcard(U,UNr))).
3658 recognised_option('-kodkod_comparision',kodkod_comparision(Nr),[Arg],tools:arg_is_number(Arg,Nr)).
3659 recognised_option('-kodkod_performance',kodkod_performance(File,Nr),[File,Arg],tools:arg_is_number(Arg,Nr)).
3660 recognised_option('-animate',cli_random_animate(N,true),[Steps],tools:arg_is_number(Steps,N)).
3661 recognised_option('-execute',execute(N,true,current_state),[Steps],tools:arg_is_number(Steps,N)).
3662 recognised_option('-logxml_write_vars',logxml_write_vars(Prefix),[Prefix],true).
3663 recognised_option('-zmq_master',zmq_master(Identifier),[Identifier], true).
3664 recognised_option('-cbc_tests', cbc_tests(Depth,EndPred,Output),[Depth,EndPred,Output],
3665 tools:check_filename_arg(Output,'cbc_tests')).
3666 recognised_option('-mcm_tests', mcm_tests(Depth,MaxStates,EndPred,Output),[Depth,MaxStates,EndPred,Output],
3667 tools:check_filename_arg(Output,'mcm_tests')).
3668 recognised_option('-test_description', test_description(File), [File],
3669 tools:check_filename_arg(File,'test_description')).
3670 recognised_option('-all_paths', all_deadlocking_paths(File), [File],
3671 tools:check_filename_arg(File,'all_paths')).
3672 recognised_option('-dot',dot_command(Category,File),[Category,File],
3673 tools:check_filename_arg(File,'dot')).
3674 recognised_option('-spdot',dot_command(state_space,File),[File], tools:check_filename_arg(File,'spdot')). % we keep this : it is shown in Wiki
3675 % recognised_option('-spmdot',dot_command(signature_merge,File),[File], tools:check_filename_arg(File,'spmdot')).
3676 % recognised_option('-spddot',dot_command(dfa_merge,File),[File], tools:check_filename_arg(File,'spddot')).
3677 % recognised_option('-sgdot',dot_command(state_as_graph,File),[File], tools:check_filename_arg(File,'sgdot')).
3678 recognised_option('-dotexpr',dot_command_for_expr(Category,Expr,File,[]),[Category,Expr,File],
3679 tools:check_filename_arg(File,'dot')).
3680 %recognised_option('-sgedot',dot_command_for_expr(expr_as_graph,Expr,File,[]),[Expr,File], tools:check_filename_arg(File,'sgedot')).
3681 % recognised_option('-sptdot',dot_command_for_expr(transition_diagram,Expr,File,[]),[Expr,File],tools:check_filename_arg(File,'sptdot')).
3682 %recognised_option('-invdot',dot_command(invariant,File),[File], tools:check_filename_arg(File,'invdot')).
3683 %recognised_option('-propdot',dot_command(properties,File),[File], tools:check_filename_arg(File,'propdot')).
3684 %recognised_option('-assdot',dot_command(assertions,File),[File], tools:check_filename_arg(File,'assdot')).
3685 %recognised_option('-deaddot',dot_command(deadlock,File)(File),[File], tools:check_filename_arg(File,'deaddot')).
3686 recognised_option('-csvhist',evaluate_expression_over_history_to_csv_file(Expr,File),[Expr,File],
3687 tools:check_filename_arg(File,'csvhist')).
3688 recognised_option('-read_write_matrix_csv',generate_read_write_matrix_csv(CsvFile),
3689 [CsvFile],
3690 tools:check_filename_arg(CsvFile,'read_write_matrix_csv')).
3691 recognised_option('-feasibility_analysis_csv',feasibility_analysis_csv(TimeOut,EnablingCsvFile),
3692 [TimeOut,EnablingCsvFile],
3693 tools:check_filename_arg(EnablingCsvFile,'feasibility_analysis_csv')).
3694 recognised_option('-l',log(Log,prolog),[Log],
3695 tools:check_filename_arg(Log,'l')).
3696 recognised_option('-log',log(Log,prolog),[Log],
3697 tools:check_filename_arg(Log,'log')).
3698 recognised_option('-logxml',log(Log,xml),[Log],
3699 tools:check_filename_arg(Log,'logxml')).
3700 recognised_option('-pp',pretty_print_internal_rep(File,needed,ascii),[File],
3701 tools:check_filename_arg(File,'pp')).
3702 recognised_option('-ppunicode',pretty_print_internal_rep(File,needed,unicode),[File],
3703 tools:check_filename_arg(File,'pp')).
3704 recognised_option('-ppf',pretty_print_internal_rep(File,all,ascii),[File],
3705 tools:check_filename_arg(File,'ppf')).
3706 recognised_option('-ppB',pretty_print_internal_rep_to_B(File),[File],
3707 tools:check_filename_arg(File,'ppB')).
3708 recognised_option('-save_state',save_state(Filename),[Filename],
3709 tools:check_filename_arg(Filename,'save_state')).
3710 recognised_option('-save',save_state_for_refinement(Filename),[Filename],
3711 tools:check_filename_arg(Filename,'save')).
3712 recognised_option('-sptxt',print_values(Filename),[Filename],
3713 tools:check_filename_arg(Filename,'sptxt')).
3714 recognised_option('-sstxt',print_all_values(Dirname),[Dirname],
3715 tools:check_filename_arg(Dirname,'sstxt')).
3716 recognised_option('-latex',process_latex_file(In,Out),[In,Out],
3717 (tools:check_filename_arg(In,'latex'),tools:check_filename_arg(Out,'latex'))).
3718
3719 recognised_option('-zmq_assertions',zmq_assertion(Identifier),[Identifier],true).
3720 recognised_option('-zmq_worker',zmq_worker(Identifier),[Identifier], true).
3721 %recognised_option('-zmq_worker2',zmq_worker2(MasterIP, Port, ProxyID, Logfile),[MasterIP, SPort, SProxyID, Logfile],
3722 % tools:(arg_is_number(SPort,Port), arg_is_number(SProxyID, ProxyID))).
3723 recognised_option('-p',set_pref(NPREF,PREFVAL),[PREF,PREFVAL],user:normalise_pref_name(PREF,NPREF)).
3724 recognised_option('-pref',set_pref(NPREF,PREFVAL),[PREF,PREFVAL],user:normalise_pref_name(PREF,NPREF)).
3725 recognised_option('-cbc_redundant_invariants',cbc_redundant_invariants(Nr),[X],tools:arg_is_number(X,Nr)).
3726 recognised_option('-expcterrpos',expect_error_pos(Type,LNr,CNr),[Type,Line,Col],
3727 (tools:arg_is_number(Line,LNr),tools:arg_is_number(Col,CNr))).
3728
3729 recognised_option('-pref_group',set_preference_group(Group,Val),[Group,Val]).
3730 recognised_option('-prefs',set_prefs_from_file(PREFFILE),[PREFFILE]).
3731 %recognised_option('-plugin',plugin(Plugin), [Plugin]).
3732 recognised_option('-card',set_card(SET,SCOPE),[SET,SCOPE]).
3733 recognised_option('-argv',set_argv(ARGV),[ARGV]).
3734 recognised_option('-goal',set_goal(GOAL),[GOAL]).
3735 recognised_option('-property',add_additional_property(PRED),[PRED]).
3736 recognised_option('-scope',set_searchscope(GOAL),[GOAL]).
3737 recognised_option('-searchscope',set_searchscope(GOAL),[GOAL]).
3738 recognised_option('-eval',eval_string_or_file(string,E,exists,_),[E]).
3739 recognised_option('-evalt',eval_string_or_file(string,E,exists,'TRUE'),[E]).
3740 recognised_option('-evalf',eval_string_or_file(string,E,exists,'FALSE'),[E]).
3741 recognised_option('-evalu',eval_string_or_file(string,E,exists,'UNKNOWN'),[E]).
3742 recognised_option('-eval_file',eval_string_or_file(file,F,exists,print_file),[F]).
3743 recognised_option('-evalt_file',eval_string_or_file(file,F,exists,'TRUE'),[F]).
3744 recognised_option('-eval_rule_file',eval_string_or_file(file,F,forall,print_file),[F]).
3745 recognised_option('-parsercp',(L),[L]).
3746 recognised_option('-lg',analyse_log(Log,timestamp,true),[Log]).
3747 recognised_option('-lgr',analyse_log(Log,revision,false),[Log]).
3748 recognised_option('-check_log',check_log(Log),[Log]).
3749 recognised_option('-expcterr',expect_error(Type),[Type]).
3750 recognised_option('-expecterr',expect_error(Type),[Type]).
3751 recognised_option('-expect',expect_error(Type),[Type]).
3752 recognised_option('-opterr',optional_error(Type),[Type]).
3753 recognised_option('-his',history(File),[File]).
3754 recognised_option('-his_option',history_option(Option),[Option]).
3755 recognised_option('-cache',cache_storage(D),[D]).
3756 recognised_option('-show_cache',show_cache,[]).
3757
3758 recognised_option('-MAIN',csp_main(ProcessName),[ProcessName]).
3759
3760 recognised_option('-ltlfile',ltl_file(Filename),[Filename]).
3761 recognised_option('-ltlformula',ltl_formula_model_check(Formula,_),[Formula]).
3762 recognised_option('-ltlformulat',ltl_formula_model_check(Formula,true),[Formula]).
3763 recognised_option('-ltlformulaf',ltl_formula_model_check(Formula,false),[Formula]).
3764 recognised_option('-ctlformula',ctl_forumla_model_check(Formula,_),[Formula]).
3765 recognised_option('-ctlformulat',ctl_forumla_model_check(Formula,true),[Formula]).
3766 recognised_option('-ctlformulaf',ctl_forumla_model_check(Formula,false),[Formula]).
3767 recognised_option('-load_state',load_state(Filename),[Filename]).
3768 recognised_option('-refchk',refinement_check(Filename,0,100000),[Filename]).
3769
3770 %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]).
3771 recognised_option('-cspref',csp_in_situ_refinement_check(AbsP1,Type,ImplP2),[AbsP1,Type,ImplP2]).
3772 % -cspref R [F= Q
3773 recognised_option('-cspdeadlock',csp_checkAssertion(Proc,Model,'deadlock free'),[Proc,Model]).
3774 % -cspdeadlock R F
3775 recognised_option('-cspdeterministic',csp_checkAssertion(Proc,Model,'deterministic'),[Proc,Model]).
3776 % -cspdeterministic R F
3777 recognised_option('-csplivelock',csp_checkAssertion(Proc,'FD','livelock free'),[Proc]).
3778 % -csplivelock R
3779 % -csp_assertion "P [F= Q"
3780 recognised_option('-csp_assertion',check_csp_assertion(Assertion),[Assertion]).
3781 recognised_option('-csp_eval', eval_csp_expression(Expr),[Expr]).
3782 recognised_option('-get_csp_assertions_as_string',csp_get_assertions,[]).
3783 recognised_option('-prologOut',csp_translate_to_file(PlFile),[PlFile]).
3784 recognised_option('-csp_guide',add_csp_guide(Filename),[Filename]).
3785 recognised_option('-get_min_max_coverage',get_min_max_coverage(FileName),[FileName]).
3786 recognised_option('-get_coverage_information',get_coverage_information(FileName),[FileName]).
3787 recognised_option('-vacuity_check',vacuity_check,[]).
3788 recognised_option('-cbc',constraint_based_check(OpName),[OpName]).
3789 recognised_option('-cbc_deadlock',cbc_deadlock_check(true),[]).
3790 recognised_option('-cbc_assertions',cbc_assertions(true,[]),[]).
3791 recognised_option('-cbc_main_assertions',cbc_assertions(true,[main_assertions]),[]).
3792 recognised_option('-cbc_assertions_proof',cbc_assertions(false,[]),[]). % do not allow enumeration warnings
3793 recognised_option('-cbc_assertions_tautology_proof',cbc_assertions(false,[tautology_check]),[]). % do not allow enumeration warnings + disregard PROPERTIES, used for Atelier-B proof/disproof
3794 recognised_option('-cbc_assertions_tautology_proof_check',cbc_assertions(false,[tautology_check,contradiction_check]),[]).
3795 recognised_option('-cbc_option',cbc_option(OPT),[OPT]). % should be tautology_check,contradiction_check, unsat_core
3796 recognised_option('-cbc_result_file',cbc_result_file(FILE),[FILE]). % write result to FILE
3797 recognised_option('-cbc_refinement',cbc_refinement,[]).
3798 recognised_option('-cbc_deadlock_pred',cbc_deadlock_check(GoalPred),[GoalPred]).
3799 recognised_option('-cbc_sequence',cbc_sequence(OpSequence,'',single_solution),[OpSequence]).
3800 recognised_option('-cbc_sequence_all',cbc_sequence(OpSequence,'',findall),[OpSequence]).
3801 recognised_option('-cbc_sequence_with_target',cbc_sequence(OpSequence,TargetPredString,single_solution),[OpSequence,TargetPredString]).
3802 recognised_option('-cbc_sequence_with_target_all',cbc_sequence(OpSequence,TargetPredString,findall),[OpSequence,TargetPredString]).
3803 recognised_option('-comment',comment(UserComment),[UserComment]). % not processed by tool, but will be stored in log-file and used by log_analyser
3804 recognised_option('-junit',junit(Dir),[Dir]).
3805 recognised_option('-mcm_cover', mcm_cover(Event),[Event]).
3806 recognised_option('-cbc_cover', cbc_cover(Event),[Event]).
3807 recognised_option('-cbc_cover_match', cbc_cover(match_event(Event)),[Event]). % find events which have Event String occuring somewhere in name
3808 recognised_option('-cbc_cover_all', cbc_cover_all,[]). % is now default if no cbc_cover provided
3809 recognised_option('-cbc_cover_final', cbc_cover_final,[]).
3810 recognised_option('-bmc', cbc_tests(Depth,'#not_invariant',''),[Depth]).
3811 recognised_option('-dot_output',dot_analyse_output_prefix(Path),[Path]).
3812 recognised_option('-evaldot',evaldot(File),[File]).
3813 recognised_option('-enabling_analysis',enabling_analysis_csv(user_output),[]).
3814 recognised_option('-enabling_analysis_csv',enabling_analysis_csv(EnablingCsvFile),[EnablingCsvFile]).
3815 recognised_option('-feasibility_analysis',feasibility_analysis_csv(1000,user_output),[]).
3816 recognised_option('-read_write_matrix',generate_read_write_matrix_csv(user_output),[]).
3817 recognised_option('-state_trace',state_trace(File),[File]).
3818 recognised_option('-typecheckertest',typechecker_test(File),[File]).
3819 recognised_option('-scc_trace',check_scc_for_ltl_formula(LtlFormula,SCC),[LtlFormula,SCC]).
3820 recognised_option('-selfcheck_module',selfcheck(M),[M]).
3821 recognised_option('-mc_mode',depth_breadth_first_mode(M),[M]). % can be mixed, hash, heuristic
3822 recognised_option('-assertion',cli_check_assertions(specific(X),[false/0,unknown/0]),[X]).
3823 recognised_option('-cbc_assertion',cbc_assertions(true,[specific(X)]),[X]). % check only a specific assertion
3824 recognised_option('-symbolic_model_check', cli_symbolic_model_check(Algorithm), [Algorithm]).
3825 recognised_option('-replay',eval_repl([File]),[File]). % used to be -eval
3826 recognised_option('-ltsmin2',ltsmin2(EndpointPath), [EndpointPath]).
3827 recognised_option('-ltsmin_ltl_output',ltsmin_ltl_output(Path), [Path]).
3828 recognised_option('-ltsmin_option', ltsmin_option(X),[X]).
3829
3830 recognised_option('-dot_all',dot_generate_for_all_formulas). % generate dot also for true formulas
3831 recognised_option('-animate_all',cli_random_animate(2147483647,false)).
3832 recognised_option('-execute_all',execute(2147483647,false,current_state)).
3833 recognised_option('-execute_all_inits',execute(2147483647,false,from_all_initial_states)).
3834 recognised_option('-animate_stats',animate_stats).
3835 recognised_option('-check_goal',check_goal).
3836 recognised_option('-ltlassertions',ltl_assertions).
3837 recognised_option('-assertions',cli_check_assertions(all,[false/0,unknown/0])).
3838 recognised_option('-main_assertions',cli_check_assertions(main,[false/0,unknown/0])).
3839 recognised_option('-properties',cli_check_properties).
3840 recognised_option('-selfcheck',selfcheck(_)).
3841 recognised_option('-pacheck',pa_check). % predicate analysis for Kodkod
3842 recognised_option('-det_check',det_check). % check if animation is deterministic
3843 recognised_option('-det_constants',det_constants_check). % check if animation for setup_constants is deterministic
3844 recognised_option('-bf',breadth_first).
3845 recognised_option('-breadth',breadth_first).
3846 recognised_option('-df',depth_first).
3847 recognised_option('-depth',depth_first).
3848 recognised_option('-strict',strict_raise_error).
3849 recognised_option('-silent',silent).
3850 recognised_option('-statistics',statistics).
3851 recognised_option('-profile_statistics',profile_statistics).
3852 recognised_option('-reset_profile_statistics',reset_profiler). % mainly for use in REPL
3853 recognised_option('-nodead',no_deadlocks).
3854 recognised_option('-noinv',no_invariant_violations).
3855 recognised_option('-nogoal',no_goal).
3856 recognised_option('-noltl',no_ltl). % just used for TLC at the moment
3857 recognised_option('-noass',no_assertion_violations).
3858 recognised_option('-nocounter',no_counter_examples).
3859 recognised_option('-disable_time_out',set_preference_group(time_out,disable_time_out)).
3860 recognised_option('-disable_timeout',set_preference_group(time_out,disable_time_out)).
3861 %recognised_option('-POR',with_reduction).
3862 recognised_option('-i',animate).
3863 recognised_option('-repl',eval_repl([])). % used to be -eval
3864 recognised_option('-c',coverage(false)).
3865 recognised_option('-cs',coverage(just_summary)).
3866 recognised_option('-coverage',coverage(false)).
3867 recognised_option('-coverage_summary',coverage(just_summary)).
3868 recognised_option('-machine_stats',cli_print_machine_statistics).
3869 recognised_option('-vc',variable_coverage).
3870 recognised_option('-variable_coverage',variable_coverage).
3871 recognised_option('-cv',coverage(true)).
3872 recognised_option('-v',verbose).
3873 recognised_option('-vv',very_verbose).
3874 recognised_option('-verbose',verbose).
3875 recognised_option('-very_verbose',very_verbose).
3876 recognised_option('-profiling_on',profiling_on). % Prolog profiling
3877 recognised_option('-profile',prob_profile). % ProB Operation profiling
3878 recognised_option('-version',print_version).
3879 recognised_option('-svers',print_short_version).
3880 recognised_option('-short_version',print_short_version).
3881 recognised_option('-check_java_version',check_java_version).
3882 recognised_option('-java_version',check_java_version).
3883 recognised_option('-file_info',file_info).
3884 recognised_option('-t',trace_check).
3885 recognised_option('-trace_check',trace_check).
3886 recognised_option('-init',initialise).
3887 recognised_option('-initialise',initialise).
3888 recognised_option('-ll',log('/tmp/prob_cli_debug.log',prolog)).
3889 recognised_option('-ss',socket(9000)).
3890 recognised_option('-sf',socket(_)).
3891 recognised_option('-help',help).
3892 recognised_option('-h',help).
3893 recognised_option('-rc',runtimechecking).
3894 recognised_option('-test_mode',test_mode).
3895 recognised_option('-check_complete',check_complete).
3896 recognised_option('-check_complete_operation_coverage', check_complete_operation_coverage).
3897 recognised_option('-mc_with_tlc', cli_start_mc_with_tlc).
3898 recognised_option('-mc_with_lts_sym', cli_start_sym_mc_with_lts(symbolic)).
3899 recognised_option('-mc_with_lts_seq', cli_start_sym_mc_with_lts(sequential)).
3900 %recognised_option('-csp',csp_pl_mode).
3901 %recognised_option('-cspm',csp_mode).
3902 recognised_option('-core',disprover_options([disprover_option(unsat_core),unsat_core_algorithm/linear])).
3903
3904 recognised_option('-ltsmin',ltsmin).
3905
3906 % some utilities to be able to call the above options directly from repl:
3907 :- public variable_coverage/0, silent/0, coverage/1, help/0.
3908 verbose :- tcltk_turn_debugging_on(19).
3909 very_verbose :- tcltk_turn_debugging_on(5).
3910 file_info :- file_loaded(true,MainFile), print_file_info(MainFile).
3911 coverage(ShowEnabledInfo) :- probcli_time_stamp(NOW), cli_show_coverage(ShowEnabledInfo,NOW).
3912 variable_coverage :- probcli_time_stamp(NOW), cli_show_variable_coverage(NOW).
3913 silent :- (option(silent) -> true ; assert_option(silent)).
3914 help :- eval_help.
3915 dot_command(DCommand,DotFile) :- call_dot_command(DCommand,DotFile,[]).
3916 dot_command_for_expr(DECommand,Expr,DotFile,Opts) :- call_dot_command_for_expr(DECommand,Expr,DotFile,Opts).
3917 save_state(StateFile) :- debug_println(20,'% Saving state space to file'),
3918 state_space:tcltk_save_state(StateFile).
3919 execute(ESteps,ErrOnDeadlock,From) :- cli_execute(ESteps,ErrOnDeadlock,From).
3920
3921 option_verbose :- (option(verbose) -> true ; option(very_verbose)).
3922
3923 % new profiler
3924 %:- use_module(('../extensions/profiler/profiler.pl').
3925 %prob_profiler :- pen.
3926
3927 % old profiler
3928 :- use_module(runtime_profiler,[print_runtime_profile/0]).
3929 :- use_module(source_profiler,[print_source_profile/0]).
3930 :- use_module(memoization,[print_memo_profile/0]).
3931 prob_profile :-
3932 print_source_profile,
3933 print_runtime_profile,
3934 print_memo_profile.
3935
3936
3937 set_random_seed_to_deterministic_start_seed :-
3938 % in test_mode we do not change the random number generator's initial seed
3939 true. %getrand(CurrState),setrand(CurrState). % this seems to be a no-op
3940
3941 set_new_random_seed :-
3942 now(TimeStamp), % getting the unix time
3943 setrand(TimeStamp). % setting new random seed by every execution of probcli
3944
3945 halt_exception :- halt_exception(0).
3946 halt_exception(Code) :- throw(halt(Code)).
3947
3948 % -----------------
3949
3950 start_xml_feature(FeatureName,[CErrs1,CWarns1]) :-
3951 debug_format(20,'% Starting ~w~n',[FeatureName]),
3952 get_counter(cli_errors,CErrs1), get_counter(cli_warnings,CWarns1),
3953 start_xml_group_in_log(FeatureName).
3954
3955 start_xml_feature(FeatureName,Attr,Value,[CErrs1,CWarns1,CEErrs1]) :-
3956 debug_format(20,'% Starting ~w (~w=~w)~n',[FeatureName,Attr,Value]),
3957 get_counter(cli_errors,CErrs1), get_counter(cli_warnings,CWarns1), get_counter(cli_expected_errors,CEErrs1),
3958 start_xml_group_in_log(FeatureName,Attr,Value).
3959
3960 stop_xml_feature(FeatureName,[CErrs1,CWarns1,CEErrs1]) :-
3961 get_counter(cli_errors,CErrs2), get_counter(cli_warnings,CWarns2), get_counter(cli_expected_errors,CEErrs2),
3962 CErrs is CErrs2-CErrs1, CWarns is CWarns2-CWarns1, CEErrs is CEErrs2-CEErrs1,
3963 (CEErrs>0 -> write_xml_element_to_log('probcli-errors',[errors/CErrs,warnings/CWarns,expected_errors/CEErrs])
3964 ; write_xml_element_to_log('probcli-errors',[errors/CErrs,warnings/CWarns])),
3965 debug_format(20,'% Finished ~w (errors=~w, warnings=~w, expected_errors=~w)~n',[FeatureName,CErrs,CWarns,CEErrs]),
3966 stop_xml_group_in_log(FeatureName).
3967 %(CErrs>0 -> (file_loaded(_,MainFile) -> true ; MainFile=unknown), Time=unknown, % TO DO: determine time
3968 % create_and_print_junit_result(FeatureName,'Feature', MainFile, Time, error) ; true).
3969 % Note: call stop_xml_group_in_log if the feature stops unexpectedly and you do not have the Info list available
3970
3971 % -----------------
3972
3973 runtime_entry(start) :- go_cli.
3974
3975 save :- save_program('probcli.sav').
3976
3977 :- announce_event(compile_prob).