37
38:- module('$messages',
39 [ print_message/2, 40 print_message_lines/3, 41 message_to_string/2 42 ]). 43
44:- multifile
45 prolog:message//1, 46 prolog:error_message//1, 47 prolog:message_context//1, 48 prolog:deprecated//1, 49 prolog:message_location//1, 50 prolog:message_line_element/2. 51:- '$hide'((
52 prolog:message//1,
53 prolog:error_message//1,
54 prolog:message_context//1,
55 prolog:deprecated//1,
56 prolog:message_location//1,
57 prolog:message_line_element/2)). 59:- multifile
60 prolog:message//2, 61 prolog:error_message//2, 62 prolog:message_context//2, 63 prolog:message_location//2, 64 prolog:deprecated//2. 65:- '$hide'((
66 prolog:message//2,
67 prolog:error_message//2,
68 prolog:message_context//2,
69 prolog:deprecated//2,
70 prolog:message_location//2)). 71
72:- discontiguous
73 prolog_message/3. 74
75:- public
76 translate_message//1, 77 prolog:translate_message//1. 78
79:- create_prolog_flag(message_context, [thread], []). 80
102
103prolog:translate_message(Term) -->
104 translate_message(Term).
105
110
111translate_message(Term) -->
112 { nonvar(Term) },
113 ( { message_lang(Lang) },
114 prolog:message(Lang, Term)
115 ; prolog:message(Term)
116 ),
117 !.
118translate_message(Term) -->
119 { nonvar(Term) },
120 translate_message2(Term),
121 !.
122translate_message(Term) -->
123 { nonvar(Term),
124 Term = error(_, _)
125 },
126 [ 'Unknown exception: ~p'-[Term] ].
127translate_message(Term) -->
128 [ 'Unknown message: ~p'-[Term] ].
129
130translate_message2(Term) -->
131 prolog_message(Term).
132translate_message2(error(resource_error(stack), Context)) -->
133 !,
134 out_of_stack(Context).
135translate_message2(error(resource_error(tripwire(Wire, Context)), _)) -->
136 !,
137 tripwire_message(Wire, Context).
138translate_message2(error(existence_error(reset, Ball), SWI)) -->
139 swi_location(SWI),
140 tabling_existence_error(Ball, SWI).
141translate_message2(error(ISO, SWI)) -->
142 swi_location(SWI),
143 term_message(ISO),
144 swi_extra(SWI).
145translate_message2(unwind(Term)) -->
146 unwind_message(Term).
147translate_message2(message_lines(Lines), L, T) :- 148 make_message_lines(Lines, L, T).
149translate_message2(format(Fmt, Args)) -->
150 [ Fmt-Args ].
151
152make_message_lines([], T, T) :- !.
153make_message_lines([Last], ['~w'-[Last]|T], T) :- !.
154make_message_lines([L0|LT], ['~w'-[L0],nl|T0], T) :-
155 make_message_lines(LT, T0, T).
156
162
163:- public term_message//1. 164term_message(Term) -->
165 {var(Term)},
166 !,
167 [ 'Unknown error term: ~p'-[Term] ].
168term_message(Term) -->
169 { message_lang(Lang) },
170 prolog:error_message(Lang, Term),
171 !.
172term_message(Term) -->
173 prolog:error_message(Term),
174 !.
175term_message(Term) -->
176 iso_message(Term).
177term_message(Term) -->
178 swi_message(Term).
179term_message(Term) -->
180 [ 'Unknown error term: ~p'-[Term] ].
181
182iso_message(resource_error(c_stack)) -->
183 out_of_c_stack.
184iso_message(resource_error(Missing)) -->
185 [ 'Not enough resources: ~w'-[Missing] ].
186iso_message(type_error(evaluable, Actual)) -->
187 { callable(Actual) },
188 [ 'Arithmetic: `~p'' is not a function'-[Actual] ].
189iso_message(type_error(free_of_attvar, Actual)) -->
190 [ 'Type error: `~W'' contains attributed variables'-
191 [Actual,[portray(true), attributes(portray)]] ].
192iso_message(type_error(Expected, Actual)) -->
193 [ 'Type error: `~w'' expected, found `~p'''-[Expected, Actual] ],
194 type_error_comment(Expected, Actual).
195iso_message(domain_error(Domain, Actual)) -->
196 [ 'Domain error: '-[] ], domain(Domain),
197 [ ' expected, found `~p'''-[Actual] ].
198iso_message(instantiation_error) -->
199 [ 'Arguments are not sufficiently instantiated' ].
200iso_message(uninstantiation_error(Var)) -->
201 [ 'Uninstantiated argument expected, found ~p'-[Var] ].
202iso_message(representation_error(What)) -->
203 [ 'Cannot represent due to `~w'''-[What] ].
204iso_message(permission_error(Action, Type, Object)) -->
205 permission_error(Action, Type, Object).
206iso_message(evaluation_error(Which)) -->
207 [ 'Arithmetic: evaluation error: `~p'''-[Which] ].
208iso_message(existence_error(procedure, Proc)) -->
209 [ 'Unknown procedure: ~q'-[Proc] ],
210 unknown_proc_msg(Proc).
211iso_message(existence_error(answer_variable, Var)) -->
212 [ '$~w was not bound by a previous query'-[Var] ].
213iso_message(existence_error(matching_rule, Goal)) -->
214 [ 'No rule matches ~p'-[Goal] ].
215iso_message(existence_error(Type, Object)) -->
216 [ '~w `~p'' does not exist'-[Type, Object] ].
217iso_message(existence_error(export, PI, module(M))) --> 218 [ 'Module ', ansi(code, '~q', [M]), ' does not export ',
219 ansi(code, '~q', [PI]) ].
220iso_message(existence_error(Type, Object, In)) --> 221 [ '~w `~p'' does not exist in ~p'-[Type, Object, In] ].
222iso_message(busy(Type, Object)) -->
223 [ '~w `~p'' is busy'-[Type, Object] ].
224iso_message(syntax_error(swi_backslash_newline)) -->
225 [ 'Deprecated ... \\<newline><white>*. Use \\c' ].
226iso_message(syntax_error(Id)) -->
227 [ 'Syntax error: ' ],
228 syntax_error(Id).
229iso_message(occurs_check(Var, In)) -->
230 [ 'Cannot unify ~p with ~p: would create an infinite tree'-[Var, In] ].
231
236
237permission_error(Action, built_in_procedure, Pred) -->
238 { user_predicate_indicator(Pred, PI)
239 },
240 [ 'No permission to ~w built-in predicate `~p'''-[Action, PI] ],
241 ( {Action \== export}
242 -> [ nl,
243 'Use :- redefine_system_predicate(+Head) if redefinition is intended'
244 ]
245 ; []
246 ).
247permission_error(import_into(Dest), procedure, Pred) -->
248 [ 'No permission to import ~p into ~w'-[Pred, Dest] ].
249permission_error(Action, static_procedure, Proc) -->
250 [ 'No permission to ~w static procedure `~p'''-[Action, Proc] ],
251 defined_definition('Defined', Proc).
252permission_error(input, stream, Stream) -->
253 [ 'No permission to read from output stream `~p'''-[Stream] ].
254permission_error(output, stream, Stream) -->
255 [ 'No permission to write to input stream `~p'''-[Stream] ].
256permission_error(input, text_stream, Stream) -->
257 [ 'No permission to read bytes from TEXT stream `~p'''-[Stream] ].
258permission_error(output, text_stream, Stream) -->
259 [ 'No permission to write bytes to TEXT stream `~p'''-[Stream] ].
260permission_error(input, binary_stream, Stream) -->
261 [ 'No permission to read characters from binary stream `~p'''-[Stream] ].
262permission_error(output, binary_stream, Stream) -->
263 [ 'No permission to write characters to binary stream `~p'''-[Stream] ].
264permission_error(open, source_sink, alias(Alias)) -->
265 [ 'No permission to reuse alias "~p": already taken'-[Alias] ].
266permission_error(tnot, non_tabled_procedure, Pred) -->
267 [ 'The argument of tnot/1 is not tabled: ~p'-[Pred] ].
268permission_error(assert, procedure, Pred) -->
269 { '$pi_head'(Pred, Head),
270 predicate_property(Head, ssu)
271 },
272 [ '~p: an SSU (Head => Body) predicate cannot have normal Prolog clauses'-
273 [Pred] ].
274permission_error(Action, Type, Object) -->
275 [ 'No permission to ~w ~w `~p'''-[Action, Type, Object] ].
276
277
278unknown_proc_msg(_:(^)/2) -->
279 !,
280 unknown_proc_msg((^)/2).
281unknown_proc_msg((^)/2) -->
282 !,
283 [nl, ' ^/2 can only appear as the 2nd argument of setof/3 and bagof/3'].
284unknown_proc_msg((:-)/2) -->
285 !,
286 [nl, ' Rules must be loaded from a file'],
287 faq('ToplevelMode').
288unknown_proc_msg((=>)/2) -->
289 !,
290 [nl, ' Rules must be loaded from a file'],
291 faq('ToplevelMode').
292unknown_proc_msg((:-)/1) -->
293 !,
294 [nl, ' Directives must be loaded from a file'],
295 faq('ToplevelMode').
296unknown_proc_msg((?-)/1) -->
297 !,
298 [nl, ' ?- is the Prolog prompt'],
299 faq('ToplevelMode').
300unknown_proc_msg(Proc) -->
301 { dwim_predicates(Proc, Dwims) },
302 ( {Dwims \== []}
303 -> [nl, ' However, there are definitions for:', nl],
304 dwim_message(Dwims)
305 ; []
306 ).
307
308dependency_error(shared(Shared), private(Private)) -->
309 [ 'Shared table for ~p may not depend on private ~p'-[Shared, Private] ].
310dependency_error(Dep, monotonic(On)) -->
311 { '$pi_head'(PI, Dep),
312 '$pi_head'(MPI, On)
313 },
314 [ 'Dependent ~p on monotonic predicate ~p is not monotonic or incremental'-
315 [PI, MPI]
316 ].
317
318faq(Page) -->
319 [nl, ' See FAQ at https://www.swi-prolog.org/FAQ/', Page, '.html' ].
320
(_Expected, Actual) -->
322 { type_of(Actual, Type),
323 ( sub_atom(Type, 0, 1, _, First),
324 memberchk(First, [a,e,i,o,u])
325 -> Article = an
326 ; Article = a
327 )
328 },
329 [ ' (~w ~w)'-[Article, Type] ].
330
331type_of(Term, Type) :-
332 ( attvar(Term) -> Type = attvar
333 ; var(Term) -> Type = var
334 ; atom(Term) -> Type = atom
335 ; integer(Term) -> Type = integer
336 ; string(Term) -> Type = string
337 ; Term == [] -> Type = empty_list
338 ; blob(Term, BlobT) -> blob_type(BlobT, Type)
339 ; rational(Term) -> Type = rational
340 ; float(Term) -> Type = float
341 ; is_stream(Term) -> Type = stream
342 ; is_dict(Term) -> Type = dict
343 ; is_list(Term) -> Type = list
344 ; cyclic_term(Term) -> Type = cyclic
345 ; compound(Term) -> Type = compound
346 ; Type = unknown
347 ).
348
349blob_type(BlobT, Type) :-
350 atom_concat(BlobT, '_reference', Type).
351
352syntax_error(end_of_clause) -->
353 [ 'Unexpected end of clause' ].
354syntax_error(end_of_clause_expected) -->
355 [ 'End of clause expected' ].
356syntax_error(end_of_file) -->
357 [ 'Unexpected end of file' ].
358syntax_error(end_of_file_in_block_comment) -->
359 [ 'End of file in /* ... */ comment' ].
360syntax_error(end_of_file_in_quoted(Quote)) -->
361 [ 'End of file in quoted ' ],
362 quoted_type(Quote).
363syntax_error(illegal_number) -->
364 [ 'Illegal number' ].
365syntax_error(long_atom) -->
366 [ 'Atom too long (see style_check/1)' ].
367syntax_error(long_string) -->
368 [ 'String too long (see style_check/1)' ].
369syntax_error(operator_clash) -->
370 [ 'Operator priority clash' ].
371syntax_error(operator_expected) -->
372 [ 'Operator expected' ].
373syntax_error(operator_balance) -->
374 [ 'Unbalanced operator' ].
375syntax_error(quoted_punctuation) -->
376 [ 'Operand expected, unquoted comma or bar found' ].
377syntax_error(list_rest) -->
378 [ 'Unexpected comma or bar in rest of list' ].
379syntax_error(cannot_start_term) -->
380 [ 'Illegal start of term' ].
381syntax_error(punct(Punct, End)) -->
382 [ 'Unexpected `~w\' before `~w\''-[Punct, End] ].
383syntax_error(undefined_char_escape(C)) -->
384 [ 'Unknown character escape in quoted atom or string: `\\~w\''-[C] ].
385syntax_error(void_not_allowed) -->
386 [ 'Empty argument list "()"' ].
387syntax_error(Term) -->
388 { compound(Term),
389 compound_name_arguments(Term, Syntax, [Text])
390 }, !,
391 [ '~w expected, found '-[Syntax], ansi(code, '"~w"', [Text]) ].
392syntax_error(Message) -->
393 [ '~w'-[Message] ].
394
395quoted_type('\'') --> [atom].
396quoted_type('\"') --> { current_prolog_flag(double_quotes, Type) }, [Type-[]].
397quoted_type('\`') --> { current_prolog_flag(back_quotes, Type) }, [Type-[]].
398
399domain(range(Low,High)) -->
400 !,
401 ['[~q..~q]'-[Low,High] ].
402domain(Domain) -->
403 ['`~w\''-[Domain] ].
404
409
410tabling_existence_error(Ball, Context) -->
411 { table_shift_ball(Ball) },
412 [ 'Tabling dependency error' ],
413 swi_extra(Context).
414
415table_shift_ball(dependency(_Head)).
416table_shift_ball(dependency(_Skeleton, _Trie, _Mono)).
417table_shift_ball(call_info(_Skeleton, _Status)).
418table_shift_ball(call_info(_GenSkeleton, _Skeleton, _Status)).
419
423
424dwim_predicates(Module:Name/_Arity, Dwims) :-
425 !,
426 findall(Dwim, dwim_predicate(Module:Name, Dwim), Dwims).
427dwim_predicates(Name/_Arity, Dwims) :-
428 findall(Dwim, dwim_predicate(user:Name, Dwim), Dwims).
429
430dwim_message([]) --> [].
431dwim_message([M:Head|T]) -->
432 { hidden_module(M),
433 !,
434 functor(Head, Name, Arity)
435 },
436 [ ' ~q'-[Name/Arity], nl ],
437 dwim_message(T).
438dwim_message([Module:Head|T]) -->
439 !,
440 { functor(Head, Name, Arity)
441 },
442 [ ' ~q'-[Module:Name/Arity], nl],
443 dwim_message(T).
444dwim_message([Head|T]) -->
445 {functor(Head, Name, Arity)},
446 [ ' ~q'-[Name/Arity], nl],
447 dwim_message(T).
448
449
450swi_message(io_error(Op, Stream)) -->
451 [ 'I/O error in ~w on stream ~p'-[Op, Stream] ].
452swi_message(thread_error(TID, false)) -->
453 [ 'Thread ~p died due to failure:'-[TID] ].
454swi_message(thread_error(TID, exception(Error))) -->
455 [ 'Thread ~p died abnormally:'-[TID], nl ],
456 translate_message(Error).
457swi_message(dependency_error(Tabled, DependsOn)) -->
458 dependency_error(Tabled, DependsOn).
459swi_message(shell(execute, Cmd)) -->
460 [ 'Could not execute `~w'''-[Cmd] ].
461swi_message(shell(signal(Sig), Cmd)) -->
462 [ 'Caught signal ~d on `~w'''-[Sig, Cmd] ].
463swi_message(format(Fmt, Args)) -->
464 [ Fmt-Args ].
465swi_message(signal(Name, Num)) -->
466 [ 'Caught signal ~d (~w)'-[Num, Name] ].
467swi_message(limit_exceeded(Limit, MaxVal)) -->
468 [ 'Exceeded ~w limit (~w)'-[Limit, MaxVal] ].
469swi_message(goal_failed(Goal)) -->
470 [ 'goal unexpectedly failed: ~p'-[Goal] ].
471swi_message(shared_object(_Action, Message)) --> 472 [ '~w'-[Message] ].
473swi_message(system_error(Error)) -->
474 [ 'error in system call: ~w'-[Error]
475 ].
476swi_message(system_error) -->
477 [ 'error in system call'
478 ].
479swi_message(failure_error(Goal)) -->
480 [ 'Goal failed: ~p'-[Goal] ].
481swi_message(timeout_error(Op, Stream)) -->
482 [ 'Timeout in ~w from ~p'-[Op, Stream] ].
483swi_message(not_implemented(Type, What)) -->
484 [ '~w `~p\' is not implemented in this version'-[Type, What] ].
485swi_message(context_error(nodirective, Goal)) -->
486 { goal_to_predicate_indicator(Goal, PI) },
487 [ 'Wrong context: ~p can only be used in a directive'-[PI] ].
488swi_message(context_error(edit, no_default_file)) -->
489 ( { current_prolog_flag(windows, true) }
490 -> [ 'Edit/0 can only be used after opening a \c
491 Prolog file by double-clicking it' ]
492 ; [ 'Edit/0 can only be used with the "-s file" commandline option'
493 ]
494 ),
495 [ nl, 'Use "?- edit(Topic)." or "?- emacs."' ].
496swi_message(context_error(function, meta_arg(S))) -->
497 [ 'Functions are not (yet) supported for meta-arguments of type ~q'-[S] ].
498swi_message(format_argument_type(Fmt, Arg)) -->
499 [ 'Illegal argument to format sequence ~~~w: ~p'-[Fmt, Arg] ].
500swi_message(format(Msg)) -->
501 [ 'Format error: ~w'-[Msg] ].
502swi_message(conditional_compilation_error(unterminated, File:Line)) -->
503 [ 'Unterminated conditional compilation from '-[], url(File:Line) ].
504swi_message(conditional_compilation_error(no_if, What)) -->
505 [ ':- ~w without :- if'-[What] ].
506swi_message(duplicate_key(Key)) -->
507 [ 'Duplicate key: ~p'-[Key] ].
508swi_message(initialization_error(failed, Goal, File:Line)) -->
509 !,
510 [ url(File:Line), ': ~p: false'-[Goal] ].
511swi_message(initialization_error(Error, Goal, File:Line)) -->
512 [ url(File:Line), ': ~p '-[Goal] ],
513 translate_message(Error).
514swi_message(determinism_error(PI, det, Found, property)) -->
515 ( { '$pi_head'(user:PI, Head),
516 predicate_property(Head, det)
517 }
518 -> [ 'Deterministic procedure ~p'-[PI] ]
519 ; [ 'Procedure ~p called from a deterministic procedure'-[PI] ]
520 ),
521 det_error(Found).
522swi_message(determinism_error(PI, det, fail, guard)) -->
523 [ 'Procedure ~p failed after $-guard'-[PI] ].
524swi_message(determinism_error(PI, det, fail, guard_in_caller)) -->
525 [ 'Procedure ~p failed after $-guard in caller'-[PI] ].
526swi_message(determinism_error(Goal, det, fail, goal)) -->
527 [ 'Goal ~p failed'-[Goal] ].
528swi_message(determinism_error(Goal, det, nondet, goal)) -->
529 [ 'Goal ~p succeeded with a choice point'-[Goal] ].
530swi_message(qlf_format_error(File, Message)) -->
531 [ '~w: Invalid QLF file: ~w'-[File, Message] ].
532swi_message(goal_expansion_error(bound, Term)) -->
533 [ 'Goal expansion bound a variable to ~p'-[Term] ].
534
535det_error(nondet) -->
536 [ ' succeeded with a choicepoint'- [] ].
537det_error(fail) -->
538 [ ' failed'- [] ].
539
540
545
546:- public swi_location//1. 547swi_location(X) -->
548 { var(X) },
549 !.
550swi_location(Context) -->
551 { message_lang(Lang) },
552 prolog:message_location(Lang, Context),
553 !.
554swi_location(Context) -->
555 prolog:message_location(Context),
556 !.
557swi_location(context(Caller, _Msg)) -->
558 { ground(Caller) },
559 !,
560 caller(Caller).
561swi_location(file(Path, Line, -1, _CharNo)) -->
562 !,
563 [ url(Path:Line), ': ' ].
564swi_location(file(Path, Line, LinePos, _CharNo)) -->
565 [ url(Path:Line:LinePos), ': ' ].
566swi_location(stream(Stream, Line, LinePos, CharNo)) -->
567 ( { is_stream(Stream),
568 stream_property(Stream, file_name(File))
569 }
570 -> swi_location(file(File, Line, LinePos, CharNo))
571 ; [ 'Stream ~w:~d:~d '-[Stream, Line, LinePos] ]
572 ).
573swi_location(autoload(File:Line)) -->
574 [ url(File:Line), ': ' ].
575swi_location(_) -->
576 [].
577
578caller(system:'$record_clause'/3) -->
579 !,
580 [].
581caller(Module:Name/Arity) -->
582 !,
583 ( { \+ hidden_module(Module) }
584 -> [ '~q:~q/~w: '-[Module, Name, Arity] ]
585 ; [ '~q/~w: '-[Name, Arity] ]
586 ).
587caller(Name/Arity) -->
588 [ '~q/~w: '-[Name, Arity] ].
589caller(Caller) -->
590 [ '~p: '-[Caller] ].
591
592
600
(X) -->
602 { var(X) },
603 !,
604 [].
605swi_extra(Context) -->
606 { message_lang(Lang) },
607 prolog:message_context(Lang, Context),
608 !.
609swi_extra(Context) -->
610 prolog:message_context(Context).
611swi_extra(context(_, Msg)) -->
612 { nonvar(Msg),
613 Msg \== ''
614 },
615 !,
616 swi_comment(Msg).
617swi_extra(string(String, CharPos)) -->
618 { sub_string(String, 0, CharPos, _, Before),
619 sub_string(String, CharPos, _, 0, After)
620 },
621 [ nl, '~w'-[Before], nl, '** here **', nl, '~w'-[After] ].
622swi_extra(_) -->
623 [].
624
(already_from(Module)) -->
626 !,
627 [ ' (already imported from ~q)'-[Module] ].
628swi_comment(directory(_Dir)) -->
629 !,
630 [ ' (is a directory)' ].
631swi_comment(not_a_directory(_Dir)) -->
632 !,
633 [ ' (is not a directory)' ].
634swi_comment(Msg) -->
635 [ ' (~w)'-[Msg] ].
636
637
638thread_context -->
639 { thread_self(Me), Me \== main, thread_property(Me, id(Id)) },
640 !,
641 ['[Thread ~w] '-[Id]].
642thread_context -->
643 [].
644
645 648
649unwind_message(Var) -->
650 { var(Var) }, !,
651 [ 'Unknown unwind message: ~p'-[Var] ].
652unwind_message(abort) -->
653 [ 'Execution Aborted' ].
654unwind_message(halt(_)) -->
655 [].
656unwind_message(thread_exit(Term)) -->
657 [ 'Invalid thread_exit/1. Payload: ~p'-[Term] ].
658unwind_message(Term) -->
659 [ 'Unknown "unwind" exception: ~p'-[Term] ].
660
661
662 665
666prolog_message(welcome) -->
667 [ 'Welcome to SWI-Prolog (' ],
668 prolog_message(threads),
669 prolog_message(address_bits),
670 ['version ' ],
671 prolog_message(version),
672 [ ')', nl ],
673 prolog_message(copyright),
674 [ nl ],
675 translate_message(user_versions),
676 [ nl ],
677 prolog_message(documentaton),
678 [ nl, nl ].
679prolog_message(user_versions) -->
680 ( { findall(Msg, prolog:version_msg(Msg), Msgs),
681 Msgs \== []
682 }
683 -> [nl],
684 user_version_messages(Msgs)
685 ; []
686 ).
687prolog_message(deprecated(Term)) -->
688 { nonvar(Term) },
689 ( { message_lang(Lang) },
690 prolog:deprecated(Lang, Term)
691 -> []
692 ; prolog:deprecated(Term)
693 -> []
694 ; deprecated(Term)
695 ).
696prolog_message(unhandled_exception(E)) -->
697 { nonvar(E) },
698 [ 'Unhandled exception: ' ],
699 ( translate_message(E)
700 -> []
701 ; [ '~p'-[E] ]
702 ).
703
705
706prolog_message(initialization_error(_, E, File:Line)) -->
707 !,
708 [ url(File:Line),
709 ': Initialization goal raised exception:', nl
710 ],
711 translate_message(E).
712prolog_message(initialization_error(Goal, E, _)) -->
713 [ 'Initialization goal ~p raised exception:'-[Goal], nl ],
714 translate_message(E).
715prolog_message(initialization_failure(_Goal, File:Line)) -->
716 !,
717 [ url(File:Line),
718 ': Initialization goal failed'-[]
719 ].
720prolog_message(initialization_failure(Goal, _)) -->
721 [ 'Initialization goal failed: ~p'-[Goal]
722 ].
723prolog_message(initialization_exception(E)) -->
724 [ 'Prolog initialisation failed:', nl ],
725 translate_message(E).
726prolog_message(init_goal_syntax(Error, Text)) -->
727 !,
728 [ '-g ~w: '-[Text] ],
729 translate_message(Error).
730prolog_message(init_goal_failed(failed, @(Goal,File:Line))) -->
731 !,
732 [ url(File:Line), ': ~p: false'-[Goal] ].
733prolog_message(init_goal_failed(Error, @(Goal,File:Line))) -->
734 !,
735 [ url(File:Line), ': ~p '-[Goal] ],
736 translate_message(Error).
737prolog_message(init_goal_failed(failed, Text)) -->
738 !,
739 [ '-g ~w: false'-[Text] ].
740prolog_message(init_goal_failed(Error, Text)) -->
741 !,
742 [ '-g ~w: '-[Text] ],
743 translate_message(Error).
744prolog_message(goal_failed(Context, Goal)) -->
745 [ 'Goal (~w) failed: ~p'-[Context, Goal] ].
746prolog_message(no_current_module(Module)) -->
747 [ '~w is not a current module (created)'-[Module] ].
748prolog_message(commandline_arg_type(Flag, Arg)) -->
749 [ 'Bad argument to commandline option -~w: ~w'-[Flag, Arg] ].
750prolog_message(missing_feature(Name)) -->
751 [ 'This version of SWI-Prolog does not support ~w'-[Name] ].
752prolog_message(singletons(_Term, List)) -->
753 [ 'Singleton variables: ~w'-[List] ].
754prolog_message(multitons(_Term, List)) -->
755 [ 'Singleton-marked variables appearing more than once: ~w'-[List] ].
756prolog_message(profile_no_cpu_time) -->
757 [ 'No CPU-time info. Check the SWI-Prolog manual for details' ].
758prolog_message(non_ascii(Text, Type)) -->
759 [ 'Unquoted ~w with non-portable characters: ~w'-[Type, Text] ].
760prolog_message(io_warning(Stream, Message)) -->
761 { stream_property(Stream, position(Position)),
762 !,
763 stream_position_data(line_count, Position, LineNo),
764 stream_position_data(line_position, Position, LinePos),
765 ( stream_property(Stream, file_name(File))
766 -> Obj = File
767 ; Obj = Stream
768 )
769 },
770 [ '~p:~d:~d: ~w'-[Obj, LineNo, LinePos, Message] ].
771prolog_message(io_warning(Stream, Message)) -->
772 [ 'stream ~p: ~w'-[Stream, Message] ].
773prolog_message(option_usage(pldoc)) -->
774 [ 'Usage: --pldoc[=port]' ].
775prolog_message(interrupt(begin)) -->
776 [ 'Action (h for help) ? ', flush ].
777prolog_message(interrupt(end)) -->
778 [ 'continue' ].
779prolog_message(interrupt(trace)) -->
780 [ 'continue (trace mode)' ].
781prolog_message(unknown_in_module_user) -->
782 [ 'Using a non-error value for unknown in the global module', nl,
783 'causes most of the development environment to stop working.', nl,
784 'Please use :- dynamic or limit usage of unknown to a module.', nl,
785 'See https://www.swi-prolog.org/howto/database.html'
786 ].
787prolog_message(untable(PI)) -->
788 [ 'Reconsult: removed tabling for ~p'-[PI] ].
789prolog_message(unknown_option(Set, Opt)) -->
790 [ 'Unknown ~w option: ~p'-[Set, Opt] ].
791
792
793 796
797prolog_message(modify_active_procedure(Who, What)) -->
798 [ '~p: modified active procedure ~p'-[Who, What] ].
799prolog_message(load_file(failed(user:File))) -->
800 [ 'Failed to load ~p'-[File] ].
801prolog_message(load_file(failed(Module:File))) -->
802 [ 'Failed to load ~p into module ~p'-[File, Module] ].
803prolog_message(load_file(failed(File))) -->
804 [ 'Failed to load ~p'-[File] ].
805prolog_message(mixed_directive(Goal)) -->
806 [ 'Cannot pre-compile mixed load/call directive: ~p'-[Goal] ].
807prolog_message(cannot_redefine_comma) -->
808 [ 'Full stop in clause-body? Cannot redefine ,/2' ].
809prolog_message(illegal_autoload_index(Dir, Term)) -->
810 [ 'Illegal term in INDEX file of directory ~w: ~w'-[Dir, Term] ].
811prolog_message(redefined_procedure(Type, Proc)) -->
812 [ 'Redefined ~w procedure ~p'-[Type, Proc] ],
813 defined_definition('Previously defined', Proc).
814prolog_message(declare_module(Module, abolish(Predicates))) -->
815 [ 'Loading module ~w abolished: ~p'-[Module, Predicates] ].
816prolog_message(import_private(Module, Private)) -->
817 [ 'import/1: ~p is not exported (still imported into ~q)'-
818 [Private, Module]
819 ].
820prolog_message(ignored_weak_import(Into, From:PI)) -->
821 [ 'Local definition of ~p overrides weak import from ~q'-
822 [Into:PI, From]
823 ].
824prolog_message(undefined_export(Module, PI)) -->
825 [ 'Exported procedure ~q:~q is not defined'-[Module, PI] ].
826prolog_message(no_exported_op(Module, Op)) -->
827 [ 'Operator ~q:~q is not exported (still defined)'-[Module, Op] ].
828prolog_message(discontiguous((-)/2,_)) -->
829 prolog_message(minus_in_identifier).
830prolog_message(discontiguous(Proc,Current)) -->
831 [ 'Clauses of ', ansi(code, '~p', [Proc]),
832 ' are not together in the source-file', nl ],
833 current_definition(Proc, 'Earlier definition at '),
834 [ 'Current predicate: ', ansi(code, '~p', [Current]), nl,
835 'Use ', ansi(code, ':- discontiguous ~p.', [Proc]),
836 ' to suppress this message'
837 ].
838prolog_message(decl_no_effect(Goal)) -->
839 [ 'Deprecated declaration has no effect: ~p'-[Goal] ].
840prolog_message(load_file(start(Level, File))) -->
841 [ '~|~t~*+Loading '-[Level] ],
842 load_file(File),
843 [ ' ...' ].
844prolog_message(include_file(start(Level, File))) -->
845 [ '~|~t~*+include '-[Level] ],
846 load_file(File),
847 [ ' ...' ].
848prolog_message(include_file(done(Level, File))) -->
849 [ '~|~t~*+included '-[Level] ],
850 load_file(File).
851prolog_message(load_file(done(Level, File, Action, Module, Time, Clauses))) -->
852 [ '~|~t~*+'-[Level] ],
853 load_file(File),
854 [ ' ~w'-[Action] ],
855 load_module(Module),
856 [ ' ~2f sec, ~D clauses'-[Time, Clauses] ].
857prolog_message(dwim_undefined(Goal, Alternatives)) -->
858 { goal_to_predicate_indicator(Goal, Pred)
859 },
860 [ 'Unknown procedure: ~q'-[Pred], nl,
861 ' However, there are definitions for:', nl
862 ],
863 dwim_message(Alternatives).
864prolog_message(dwim_correct(Into)) -->
865 [ 'Correct to: ~q? '-[Into], flush ].
866prolog_message(error(loop_error(Spec), file_search(Used))) -->
867 [ 'File search: too many levels of indirections on: ~p'-[Spec], nl,
868 ' Used alias expansions:', nl
869 ],
870 used_search(Used).
871prolog_message(minus_in_identifier) -->
872 [ 'The "-" character should not be used to separate words in an', nl,
873 'identifier. Check the SWI-Prolog FAQ for details.'
874 ].
875prolog_message(qlf(removed_after_error(File))) -->
876 [ 'Removed incomplete QLF file ~w'-[File] ].
877prolog_message(qlf(recompile(Spec,_Pl,_Qlf,Reason))) -->
878 [ '~p: recompiling QLF file'-[Spec] ],
879 qlf_recompile_reason(Reason).
880prolog_message(qlf(can_not_recompile(Spec,QlfFile,_Reason))) -->
881 [ '~p: can not recompile "~w" (access denied)'-[Spec, QlfFile], nl,
882 '\tLoading from source'-[]
883 ].
884prolog_message(qlf(system_lib_out_of_date(Spec,QlfFile))) -->
885 [ '~p: can not recompile "~w" (access denied)'-[Spec, QlfFile], nl,
886 '\tLoading QlfFile'-[]
887 ].
888prolog_message(redefine_module(Module, OldFile, File)) -->
889 [ 'Module "~q" already loaded from ~w.'-[Module, OldFile], nl,
890 'Wipe and reload from ~w? '-[File], flush
891 ].
892prolog_message(redefine_module_reply) -->
893 [ 'Please answer y(es), n(o) or a(bort)' ].
894prolog_message(reloaded_in_module(Absolute, OldContext, LM)) -->
895 [ '~w was previously loaded in module ~w'-[Absolute, OldContext], nl,
896 '\tnow it is reloaded into module ~w'-[LM] ].
897prolog_message(expected_layout(Expected, Pos)) -->
898 [ 'Layout data: expected ~w, found: ~p'-[Expected, Pos] ].
899
900defined_definition(Message, Spec) -->
901 { strip_module(user:Spec, M, Name/Arity),
902 functor(Head, Name, Arity),
903 predicate_property(M:Head, file(File)),
904 predicate_property(M:Head, line_count(Line))
905 },
906 !,
907 [ nl, '~w at '-[Message], url(File:Line) ].
908defined_definition(_, _) --> [].
909
910used_search([]) -->
911 [].
912used_search([Alias=Expanded|T]) -->
913 [ ' file_search_path(~p, ~p)'-[Alias, Expanded], nl ],
914 used_search(T).
915
916load_file(file(Spec, _Path)) -->
917 ( {atomic(Spec)}
918 -> [ '~w'-[Spec] ]
919 ; [ '~p'-[Spec] ]
920 ).
923
924load_module(user) --> !.
925load_module(system) --> !.
926load_module(Module) -->
927 [ ' into ~w'-[Module] ].
928
929goal_to_predicate_indicator(Goal, PI) :-
930 strip_module(Goal, Module, Head),
931 callable_name_arity(Head, Name, Arity),
932 user_predicate_indicator(Module:Name/Arity, PI).
933
934callable_name_arity(Goal, Name, Arity) :-
935 compound(Goal),
936 !,
937 compound_name_arity(Goal, Name, Arity).
938callable_name_arity(Goal, Goal, 0) :-
939 atom(Goal).
940
941user_predicate_indicator(Module:PI, PI) :-
942 hidden_module(Module),
943 !.
944user_predicate_indicator(PI, PI).
945
946hidden_module(user) :- !.
947hidden_module(system) :- !.
948hidden_module(M) :-
949 sub_atom(M, 0, _, _, $).
950
951current_definition(Proc, Prefix) -->
952 { pi_uhead(Proc, Head),
953 predicate_property(Head, file(File)),
954 predicate_property(Head, line_count(Line))
955 },
956 [ '~w'-[Prefix], url(File:Line), nl ].
957current_definition(_, _) --> [].
958
959pi_uhead(Module:Name/Arity, Module:Head) :-
960 !,
961 atom(Module), atom(Name), integer(Arity),
962 functor(Head, Name, Arity).
963pi_uhead(Name/Arity, user:Head) :-
964 atom(Name), integer(Arity),
965 functor(Head, Name, Arity).
966
967qlf_recompile_reason(old) -->
968 !,
969 [ ' (out of date)'-[] ].
970qlf_recompile_reason(_) -->
971 [ ' (incompatible with current Prolog version)'-[] ].
972
973prolog_message(file_search(cache(Spec, _Cond), Path)) -->
974 [ 'File search: ~p --> ~p (cache)'-[Spec, Path] ].
975prolog_message(file_search(found(Spec, Cond), Path)) -->
976 [ 'File search: ~p --> ~p OK ~p'-[Spec, Path, Cond] ].
977prolog_message(file_search(tried(Spec, Cond), Path)) -->
978 [ 'File search: ~p --> ~p NO ~p'-[Spec, Path, Cond] ].
979
980 983
984prolog_message(agc(start)) -->
985 thread_context,
986 [ 'AGC: ', flush ].
987prolog_message(agc(done(Collected, Remaining, Time))) -->
988 [ at_same_line,
989 'reclaimed ~D atoms in ~3f sec. (remaining: ~D)'-
990 [Collected, Time, Remaining]
991 ].
992prolog_message(cgc(start)) -->
993 thread_context,
994 [ 'CGC: ', flush ].
995prolog_message(cgc(done(CollectedClauses, _CollectedBytes,
996 RemainingBytes, Time))) -->
997 [ at_same_line,
998 'reclaimed ~D clauses in ~3f sec. (pending: ~D bytes)'-
999 [CollectedClauses, Time, RemainingBytes]
1000 ].
1001
1002 1005
1006out_of_stack(Context) -->
1007 { human_stack_size(Context.localused, Local),
1008 human_stack_size(Context.globalused, Global),
1009 human_stack_size(Context.trailused, Trail),
1010 human_stack_size(Context.stack_limit, Limit),
1011 LCO is (100*(Context.depth - Context.environments))/Context.depth
1012 },
1013 [ 'Stack limit (~s) exceeded'-[Limit], nl,
1014 ' Stack sizes: local: ~s, global: ~s, trail: ~s'-[Local,Global,Trail], nl,
1015 ' Stack depth: ~D, last-call: ~0f%, Choice points: ~D'-
1016 [Context.depth, LCO, Context.choicepoints], nl
1017 ],
1018 overflow_reason(Context, Resolve),
1019 resolve_overflow(Resolve).
1020
1021human_stack_size(Size, String) :-
1022 Size < 100,
1023 format(string(String), '~dKb', [Size]).
1024human_stack_size(Size, String) :-
1025 Size < 100 000,
1026 Value is Size / 1024,
1027 format(string(String), '~1fMb', [Value]).
1028human_stack_size(Size, String) :-
1029 Value is Size / (1024*1024),
1030 format(string(String), '~1fGb', [Value]).
1031
1032overflow_reason(Context, fix) -->
1033 show_non_termination(Context),
1034 !.
1035overflow_reason(Context, enlarge) -->
1036 { Stack = Context.get(stack) },
1037 !,
1038 [ ' In:'-[], nl ],
1039 stack(Stack).
1040overflow_reason(_Context, enlarge) -->
1041 [ ' Insufficient global stack'-[] ].
1042
1043show_non_termination(Context) -->
1044 ( { Stack = Context.get(cycle) }
1045 -> [ ' Probable infinite recursion (cycle):'-[], nl ]
1046 ; { Stack = Context.get(non_terminating) }
1047 -> [ ' Possible non-terminating recursion:'-[], nl ]
1048 ),
1049 stack(Stack).
1050
1051stack([]) --> [].
1052stack([frame(Depth, M:Goal, _)|T]) -->
1053 [ ' [~D] ~q:'-[Depth, M] ],
1054 stack_goal(Goal),
1055 [ nl ],
1056 stack(T).
1057
1058stack_goal(Goal) -->
1059 { compound(Goal),
1060 !,
1061 compound_name_arity(Goal, Name, Arity)
1062 },
1063 [ '~q('-[Name] ],
1064 stack_goal_args(1, Arity, Goal),
1065 [ ')'-[] ].
1066stack_goal(Goal) -->
1067 [ '~q'-[Goal] ].
1068
1069stack_goal_args(I, Arity, Goal) -->
1070 { I =< Arity,
1071 !,
1072 arg(I, Goal, A),
1073 I2 is I + 1
1074 },
1075 stack_goal_arg(A),
1076 ( { I2 =< Arity }
1077 -> [ ', '-[] ],
1078 stack_goal_args(I2, Arity, Goal)
1079 ; []
1080 ).
1081stack_goal_args(_, _, _) -->
1082 [].
1083
1084stack_goal_arg(A) -->
1085 { nonvar(A),
1086 A = [Len|T],
1087 !
1088 },
1089 ( {Len == cyclic_term}
1090 -> [ '[cyclic list]'-[] ]
1091 ; {T == []}
1092 -> [ '[length:~D]'-[Len] ]
1093 ; [ '[length:~D|~p]'-[Len, T] ]
1094 ).
1095stack_goal_arg(A) -->
1096 { nonvar(A),
1097 A = _/_,
1098 !
1099 },
1100 [ '<compound ~p>'-[A] ].
1101stack_goal_arg(A) -->
1102 [ '~p'-[A] ].
1103
1104resolve_overflow(fix) -->
1105 [].
1106resolve_overflow(enlarge) -->
1107 { current_prolog_flag(stack_limit, LimitBytes),
1108 NewLimit is LimitBytes * 2
1109 },
1110 [ nl,
1111 'Use the --stack_limit=size[KMG] command line option or'-[], nl,
1112 '?- set_prolog_flag(stack_limit, ~I). to double the limit.'-[NewLimit]
1113 ].
1114
1119
1120out_of_c_stack -->
1121 { statistics(c_stack, Limit), Limit > 0 },
1122 !,
1123 [ 'C-stack limit (~D bytes) exceeded.'-[Limit], nl ],
1124 resolve_c_stack_overflow(Limit).
1125out_of_c_stack -->
1126 { statistics(c_stack, Limit), Limit > 0 },
1127 [ 'C-stack limit exceeded.'-[Limit], nl ],
1128 resolve_c_stack_overflow(Limit).
1129
1130resolve_c_stack_overflow(_Limit) -->
1131 { thread_self(main) },
1132 [ 'Use the shell command ' ], code('~w', 'ulimit -s size'),
1133 [ ' to enlarge the limit.' ].
1134resolve_c_stack_overflow(_Limit) -->
1135 [ 'Use the ' ], code('~w', 'c_stack(KBytes)'),
1136 [ ' option of '], code(thread_create/3), [' to enlarge the limit.' ].
1137
1138
1139 1142
1143prolog_message(make(reload(Files))) -->
1144 { length(Files, N)
1145 },
1146 [ 'Make: reloading ~D files'-[N] ].
1147prolog_message(make(done(_Files))) -->
1148 [ 'Make: finished' ].
1149prolog_message(make(library_index(Dir))) -->
1150 [ 'Updating index for library ~w'-[Dir] ].
1151prolog_message(autoload(Pred, File)) -->
1152 thread_context,
1153 [ 'autoloading ~p from ~w'-[Pred, File] ].
1154prolog_message(autoload(read_index(Dir))) -->
1155 [ 'Loading autoload index for ~w'-[Dir] ].
1156prolog_message(autoload(disabled(Loaded))) -->
1157 [ 'Disabled autoloading (loaded ~D files)'-[Loaded] ].
1158prolog_message(autoload(already_defined(PI, From))) -->
1159 code(PI),
1160 ( { '$pi_head'(PI, Head),
1161 predicate_property(Head, built_in)
1162 }
1163 -> [' is a built-in predicate']
1164 ; [ ' is already imported from module ' ],
1165 code(From)
1166 ).
1167
1168swi_message(autoload(Msg)) -->
1169 [ nl, ' ' ],
1170 autoload_message(Msg).
1171
1172autoload_message(not_exported(PI, Spec, _FullFile, _Exports)) -->
1173 [ ansi(code, '~w', [Spec]),
1174 ' does not export ',
1175 ansi(code, '~p', [PI])
1176 ].
1177autoload_message(no_file(Spec)) -->
1178 [ ansi(code, '~p', [Spec]), ': No such file' ].
1179
1180
1181 1184
1187
1188prolog_message(compiler_warnings(Clause, Warnings0)) -->
1189 { print_goal_options(DefOptions),
1190 ( prolog_load_context(variable_names, VarNames)
1191 -> warnings_with_named_vars(Warnings0, VarNames, Warnings),
1192 Options = [variable_names(VarNames)|DefOptions]
1193 ; Options = DefOptions,
1194 Warnings = Warnings0
1195 )
1196 },
1197 compiler_warnings(Warnings, Clause, Options).
1198
1199warnings_with_named_vars([], _, []).
1200warnings_with_named_vars([H|T0], VarNames, [H|T]) :-
1201 term_variables(H, Vars),
1202 '$member'(V1, Vars),
1203 '$member'(_=V2, VarNames),
1204 V1 == V2,
1205 !,
1206 warnings_with_named_vars(T0, VarNames, T).
1207warnings_with_named_vars([_|T0], VarNames, T) :-
1208 warnings_with_named_vars(T0, VarNames, T).
1209
1210
1211compiler_warnings([], _, _) --> [].
1212compiler_warnings([H|T], Clause, Options) -->
1213 ( compiler_warning(H, Clause, Options)
1214 -> []
1215 ; [ 'Unknown compiler warning: ~W'-[H,Options] ]
1216 ),
1217 ( {T==[]}
1218 -> []
1219 ; [nl]
1220 ),
1221 compiler_warnings(T, Clause, Options).
1222
1223compiler_warning(eq_vv(A,B), _Clause, Options) -->
1224 ( { A == B }
1225 -> [ 'Test is always true: ~W'-[A==B, Options] ]
1226 ; [ 'Test is always false: ~W'-[A==B, Options] ]
1227 ).
1228compiler_warning(eq_singleton(A,B), _Clause, Options) -->
1229 [ 'Test is always false: ~W'-[A==B, Options] ].
1230compiler_warning(neq_vv(A,B), _Clause, Options) -->
1231 ( { A \== B }
1232 -> [ 'Test is always true: ~W'-[A\==B, Options] ]
1233 ; [ 'Test is always false: ~W'-[A\==B, Options] ]
1234 ).
1235compiler_warning(neq_singleton(A,B), _Clause, Options) -->
1236 [ 'Test is always true: ~W'-[A\==B, Options] ].
1237compiler_warning(unify_singleton(A,B), _Clause, Options) -->
1238 [ 'Unified variable is not used: ~W'-[A=B, Options] ].
1239compiler_warning(always(Bool, Pred, Arg), _Clause, Options) -->
1240 { Goal =.. [Pred,Arg] },
1241 [ 'Test is always ~w: ~W'-[Bool, Goal, Options] ].
1242compiler_warning(unbalanced_var(V), _Clause, Options) -->
1243 [ 'Variable not introduced in all branches: ~W'-[V, Options] ].
1244compiler_warning(branch_singleton(V), _Clause, Options) -->
1245 [ 'Singleton variable in branch: ~W'-[V, Options] ].
1246compiler_warning(negation_singleton(V), _Clause, Options) -->
1247 [ 'Singleton variable in \\+: ~W'-[V, Options] ].
1248compiler_warning(multiton(V), _Clause, Options) -->
1249 [ 'Singleton-marked variable appears more than once: ~W'-[V, Options] ].
1250
1251print_goal_options(
1252 [ quoted(true),
1253 portray(true)
1254 ]).
1255
1256
1257 1260
1261prolog_message(version) -->
1262 { current_prolog_flag(version_git, Version) },
1263 !,
1264 [ '~w'-[Version] ].
1265prolog_message(version) -->
1266 { current_prolog_flag(version_data, swi(Major,Minor,Patch,Options))
1267 },
1268 ( { memberchk(tag(Tag), Options) }
1269 -> [ '~w.~w.~w-~w'-[Major, Minor, Patch, Tag] ]
1270 ; [ '~w.~w.~w'-[Major, Minor, Patch] ]
1271 ).
1272prolog_message(address_bits) -->
1273 { current_prolog_flag(address_bits, Bits)
1274 },
1275 !,
1276 [ '~d bits, '-[Bits] ].
1277prolog_message(threads) -->
1278 { current_prolog_flag(threads, true)
1279 },
1280 !,
1281 [ 'threaded, ' ].
1282prolog_message(threads) -->
1283 [].
1284prolog_message(copyright) -->
1285 [ 'SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.', nl,
1286 'Please run ?- license. for legal details.'
1287 ].
1288prolog_message(documentaton) -->
1289 [ 'For online help and background, visit https://www.swi-prolog.org', nl,
1290 'For built-in help, use ?- help(Topic). or ?- apropos(Word).'
1291 ].
1292prolog_message(about) -->
1293 [ 'SWI-Prolog version (' ],
1294 prolog_message(threads),
1295 prolog_message(address_bits),
1296 ['version ' ],
1297 prolog_message(version),
1298 [ ')', nl ],
1299 prolog_message(copyright).
1300prolog_message(halt) -->
1301 [ 'halt' ].
1302prolog_message(break(begin, Level)) -->
1303 [ 'Break level ~d'-[Level] ].
1304prolog_message(break(end, Level)) -->
1305 [ 'Exit break level ~d'-[Level] ].
1306prolog_message(var_query(_)) -->
1307 [ '... 1,000,000 ............ 10,000,000 years later', nl, nl,
1308 '~t~8|>> 42 << (last release gives the question)'
1309 ].
1310prolog_message(close_on_abort(Stream)) -->
1311 [ 'Abort: closed stream ~p'-[Stream] ].
1312prolog_message(cancel_halt(Reason)) -->
1313 [ 'Halt cancelled: ~p'-[Reason] ].
1314prolog_message(on_error(halt(Status))) -->
1315 { statistics(errors, Errors),
1316 statistics(warnings, Warnings)
1317 },
1318 [ 'Halting with status ~w due to ~D errors and ~D warnings'-
1319 [Status, Errors, Warnings] ].
1320
1321prolog_message(query(QueryResult)) -->
1322 query_result(QueryResult).
1323
1324query_result(no) --> 1325 [ ansi(truth(false), 'false.', []) ],
1326 extra_line.
1327query_result(yes(true, [])) --> 1328 !,
1329 [ ansi(truth(true), 'true.', []) ],
1330 extra_line.
1331query_result(yes(Delays, Residuals)) -->
1332 result([], Delays, Residuals),
1333 extra_line.
1334query_result(done) --> 1335 extra_line.
1336query_result(yes(Bindings, Delays, Residuals)) -->
1337 result(Bindings, Delays, Residuals),
1338 prompt(yes, Bindings, Delays, Residuals).
1339query_result(more(Bindings, Delays, Residuals)) -->
1340 result(Bindings, Delays, Residuals),
1341 prompt(more, Bindings, Delays, Residuals).
1342query_result(help) -->
1343 [ ansi(bold, ' Possible actions:', []), nl,
1344 ' ; (n,r,space,TAB): redo | t: trace&redo'-[], nl,
1345 ' *: show choicepoint | c (a,RET): stop'-[], nl,
1346 ' w: write | p: print'-[], nl,
1347 ' +: max_depth*10 | -: max_depth//10'-[], nl,
1348 ' b: break | h (?): help'-[],
1349 nl, nl
1350 ].
1351query_result(action) -->
1352 [ 'Action? '-[], flush ].
1353query_result(confirm) -->
1354 [ 'Please answer \'y\' or \'n\'? '-[], flush ].
1355query_result(eof) -->
1356 [ nl ].
1357query_result(toplevel_open_line) -->
1358 [].
1359
1360prompt(Answer, [], true, []-[]) -->
1361 !,
1362 prompt(Answer, empty).
1363prompt(Answer, _, _, _) -->
1364 !,
1365 prompt(Answer, non_empty).
1366
1367prompt(yes, empty) -->
1368 !,
1369 [ ansi(truth(true), 'true.', []) ],
1370 extra_line.
1371prompt(yes, _) -->
1372 !,
1373 [ full_stop ],
1374 extra_line.
1375prompt(more, empty) -->
1376 !,
1377 [ ansi(truth(true), 'true ', []), flush ].
1378prompt(more, _) -->
1379 !,
1380 [ ' '-[], flush ].
1381
1382result(Bindings, Delays, Residuals) -->
1383 { current_prolog_flag(answer_write_options, Options0),
1384 Options = [partial(true)|Options0],
1385 GOptions = [priority(999)|Options0]
1386 },
1387 wfs_residual_program(Delays, GOptions),
1388 bindings(Bindings, [priority(699)|Options]),
1389 ( {Residuals == []-[]}
1390 -> bind_delays_sep(Bindings, Delays),
1391 delays(Delays, GOptions)
1392 ; bind_res_sep(Bindings, Residuals),
1393 residuals(Residuals, GOptions),
1394 ( {Delays == true}
1395 -> []
1396 ; [','-[], nl],
1397 delays(Delays, GOptions)
1398 )
1399 ).
1400
1401bindings([], _) -->
1402 [].
1403bindings([binding(Names,Skel,Subst)|T], Options) -->
1404 { '$last'(Names, Name) },
1405 var_names(Names), value(Name, Skel, Subst, Options),
1406 ( { T \== [] }
1407 -> [ ','-[], nl ],
1408 bindings(T, Options)
1409 ; []
1410 ).
1411
1412var_names([Name]) -->
1413 !,
1414 [ '~w = '-[Name] ].
1415var_names([Name1,Name2|T]) -->
1416 !,
1417 [ '~w = ~w, '-[Name1, Name2] ],
1418 var_names([Name2|T]).
1419
1420
1421value(Name, Skel, Subst, Options) -->
1422 ( { var(Skel), Subst = [Skel=S] }
1423 -> { Skel = '$VAR'(Name) },
1424 [ '~W'-[S, Options] ]
1425 ; [ '~W'-[Skel, Options] ],
1426 substitution(Subst, Options)
1427 ).
1428
1429substitution([], _) --> !.
1430substitution([N=V|T], Options) -->
1431 [ ', ', ansi(comment, '% where', []), nl,
1432 ' ~w = ~W'-[N,V,Options] ],
1433 substitutions(T, Options).
1434
1435substitutions([], _) --> [].
1436substitutions([N=V|T], Options) -->
1437 [ ','-[], nl, ' ~w = ~W'-[N,V,Options] ],
1438 substitutions(T, Options).
1439
1440
1441residuals(Normal-Hidden, Options) -->
1442 residuals1(Normal, Options),
1443 bind_res_sep(Normal, Hidden),
1444 ( {Hidden == []}
1445 -> []
1446 ; [ansi(comment, '% with pending residual goals', []), nl]
1447 ),
1448 residuals1(Hidden, Options).
1449
1450residuals1([], _) -->
1451 [].
1452residuals1([G|Gs], Options) -->
1453 ( { Gs \== [] }
1454 -> [ '~W,'-[G, Options], nl ],
1455 residuals1(Gs, Options)
1456 ; [ '~W'-[G, Options] ]
1457 ).
1458
1459wfs_residual_program(true, _Options) -->
1460 !.
1461wfs_residual_program(Goal, _Options) -->
1462 { current_prolog_flag(toplevel_list_wfs_residual_program, true),
1463 '$current_typein_module'(TypeIn),
1464 ( current_predicate(delays_residual_program/2)
1465 -> true
1466 ; use_module(library(wfs), [delays_residual_program/2])
1467 ),
1468 delays_residual_program(TypeIn:Goal, TypeIn:Program),
1469 Program \== []
1470 },
1471 !,
1472 [ ansi(comment, '% WFS residual program', []), nl ],
1473 [ ansi(wfs(residual_program), '~@', ['$messages':list_clauses(Program)]) ].
1474wfs_residual_program(_, _) --> [].
1475
1476delays(true, _Options) -->
1477 !.
1478delays(Goal, Options) -->
1479 { current_prolog_flag(toplevel_list_wfs_residual_program, true)
1480 },
1481 !,
1482 [ ansi(truth(undefined), '~W', [Goal, Options]) ].
1483delays(_, _Options) -->
1484 [ ansi(truth(undefined), undefined, []) ].
1485
1486:- public list_clauses/1. 1487
1488list_clauses([]).
1489list_clauses([H|T]) :-
1490 ( system_undefined(H)
1491 -> true
1492 ; portray_clause(user_output, H, [indent(4)])
1493 ),
1494 list_clauses(T).
1495
1496system_undefined((undefined :- tnot(undefined))).
1497system_undefined((answer_count_restraint :- tnot(answer_count_restraint))).
1498system_undefined((radial_restraint :- tnot(radial_restraint))).
1499
1500bind_res_sep(_, []) --> !.
1501bind_res_sep(_, []-[]) --> !.
1502bind_res_sep([], _) --> !.
1503bind_res_sep(_, _) --> [','-[], nl].
1504
1505bind_delays_sep([], _) --> !.
1506bind_delays_sep(_, true) --> !.
1507bind_delays_sep(_, _) --> [','-[], nl].
1508
-->
1510 { current_prolog_flag(toplevel_extra_white_line, true) },
1511 !,
1512 ['~N'-[]].
1513extra_line -->
1514 [].
1515
1516prolog_message(if_tty(Message)) -->
1517 ( {current_prolog_flag(tty_control, true)}
1518 -> [ at_same_line | Message ]
1519 ; []
1520 ).
1521prolog_message(halt(Reason)) -->
1522 [ '~w: halt'-[Reason] ].
1523prolog_message(no_action(Char)) -->
1524 [ 'Unknown action: ~c (h for help)'-[Char], nl ].
1525
1526prolog_message(history(help(Show, Help))) -->
1527 [ 'History Commands:', nl,
1528 ' !!. Repeat last query', nl,
1529 ' !nr. Repeat query numbered <nr>', nl,
1530 ' !str. Repeat last query starting with <str>', nl,
1531 ' !?str. Repeat last query holding <str>', nl,
1532 ' ^old^new. Substitute <old> into <new> of last query', nl,
1533 ' !nr^old^new. Substitute in query numbered <nr>', nl,
1534 ' !str^old^new. Substitute in query starting with <str>', nl,
1535 ' !?str^old^new. Substitute in query holding <str>', nl,
1536 ' ~w.~21|Show history list'-[Show], nl,
1537 ' ~w.~21|Show this list'-[Help], nl, nl
1538 ].
1539prolog_message(history(no_event)) -->
1540 [ '! No such event' ].
1541prolog_message(history(bad_substitution)) -->
1542 [ '! Bad substitution' ].
1543prolog_message(history(expanded(Event))) -->
1544 [ '~w.'-[Event] ].
1545prolog_message(history(history(Events))) -->
1546 history_events(Events).
1547
1548history_events([]) -->
1549 [].
1550history_events([Nr/Event|T]) -->
1551 [ '~t~w ~8|~W~W'-[ Nr,
1552 Event, [partial(true)],
1553 '.', [partial(true)]
1554 ],
1555 nl
1556 ],
1557 history_events(T).
1558
1559
1564
1565user_version_messages([]) --> [].
1566user_version_messages([H|T]) -->
1567 user_version_message(H),
1568 user_version_messages(T).
1569
1571
1572user_version_message(Term) -->
1573 translate_message(Term), !, [nl].
1574user_version_message(Atom) -->
1575 [ '~w'-[Atom], nl ].
1576
1577
1578 1581
1582prolog_message(spy(Head)) -->
1583 { goal_to_predicate_indicator(Head, Pred)
1584 },
1585 [ 'Spy point on ~p'-[Pred] ].
1586prolog_message(nospy(Head)) -->
1587 { goal_to_predicate_indicator(Head, Pred)
1588 },
1589 [ 'Spy point removed from ~p'-[Pred] ].
1590prolog_message(trace_mode(OnOff)) -->
1591 [ 'Trace mode switched to ~w'-[OnOff] ].
1592prolog_message(debug_mode(OnOff)) -->
1593 [ 'Debug mode switched to ~w'-[OnOff] ].
1594prolog_message(debugging(OnOff)) -->
1595 [ 'Debug mode is ~w'-[OnOff] ].
1596prolog_message(spying([])) -->
1597 !,
1598 [ 'No spy points' ].
1599prolog_message(spying(Heads)) -->
1600 [ 'Spy points (see spy/1) on:', nl ],
1601 predicate_list(Heads).
1602prolog_message(trace(Head, [])) -->
1603 !,
1604 [ ' ' ], goal_predicate(Head), [ ' Not tracing'-[], nl].
1605prolog_message(trace(Head, Ports)) -->
1606 { '$member'(Port, Ports), compound(Port),
1607 !,
1608 numbervars(Head+Ports, 0, _, [singletons(true)])
1609 },
1610 [ ' ~p: ~p'-[Head,Ports] ].
1611prolog_message(trace(Head, Ports)) -->
1612 [ ' ' ], goal_predicate(Head), [ ': ~w'-[Ports], nl].
1613prolog_message(tracing([])) -->
1614 !,
1615 [ 'No traced predicates (see trace/1,2)' ].
1616prolog_message(tracing(Heads)) -->
1617 [ 'Trace points (see trace/1,2) on:', nl ],
1618 tracing_list(Heads).
1619
1620goal_predicate(Head) -->
1621 { predicate_property(Head, file(File)),
1622 predicate_property(Head, line_count(Line)),
1623 goal_to_predicate_indicator(Head, PI),
1624 term_string(PI, PIS, [quoted(true)])
1625 },
1626 [ url(File:Line, PIS) ].
1627goal_predicate(Head) -->
1628 { goal_to_predicate_indicator(Head, PI)
1629 },
1630 [ '~p'-[PI] ].
1631
1632
1633predicate_list([]) --> 1634 [].
1635predicate_list([H|T]) -->
1636 [ ' ' ], goal_predicate(H), [nl],
1637 predicate_list(T).
1638
1639tracing_list([]) -->
1640 [].
1641tracing_list([trace(Head, Ports)|T]) -->
1642 translate_message(trace(Head, Ports)),
1643 tracing_list(T).
1644
1645prolog_message(frame(Frame, backtrace, _PC)) -->
1646 !,
1647 { prolog_frame_attribute(Frame, level, Level)
1648 },
1649 [ ansi(frame(level), '~t[~D] ~10|', [Level]) ],
1650 frame_context(Frame),
1651 frame_goal(Frame).
1652prolog_message(frame(Frame, choice, PC)) -->
1653 !,
1654 prolog_message(frame(Frame, backtrace, PC)).
1655prolog_message(frame(_, cut_call, _)) --> !, [].
1656prolog_message(frame(Goal, trace(Port))) -->
1657 !,
1658 thread_context,
1659 [ ' T ' ],
1660 port(Port),
1661 goal(Goal).
1662prolog_message(frame(Goal, trace(Port, Id))) -->
1663 !,
1664 thread_context,
1665 [ ' T ' ],
1666 port(Port, Id),
1667 goal(Goal).
1668prolog_message(frame(Frame, Port, _PC)) -->
1669 frame_flags(Frame),
1670 port(Port),
1671 frame_level(Frame),
1672 frame_context(Frame),
1673 frame_depth_limit(Port, Frame),
1674 frame_goal(Frame),
1675 [ flush ].
1676
1677frame_goal(Frame) -->
1678 { prolog_frame_attribute(Frame, goal, Goal)
1679 },
1680 goal(Goal).
1681
1682goal(Goal0) -->
1683 { clean_goal(Goal0, Goal),
1684 current_prolog_flag(debugger_write_options, Options)
1685 },
1686 [ '~W'-[Goal, Options] ].
1687
1688frame_level(Frame) -->
1689 { prolog_frame_attribute(Frame, level, Level)
1690 },
1691 [ '(~D) '-[Level] ].
1692
1693frame_context(Frame) -->
1694 ( { current_prolog_flag(debugger_show_context, true),
1695 prolog_frame_attribute(Frame, context_module, Context)
1696 }
1697 -> [ '[~w] '-[Context] ]
1698 ; []
1699 ).
1700
1701frame_depth_limit(fail, Frame) -->
1702 { prolog_frame_attribute(Frame, depth_limit_exceeded, true)
1703 },
1704 !,
1705 [ '[depth-limit exceeded] ' ].
1706frame_depth_limit(_, _) -->
1707 [].
1708
1709frame_flags(Frame) -->
1710 { prolog_frame_attribute(Frame, goal, Goal),
1711 ( predicate_property(Goal, transparent)
1712 -> T = '^'
1713 ; T = ' '
1714 ),
1715 ( predicate_property(Goal, spying)
1716 -> S = '*'
1717 ; S = ' '
1718 )
1719 },
1720 [ '~w~w '-[T, S] ].
1721
1723port(Port, Dict) -->
1724 { _{level:Level, start:Time} :< Dict
1725 },
1726 ( { Port \== call,
1727 get_time(Now),
1728 Passed is (Now - Time)*1000.0
1729 }
1730 -> [ '[~d +~1fms] '-[Level, Passed] ]
1731 ; [ '[~d] '-[Level] ]
1732 ),
1733 port(Port).
1734port(Port, _Id-Level) -->
1735 [ '[~d] '-[Level] ],
1736 port(Port).
1737
1738port(Port) -->
1739 { port_name(Port, Name)
1740 },
1741 !,
1742 [ ansi(port(Port), '~w: ', [Name]) ].
1743
1744port_name(call, 'Call').
1745port_name(exit, 'Exit').
1746port_name(fail, 'Fail').
1747port_name(redo, 'Redo').
1748port_name(unify, 'Unify').
1749port_name(exception, 'Exception').
1750
1751clean_goal(M:Goal, Goal) :-
1752 hidden_module(M),
1753 !.
1754clean_goal(M:Goal, Goal) :-
1755 predicate_property(M:Goal, built_in),
1756 !.
1757clean_goal(Goal, Goal).
1758
1759
1760 1763
1764prolog_message(compatibility(renamed(Old, New))) -->
1765 [ 'The predicate ~p has been renamed to ~p.'-[Old, New], nl,
1766 'Please update your sources for compatibility with future versions.'
1767 ].
1768
1769
1770 1773
1774prolog_message(abnormal_thread_completion(Goal, exception(Ex))) -->
1775 !,
1776 [ 'Thread running "~p" died on exception: '-[Goal] ],
1777 translate_message(Ex).
1778prolog_message(abnormal_thread_completion(Goal, fail)) -->
1779 [ 'Thread running "~p" died due to failure'-[Goal] ].
1780prolog_message(threads_not_died(Running)) -->
1781 [ 'The following threads wouldn\'t die: ~p'-[Running] ].
1782
1783
1784 1787
1788prolog_message(pack(attached(Pack, BaseDir))) -->
1789 [ 'Attached package ~w at ~q'-[Pack, BaseDir] ].
1790prolog_message(pack(duplicate(Entry, OldDir, Dir))) -->
1791 [ 'Package ~w already attached at ~q.'-[Entry,OldDir], nl,
1792 '\tIgnoring version from ~q'- [Dir]
1793 ].
1794prolog_message(pack(no_arch(Entry, Arch))) -->
1795 [ 'Package ~w: no binary for architecture ~w'-[Entry, Arch] ].
1796
1797 1800
1801prolog_message(null_byte_in_path(Component)) -->
1802 [ '0-byte in PATH component: ~p (skipped directory)'-[Component] ].
1803prolog_message(invalid_tmp_dir(Dir, Reason)) -->
1804 [ 'Cannot use ~p as temporary file directory: ~w'-[Dir, Reason] ].
1805prolog_message(ambiguous_stream_pair(Pair)) -->
1806 [ 'Ambiguous operation on stream pair ~p'-[Pair] ].
1807prolog_message(backcomp(init_file_moved(FoundFile))) -->
1808 { absolute_file_name(app_config('init.pl'), InitFile,
1809 [ file_errors(fail)
1810 ])
1811 },
1812 [ 'The location of the config file has moved'-[], nl,
1813 ' from "~w"'-[FoundFile], nl,
1814 ' to "~w"'-[InitFile], nl,
1815 ' See https://www.swi-prolog.org/modified/config-files.html'-[]
1816 ].
1817prolog_message(not_accessed_flags(List)) -->
1818 [ 'The following Prolog flags have been set but not used:', nl ],
1819 flags(List).
1820prolog_message(prolog_flag_invalid_preset(Flag, Preset, _Type, New)) -->
1821 [ 'Prolog flag ', ansi(code, '~q', Flag), ' has been (re-)created with a type that is \c
1822 incompatible with its value.', nl,
1823 'Value updated from ', ansi(code, '~p', [Preset]), ' to default (',
1824 ansi(code, '~p', [New]), ')'
1825 ].
1826
1827
1828flags([H|T]) -->
1829 [' ', ansi(code, '~q', [H])],
1830 ( {T == []}
1831 -> []
1832 ; [nl],
1833 flags(T)
1834 ).
1835
1836
1837 1840
1841deprecated(set_prolog_stack(_Stack,limit)) -->
1842 [ 'set_prolog_stack/2: limit(Size) sets the combined limit.'-[], nl,
1843 'See https://www.swi-prolog.org/changes/stack-limit.html'
1844 ].
1845deprecated(autoload(TargetModule, File, _M:PI, expansion)) -->
1846 !,
1847 [ 'Auto-loading ', ansi(code, '~p', [PI]), ' from ' ],
1848 load_file(File), [ ' into ' ],
1849 target_module(TargetModule),
1850 [ ' is deprecated due to term- or goal-expansion' ].
1851deprecated(source_search_working_directory(File, _FullFile)) -->
1852 [ 'Found file ', ansi(code, '~w', [File]),
1853 ' relative to the current working directory.', nl,
1854 'This behaviour is deprecated but still supported by', nl,
1855 'the Prolog flag ',
1856 ansi(code, source_search_working_directory, []), '.', nl
1857 ].
1858
1859load_file(File) -->
1860 { file_base_name(File, Base),
1861 absolute_file_name(library(Base), File, [access(read), file_errors(fail)]),
1862 file_name_extension(Clean, pl, Base)
1863 },
1864 !,
1865 [ ansi(code, '~p', [library(Clean)]) ].
1866load_file(File) -->
1867 [ url(File) ].
1868
1869target_module(Module) -->
1870 { module_property(Module, file(File)) },
1871 !,
1872 load_file(File).
1873target_module(Module) -->
1874 [ 'module ', ansi(code, '~p', [Module]) ].
1875
1876
1877
1878 1881
1882tripwire_message(max_integer_size, Bytes) -->
1883 !,
1884 [ 'Trapped tripwire max_integer_size: big integers and \c
1885 rationals are limited to ~D bytes'-[Bytes] ].
1886tripwire_message(Wire, Context) -->
1887 [ 'Trapped tripwire ~w for '-[Wire] ],
1888 tripwire_context(Wire, Context).
1889
1890tripwire_context(_, ATrie) -->
1891 { '$is_answer_trie'(ATrie, _),
1892 !,
1893 '$tabling':atrie_goal(ATrie, QGoal),
1894 user_predicate_indicator(QGoal, Goal)
1895 },
1896 [ '~p'-[Goal] ].
1897tripwire_context(_, Ctx) -->
1898 [ '~p'-[Ctx] ].
1899
1900
1901 1904
1905:- create_prolog_flag(message_language, default, []). 1906
1911
1912message_lang(Lang) :-
1913 current_message_lang(Lang0),
1914 ( Lang0 == en
1915 -> Lang = en
1916 ; sub_atom(Lang0, 0, _, _, en_)
1917 -> longest_id(Lang0, Lang)
1918 ; ( longest_id(Lang0, Lang)
1919 ; Lang = en
1920 )
1921 ).
1922
1923longest_id(Lang, Id) :-
1924 split_string(Lang, "_-", "", [H|Components]),
1925 longest_prefix(Components, Taken),
1926 atomic_list_concat([H|Taken], '_', Id).
1927
1928longest_prefix([H|T0], [H|T]) :-
1929 longest_prefix(T0, T).
1930longest_prefix(_, []).
1931
1935
1936current_message_lang(Lang) :-
1937 ( current_prolog_flag(message_language, Lang0),
1938 Lang0 \== default
1939 -> Lang = Lang0
1940 ; os_user_lang(Lang0)
1941 -> clean_encoding(Lang0, Lang1),
1942 set_prolog_flag(message_language, Lang1),
1943 Lang = Lang1
1944 ; Lang = en
1945 ).
1946
1947os_user_lang(Lang) :-
1948 current_prolog_flag(windows, true),
1949 win_get_user_preferred_ui_languages(name, [Lang|_]).
1950os_user_lang(Lang) :-
1951 catch(setlocale(messages, _, ''), _, fail),
1952 setlocale(messages, Lang, Lang).
1953os_user_lang(Lang) :-
1954 getenv('LANG', Lang).
1955
1956
1957clean_encoding(Lang0, Lang) :-
1958 ( sub_atom(Lang0, A, _, _, '.')
1959 -> sub_atom(Lang0, 0, A, _, Lang)
1960 ; Lang = Lang0
1961 ).
1962
1963 1966
1967code(Term) -->
1968 code('~p', Term).
1969
1970code(Format, Term) -->
1971 [ ansi(code, Format, [Term]) ].
1972
1973
1974 1977
1978:- public default_theme/2. 1979
1980default_theme(var, [fg(red)]).
1981default_theme(code, [fg(blue)]).
1982default_theme(comment, [fg(green)]).
1983default_theme(warning, [fg(red)]).
1984default_theme(error, [bold, fg(red)]).
1985default_theme(truth(false), [bold, fg(red)]).
1986default_theme(truth(true), [bold]).
1987default_theme(truth(undefined), [bold, fg(cyan)]).
1988default_theme(wfs(residual_program), [fg(cyan)]).
1989default_theme(frame(level), [bold]).
1990default_theme(port(call), [bold, fg(green)]).
1991default_theme(port(exit), [bold, fg(green)]).
1992default_theme(port(fail), [bold, fg(red)]).
1993default_theme(port(redo), [bold, fg(yellow)]).
1994default_theme(port(unify), [bold, fg(blue)]).
1995default_theme(port(exception), [bold, fg(magenta)]).
1996default_theme(message(informational), [fg(green)]).
1997default_theme(message(information), [fg(green)]).
1998default_theme(message(debug(_)), [fg(blue)]).
1999default_theme(message(Level), Attrs) :-
2000 nonvar(Level),
2001 default_theme(Level, Attrs).
2002
2003
2004 2007
2008:- multifile
2009 user:message_hook/3,
2010 prolog:message_prefix_hook/2. 2011:- dynamic
2012 user:message_hook/3,
2013 prolog:message_prefix_hook/2. 2014:- thread_local
2015 user:thread_message_hook/3. 2016:- '$notransact'((user:message_hook/3,
2017 prolog:message_prefix_hook/2,
2018 user:thread_message_hook/3)). 2019
2024
2025print_message(Level, _Term) :-
2026 msg_property(Level, stream(S)),
2027 stream_property(S, error(true)),
2028 !.
2029print_message(Level, Term) :-
2030 setup_call_cleanup(
2031 notrace(push_msg(Term, Stack)),
2032 ignore(print_message_guarded(Level, Term)),
2033 notrace(pop_msg(Stack))),
2034 !.
2035print_message(Level, Term) :-
2036 ( Level \== silent
2037 -> format(user_error, 'Recursive ~w message: ~q~n', [Level, Term]),
2038 backtrace(20)
2039 ; true
2040 ).
2041
2042push_msg(Term, Messages) :-
2043 nb_current('$inprint_message', Messages),
2044 !,
2045 \+ ( '$member'(Msg, Messages),
2046 Msg =@= Term
2047 ),
2048 Stack = [Term|Messages],
2049 b_setval('$inprint_message', Stack).
2050push_msg(Term, []) :-
2051 b_setval('$inprint_message', [Term]).
2052
2053pop_msg(Stack) :-
2054 nb_delete('$inprint_message'), 2055 b_setval('$inprint_message', Stack).
2056
2057print_message_guarded(Level, Term) :-
2058 ( must_print(Level, Term)
2059 -> ( translate_message(Term, Lines, [])
2060 -> ( nonvar(Term),
2061 ( notrace(user:thread_message_hook(Term, Level, Lines))
2062 -> true
2063 ; notrace(user:message_hook(Term, Level, Lines))
2064 )
2065 -> true
2066 ; '$inc_message_count'(Level),
2067 print_system_message(Term, Level, Lines),
2068 maybe_halt_on_error(Level)
2069 )
2070 )
2071 ; true
2072 ).
2073
2074maybe_halt_on_error(error) :-
2075 current_prolog_flag(on_error, halt),
2076 !,
2077 halt(1).
2078maybe_halt_on_error(warning) :-
2079 current_prolog_flag(on_warning, halt),
2080 !,
2081 halt(1).
2082maybe_halt_on_error(_).
2083
2084
2091
2092print_system_message(_, silent, _) :- !.
2093print_system_message(_, informational, _) :-
2094 current_prolog_flag(verbose, silent),
2095 !.
2096print_system_message(_, banner, _) :-
2097 current_prolog_flag(verbose, silent),
2098 !.
2099print_system_message(_, _, []) :- !.
2100print_system_message(Term, Kind, Lines) :-
2101 catch(flush_output(user_output), _, true), 2102 source_location(File, Line),
2103 Term \= error(syntax_error(_), _),
2104 msg_property(Kind, location_prefix(File:Line, LocPrefix, LinePrefix)),
2105 !,
2106 to_list(LocPrefix, LocPrefixL),
2107 insert_prefix(Lines, LinePrefix, Ctx, PrefixLines),
2108 '$append'([ [begin(Kind, Ctx)],
2109 LocPrefixL,
2110 [nl],
2111 PrefixLines,
2112 [end(Ctx)]
2113 ],
2114 AllLines),
2115 msg_property(Kind, stream(Stream)),
2116 ignore(stream_property(Stream, position(Pos))),
2117 print_message_lines(Stream, AllLines),
2118 ( \+ stream_property(Stream, position(Pos)),
2119 msg_property(Kind, wait(Wait)),
2120 Wait > 0
2121 -> sleep(Wait)
2122 ; true
2123 ).
2124print_system_message(_, Kind, Lines) :-
2125 msg_property(Kind, stream(Stream)),
2126 print_message_lines(Stream, kind(Kind), Lines).
2127
2128to_list(ListIn, List) :-
2129 is_list(ListIn),
2130 !,
2131 List = ListIn.
2132to_list(NonList, [NonList]).
2133
2134:- multifile
2135 user:message_property/2. 2136
2137msg_property(Kind, Property) :-
2138 notrace(user:message_property(Kind, Property)),
2139 !.
2140msg_property(Kind, prefix(Prefix)) :-
2141 msg_prefix(Kind, Prefix),
2142 !.
2143msg_property(_, prefix('~N')) :- !.
2144msg_property(query, stream(user_output)) :- !.
2145msg_property(_, stream(user_error)) :- !.
2146msg_property(error, tag('ERROR')).
2147msg_property(warning, tag('Warning')).
2148msg_property(Level,
2149 location_prefix(File:Line,
2150 ['~N~w: '-[Tag], url(File:Line), ':'],
2151 '~N~w: '-[Tag])) :-
2152 include_msg_location(Level),
2153 msg_property(Level, tag(Tag)).
2154msg_property(error, wait(0.1)) :- !.
2155
2156include_msg_location(warning).
2157include_msg_location(error).
2158
2159msg_prefix(debug(_), Prefix) :-
2160 msg_context('~N% ', Prefix).
2161msg_prefix(Level, Prefix) :-
2162 msg_property(Level, tag(Tag)),
2163 atomics_to_string(['~N', Tag, ': '], Prefix0),
2164 msg_context(Prefix0, Prefix).
2165msg_prefix(informational, '~N% ').
2166msg_prefix(information, '~N% ').
2167
2179
2180msg_context(Prefix0, Prefix) :-
2181 current_prolog_flag(message_context, Context),
2182 is_list(Context),
2183 !,
2184 add_message_context(Context, Prefix0, Prefix).
2185msg_context(Prefix, Prefix).
2186
2187add_message_context([], Prefix, Prefix).
2188add_message_context([H|T], Prefix0, Prefix) :-
2189 ( add_message_context1(H, Prefix0, Prefix1)
2190 -> true
2191 ; Prefix1 = Prefix0
2192 ),
2193 add_message_context(T, Prefix1, Prefix).
2194
2195add_message_context1(Context, Prefix0, Prefix) :-
2196 prolog:message_prefix_hook(Context, Extra),
2197 atomics_to_string([Prefix0, Extra, ' '], Prefix).
2198add_message_context1(time, Prefix0, Prefix) :-
2199 get_time(Now),
2200 format_time(string(S), '%T.%3f ', Now),
2201 string_concat(Prefix0, S, Prefix).
2202add_message_context1(time(Format), Prefix0, Prefix) :-
2203 get_time(Now),
2204 format_time(string(S), Format, Now),
2205 atomics_to_string([Prefix0, S, ' '], Prefix).
2206add_message_context1(thread, Prefix0, Prefix) :-
2207 thread_self(Id0),
2208 Id0 \== main,
2209 !,
2210 ( atom(Id0)
2211 -> Id = Id0
2212 ; thread_property(Id0, id(Id))
2213 ),
2214 format(string(Prefix), '~w[Thread ~w] ', [Prefix0, Id]).
2215
2220
2221print_message_lines(Stream, kind(Kind), Lines) :-
2222 !,
2223 msg_property(Kind, prefix(Prefix)),
2224 insert_prefix(Lines, Prefix, Ctx, PrefixLines),
2225 '$append'([ begin(Kind, Ctx)
2226 | PrefixLines
2227 ],
2228 [ end(Ctx)
2229 ],
2230 AllLines),
2231 print_message_lines(Stream, AllLines).
2232print_message_lines(Stream, Prefix, Lines) :-
2233 insert_prefix(Lines, Prefix, _, PrefixLines),
2234 print_message_lines(Stream, PrefixLines).
2235
2237
2238insert_prefix([at_same_line|Lines0], Prefix, Ctx, Lines) :-
2239 !,
2240 prefix_nl(Lines0, Prefix, Ctx, Lines).
2241insert_prefix(Lines0, Prefix, Ctx, [prefix(Prefix)|Lines]) :-
2242 prefix_nl(Lines0, Prefix, Ctx, Lines).
2243
2244prefix_nl([], _, _, [nl]).
2245prefix_nl([nl], _, _, [nl]) :- !.
2246prefix_nl([flush], _, _, [flush]) :- !.
2247prefix_nl([nl|T0], Prefix, Ctx, [nl, prefix(Prefix)|T]) :-
2248 !,
2249 prefix_nl(T0, Prefix, Ctx, T).
2250prefix_nl([ansi(Attrs,Fmt,Args)|T0], Prefix, Ctx,
2251 [ansi(Attrs,Fmt,Args,Ctx)|T]) :-
2252 !,
2253 prefix_nl(T0, Prefix, Ctx, T).
2254prefix_nl([H|T0], Prefix, Ctx, [H|T]) :-
2255 prefix_nl(T0, Prefix, Ctx, T).
2256
2258
2259print_message_lines(Stream, Lines) :-
2260 with_output_to(
2261 Stream,
2262 notrace(print_message_lines_guarded(current_output, Lines))).
2263
2264print_message_lines_guarded(_, []) :- !.
2265print_message_lines_guarded(S, [H|T]) :-
2266 line_element(S, H),
2267 print_message_lines_guarded(S, T).
2268
2269line_element(S, E) :-
2270 prolog:message_line_element(S, E),
2271 !.
2272line_element(S, full_stop) :-
2273 !,
2274 '$put_token'(S, '.'). 2275line_element(S, nl) :-
2276 !,
2277 nl(S).
2278line_element(S, prefix(Fmt-Args)) :-
2279 !,
2280 safe_format(S, Fmt, Args).
2281line_element(S, prefix(Fmt)) :-
2282 !,
2283 safe_format(S, Fmt, []).
2284line_element(S, flush) :-
2285 !,
2286 flush_output(S).
2287line_element(S, Fmt-Args) :-
2288 !,
2289 safe_format(S, Fmt, Args).
2290line_element(S, ansi(_, Fmt, Args)) :-
2291 !,
2292 safe_format(S, Fmt, Args).
2293line_element(S, ansi(_, Fmt, Args, _Ctx)) :-
2294 !,
2295 safe_format(S, Fmt, Args).
2296line_element(S, url(URL)) :-
2297 !,
2298 print_link(S, URL).
2299line_element(S, url(_URL, Fmt-Args)) :-
2300 !,
2301 safe_format(S, Fmt, Args).
2302line_element(S, url(_URL, Fmt)) :-
2303 !,
2304 safe_format(S, Fmt, []).
2305line_element(_, begin(_Level, _Ctx)) :- !.
2306line_element(_, end(_Ctx)) :- !.
2307line_element(S, Fmt) :-
2308 safe_format(S, Fmt, []).
2309
2310print_link(S, File:Line:Column) :-
2311 !,
2312 safe_format(S, '~w:~d:~d', [File, Line, Column]).
2313print_link(S, File:Line) :-
2314 !,
2315 safe_format(S, '~w:~d', [File, Line]).
2316print_link(S, File) :-
2317 safe_format(S, '~w', [File]).
2318
2320
2321safe_format(S, Fmt, Args) :-
2322 E = error(_,_),
2323 catch(format(S,Fmt,Args), E,
2324 format_failed(S,Fmt,Args,E)).
2325
2326format_failed(S, _Fmt, _Args, E) :-
2327 stream_property(S, error(true)),
2328 !,
2329 throw(E).
2330format_failed(S, Fmt, Args, error(E,_)) :-
2331 format(S, '~N [[ EXCEPTION while printing message ~q~n\c
2332 ~7|with arguments ~W:~n\c
2333 ~7|raised: ~W~n~4|]]~n',
2334 [ Fmt,
2335 Args, [quoted(true), max_depth(10)],
2336 E, [quoted(true), max_depth(10)]
2337 ]).
2338
2342
2343message_to_string(Term, Str) :-
2344 translate_message(Term, Actions, []),
2345 !,
2346 actions_to_format(Actions, Fmt, Args),
2347 format(string(Str), Fmt, Args).
2348
2349actions_to_format([], '', []) :- !.
2350actions_to_format([nl], '', []) :- !.
2351actions_to_format([Term, nl], Fmt, Args) :-
2352 !,
2353 actions_to_format([Term], Fmt, Args).
2354actions_to_format([nl|T], Fmt, Args) :-
2355 !,
2356 actions_to_format(T, Fmt0, Args),
2357 atom_concat('~n', Fmt0, Fmt).
2358actions_to_format([ansi(_Attrs, Fmt0, Args0)|Tail], Fmt, Args) :-
2359 !,
2360 actions_to_format(Tail, Fmt1, Args1),
2361 atom_concat(Fmt0, Fmt1, Fmt),
2362 append_args(Args0, Args1, Args).
2363actions_to_format([url(Pos)|Tail], Fmt, Args) :-
2364 !,
2365 actions_to_format(Tail, Fmt1, Args1),
2366 url_actions_to_format(url(Pos), Fmt1, Args1, Fmt, Args).
2367actions_to_format([url(URL, Label)|Tail], Fmt, Args) :-
2368 !,
2369 actions_to_format(Tail, Fmt1, Args1),
2370 url_actions_to_format(url(URL, Label), Fmt1, Args1, Fmt, Args).
2371actions_to_format([Fmt0-Args0|Tail], Fmt, Args) :-
2372 !,
2373 actions_to_format(Tail, Fmt1, Args1),
2374 atom_concat(Fmt0, Fmt1, Fmt),
2375 append_args(Args0, Args1, Args).
2376actions_to_format([Skip|T], Fmt, Args) :-
2377 action_skip(Skip),
2378 !,
2379 actions_to_format(T, Fmt, Args).
2380actions_to_format([Term|Tail], Fmt, Args) :-
2381 atomic(Term),
2382 !,
2383 actions_to_format(Tail, Fmt1, Args),
2384 atom_concat(Term, Fmt1, Fmt).
2385actions_to_format([Term|Tail], Fmt, Args) :-
2386 actions_to_format(Tail, Fmt1, Args1),
2387 atom_concat('~w', Fmt1, Fmt),
2388 append_args([Term], Args1, Args).
2389
2390action_skip(at_same_line).
2391action_skip(flush).
2392action_skip(begin(_Level, _Ctx)).
2393action_skip(end(_Ctx)).
2394
2395url_actions_to_format(url(File:Line:Column), Fmt1, Args1, Fmt, Args) :-
2396 !,
2397 atom_concat('~w:~d:~d', Fmt1, Fmt),
2398 append_args([File,Line,Column], Args1, Args).
2399url_actions_to_format(url(File:Line), Fmt1, Args1, Fmt, Args) :-
2400 !,
2401 atom_concat('~w:~d', Fmt1, Fmt),
2402 append_args([File,Line], Args1, Args).
2403url_actions_to_format(url(File), Fmt1, Args1, Fmt, Args) :-
2404 !,
2405 atom_concat('~w', Fmt1, Fmt),
2406 append_args([File], Args1, Args).
2407url_actions_to_format(url(_URL, Label), Fmt1, Args1, Fmt, Args) :-
2408 !,
2409 atom_concat('~w', Fmt1, Fmt),
2410 append_args([Label], Args1, Args).
2411
2412
2413append_args(M:Args0, Args1, M:Args) :-
2414 !,
2415 strip_module(Args1, _, A1),
2416 to_list(Args0, Args01),
2417 '$append'(Args01, A1, Args).
2418append_args(Args0, Args1, Args) :-
2419 strip_module(Args1, _, A1),
2420 to_list(Args0, Args01),
2421 '$append'(Args01, A1, Args).
2422
2423 2426
2427:- dynamic
2428 printed/2. 2429
2433
2434print_once(compatibility(_), _).
2435print_once(null_byte_in_path(_), _).
2436print_once(deprecated(_), _).
2437
2441
2442must_print(Level, Message) :-
2443 nonvar(Message),
2444 print_once(Message, Level),
2445 !,
2446 \+ printed(Message, Level),
2447 assert(printed(Message, Level)).
2448must_print(_, _)