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
666:- dynamic prolog:version_msg/1. 667:- multifile prolog:version_msg/1. 668
669prolog_message(welcome) -->
670 [ 'Welcome to SWI-Prolog (' ],
671 prolog_message(threads),
672 prolog_message(address_bits),
673 ['version ' ],
674 prolog_message(version),
675 [ ')', nl ],
676 prolog_message(copyright),
677 [ nl ],
678 translate_message(user_versions),
679 [ nl ],
680 prolog_message(documentaton),
681 [ nl, nl ].
682prolog_message(user_versions) -->
683 ( { findall(Msg, prolog:version_msg(Msg), Msgs),
684 Msgs \== []
685 }
686 -> [nl],
687 user_version_messages(Msgs)
688 ; []
689 ).
690prolog_message(deprecated(Term)) -->
691 { nonvar(Term) },
692 ( { message_lang(Lang) },
693 prolog:deprecated(Lang, Term)
694 -> []
695 ; prolog:deprecated(Term)
696 -> []
697 ; deprecated(Term)
698 ).
699prolog_message(unhandled_exception(E)) -->
700 { nonvar(E) },
701 [ 'Unhandled exception: ' ],
702 ( translate_message(E)
703 -> []
704 ; [ '~p'-[E] ]
705 ).
706
708
709prolog_message(initialization_error(_, E, File:Line)) -->
710 !,
711 [ url(File:Line),
712 ': Initialization goal raised exception:', nl
713 ],
714 translate_message(E).
715prolog_message(initialization_error(Goal, E, _)) -->
716 [ 'Initialization goal ~p raised exception:'-[Goal], nl ],
717 translate_message(E).
718prolog_message(initialization_failure(_Goal, File:Line)) -->
719 !,
720 [ url(File:Line),
721 ': Initialization goal failed'-[]
722 ].
723prolog_message(initialization_failure(Goal, _)) -->
724 [ 'Initialization goal failed: ~p'-[Goal]
725 ].
726prolog_message(initialization_exception(E)) -->
727 [ 'Prolog initialisation failed:', nl ],
728 translate_message(E).
729prolog_message(init_goal_syntax(Error, Text)) -->
730 !,
731 [ '-g ~w: '-[Text] ],
732 translate_message(Error).
733prolog_message(init_goal_failed(failed, @(Goal,File:Line))) -->
734 !,
735 [ url(File:Line), ': ~p: false'-[Goal] ].
736prolog_message(init_goal_failed(Error, @(Goal,File:Line))) -->
737 !,
738 [ url(File:Line), ': ~p '-[Goal] ],
739 translate_message(Error).
740prolog_message(init_goal_failed(failed, Text)) -->
741 !,
742 [ '-g ~w: false'-[Text] ].
743prolog_message(init_goal_failed(Error, Text)) -->
744 !,
745 [ '-g ~w: '-[Text] ],
746 translate_message(Error).
747prolog_message(goal_failed(Context, Goal)) -->
748 [ 'Goal (~w) failed: ~p'-[Context, Goal] ].
749prolog_message(no_current_module(Module)) -->
750 [ '~w is not a current module (created)'-[Module] ].
751prolog_message(commandline_arg_type(Flag, Arg)) -->
752 [ 'Bad argument to commandline option -~w: ~w'-[Flag, Arg] ].
753prolog_message(missing_feature(Name)) -->
754 [ 'This version of SWI-Prolog does not support ~w'-[Name] ].
755prolog_message(singletons(_Term, List)) -->
756 [ 'Singleton variables: ~w'-[List] ].
757prolog_message(multitons(_Term, List)) -->
758 [ 'Singleton-marked variables appearing more than once: ~w'-[List] ].
759prolog_message(profile_no_cpu_time) -->
760 [ 'No CPU-time info. Check the SWI-Prolog manual for details' ].
761prolog_message(non_ascii(Text, Type)) -->
762 [ 'Unquoted ~w with non-portable characters: ~w'-[Type, Text] ].
763prolog_message(io_warning(Stream, Message)) -->
764 { stream_property(Stream, position(Position)),
765 !,
766 stream_position_data(line_count, Position, LineNo),
767 stream_position_data(line_position, Position, LinePos),
768 ( stream_property(Stream, file_name(File))
769 -> Obj = File
770 ; Obj = Stream
771 )
772 },
773 [ '~p:~d:~d: ~w'-[Obj, LineNo, LinePos, Message] ].
774prolog_message(io_warning(Stream, Message)) -->
775 [ 'stream ~p: ~w'-[Stream, Message] ].
776prolog_message(option_usage(pldoc)) -->
777 [ 'Usage: --pldoc[=port]' ].
778prolog_message(interrupt(begin)) -->
779 [ 'Action (h for help) ? ', flush ].
780prolog_message(interrupt(end)) -->
781 [ 'continue' ].
782prolog_message(interrupt(trace)) -->
783 [ 'continue (trace mode)' ].
784prolog_message(unknown_in_module_user) -->
785 [ 'Using a non-error value for unknown in the global module', nl,
786 'causes most of the development environment to stop working.', nl,
787 'Please use :- dynamic or limit usage of unknown to a module.', nl,
788 'See https://www.swi-prolog.org/howto/database.html'
789 ].
790prolog_message(untable(PI)) -->
791 [ 'Reconsult: removed tabling for ~p'-[PI] ].
792prolog_message(unknown_option(Set, Opt)) -->
793 [ 'Unknown ~w option: ~p'-[Set, Opt] ].
794
795
796 799
800prolog_message(modify_active_procedure(Who, What)) -->
801 [ '~p: modified active procedure ~p'-[Who, What] ].
802prolog_message(load_file(failed(user:File))) -->
803 [ 'Failed to load ~p'-[File] ].
804prolog_message(load_file(failed(Module:File))) -->
805 [ 'Failed to load ~p into module ~p'-[File, Module] ].
806prolog_message(load_file(failed(File))) -->
807 [ 'Failed to load ~p'-[File] ].
808prolog_message(mixed_directive(Goal)) -->
809 [ 'Cannot pre-compile mixed load/call directive: ~p'-[Goal] ].
810prolog_message(cannot_redefine_comma) -->
811 [ 'Full stop in clause-body? Cannot redefine ,/2' ].
812prolog_message(illegal_autoload_index(Dir, Term)) -->
813 [ 'Illegal term in INDEX file of directory ~w: ~w'-[Dir, Term] ].
814prolog_message(redefined_procedure(Type, Proc)) -->
815 [ 'Redefined ~w procedure ~p'-[Type, Proc] ],
816 defined_definition('Previously defined', Proc).
817prolog_message(declare_module(Module, abolish(Predicates))) -->
818 [ 'Loading module ~w abolished: ~p'-[Module, Predicates] ].
819prolog_message(import_private(Module, Private)) -->
820 [ 'import/1: ~p is not exported (still imported into ~q)'-
821 [Private, Module]
822 ].
823prolog_message(ignored_weak_import(Into, From:PI)) -->
824 [ 'Local definition of ~p overrides weak import from ~q'-
825 [Into:PI, From]
826 ].
827prolog_message(undefined_export(Module, PI)) -->
828 [ 'Exported procedure ~q:~q is not defined'-[Module, PI] ].
829prolog_message(no_exported_op(Module, Op)) -->
830 [ 'Operator ~q:~q is not exported (still defined)'-[Module, Op] ].
831prolog_message(discontiguous((-)/2,_)) -->
832 prolog_message(minus_in_identifier).
833prolog_message(discontiguous(Proc,Current)) -->
834 [ 'Clauses of ', ansi(code, '~p', [Proc]),
835 ' are not together in the source-file', nl ],
836 current_definition(Proc, 'Earlier definition at '),
837 [ 'Current predicate: ', ansi(code, '~p', [Current]), nl,
838 'Use ', ansi(code, ':- discontiguous ~p.', [Proc]),
839 ' to suppress this message'
840 ].
841prolog_message(decl_no_effect(Goal)) -->
842 [ 'Deprecated declaration has no effect: ~p'-[Goal] ].
843prolog_message(load_file(start(Level, File))) -->
844 [ '~|~t~*+Loading '-[Level] ],
845 load_file(File),
846 [ ' ...' ].
847prolog_message(include_file(start(Level, File))) -->
848 [ '~|~t~*+include '-[Level] ],
849 load_file(File),
850 [ ' ...' ].
851prolog_message(include_file(done(Level, File))) -->
852 [ '~|~t~*+included '-[Level] ],
853 load_file(File).
854prolog_message(load_file(done(Level, File, Action, Module, Time, Clauses))) -->
855 [ '~|~t~*+'-[Level] ],
856 load_file(File),
857 [ ' ~w'-[Action] ],
858 load_module(Module),
859 [ ' ~2f sec, ~D clauses'-[Time, Clauses] ].
860prolog_message(dwim_undefined(Goal, Alternatives)) -->
861 { goal_to_predicate_indicator(Goal, Pred)
862 },
863 [ 'Unknown procedure: ~q'-[Pred], nl,
864 ' However, there are definitions for:', nl
865 ],
866 dwim_message(Alternatives).
867prolog_message(dwim_correct(Into)) -->
868 [ 'Correct to: ~q? '-[Into], flush ].
869prolog_message(error(loop_error(Spec), file_search(Used))) -->
870 [ 'File search: too many levels of indirections on: ~p'-[Spec], nl,
871 ' Used alias expansions:', nl
872 ],
873 used_search(Used).
874prolog_message(minus_in_identifier) -->
875 [ 'The "-" character should not be used to separate words in an', nl,
876 'identifier. Check the SWI-Prolog FAQ for details.'
877 ].
878prolog_message(qlf(removed_after_error(File))) -->
879 [ 'Removed incomplete QLF file ~w'-[File] ].
880prolog_message(qlf(recompile(Spec,_Pl,_Qlf,Reason))) -->
881 [ '~p: recompiling QLF file'-[Spec] ],
882 qlf_recompile_reason(Reason).
883prolog_message(qlf(can_not_recompile(Spec,QlfFile,_Reason))) -->
884 [ '~p: can not recompile "~w" (access denied)'-[Spec, QlfFile], nl,
885 '\tLoading from source'-[]
886 ].
887prolog_message(qlf(system_lib_out_of_date(Spec,QlfFile))) -->
888 [ '~p: can not recompile "~w" (access denied)'-[Spec, QlfFile], nl,
889 '\tLoading QlfFile'-[]
890 ].
891prolog_message(redefine_module(Module, OldFile, File)) -->
892 [ 'Module "~q" already loaded from ~w.'-[Module, OldFile], nl,
893 'Wipe and reload from ~w? '-[File], flush
894 ].
895prolog_message(redefine_module_reply) -->
896 [ 'Please answer y(es), n(o) or a(bort)' ].
897prolog_message(reloaded_in_module(Absolute, OldContext, LM)) -->
898 [ '~w was previously loaded in module ~w'-[Absolute, OldContext], nl,
899 '\tnow it is reloaded into module ~w'-[LM] ].
900prolog_message(expected_layout(Expected, Pos)) -->
901 [ 'Layout data: expected ~w, found: ~p'-[Expected, Pos] ].
902
903defined_definition(Message, Spec) -->
904 { strip_module(user:Spec, M, Name/Arity),
905 functor(Head, Name, Arity),
906 predicate_property(M:Head, file(File)),
907 predicate_property(M:Head, line_count(Line))
908 },
909 !,
910 [ nl, '~w at '-[Message], url(File:Line) ].
911defined_definition(_, _) --> [].
912
913used_search([]) -->
914 [].
915used_search([Alias=Expanded|T]) -->
916 [ ' file_search_path(~p, ~p)'-[Alias, Expanded], nl ],
917 used_search(T).
918
919load_file(file(Spec, _Path)) -->
920 ( {atomic(Spec)}
921 -> [ '~w'-[Spec] ]
922 ; [ '~p'-[Spec] ]
923 ).
926
927load_module(user) --> !.
928load_module(system) --> !.
929load_module(Module) -->
930 [ ' into ~w'-[Module] ].
931
932goal_to_predicate_indicator(Goal, PI) :-
933 strip_module(Goal, Module, Head),
934 callable_name_arity(Head, Name, Arity),
935 user_predicate_indicator(Module:Name/Arity, PI).
936
937callable_name_arity(Goal, Name, Arity) :-
938 compound(Goal),
939 !,
940 compound_name_arity(Goal, Name, Arity).
941callable_name_arity(Goal, Goal, 0) :-
942 atom(Goal).
943
944user_predicate_indicator(Module:PI, PI) :-
945 hidden_module(Module),
946 !.
947user_predicate_indicator(PI, PI).
948
949hidden_module(user) :- !.
950hidden_module(system) :- !.
951hidden_module(M) :-
952 sub_atom(M, 0, _, _, $).
953
954current_definition(Proc, Prefix) -->
955 { pi_uhead(Proc, Head),
956 predicate_property(Head, file(File)),
957 predicate_property(Head, line_count(Line))
958 },
959 [ '~w'-[Prefix], url(File:Line), nl ].
960current_definition(_, _) --> [].
961
962pi_uhead(Module:Name/Arity, Module:Head) :-
963 !,
964 atom(Module), atom(Name), integer(Arity),
965 functor(Head, Name, Arity).
966pi_uhead(Name/Arity, user:Head) :-
967 atom(Name), integer(Arity),
968 functor(Head, Name, Arity).
969
970qlf_recompile_reason(old) -->
971 !,
972 [ ' (out of date)'-[] ].
973qlf_recompile_reason(_) -->
974 [ ' (incompatible with current Prolog version)'-[] ].
975
976prolog_message(file_search(cache(Spec, _Cond), Path)) -->
977 [ 'File search: ~p --> ~p (cache)'-[Spec, Path] ].
978prolog_message(file_search(found(Spec, Cond), Path)) -->
979 [ 'File search: ~p --> ~p OK ~p'-[Spec, Path, Cond] ].
980prolog_message(file_search(tried(Spec, Cond), Path)) -->
981 [ 'File search: ~p --> ~p NO ~p'-[Spec, Path, Cond] ].
982
983 986
987prolog_message(agc(start)) -->
988 thread_context,
989 [ 'AGC: ', flush ].
990prolog_message(agc(done(Collected, Remaining, Time))) -->
991 [ at_same_line,
992 'reclaimed ~D atoms in ~3f sec. (remaining: ~D)'-
993 [Collected, Time, Remaining]
994 ].
995prolog_message(cgc(start)) -->
996 thread_context,
997 [ 'CGC: ', flush ].
998prolog_message(cgc(done(CollectedClauses, _CollectedBytes,
999 RemainingBytes, Time))) -->
1000 [ at_same_line,
1001 'reclaimed ~D clauses in ~3f sec. (pending: ~D bytes)'-
1002 [CollectedClauses, Time, RemainingBytes]
1003 ].
1004
1005 1008
1009out_of_stack(Context) -->
1010 { human_stack_size(Context.localused, Local),
1011 human_stack_size(Context.globalused, Global),
1012 human_stack_size(Context.trailused, Trail),
1013 human_stack_size(Context.stack_limit, Limit),
1014 LCO is (100*(Context.depth - Context.environments))/Context.depth
1015 },
1016 [ 'Stack limit (~s) exceeded'-[Limit], nl,
1017 ' Stack sizes: local: ~s, global: ~s, trail: ~s'-[Local,Global,Trail], nl,
1018 ' Stack depth: ~D, last-call: ~0f%, Choice points: ~D'-
1019 [Context.depth, LCO, Context.choicepoints], nl
1020 ],
1021 overflow_reason(Context, Resolve),
1022 resolve_overflow(Resolve).
1023
1024human_stack_size(Size, String) :-
1025 Size < 100,
1026 format(string(String), '~dKb', [Size]).
1027human_stack_size(Size, String) :-
1028 Size < 100 000,
1029 Value is Size / 1024,
1030 format(string(String), '~1fMb', [Value]).
1031human_stack_size(Size, String) :-
1032 Value is Size / (1024*1024),
1033 format(string(String), '~1fGb', [Value]).
1034
1035overflow_reason(Context, fix) -->
1036 show_non_termination(Context),
1037 !.
1038overflow_reason(Context, enlarge) -->
1039 { Stack = Context.get(stack) },
1040 !,
1041 [ ' In:'-[], nl ],
1042 stack(Stack).
1043overflow_reason(_Context, enlarge) -->
1044 [ ' Insufficient global stack'-[] ].
1045
1046show_non_termination(Context) -->
1047 ( { Stack = Context.get(cycle) }
1048 -> [ ' Probable infinite recursion (cycle):'-[], nl ]
1049 ; { Stack = Context.get(non_terminating) }
1050 -> [ ' Possible non-terminating recursion:'-[], nl ]
1051 ),
1052 stack(Stack).
1053
1054stack([]) --> [].
1055stack([frame(Depth, M:Goal, _)|T]) -->
1056 [ ' [~D] ~q:'-[Depth, M] ],
1057 stack_goal(Goal),
1058 [ nl ],
1059 stack(T).
1060
1061stack_goal(Goal) -->
1062 { compound(Goal),
1063 !,
1064 compound_name_arity(Goal, Name, Arity)
1065 },
1066 [ '~q('-[Name] ],
1067 stack_goal_args(1, Arity, Goal),
1068 [ ')'-[] ].
1069stack_goal(Goal) -->
1070 [ '~q'-[Goal] ].
1071
1072stack_goal_args(I, Arity, Goal) -->
1073 { I =< Arity,
1074 !,
1075 arg(I, Goal, A),
1076 I2 is I + 1
1077 },
1078 stack_goal_arg(A),
1079 ( { I2 =< Arity }
1080 -> [ ', '-[] ],
1081 stack_goal_args(I2, Arity, Goal)
1082 ; []
1083 ).
1084stack_goal_args(_, _, _) -->
1085 [].
1086
1087stack_goal_arg(A) -->
1088 { nonvar(A),
1089 A = [Len|T],
1090 !
1091 },
1092 ( {Len == cyclic_term}
1093 -> [ '[cyclic list]'-[] ]
1094 ; {T == []}
1095 -> [ '[length:~D]'-[Len] ]
1096 ; [ '[length:~D|~p]'-[Len, T] ]
1097 ).
1098stack_goal_arg(A) -->
1099 { nonvar(A),
1100 A = _/_,
1101 !
1102 },
1103 [ '<compound ~p>'-[A] ].
1104stack_goal_arg(A) -->
1105 [ '~p'-[A] ].
1106
1107resolve_overflow(fix) -->
1108 [].
1109resolve_overflow(enlarge) -->
1110 { current_prolog_flag(stack_limit, LimitBytes),
1111 NewLimit is LimitBytes * 2
1112 },
1113 [ nl,
1114 'Use the --stack_limit=size[KMG] command line option or'-[], nl,
1115 '?- set_prolog_flag(stack_limit, ~I). to double the limit.'-[NewLimit]
1116 ].
1117
1122
1123out_of_c_stack -->
1124 { statistics(c_stack, Limit), Limit > 0 },
1125 !,
1126 [ 'C-stack limit (~D bytes) exceeded.'-[Limit], nl ],
1127 resolve_c_stack_overflow(Limit).
1128out_of_c_stack -->
1129 { statistics(c_stack, Limit), Limit > 0 },
1130 [ 'C-stack limit exceeded.'-[Limit], nl ],
1131 resolve_c_stack_overflow(Limit).
1132
1133resolve_c_stack_overflow(_Limit) -->
1134 { thread_self(main) },
1135 [ 'Use the shell command ' ], code('~w', 'ulimit -s size'),
1136 [ ' to enlarge the limit.' ].
1137resolve_c_stack_overflow(_Limit) -->
1138 [ 'Use the ' ], code('~w', 'c_stack(KBytes)'),
1139 [ ' option of '], code(thread_create/3), [' to enlarge the limit.' ].
1140
1141
1142 1145
1146prolog_message(make(reload(Files))) -->
1147 { length(Files, N)
1148 },
1149 [ 'Make: reloading ~D files'-[N] ].
1150prolog_message(make(done(_Files))) -->
1151 [ 'Make: finished' ].
1152prolog_message(make(library_index(Dir))) -->
1153 [ 'Updating index for library ~w'-[Dir] ].
1154prolog_message(autoload(Pred, File)) -->
1155 thread_context,
1156 [ 'autoloading ~p from ~w'-[Pred, File] ].
1157prolog_message(autoload(read_index(Dir))) -->
1158 [ 'Loading autoload index for ~w'-[Dir] ].
1159prolog_message(autoload(disabled(Loaded))) -->
1160 [ 'Disabled autoloading (loaded ~D files)'-[Loaded] ].
1161prolog_message(autoload(already_defined(PI, From))) -->
1162 code(PI),
1163 ( { '$pi_head'(PI, Head),
1164 predicate_property(Head, built_in)
1165 }
1166 -> [' is a built-in predicate']
1167 ; [ ' is already imported from module ' ],
1168 code(From)
1169 ).
1170
1171swi_message(autoload(Msg)) -->
1172 [ nl, ' ' ],
1173 autoload_message(Msg).
1174
1175autoload_message(not_exported(PI, Spec, _FullFile, _Exports)) -->
1176 [ ansi(code, '~w', [Spec]),
1177 ' does not export ',
1178 ansi(code, '~p', [PI])
1179 ].
1180autoload_message(no_file(Spec)) -->
1181 [ ansi(code, '~p', [Spec]), ': No such file' ].
1182
1183
1184 1187
1190
1191prolog_message(compiler_warnings(Clause, Warnings0)) -->
1192 { print_goal_options(DefOptions),
1193 ( prolog_load_context(variable_names, VarNames)
1194 -> warnings_with_named_vars(Warnings0, VarNames, Warnings),
1195 Options = [variable_names(VarNames)|DefOptions]
1196 ; Options = DefOptions,
1197 Warnings = Warnings0
1198 )
1199 },
1200 compiler_warnings(Warnings, Clause, Options).
1201
1202warnings_with_named_vars([], _, []).
1203warnings_with_named_vars([H|T0], VarNames, [H|T]) :-
1204 term_variables(H, Vars),
1205 '$member'(V1, Vars),
1206 '$member'(_=V2, VarNames),
1207 V1 == V2,
1208 !,
1209 warnings_with_named_vars(T0, VarNames, T).
1210warnings_with_named_vars([_|T0], VarNames, T) :-
1211 warnings_with_named_vars(T0, VarNames, T).
1212
1213
1214compiler_warnings([], _, _) --> [].
1215compiler_warnings([H|T], Clause, Options) -->
1216 ( compiler_warning(H, Clause, Options)
1217 -> []
1218 ; [ 'Unknown compiler warning: ~W'-[H,Options] ]
1219 ),
1220 ( {T==[]}
1221 -> []
1222 ; [nl]
1223 ),
1224 compiler_warnings(T, Clause, Options).
1225
1226compiler_warning(eq_vv(A,B), _Clause, Options) -->
1227 ( { A == B }
1228 -> [ 'Test is always true: ~W'-[A==B, Options] ]
1229 ; [ 'Test is always false: ~W'-[A==B, Options] ]
1230 ).
1231compiler_warning(eq_singleton(A,B), _Clause, Options) -->
1232 [ 'Test is always false: ~W'-[A==B, Options] ].
1233compiler_warning(neq_vv(A,B), _Clause, Options) -->
1234 ( { A \== B }
1235 -> [ 'Test is always true: ~W'-[A\==B, Options] ]
1236 ; [ 'Test is always false: ~W'-[A\==B, Options] ]
1237 ).
1238compiler_warning(neq_singleton(A,B), _Clause, Options) -->
1239 [ 'Test is always true: ~W'-[A\==B, Options] ].
1240compiler_warning(unify_singleton(A,B), _Clause, Options) -->
1241 [ 'Unified variable is not used: ~W'-[A=B, Options] ].
1242compiler_warning(always(Bool, Pred, Arg), _Clause, Options) -->
1243 { Goal =.. [Pred,Arg] },
1244 [ 'Test is always ~w: ~W'-[Bool, Goal, Options] ].
1245compiler_warning(unbalanced_var(V), _Clause, Options) -->
1246 [ 'Variable not introduced in all branches: ~W'-[V, Options] ].
1247compiler_warning(branch_singleton(V), _Clause, Options) -->
1248 [ 'Singleton variable in branch: ~W'-[V, Options] ].
1249compiler_warning(negation_singleton(V), _Clause, Options) -->
1250 [ 'Singleton variable in \\+: ~W'-[V, Options] ].
1251compiler_warning(multiton(V), _Clause, Options) -->
1252 [ 'Singleton-marked variable appears more than once: ~W'-[V, Options] ].
1253
1254print_goal_options(
1255 [ quoted(true),
1256 portray(true)
1257 ]).
1258
1259
1260 1263
1264prolog_message(version) -->
1265 { current_prolog_flag(version_git, Version) },
1266 !,
1267 [ '~w'-[Version] ].
1268prolog_message(version) -->
1269 { current_prolog_flag(version_data, swi(Major,Minor,Patch,Options))
1270 },
1271 ( { memberchk(tag(Tag), Options) }
1272 -> [ '~w.~w.~w-~w'-[Major, Minor, Patch, Tag] ]
1273 ; [ '~w.~w.~w'-[Major, Minor, Patch] ]
1274 ).
1275prolog_message(address_bits) -->
1276 { current_prolog_flag(address_bits, Bits)
1277 },
1278 !,
1279 [ '~d bits, '-[Bits] ].
1280prolog_message(threads) -->
1281 { current_prolog_flag(threads, true)
1282 },
1283 !,
1284 [ 'threaded, ' ].
1285prolog_message(threads) -->
1286 [].
1287prolog_message(copyright) -->
1288 [ 'SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.', nl,
1289 'Please run ', ansi(code, '?- license.', []), ' for legal details.'
1290 ].
1291prolog_message(documentaton) -->
1292 [ 'For online help and background, visit ', url('https://www.swi-prolog.org') ],
1293 ( { exists_source(library(help)) }
1294 -> [ nl,
1295 'For built-in help, use ', ansi(code, '?- help(Topic).', []),
1296 ' or ', ansi(code, '?- apropos(Word).', [])
1297 ]
1298 ; []
1299 ).
1300prolog_message(about) -->
1301 [ 'SWI-Prolog version (' ],
1302 prolog_message(threads),
1303 prolog_message(address_bits),
1304 ['version ' ],
1305 prolog_message(version),
1306 [ ')', nl ],
1307 prolog_message(copyright).
1308prolog_message(halt) -->
1309 [ 'halt' ].
1310prolog_message(break(begin, Level)) -->
1311 [ 'Break level ~d'-[Level] ].
1312prolog_message(break(end, Level)) -->
1313 [ 'Exit break level ~d'-[Level] ].
1314prolog_message(var_query(_)) -->
1315 [ '... 1,000,000 ............ 10,000,000 years later', nl, nl,
1316 '~t~8|>> 42 << (last release gives the question)'
1317 ].
1318prolog_message(close_on_abort(Stream)) -->
1319 [ 'Abort: closed stream ~p'-[Stream] ].
1320prolog_message(cancel_halt(Reason)) -->
1321 [ 'Halt cancelled: ~p'-[Reason] ].
1322prolog_message(on_error(halt(Status))) -->
1323 { statistics(errors, Errors),
1324 statistics(warnings, Warnings)
1325 },
1326 [ 'Halting with status ~w due to ~D errors and ~D warnings'-
1327 [Status, Errors, Warnings] ].
1328
1329prolog_message(query(QueryResult)) -->
1330 query_result(QueryResult).
1331
1332query_result(no) --> 1333 [ ansi(truth(false), 'false.', []) ],
1334 extra_line.
1335query_result(yes(true, [])) --> 1336 !,
1337 [ ansi(truth(true), 'true.', []) ],
1338 extra_line.
1339query_result(yes(Delays, Residuals)) -->
1340 result([], Delays, Residuals),
1341 extra_line.
1342query_result(done) --> 1343 extra_line.
1344query_result(yes(Bindings, Delays, Residuals)) -->
1345 result(Bindings, Delays, Residuals),
1346 prompt(yes, Bindings, Delays, Residuals).
1347query_result(more(Bindings, Delays, Residuals)) -->
1348 result(Bindings, Delays, Residuals),
1349 prompt(more, Bindings, Delays, Residuals).
1350:- if(current_prolog_flag(emscripten, true)). 1351query_result(help) -->
1352 [ ansi(bold, ' Possible actions:', []), nl,
1353 ' ; (n,r,space): redo | t: trace&redo'-[], nl,
1354 ' *: show choicepoint | . (c,a): stop'-[], nl,
1355 ' w: write | p: print'-[], nl,
1356 ' +: max_depth*5 | -: max_depth//5'-[], nl,
1357 ' h (?): help'-[],
1358 nl, nl
1359 ].
1360:- else. 1361query_result(help) -->
1362 [ ansi(bold, ' Possible actions:', []), nl,
1363 ' ; (n,r,space,TAB): redo | t: trace&redo'-[], nl,
1364 ' *: show choicepoint | . (c,a,RET): stop'-[], nl,
1365 ' w: write | p: print'-[], nl,
1366 ' +: max_depth*5 | -: max_depth//5'-[], nl,
1367 ' b: break | h (?): help'-[],
1368 nl, nl
1369 ].
1370:- endif. 1371query_result(action) -->
1372 [ 'Action? '-[], flush ].
1373query_result(confirm) -->
1374 [ 'Please answer \'y\' or \'n\'? '-[], flush ].
1375query_result(eof) -->
1376 [ nl ].
1377query_result(toplevel_open_line) -->
1378 [].
1379
1380prompt(Answer, [], true, []-[]) -->
1381 !,
1382 prompt(Answer, empty).
1383prompt(Answer, _, _, _) -->
1384 !,
1385 prompt(Answer, non_empty).
1386
1387prompt(yes, empty) -->
1388 !,
1389 [ ansi(truth(true), 'true.', []) ],
1390 extra_line.
1391prompt(yes, _) -->
1392 !,
1393 [ full_stop ],
1394 extra_line.
1395prompt(more, empty) -->
1396 !,
1397 [ ansi(truth(true), 'true ', []), flush ].
1398prompt(more, _) -->
1399 !,
1400 [ ' '-[], flush ].
1401
1402result(Bindings, Delays, Residuals) -->
1403 { current_prolog_flag(answer_write_options, Options0),
1404 Options = [partial(true)|Options0],
1405 GOptions = [priority(999)|Options0]
1406 },
1407 wfs_residual_program(Delays, GOptions),
1408 bindings(Bindings, [priority(699)|Options]),
1409 ( {Residuals == []-[]}
1410 -> bind_delays_sep(Bindings, Delays),
1411 delays(Delays, GOptions)
1412 ; bind_res_sep(Bindings, Residuals),
1413 residuals(Residuals, GOptions),
1414 ( {Delays == true}
1415 -> []
1416 ; [','-[], nl],
1417 delays(Delays, GOptions)
1418 )
1419 ).
1420
1421bindings([], _) -->
1422 [].
1423bindings([binding(Names,Skel,Subst)|T], Options) -->
1424 { '$last'(Names, Name) },
1425 var_names(Names), value(Name, Skel, Subst, Options),
1426 ( { T \== [] }
1427 -> [ ','-[], nl ],
1428 bindings(T, Options)
1429 ; []
1430 ).
1431
1432var_names([Name]) -->
1433 !,
1434 [ '~w = '-[Name] ].
1435var_names([Name1,Name2|T]) -->
1436 !,
1437 [ '~w = ~w, '-[Name1, Name2] ],
1438 var_names([Name2|T]).
1439
1440
1441value(Name, Skel, Subst, Options) -->
1442 ( { var(Skel), Subst = [Skel=S] }
1443 -> { Skel = '$VAR'(Name) },
1444 [ '~W'-[S, Options] ]
1445 ; [ '~W'-[Skel, Options] ],
1446 substitution(Subst, Options)
1447 ).
1448
1449substitution([], _) --> !.
1450substitution([N=V|T], Options) -->
1451 [ ', ', ansi(comment, '% where', []), nl,
1452 ' ~w = ~W'-[N,V,Options] ],
1453 substitutions(T, Options).
1454
1455substitutions([], _) --> [].
1456substitutions([N=V|T], Options) -->
1457 [ ','-[], nl, ' ~w = ~W'-[N,V,Options] ],
1458 substitutions(T, Options).
1459
1460
1461residuals(Normal-Hidden, Options) -->
1462 residuals1(Normal, Options),
1463 bind_res_sep(Normal, Hidden),
1464 ( {Hidden == []}
1465 -> []
1466 ; [ansi(comment, '% with pending residual goals', []), nl]
1467 ),
1468 residuals1(Hidden, Options).
1469
1470residuals1([], _) -->
1471 [].
1472residuals1([G|Gs], Options) -->
1473 ( { Gs \== [] }
1474 -> [ '~W,'-[G, Options], nl ],
1475 residuals1(Gs, Options)
1476 ; [ '~W'-[G, Options] ]
1477 ).
1478
1479wfs_residual_program(true, _Options) -->
1480 !.
1481wfs_residual_program(Goal, _Options) -->
1482 { current_prolog_flag(toplevel_list_wfs_residual_program, true),
1483 '$current_typein_module'(TypeIn),
1484 ( current_predicate(delays_residual_program/2)
1485 -> true
1486 ; use_module(library(wfs), [delays_residual_program/2])
1487 ),
1488 delays_residual_program(TypeIn:Goal, TypeIn:Program),
1489 Program \== []
1490 },
1491 !,
1492 [ ansi(comment, '% WFS residual program', []), nl ],
1493 [ ansi(wfs(residual_program), '~@', ['$messages':list_clauses(Program)]) ].
1494wfs_residual_program(_, _) --> [].
1495
1496delays(true, _Options) -->
1497 !.
1498delays(Goal, Options) -->
1499 { current_prolog_flag(toplevel_list_wfs_residual_program, true)
1500 },
1501 !,
1502 [ ansi(truth(undefined), '~W', [Goal, Options]) ].
1503delays(_, _Options) -->
1504 [ ansi(truth(undefined), undefined, []) ].
1505
1506:- public list_clauses/1. 1507
1508list_clauses([]).
1509list_clauses([H|T]) :-
1510 ( system_undefined(H)
1511 -> true
1512 ; portray_clause(user_output, H, [indent(4)])
1513 ),
1514 list_clauses(T).
1515
1516system_undefined((undefined :- tnot(undefined))).
1517system_undefined((answer_count_restraint :- tnot(answer_count_restraint))).
1518system_undefined((radial_restraint :- tnot(radial_restraint))).
1519
1520bind_res_sep(_, []) --> !.
1521bind_res_sep(_, []-[]) --> !.
1522bind_res_sep([], _) --> !.
1523bind_res_sep(_, _) --> [','-[], nl].
1524
1525bind_delays_sep([], _) --> !.
1526bind_delays_sep(_, true) --> !.
1527bind_delays_sep(_, _) --> [','-[], nl].
1528
-->
1530 { current_prolog_flag(toplevel_extra_white_line, true) },
1531 !,
1532 ['~N'-[]].
1533extra_line -->
1534 [].
1535
1536prolog_message(if_tty(Message)) -->
1537 ( {current_prolog_flag(tty_control, true)}
1538 -> [ at_same_line ], list(Message)
1539 ; []
1540 ).
1541prolog_message(halt(Reason)) -->
1542 [ '~w: halt'-[Reason] ].
1543prolog_message(no_action(Char)) -->
1544 [ 'Unknown action: ~c (h for help)'-[Char], nl ].
1545
1546prolog_message(history(help(Show, Help))) -->
1547 [ 'History Commands:', nl,
1548 ' !!. Repeat last query', nl,
1549 ' !nr. Repeat query numbered <nr>', nl,
1550 ' !str. Repeat last query starting with <str>', nl,
1551 ' !?str. Repeat last query holding <str>', nl,
1552 ' ^old^new. Substitute <old> into <new> of last query', nl,
1553 ' !nr^old^new. Substitute in query numbered <nr>', nl,
1554 ' !str^old^new. Substitute in query starting with <str>', nl,
1555 ' !?str^old^new. Substitute in query holding <str>', nl,
1556 ' ~w.~21|Show history list'-[Show], nl,
1557 ' ~w.~21|Show this list'-[Help], nl, nl
1558 ].
1559prolog_message(history(no_event)) -->
1560 [ '! No such event' ].
1561prolog_message(history(bad_substitution)) -->
1562 [ '! Bad substitution' ].
1563prolog_message(history(expanded(Event))) -->
1564 [ '~w.'-[Event] ].
1565prolog_message(history(history(Events))) -->
1566 history_events(Events).
1567
1568history_events([]) -->
1569 [].
1570history_events([Nr/Event|T]) -->
1571 [ '~t~w ~8|~W~W'-[ Nr,
1572 Event, [partial(true)],
1573 '.', [partial(true)]
1574 ],
1575 nl
1576 ],
1577 history_events(T).
1578
1579
1584
1585user_version_messages([]) --> [].
1586user_version_messages([H|T]) -->
1587 user_version_message(H),
1588 user_version_messages(T).
1589
1591
1592user_version_message(Term) -->
1593 translate_message(Term), !, [nl].
1594user_version_message(Atom) -->
1595 [ '~w'-[Atom], nl ].
1596
1597
1598 1601
1602prolog_message(spy(Head)) -->
1603 { goal_to_predicate_indicator(Head, Pred)
1604 },
1605 [ 'Spy point on ~p'-[Pred] ].
1606prolog_message(nospy(Head)) -->
1607 { goal_to_predicate_indicator(Head, Pred)
1608 },
1609 [ 'Spy point removed from ~p'-[Pred] ].
1610prolog_message(trace_mode(OnOff)) -->
1611 [ 'Trace mode switched to ~w'-[OnOff] ].
1612prolog_message(debug_mode(OnOff)) -->
1613 [ 'Debug mode switched to ~w'-[OnOff] ].
1614prolog_message(debugging(OnOff)) -->
1615 [ 'Debug mode is ~w'-[OnOff] ].
1616prolog_message(spying([])) -->
1617 !,
1618 [ 'No spy points' ].
1619prolog_message(spying(Heads)) -->
1620 [ 'Spy points (see spy/1) on:', nl ],
1621 predicate_list(Heads).
1622prolog_message(trace(Head, [])) -->
1623 !,
1624 [ ' ' ], goal_predicate(Head), [ ' Not tracing'-[], nl].
1625prolog_message(trace(Head, Ports)) -->
1626 { '$member'(Port, Ports), compound(Port),
1627 !,
1628 numbervars(Head+Ports, 0, _, [singletons(true)])
1629 },
1630 [ ' ~p: ~p'-[Head,Ports] ].
1631prolog_message(trace(Head, Ports)) -->
1632 [ ' ' ], goal_predicate(Head), [ ': ~w'-[Ports], nl].
1633prolog_message(tracing([])) -->
1634 !,
1635 [ 'No traced predicates (see trace/1,2)' ].
1636prolog_message(tracing(Heads)) -->
1637 [ 'Trace points (see trace/1,2) on:', nl ],
1638 tracing_list(Heads).
1639
1640goal_predicate(Head) -->
1641 { predicate_property(Head, file(File)),
1642 predicate_property(Head, line_count(Line)),
1643 goal_to_predicate_indicator(Head, PI),
1644 term_string(PI, PIS, [quoted(true)])
1645 },
1646 [ url(File:Line, PIS) ].
1647goal_predicate(Head) -->
1648 { goal_to_predicate_indicator(Head, PI)
1649 },
1650 [ '~p'-[PI] ].
1651
1652
1653predicate_list([]) --> 1654 [].
1655predicate_list([H|T]) -->
1656 [ ' ' ], goal_predicate(H), [nl],
1657 predicate_list(T).
1658
1659tracing_list([]) -->
1660 [].
1661tracing_list([trace(Head, Ports)|T]) -->
1662 translate_message(trace(Head, Ports)),
1663 tracing_list(T).
1664
1666prolog_message(frame(Frame, _Choice, backtrace, _PC)) -->
1667 !,
1668 { prolog_frame_attribute(Frame, level, Level)
1669 },
1670 [ ansi(frame(level), '~t[~D] ~10|', [Level]) ],
1671 frame_context(Frame),
1672 frame_goal(Frame).
1673prolog_message(frame(Frame, _Choice, choice, PC)) -->
1674 !,
1675 prolog_message(frame(Frame, backtrace, PC)).
1676prolog_message(frame(_, _Choice, cut_call(_PC), _)) --> !.
1677prolog_message(frame(Frame, _Choice, Port, _PC)) -->
1678 frame_flags(Frame),
1679 port(Port),
1680 frame_level(Frame),
1681 frame_context(Frame),
1682 frame_depth_limit(Port, Frame),
1683 frame_goal(Frame),
1684 [ flush ].
1685
1687prolog_message(frame(Goal, trace(Port))) -->
1688 !,
1689 thread_context,
1690 [ ' T ' ],
1691 port(Port),
1692 goal(Goal).
1693prolog_message(frame(Goal, trace(Port, Id))) -->
1694 !,
1695 thread_context,
1696 [ ' T ' ],
1697 port(Port, Id),
1698 goal(Goal).
1699
1700frame_goal(Frame) -->
1701 { prolog_frame_attribute(Frame, goal, Goal)
1702 },
1703 goal(Goal).
1704
1705goal(Goal0) -->
1706 { clean_goal(Goal0, Goal),
1707 current_prolog_flag(debugger_write_options, Options)
1708 },
1709 [ '~W'-[Goal, Options] ].
1710
1711frame_level(Frame) -->
1712 { prolog_frame_attribute(Frame, level, Level)
1713 },
1714 [ '(~D) '-[Level] ].
1715
1716frame_context(Frame) -->
1717 ( { current_prolog_flag(debugger_show_context, true),
1718 prolog_frame_attribute(Frame, context_module, Context)
1719 }
1720 -> [ '[~w] '-[Context] ]
1721 ; []
1722 ).
1723
1724frame_depth_limit(fail, Frame) -->
1725 { prolog_frame_attribute(Frame, depth_limit_exceeded, true)
1726 },
1727 !,
1728 [ '[depth-limit exceeded] ' ].
1729frame_depth_limit(_, _) -->
1730 [].
1731
1732frame_flags(Frame) -->
1733 { prolog_frame_attribute(Frame, goal, Goal),
1734 ( predicate_property(Goal, transparent)
1735 -> T = '^'
1736 ; T = ' '
1737 ),
1738 ( predicate_property(Goal, spying)
1739 -> S = '*'
1740 ; S = ' '
1741 )
1742 },
1743 [ '~w~w '-[T, S] ].
1744
1746port(Port, Dict) -->
1747 { _{level:Level, start:Time} :< Dict
1748 },
1749 ( { Port \== call,
1750 get_time(Now),
1751 Passed is (Now - Time)*1000.0
1752 }
1753 -> [ '[~d +~1fms] '-[Level, Passed] ]
1754 ; [ '[~d] '-[Level] ]
1755 ),
1756 port(Port).
1757port(Port, _Id-Level) -->
1758 [ '[~d] '-[Level] ],
1759 port(Port).
1760
1761port(PortTerm) -->
1762 { functor(PortTerm, Port, _),
1763 port_name(Port, Name)
1764 },
1765 !,
1766 [ ansi(port(Port), '~w: ', [Name]) ].
1767
1768port_name(call, 'Call').
1769port_name(exit, 'Exit').
1770port_name(fail, 'Fail').
1771port_name(redo, 'Redo').
1772port_name(unify, 'Unify').
1773port_name(exception, 'Exception').
1774
1775clean_goal(M:Goal, Goal) :-
1776 hidden_module(M),
1777 !.
1778clean_goal(M:Goal, Goal) :-
1779 predicate_property(M:Goal, built_in),
1780 !.
1781clean_goal(Goal, Goal).
1782
1783
1784 1787
1788prolog_message(compatibility(renamed(Old, New))) -->
1789 [ 'The predicate ~p has been renamed to ~p.'-[Old, New], nl,
1790 'Please update your sources for compatibility with future versions.'
1791 ].
1792
1793
1794 1797
1798prolog_message(abnormal_thread_completion(Goal, exception(Ex))) -->
1799 !,
1800 [ 'Thread running "~p" died on exception: '-[Goal] ],
1801 translate_message(Ex).
1802prolog_message(abnormal_thread_completion(Goal, fail)) -->
1803 [ 'Thread running "~p" died due to failure'-[Goal] ].
1804prolog_message(threads_not_died(Running)) -->
1805 [ 'The following threads wouldn\'t die: ~p'-[Running] ].
1806
1807
1808 1811
1812prolog_message(pack(attached(Pack, BaseDir))) -->
1813 [ 'Attached package ~w at ~q'-[Pack, BaseDir] ].
1814prolog_message(pack(duplicate(Entry, OldDir, Dir))) -->
1815 [ 'Package ~w already attached at ~q.'-[Entry,OldDir], nl,
1816 '\tIgnoring version from ~q'- [Dir]
1817 ].
1818prolog_message(pack(no_arch(Entry, Arch))) -->
1819 [ 'Package ~w: no binary for architecture ~w'-[Entry, Arch] ].
1820
1821 1824
1825prolog_message(null_byte_in_path(Component)) -->
1826 [ '0-byte in PATH component: ~p (skipped directory)'-[Component] ].
1827prolog_message(invalid_tmp_dir(Dir, Reason)) -->
1828 [ 'Cannot use ~p as temporary file directory: ~w'-[Dir, Reason] ].
1829prolog_message(ambiguous_stream_pair(Pair)) -->
1830 [ 'Ambiguous operation on stream pair ~p'-[Pair] ].
1831prolog_message(backcomp(init_file_moved(FoundFile))) -->
1832 { absolute_file_name(app_config('init.pl'), InitFile,
1833 [ file_errors(fail)
1834 ])
1835 },
1836 [ 'The location of the config file has moved'-[], nl,
1837 ' from "~w"'-[FoundFile], nl,
1838 ' to "~w"'-[InitFile], nl,
1839 ' See https://www.swi-prolog.org/modified/config-files.html'-[]
1840 ].
1841prolog_message(not_accessed_flags(List)) -->
1842 [ 'The following Prolog flags have been set but not used:', nl ],
1843 flags(List).
1844prolog_message(prolog_flag_invalid_preset(Flag, Preset, _Type, New)) -->
1845 [ 'Prolog flag ', ansi(code, '~q', Flag), ' has been (re-)created with a type that is \c
1846 incompatible with its value.', nl,
1847 'Value updated from ', ansi(code, '~p', [Preset]), ' to default (',
1848 ansi(code, '~p', [New]), ')'
1849 ].
1850
1851
1852flags([H|T]) -->
1853 [' ', ansi(code, '~q', [H])],
1854 ( {T == []}
1855 -> []
1856 ; [nl],
1857 flags(T)
1858 ).
1859
1860
1861 1864
1865deprecated(set_prolog_stack(_Stack,limit)) -->
1866 [ 'set_prolog_stack/2: limit(Size) sets the combined limit.'-[], nl,
1867 'See https://www.swi-prolog.org/changes/stack-limit.html'
1868 ].
1869deprecated(autoload(TargetModule, File, _M:PI, expansion)) -->
1870 !,
1871 [ 'Auto-loading ', ansi(code, '~p', [PI]), ' from ' ],
1872 load_file(File), [ ' into ' ],
1873 target_module(TargetModule),
1874 [ ' is deprecated due to term- or goal-expansion' ].
1875deprecated(source_search_working_directory(File, _FullFile)) -->
1876 [ 'Found file ', ansi(code, '~w', [File]),
1877 ' relative to the current working directory.', nl,
1878 'This behaviour is deprecated but still supported by', nl,
1879 'the Prolog flag ',
1880 ansi(code, source_search_working_directory, []), '.', nl
1881 ].
1882
1883load_file(File) -->
1884 { file_base_name(File, Base),
1885 absolute_file_name(library(Base), File, [access(read), file_errors(fail)]),
1886 file_name_extension(Clean, pl, Base)
1887 },
1888 !,
1889 [ ansi(code, '~p', [library(Clean)]) ].
1890load_file(File) -->
1891 [ url(File) ].
1892
1893target_module(Module) -->
1894 { module_property(Module, file(File)) },
1895 !,
1896 load_file(File).
1897target_module(Module) -->
1898 [ 'module ', ansi(code, '~p', [Module]) ].
1899
1900
1901
1902 1905
1906tripwire_message(max_integer_size, Bytes) -->
1907 !,
1908 [ 'Trapped tripwire max_integer_size: big integers and \c
1909 rationals are limited to ~D bytes'-[Bytes] ].
1910tripwire_message(Wire, Context) -->
1911 [ 'Trapped tripwire ~w for '-[Wire] ],
1912 tripwire_context(Wire, Context).
1913
1914tripwire_context(_, ATrie) -->
1915 { '$is_answer_trie'(ATrie, _),
1916 !,
1917 '$tabling':atrie_goal(ATrie, QGoal),
1918 user_predicate_indicator(QGoal, Goal)
1919 },
1920 [ '~p'-[Goal] ].
1921tripwire_context(_, Ctx) -->
1922 [ '~p'-[Ctx] ].
1923
1924
1925 1928
1929:- create_prolog_flag(message_language, default, []). 1930
1935
1936message_lang(Lang) :-
1937 current_message_lang(Lang0),
1938 ( Lang0 == en
1939 -> Lang = en
1940 ; sub_atom(Lang0, 0, _, _, en_)
1941 -> longest_id(Lang0, Lang)
1942 ; ( longest_id(Lang0, Lang)
1943 ; Lang = en
1944 )
1945 ).
1946
1947longest_id(Lang, Id) :-
1948 split_string(Lang, "_-", "", [H|Components]),
1949 longest_prefix(Components, Taken),
1950 atomic_list_concat([H|Taken], '_', Id).
1951
1952longest_prefix([H|T0], [H|T]) :-
1953 longest_prefix(T0, T).
1954longest_prefix(_, []).
1955
1959
1960current_message_lang(Lang) :-
1961 ( current_prolog_flag(message_language, Lang0),
1962 Lang0 \== default
1963 -> Lang = Lang0
1964 ; os_user_lang(Lang0)
1965 -> clean_encoding(Lang0, Lang1),
1966 set_prolog_flag(message_language, Lang1),
1967 Lang = Lang1
1968 ; Lang = en
1969 ).
1970
1971os_user_lang(Lang) :-
1972 current_prolog_flag(windows, true),
1973 win_get_user_preferred_ui_languages(name, [Lang|_]).
1974os_user_lang(Lang) :-
1975 catch(setlocale(messages, _, ''), _, fail),
1976 setlocale(messages, Lang, Lang).
1977os_user_lang(Lang) :-
1978 getenv('LANG', Lang).
1979
1980
1981clean_encoding(Lang0, Lang) :-
1982 ( sub_atom(Lang0, A, _, _, '.')
1983 -> sub_atom(Lang0, 0, A, _, Lang)
1984 ; Lang = Lang0
1985 ).
1986
1987 1990
1991code(Term) -->
1992 code('~p', Term).
1993
1994code(Format, Term) -->
1995 [ ansi(code, Format, [Term]) ].
1996
1997list([]) --> [].
1998list([H|T]) --> [H], list(T).
1999
2000
2001 2004
2005:- public default_theme/2. 2006
2007default_theme(var, [fg(red)]).
2008default_theme(code, [fg(blue)]).
2009default_theme(comment, [fg(green)]).
2010default_theme(warning, [fg(red)]).
2011default_theme(error, [bold, fg(red)]).
2012default_theme(truth(false), [bold, fg(red)]).
2013default_theme(truth(true), [bold]).
2014default_theme(truth(undefined), [bold, fg(cyan)]).
2015default_theme(wfs(residual_program), [fg(cyan)]).
2016default_theme(frame(level), [bold]).
2017default_theme(port(call), [bold, fg(green)]).
2018default_theme(port(exit), [bold, fg(green)]).
2019default_theme(port(fail), [bold, fg(red)]).
2020default_theme(port(redo), [bold, fg(yellow)]).
2021default_theme(port(unify), [bold, fg(blue)]).
2022default_theme(port(exception), [bold, fg(magenta)]).
2023default_theme(message(informational), [fg(green)]).
2024default_theme(message(information), [fg(green)]).
2025default_theme(message(debug(_)), [fg(blue)]).
2026default_theme(message(Level), Attrs) :-
2027 nonvar(Level),
2028 default_theme(Level, Attrs).
2029
2030
2031 2034
2035:- multifile
2036 user:message_hook/3,
2037 prolog:message_prefix_hook/2. 2038:- dynamic
2039 user:message_hook/3,
2040 prolog:message_prefix_hook/2. 2041:- thread_local
2042 user:thread_message_hook/3. 2043:- '$notransact'((user:message_hook/3,
2044 prolog:message_prefix_hook/2,
2045 user:thread_message_hook/3)). 2046
2051
2052print_message(Level, _Term) :-
2053 msg_property(Level, stream(S)),
2054 stream_property(S, error(true)),
2055 !.
2056print_message(Level, Term) :-
2057 setup_call_cleanup(
2058 notrace(push_msg(Term, Stack)),
2059 ignore(print_message_guarded(Level, Term)),
2060 notrace(pop_msg(Stack))),
2061 !.
2062print_message(Level, Term) :-
2063 ( Level \== silent
2064 -> format(user_error, 'Recursive ~w message: ~q~n', [Level, Term]),
2065 backtrace(20)
2066 ; true
2067 ).
2068
2069push_msg(Term, Messages) :-
2070 nb_current('$inprint_message', Messages),
2071 !,
2072 \+ ( '$member'(Msg, Messages),
2073 Msg =@= Term
2074 ),
2075 Stack = [Term|Messages],
2076 b_setval('$inprint_message', Stack).
2077push_msg(Term, []) :-
2078 b_setval('$inprint_message', [Term]).
2079
2080pop_msg(Stack) :-
2081 nb_delete('$inprint_message'), 2082 b_setval('$inprint_message', Stack).
2083
2084print_message_guarded(Level, Term) :-
2085 ( must_print(Level, Term)
2086 -> ( translate_message(Term, Lines, [])
2087 -> ( nonvar(Term),
2088 ( notrace(user:thread_message_hook(Term, Level, Lines))
2089 -> true
2090 ; notrace(user:message_hook(Term, Level, Lines))
2091 )
2092 -> true
2093 ; '$inc_message_count'(Level),
2094 print_system_message(Term, Level, Lines),
2095 maybe_halt_on_error(Level)
2096 )
2097 )
2098 ; true
2099 ).
2100
2101maybe_halt_on_error(error) :-
2102 current_prolog_flag(on_error, halt),
2103 !,
2104 halt(1).
2105maybe_halt_on_error(warning) :-
2106 current_prolog_flag(on_warning, halt),
2107 !,
2108 halt(1).
2109maybe_halt_on_error(_).
2110
2111
2118
2119print_system_message(_, silent, _) :- !.
2120print_system_message(_, informational, _) :-
2121 current_prolog_flag(verbose, silent),
2122 !.
2123print_system_message(_, banner, _) :-
2124 current_prolog_flag(verbose, silent),
2125 !.
2126print_system_message(_, _, []) :- !.
2127print_system_message(Term, Kind, Lines) :-
2128 catch(flush_output(user_output), _, true), 2129 source_location(File, Line),
2130 Term \= error(syntax_error(_), _),
2131 msg_property(Kind, location_prefix(File:Line, LocPrefix, LinePrefix)),
2132 !,
2133 to_list(LocPrefix, LocPrefixL),
2134 insert_prefix(Lines, LinePrefix, Ctx, PrefixLines),
2135 '$append'([ [begin(Kind, Ctx)],
2136 LocPrefixL,
2137 [nl],
2138 PrefixLines,
2139 [end(Ctx)]
2140 ],
2141 AllLines),
2142 msg_property(Kind, stream(Stream)),
2143 ignore(stream_property(Stream, position(Pos))),
2144 print_message_lines(Stream, AllLines),
2145 ( \+ stream_property(Stream, position(Pos)),
2146 msg_property(Kind, wait(Wait)),
2147 Wait > 0
2148 -> sleep(Wait)
2149 ; true
2150 ).
2151print_system_message(_, Kind, Lines) :-
2152 msg_property(Kind, stream(Stream)),
2153 print_message_lines(Stream, kind(Kind), Lines).
2154
2155to_list(ListIn, List) :-
2156 is_list(ListIn),
2157 !,
2158 List = ListIn.
2159to_list(NonList, [NonList]).
2160
2161:- multifile
2162 user:message_property/2. 2163
2164msg_property(Kind, Property) :-
2165 notrace(user:message_property(Kind, Property)),
2166 !.
2167msg_property(Kind, prefix(Prefix)) :-
2168 msg_prefix(Kind, Prefix),
2169 !.
2170msg_property(_, prefix('~N')) :- !.
2171msg_property(query, stream(user_output)) :- !.
2172msg_property(_, stream(user_error)) :- !.
2173msg_property(error, tag('ERROR')).
2174msg_property(warning, tag('Warning')).
2175msg_property(Level,
2176 location_prefix(File:Line,
2177 ['~N~w: '-[Tag], url(File:Line), ':'],
2178 '~N~w: '-[Tag])) :-
2179 include_msg_location(Level),
2180 msg_property(Level, tag(Tag)).
2181msg_property(error, wait(0.1)) :- !.
2182
2183include_msg_location(warning).
2184include_msg_location(error).
2185
2186msg_prefix(debug(_), Prefix) :-
2187 msg_context('~N% ', Prefix).
2188msg_prefix(Level, Prefix) :-
2189 msg_property(Level, tag(Tag)),
2190 atomics_to_string(['~N', Tag, ': '], Prefix0),
2191 msg_context(Prefix0, Prefix).
2192msg_prefix(informational, '~N% ').
2193msg_prefix(information, '~N% ').
2194
2206
2207msg_context(Prefix0, Prefix) :-
2208 current_prolog_flag(message_context, Context),
2209 is_list(Context),
2210 !,
2211 add_message_context(Context, Prefix0, Prefix).
2212msg_context(Prefix, Prefix).
2213
2214add_message_context([], Prefix, Prefix).
2215add_message_context([H|T], Prefix0, Prefix) :-
2216 ( add_message_context1(H, Prefix0, Prefix1)
2217 -> true
2218 ; Prefix1 = Prefix0
2219 ),
2220 add_message_context(T, Prefix1, Prefix).
2221
2222add_message_context1(Context, Prefix0, Prefix) :-
2223 prolog:message_prefix_hook(Context, Extra),
2224 atomics_to_string([Prefix0, Extra, ' '], Prefix).
2225add_message_context1(time, Prefix0, Prefix) :-
2226 get_time(Now),
2227 format_time(string(S), '%T.%3f ', Now),
2228 string_concat(Prefix0, S, Prefix).
2229add_message_context1(time(Format), Prefix0, Prefix) :-
2230 get_time(Now),
2231 format_time(string(S), Format, Now),
2232 atomics_to_string([Prefix0, S, ' '], Prefix).
2233add_message_context1(thread, Prefix0, Prefix) :-
2234 thread_self(Id0),
2235 Id0 \== main,
2236 !,
2237 ( atom(Id0)
2238 -> Id = Id0
2239 ; thread_property(Id0, id(Id))
2240 ),
2241 format(string(Prefix), '~w[Thread ~w] ', [Prefix0, Id]).
2242
2247
2248print_message_lines(Stream, kind(Kind), Lines) :-
2249 !,
2250 msg_property(Kind, prefix(Prefix)),
2251 insert_prefix(Lines, Prefix, Ctx, PrefixLines),
2252 '$append'([ begin(Kind, Ctx)
2253 | PrefixLines
2254 ],
2255 [ end(Ctx)
2256 ],
2257 AllLines),
2258 print_message_lines(Stream, AllLines).
2259print_message_lines(Stream, Prefix, Lines) :-
2260 insert_prefix(Lines, Prefix, _, PrefixLines),
2261 print_message_lines(Stream, PrefixLines).
2262
2264
2265insert_prefix([at_same_line|Lines0], Prefix, Ctx, Lines) :-
2266 !,
2267 prefix_nl(Lines0, Prefix, Ctx, Lines).
2268insert_prefix(Lines0, Prefix, Ctx, [prefix(Prefix)|Lines]) :-
2269 prefix_nl(Lines0, Prefix, Ctx, Lines).
2270
2271prefix_nl([], _, _, [nl]).
2272prefix_nl([nl], _, _, [nl]) :- !.
2273prefix_nl([flush], _, _, [flush]) :- !.
2274prefix_nl([nl|T0], Prefix, Ctx, [nl, prefix(Prefix)|T]) :-
2275 !,
2276 prefix_nl(T0, Prefix, Ctx, T).
2277prefix_nl([ansi(Attrs,Fmt,Args)|T0], Prefix, Ctx,
2278 [ansi(Attrs,Fmt,Args,Ctx)|T]) :-
2279 !,
2280 prefix_nl(T0, Prefix, Ctx, T).
2281prefix_nl([H|T0], Prefix, Ctx, [H|T]) :-
2282 prefix_nl(T0, Prefix, Ctx, T).
2283
2285
2286print_message_lines(Stream, Lines) :-
2287 with_output_to(
2288 Stream,
2289 notrace(print_message_lines_guarded(current_output, Lines))).
2290
2291print_message_lines_guarded(_, []) :- !.
2292print_message_lines_guarded(S, [H|T]) :-
2293 line_element(S, H),
2294 print_message_lines_guarded(S, T).
2295
2296line_element(S, E) :-
2297 prolog:message_line_element(S, E),
2298 !.
2299line_element(S, full_stop) :-
2300 !,
2301 '$put_token'(S, '.'). 2302line_element(S, nl) :-
2303 !,
2304 nl(S).
2305line_element(S, prefix(Fmt-Args)) :-
2306 !,
2307 safe_format(S, Fmt, Args).
2308line_element(S, prefix(Fmt)) :-
2309 !,
2310 safe_format(S, Fmt, []).
2311line_element(S, flush) :-
2312 !,
2313 flush_output(S).
2314line_element(S, Fmt-Args) :-
2315 !,
2316 safe_format(S, Fmt, Args).
2317line_element(S, ansi(_, Fmt, Args)) :-
2318 !,
2319 safe_format(S, Fmt, Args).
2320line_element(S, ansi(_, Fmt, Args, _Ctx)) :-
2321 !,
2322 safe_format(S, Fmt, Args).
2323line_element(S, url(URL)) :-
2324 !,
2325 print_link(S, URL).
2326line_element(S, url(_URL, Fmt-Args)) :-
2327 !,
2328 safe_format(S, Fmt, Args).
2329line_element(S, url(_URL, Fmt)) :-
2330 !,
2331 safe_format(S, Fmt, []).
2332line_element(_, begin(_Level, _Ctx)) :- !.
2333line_element(_, end(_Ctx)) :- !.
2334line_element(S, Fmt) :-
2335 safe_format(S, Fmt, []).
2336
2337print_link(S, File:Line:Column) :-
2338 !,
2339 safe_format(S, '~w:~d:~d', [File, Line, Column]).
2340print_link(S, File:Line) :-
2341 !,
2342 safe_format(S, '~w:~d', [File, Line]).
2343print_link(S, File) :-
2344 safe_format(S, '~w', [File]).
2345
2347
2348safe_format(S, Fmt, Args) :-
2349 E = error(_,_),
2350 catch(format(S,Fmt,Args), E,
2351 format_failed(S,Fmt,Args,E)).
2352
2353format_failed(S, _Fmt, _Args, E) :-
2354 stream_property(S, error(true)),
2355 !,
2356 throw(E).
2357format_failed(S, Fmt, Args, error(E,_)) :-
2358 format(S, '~N [[ EXCEPTION while printing message ~q~n\c
2359 ~7|with arguments ~W:~n\c
2360 ~7|raised: ~W~n~4|]]~n',
2361 [ Fmt,
2362 Args, [quoted(true), max_depth(10)],
2363 E, [quoted(true), max_depth(10)]
2364 ]).
2365
2369
2370message_to_string(Term, Str) :-
2371 translate_message(Term, Actions, []),
2372 !,
2373 actions_to_format(Actions, Fmt, Args),
2374 format(string(Str), Fmt, Args).
2375
2376actions_to_format([], '', []) :- !.
2377actions_to_format([nl], '', []) :- !.
2378actions_to_format([Term, nl], Fmt, Args) :-
2379 !,
2380 actions_to_format([Term], Fmt, Args).
2381actions_to_format([nl|T], Fmt, Args) :-
2382 !,
2383 actions_to_format(T, Fmt0, Args),
2384 atom_concat('~n', Fmt0, Fmt).
2385actions_to_format([ansi(_Attrs, Fmt0, Args0)|Tail], Fmt, Args) :-
2386 !,
2387 actions_to_format(Tail, Fmt1, Args1),
2388 atom_concat(Fmt0, Fmt1, Fmt),
2389 append_args(Args0, Args1, Args).
2390actions_to_format([url(Pos)|Tail], Fmt, Args) :-
2391 !,
2392 actions_to_format(Tail, Fmt1, Args1),
2393 url_actions_to_format(url(Pos), Fmt1, Args1, Fmt, Args).
2394actions_to_format([url(URL, Label)|Tail], Fmt, Args) :-
2395 !,
2396 actions_to_format(Tail, Fmt1, Args1),
2397 url_actions_to_format(url(URL, Label), Fmt1, Args1, Fmt, Args).
2398actions_to_format([Fmt0-Args0|Tail], Fmt, Args) :-
2399 !,
2400 actions_to_format(Tail, Fmt1, Args1),
2401 atom_concat(Fmt0, Fmt1, Fmt),
2402 append_args(Args0, Args1, Args).
2403actions_to_format([Skip|T], Fmt, Args) :-
2404 action_skip(Skip),
2405 !,
2406 actions_to_format(T, Fmt, Args).
2407actions_to_format([Term|Tail], Fmt, Args) :-
2408 atomic(Term),
2409 !,
2410 actions_to_format(Tail, Fmt1, Args),
2411 atom_concat(Term, Fmt1, Fmt).
2412actions_to_format([Term|Tail], Fmt, Args) :-
2413 actions_to_format(Tail, Fmt1, Args1),
2414 atom_concat('~w', Fmt1, Fmt),
2415 append_args([Term], Args1, Args).
2416
2417action_skip(at_same_line).
2418action_skip(flush).
2419action_skip(begin(_Level, _Ctx)).
2420action_skip(end(_Ctx)).
2421
2422url_actions_to_format(url(File:Line:Column), Fmt1, Args1, Fmt, Args) :-
2423 !,
2424 atom_concat('~w:~d:~d', Fmt1, Fmt),
2425 append_args([File,Line,Column], Args1, Args).
2426url_actions_to_format(url(File:Line), Fmt1, Args1, Fmt, Args) :-
2427 !,
2428 atom_concat('~w:~d', Fmt1, Fmt),
2429 append_args([File,Line], Args1, Args).
2430url_actions_to_format(url(File), Fmt1, Args1, Fmt, Args) :-
2431 !,
2432 atom_concat('~w', Fmt1, Fmt),
2433 append_args([File], Args1, Args).
2434url_actions_to_format(url(_URL, Label), Fmt1, Args1, Fmt, Args) :-
2435 !,
2436 atom_concat('~w', Fmt1, Fmt),
2437 append_args([Label], Args1, Args).
2438
2439
2440append_args(M:Args0, Args1, M:Args) :-
2441 !,
2442 strip_module(Args1, _, A1),
2443 to_list(Args0, Args01),
2444 '$append'(Args01, A1, Args).
2445append_args(Args0, Args1, Args) :-
2446 strip_module(Args1, _, A1),
2447 to_list(Args0, Args01),
2448 '$append'(Args01, A1, Args).
2449
2450 2453
2454:- dynamic
2455 printed/2. 2456
2460
2461print_once(compatibility(_), _).
2462print_once(null_byte_in_path(_), _).
2463print_once(deprecated(_), _).
2464
2468
2469must_print(Level, Message) :-
2470 nonvar(Message),
2471 print_once(Message, Level),
2472 !,
2473 \+ printed(Message, Level),
2474 assert(printed(Message, Level)).
2475must_print(_, _)