1 % (c) 2009-2025 Lehrstuhl fuer Softwaretechnik und Programmiersprachen,
2 % Heinrich Heine Universitaet Duesseldorf
3 % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html)
4
5 :- module(parsercall, [load_b_machine_as_term/3,
6 load_b_machine_probfile_as_term/2, % a way to directly load a .prob file
7 load_b_machine_probfile_as_term/3,
8 load_b_machine_list_of_facts_as_term/2,
9 get_parser_version/1,
10 get_parser_version/2,
11 get_parser_version/6,
12 get_java_command_path/1,
13 check_java_version/2,
14 get_java_fullversion/1, get_java_fullversion/3, get_java_version/1,
15 ensure_console_parser_launched/0, % just make sure the console parser is up and running
16 connect_to_external_console_parser_on_port/1, % connect to a separately started parser
17 release_console_parser/0,
18 console_parser_jar_available_in_lib/0,
19 call_ltl_parser/3,
20 call_tla2b_parser/1, tla2b_filename/2,
21 %call_promela_parser/1, promela_prolog_filename/2,
22 call_alloy2pl_parser/2,
23 tla2prob_filename/2,
24 parse/3,
25 parse_at_position_in_file/5,
26 parse_formula/2, parse_predicate/2, parse_expression/2,
27 parse_substitution/2,
28 transform_string_template/3,
29 call_fuzz_parser/2,
30 register_parsing_call_back/1, deregister_parsing_call_back/0,
31 set_default_filenumber/2, reset_default_filenumber/2
32 ]).
33
34 :- meta_predicate register_parsing_call_back(4).
35
36 :- use_module(module_information,[module_info/2]).
37 :- module_info(group,typechecker).
38 :- module_info(description,'This module takes care of calling the Java B Parser if necessary.').
39
40 :- use_module(library(lists)).
41 :- use_module(library(process)).
42 :- use_module(library(file_systems)).
43 :- use_module(library(codesio)).
44 :- use_module(library(system)).
45 :- use_module(library(sockets)).
46
47 :- use_module(error_manager,[add_error/2, add_error/3, add_error/4, add_error_fail/3,
48 add_failed_call_error/1, add_internal_error/2, add_warning/3, add_warning/4, real_error_occurred/0,
49 add_message/3, add_message/4, extract_line_col/5, add_all_perrors/3]).
50 :- use_module(self_check).
51 :- use_module(preferences).
52 :- use_module(tools, [split_filename/3, same_file_name/2, get_PROBPATH/1, safe_atom_chars/3]).
53 :- use_module(tools_platform, [host_platform/1, platform_is_64_bit/0]).
54 :- use_module(tools_strings,[ajoin_with_sep/3, ajoin/2]).
55 :- use_module(tools_printing,[print_error/1, format_with_colour_nl/4]).
56 :- use_module(debug).
57 :- use_module(bmachine,[b_get_definition/5, b_machine_is_loaded/0]).
58 :- use_module(specfile, [b_or_z_mode/0]).
59
60 :- set_prolog_flag(double_quotes, codes).
61
62 :- dynamic java_parser_version/6.
63
64 % stores the java process of the parser, consisting of ProcessIdentifier, Socket Stream, STDErrStream
65 :- dynamic java_parser_process/4.
66 :- volatile java_parser_process/4.
67
68
69 send_definition(Stream,def(Name,Type,Arity)) :-
70 write(Stream,'definition'), nl(Stream),
71 format(Stream,'~w\n~w\n~w\n',[Name,Type,Arity]).
72
73 :- dynamic definitions_already_sent/0.
74 :- volatile definitions_already_sent/0.
75
76 send_definitions(ToParser) :-
77 b_or_z_mode, b_machine_is_loaded,
78 \+ definitions_already_sent,
79 !,
80 findall_definitions(L),
81 % format('~nSending definitions ~w~n~n',[L]),
82 maplist(send_definition(ToParser),L),
83 assertz(definitions_already_sent).
84 send_definitions(_).
85
86 findall_definitions(DefList) :-
87 findall(def(Name,Type,Arity),(b_get_definition(Name,Type,Args,_,_),length(Args,Arity)),DefList).
88
89 get_definitions(L) :- b_or_z_mode, b_machine_is_loaded,!, findall_definitions(L).
90 get_definitions([]).
91
92 reset_definitions :-
93 retractall(definitions_already_sent),
94 parser_is_launched, % otherwise no need to reset; inside prob2_kernel there is no Java parser for probcli
95 (debug_mode(off) -> true
96 ; get_parser_version(Version),
97 format('Resetting DEFINITIONS for parser version ~w ~n',[Version])
98 ),
99 % TO DO: check if parser Version is at least 2.9.27
100 get_console_parser(ParserStream,Out,Err),!,
101 write(ParserStream,'resetdefinitions'), nl(ParserStream), % only supported in more recent versions of the parser
102 flush_output(ParserStream),
103 display_pending_outputs(Out,user_output),
104 display_pending_outputs(Err,user_error).
105 reset_definitions.
106
107 % update preferences of parser using new PREPL commands
108 update_jvm_parser_preferences :-
109 get_preference(jvm_parser_fastrw,FAST),
110 try_set_parser_option_nc(fastPrologOutput,FAST,_),
111 get_preference(jvm_parser_position_infos,LINENO),
112 try_set_parser_option_nc(addLineNumbers,LINENO,_),
113 % we have to set the swi mode here so it works with older parser versions
114 (current_prolog_flag(dialect, swi) -> SWI=true ; SWI=false),
115 try_set_parser_option_nc(swiSupport,SWI,_),
116 (debug_mode(off) -> VERBOSE=false ; VERBOSE=true),
117 try_set_parser_option_nc(verbose,VERBOSE,_).
118
119
120 :- dynamic cur_defaultFileNumber/1.
121
122 try_set_parser_option(defaultFileNumber,Value,Res) :- !,
123 (cur_defaultFileNumber(Value) % cache last value to avoid unnecessary parser calls
124 -> Res=prev_value(Value) % nothing to do
125 ; retractall(cur_defaultFileNumber(_)),
126 assert(cur_defaultFileNumber(Value)),
127 try_set_parser_option_nc(defaultFileNumber,Value,Res)
128 ).
129 try_set_parser_option(Name,Value,Res) :-
130 try_set_parser_option_nc(Name,Value,Res).
131
132 reset_parser_option_cache :- retractall(cur_defaultFileNumber(_)).
133
134 % try_set_parser_option_nc: non-caching version
135 try_set_parser_option_nc(Name,Value,Res) :-
136 parser_command_supported(setoption),
137 !,
138 debug_format(4,'Updating parser option: ~q=~q~n',[Name,Value]),
139 get_console_parser(Stream,_Out,Err),
140 write(Stream,setoption), nl(Stream),
141 write(Stream,Name), nl(Stream),
142 write(Stream,Value), nl(Stream),
143 flush_output(Stream),
144 read_line(Stream,CodesIn),
145 my_read_from_codes(CodesIn,Res,Stream,Err).
146 try_set_parser_option_nc(Name,Value,Res) :-
147 old_option_command(Name,Command),
148 parser_command_supported(Command),
149 !,
150 debug_format(19,'Updating JVM parser option (using old command ~q): ~q=~q~n',[Command,Name,Value]),
151 get_console_parser(Stream,_Out,_Err),
152 write(Stream,Command), nl(Stream),
153 write(Stream,Value), nl(Stream),
154 flush_output(Stream),
155 Res = changed. % prev_value isn't returned here
156 try_set_parser_option_nc(Name,Value,unsupported) :-
157 debug_format(19,'Parser too old to change option at runtime: ~q=~q~n',[Name,Value]).
158
159 get_parser_option(Name,Value) :-
160 parser_command_supported(getoption),
161 !,
162 debug_format(4,'Getting parser option: ~q~n',[Name]),
163 get_console_parser(Stream,_Out,Err),
164 write(Stream,getoption), nl(Stream),
165 write(Stream,Name), nl(Stream),
166 flush_output(Stream),
167 read_line(Stream,CodesIn),
168 my_read_from_codes(CodesIn,Value,Stream,Err).
169
170 old_option_command(addLineNumbers,lineno).
171 old_option_command(verbose,verbose).
172 old_option_command(fastPrologOutput,fastprolog).
173 old_option_command(compactPrologPositions,compactpos).
174 old_option_command(machineNameMustMatchFileName,checkname).
175
176 ?reset_old_parser_option_value(Name,Value,prev_value(Old)) :- \+ unchanged(Value,Old), !,
177 try_set_parser_option(Name,Old,_).
178 reset_old_parser_option_value(_,_,_).
179
180 % the Java values are stored as strings, even for number attributes
181 unchanged(V,V).
182 unchanged(N,A) :- number(N), atom(A), number_codes(N,C), atom_codes(A,C).
183
184 reset_parser :- reset_definitions, reset_parser_option_cache.
185 :- use_module(probsrc(eventhandling),[register_event_listener/3]).
186 :- register_event_listener(clear_specification,reset_parser,
187 'Remove DEFINITIONS from parser cache and reset parer options cache.').
188
189 crlf(10).
190 crlf(13).
191
192 % remove newlines in a B formula so that we can pass the formula as a single line to the parser
193 cleanup_newlines([],[]).
194 cleanup_newlines([H|T],CleanCodes) :- crlf(H),!,
195 % this could also be inside a multi-line string; the string will be modified by this conversion
196 CleanCodes=[8232|TC], % 8232 \x2028 is Unicode line separator
197 cleanup_newlines(T,TC).
198 %cleanup_newlines([47,47|T],CleanCodes) :-
199 % % a B Comment '//': we used to skip until end of line
200 % % but this could be inside a string ! see test 2236
201 % CleanCodes=[8232|TC], skip_until_crlf(T,T2), !, cleanup_newlines(T2,TC).
202 cleanup_newlines([H|T],[H|R]) :- cleanup_newlines(T,R).
203
204 %skip_until_crlf([],[]).
205 %skip_until_crlf([H|T],T) :- crlf(H),!.
206 %skip_until_crlf([_|T],R) :- skip_until_crlf(T,R).
207
208 % register parsing call back from prob_socket_server within ProB2
209 :- dynamic prob2_call_back_available/1.
210 register_parsing_call_back(CallBackPred4) :- deregister_parsing_call_back,
211 assertz(prob2_call_back_available(CallBackPred4)).
212 deregister_parsing_call_back :-
213 retractall(prob2_call_back_available(_)).
214
215 % ---------
216
217 %! parse_x(+Kind,+Codes,-Tree)
218 % Kind is formula, expression, predicate, substitution
219 %:- use_module(prob_socketserver,[prob2_call_back_available/0, prob2_call_back/2]).
220 parse_x(Kind,CodesWithNewlines,Tree) :-
221 parse_simple(Kind,CodesWithNewlines,Res),!,
222 % format('Parse simple ~s : ~w~n',[CodesWithNewlines,Res]),
223 Tree=Res.
224 parse_x(Kind,CodesWithNewlines,Tree) :-
225 parse_y(Kind,CodesWithNewlines,Tree).
226
227 % a version which does not attempt simple parsing without calling Java:
228 parse_y(Kind,CodesWithNewlines,Tree) :-
229 prob2_call_back_available(ParseCallBackPred),
230 cleanup_newlines(CodesWithNewlines,Codes), atom_codes(Formula,Codes),
231 debug_format(19,'Parsing ~w via call_back: ~w~n',[Kind,Formula]),
232 get_definitions(DefList),
233 call(ParseCallBackPred,Kind,DefList,Formula,Tree),
234 % TO DO: deal with substitutions
235 debug_println(19,prob2_call_back_available_parse_result(Tree)),
236 (Tree = call_back_not_supported ->
237 % Parsing callback isn't implemented (e. g. ProB Rodin plugin) - don't try to use it again in the future.
238 deregister_parsing_call_back,
239 fail
240 ; true),
241 !,
242 (Tree = parse_error(Exception)
243 -> handle_parser_exception(Exception)
244 ; functor(Tree,parse_error,_) % deprecated
245 -> throw(parse_errors([error('Parse error occurred via ProB2 call_back:',unknown)]))
246 ; true).
247 parse_y(Kind,CodesWithNewlines,Tree) :-
248 % Java parser expects only one line of input -> remove newlines
249 cleanup_newlines(CodesWithNewlines,Codes),
250 % statistics(walltime,[Tot,Delta]), format('~s~n~w~n0 ~w (Delta ~w) ms ~n',[Codes,Kind,Tot,Delta]),
251 get_console_parser(Stream,Out,Err),
252 send_definitions(Stream),
253 write(Stream,Kind),
254 nl(Stream),
255 format(Stream,'~s',[Codes]), %format(user_output,'sent: ~s~n',[Codes]),
256 nl(Stream),
257 flush_output(Stream),
258 read_line(Stream,CodesIn),
259 %format('read: ~s~n',[CodesIn]),
260 catch(
261 (my_read_from_codes(CodesIn,Tree,Stream,Err),handle_parser_exception(Tree)),
262 error(_,_),
263 (append("Illegal parser result exception: ",CodesIn,ErrMsgCodes),
264 atom_codes(ErrMsg,ErrMsgCodes),
265 throw(parse_errors([internal_error(ErrMsg,none)])))),
266 display_pending_outputs(Out,user_output).
267 %statistics(walltime,[Tot4,Delta4]), format('4 ~w (Delta ~w) ms ~n ~n',[Tot4,Delta4]).
268
269 % a few very simple cases, which can be parsed without accessing Java parser:
270 % common e.g., in JSON trace files or Latex files to avoid overhead of calling parser
271 parse_simple(Kind,Codes,AST) :-
272 (Kind=expression -> true ; Kind=formula),
273 (cur_defaultFileNumber(FN) -> true ; FN = -1),
274 parse_simple_codes(Codes,FN,1,1,AST).
275
276 % ---------------------------
277
278 % benchmarking code:
279 % statistics(walltime,[_W1,_]),(for(I,1,10000) do parsercall:parse_formula("123",Tree)),statistics(walltime,[_W2,_]),D is _W2-_W1.
280 % | ?- findall("|-> 123",between(2,10000,X),L), append(["123 "|L],Str), statistics(walltime,[_W1,_]),parsercall:parse_expression(Str,Tree), statistics(walltime,[_W2,_]),D is _W2-_W1.
281
282 parse_simple_codes(Codes,FileNr,SL,SC,AST) :-
283 parse_int_codes(Codes,Len,Val), !,
284 L2 is Len+SC, % EndColumn of p4 position (same line)
285 AST=integer(p4(FileNr,SL,SC,L2),Val).
286 parse_simple_codes("TRUE",FileNr,SL,SC,AST) :- !, EC is SC+4, AST=boolean_true(p4(FileNr,SL,SC,EC)).
287 parse_simple_codes("FALSE",FileNr,SL,SC,AST) :- !, EC is SC+5, AST=boolean_false(p4(FileNr,SL,SC,EC)).
288 parse_simple_codes("{}",FileNr,SL,SC,AST) :- !, EC is SC+2, AST=empty_set(p4(FileNr,SL,SC,EC)).
289 ?parse_simple_codes(Codes,FileNr,SL,SC,AST) :- is_real_literal_codes(Codes),!,
290 length(Codes,Len), L2 is Len+SC,
291 atom_codes(Atom,Codes),
292 AST=real(p4(FileNr,SL,SC,L2),Atom).
293 % TO DO: maybe simple string values, simple identifiers: but we need to know the keyword list for this
294
295 :- assert_must_succeed((parsercall:parse_int_codes("0",Len,Res), Len==1, Res==0)).
296 :- assert_must_succeed((parsercall:parse_int_codes("1",Len,Res), Len==1, Res==1)).
297 :- assert_must_succeed((parsercall:parse_int_codes("12",Len,Res), Len==2, Res==12)).
298 :- assert_must_succeed((parsercall:parse_int_codes("931",Len,Res), Len==3, Res==931)).
299 :- assert_must_succeed((parsercall:parse_int_codes("100931",Len,Res), Len==6, Res==100931)).
300 parse_int_codes([Digit|T],Len,Res) :- digit_code_2_int(Digit,DVal),
301 (DVal=0 -> T=[], Len=1, Res=0
302 ; parse_int2(T,DVal,Res,1,Len)).
303
304 parse_int2([],Acc,Acc,LenAcc,LenAcc).
305 parse_int2([Digit|T],Acc,Res,LenAcc,Len) :-
306 digit_code_2_int(Digit,DVal),
307 NewAcc is Acc*10 + DVal,
308 L1 is LenAcc+1,
309 parse_int2(T,NewAcc,Res,L1,Len).
310
311 digit_code_2_int(X,Val) :- X >= 48, X =< 57, Val is X - 48.
312 is_digit(X) :- X >= 48, X =< 57.
313
314 :- assert_must_succeed(parsercall:is_real_literal_codes("0.0")).
315 :- assert_must_succeed(parsercall:is_real_literal_codes("112300.0010")).
316 :- assert_must_succeed(parsercall:is_real_literal_codes("1234567890.9876543210")).
317 :- assert_must_succeed(parsercall:is_real_literal_codes("001.0")). % is accepted by parser
318 :- assert_must_fail(parsercall:is_real_literal_codes("0")).
319 :- assert_must_fail(parsercall:is_real_literal_codes("11.")).
320 :- assert_must_fail(parsercall:is_real_literal_codes(".12")).
321 :- assert_must_fail(parsercall:is_real_literal_codes("12a.0")).
322 % TODO: we could return length and merge with parse_int_codes to do only one traversal
323
324 ?is_real_literal_codes([Digit|T]) :- is_digit(Digit), is_real_lit1(T).
325 is_real_lit1([0'.,Digit|T]) :- is_digit(Digit), is_real_lit2(T).
326 is_real_lit1([Digit|T]) :- is_digit(Digit), is_real_lit1(T).
327 is_real_lit2([]).
328 is_real_lit2([Digit|T]) :- is_digit(Digit), is_real_lit2(T).
329
330 % ---------------------
331
332 my_read_from_codes(end_of_file,_,_,Err) :- !,
333 read_line_if_ready(Err,Err1Codes), % we just read one line
334 safe_name(ErrMsg,Err1Codes),
335 add_error(parsercall,'Abnormal termination of parser: ',ErrMsg),
336 missing_parser_diagnostics,
337 ajoin(['Parser not available (',ErrMsg,')'],FullErrMsg),
338 read_lines_and_add_as_error(Err), % add other info on error stream as single error
339 throw(parse_errors([error(FullErrMsg,none)])).
340 my_read_from_codes(ErrorCodes,_Tree,Out,_) :-
341 append("Error",_,ErrorCodes),!,
342 atom_codes(ErrMsg,ErrorCodes),
343 add_error(parsercall,'Error running/starting parser: ',ErrMsg),
344 read_lines_and_add_as_error(Out),
345 fail.
346 my_read_from_codes(CodesIn,Tree,_,_) :- read_from_codes(CodesIn,Tree).
347
348 % a version of my_read_from_codes which has no access to error stream
349 my_read_from_codes(end_of_file,_) :- !,
350 missing_parser_diagnostics,
351 throw(parse_errors([error('Parser not available (end_of_file on input stream)',none)])).
352 my_read_from_codes(ErrorCodes,_Tree) :-
353 append("Error",_,ErrorCodes),!,
354 atom_codes(ErrMsg,ErrorCodes),
355 add_error(parsercall,'Error running/starting parser: ',ErrMsg),
356 fail.
357 my_read_from_codes(CodesIn,Tree) :- read_from_codes(CodesIn,Tree).
358
359 :- use_module(probsrc(preferences),[get_prob_application_type/1]).
360 missing_parser_diagnostics :-
361 parser_location(Classpath), debug_println(9,classpath(Classpath)),fail.
362 missing_parser_diagnostics :- runtime_application_path(P),
363 atom_concat(P,'/lib/probcliparser.jar',ConParser), % TODO: adapt for GraalVM cliparser
364 (file_exists(ConParser)
365 -> add_error(parsercall,'The Java B parser (probcliparser.jar) cannot be launched: ',ConParser),
366 (get_prob_application_type(tcltk) ->
367 add_error(parsercall,'Please check that Java and B Parser are available using the "Check Java and Parser Version" command in the Debug menu.')
368 ; host_platform(windows) ->
369 add_error(parsercall,'Please check that Java and B Parser are available, e.g., using "probcli.exe -check_java_version" command.')
370 ; add_error(parsercall,'Please check that Java and B Parser are available, e.g., using "probcli -check_java_version" command.')
371 % application_type
372 % TODO: avoid printing the message when the user is already calling check_java_version
373 ),
374 (get_preference(jvm_parser_additional_args,ExtraArgStr), ExtraArgStr\=''
375 -> add_error(parsercall,'Also check your JVM_PARSER_ARGS preference value:',ExtraArgStr)
376 ; true)
377 ; add_internal_error('Java B parser (probcliparser.jar) is missing from lib directory in: ',P)
378 ).
379
380 % ProB2 cli builds do not have the cli parser bundled
381 % check if there is a jar available in the lib folder:
382 % should only happen for get_prob_application_type(probcli) in ProB2
383 console_parser_jar_available_in_lib :-
384 runtime_application_path(P),
385 atom_concat(P,'/lib/probcliparser.jar',ConParser),
386 file_exists(ConParser).
387
388 handle_parser_exception(Exception) :-
389 ? handle_parser_exception(Exception,ExAuxs,[]),
390 !,
391 throw(parse_errors(ExAuxs)).
392 handle_parser_exception(_).
393
394 handle_parser_exception(compound_exception([])) --> [].
395 handle_parser_exception(compound_exception([Ex|MoreEx])) -->
396 handle_parser_exception(Ex),
397 handle_parser_exception(compound_exception(MoreEx)).
398 % Non-list version of parse_exception is handled in handle_parser_exception_aux.
399 % (Note: The non-list version is no longer generated by the parser -
400 % see comments on handle_console_parser_result below.)
401 handle_parser_exception(parse_exception([],_Msg)) --> [].
402 handle_parser_exception(parse_exception([Pos|MorePos],Msg)) -->
403 [error(Msg,Pos)],
404 ? handle_parser_exception(parse_exception(MorePos,Msg)).
405 handle_parser_exception(Ex) -->
406 {handle_parser_exception_aux(Ex,ExAux)},
407 [ExAux].
408
409 handle_parser_exception_aux(parse_exception(Pos,Msg),error(SanitizedMsg,Pos)) :-
410 remove_msg_posinfo_known(Msg,SanitizedMsg).
411 handle_parser_exception_aux(io_exception(Pos,Msg),error(Msg,Pos)).
412 handle_parser_exception_aux(io_exception(Msg),error(Msg,unknown)).
413 handle_parser_exception_aux(exception(Msg),error(Msg,unknown)). % TO DO: get Pos from Java parser !
414
415 %! parse_formula(+Codes,-Tree)
416 parse_formula(Codes,Tree) :-
417 parse_x(formula,Codes,Tree).
418
419 %! parse_expression(+Codes,-Tree)
420 parse_expression(Codes,Tree) :-
421 parse_x(expression,Codes,Tree).
422
423 %! parse_predicate(+Codes,-Tree)
424 parse_predicate(Codes,Tree) :-
425 parse_x(predicate,Codes,Tree).
426
427 %! parse_substitution(+Codes,-Tree)
428 parse_substitution(Codes,Tree) :-
429 parse_x(substitution,Codes,Tree).
430
431 % parse in the context of particular files and position within the file (e.g., VisB JSON file)
432
433 parse_at_position_in_file(Kind,Codes,Tree,Span,Filenumber) :- Span \= unknown,
434 %format('Parse @ ~w~n ~s~n',[Span,Codes]),
435 extract_line_col_for_b_parser(Span,Line,Col),!,
436 parse_at_position_in_file2(Kind,Codes,Tree,Filenumber,Line,Col).
437 parse_at_position_in_file(Kind,Codes,Tree,_,_) :-
438 parse_x(Kind,Codes,Tree).
439
440 parse_at_position_in_file2(Kind,Codes,Tree,Filenumber,Line,Col) :-
441 (Kind=expression -> true ; Kind=formula),
442 % special case to avoid setting parser options if parser not called in parse_x !
443 parse_simple_codes(Codes,Filenumber,Line,Col,AST),!,
444 Tree=AST.
445 parse_at_position_in_file2(Kind,Codes,Tree,Filenumber,Line,Col) :-
446 (Line \= 1 -> try_set_parser_option_nc(startLineNumber,Line,_OldLine)
447 ; true), % default in ParsingBehaviour.java: 1
448 (Col \= 1 -> try_set_parser_option_nc(startColumnNumber,Col,_OldCol)
449 ; true), % default in ParsingBehaviour.java: 1
450 (integer(Filenumber) -> Fnr=Filenumber ; format('Invalid filenumber : ~w~n',[Filenumber]), Fnr = -1),
451 try_set_parser_option(defaultFileNumber,Fnr,OldFile),
452 % Note: Filenumber will be used in AST, but parse errors will have null as filename
453 % format('Parsing at line ~w col ~w in file ~w (old ~w:~w in ~w)~n',[Line,Col,Filenumber,OldLine,OldCol,OldFile]),
454 call_cleanup(parse_y(Kind,Codes,Tree),
455 (%reset_old_parser_option_value(startLineNumber,Line,OldLine), % not required anymore, is now volatile
456 %reset_old_parser_option_value(startColumnNumber,Col,OldCol), % not required anymore, is now volatile
457 % TODO: should we check at startup whether the parser has volatilePosOptions feature?
458 reset_old_parser_option_value(defaultFileNumber,Filenumber,OldFile))).
459
460 extract_line_col_for_b_parser(Span,Line,Col1) :-
461 extract_line_col(Span,Line,Col,_EndLine,_EndCol),
462 Col1 is Col+1. % the BParser starts column numbering at 1
463
464 set_default_filenumber(Filenumber,OldFile) :- try_set_parser_option(defaultFileNumber,Filenumber,OldFile).
465 reset_default_filenumber(Filenumber,OldFile) :- reset_old_parser_option_value(defaultFileNumber,Filenumber,OldFile).
466
467 %! parse(+Kind,+Codes,-Tree)
468 parse(Kind,Codes,Tree) :- parse_x(Kind,Codes,Tree).
469
470 %! parse_temporal_formula(+Kind,+LanguageExtension,+Formula,-Tree)
471 % Formula is either an atom or a codes list
472 % LanguageExtension is either ltl, ctl or pctl
473 % TODO: we could check if the parser supports the pctl command before sending it
474 parse_temporal_formula(Kind,LanguageExtension,Formula,Tree) :-
475 (Formula = [Nr|_], integer(Nr)
476 -> CodesWithNewlines = Formula
477 ; write_to_codes(Formula,CodesWithNewlines)
478 ),
479 % Java parser expects only one line of input -> remove newlines
480 cleanup_newlines(CodesWithNewlines,Codes),
481 get_console_parser(Stream,Out,Err),
482 send_definitions(Stream),
483 format(Stream,'~s', [Kind]), nl(Stream),
484 format(Stream,'~s', [LanguageExtension]), nl(Stream),
485 format(Stream,'~s',[Codes]), nl(Stream),
486 flush_output(Stream),
487 % format('Parsing temporal formula, kind=~s, lge=~s, formula="~s"~n',[Kind,LanguageExtension,Codes]),
488 read_line(Stream,CodesIn), % TODO: Improve feedback from java!
489 catch(my_read_from_codes(CodesIn,Tree,Stream,Err),_,throw(parse_errors([error(exception,none)]))),
490 display_pending_outputs(Out,user_output).
491
492 % throws parse_errors(Errors) in case of syntax errors
493 load_b_machine_as_term(Filename, Machine,Options) :- %print(load_b_machine(Filename)),nl,
494 prob_filename(Filename, ProBFile),
495 debug_println(9,prob_filename(Filename,ProBFile)),
496 ( get_preference(jvm_parser_force_parsing,false),
497 dont_need_compilation(Filename,ProBFile,Machine,LoadResult,Options) ->
498 % no compilation is needed, .prob file was loaded
499 release_parser_if_requested(Options),
500 (LoadResult=loaded -> debug_println(20,'.prob file up-to-date')
501 ; print_error('*** Loading failed *** '),nl,fail)
502 ; % we need to parse and generate .prob file
503 (debug:debug_mode(on) ->
504 time_with_msg('generating .prob file with Java parser',call_console_parser(Filename,ProBFile))
505 ; call_console_parser(Filename,ProBFile)
506 ),
507 release_parser_if_requested(Options),
508 load_b_machine_probfile_as_term(ProBFile, Options, Machine)
509 ).
510 ?release_parser_if_requested(Options) :- (member(release_java_parser,Options) -> release_console_parser ; true).
511
512 % converts the filename of the machine into a filename for the parsed machine
513 prob_filename(Filename, ProB) :-
514 split_filename(Filename,Basename,_Extension),
515 safe_atom_chars(Basename,BasenameC,prob_filename1),
516 append(BasenameC,['.','p','r','o','b'],ProBC),
517 safe_atom_chars(ProB,ProBC,prob_filename2),!.
518 prob_filename(Filename, ProB) :-
519 add_failed_call_error(prob_filename(Filename,ProB)),fail.
520
521 check_version_and_read_machine(Filename,ProBFile, ProbTime, Version, GitSha, Machine,Options) :-
522 (Version='$UNKNOWN'
523 -> add_warning(parsercall,'*** Unknown parser version number. Trying to load parsed file: ',ProBFile)
524 /* keep CheckVersionNr as variable */
525 ; CheckVersionNr=Version),
526 read_machine_term_from_file(ProBFile,prob_parser_version(CheckVersionNr,GitSha),
527 [check_if_up_to_date(Filename,ProbTime)|Options],Machine).
528
529 read_machine_term_from_file(ProBFile,VersionTerm,Options,CompleteMachine) :-
530 (debug:debug_mode(on)
531 -> time_with_msg('loading .prob file',
532 read_machine_term_from_file_aux(ProBFile,VersionTerm,Options,CompleteMachine))
533 ; read_machine_term_from_file_aux(ProBFile,VersionTerm,Options,CompleteMachine)).
534
535 read_machine_term_from_file_aux(ProBFile,VersionTerm,Options,complete_machine(MainName,Machines,Files)) :-
536 open_probfile(ProBFile,Options,Stream,Opt2),
537 call_cleanup(( safe_read_term(Stream,Opt2,ProBFile,parser_version,VersionTermInFile),
538 debug_format(9,'Parser version term in file: ~w~n',[VersionTermInFile]),
539 same_parser_version(VersionTermInFile,VersionTerm), % CHECK correct version
540 read_machines(Stream,ProBFile,Opt2,Machines,MainName,Files),
541 (var(MainName)
542 -> add_internal_error('Missing classical_b fact',ProBFile), MainName=unknown,Files=[]
543 ; true)
544 ),
545 close(Stream)).
546
547 % open a .prob file:
548 open_probfile(ProBFile,Options,NewStream,NewOptions) :-
549 open(ProBFile, read, Stream),
550 file_property(ProBFile,size_in_bytes,Size),
551 check_prob_file_not_empty(Stream,Size,ProBFile,Options),
552 peek_code(Stream,Code),
553 open_probfile_aux(Code,Size,Stream,ProBFile,Options,NewStream,NewOptions).
554
555 open_probfile_aux(Code,_,Stream,ProBFile,Options,NewStream,NewOptions) :-
556 fastrw_start_code(Code),!,
557 close(Stream),
558 add_message(parsercall,'Reading .prob file using fastrw library: ',ProBFile),
559 open(ProBFile, read, NewStream, [type(binary)]),
560 % delete(use_fastread)
561 NewOptions = [use_fastrw|Options].
562 open_probfile_aux(Code,Size,Stream,ProBFile,Options,Stream,NewOptions) :-
563 check_prob_file_first_code(Code,Stream,ProBFile,Options),
564 update_options(Options,Size,NewOptions).
565
566 % automatically use fastread if file large
567 update_options(Options,Size,Opt2) :- nonmember(use_fastread,Options),
568 nonmember(use_fastrw,Options),
569 Size>1000000, % greater than 1 MB
570 !, Opt2 = [use_fastread|Options],
571 debug_println(19,automatically_using_fastread(Size)).
572 update_options(Opts,_,Opts).
573
574 % check if the file starts out in an expected way
575 check_prob_file_not_empty(Stream,Size,ProBFile,Options) :- Size=<0,!,
576 close(Stream),
577 (member(check_if_up_to_date(_,_),Options)
578 -> add_warning(parsercall,'Re-running parser as .prob file is empty: ',ProBFile)
579 % due to possible crash or CTRL-C of previous parser run
580 ; add_internal_error('Generated .prob file is empty',ProBFile)
581 ),fail.
582 check_prob_file_not_empty(_,_,_,_).
583
584 % check first character code
585 check_prob_file_first_code(Code,Stream,ProBFile,Options) :-
586 (valid_start_code(Code) -> true
587 ; fastrw_start_code(Code)
588 -> close(Stream),
589 % we need to do: open(ProBFile,read,S,[type(binary)]),
590 (member(check_if_up_to_date(_,_),Options)
591 -> add_warning(parsercall,'Re-running parser as .prob file seems to be in new fast-rw format: ',ProBFile)
592 ; add_error(parsercall,'Cannot load .prob file; it seems to be in new fast-rw format:',ProBFile)
593 ),
594 fail
595 ; add_message(parsercall,'Strange start character code in .prob file: ',[Code]) % probably syntax error will happen
596 ).
597
598 :- if(current_prolog_flag(dialect, swi)).
599 fastrw_start_code(C) :- fastrw_start_code_swi(C).
600
601 fastrw_start_code_swi(C) :- platform_is_64_bit -> fastrw_start_code_swi_64(C) ; fastrw_start_code_swi_32(C).
602 fastrw_start_code_swi_64(98). % b / 0x62, base header for 64bit
603 fastrw_start_code_swi_64(114). % r / 0x72, base header + ground for 64bit
604 fastrw_start_code_swi_64(118). % v / 0x76, int fast path for 64bit
605 fastrw_start_code_swi_64(122). % z / 0x7a, atom fast path for 64bit
606 fastrw_start_code_swi_32(97). % a / 0x61, base header for 32bit
607 fastrw_start_code_swi_32(113). % q / 0x71, base header + ground for 32bit
608 fastrw_start_code_swi_32(117). % u / 0x75, int fast path for 32bit
609 fastrw_start_code_swi_32(121). % y / 0x79, atom fast path for 32bit
610 :- else.
611 fastrw_start_code(C) :- fastrw_start_code_sicstus(C).
612
613 fastrw_start_code_sicstus(0'D). % typical start DS...
614 :- endif.
615
616
617
618 valid_start_code(0'p). % from parser_version(_) term
619 valid_start_code(37). % percentage sign; appears when parser called with verbose flag
620 valid_start_code(47). % start of comment slash (inserted by user)
621 valid_start_code(39). % ' (inserted by user)
622 valid_start_code(32). % whitespace (inserted by user)
623 valid_start_code(8). % tab (inserted by user)
624 valid_start_code(10). % lf (inserted by user)
625 valid_start_code(13). % cr (inserted by user)
626
627 % --------------------
628
629 % use various read_term mechanisms depending on Options
630
631 safe_read_term(Stream,Options,File,Expecting,T) :-
632 catch(
633 safe_read_term2(Options,Stream,File,Expecting,T),
634 error(permission_error(_,_,_),ERR),
635 (
636 ajoin(['Permission error in .prob file trying to read ',Expecting,' term in ',File,':'],Msg),
637 add_internal_error(Msg,ERR),
638 fail
639 )).
640
641 :- use_module(tools_fastread,[read_term_from_stream/2, fastrw_read/3]).
642
643 safe_read_term2([use_fastrw|_],Stream,File,Expecting,Term) :- !,
644 fastrw_read(Stream,Term,Error),
645 (Error=false -> true
646 ; ajoin(['.prob (fastrw) file has error in ',Expecting,' term:'],Msg),
647 add_internal_error(Msg,File),
648 fail
649 ), functor(Term,F,N),debug_println(19,fast_read_term(F,N)).
650 safe_read_term2([use_fastread|_],Stream,File,Expecting,Term) :- !,
651 (read_term_from_stream(Stream,Term) -> true
652 ; ajoin(['.prob file has Prolog syntax error in ',Expecting,' term:'],Msg),
653 add_internal_error(Msg,File), fail
654 ).
655 safe_read_term2([_|Opts],Stream,File,Expecting,T) :- !,
656 safe_read_term2(Opts,Stream,File,Expecting,T).
657 safe_read_term2([],Stream,File,Expecting,T) :- % use regular SICStus Prolog reader
658 catch(read(Stream,T), error(E1,E2), (
659 ajoin(['.prob file (',File,') has error in ',Expecting,' term:'],Msg),
660 add_error(parser_call,Msg,error(E1,E2)),
661 fail
662 )).
663
664
665
666 % ------------------
667
668 % check if file was parsed with same parser version as currently in use by ProB
669 same_parser_version(parser_version(V), prob_parser_version(VB,GitSha)) :- !,
670 (V=VB -> true ; V=GitSha).
671 same_parser_version(end_of_file,_) :- !, debug_format(19,'.prob file is empty~n',[]).
672 same_parser_version(T,_) :-
673 add_internal_error('.prob file contains illegal parser_version term:',T),fail.
674
675 load_b_machine_list_of_facts_as_term(Facts,Machine) :-
676 read_machine_term_from_list_of_facts(Facts,_,Machine).
677 read_machine_term_from_list_of_facts(Facts,VersionTerm,complete_machine(MainName,Machines,FileList)) :-
678 (select(parser_version(VERS),Facts,F2) -> VersionTerm = parser_version(VERS)
679 ; add_internal_error('No parser_version available',read_machine_from_list_of_facts),
680 F2=Facts, VersionTerm = unknown),
681 (select(classical_b(MainName,FileList),F2,F3) -> true
682 ; add_internal_error('No classical_b file information available',read_machine_from_list_of_facts),
683 fail),
684 debug_println(9,loading_classical_b(VersionTerm,MainName,FileList)),
685 include(is_machine_term,F3,F4),
686 maplist(get_machine_term,F4,Machines).
687
688 is_machine_term(machine(_M)).
689 get_machine_term(machine(M),M).
690
691 load_b_machine_probfile_as_term(ProBFile, Machine) :-
692 load_b_machine_probfile_as_term(ProBFile, [], Machine).
693
694 load_b_machine_probfile_as_term(ProBFile, Options, Machine) :-
695 debug_println(9,consulting(ProBFile)),
696 ( read_machine_term_from_file(ProBFile,_VersionTerm,Options,Machine) -> true
697 ; add_error(parsercall,'Failed to read parser output: wrong format?',ProBFile),fail).
698
699 read_machines(S,ProBFile,Options,Machines,MainName,Files) :-
700 safe_read_term(S,Options,ProBFile,machine,Term),
701 %, write_term(Term,[max_depth(5),numbervars(true)]),nl,
702 ( Term == end_of_file ->
703 Machines = []
704 ; Term = classical_b(M,F) ->
705 ((M,F)=(MainName,Files) -> true ; add_internal_error('Inconsistent classical_b fact: ',classical_b(M,F))),
706 ? (member(check_if_up_to_date(MainFileName,ProbTime),Options)
707 -> debug_format(9,'Checking if .prob file up-to-date for subsidiary files and if it was generated for ~w~n',[MainFileName]),
708 all_older(Files, ProbTime), % avoid reading rest if subsidiary source files not all_older !
709 (Files = [File1|_],
710 same_file_name(MainFileName,File1) -> true
711 ; format('Re-parsing: .prob file created for different source file:~n ~w~n',[MainFileName]),
712 % this can happen, e.g., when we have M.def and M.mch and we previously loaded the other file
713 Files = [File1|_],
714 format(' ~w~n',[File1]),
715 fail
716 )
717 ; true),
718 read_machines(S,ProBFile,Options,Machines,MainName,Files)
719 ; Term = machine(M) ->
720 Machines = [M|Mrest],
721 read_machines(S,ProBFile,Options,Mrest,MainName,Files)
722 ).
723
724
725 % checks if all files that the prob-file depends on
726 % are older than the prob-file
727 dont_need_compilation(Filename,ProB,Machine,LoadResult,Options) :-
728 file_exists(Filename),
729 catch( ( get_parser_version(Version,GitSha),
730 file_property(Filename, modify_timestamp, BTime),
731 debug_format(9, 'Parser Version: ~w, Filename Timestamp: ~w : ~w~n',[Version,Filename,BTime]),
732 file_exists(ProB), % the .prob file exists
733 file_property(ProB, modify_timestamp, ProbTime),
734 debug_format(9, '.prob Timestamp: ~w : ~w~n',[ProB,ProbTime]),
735 % print(time_stamps(ProB,ProbTime,Filename,BTime)),nl,
736 BTime < ProbTime, % .mch file is older than .prob file
737 file_property(ProB,size_in_bytes,Size),
738 (Size>0 -> true
739 ; debug_mode(on),
740 add_message(parsercall,'.prob file is empty; parsing again',ProB),
741 % possibly due to crash or error before, cf second run of test 254
742 fail),
743 check_version_and_read_machine(Filename,ProB, ProbTime, Version, GitSha, Machine,Options),
744 %Machine = complete_machine(_,_,_),
745 LoadResult = loaded),
746 error(A,B),
747 (debug_println(9,error(A,B)),
748 (A=resource_error(memory)
749 -> add_error(load_b_machine,'Insufficient memory to load file.\nTry starting up ProB with more memory\n (e.g., setting GLOBALSTKSIZE=500M before starting ProB).'),
750 LoadResult=A
751 ; fail))).
752
753 % check that all included files are older than the .prob file (ProbTime):
754 all_older([],_).
755 all_older([File|Rest],ProbTime) :-
756 (file_exists(File)
757 -> file_property(File, modify_timestamp, BTime),
758 debug_format(9,' Subsidiary File Timestamp: ~w:~w~n',[File,BTime]),
759 ( BTime < ProbTime -> true
760 ; format('File has changed : ~w : ~w~n',[File,BTime]),
761 fail )
762 ; virtual_dsl_file(File) -> debug_format(9,'Virtual file generated by DSL translator: ~w~n',[File])
763 ; debug_format(20,'File does not exist anymore: ~w; calling parser.~n',[File]),fail),
764 all_older(Rest,ProbTime).
765
766 virtual_dsl_file(File) :- atom_codes(File,Codes),
767 Codes = [95|_], % file name starts with _ underscore
768 nonmember(47,Codes), % no slash
769 nonmember(92,Codes). % no backslash
770
771 :- use_module(system_call).
772
773 get_extra_args_list(ExtraArgs) :-
774 get_preference(jvm_parser_additional_args,ExtraArgsStr),
775 ExtraArgsStr \= '',
776 atom_codes(ExtraArgsStr,C),
777 split_chars(C," ",CA),
778 maplist(atom_codes,ExtraArgs,CA).
779
780 jvm_options -->
781 ({get_preference(jvm_parser_heap_size_mb,Heap), Heap>0} ->
782 {ajoin(['-Xmx',Heap,'m'],HeapOpt)},
783 [HeapOpt]
784 ;
785 % comment in to simulate low-memory situations
786 % use -Xmx221500000m instead to force exception and test ProB's response
787 [] %['-Xmx20m']
788 ),
789
790 ({get_extra_args_list(ExtraArgs)} ->
791 {debug_format(19,'Using additional arguments for JVM (JVM_PARSER_ARGS): ~w~n',[ExtraArgs])},
792 ExtraArgs
793 % use the former LARGE_JVM / use_large_jvm_for_parser by default
794 % if we are running on a 64-bit system
795 % FIXME Is it intentional that this option is not added if JVM_PARSER_ARGS is set?
796 ; {platform_is_64_bit} -> ['-Xss5m'] % default stacksize; set to -Xss150k to mimic low stack setting
797 ; []
798 ).
799
800 parser_jvm_options -->
801 {get_PROBPATH(PROBPATH), atom_concat('-Dprob.stdlib=', PROBPATH, Stdlibpref)},
802 [Stdlibpref],
803 jvm_options.
804
805
806 % we could do something like this: or allow user to provide list of JVM options
807 %get_gc_options([]) :- !,get_preference(jvm_parser_aggressive_gc,true).
808 %get_gc_options(['-XX:GCTimeRatio=19', '-XX:MinHeapFreeRatio=20', '-XX:MaxHeapFreeRatio=30']).
809 % see https://stackoverflow.com/questions/30458195/does-gc-release-back-memory-to-os
810
811 parser_cli_options -->
812 %% ['-v'], % comment in for verbose, -time for timing info
813 ({debug_mode(on)} -> ['-v', '-time'] ; []),
814
815 % useful for very large data validation machines
816 ({get_preference(jvm_parser_position_infos,true)} -> ['-lineno'] ; []),
817
818 %( get_preference(jvm_parser_fastrw,false) ; parser_version_at_least(2,12,0) )
819 % we cannot call: parser_version_at_least(2,12,0) as parser not yet started
820 % older parsers were printing comments into the binary fastrw output; TODO: perform check later
821 ({get_preference(jvm_parser_fastrw,true)} -> ['-fastprolog'] ; ['-prolog']),
822
823 % enable swi support when required
824 % does not work on older parsers and version check is inaccessible here
825 % ({current_prolog_flag(dialect, swi)} -> ['-swi'] ; []),
826
827 % -compactpos enables new p3, p4, p5 position terms and disables node numbering
828 ['-prepl', '-compactpos'].
829
830 parser_command_args(native(NativeCmd), NativeCmd) -->
831 parser_jvm_options,
832 parser_cli_options.
833 parser_command_args(java_jar(NativeCmd,JarPath), NativeCmd) -->
834 parser_jvm_options,
835 ['-jar', JarPath],
836 parser_cli_options.
837
838 % ensure that the console Java process is running
839 ensure_console_parser_launched :-
840 catch(parse_formula("1",_), E, (
841 add_internal_error('Cannot launch console parser (probcliparser.jar)',E),
842 fail
843 )).
844
845 parser_is_launched :-
846 java_parser_process(_,_,_,_).
847
848
849 % TO DO: also store output stream for debugging messages
850 get_console_parser(Stream,Out,Err) :-
851 java_parser_process(PID,Stream,Out,Err),
852 % On SICStus, calling is_process seams to be unreliable (if the process has crashed)
853 % and process_wait does not always work either,
854 % so first check if in and output streams are still available.
855 \+ at_end_of_stream(Stream),
856 % On SWI, at_end_of_stream doesn't detect broken pipes,
857 % so additionally also check that the process has not exited/crashed.
858 process_wait(PID,timeout,[timeout(0)]),
859 !,
860 (at_end_of_stream(Err)
861 -> add_error(parsercall,'Java process not running'),
862 read_lines_and_add_as_error(Stream)
863 ; true).
864 get_console_parser(Stream,Out,Err) :-
865 clear_old_console_parsers,
866 get_java_command_for_parser(ParserCmd),
867 phrase(parser_command_args(ParserCmd, NativeCmd), FullArgs),
868 debug_println(19,launching_java_console_parser(NativeCmd,FullArgs)),
869 debug_print_system_call(NativeCmd,FullArgs),
870 system_call_keep_open(NativeCmd,FullArgs,PID,_In,Out,Err,[]), % note: if probcliparser.jar does not exist we will not yet get an error here !
871 debug_println(9,java_console_parser_launched(PID)),
872 % read first line to get port number
873 safe_read_line(Out,Err,1,[],PortTerm),
874 connect_to_console_parser_on_port(PortTerm,PID,Out,Err,Stream),
875 !.
876 get_console_parser(_,_,_) :- missing_parser_diagnostics, fail.
877
878
879
880
881 connect_to_console_parser_on_port(PortTerm,PID,Out,Err,Stream) :-
882 catch(
883 socket_client_open('':PortTerm, Stream, [type(text),encoding(utf8)]),
884 Exc, %error(system_error,system_error(E)), % SPIO_E_NET_HOST_NOT_FOUND
885 (
886 ajoin(['Exception while opening parser socket on port ', PortTerm,
887 ' (possibly an error occurred during startup of the parser): '],Msg),
888 add_internal_error(Msg,Exc),
889 % e.g., not enough memory to start parser and wait for socket connection
890 read_lines_and_add_as_error(Err), % try and read additional info;
891 % if we set the stack size to be very small (-Xss20k) we get: Error: Could not create the Java Virtual Machine
892 fail
893 )),
894 assertz(java_parser_process(PID,Stream,Out,Err)).
895
896 % connect to a separately started parser
897 % allow to connect to a separately started java command line parser (java -jar probcliparser.jar -prepl)
898 connect_to_external_console_parser_on_port(PortNumber) :-
899 clear_old_console_parsers,
900 format('Trying to connect to external parser on port ~w~n',[PortNumber]),
901 Out=user_input, Err=user_input,
902 (connect_to_console_parser_on_port(PortNumber,external_process,Out,Err,_)
903 -> format('Connected to parser on port ~w~n',[PortNumber])
904 ; add_error(parsercall,'Could not connect to parser on port:',PortNumber)
905 ).
906
907 clear_old_console_parsers :-
908 retract(java_parser_process(PID,_,_,_)),
909 parser_process_release(PID),
910 fail.
911 clear_old_console_parsers.
912
913 parser_process_release(external_process) :- !.
914 parser_process_release(PID) :- process_release(PID).
915
916 % useful to try and free up memory
917 % alternatively we could add some JVM options: -XX:GCTimeRatio=19 -XX:MinHeapFreeRatio=20 -XX:MaxHeapFreeRatio=30
918 % see https://stackoverflow.com/questions/30458195/does-gc-release-back-memory-to-os
919 release_console_parser :-
920 (java_parser_process(PID,Stream,_,_),
921 PID \= external_process
922 -> format('Releasing Java parser id=~w (note: access to DEFINITIONS is lost)~n',[PID]),
923 write(Stream,'halt'), nl(Stream),
924 flush_output(Stream), % handled in Java in runPRepl in CliBParser.java;
925 retract(java_parser_process(PID,_,_,_)),
926 parser_process_release(PID) % or should we call process_kill ?
927 %process_kill(PID)
928 % Note: parser maybe launched again, but then not have access to DEFINITIONS
929 ; true).
930
931 :- use_module(runtime_profiler,[profile_single_call/3]).
932 call_console_parser(Filename, ProB) :-
933 profile_single_call('$parsing',unknown,parsercall:call_console_parser2(Filename, ProB)).
934 call_console_parser2(Filename, ProB) :-
935 update_jvm_parser_preferences,
936 get_console_parser(Stream,Out,Err),
937
938 % path to the .prob file
939 replace_windows_path_backslashes(ProB,ProBW),
940 % the input file
941 replace_windows_path_backslashes(Filename,FilenameW),
942 % call PREPL 'machine' command
943 debug_format(4,'PREPL command: machine~n~w~n~w~n',[FilenameW,ProBW]),
944 format(Stream,'machine~n~w~n~w~n',[FilenameW,ProBW]), % tell parser to write output to ProBW .prob file
945 flush_output(Stream),
946
947 %% WARNING: if the java parser writes too much output on the out stream it will block
948 %% until its output is read and we have a deadlock !
949 %% hence we use safe_polling_read_line
950 safe_polling_read_line(Stream,Out,Err,1,[],Term),
951
952 display_pending_outputs(Out,user_output),
953 handle_console_parser_result(Term,Err).
954
955
956 safe_read_line(Out,Err,LineNr,SoFar,Term) :-
957 safe_read_line_aux(read_line,Out,Err,LineNr,SoFar,Term).
958
959 safe_read_line_if_ready(Out,Err,LineNr,SoFar,Term) :-
960 safe_read_line_aux(read_line_if_ready,Out,Err,LineNr,SoFar,Term).
961
962 % a version that will check every second if there is output to be read
963 safe_polling_read_line(Stream,_Out,Err,LineNr,SoFar,Term) :-
964 stream_ready_to_read(Stream,2),!, % try for two seconds
965 safe_read_line_aux(read_line,Stream,Err,LineNr,SoFar,Term).
966 safe_polling_read_line(Stream,Out,Err,LineNr,SoFar,Term) :-
967 % this should normally not happen unless we have a debugging version of the parser
968 debug_format(19,'Parser not responded yet, trying to read its output~n',[]),
969 display_pending_outputs(Out,user_output),
970 read_lines_and_add_as_error(Err),
971 safe_polling_read_line(Stream,Out,Err,LineNr,SoFar,Term).
972
973 safe_read_line_aux(Pred,Out,Err,LineNr,SoFar,Term) :-
974 catch(call(Pred,Out,Codes),Exception, % read another line
975 (add_error(parsercall,'Exception while reading next line: ',Exception),
976 read_lines_and_add_as_error(Err),
977 display_pending_outputs(user_error,Out),
978 throw(Exception))),
979 Codes \= end_of_file, !, % happens if parser crashed and stream is closed
980 append(SoFar,Codes,NewCodes),
981 catch(my_read_from_codes(NewCodes,Term,Out,Err),Exception,
982 safe_read_exception(Out,Err,LineNr,Exception,NewCodes,Term)).
983 safe_read_line_aux(_Pred,_Out,Err,_LineNr,CodesSoFar,_) :-
984 safe_name(T,CodesSoFar),
985 add_error(parsercall,'Unexpected error while parsing machine: ',T),
986 read_lines_and_add_as_error(Err),fail.
987
988
989 safe_read_exception(Out,_,1,_Exception,CodesSoFar,_Term) :- append("Error",_,CodesSoFar),!,
990 % probably some Java error, we do not obtain a correct Prolog term, but probably something like:
991 % "Error occurred during initialization of VM"
992 safe_name(T,CodesSoFar),
993 add_error(parsercall,'Java error while parsing machine: ',T),
994 read_lines_and_add_as_error(Out),fail.
995 safe_read_exception(Out,Err,LineNr,error(syntax_error(M),_),CodesSoFar,Term) :- LineNr<10, % avoid infinite loop in case unexpected errors occur which cannot be solved by reading more input lines
996 !,
997 %(debug:debug_mode(off) -> true ; format('Syntax error in parser result (line ~w): ~w~nTrying to read another line.~n',[LineNr,M])),
998 add_warning(parsercall,'Syntax error in parser result; trying to read another line. Line:Error = ',LineNr:M),
999 L1 is LineNr+1,
1000 safe_read_line_if_ready(Out,Err,L1,CodesSoFar,Term). % try and read another line; we assume the syntax error is because the TERM is not complete yet and transmitted on multiple lines (Windows issue)
1001 safe_read_exception(_,_,_LineNr,parse_errors(Errors),_CodesSoFar,_Term) :- !,
1002 debug_println(4,read_parse_errors(Errors)),
1003 throw(parse_errors(Errors)).
1004 safe_read_exception(_,_,_LineNr,Exception,_CodesSoFar,_Term) :-
1005 add_internal_error('Unexpected exception occurred during parsing: ',Exception),fail.
1006 %safe_name(T,CodesSoFar), add_error_fail(parsercall,'Unexpected error while parsing machine: ',T).
1007
1008 safe_name(Name,Codes) :- var(Name),Codes == end_of_file,!,
1009 %add_internal_error('Parser does not seem to be available',''),
1010 Name=end_of_file.
1011 safe_name(Name,Codes) :- number(Name),!,
1012 safe_number_codes(Name,Codes).
1013 safe_name(Name,Codes) :-
1014 catch(atom_codes(Name,Codes), E,
1015 (print('Exception during atom_codes: '),print(E),nl,nl,throw(E))).
1016
1017 safe_number_codes(Name,Codes) :-
1018 catch(number_codes(Name,Codes), E,
1019 (print('Exception during number_codes: '),print(E),nl,nl,throw(E))).
1020
1021 % Note: As of parser version 2.9.28 commit ee2592d8ca2900b4e339da973920e034dff43658,
1022 % all parse errors are reported as terms of the form
1023 % parse_exception(Positions,Msg) where Positions is a list of pos/5 terms.
1024 % The term formats preparse_exception(Tokens,Msg) (where Tokens is a list of none/0 or pos/3 terms)
1025 % and parse_exception(Pos,Msg) (where Pos is a single none/0, pos/3 or pos/5 term)
1026 % are no longer generated by the parser.
1027 % The code for handling these old term formats can probably be removed soon.
1028
1029 % see also handle_parser_exception
1030 %handle_console_parser_result(E,_) :- nl,print(E),nl,fail.
1031 handle_console_parser_result(exit(0),_) :- !.
1032 handle_console_parser_result(io_exception(Msg),_) :- !,
1033 add_error_fail(parsercall,'Error while opening the B file: ',Msg).
1034 handle_console_parser_result(compound_exception(List),ErrStream) :- !,
1035 get_compound_exceptions(List,ErrStream,ParseErrors,[]),
1036 throw(parse_errors(ParseErrors)).
1037 handle_console_parser_result(preparse_exception(Tokens,Msg),_) :- !,
1038 remove_msg_posinfo(Msg,SanitizedMsg,MsgPos),
1039 findall(error(SanitizedMsg,Pos),member(Pos,Tokens),Errors1),
1040 (Errors1 = []
1041 -> /* if there are no error tokens: use pos. info from text Msg */
1042 Errors = [error(SanitizedMsg,MsgPos)]
1043 ; Errors = Errors1),
1044 debug_println(4,preparse_exception_parse_errors(Tokens,Msg,Errors)),
1045 throw(parse_errors(Errors)).
1046 handle_console_parser_result(parse_exception([],Msg),_) :-
1047 atom(Msg), atom_codes(Msg,MC),
1048 append("StackOverflowError",_,MC),!,
1049 add_error(parsercall,'Java VM error while running parser: ',Msg),
1050 print_hint('Try increasing stack size for Java using the JVM_PARSER_ARGS preference (e.g.,"-Xss10m").'),
1051 fail.
1052 handle_console_parser_result(parse_exception(Positions,Msg),_) :-
1053 (Positions = [] ; Positions = [_|_]), !,
1054 remove_msg_posinfo(Msg,SanitizedMsg,MsgPos),
1055 findall(error(SanitizedMsg,Pos),member(Pos,Positions),Errors1),
1056 (Errors1 = []
1057 -> /* if there are no error tokens: use pos. info from text Msg */
1058 Errors = [error(SanitizedMsg,MsgPos)]
1059 ; Errors = Errors1),
1060 debug_println(4,parse_exception_parse_errors(Positions,Msg,Errors)),
1061 throw(parse_errors(Errors)).
1062 handle_console_parser_result(parse_exception(Pos,Msg),_) :- !,
1063 remove_msg_posinfo_known(Msg,SanitizedMsg), %print(sanitized(SanitizedMsg)),nl,
1064 debug_println(4,parse_exception(Pos,Msg,SanitizedMsg)),
1065 throw(parse_errors([error(SanitizedMsg,Pos)])).
1066 handle_console_parser_result(exception(Msg),_) :- !,
1067 %add_error(bmachine,'Error in the classical B parser: ', Msg),
1068 remove_msg_posinfo(Msg,SanitizedMsg,Pos),
1069 debug_println(4,exception_in_parser(Msg,SanitizedMsg,Pos)),
1070 throw(parse_errors([error(SanitizedMsg,Pos)])).
1071 handle_console_parser_result(end_of_file,Err) :- !,
1072 % probably NullPointerException or similar in parser; no result on StdOut
1073 debug_println(9,end_of_file_on_parser_output_stream),
1074 format(user_error,'Detected abnormal termination of B Parser~n',[]), % print in case we block
1075 read_line_if_ready(Err,Err1),
1076 (Err1=end_of_file -> Msg = 'Abnormal termination of B Parser: EOF on streams'
1077 ; append("Abnormal termination of B Parser: ",Err1,ErrMsgCodes),
1078 safe_name(Msg,ErrMsgCodes),
1079 read_lines_and_add_as_error(Err) % also show additional error infos
1080 ),
1081 throw(parse_errors([error(Msg,none)])).
1082 handle_console_parser_result(compound_exception(Exs),_) :- !,
1083 maplist(handle_parser_exception_aux,Exs,ExAuxs),
1084 debug_println(4,compound_exception(Exs,ExAuxs)),
1085 throw(parse_errors(ExAuxs)).
1086 handle_console_parser_result(Term,_) :- !,
1087 write_term_to_codes(Term,Text,[]),
1088 safe_name(Msg,Text),
1089 %add_error(bmachine,'Error in the classical B parser: ', Msg),
1090 remove_msg_posinfo(Msg,SanitizedMsg,Pos),
1091 debug_println(4,unknown_error_term(Term,SanitizedMsg,Pos)),
1092 throw(parse_errors([error(SanitizedMsg,Pos)])).
1093
1094 % get all compound exceptions as a single result to be thrown once later:
1095 get_compound_exceptions([],_) --> [].
1096 get_compound_exceptions([Err1|T],ErrStream) -->
1097 {handle_and_catch(Err1,ErrStream,ParseErrors) },
1098 ParseErrors,
1099 get_compound_exceptions(T,ErrStream).
1100
1101 handle_and_catch(Exception,ErrStream,ParseErrors) :-
1102 catch(
1103 (handle_console_parser_result(Exception,ErrStream) -> ParseErrors=[] ; ParseErrors=[]),
1104 parse_errors(Errors1),
1105 ParseErrors=Errors1).
1106
1107 % now replaced by remove_msg_posinfo:
1108 %extract_position_info(Text,pos(Row,Col,Filename)) :-
1109 % atom_codes(Text,Codes),
1110 % epi(Row,Col,Filename,Codes,_),!.
1111 %extract_position_info(_Text,none).
1112
1113 :- assert_must_succeed((parsercall:epi(R,C,F,"[2,3] xxx in file: /usr/lib.c",[]), R==2,C==3,F=='/usr/lib.c')).
1114 :- assert_must_succeed((parsercall:epi(R,C,F,"[22,33] xxx yyy ",_), R==22,C==33,F=='unknown')).
1115
1116 % we expect error messages to start with [Line,Col] information
1117 epi(Row,Col,Filename) --> " ",!,epi(Row,Col,Filename).
1118 epi(Row,Col,Filename) --> "[", epi_number(Row),",",epi_number(Col),"]",
1119 (epi_filename(Filename) -> [] ; {Filename=unknown}).
1120 epi_number(N) --> epi_numbers(Chars),{safe_number_codes(N,Chars)}.
1121 epi_numbers([C|Rest]) --> [C],{is_number(C)},epi_numbers2(Rest).
1122 epi_numbers2([C|Rest]) --> [C],{is_number(C),!},epi_numbers2(Rest).
1123 epi_numbers2("") --> !.
1124 is_number(C) :- member(C,"0123456789"),!.
1125 epi_filename(F) --> " in file: ",!,epi_path2(Chars),{safe_name(F,Chars)}.
1126 epi_filename(F) --> [_], epi_filename(F).
1127 epi_path2([C|Rest]) --> [C],!,epi_path2(Rest). % assume everything until the end is a filename
1128 epi_path2([]) --> [].
1129
1130 :- assert_must_succeed((parsercall:remove_rowcol(R,C,"[22,33] xxx yyy ",_), R==22,C==33)).
1131 % remove parser location info from message to avoid user clutter
1132 remove_rowcol(Row,Col) --> " ",!, remove_rowcol(Row,Col).
1133 remove_rowcol(Row,Col) --> "[", epi_number(Row),",",epi_number(Col),"]".
1134
1135 :- assert_must_succeed((parsercall:remove_filename(F,C,"xxx yyy in file: a.out",R), F == 'a.out', C == "xxx yyy", R==[])).
1136 remove_filename(F,[]) --> " in file: ",!,epi_path2(Chars),{safe_name(F,Chars)}.
1137 remove_filename(F,[C|T]) --> [C], remove_filename(F,T).
1138
1139 :- assert_must_succeed((parsercall:remove_filename_from_codes("xxx yyy in file: a.out",F,C), F == 'a.out', C == "xxx yyy")).
1140 :- assert_must_succeed((parsercall:remove_filename_from_codes("xxx yyy zzz",F,C), F == 'unknown', C == "xxx yyy zzz")).
1141 remove_filename_from_codes(Codes,F,NewCodes) :-
1142 (remove_filename(F,C1,Codes,C2) -> append(C1,C2,NewCodes) ; F=unknown, NewCodes=Codes).
1143
1144 % obtain position information from a message atom and remove the parts from the message at the same time
1145 remove_msg_posinfo_known(Msg,NewMsg) :- remove_msg_posinfo(Msg,NewMsg,_,pos_already_known).
1146 remove_msg_posinfo(Msg,NewMsg,Pos) :- remove_msg_posinfo(Msg,NewMsg,Pos,not_known).
1147 remove_msg_posinfo(Msg,NewMsg,Pos,AlreadyKnown) :- %print(msg(Msg,AlreadyKnown)),nl,
1148 atom_codes(Msg,Codes),
1149 (remove_rowcol(Row,Col,Codes,RestCodes)
1150 -> Pos=pos(Row,Col,Filename),
1151 remove_filename_from_codes(RestCodes,Filename,NewCodes)
1152 ; AlreadyKnown==pos_already_known ->
1153 Pos = none,
1154 remove_filename_from_codes(Codes,_Filename2,NewCodes)
1155 ;
1156 NewCodes=Codes, Pos=none
1157 % do not remove filename: we have not found a position and cannot return the filename
1158 % see, e.g., public_examples/B/Tickets/Hansen27_NestedMchErr/M1.mch
1159 ),
1160 !,
1161 atom_codes(NewMsg,NewCodes).
1162 remove_msg_posinfo(M,M,none,_).
1163
1164
1165 % ----------------------
1166
1167 parser_command_supported(_) :-
1168 prob2_call_back_available(_), % TODO: support at least setoption in parser callback in ProB2
1169 !,
1170 fail.
1171 parser_command_supported(Command) :-
1172 parser_version_at_least(2,12,2),
1173 !,
1174 query_command_supported(Command,true).
1175 parser_command_supported(Command) :-
1176 (Command = fastprolog
1177 ; Command = compactpos
1178 ; Command = verbose
1179 ; Command = checkname
1180 ; Command = lineno
1181 ),
1182 !,
1183 parser_version_at_least(2,12,0).
1184
1185 :- dynamic query_command_supported_cached/2.
1186
1187 query_command_supported(Command,Res) :-
1188 query_command_supported_cached(Command,Res),
1189 !.
1190 query_command_supported(Command,Res) :-
1191 get_console_parser(Stream,_Out,Err),
1192 !,
1193 write(Stream,'commandsupported'), nl(Stream),
1194 write(Stream,Command), nl(Stream),
1195 flush_output(Stream),
1196 read_line(Stream,CodesIn),
1197 my_read_from_codes(CodesIn,Res,Stream,Err),
1198 assertz(query_command_supported_cached(Command,Res)).
1199
1200 % java_parser_version(VersionStr) :- java_parser_version(VersionStr,_,_,_,_,_).
1201
1202 parser_version_at_least(RV1,RV2,RV3) :-
1203 get_parser_version(_,V1,V2,V3,_,_),
1204 lex_leq([RV1,RV2,RV3],[V1,V2,V3]).
1205
1206 lex_leq([V1|_],[VV1|_]) :- number(VV1), % with old parsers this can be '?'
1207 V1 < VV1,!.
1208 lex_leq([V1|T1],[V1|T2]) :- lex_leq(T1,T2).
1209 lex_leq([],_).
1210
1211
1212 get_parser_version(VersionStr) :- get_parser_version(VersionStr,_).
1213 get_parser_version(VersionStr,GitSha) :- get_parser_version(VersionStr,_,_,_,_,GitSha).
1214
1215 get_parser_version(VersionStr,V1,V2,V3,SNAPSHOT,GitSha) :- java_parser_version(VersionStr,V1,V2,V3,SNAPSHOT,GitSha),!.
1216 get_parser_version(VersionStr,V1,V2,V3,SNAPSHOT,GitSha) :-
1217 get_version_from_parser(VersionStr),
1218 !,
1219 ? (get_version_numbers(VersionStr,V1,V2,V3,SNAPSHOT,GitSha)
1220 -> assertz(java_parser_version(VersionStr,V1,V2,V3,SNAPSHOT,GitSha)),
1221 debug_format(19,'Parser version recognized ~w.~w.~w (SNAPSHOT=~w)~n',[V1,V2,V3,SNAPSHOT])
1222 ; assertz(java_parser_version(VersionStr,'?','?','?','?','?'))
1223 ).
1224 get_parser_version(_Vers,_V1,_V2,_V3,_SNAPSHOT,_GitSha) :-
1225 (real_error_occurred -> true % already produced error messages in get_version_from_parser
1226 ; add_error(get_parser_version,'Could not get parser version.')),
1227 %missing_parser_diagnostics, % already called if necessary by get_version_from_parser
1228 fail.
1229
1230 :- use_module(probsrc(tools),[split_atom/3,atom_to_number/2]).
1231 % newer parsers generate a version string like 2.9.27-GITSHA or 2.9.27-SNAPSHOT-GITSHA; older ones just GITSHA
1232 get_version_numbers(VersionStr,V1,V2,V3,SNAPSHOT,GitSha) :-
1233 split_atom(VersionStr,['.'],List),
1234 [AV1,AV2,AV3T] = List,
1235 split_atom(AV3T,['-'],List2),
1236 [AV3,Suffix1|T] = List2,
1237 ? atom_to_number(AV1,V1),
1238 ? atom_to_number(AV2,V2),
1239 ? atom_to_number(AV3,V3),
1240 (Suffix1 = 'SNAPSHOT' -> SNAPSHOT=true, [GitSha]=T
1241 ; T=[], SNAPSHOT=false, GitSha=Suffix1).
1242
1243
1244 get_version_from_parser(Version) :-
1245 get_console_parser(Stream,Out,Err),
1246 write(Stream,'version'), nl(Stream),
1247 flush_output(Stream),
1248 read_line(Stream,Text), % if parser cannot be started we receive end_of_file; length will fail
1249 (Text = end_of_file -> add_error(parsercall,'Could not get parser version: '),
1250 read_lines_and_add_as_error(Err),fail
1251 ; length(Text,Length),
1252 ( append("Error",_,Text)
1253 -> atom_codes(ErrMsg,Text),
1254 add_error(parsercall,'Error getting parser version: ',ErrMsg),
1255 read_lines_and_add_as_error(Stream),fail
1256 ; Length < 100 -> atom_codes(Version,Text)
1257 ; prefix_length(Text,Prefix,100),
1258 append(Prefix,"...",Full),
1259 safe_name(Msg,Full),
1260 add_error_fail(parsercall, 'B parser returned unexpected version string: ', Msg))
1261 ),
1262 display_pending_outputs(Out,user_output).
1263
1264 :- use_module(library(sockets),[socket_select/7]).
1265 % check if a stream is ready for reading
1266 stream_ready_to_read(Out) :- stream_ready_to_read(Out,1). % wait 1 second, off: wait forever
1267 stream_ready_to_read(Out,TO) :- var(Out),!,
1268 add_internal_error('Illegal stream: ',stream_ready_to_read(Out,TO)),fail.
1269 stream_ready_to_read(Out,TO) :-
1270 socket_select([],_, [Out],RReady, [],_, TO), % wait TO sec at most %print(ready(Out,RReady)),nl,
1271 RReady == [Out].
1272
1273
1274 read_lines_and_add_as_error(Out) :- read_lines_until_eof(Out,false,ErrMsgCodes,[]),
1275 (ErrMsgCodes=[] -> true
1276 ; ErrMsgCodes=[10] -> true % just a single newline
1277 ; ErrMsgCodes=[13] -> true % ditto
1278 ; safe_name(ErrMsg,ErrMsgCodes),
1279 add_error(parsercall,'Additional information: ',ErrMsg),
1280 analyse_java_error_msg(ErrMsgCodes)
1281 ).
1282
1283 % analyse error messages from the JVM; providing possible solutions:
1284 analyse_java_error_msg(ErrMsgCodes) :-
1285 append([_,"java.lang.OutOfMemoryError",_],ErrMsgCodes),!,
1286 % a typical message contains: Exception in thread "main" java.lang.OutOfMemoryError: GC overhead limit exceeded
1287 % or: Exception in ...: Java heap space
1288 print_hint('Try increasing memory for Java by setting the JVM_PARSER_HEAP_MB preference.'),
1289 print_hint('You can also provide custom JVM arguments using the JVM_PARSER_ARGS preference.').
1290 analyse_java_error_msg(ErrMsgCodes) :-
1291 append([_,"java.lang.StackOverflowError",_],ErrMsgCodes),!,
1292 print_hint('Try increasing stack size for Java using the JVM_PARSER_ARGS preference (e.g.,"-Xss10m").').
1293 analyse_java_error_msg(_).
1294
1295 print_hint(Msg) :- format_with_colour_nl(user_error,[blue],'~w',[Msg]).
1296
1297 read_line_if_ready(Stream,Line) :- stream_ready_to_read(Stream), !, read_line(Stream,Line).
1298 read_line_if_ready(_,end_of_file). % pretend we are at the eof
1299
1300 read_lines_until_eof(Out,NewlineRequired) --> {read_line_if_ready(Out,Text)},
1301 !,
1302 ({Text = end_of_file} -> []
1303 ; ({NewlineRequired==true} -> "\n" ; []),
1304 Text, %{format("read: ~s~n",[Text])},
1305 read_lines_until_eof(Out,true)).
1306 read_lines_until_eof(_Out,_) --> [].
1307
1308 % display pending output lines from a stream
1309 display_pending_outputs(OutStream,ToStream) :- stream_ready_to_read(OutStream,0), !, read_line(OutStream,Line),
1310 (Line=end_of_file -> true
1311 ; format(ToStream,' =parser-output=> ~s~n',[Line]),
1312 display_pending_outputs(OutStream,ToStream)).
1313 display_pending_outputs(_,_).
1314
1315 :- use_module(tools,[get_tail_filename/2]).
1316 get_java_command_for_parser(native(GraalNativeCmd)) :-
1317 (parser_location(GraalNativeCmd)
1318 -> get_tail_filename(GraalNativeCmd,'cliparser'),
1319 (file_exists(GraalNativeCmd) -> true
1320 ; add_warning(parsercall,'Path to parser points to non-existant compiled GraalVM binary: ',GraalNativeCmd)
1321 )
1322 ; fail, % comment out fail to enable auto-detection of cliparser in lib folder
1323 library_abs_name('cliparser',GraalNativeCmd),
1324 file_exists(GraalNativeCmd)
1325 ),
1326 format('Using GRAAL native parser at ~w~n',[GraalNativeCmd]),
1327 !.
1328 get_java_command_for_parser(java_jar(JavaCmdW,JarPathW)) :-
1329 (parser_location(JarPath) -> true ; library_abs_name('probcliparser.jar',JarPath)),
1330 get_java_command_path(JavaCmdW),
1331 replace_windows_path_backslashes(JarPath,JarPathW).
1332
1333 parser_location(PathToParser) :- get_preference(path_to_java_parser,PathToParser), PathToParser \= ''.
1334
1335 % a predicate to check whether we have correct java version number and whether java seems to work ok
1336 % ResultStatus=compatible if everything is ok
1337 check_java_version(VersionCheckResult,ResultStatus) :- get_java_fullversion(Version),!,
1338 check_java_version_aux(Version,VersionCheckResult,ResultStatus).
1339 check_java_version(VersionCheckResult,error) :- get_java_command_for_parser(java_jar(JavaCmdW,JarPathW)),!,
1340 ajoin(['*** Unable to launch java command: ',JavaCmdW,' (classpath: ',JarPathW,')!'],VersionCheckResult).
1341 check_java_version('*** Unable to launch Java or get path to java command!',error). % should not happen
1342
1343 check_java_version_aux(VersionCodes,VersionCheckResult,ResultStatus) :-
1344 get_java_fullversion_numbers(VersionCodes,V1,V2,V3Atom),!,
1345 check_java_version_aux2(V1,V2,V3Atom,VersionCheckResult,ResultStatus).
1346 check_java_version_aux(VersionCodes,VersionCheckResult,error) :-
1347 atom_codes(VersionA,VersionCodes),
1348 ajoin(['*** Unable to identify Java version number: ',VersionA, ' !'],VersionCheckResult).
1349
1350 check_java_version_aux2(V1,V2,V3Atom,VersionCheckResult,compatible) :- java_version_ok_for_parser(V1,V2,V3Atom),
1351 get_java_version(_),!, % if get_java_version fails, this is an indication that Java not fully installed with admin rights
1352 ajoin(['Java is correctly installed and version ',V1,'.',V2,'.',V3Atom,
1353 ' is compatible with ProB requirements (>= 1.7).'],VersionCheckResult).
1354 check_java_version_aux2(V1,V2,V3Atom,VersionCheckResult,error) :- java_version_ok_for_parser(V1,V2,V3Atom),!,
1355 ajoin(['*** Java version ',V1,'.',V2,'.',V3Atom,
1356 ' is compatible with ProB requirements (>= 1.7) ',
1357 'but does not seem to be correctly installed: reinstall Java with admin rights!'],VersionCheckResult).
1358 check_java_version_aux2(V1,V2,V3Atom,VersionCheckResult,incompatible) :-
1359 get_java_version(_),!,
1360 ajoin(['*** Java is correctly installed but version ',V1,'.',V2,'.',V3Atom,
1361 ' is *not* compatible with ProB requirements (>= 1.7)!'],VersionCheckResult).
1362 check_java_version_aux2(V1,V2,V3Atom,VersionCheckResult,error) :-
1363 ajoin(['*** Java is not correctly installed and version ',V1,'.',V2,'.',V3Atom,
1364 ' is *not* compatible with ProB requirements (>= 1.7)!'],VersionCheckResult).
1365
1366
1367 % we need Java 1.7 or higher
1368 java_version_ok_for_parser(V1,_V2,_) :- V1>1.
1369 java_version_ok_for_parser(1,V2,_) :- V2>=7.
1370
1371 get_java_fullversion(V1,V2,V3Atom) :-
1372 get_java_fullversion(VersionCodes),
1373 get_java_fullversion_numbers(VersionCodes,VV1,VV2,VV3),!,
1374 V1=VV1, V2=VV2, V3Atom=VV3.
1375
1376 :- assert_must_succeed((parsercall:get_java_fullversion_numbers("openjdk full version \"1.8.0_312\"",V1,V2,V3),
1377 V1==1, V2==8, V3=='0_312')).
1378 :- assert_must_succeed((parsercall:get_java_fullversion_numbers("openjdk full version \"15+36-1562\"",V1,V2,V3),
1379 V1==1, V2==15, V3=='36-1562')).
1380 :- assert_must_succeed((parsercall:get_java_fullversion_numbers("java full version \"17.0.1+12-LTS-39\"",V1,V2,V3),
1381 V1==1, V2==17, V3=='0.1+12-LTS-39')). % Oracle JDK on macOS
1382 :- use_module(tools,[split_chars/3]).
1383 get_java_fullversion_numbers(VersionCodes,V1,V2,V3Atom) :-
1384 append("java full version """,Tail,VersionCodes), !,
1385 get_java_fullversion_numbers_aux(Tail,V1,V2,V3Atom).
1386 get_java_fullversion_numbers(VersionCodes,V1,V2,V3Atom) :-
1387 append("openjdk full version """,Tail,VersionCodes), !,
1388 get_java_fullversion_numbers_aux(Tail,V1,V2,V3Atom).
1389 get_java_fullversion_numbers_aux(Tail,1,V2,V3Atom) :-
1390 % new version scheme (https://openjdk.java.net/jeps/223), leading 1 dropped, 13+33 stands for 1.13.33
1391 split_chars(Tail,"+",[V2C,V3C]),
1392 !,
1393 (try_number_codes(V2,V2C)
1394 -> get_v3_atom(V3C,V3Atom)
1395 ; append(V2CC,[0'. | FurtherC], V2C) % there is at least one more dot in the version nr (e.g. 17.0.1+12-LTS-39)
1396 ->
1397 try_number_codes(V2,V2CC),
1398 append(FurtherC,[0'+ | V3C], V3C3),
1399 get_v3_atom(V3C3,V3Atom)
1400 ).
1401 get_java_fullversion_numbers_aux(Tail,V1,V2,V3Atom) :-
1402 split_chars(Tail,".",[V1C,V2C|FurtherC]),
1403 append(FurtherC,V3C),
1404 try_number_codes(V1,V1C),
1405 try_number_codes(V2,V2C),!,
1406 get_v3_atom(V3C,V3Atom).
1407
1408 get_v3_atom(V3C,V3Atom) :- strip_closing_quote(V3C,V3C2),
1409 atom_codes(V3Atom,V3C2).
1410
1411 try_number_codes(Name,Codes) :-
1412 catch(number_codes(Name,Codes), _Exc, fail).
1413
1414 strip_closing_quote([],[]).
1415 strip_closing_quote([H|_],R) :- (H=34 ; H=32),!, R=[]. % closing " or newline
1416 strip_closing_quote([H|T],[H|R]) :- strip_closing_quote(T,R).
1417
1418 % get java fullversion as code list; format "java full version "...."\n"
1419 get_java_fullversion(Version) :-
1420 get_java_command_path(JavaCmdW),
1421 (my_system_call(JavaCmdW, ['-fullversion'],java_version,Text) -> Text=Version
1422 ; format(user_error,'Could not execute ~w -fullversion~n',[JavaCmdW]),
1423 fail).
1424
1425 % when java -fullversion works but not java -version it seems that Java was improperly
1426 % installed without admin rights (http://stackoverflow.com/questions/11808829/jre-1-7-returns-java-lang-noclassdeffounderror-java-lang-object)
1427 get_java_version(Version) :-
1428 get_java_command_path(JavaCmdW),
1429 (my_system_call(JavaCmdW, ['-version'],java_version,Text) -> Text=Version
1430 ; format(user_error,'Could not execute ~w -version~n',[JavaCmdW]),
1431 fail).
1432 % should we check for JAVA_PATH first ? would allow user to override java; but default pref would have to be set to ''
1433 get_java_command_path(JavaCmdW) :-
1434 %host_platform(darwin)
1435 get_preference(path_to_java,X),
1436 debug_println(8,path_to_java_preference(X)),
1437 (X=''
1438 ; preference_default_value(path_to_java,Default), debug_println(8,default(Default)),
1439 Default=X
1440 ),
1441 % only try this when the Java path has not been set explicitly
1442 % on Mac: /usr/bin/java exists even when Java not installed ! it is a fake java command that launches a dialog
1443 ? absolute_file_name(path(java),
1444 JavaCmd,
1445 [access(exist),extensions(['.exe','']),solutions(all),file_errors(fail)]),
1446 debug_println(8,obtained_java_cmd_from_path(JavaCmd)),
1447 replace_windows_path_backslashes(JavaCmd,JavaCmdW),
1448 !.
1449 get_java_command_path(JavaCmdW) :- get_preference(path_to_java,JavaCmd),
1450 JavaCmd \= '',
1451 debug_println(8,using_path_to_java_preference(JavaCmd)),
1452 (file_exists(JavaCmd) -> true
1453 ; directory_exists(JavaCmd) -> add_warning(get_java_command_path,'No Java Runtime (7 or newer) found; please correct the JAVA_PATH advanced preference (it has to point to the java tool, *not* the directory enclosing it): ',JavaCmd)
1454 ; add_warning(get_java_command_path,'No Java Runtime (7 or newer) found; please correct the JAVA_PATH advanced preference: ',JavaCmd)),
1455 replace_windows_path_backslashes(JavaCmd,JavaCmdW),
1456 !.
1457 get_java_command_path(_JavaCmd) :-
1458 add_error(get_java_command_path,'Could not get path to the java tool. Make sure a Java Runtime (7 or newer) is installed',''),
1459 fail.
1460
1461 library_abs_name(Lib,Abs) :- absolute_file_name(prob_lib(Lib),Abs).
1462
1463 % CtlOrLtl is either ctl, ltl, or pctl
1464 call_ltl_parser(Formulas, CtlOrLtl, Result) :-
1465 get_ltl_lang_spec(LangSpec),
1466 maplist(parse_temporal_formula(CtlOrLtl,LangSpec),Formulas,Result).
1467
1468 :- use_module(specfile,[b_or_z_mode/0,csp_with_bz_mode/0]).
1469 get_ltl_lang_spec('B,none') :- csp_with_bz_mode,!.
1470 get_ltl_lang_spec('B') :- b_or_z_mode,!.
1471 get_ltl_lang_spec(none).
1472
1473 /* unused code :
1474 generate_formula_codes([F]) -->
1475 !,generate_formula_codes2(F),"\n".
1476 generate_formula_codes([F|Rest]) -->
1477 generate_formula_codes2(F), "###\n",
1478 generate_formula_codes(Rest).
1479 generate_formula_codes2(F) -->
1480 write_to_codes(F).
1481 */
1482
1483
1484 % ---------------------------
1485
1486 % call the TLA2B parser to translate a TLA file into a B machine
1487 call_tla2b_parser(TLAFile) :-
1488 get_java_command_path(JavaCmdW),
1489 replace_windows_path_backslashes(TLAFile,TLAFileW),
1490 phrase(jvm_options, XOpts),
1491 absolute_file_name(prob_lib('TLA2B.jar'),TLA2BJAR),
1492 append(XOpts,['-jar',file(TLA2BJAR),file(TLAFileW)],FullArgs),
1493 % other possible options -verbose -version -config FILE
1494 (my_system_call(JavaCmdW, FullArgs,tla2b_parser)
1495 -> true
1496 ; \+ file_exists(TLA2BJAR),
1497 print_error('Be sure to download TLA2B.jar from https://stups.hhu-hosting.de/downloads/prob/tcltk/jars/,'),
1498 print_error('and put it into the ProB lib/ directory.'),
1499 fail
1500 ).
1501
1502 %call_cspmj_parser(CSPFile,PrologFile) :-
1503 % get_java_command_path(JavaCmdW),
1504 % replace_windows_path_backslashes(CSPFile,CSPFileW),
1505 % phrase(jvm_options, XOpts),
1506 % absolute_file_name(prob_lib('cspmj.jar'),CSPMJAR),
1507 % get_writable_compiled_filename(CSPFile,'.pl',PrologFile),
1508 % tools:string_concatenate('--prologOut=', PrologFile, PrologFileOutArg),
1509 % append(XOpts,['-jar',CSPMJAR,'-parse',CSPFileW,PrologFileOutArg],FullArgs),
1510 % debug_println(9,calling_java(FullArgs)),
1511 % (my_system_call(JavaCmdW, FullArgs,cspmj_parser) -> true
1512 % ; print_error('Be sure that cspmj.jar parser is installed.'),
1513 % fail).
1514
1515
1516 tla2prob_filename(TLAFile,GeneratedProbFile) :-
1517 split_filename(TLAFile,Basename,_Extension),
1518 atom_chars(Basename,BasenameC),
1519 append(BasenameC,['.','p','r','o','b'],TLABC),
1520 atom_chars(GeneratedProbFile,TLABC),!.
1521 tla2prob_filename(Filename, GeneratedProbFile) :-
1522 add_failed_call_error(tla2b_filename(Filename,GeneratedProbFile)),fail.
1523
1524 tla2b_filename(TLAFile,BFile) :-
1525 split_filename(TLAFile,Basename,_Extension),
1526 atom_chars(Basename,BasenameC),
1527 append(BasenameC,['_',t,l,a,'.','m','c','h'],TLABC),
1528 atom_chars(BFile,TLABC),!.
1529 tla2b_filename(Filename, BFile) :-
1530 add_failed_call_error(tla2b_filename(Filename,BFile)),fail.
1531
1532
1533 my_system_call(Command,Args,Origin) :- my_system_call(Command,Args,Origin,_Text).
1534 my_system_call(Command,Args,Origin,ErrText) :-
1535 debug_print_system_call(Command,Args),
1536 system_call(Command,Args,ErrText,Exit), %nl,print(exit(Exit)),nl,nl,
1537 treat_exit_code(Exit,Command,Args,ErrText,Origin).
1538
1539 debug_print_system_call(Command,Args) :-
1540 (debug_mode(off) -> true ; print_system_call(Command,Args)).
1541 print_system_call(Command,Args) :-
1542 ajoin_with_sep(Args,' ',FS), format(user_output,'Executing: ~w ~w~n',[Command,FS]).
1543
1544 my_system_call5(Command,Args,Origin,OutputText,ErrText) :-
1545 system_call(Command,Args,OutputText,ErrText,Exit), %nl,print(exit(Exit)),nl,nl,
1546 treat_exit_code(Exit,Command,Args,ErrText,Origin).
1547
1548 treat_exit_code(exit(0),_,_,_,_) :- !.
1549 treat_exit_code(Exit,Command,Args,ErrText,Origin) :-
1550 debug_println(9,treat_exit_code(Exit,Command,Args,ErrText,Origin)),
1551 catch( my_read_from_codes(ErrText,Term),
1552 _,
1553 (safe_name(T,ErrText),Term = T)), !,
1554 %print_error(Term),
1555 (Term = end_of_file -> ErrMsg = '' ; ErrMsg = Term),
1556 ajoin(['Exit code ',Exit,' for command ',Command, ', error message: '],Msg),
1557 (get_error_position_from_term(Origin,Term,Pos)
1558 -> add_error(Origin,Msg,ErrMsg,Pos)
1559 ; add_error(Origin,Msg,ErrMsg)
1560 ),
1561 fail.
1562
1563
1564 get_error_position_from_term(alloy2b,Term,Pos) :- atom(Term),
1565 atom_codes(Term,Codes), get_error_position_from_codes(Codes,Pos).
1566
1567 % Alloy error message: ! Exception in thread "main" Type error in .../Restrictions.als at line 41 column 23:
1568 get_error_position_from_codes([97,116,32,108,105,110,101,32|Tail],lineCol(Line,Col)) :- % "at line "
1569 epi_number(Line,Tail,RestTail),
1570 (RestTail = [32,99,111,108,117,109,110,32|Tail2], % "column "
1571 epi_number(Col,Tail2,_) -> true
1572 ; Col=0).
1573 get_error_position_from_codes([_|T],Pos) :- get_error_position_from_codes(T,Pos).
1574
1575 % replace backslashes by forward slashes in atoms, only under windows
1576 % TODO(DP,14.8.2008): Check if still needed with SICStus 4.0.4 and if
1577 % everybody uses that version
1578 replace_windows_path_backslashes(Old,New) :-
1579 ( host_platform(windows) ->
1580 safe_name(Old,OldStr),
1581 replace_string_backslashes(OldStr,NewStr),
1582 safe_name(New,NewStr)
1583 ;
1584 Old=New).
1585
1586 replace_string_backslashes([],[]) :- !.
1587 replace_string_backslashes([C|OldRest],[N|NewRest]) :- !,
1588 ( C=92 /* backslash */ ->
1589 N=47 /* forward slash */
1590 ;
1591 N=C ),
1592 replace_string_backslashes(OldRest,NewRest).
1593 replace_string_backslashes(X,Y) :-
1594 add_error(parsercall,'Illegal call: ',replace_string_backslashes(X,Y)),
1595 fail.
1596
1597 % ---------------------------
1598
1599 :- assert_must_succeed((parsercall:parse_string_template("0",Res), Res==[string_codes("0")])).
1600 :- assert_must_succeed((parsercall:parse_string_template("ab${xy}cd",Res),
1601 Res==[string_codes("ab"),template_codes("xy",2,3,[]),string_codes("cd")])).
1602 :- assert_must_succeed((parsercall:parse_string_template("ab${xy}$<<z>>cd$\xab\v\xbb\",Res),
1603 Res==[string_codes("ab"),template_codes("xy",2,3,[]),template_codes("z",3,5,[]),
1604 string_codes("cd"),template_codes("v",2,3,[])])). % \xab\ is double angle
1605
1606 % parse a ProB string template
1607 % each recognised template is an expression.
1608 parse_string_template(Codes,TemplateList) :- %format("parsing: ~s~n",[Codes]),
1609 parse_string_template([],TemplateList,Codes,[]).
1610
1611 parse_string_template(Acc,TemplateList) -->
1612 ? template_inside_string(Str,StartOffset,AdditionalChars,Options),!,
1613 {add_acc_string(Acc,TemplateList,
1614 [template_codes(Str,StartOffset,AdditionalChars,Options)|T])},
1615 parse_string_template([],T).
1616 parse_string_template(Acc,TemplateList) --> [H], !, parse_string_template([H|Acc],TemplateList).
1617 parse_string_template(Acc,TemplateList) --> "", {add_acc_string(Acc,TemplateList,[])}.
1618
1619 % add accumulator as regular string before a detected template ${...}
1620 add_acc_string([],L,R) :- !, L=R.
1621 add_acc_string(Acc,[string_codes(Str)|T],T) :- reverse(Acc,Str).
1622
1623 template_inside_string(Str,StartOffset,AdditionalChars,Options) --> "$",
1624 template_options(Options,OptLen),
1625 ? template_open_paren(ClosingParen,ParenLen),
1626 {StartOffset is OptLen+ParenLen+1,
1627 AdditionalChars is StartOffset+ParenLen}, % add closing parentheses length
1628 template_content(Str,ClosingParen).
1629
1630 template_options(Options,Len) --> "[", template_options2(Options,Len).
1631 template_options([],0) --> [].
1632
1633 template_options2([H|T],Len) --> template_option(H,HLen), !, template_options3(T,HLen,Len).
1634 template_options2([],2) --> "]".
1635 template_options3([H|T],AccLen,Len) --> ",", template_option(H,HLen), !,
1636 {A1 is AccLen+HLen},template_options3(T,A1,Len).
1637 template_options3([],AccLen,Len) --> "]", {Len is AccLen+2}.
1638 template_option(ascii,5) --> "ascii".
1639 template_option(ascii,1) --> "a".
1640 template_option(unicode,7) --> "unicode".
1641 template_option(unicode,1) --> "u".
1642 template_option(template_width(Option,Nr),L1) --> digits(Nr,Len),template_width_option(Option,LO), {L1 is Len+LO}.
1643 % other options could be hex output or padding, ...
1644 % TODO: provide error feedback when option/template parsing fails
1645
1646 template_width_option(float_fixed_point,1) --> "f".
1647 template_width_option(integer_decimal_string,1) --> "d".
1648 template_width_option(pad_string(' '),1) --> "p".
1649
1650 digits(MinusNr,Len) --> "-",!, digit(X), digits2(X,Nr,2,Len), {MinusNr is -Nr}.
1651 digits(Nr,Len) --> digit(X), digits2(X,Nr,1,Len).
1652 digits2(X,Nr,AccLen,Len) --> digit(Y), !, {XY is X*10+Y, A1 is AccLen+1}, digits2(XY,Nr,A1,Len).
1653 digits2(X,X,Len,Len) --> "".
1654
1655 digit(Nr) --> [X], {X >= 48, X=<57, Nr is X-48}.
1656
1657 template_open_paren("}",1) --> "{".
1658 template_open_paren(">>",2) --> "<<".
1659 template_open_paren([187],1) --> [ 171 ]. % Double angle quotation mark "«»"
1660
1661 template_content("",Closing) --> Closing,!.
1662 template_content([H|T],Closing) --> [H], template_content(T,Closing).
1663
1664 % TODO: offset span within template
1665 parse_template_b_expression(Span,Filenumber,template_codes(Codes,_,_,Options),RawStrExpr) :-
1666 \+ get_prob_application_type(rodin), % in Rodin parser callback is not available
1667 !,
1668 catch( parse_at_position_in_file(expression,Codes,RawExpr,Span,Filenumber),
1669 parse_errors(Errors),
1670 (add_all_perrors(Errors,[],parse_template_string), % add_all_perrors_in_context_of_used_filenames?
1671 fail)
1672 ),
1673 create_to_string_conversion(RawExpr,Span,Options,RawStrExpr).
1674 parse_template_b_expression(Span,_,template_codes(Codes,_,_,_),string(Span,Atom)) :-
1675 atom_codes(Atom,Codes).
1676 parse_template_b_expression(Span,_,string_codes(Codes),string(Span,Atom)) :-
1677 atom_codes(Atom,Codes).
1678
1679 :- assert_must_succeed((parsercall:transform_string_template('1+1 = ${1+1}',p3(1,1,12),Res),
1680 Res= general_concat(_,sequence_extension(_,[_|_])) )).
1681 :- assert_must_succeed((parsercall:transform_string_template('abc',p3(1,1,3),Res),
1682 Res= string(_,'abc') )).
1683
1684 :- use_module(error_manager,[extract_file_number_and_name/3]).
1685 % transform a string template into a raw expression that computes a string value
1686 transform_string_template(Atom,Span,RawExpr) :-
1687 atom_codes(Atom,Codes),
1688 parse_string_template(Codes,TemplateList),
1689 ? transform_str_templ_aux(TemplateList,Atom,Span,RawExpr).
1690
1691 transform_str_templ_aux([string_codes(_)],Atom,Span,RawExpr) :- !,
1692 debug_println(19,unnecessary_string_template(Span)), % regular string suffices
1693 RawExpr = string(Span,Atom).
1694 transform_str_templ_aux(TemplateList,_,Span,RawExpr) :-
1695 (extract_file_number_and_name(Span,FileNr,_) -> true ; FileNr = -1),
1696 InitialOffset = 3, % for three starting quotes
1697 ? l_parse_templates(TemplateList,0,InitialOffset,Span,FileNr,BTemplateList),
1698 generate_conc_expr(BTemplateList,Span,RawExpr).
1699
1700 :- use_module(tools_positions, [add_col_offset_to_position/3, add_line_col_offset_to_position/4]).
1701 l_parse_templates([],_,_,_,_,[]).
1702 l_parse_templates([Templ1|T],LineOffset,ColOffset,Span,FileNr,[RawStrExpr|BT]) :-
1703 templ_start_offset(Templ1,StartOffset),
1704 CO2 is ColOffset+StartOffset, % e.g., add two chars for ${ in case Templ1 is a template
1705 add_line_col_offset_to_position(Span,LineOffset,CO2,Span1),
1706 % it is only start position of Span1 that is important
1707 parse_template_b_expression(Span1,FileNr,Templ1,RawStrExpr),
1708 ? count_template_offset(Templ1,LineOffset,ColOffset,LineOffset2,ColOffset2),
1709 ? l_parse_templates(T,LineOffset2,ColOffset2,Span,FileNr,BT).
1710
1711 % accumulate length of template part and add to line/col offset to be added to start of template string
1712 count_template_offset(template_codes(Codes,_StartOffset,AdditionalChars,_),L,C,LineOffset,C3) :-
1713 ? count_offset(Codes,L,C,LineOffset,ColOffset),
1714 C3 is ColOffset+AdditionalChars. % e.g., 3 for ${.}
1715 count_template_offset(string_codes(Codes),L,C,LineOffset,ColOffset) :-
1716 ? count_offset(Codes,L,C,LineOffset,ColOffset).
1717
1718 templ_start_offset(template_codes(_,StartOffset,_,_),StartOffset). % usually 2 for ${
1719 templ_start_offset(string_codes(_),0).
1720
1721 % count line/column offset inside a list of codes:
1722 %count_offset(Codes,LineOffset,ColOffset) :- count_offset(Codes,0,0,LineOffset,ColOffset).
1723 count_offset([],Line,Col,Line,Col).
1724 count_offset(Codes,L,_ColOffset,Line,Col) :- newline(Codes,T),!,
1725 L1 is L+1,
1726 count_offset(T,L1,0,Line,Col).
1727 count_offset([_|T],L,ColOffset,Line,Col) :- C1 is ColOffset+1,
1728 ? count_offset(T,L,C1,Line,Col).
1729
1730 newline([10|T],T).
1731 newline([13|X],T) :- (X=[10|TX] -> T=TX ; T=X). % TO DO: should we check if we are on Windows ?
1732
1733 % generate a raw expression for the concatenation of a list of expressions
1734 generate_conc_expr([],Pos,string(Pos,'')).
1735 generate_conc_expr([OneEl],_,Res) :- !, Res = OneEl. % no need to concatenate
1736 generate_conc_expr(List,Pos,general_concat(Pos,sequence_extension(Pos,List))).
1737
1738 create_to_string_conversion(RawExpr,Pos,Options,
1739 external_function_call_auto(Pos,'STRING_PADLEFT',[RawStrExpr,Len,Char])) :-
1740 select(template_width(pad_string(PadChar),Nr),Options,RestOpts),!,
1741 create_to_string_conversion(RawExpr,Pos,RestOpts,RawStrExpr),
1742 Char = string(Pos,PadChar),
1743 Len = integer(Pos,Nr).
1744 create_to_string_conversion(RawExpr,Pos,Options,RawStrExpr) :-
1745 is_definitely_string(RawExpr),!,
1746 (Options=[] -> true
1747 ; add_warning(string_template,'Ignoring options in string template (already a string): ',Options, Pos)),
1748 RawStrExpr=RawExpr.
1749 create_to_string_conversion(RawExpr,Pos,Options,external_function_call_auto(Pos,'REAL_TO_DEC_STRING',[RawExpr,Prec])) :-
1750 select_option(template_width(float_fixed_point,Nr),Options,Pos),!,
1751 Prec = integer(Pos,Nr).
1752 create_to_string_conversion(RawExpr,Pos,Options,external_function_call_auto(Pos,'INT_TO_DEC_STRING',[RawExpr,Prec])) :-
1753 select_option(template_width(integer_decimal_string,Nr),Options,Pos),!,
1754 Prec = integer(Pos,Nr).
1755 create_to_string_conversion(RawExpr,Pos,Options,external_function_call_auto(Pos,'TO_STRING_UNICODE',[RawExpr])) :-
1756 select_option(unicode,Options,Pos),!. % TODO use a TO_STRING function with options list
1757 create_to_string_conversion(RawExpr,Pos,_Options,external_function_call_auto(Pos,'TO_STRING',[RawExpr])).
1758
1759 select_option(Option,Options,Pos) :-
1760 select(Option,Options,Rest),
1761 (Rest=[] -> true ; add_warning(string_template,'Ignoring additional string template options: ',Rest,Pos)).
1762
1763
1764 is_definitely_string(string(_,_)).
1765
1766 % ---------------------------
1767 :- use_module(pathes,[runtime_application_path/1]).
1768
1769 call_jar_parser(PMLFile,JARFile,Args,ParserName) :-
1770 get_java_command_path(JavaCmdW),
1771 replace_windows_path_backslashes(PMLFile,PMLFileW),
1772 phrase(jvm_options, XOpts),
1773 absolute_file_name(prob_lib(JARFile),FullJAR),
1774 append(XOpts,['-jar',FullJAR,PMLFileW|Args],FullArgs),
1775 %format('Java: ~w, Parser: ~w, Args: ~w~n',[JavaCmdW,ParserName,FullArgs]),
1776 my_system_call(JavaCmdW, FullArgs,ParserName).
1777
1778
1779
1780 call_alloy2pl_parser(AlloyFile,BFile) :-
1781 alloy_pl_filename(AlloyFile,BFile),
1782 call_alloy2pl_parser_aux(AlloyFile,'alloy2b.jar',BFile).
1783
1784 call_alloy2pl_parser_aux(AlloyFile,JARFile,PrologBFile) :-
1785 compilation_not_needed(AlloyFile,PrologBFile,JARFile),!.
1786 call_alloy2pl_parser_aux(AlloyFile,JARFile,PrologBFile) :-
1787 (file_exists(PrologBFile) -> delete_file(PrologBFile) ; true), % TODO: only delete generated files
1788 replace_windows_path_backslashes(PrologBFile,BFileW),
1789 call_jar_parser(AlloyFile,JARFile,['-toProlog',BFileW],alloy2b).
1790
1791 alloy_pl_filename(AlloyFile,BFile) :- atom_codes(AlloyFile,BasenameC),
1792 append(BasenameC,".pl",NewC),
1793 atom_codes(BFile,NewC),!.
1794 alloy_pl_filename(Filename, BFile) :-
1795 add_failed_call_error(alloy_pl_filename(Filename,BFile)),fail.
1796
1797 compilation_not_needed(BaseFile,DerivedFile,LibraryFile) :-
1798 file_exists(BaseFile),
1799 file_property(BaseFile, modify_timestamp, BTime),
1800 %system:datime(BTime,datime(_Year,Month,Day,Hour,Min,Sec)), format('~w modfied on ~w/~w at ~w:~w (~w sec)~n',[BaseFile,Day,Month,Hour,Min,Sec]),
1801 file_exists(DerivedFile),
1802 file_property(DerivedFile, modify_timestamp, DTime),
1803 DTime > BTime,
1804 absolute_file_name(prob_lib(LibraryFile),FullLibFile),
1805 (file_exists(FullLibFile)
1806 -> file_property(FullLibFile, modify_timestamp, LibTime),
1807 DTime > LibTime % check that file was generated by this library (hopefully); ideally we should put version numbers into the DerivedFiles
1808 ; true % Jar/command not available anyway; use the derived file
1809 ).
1810
1811 % ---------------------------
1812
1813 call_fuzz_parser(TexFile,FuzzFile) :-
1814 ? get_command_in_lib(fuzz,FuzzCmd),
1815 absolute_file_name(prob_lib('fuzzlib'),FUZZLIB), % TO DO: windows
1816 fuzz_filename(TexFile,FuzzFile),
1817 % fuzz options:
1818 % -d Allow use before definition
1819 % -l Lisp-style echoing of input
1820 % -p file Use <file> in place of standard prelude
1821 debug_format(19,'Fuzz: running ~w -d -l with library ~w on ~w~n',[FuzzCmd,FUZZLIB,TexFile]),
1822 (file_exists(FUZZLIB)
1823 -> my_system_call5(FuzzCmd,['-d', '-l', '-p', file(FUZZLIB), file(TexFile)],call_fuzz_parser,Text,_ErrText)
1824 ; my_system_call5(FuzzCmd,['-d', '-l', file(TexFile)],call_fuzz_parser,Text,_ErrText)
1825 ),
1826 format('Writing fuzz AST to ~s~n',[FuzzFile]),
1827 open(FuzzFile,write,Stream),
1828 call_cleanup(format(Stream,'~s~n',[Text]), close(Stream)).
1829
1830 get_command_in_lib(Name,Command) :-
1831 get_binary_extensions(Extensions),
1832 ? absolute_file_name(prob_lib(Name),
1833 Command,
1834 [access(exist),extensions(Extensions),solutions(all),file_errors(fail)]).
1835
1836 get_binary_extensions(List) :-
1837 host_platform(windows),!, List=['.exe','']. % will backtrack in get_command_in_lib
1838 get_binary_extensions(['']).
1839
1840 fuzz_filename(TexFile,FuzzFile) :-
1841 split_filename(TexFile,Basename,_Extension),
1842 atom_chars(Basename,BasenameC),
1843 append(BasenameC,['.','f','u','z','z'],CC),
1844 atom_chars(FuzzFile,CC),!.
1845 fuzz_filename(TexFile, FuzzFile) :-
1846 add_failed_call_error(fuzz_filename(TexFile,FuzzFile)),fail.