1/*************************************************************************
2*									 *
3*	 YAP Prolog 							 *
4*									 *
5*	Yap Prolog was developed at NCCUP - Universidade do Porto	 *
6*									 *
7* Copyright L.Damas, V.S.Costa and Universidade do Porto 1985-1997	 *
8*									 *
9**************************************************************************
10*									 *
11* File:		utilities for displaying messages in YAP.		 *
12* comments:	error messages for YAP					 *
13*									 *
14* Last rev:     $Date: 2008-07-16 10:58:59 $,$Author: vsc $						 *
15*									 *
16*									 *
17*************************************************************************/
18
19:- module('$messages',
20	  [system_message/4,
21	   prefix/6,
22	   prefix/5,
23	   file_location/3]).
24
25file_location(Prefix) -->
26	{
27	 prolog_load_context(file, FileName)
28	},
29	{ '$start_line'(LN) },
30	file_position(FileName,LN,Prefix),
31	[ nl ].
32
33file_position(user_input,LN,MsgCodes) -->
34	[ '~a (user_input:~d).' - [MsgCodes,LN] ].
35file_position(FileName,LN,MsgCodes) -->
36	[ '~a (~a:~d).' - [MsgCodes,FileName,LN] ].
37
38generate_message(halt) --> !,
39	['YAP execution halted'].
40generate_message('$abort') --> !,
41	['YAP execution aborted'].
42generate_message(abort(user)) --> !,
43	['YAP execution aborted'].
44generate_message(loading(_,user)) --> !.
45generate_message(loading(What,AbsoluteFileName)) --> !,
46	[ '~a ~a...' - [What, AbsoluteFileName] ].
47generate_message(loaded(_,user,_,_,_)) --> !.
48generate_message(loaded(included,AbsoluteFileName,Mod,Time,Space)) --> !,
49	[ '~a included in module ~a, ~d msec ~d bytes' - [AbsoluteFileName,Mod,Time,Space] ].
50generate_message(loaded(What,AbsoluteFileName,Mod,Time,Space)) --> !,
51	[ '~a ~a in module ~a, ~d msec ~d bytes' - [What, AbsoluteFileName,Mod,Time,Space] ].
52generate_message(prompt(BreakLevel,TraceDebug)) --> !,
53	( { BreakLevel =:= 0 } ->
54	    (
55	     { var(TraceDebug) } ->
56	     []
57	    ;
58	     [ '~a' - [TraceDebug] ]
59	    )
60	;
61	    (
62	     { var(TraceDebug) } ->
63	     [ '~d' - [BreakLevel] ]
64	    ;
65	     [ '~d ~a' - [BreakLevel, TraceDebug] ]
66	    )
67	).
68generate_message(debug) --> !,
69	[ debug ].
70generate_message(trace) --> !,
71	[ trace ].
72generate_message(M) -->
73	system_message(M),
74	stack_dump(M).
75
76stack_dump(error(_,_)) -->
77	{ fail },
78	{ recorded(sp_info,local_sp(P,CP,Envs,CPs),_) },
79	{ Envs = [_|_] ; CPs = [_|_] }, !,
80	[nl],
81	'$hacks':display_stack_info(CPs, Envs, 20, CP).
82stack_dump(_) --> [].
83
84prolog_message(X,Y,Z) :-
85	system_message(X,Y,Z).
86
87%message(loaded(Past,AbsoluteFileName,user,Msec,Bytes), Prefix, Suffix) :- !,
88system_message(query(_QueryResult,_)) --> [].
89system_message(format(Msg, Args)) -->
90	[Msg - Args].
91system_message(ancestors([])) -->
92	[ 'There are no ancestors.' ].
93system_message(breakp(bp(debugger,_,_,M:F/N,_),add,already)) -->
94	[ 'There is already a spy point on ~w:~w/~w.' - [M,F,N]].
95system_message(breakp(bp(debugger,_,_,M:F/N,_),add,ok)) -->
96	[ 'Spy point set on ~w:~w/~w.' - [M,F,N] ].
97system_message(breakp(bp(debugger,_,_,M:F/N,_),remove,last)) -->
98	[ 'Spy point on ~w:~w/~w removed.' - [M,F,N] ].
99system_message(breakp(no,breakpoint_for,M:F/N)) -->
100	[ 'There is no spy point on ~w:~w/~w.' - [M,F,N]].
101system_message(breakpoints([])) -->
102	[ 'There are no spy-points set.' ].
103system_message(breakpoints(L)) -->
104	[ 'Spy-points set on:' ],
105	list_of_preds(L).
106system_message(clauses_not_together(P)) -->
107	[ 'Discontiguous definition of ~q.' - [P] ].
108system_message(debug(debug)) -->
109	[ 'Debug mode on.' ].
110system_message(debug(off)) -->
111	[ 'Debug mode off.' ].
112system_message(debug(trace)) -->
113	[ 'Trace mode on.' ].
114system_message(declaration(Args,Action)) -->
115	[ 'declaration ~w ~w.' - [Args,Action] ].
116system_message(defined_elsewhere(P,F)) -->
117	[  'predicate ~q previously defined in file ~w' - [P,F] ].
118system_message(import(Pred,To,From,private)) -->
119	[ 'Importing private predicate ~w:~w to ~w.' - [From,Pred,To] ].
120system_message(leash([])) -->
121	[ 'No leashing.' ].
122system_message(leash([A|B])) -->
123	[ 'Leashing set to ~w.' - [[A|B]] ].
124system_message(no) -->
125	[ 'no'  ].
126system_message(no_match(P)) -->
127	[ 'No matching predicate for ~w.' - [P] ].
128system_message(leash([A|B])) -->
129	[ 'Leashing set to ~w.' - [[A|B]] ].
130system_message(existence_error(prolog_flag,F)) -->
131	[ 'Prolog Flag ~w: new Prolog flags must be created using create_prolog_flag/3.' - [F] ].
132system_message(singletons([SV],P)) -->
133	[ 'Singleton variable ~s in ~q.' - [SV,P] ].
134system_message(singletons(SVs,P)) -->
135	[  'Singleton variables ~s in ~q.' - [SVsL, P] ],
136	{ svs(SVs,SVsL,[]) }.
137system_message(trace_command(-1)) -->
138	[ 'EOF is not a valid debugger command.'  ].
139system_message(trace_command(C)) -->
140	[ '~c is not a valid debugger command.' - [C] ].
141system_message(trace_help) -->
142	[ '   Please enter a valid debugger command (h for help).'  ].
143system_message(version(Version)) -->
144	[ '~a' - [Version] ].
145system_message(myddas_version(Version)) -->
146	[ 'MYDDAS version ~a' - [Version] ].
147system_message(yes) -->
148	[  'yes'  ].
149system_message(error,error(Msg,Info)) -->
150	( { var(Msg) } ; { var(Info)} ), !,
151	['bad error ~w' - [error(Msg,Info)]].
152system_message(error(consistency_error(Who),Where)) -->
153	[ 'CONSISTENCY ERROR (arguments not compatible with format)- ~w ~w' - [Who,Where] ].
154system_message(error(context_error(Goal,Who),Where)) -->
155	[ 'CONTEXT ERROR- ~w: ~w appeared in ~w' - [Goal,Who,Where] ].
156system_message(error(domain_error(DomainType,Opt), Where)) -->
157	[ 'DOMAIN ERROR- ~w: ' - Where],
158	domain_error(DomainType, Opt).
159system_message(error(existence_error(prolog_flag,P), Where)) --> !,
160	[ 'EXISTENCE ERROR- ~w: prolog flag ~w is undefined' - [Where,P] ].
161system_message(error(existence_error(procedure,P), context(Call,Parent))) --> !,
162	[ 'EXISTENCE ERROR- procedure ~w is undefined, called from context  ~w~n                 Goal was ~w' - [P,Parent,Call] ].
163system_message(error(existence_error(stream,Stream), Where)) -->
164	[ 'EXISTENCE ERROR- ~w: ~w not an open stream' - [Where,Stream] ].
165system_message(error(existence_error(key,Key), Where)) -->
166	[ 'EXISTENCE ERROR- ~w: ~w not an existing key' - [Where,Key] ].
167system_message(error(existence_error(thread,Thread), Where)) -->
168	[ 'EXISTENCE ERROR- ~w: ~w not a running thread' - [Where,Thread] ].
169system_message(error(existence_error(variable,Var), Where)) -->
170	[ 'EXISTENCE ERROR- ~w: variable ~w does not exist' - [Where,Var] ].
171system_message(error(existence_error(Name,F), W)) -->
172	{ object_name(Name, ObjName) },
173	[ 'EXISTENCE ERROR- ~w could not open ~a ~w' - [W,ObjName,F] ].
174system_message(error(evaluation_error(int_overflow), Where)) -->
175	[ 'INTEGER OVERFLOW ERROR- ~w' - [Where] ].
176system_message(error(evaluation_error(float_overflow), Where)) -->
177	[ 'FLOATING POINT OVERFLOW ERROR- ~w' - [Where] ].
178system_message(error(evaluation_error(undefined), Where)) -->
179	[ 'UNDEFINED ARITHMETIC RESULT ERROR- ~w' - [Where] ].
180system_message(error(evaluation_error(underflow), Where)) -->
181	[ 'UNDERFLOW ERROR- ~w' - [Where] ].
182system_message(error(evaluation_error(float_underflow), Where)) -->
183	[ 'FLOATING POINT UNDERFLOW ERROR- ~w' - [Where] ].
184system_message(error(evaluation_error(zero_divisor), Where)) -->
185	[ 'ZERO DIVISOR ERROR- ~w' - [Where] ].
186system_message(error(instantiation_error, Where)) -->
187	[ 'INSTANTIATION ERROR- ~w: expected bound value' - [Where] ].
188system_message(error(not_implemented(Type, What), Where)) -->
189	[ '~w not implemented- ~w' - [Type, What] ].
190system_message(error(operating_system_error, Where)) -->
191	[ 'OPERATING SYSTEM ERROR- ~w' - [Where] ].
192system_message(error(out_of_heap_error, Where)) -->
193	[ 'OUT OF DATABASE SPACE ERROR- ~w' - [Where] ].
194system_message(error(out_of_stack_error, Where)) -->
195	[ 'OUT OF STACK SPACE ERROR- ~w' - [Where] ].
196system_message(error(out_of_trail_error, Where)) -->
197	[ 'OUT OF TRAIL SPACE ERROR- ~w' - [Where] ].
198system_message(error(out_of_attvars_error, Where)) -->
199	[ 'OUT OF STACK SPACE ERROR- ~w' - [Where] ].
200system_message(error(out_of_auxspace_error, Where)) -->
201	[ 'OUT OF AUXILIARY STACK SPACE ERROR- ~w' - [Where] ].
202system_message(error(permission_error(access,private_procedure,P), Where)) -->
203	[ 'PERMISSION ERROR- ~w: cannot see clauses for ~w' - [Where,P] ].
204system_message(error(permission_error(access,static_procedure,P), Where)) -->
205	[ 'PERMISSION ERROR- ~w: cannot access static procedure ~w' - [Where,P] ].
206system_message(error(permission_error(alias,new,P), Where)) -->
207	[ 'PERMISSION ERROR- ~w: cannot create alias ~w' - [Where,P] ].
208system_message(error(permission_error(create,Name,P), Where)) -->
209	{ object_name(Name, ObjName) },
210	[ 'PERMISSION ERROR- ~w: cannot create ~a ~w' - [Where,ObjName,P] ].
211system_message(error(permission_error(input,binary_stream,Stream), Where)) -->
212	[ 'PERMISSION ERROR- ~w: cannot read from binary stream ~w' - [Where,Stream] ].
213system_message(error(permission_error(input,closed_stream,Stream), Where)) -->
214	[ 'PERMISSION ERROR- ~w: trying to read from closed stream ~w' - [Where,Stream] ].
215system_message(error(permission_error(input,past_end_of_stream,Stream), Where)) -->
216	[ 'PERMISSION ERROR- ~w: past end of stream ~w' - [Where,Stream] ].
217system_message(error(permission_error(input,stream,Stream), Where)) -->
218	[ 'PERMISSION ERROR- ~w: cannot read from ~w' - [Where,Stream] ].
219system_message(error(permission_error(input,text_stream,Stream), Where)) -->
220	[ 'PERMISSION ERROR- ~w: cannot read from text stream ~w' - [Where,Stream] ].
221system_message(error(permission_error(modify,dynamic_procedure,_), Where)) -->
222	[ 'PERMISSION ERROR- ~w: modifying a dynamic procedure' - [Where] ].
223system_message(error(permission_error(modify,flag,W), _)) -->
224	[ 'PERMISSION ERROR- cannot modify flag ~w' - [W] ].
225system_message(error(permission_error(modify,operator,W), Q)) -->
226	[ 'PERMISSION ERROR- ~w: cannot modify operator ~q' - [Q,W] ].
227system_message(error(permission_error(modify,dynamic_procedure,F), Where)) -->
228	[ 'PERMISSION ERROR- ~w: modifying dynamic procedure ~w' - [Where,F] ].
229system_message(error(permission_error(modify,static_procedure,F), Where)) -->
230	[ 'PERMISSION ERROR- ~w: modifying static procedure ~w' - [Where,F] ].
231system_message(error(permission_error(modify,static_procedure_in_use,_), Where)) -->
232	[ 'PERMISSION ERROR- ~w: modifying a static procedure in use' - [Where] ].
233system_message(error(permission_error(modify,table,P), _)) -->
234	[ 'PERMISSION ERROR- cannot table procedure ~w' - [P] ].
235system_message(error(permission_error(module,redefined,Mod), Who)) -->
236	[ 'PERMISSION ERROR ~w- redefining module ~a in a different file' - [Who,Mod] ].
237system_message(error(permission_error(open,source_sink,Stream), Where)) -->
238	[ 'PERMISSION ERROR- ~w: cannot open file ~w' - [Where,Stream] ].
239system_message(error(permission_error(output,binary_stream,Stream), Where)) -->
240	[ 'PERMISSION ERROR- ~w: cannot write to binary stream ~w' - [Where,Stream] ].
241system_message(error(permission_error(output,stream,Stream), Where)) -->
242	[ 'PERMISSION ERROR- ~w: cannot write to ~w' - [Where,Stream] ].
243system_message(error(permission_error(output,text_stream,Stream), Where)) -->
244	[ 'PERMISSION ERROR- ~w: cannot write to text stream ~w' - [Where,Stream] ].
245system_message(error(permission_error(resize,array,P), Where)) -->
246	[ 'PERMISSION ERROR- ~w: cannot resize array ~w' - [Where,P] ].
247system_message(error(permission_error(unlock,mutex,P), Where)) -->
248	[ 'PERMISSION ERROR- ~w: cannot unlock mutex ~w' - [Where,P] ].
249system_message(error(representation_error(character), Where)) -->
250	[ 'REPRESENTATION ERROR- ~w: expected character' - [Where] ].
251system_message(error(representation_error(character_code), Where)) -->
252	[ 'REPRESENTATION ERROR- ~w: expected character code' - [Where] ].
253system_message(error(representation_error(max_arity), Where)) -->
254	[ 'REPRESENTATION ERROR- ~w: number too big' - [Where] ].
255system_message(error(representation_error(variable), Where)) -->
256	[ 'REPRESENTATION ERROR- ~w: should be a variable' - [Where] ].
257system_message(error(resource_error(code_space), Where)) -->
258	[ 'RESOURCE ERROR- not enough code space' - [Where] ].
259system_message(error(resource_error(huge_int), Where)) -->
260	[ 'RESOURCE ERROR- too large an integer in absolute value' - [Where] ].
261system_message(error(resource_error(memory), Where)) -->
262	[ 'RESOURCE ERROR- not enough virtual memory' - [Where] ].
263system_message(error(resource_error(stack), Where)) -->
264	[ 'RESOURCE ERROR- not enough stack' - [Where] ].
265system_message(error(resource_error(streams), Where)) -->
266	[ 'RESOURCE ERROR- could not find a free stream' - [Where] ].
267system_message(error(resource_error(threads), Where)) -->
268	[ 'RESOURCE ERROR- too many open threads' - [Where] ].
269system_message(error(resource_error(trail), Where)) -->
270	[ 'RESOURCE ERROR- not enough trail space' - [Where] ].
271system_message(error(signal(SIG,_), _)) -->
272	[ 'UNEXPECTED SIGNAL: ~a' - [SIG] ].
273system_message(error(syntax_error(syntax_error(G,0,Msg,[],0,0,File)), _)) -->
274	[ 'SYNTAX ERROR at "~a", goal ~q: ~a' - [File,G,Msg] ].
275system_message(error(syntax_error(syntax_error(read(Term),_,_,Term,Pos,Start,File)), Where)) -->
276	['~w' - [Where]],
277	syntax_error_line(File, Start, Pos),
278	syntax_error_term(10, Pos, Term),
279	[ '.' ].
280system_message(error(system_error, Where)) -->
281	[ 'SYSTEM ERROR- ~w' - [Where] ].
282system_message(error(internal_compiler_error, Where)) -->
283	[ 'INTERNAL COMPILER ERROR- ~w' - [Where] ].
284system_message(error(system_error(Message), Where)) -->
285	[ 'SYSTEM ERROR- ~w at ~w]' - [Message,Where] ].
286system_message(error(timeout_error(T,Obj), _Where)) -->
287	[ 'TIMEOUT ERROR- operation ~w on object ~w' - [T,Obj] ].
288system_message(error(type_error(T,_,Err,M), _Where)) -->
289	[ 'TYPE ERROR- ~w: expected ~w, got ~w' - [T,Err,M] ].
290system_message(error(type_error(TE,W), Where)) -->
291	{ object_name(TE, M) }, !,
292	[ 'TYPE ERROR- ~w: expected ~a, got ~w' - [Where,M,W] ].
293system_message(error(type_error(TE,W), Where)) -->
294	[ 'TYPE ERROR- ~w: expected ~q, got ~w' - [Where,TE,W] ].
295system_message(error(unknown, Where)) -->
296	[ 'EXISTENCE ERROR- procedure ~w undefined' - [Where] ].
297system_message(error(unhandled_exception,Throw)) -->
298	[ 'UNHANDLED EXCEPTION - message ~w unknown' - [Throw] ].
299system_message(error(uninstantiation_error(TE), Where)) -->
300	[ 'UNINSTANTIATION ERROR - expected unbound term, got ~q' - [TE] ].
301system_message(Messg) -->
302	[ '~q' - Messg ].
303
304
305domain_error(array_overflow, Opt) --> !,
306	[ 'invalid static index ~w for array' - Opt ].
307domain_error(array_type, Opt) --> !,
308	[ 'invalid static array type ~w' - Opt ].
309domain_error(builtin_procedure, _) --> !,
310	[ 'non-iso built-in procedure'  ].
311domain_error(character_code_list, Opt) --> !,
312	[ 'invalid list of codes ~w' - [Opt] ].
313domain_error(close_option, Opt) --> !,
314	[ 'invalid close option ~w' - [Opt] ].
315domain_error(delete_file_option, Opt) --> !,
316	[ 'invalid list of options ~w' - [Opt] ].
317domain_error(encoding, Opt) --> !,
318	[ 'invalid encoding ~w' - [Opt] ].
319domain_error(flag_value, Opt) --> !,
320	[ 'invalid value ~w for flag ~w' - [Opt] ].
321domain_error(io_mode, Opt) --> !,
322	[ 'invalid io mode ~w' - [Opt] ].
323domain_error(mutable, Opt) --> !,
324	[ 'invalid id mutable ~w' - [Opt] ].
325domain_error(module_decl_options, Opt) --> !,
326	[ 'expect module declaration options, found ~w' - [Opt] ].
327domain_error(non_empty_list, Opt) --> !,
328	[ 'found empty list' - [Opt] ].
329domain_error(not_less_than_zero, Opt) --> !,
330	[ 'number ~w less than zero' - [Opt] ].
331domain_error(not_newline, Opt) --> !,
332	[ 'number ~w not newline' - [Opt] ].
333domain_error(not_zero, Opt) --> !,
334	[ '~w is not allowed in the domain' - [Opt] ].
335domain_error(operator_priority, Opt) --> !,
336	[ '~w invalid operator priority' - [Opt] ].
337domain_error(operator_specifier, Opt) --> !,
338	[ 'invalid operator specifier ~w' - [Opt] ].
339domain_error(out_of_range, Opt) --> !,
340	[ 'expression ~w is out of range' - [Opt] ].
341domain_error(predicate_spec, Opt) --> !,
342	[ '~w invalid predicate specifier' - [Opt] ].
343domain_error(radix, Opt) --> !,
344	[ 'invalid radix ~w' - [Opt] ].
345vdomain_error(read_option, Opt) --> !,
346	[ '~w invalid option to read_term' - [Opt] ].
347domain_error(semantics_indicatior, Opt) --> !,
348	[ '~w expected predicate indicator, got ~w' - [Opt] ].
349domain_error(shift_count_overflow, Opt) --> !,
350	[ 'shift count overflow in ~w' - [Opt] ].
351domain_error(source_sink, Opt) --> !,
352	[ '~w is not a source sink term' - [Opt] ].
353domain_error(stream, Opt) --> !,
354	[ '~w is not a stream' - [Opt] ].
355domain_error(stream_or_alias, Opt) --> !,
356	[ '~w is not a stream (or alias)' - [Opt] ].
357domain_error(stream_encoding, Opt) --> !,
358	[ '~w is not a supported stream encoding' - [Opt] ].
359domain_error(stream_position, Opt) --> !,
360	[ '~w is not a stream position' - [Opt] ].
361domain_error(stream_property, Opt) --> !,
362	[ '~w is not a stream property' - [Opt] ].
363domain_error(syntax_error_handler, Opt) --> !,
364	[ '~w is not a syntax error handler' - [Opt] ].
365domain_error(table, Opt) --> !,
366	[ 'non-tabled procedure ~w' - [Opt] ].
367domain_error(thread_create_option, Opt) --> !,
368	[ '~w is not a thread_create option' - [Opt] ].
369domain_error(time_out_spec, Opt) --> !,
370	[ '~w is not valid specificatin for time_out' - [Opt] ].
371domain_error(unimplemented_option, Opt) --> !,
372	[ '~w is not yet implemented' - [Opt] ].
373domain_error(write_option, Opt) --> !,
374	[ '~w invalid write option' - [Opt] ].
375domain_error(Domain, Opt) -->
376	[ '~w not a valid element for ~w' - [Opt,Domain] ].
377
378
379object_name(array, array).
380object_name(atom, atom).
381object_name(atomic, atomic).
382object_name(byte, byte).
383object_name(callable, 'callable goal').
384object_name(char, char).
385object_name(character_code, 'character code').
386object_name(compound, 'compound term').
387object_name(db_reference, 'data base reference').
388object_name(evaluable, 'evaluable term').
389object_name(file, file).
390object_name(float, float).
391object_name(in_byte, byte).
392object_name(in_character, character).
393object_name(integer, integer).
394object_name(key, 'database key').
395object_name(leash_mode, 'leash mode').
396object_name(library, library).
397object_name(list, list).
398object_name(message_queue, 'message queue').
399object_name(mutex, mutex).
400object_name(number, number).
401object_name(operator, operator).
402object_name(pointer, pointer).
403object_name(predicate_indicator, 'predicate indicator').
404object_name(source_sink, file).
405object_name(unsigned_byte, 'unsigned byte').
406object_name(unsigned_char, 'unsigned char').
407object_name(variable, 'unbound variable').
408
409svs([H]) --> !, H.
410svs([H|L]) -->
411	H,
412	", ",
413	svs(L).
414
415list_of_preds([]) --> [].
416list_of_preds([P|L]) -->
417	['~q' - [P]],
418	list_of_preds(L).
419
420
421syntax_error_line(File, Position,_) -->
422	[' at ~a, near line ~d:~n' - [File,Position]].
423
424syntax_error_term(0,J,L) -->
425	['~n' ],
426	syntax_error_term(10,J,L).
427syntax_error_term(_,0,L) --> !,
428	[ '~n<==== HERE ====>~n' ],
429	syntax_error_term(10,-1,L).
430syntax_error_term(_,_,[]) --> !.
431syntax_error_term(I,J,[T-_P|R]) -->
432	syntax_error_token(T),
433	{
434	 I1 is I-1,
435	 J1 is J-1
436	},
437	syntax_error_term(I1,J1,R).
438
439syntax_error_token(atom(A)) --> !,
440	[ ' ~a' - [A] ].
441syntax_error_token(number(N)) --> !,
442	[ ' ~w' - [N] ].
443syntax_error_token(var(_,S,_))  --> !,
444	[ ' ~s'  - [S] ].
445syntax_error_token(string(S)) --> !,
446	[ ' ""~s"' - [S] ].
447syntax_error_token('(') --> !,
448	[ '('  ].
449syntax_error_token(')') --> !,
450	[ ' )'  ].
451syntax_error_token(',') --> !,
452	[ ' ,' ].
453syntax_error_token(A) --> !,
454	[ ' ~a' - [A] ].
455
456
457%	print_message_lines(+Stream, +Prefix, +Lines)
458%
459%	Quintus/SICStus/SWI compatibility predicate to print message lines
460%       using  a prefix.
461
462prolog:print_message_lines(_, _, []) :- !.
463prolog:print_message_lines(S, P, [at_same_line|Lines]) :- !,
464	print_message_line(S, Lines, Rest),
465	prolog:print_message_lines(S, P, Rest).
466prolog:print_message_lines(S, P-Opts, Lines) :- !,
467	atom_concat('~N', P, Prefix),
468	format(S, Prefix, Opts),
469	print_message_line(S, Lines, Rest),
470	prolog:print_message_lines(S, P-Opts, Rest).
471prolog:print_message_lines(S, P, Lines) :-
472	atom_concat('~N', P, Prefix),
473	format(S, Prefix, []),
474	print_message_line(S, Lines, Rest),
475	prolog:print_message_lines(S, P, Rest).
476
477print_message_line(S, [flush], []) :- !,
478	flush_output(S).
479print_message_line(S, [], []) :- !,
480	nl(S).
481print_message_line(S, [nl|T], T) :- !,
482	nl(S).
483print_message_line(S, [Fmt-Args|T0], T) :- !,
484	format(S, Fmt, Args),
485	print_message_line(S, T0, T).
486print_message_line(S, [Fmt|T0], T) :-
487	format(S, Fmt, []),
488	print_message_line(S, T0, T).
489
490prefix(error,   '     ', user_error, 'ERROR!! ').
491prefix(warning, '% ', user_error, 'Warning: ').
492
493prefix(help,	      '',          user_error) --> [].
494prefix(query,	      '',          user_error) --> [].
495prefix(debug,	      '',          user_output) --> [].
496prefix(warning,	      '% ',      user_error) -->
497	{ thread_self(Id) },
498	(   { Id == main }
499	->  [ 'Warning: ', nl ]
500	;   ['Warning: [Thread ~d ]' - Id, nl ]
501	).
502prefix(error,	      '     ',   user_error) -->
503	{ recorded(sp_info,local_sp(P,_,_,_),_) },
504	{ thread_self(Id) },
505	(   { Id == main }
506	->  [ 'ERROR at ' ]
507	;   [ 'ERROR [Thread ~d ] at ' - Id ]
508	),
509	'$hacks':display_pc(P),
510	!,
511	[' !!', nl].
512prefix(error,	      '     ',   user_error) -->
513	{ thread_self(Id) },
514	(   { Id == main }
515	->  [ 'ERROR!!', nl ]
516	;   [ 'ERROR!! [Thread ~d ]' - Id, nl ]
517	).
518prefix(banner,	      '',	   user_error) --> [].
519prefix(informational, '~*|% '-[LC],     user_error) -->
520	{ '$show_consult_level'(LC) }.
521
522
523