View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  1997-2020, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module('$messages',
   38          [ print_message/2,            % +Kind, +Term
   39            print_message_lines/3,      % +Stream, +Prefix, +Lines
   40            message_to_string/2         % +Term, -String
   41          ]).   42
   43:- multifile
   44    prolog:message//1,              % entire message
   45    prolog:error_message//1,        % 1-st argument of error term
   46    prolog:message_context//1,      % Context of error messages
   47    prolog:deprecated//1,	    % Deprecated features
   48    prolog:message_location//1,     % (File) location of error messages
   49    prolog:message_line_element/2.  % Extend printing
   50:- discontiguous
   51    prolog_message/3.   52
   53:- public
   54    translate_message//1.   55
   56:- create_prolog_flag(message_context, [thread], []).
 translate_message(+Term)// is det
Translate a message Term into message lines. The produced lines is a list of
nl
Emit a newline
Fmt - Args
Emit the result of format(Fmt, Args)
Fmt
Emit the result of format(Fmt)
flush
Used only as last element of the list. Simply flush the output instead of producing a final newline.
at_same_line
Start the messages at the same line (instead of using ~N)
   75translate_message(Term) -->
   76    translate_message2(Term),
   77    !.
   78translate_message(Term) -->
   79    { Term = error(_, _) },
   80    [ 'Unknown exception: ~p'-[Term] ].
   81translate_message(Term) -->
   82    [ 'Unknown message: ~p'-[Term] ].
   83
   84translate_message2(Term) -->
   85    {var(Term)},
   86    !,
   87    [ 'Unknown message: ~p'-[Term] ].
   88translate_message2(Term) -->
   89    prolog:message(Term).
   90translate_message2(Term) -->
   91    prolog_message(Term).
   92translate_message2(error(resource_error(stack), Context)) -->
   93    !,
   94    out_of_stack(Context).
   95translate_message2(error(resource_error(tripwire(Wire, Context)), _)) -->
   96    !,
   97    tripwire_message(Wire, Context).
   98translate_message2(error(existence_error(reset, Ball), SWI)) -->
   99    swi_location(SWI),
  100    tabling_existence_error(Ball, SWI).
  101translate_message2(error(ISO, SWI)) -->
  102    swi_location(SWI),
  103    term_message(ISO),
  104    swi_extra(SWI).
  105translate_message2('$aborted') -->
  106    [ 'Execution Aborted' ].
  107translate_message2(message_lines(Lines), L, T) :- % deal with old C-warning()
  108    make_message_lines(Lines, L, T).
  109translate_message2(format(Fmt, Args)) -->
  110    [ Fmt-Args ].
  111
  112make_message_lines([], T, T) :- !.
  113make_message_lines([Last],  ['~w'-[Last]|T], T) :- !.
  114make_message_lines([L0|LT], ['~w'-[L0],nl|T0], T) :-
  115    make_message_lines(LT, T0, T).
  116
  117term_message(Term) -->
  118    {var(Term)},
  119    !,
  120    [ 'Unknown error term: ~p'-[Term] ].
  121term_message(Term) -->
  122    prolog:error_message(Term).
  123term_message(Term) -->
  124    iso_message(Term).
  125term_message(Term) -->
  126    swi_message(Term).
  127term_message(Term) -->
  128    [ 'Unknown error term: ~p'-[Term] ].
  129
  130iso_message(resource_error(Missing)) -->
  131    [ 'Not enough resources: ~w'-[Missing] ].
  132iso_message(type_error(evaluable, Actual)) -->
  133    { callable(Actual) },
  134    [ 'Arithmetic: `~p'' is not a function'-[Actual] ].
  135iso_message(type_error(free_of_attvar, Actual)) -->
  136    [ 'Type error: `~W'' contains attributed variables'-
  137      [Actual,[portray(true), attributes(portray)]] ].
  138iso_message(type_error(Expected, Actual)) -->
  139    [ 'Type error: `~w'' expected, found `~p'''-[Expected, Actual] ],
  140    type_error_comment(Expected, Actual).
  141iso_message(domain_error(Domain, Actual)) -->
  142    [ 'Domain error: '-[] ], domain(Domain),
  143    [ ' expected, found `~p'''-[Actual] ].
  144iso_message(instantiation_error) -->
  145    [ 'Arguments are not sufficiently instantiated' ].
  146iso_message(uninstantiation_error(Var)) -->
  147    [ 'Uninstantiated argument expected, found ~p'-[Var] ].
  148iso_message(representation_error(What)) -->
  149    [ 'Cannot represent due to `~w'''-[What] ].
  150iso_message(permission_error(Action, Type, Object)) -->
  151    permission_error(Action, Type, Object).
  152iso_message(evaluation_error(Which)) -->
  153    [ 'Arithmetic: evaluation error: `~p'''-[Which] ].
  154iso_message(existence_error(procedure, Proc)) -->
  155    [ 'Unknown procedure: ~q'-[Proc] ],
  156    unknown_proc_msg(Proc).
  157iso_message(existence_error(answer_variable, Var)) -->
  158    [ '$~w was not bound by a previous query'-[Var] ].
  159iso_message(existence_error(Type, Object)) -->
  160    [ '~w `~p'' does not exist'-[Type, Object] ].
  161iso_message(existence_error(Type, Object, In)) --> % not ISO
  162    [ '~w `~p'' does not exist in ~p'-[Type, Object, In] ].
  163iso_message(busy(Type, Object)) -->
  164    [ '~w `~p'' is busy'-[Type, Object] ].
  165iso_message(syntax_error(swi_backslash_newline)) -->
  166    [ 'Deprecated ... \\<newline><white>*.  Use \\c' ].
  167iso_message(syntax_error(Id)) -->
  168    [ 'Syntax error: ' ],
  169    syntax_error(Id).
  170iso_message(occurs_check(Var, In)) -->
  171    [ 'Cannot unify ~p with ~p: would create an infinite tree'-[Var, In] ].
 permission_error(Action, Type, Object)//
Translate permission errors. Most follow te pattern "No permission to Action Type Object", but some are a bit different.
  178permission_error(Action, built_in_procedure, Pred) -->
  179    { user_predicate_indicator(Pred, PI)
  180    },
  181    [ 'No permission to ~w built-in predicate `~p'''-[Action, PI] ],
  182    (   {Action \== export}
  183    ->  [ nl,
  184          'Use :- redefine_system_predicate(+Head) if redefinition is intended'
  185        ]
  186    ;   []
  187    ).
  188permission_error(import_into(Dest), procedure, Pred) -->
  189    [ 'No permission to import ~p into ~w'-[Pred, Dest] ].
  190permission_error(Action, static_procedure, Proc) -->
  191    [ 'No permission to ~w static procedure `~p'''-[Action, Proc] ],
  192    defined_definition('Defined', Proc).
  193permission_error(input, stream, Stream) -->
  194    [ 'No permission to read from output stream `~p'''-[Stream] ].
  195permission_error(output, stream, Stream) -->
  196    [ 'No permission to write to input stream `~p'''-[Stream] ].
  197permission_error(input, text_stream, Stream) -->
  198    [ 'No permission to read bytes from TEXT stream `~p'''-[Stream] ].
  199permission_error(output, text_stream, Stream) -->
  200    [ 'No permission to write bytes to TEXT stream `~p'''-[Stream] ].
  201permission_error(input, binary_stream, Stream) -->
  202    [ 'No permission to read characters from binary stream `~p'''-[Stream] ].
  203permission_error(output, binary_stream, Stream) -->
  204    [ 'No permission to write characters to binary stream `~p'''-[Stream] ].
  205permission_error(open, source_sink, alias(Alias)) -->
  206    [ 'No permission to reuse alias "~p": already taken'-[Alias] ].
  207permission_error(tnot, non_tabled_procedure, Pred) -->
  208    [ 'The argument of tnot/1 is not tabled: ~p'-[Pred] ].
  209permission_error(Action, Type, Object) -->
  210    [ 'No permission to ~w ~w `~p'''-[Action, Type, Object] ].
  211
  212
  213unknown_proc_msg(_:(^)/2) -->
  214    !,
  215    unknown_proc_msg((^)/2).
  216unknown_proc_msg((^)/2) -->
  217    !,
  218    [nl, '  ^/2 can only appear as the 2nd argument of setof/3 and bagof/3'].
  219unknown_proc_msg((:-)/2) -->
  220    !,
  221    [nl, '  Rules must be loaded from a file'],
  222    faq('ToplevelMode').
  223unknown_proc_msg((:-)/1) -->
  224    !,
  225    [nl, '  Directives must be loaded from a file'],
  226    faq('ToplevelMode').
  227unknown_proc_msg((?-)/1) -->
  228    !,
  229    [nl, '  ?- is the Prolog prompt'],
  230    faq('ToplevelMode').
  231unknown_proc_msg(Proc) -->
  232    { dwim_predicates(Proc, Dwims) },
  233    (   {Dwims \== []}
  234    ->  [nl, '  However, there are definitions for:', nl],
  235        dwim_message(Dwims)
  236    ;   []
  237    ).
  238
  239dependency_error(shared(Shared), private(Private)) -->
  240    [ 'Shared table for ~p may not depend on private ~p'-[Shared, Private] ].
  241dependency_error(Dep, monotonic(On)) -->
  242    { '$pi_head'(PI, Dep),
  243      '$pi_head'(MPI, On)
  244    },
  245    [ 'Dependent ~p on monotonic predicate ~p is not monotonic or incremental'-
  246      [PI, MPI]
  247    ].
  248
  249faq(Page) -->
  250    [nl, '  See FAQ at https://www.swi-prolog.org/FAQ/', Page, '.txt' ].
  251
  252type_error_comment(_Expected, Actual) -->
  253    { type_of(Actual, Type),
  254      (   sub_atom(Type, 0, 1, _, First),
  255          memberchk(First, [a,e,i,o,u])
  256      ->  Article = an
  257      ;   Article = a
  258      )
  259    },
  260    [ ' (~w ~w)'-[Article, Type] ].
  261
  262type_of(Term, Type) :-
  263    (   attvar(Term)      -> Type = attvar
  264    ;   var(Term)         -> Type = var
  265    ;   atom(Term)        -> Type = atom
  266    ;   integer(Term)     -> Type = integer
  267    ;   string(Term)      -> Type = string
  268    ;   Term == []        -> Type = empty_list
  269    ;   blob(Term, BlobT) -> blob_type(BlobT, Type)
  270    ;   rational(Term)    -> Type = rational
  271    ;   float(Term)       -> Type = float
  272    ;   is_stream(Term)   -> Type = stream
  273    ;   is_dict(Term)     -> Type = dict
  274    ;   is_list(Term)     -> Type = list
  275    ;   cyclic_term(Term) -> Type = cyclic
  276    ;   compound(Term)    -> Type = compound
  277    ;                        Type = unknown
  278    ).
  279
  280blob_type(BlobT, Type) :-
  281    atom_concat(BlobT, '_reference', Type).
  282
  283syntax_error(end_of_clause) -->
  284    [ 'Unexpected end of clause' ].
  285syntax_error(end_of_clause_expected) -->
  286    [ 'End of clause expected' ].
  287syntax_error(end_of_file) -->
  288    [ 'Unexpected end of file' ].
  289syntax_error(end_of_file_in_block_comment) -->
  290    [ 'End of file in /* ... */ comment' ].
  291syntax_error(end_of_file_in_quoted(Quote)) -->
  292    [ 'End of file in quoted ' ],
  293    quoted_type(Quote).
  294syntax_error(illegal_number) -->
  295    [ 'Illegal number' ].
  296syntax_error(long_atom) -->
  297    [ 'Atom too long (see style_check/1)' ].
  298syntax_error(long_string) -->
  299    [ 'String too long (see style_check/1)' ].
  300syntax_error(operator_clash) -->
  301    [ 'Operator priority clash' ].
  302syntax_error(operator_expected) -->
  303    [ 'Operator expected' ].
  304syntax_error(operator_balance) -->
  305    [ 'Unbalanced operator' ].
  306syntax_error(quoted_punctuation) -->
  307    [ 'Operand expected, unquoted comma or bar found' ].
  308syntax_error(list_rest) -->
  309    [ 'Unexpected comma or bar in rest of list' ].
  310syntax_error(cannot_start_term) -->
  311    [ 'Illegal start of term' ].
  312syntax_error(punct(Punct, End)) -->
  313    [ 'Unexpected `~w\' before `~w\''-[Punct, End] ].
  314syntax_error(undefined_char_escape(C)) -->
  315    [ 'Unknown character escape in quoted atom or string: `\\~w\''-[C] ].
  316syntax_error(void_not_allowed) -->
  317    [ 'Empty argument list "()"' ].
  318syntax_error(Message) -->
  319    [ '~w'-[Message] ].
  320
  321quoted_type('\'') --> [atom].
  322quoted_type('\"') --> { current_prolog_flag(double_quotes, Type) }, [Type-[]].
  323quoted_type('\`') --> { current_prolog_flag(back_quotes, Type) }, [Type-[]].
  324
  325domain(range(Low,High)) -->
  326    !,
  327    ['[~q..~q]'-[Low,High] ].
  328domain(Domain) -->
  329    ['`~w\''-[Domain] ].
 tabling_existence_error(+Ball, +Context)//
Called on invalid shift/1 calls. Track those that result from tabling errors.
  336tabling_existence_error(Ball, Context) -->
  337    { table_shift_ball(Ball) },
  338    [ 'Tabling dependency error' ],
  339    swi_extra(Context).
  340
  341table_shift_ball(dependency(_Head)).
  342table_shift_ball(dependency(_Skeleton, _Trie, _Mono)).
  343table_shift_ball(call_info(_Skeleton, _Status)).
  344table_shift_ball(call_info(_GenSkeleton, _Skeleton, _Status)).
 dwim_predicates(+PI, -Dwims)
Find related predicate indicators.
  350dwim_predicates(Module:Name/_Arity, Dwims) :-
  351    !,
  352    findall(Dwim, dwim_predicate(Module:Name, Dwim), Dwims).
  353dwim_predicates(Name/_Arity, Dwims) :-
  354    findall(Dwim, dwim_predicate(user:Name, Dwim), Dwims).
  355
  356dwim_message([]) --> [].
  357dwim_message([M:Head|T]) -->
  358    { hidden_module(M),
  359      !,
  360      functor(Head, Name, Arity)
  361    },
  362    [ '        ~q'-[Name/Arity], nl ],
  363    dwim_message(T).
  364dwim_message([Module:Head|T]) -->
  365    !,
  366    { functor(Head, Name, Arity)
  367    },
  368    [ '        ~q'-[Module:Name/Arity], nl],
  369    dwim_message(T).
  370dwim_message([Head|T]) -->
  371    {functor(Head, Name, Arity)},
  372    [ '        ~q'-[Name/Arity], nl],
  373    dwim_message(T).
  374
  375
  376swi_message(io_error(Op, Stream)) -->
  377    [ 'I/O error in ~w on stream ~p'-[Op, Stream] ].
  378swi_message(thread_error(TID, false)) -->
  379    [ 'Thread ~p died due to failure:'-[TID] ].
  380swi_message(thread_error(TID, exception(Error))) -->
  381    [ 'Thread ~p died abnormally:'-[TID], nl ],
  382    translate_message(Error).
  383swi_message(dependency_error(Tabled, DependsOn)) -->
  384    dependency_error(Tabled, DependsOn).
  385swi_message(shell(execute, Cmd)) -->
  386    [ 'Could not execute `~w'''-[Cmd] ].
  387swi_message(shell(signal(Sig), Cmd)) -->
  388    [ 'Caught signal ~d on `~w'''-[Sig, Cmd] ].
  389swi_message(format(Fmt, Args)) -->
  390    [ Fmt-Args ].
  391swi_message(signal(Name, Num)) -->
  392    [ 'Caught signal ~d (~w)'-[Num, Name] ].
  393swi_message(limit_exceeded(Limit, MaxVal)) -->
  394    [ 'Exceeded ~w limit (~w)'-[Limit, MaxVal] ].
  395swi_message(goal_failed(Goal)) -->
  396    [ 'goal unexpectedly failed: ~p'-[Goal] ].
  397swi_message(shared_object(_Action, Message)) --> % Message = dlerror()
  398    [ '~w'-[Message] ].
  399swi_message(system_error(Error)) -->
  400    [ 'error in system call: ~w'-[Error]
  401    ].
  402swi_message(system_error) -->
  403    [ 'error in system call'
  404    ].
  405swi_message(failure_error(Goal)) -->
  406    [ 'Goal failed: ~p'-[Goal] ].
  407swi_message(timeout_error(Op, Stream)) -->
  408    [ 'Timeout in ~w from ~p'-[Op, Stream] ].
  409swi_message(not_implemented(Type, What)) -->
  410    [ '~w `~p\' is not implemented in this version'-[Type, What] ].
  411swi_message(context_error(nodirective, Goal)) -->
  412    { goal_to_predicate_indicator(Goal, PI) },
  413    [ 'Wrong context: ~p can only be used in a directive'-[PI] ].
  414swi_message(context_error(edit, no_default_file)) -->
  415    (   { current_prolog_flag(windows, true) }
  416    ->  [ 'Edit/0 can only be used after opening a \c
  417               Prolog file by double-clicking it' ]
  418    ;   [ 'Edit/0 can only be used with the "-s file" commandline option'
  419        ]
  420    ),
  421    [ nl, 'Use "?- edit(Topic)." or "?- emacs."' ].
  422swi_message(context_error(function, meta_arg(S))) -->
  423    [ 'Functions are not (yet) supported for meta-arguments of type ~q'-[S] ].
  424swi_message(format_argument_type(Fmt, Arg)) -->
  425    [ 'Illegal argument to format sequence ~~~w: ~p'-[Fmt, Arg] ].
  426swi_message(format(Msg)) -->
  427    [ 'Format error: ~w'-[Msg] ].
  428swi_message(conditional_compilation_error(unterminated, Where)) -->
  429    [ 'Unterminated conditional compilation from '-[] ],
  430    cond_location(Where).
  431swi_message(conditional_compilation_error(no_if, What)) -->
  432    [ ':- ~w without :- if'-[What] ].
  433swi_message(duplicate_key(Key)) -->
  434    [ 'Duplicate key: ~p'-[Key] ].
  435swi_message(initialization_error(failed, Goal, File:Line)) -->
  436    !,
  437    [ '~w:~w: ~p: false'-[File, Line, Goal] ].
  438swi_message(initialization_error(Error, Goal, File:Line)) -->
  439    [ '~w:~w: ~p '-[File, Line, Goal] ],
  440    translate_message(Error).
  441swi_message(qlf_format_error(File, Message)) -->
  442    [ '~w: Invalid QLF file: ~w'-[File, Message] ].
  443
  444cond_location(File:Line) -->
  445    { file_base_name(File, Base) },
  446    [ '~w:~d'-[Base, Line] ].
  447
  448swi_location(X) -->
  449    { var(X)
  450    },
  451    !,
  452    [].
  453swi_location(Context) -->
  454    prolog:message_location(Context),
  455    !.
  456swi_location(context(Caller, _Msg)) -->
  457    { ground(Caller)
  458    },
  459    !,
  460    caller(Caller).
  461swi_location(file(Path, Line, -1, _CharNo)) -->
  462    !,
  463    [ '~w:~d: '-[Path, Line] ].
  464swi_location(file(Path, Line, LinePos, _CharNo)) -->
  465    [ '~w:~d:~d: '-[Path, Line, LinePos] ].
  466swi_location(stream(Stream, Line, LinePos, CharNo)) -->
  467    (   { is_stream(Stream),
  468          stream_property(Stream, file_name(File))
  469        }
  470    ->  swi_location(file(File, Line, LinePos, CharNo))
  471    ;   [ 'Stream ~w:~d:~d '-[Stream, Line, LinePos] ]
  472    ).
  473swi_location(autoload(File:Line)) -->
  474    [ '~w:~w: '-[File, Line] ].
  475swi_location(_) -->
  476    [].
  477
  478caller(system:'$record_clause'/3) -->
  479    !,
  480    [].
  481caller(Module:Name/Arity) -->
  482    !,
  483    (   { \+ hidden_module(Module) }
  484    ->  [ '~q:~q/~w: '-[Module, Name, Arity] ]
  485    ;   [ '~q/~w: '-[Name, Arity] ]
  486    ).
  487caller(Name/Arity) -->
  488    [ '~q/~w: '-[Name, Arity] ].
  489caller(Caller) -->
  490    [ '~p: '-[Caller] ].
  491
  492
  493swi_extra(X) -->
  494    { var(X)
  495    },
  496    !,
  497    [].
  498swi_extra(Context) -->
  499    prolog:message_context(Context).
  500swi_extra(context(_, Msg)) -->
  501    { nonvar(Msg),
  502      Msg \== ''
  503    },
  504    !,
  505    swi_comment(Msg).
  506swi_extra(string(String, CharPos)) -->
  507    { sub_string(String, 0, CharPos, _, Before),
  508      sub_string(String, CharPos, _, 0, After)
  509    },
  510    [ nl, '~w'-[Before], nl, '** here **', nl, '~w'-[After] ].
  511swi_extra(_) -->
  512    [].
  513
  514swi_comment(already_from(Module)) -->
  515    !,
  516    [ ' (already imported from ~q)'-[Module] ].
  517swi_comment(directory(_Dir)) -->
  518    !,
  519    [ ' (is a directory)' ].
  520swi_comment(not_a_directory(_Dir)) -->
  521    !,
  522    [ ' (is not a directory)' ].
  523swi_comment(Msg) -->
  524    [ ' (~w)'-[Msg] ].
  525
  526
  527thread_context -->
  528    { thread_self(Me), Me \== main, thread_property(Me, id(Id)) },
  529    !,
  530    ['[Thread ~w] '-[Id]].
  531thread_context -->
  532    [].
  533
  534                 /*******************************
  535                 *        NORMAL MESSAGES       *
  536                 *******************************/
  537
  538prolog_message(initialization_error(_, E, File:Line)) -->
  539    !,
  540    [ '~w:~d: '-[File, Line],
  541      'Initialization goal raised exception:', nl
  542    ],
  543    translate_message(E).
  544prolog_message(initialization_error(Goal, E, _)) -->
  545    [ 'Initialization goal ~p raised exception:'-[Goal], nl ],
  546    translate_message(E).
  547prolog_message(initialization_failure(_Goal, File:Line)) -->
  548    !,
  549    [ '~w:~d: '-[File, Line],
  550      'Initialization goal failed'-[]
  551    ].
  552prolog_message(initialization_failure(Goal, _)) -->
  553    [ 'Initialization goal failed: ~p'-[Goal]
  554    ].
  555prolog_message(initialization_exception(E)) -->
  556    [ 'Prolog initialisation failed:', nl ],
  557    translate_message(E).
  558prolog_message(init_goal_syntax(Error, Text)) -->
  559    !,
  560    [ '-g ~w: '-[Text] ],
  561    translate_message(Error).
  562prolog_message(init_goal_failed(failed, @(Goal,File:Line))) -->
  563    !,
  564    [ '~w:~w: ~p: false'-[File, Line, Goal] ].
  565prolog_message(init_goal_failed(Error, @(Goal,File:Line))) -->
  566    !,
  567    [ '~w:~w: ~p '-[File, Line, Goal] ],
  568    translate_message(Error).
  569prolog_message(init_goal_failed(failed, Text)) -->
  570    !,
  571    [ '-g ~w: false'-[Text] ].
  572prolog_message(init_goal_failed(Error, Text)) -->
  573    !,
  574    [ '-g ~w: '-[Text] ],
  575    translate_message(Error).
  576prolog_message(unhandled_exception(E)) -->
  577    [ 'Unhandled exception: ' ],
  578    (   translate_message2(E)
  579    ->  []
  580    ;   [ '~p'-[E] ]
  581    ).
  582prolog_message(goal_failed(Context, Goal)) -->
  583    [ 'Goal (~w) failed: ~p'-[Context, Goal] ].
  584prolog_message(no_current_module(Module)) -->
  585    [ '~w is not a current module (created)'-[Module] ].
  586prolog_message(commandline_arg_type(Flag, Arg)) -->
  587    [ 'Bad argument to commandline option -~w: ~w'-[Flag, Arg] ].
  588prolog_message(missing_feature(Name)) -->
  589    [ 'This version of SWI-Prolog does not support ~w'-[Name] ].
  590prolog_message(singletons(_Term, List)) -->
  591    [ 'Singleton variables: ~w'-[List] ].
  592prolog_message(multitons(_Term, List)) -->
  593    [ 'Singleton-marked variables appearing more than once: ~w'-[List] ].
  594prolog_message(profile_no_cpu_time) -->
  595    [ 'No CPU-time info.  Check the SWI-Prolog manual for details' ].
  596prolog_message(non_ascii(Text, Type)) -->
  597    [ 'Unquoted ~w with non-portable characters: ~w'-[Type, Text] ].
  598prolog_message(io_warning(Stream, Message)) -->
  599    { stream_property(Stream, position(Position)),
  600      !,
  601      stream_position_data(line_count, Position, LineNo),
  602      stream_position_data(line_position, Position, LinePos),
  603      (   stream_property(Stream, file_name(File))
  604      ->  Obj = File
  605      ;   Obj = Stream
  606      )
  607    },
  608    [ '~p:~d:~d: ~w'-[Obj, LineNo, LinePos, Message] ].
  609prolog_message(io_warning(Stream, Message)) -->
  610    [ 'stream ~p: ~w'-[Stream, Message] ].
  611prolog_message(option_usage(pldoc)) -->
  612    [ 'Usage: --pldoc[=port]' ].
  613prolog_message(interrupt(begin)) -->
  614    [ 'Action (h for help) ? ', flush ].
  615prolog_message(interrupt(end)) -->
  616    [ 'continue' ].
  617prolog_message(interrupt(trace)) -->
  618    [ 'continue (trace mode)' ].
  619prolog_message(unknown_in_module_user) -->
  620    [ 'Using a non-error value for unknown in the global module', nl,
  621      'causes most of the development environment to stop working.', nl,
  622      'Please use :- dynamic or limit usage of unknown to a module.', nl,
  623      'See https://www.swi-prolog.org/howto/database.html'
  624    ].
  625prolog_message(deprecated(What)) -->
  626    deprecated(What).
  627prolog_message(untable(PI)) -->
  628    [ 'Reconsult: removed tabling for ~p'-[PI] ].
  629
  630
  631                 /*******************************
  632                 *         LOADING FILES        *
  633                 *******************************/
  634
  635prolog_message(modify_active_procedure(Who, What)) -->
  636    [ '~p: modified active procedure ~p'-[Who, What] ].
  637prolog_message(load_file(failed(user:File))) -->
  638    [ 'Failed to load ~p'-[File] ].
  639prolog_message(load_file(failed(Module:File))) -->
  640    [ 'Failed to load ~p into module ~p'-[File, Module] ].
  641prolog_message(load_file(failed(File))) -->
  642    [ 'Failed to load ~p'-[File] ].
  643prolog_message(mixed_directive(Goal)) -->
  644    [ 'Cannot pre-compile mixed load/call directive: ~p'-[Goal] ].
  645prolog_message(cannot_redefine_comma) -->
  646    [ 'Full stop in clause-body?  Cannot redefine ,/2' ].
  647prolog_message(illegal_autoload_index(Dir, Term)) -->
  648    [ 'Illegal term in INDEX file of directory ~w: ~w'-[Dir, Term] ].
  649prolog_message(redefined_procedure(Type, Proc)) -->
  650    [ 'Redefined ~w procedure ~p'-[Type, Proc] ],
  651    defined_definition('Previously defined', Proc).
  652prolog_message(declare_module(Module, abolish(Predicates))) -->
  653    [ 'Loading module ~w abolished: ~p'-[Module, Predicates] ].
  654prolog_message(import_private(Module, Private)) -->
  655    [ 'import/1: ~p is not exported (still imported into ~q)'-
  656      [Private, Module]
  657    ].
  658prolog_message(ignored_weak_import(Into, From:PI)) -->
  659    [ 'Local definition of ~p overrides weak import from ~q'-
  660      [Into:PI, From]
  661    ].
  662prolog_message(undefined_export(Module, PI)) -->
  663    [ 'Exported procedure ~q:~q is not defined'-[Module, PI] ].
  664prolog_message(no_exported_op(Module, Op)) -->
  665    [ 'Operator ~q:~q is not exported (still defined)'-[Module, Op] ].
  666prolog_message(discontiguous((-)/2,_)) -->
  667    prolog_message(minus_in_identifier).
  668prolog_message(discontiguous(Proc,Current)) -->
  669    [ 'Clauses of ', ansi(code, '~p', [Proc]),
  670      ' are not together in the source-file', nl ],
  671    current_definition(Proc, 'Earlier definition at '),
  672    [ 'Current predicate: ', ansi(code, '~p', [Current]), nl,
  673      'Use ', ansi(code, ':- discontiguous ~p.', [Proc]),
  674      ' to suppress this message'
  675    ].
  676prolog_message(decl_no_effect(Goal)) -->
  677    [ 'Deprecated declaration has no effect: ~p'-[Goal] ].
  678prolog_message(load_file(start(Level, File))) -->
  679    [ '~|~t~*+Loading '-[Level] ],
  680    load_file(File),
  681    [ ' ...' ].
  682prolog_message(include_file(start(Level, File))) -->
  683    [ '~|~t~*+include '-[Level] ],
  684    load_file(File),
  685    [ ' ...' ].
  686prolog_message(include_file(done(Level, File))) -->
  687    [ '~|~t~*+included '-[Level] ],
  688    load_file(File).
  689prolog_message(load_file(done(Level, File, Action, Module, Time, Clauses))) -->
  690    [ '~|~t~*+'-[Level] ],
  691    load_file(File),
  692    [ ' ~w'-[Action] ],
  693    load_module(Module),
  694    [ ' ~2f sec, ~D clauses'-[Time, Clauses] ].
  695prolog_message(dwim_undefined(Goal, Alternatives)) -->
  696    { goal_to_predicate_indicator(Goal, Pred)
  697    },
  698    [ 'Unknown procedure: ~q'-[Pred], nl,
  699      '    However, there are definitions for:', nl
  700    ],
  701    dwim_message(Alternatives).
  702prolog_message(dwim_correct(Into)) -->
  703    [ 'Correct to: ~q? '-[Into], flush ].
  704prolog_message(error(loop_error(Spec), file_search(Used))) -->
  705    [ 'File search: too many levels of indirections on: ~p'-[Spec], nl,
  706      '    Used alias expansions:', nl
  707    ],
  708    used_search(Used).
  709prolog_message(minus_in_identifier) -->
  710    [ 'The "-" character should not be used to separate words in an', nl,
  711      'identifier.  Check the SWI-Prolog FAQ for details.'
  712    ].
  713prolog_message(qlf(removed_after_error(File))) -->
  714    [ 'Removed incomplete QLF file ~w'-[File] ].
  715prolog_message(qlf(recompile(Spec,_Pl,_Qlf,Reason))) -->
  716    [ '~p: recompiling QLF file'-[Spec] ],
  717    qlf_recompile_reason(Reason).
  718prolog_message(qlf(can_not_recompile(Spec,QlfFile,_Reason))) -->
  719    [ '~p: can not recompile "~w" (access denied)'-[Spec, QlfFile], nl,
  720      '\tLoading from source'-[]
  721    ].
  722prolog_message(qlf(system_lib_out_of_date(Spec,QlfFile))) -->
  723    [ '~p: can not recompile "~w" (access denied)'-[Spec, QlfFile], nl,
  724      '\tLoading QlfFile'-[]
  725    ].
  726prolog_message(redefine_module(Module, OldFile, File)) -->
  727    [ 'Module "~q" already loaded from ~w.'-[Module, OldFile], nl,
  728      'Wipe and reload from ~w? '-[File], flush
  729    ].
  730prolog_message(redefine_module_reply) -->
  731    [ 'Please answer y(es), n(o) or a(bort)' ].
  732prolog_message(reloaded_in_module(Absolute, OldContext, LM)) -->
  733    [ '~w was previously loaded in module ~w'-[Absolute, OldContext], nl,
  734      '\tnow it is reloaded into module ~w'-[LM] ].
  735prolog_message(expected_layout(Expected, Pos)) -->
  736    [ 'Layout data: expected ~w, found: ~p'-[Expected, Pos] ].
  737
  738defined_definition(Message, Spec) -->
  739    { strip_module(user:Spec, M, Name/Arity),
  740      functor(Head, Name, Arity),
  741      predicate_property(M:Head, file(File)),
  742      predicate_property(M:Head, line_count(Line))
  743    },
  744    !,
  745    [ nl, '~w at ~w:~d'-[Message, File,Line] ].
  746defined_definition(_, _) --> [].
  747
  748used_search([]) -->
  749    [].
  750used_search([Alias=Expanded|T]) -->
  751    [ '        file_search_path(~p, ~p)'-[Alias, Expanded], nl ],
  752    used_search(T).
  753
  754load_file(file(Spec, _Path)) -->
  755    (   {atomic(Spec)}
  756    ->  [ '~w'-[Spec] ]
  757    ;   [ '~p'-[Spec] ]
  758    ).
  759%load_file(file(_, Path)) -->
  760%       [ '~w'-[Path] ].
  761
  762load_module(user) --> !.
  763load_module(system) --> !.
  764load_module(Module) -->
  765    [ ' into ~w'-[Module] ].
  766
  767goal_to_predicate_indicator(Goal, PI) :-
  768    strip_module(Goal, Module, Head),
  769    callable_name_arity(Head, Name, Arity),
  770    user_predicate_indicator(Module:Name/Arity, PI).
  771
  772callable_name_arity(Goal, Name, Arity) :-
  773    compound(Goal),
  774    !,
  775    compound_name_arity(Goal, Name, Arity).
  776callable_name_arity(Goal, Goal, 0) :-
  777    atom(Goal).
  778
  779user_predicate_indicator(Module:PI, PI) :-
  780    hidden_module(Module),
  781    !.
  782user_predicate_indicator(PI, PI).
  783
  784hidden_module(user) :- !.
  785hidden_module(system) :- !.
  786hidden_module(M) :-
  787    sub_atom(M, 0, _, _, $).
  788
  789current_definition(Proc, Prefix) -->
  790    { pi_uhead(Proc, Head),
  791      predicate_property(Head, file(File)),
  792      predicate_property(Head, line_count(Line))
  793    },
  794    [ '~w~w:~d'-[Prefix,File,Line], nl ].
  795current_definition(_, _) --> [].
  796
  797pi_uhead(Module:Name/Arity, Module:Head) :-
  798    !,
  799    atom(Module), atom(Name), integer(Arity),
  800    functor(Head, Name, Arity).
  801pi_uhead(Name/Arity, user:Head) :-
  802    atom(Name), integer(Arity),
  803    functor(Head, Name, Arity).
  804
  805qlf_recompile_reason(old) -->
  806    !,
  807    [ ' (out of date)'-[] ].
  808qlf_recompile_reason(_) -->
  809    [ ' (incompatible with current Prolog version)'-[] ].
  810
  811prolog_message(file_search(cache(Spec, _Cond), Path)) -->
  812    [ 'File search: ~p --> ~p (cache)'-[Spec, Path] ].
  813prolog_message(file_search(found(Spec, Cond), Path)) -->
  814    [ 'File search: ~p --> ~p OK ~p'-[Spec, Path, Cond] ].
  815prolog_message(file_search(tried(Spec, Cond), Path)) -->
  816    [ 'File search: ~p --> ~p NO ~p'-[Spec, Path, Cond] ].
  817
  818                 /*******************************
  819                 *              GC              *
  820                 *******************************/
  821
  822prolog_message(agc(start)) -->
  823    thread_context,
  824    [ 'AGC: ', flush ].
  825prolog_message(agc(done(Collected, Remaining, Time))) -->
  826    [ at_same_line,
  827      'reclaimed ~D atoms in ~3f sec. (remaining: ~D)'-
  828      [Collected, Time, Remaining]
  829    ].
  830prolog_message(cgc(start)) -->
  831    thread_context,
  832    [ 'CGC: ', flush ].
  833prolog_message(cgc(done(CollectedClauses, _CollectedBytes,
  834                        RemainingBytes, Time))) -->
  835    [ at_same_line,
  836      'reclaimed ~D clauses in ~3f sec. (pending: ~D bytes)'-
  837      [CollectedClauses, Time, RemainingBytes]
  838    ].
  839
  840		 /*******************************
  841		 *        STACK OVERFLOW	*
  842		 *******************************/
  843
  844out_of_stack(Context) -->
  845    { human_stack_size(Context.localused,   Local),
  846      human_stack_size(Context.globalused,  Global),
  847      human_stack_size(Context.trailused,   Trail),
  848      human_stack_size(Context.stack_limit, Limit),
  849      LCO is (100*(Context.depth - Context.environments))/Context.depth
  850    },
  851    [ 'Stack limit (~s) exceeded'-[Limit], nl,
  852      '  Stack sizes: local: ~s, global: ~s, trail: ~s'-[Local,Global,Trail], nl,
  853      '  Stack depth: ~D, last-call: ~0f%, Choice points: ~D'-
  854         [Context.depth, LCO, Context.choicepoints], nl
  855    ],
  856    overflow_reason(Context, Resolve),
  857    resolve_overflow(Resolve).
  858
  859human_stack_size(Size, String) :-
  860    Size < 100,
  861    format(string(String), '~dKb', [Size]).
  862human_stack_size(Size, String) :-
  863    Size < 100 000,
  864    Value is Size / 1024,
  865    format(string(String), '~1fMb', [Value]).
  866human_stack_size(Size, String) :-
  867    Value is Size / (1024*1024),
  868    format(string(String), '~1fGb', [Value]).
  869
  870overflow_reason(Context, fix) -->
  871    show_non_termination(Context),
  872    !.
  873overflow_reason(Context, enlarge) -->
  874    { Stack = Context.get(stack) },
  875    !,
  876    [ '  In:'-[], nl ],
  877    stack(Stack).
  878overflow_reason(_Context, enlarge) -->
  879    [ '  Insufficient global stack'-[] ].
  880
  881show_non_termination(Context) -->
  882    (   { Stack = Context.get(cycle) }
  883    ->  [ '  Probable infinite recursion (cycle):'-[], nl ]
  884    ;   { Stack = Context.get(non_terminating) }
  885    ->  [ '  Possible non-terminating recursion:'-[], nl ]
  886    ),
  887    stack(Stack).
  888
  889stack([]) --> [].
  890stack([frame(Depth, M:Goal, _)|T]) -->
  891    [ '    [~D] ~q:'-[Depth, M] ],
  892    stack_goal(Goal),
  893    [ nl ],
  894    stack(T).
  895
  896stack_goal(Goal) -->
  897    { compound(Goal),
  898      !,
  899      compound_name_arity(Goal, Name, Arity)
  900    },
  901    [ '~q('-[Name] ],
  902    stack_goal_args(1, Arity, Goal),
  903    [ ')'-[] ].
  904stack_goal(Goal) -->
  905    [ '~q'-[Goal] ].
  906
  907stack_goal_args(I, Arity, Goal) -->
  908    { I =< Arity,
  909      !,
  910      arg(I, Goal, A),
  911      I2 is I + 1
  912    },
  913    stack_goal_arg(A),
  914    (   { I2 =< Arity }
  915    ->  [ ', '-[] ],
  916        stack_goal_args(I2, Arity, Goal)
  917    ;   []
  918    ).
  919stack_goal_args(_, _, _) -->
  920    [].
  921
  922stack_goal_arg(A) -->
  923    { nonvar(A),
  924      A = [Len|T],
  925      !
  926    },
  927    (   {Len == cyclic_term}
  928    ->  [ '[cyclic list]'-[] ]
  929    ;   {T == []}
  930    ->  [ '[length:~D]'-[Len] ]
  931    ;   [ '[length:~D|~p]'-[Len, T] ]
  932    ).
  933stack_goal_arg(A) -->
  934    { nonvar(A),
  935      A = _/_,
  936      !
  937    },
  938    [ '<compound ~p>'-[A] ].
  939stack_goal_arg(A) -->
  940    [ '~p'-[A] ].
  941
  942resolve_overflow(fix) -->
  943    [].
  944resolve_overflow(enlarge) -->
  945    { current_prolog_flag(stack_limit, LimitBytes),
  946      NewLimit is LimitBytes * 2
  947    },
  948    [ nl,
  949      'Use the --stack_limit=size[KMG] command line option or'-[], nl,
  950      '?- set_prolog_flag(stack_limit, ~I). to double the limit.'-[NewLimit]
  951    ].
  952
  953
  954                 /*******************************
  955                 *        MAKE/AUTOLOAD         *
  956                 *******************************/
  957
  958prolog_message(make(reload(Files))) -->
  959    { length(Files, N)
  960    },
  961    [ 'Make: reloading ~D files'-[N] ].
  962prolog_message(make(done(_Files))) -->
  963    [ 'Make: finished' ].
  964prolog_message(make(library_index(Dir))) -->
  965    [ 'Updating index for library ~w'-[Dir] ].
  966prolog_message(autoload(Pred, File)) -->
  967    thread_context,
  968    [ 'autoloading ~p from ~w'-[Pred, File] ].
  969prolog_message(autoload(read_index(Dir))) -->
  970    [ 'Loading autoload index for ~w'-[Dir] ].
  971prolog_message(autoload(disabled(Loaded))) -->
  972    [ 'Disabled autoloading (loaded ~D files)'-[Loaded] ].
  973prolog_message(autoload(already_defined(PI, From))) -->
  974    [ ansi(code, '~p', [PI]) ],
  975    (   { '$pi_head'(PI, Head),
  976          predicate_property(Head, built_in)
  977        }
  978    ->  [' is a built-in predicate']
  979    ;   [ ' is already imported from module ',
  980          ansi(code, '~p', [From])
  981        ]
  982    ).
  983
  984swi_message(autoload(Msg)) -->
  985    [ nl, '  ' ],
  986    autoload_message(Msg).
  987
  988autoload_message(not_exported(PI, Spec, _FullFile, _Exports)) -->
  989    [ ansi(code, '~w', [Spec]),
  990      ' does not export ',
  991      ansi(code, '~p', [PI])
  992    ].
  993autoload_message(no_file(Spec)) -->
  994    [ ansi(code, '~p', [Spec]), ': No such file' ].
  995
  996
  997                 /*******************************
  998                 *       COMPILER WARNINGS      *
  999                 *******************************/
 1000
 1001% print warnings about dubious code raised by the compiler.
 1002% TBD: pass in PC to produce exact error locations.
 1003
 1004prolog_message(compiler_warnings(Clause, Warnings0)) -->
 1005    {   print_goal_options(DefOptions),
 1006        (   prolog_load_context(variable_names, VarNames)
 1007        ->  warnings_with_named_vars(Warnings0, VarNames, Warnings),
 1008            Options = [variable_names(VarNames)|DefOptions]
 1009        ;   Options = DefOptions,
 1010            Warnings = Warnings0
 1011        )
 1012    },
 1013    compiler_warnings(Warnings, Clause, Options).
 1014
 1015warnings_with_named_vars([], _, []).
 1016warnings_with_named_vars([H|T0], VarNames, [H|T]) :-
 1017    term_variables(H, Vars),
 1018    '$member'(V1, Vars),
 1019    '$member'(_=V2, VarNames),
 1020    V1 == V2,
 1021    !,
 1022    warnings_with_named_vars(T0, VarNames, T).
 1023warnings_with_named_vars([_|T0], VarNames, T) :-
 1024    warnings_with_named_vars(T0, VarNames, T).
 1025
 1026
 1027compiler_warnings([], _, _) --> [].
 1028compiler_warnings([H|T], Clause, Options) -->
 1029    (   compiler_warning(H, Clause, Options)
 1030    ->  []
 1031    ;   [ 'Unknown compiler warning: ~W'-[H,Options] ]
 1032    ),
 1033    (   {T==[]}
 1034    ->  []
 1035    ;   [nl]
 1036    ),
 1037    compiler_warnings(T, Clause, Options).
 1038
 1039compiler_warning(eq_vv(A,B), _Clause, Options) -->
 1040    (   { A == B }
 1041    ->  [ 'Test is always true: ~W'-[A==B, Options] ]
 1042    ;   [ 'Test is always false: ~W'-[A==B, Options] ]
 1043    ).
 1044compiler_warning(eq_singleton(A,B), _Clause, Options) -->
 1045    [ 'Test is always false: ~W'-[A==B, Options] ].
 1046compiler_warning(neq_vv(A,B), _Clause, Options) -->
 1047    (   { A \== B }
 1048    ->  [ 'Test is always true: ~W'-[A\==B, Options] ]
 1049    ;   [ 'Test is always false: ~W'-[A\==B, Options] ]
 1050    ).
 1051compiler_warning(neq_singleton(A,B), _Clause, Options) -->
 1052    [ 'Test is always true: ~W'-[A\==B, Options] ].
 1053compiler_warning(unify_singleton(A,B), _Clause, Options) -->
 1054    [ 'Unified variable is not used: ~W'-[A=B, Options] ].
 1055compiler_warning(always(Bool, Pred, Arg), _Clause, Options) -->
 1056    { Goal =.. [Pred,Arg] },
 1057    [ 'Test is always ~w: ~W'-[Bool, Goal, Options] ].
 1058compiler_warning(unbalanced_var(V), _Clause, Options) -->
 1059    [ 'Variable not introduced in all branches: ~W'-[V, Options] ].
 1060compiler_warning(branch_singleton(V), _Clause, Options) -->
 1061    [ 'Singleton variable in branch: ~W'-[V, Options] ].
 1062compiler_warning(negation_singleton(V), _Clause, Options) -->
 1063    [ 'Singleton variable in \\+: ~W'-[V, Options] ].
 1064compiler_warning(multiton(V), _Clause, Options) -->
 1065    [ 'Singleton-marked variable appears more than once: ~W'-[V, Options] ].
 1066
 1067print_goal_options(
 1068    [ quoted(true),
 1069      portray(true)
 1070    ]).
 1071
 1072
 1073                 /*******************************
 1074                 *      TOPLEVEL MESSAGES       *
 1075                 *******************************/
 1076
 1077prolog_message(version) -->
 1078    { current_prolog_flag(version_git, Version) },
 1079    !,
 1080    [ '~w'-[Version] ].
 1081prolog_message(version) -->
 1082    { current_prolog_flag(version_data, swi(Major,Minor,Patch,Options))
 1083    },
 1084    (   { memberchk(tag(Tag), Options) }
 1085    ->  [ '~w.~w.~w-~w'-[Major, Minor, Patch, Tag] ]
 1086    ;   [ '~w.~w.~w'-[Major, Minor, Patch] ]
 1087    ).
 1088prolog_message(address_bits) -->
 1089    { current_prolog_flag(address_bits, Bits)
 1090    },
 1091    !,
 1092    [ '~d bits, '-[Bits] ].
 1093prolog_message(threads) -->
 1094    { current_prolog_flag(threads, true)
 1095    },
 1096    !,
 1097    [ 'threaded, ' ].
 1098prolog_message(threads) -->
 1099    [].
 1100prolog_message(copyright) -->
 1101    [ 'SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.', nl,
 1102      'Please run ?- license. for legal details.'
 1103    ].
 1104prolog_message(user_versions) -->
 1105    (   { findall(Msg, prolog:version_msg(Msg), Msgs),
 1106          Msgs \== []
 1107        }
 1108    ->  [nl],
 1109        user_version_messages(Msgs)
 1110    ;   []
 1111    ).
 1112prolog_message(documentaton) -->
 1113    [ 'For online help and background, visit https://www.swi-prolog.org', nl,
 1114      'For built-in help, use ?- help(Topic). or ?- apropos(Word).'
 1115    ].
 1116prolog_message(welcome) -->
 1117    [ 'Welcome to SWI-Prolog (' ],
 1118    prolog_message(threads),
 1119    prolog_message(address_bits),
 1120    ['version ' ],
 1121    prolog_message(version),
 1122    [ ')', nl ],
 1123    prolog_message(copyright),
 1124    [ nl ],
 1125    prolog_message(user_versions),
 1126    [ nl ],
 1127    prolog_message(documentaton),
 1128    [ nl, nl ].
 1129prolog_message(about) -->
 1130    [ 'SWI-Prolog version (' ],
 1131    prolog_message(threads),
 1132    prolog_message(address_bits),
 1133    ['version ' ],
 1134    prolog_message(version),
 1135    [ ')', nl ],
 1136    prolog_message(copyright).
 1137prolog_message(halt) -->
 1138    [ 'halt' ].
 1139prolog_message(break(begin, Level)) -->
 1140    [ 'Break level ~d'-[Level] ].
 1141prolog_message(break(end, Level)) -->
 1142    [ 'Exit break level ~d'-[Level] ].
 1143prolog_message(var_query(_)) -->
 1144    [ '... 1,000,000 ............ 10,000,000 years later', nl, nl,
 1145      '~t~8|>> 42 << (last release gives the question)'
 1146    ].
 1147prolog_message(close_on_abort(Stream)) -->
 1148    [ 'Abort: closed stream ~p'-[Stream] ].
 1149prolog_message(cancel_halt(Reason)) -->
 1150    [ 'Halt cancelled: ~p'-[Reason] ].
 1151
 1152prolog_message(query(QueryResult)) -->
 1153    query_result(QueryResult).
 1154
 1155query_result(no) -->            % failure
 1156    [ ansi(truth(false), 'false.', []) ],
 1157    extra_line.
 1158query_result(yes(true, [])) -->      % prompt_alternatives_on: groundness
 1159    !,
 1160    [ ansi(truth(true), 'true.', []) ],
 1161    extra_line.
 1162query_result(yes(Delays, Residuals)) -->
 1163    result([], Delays, Residuals),
 1164    extra_line.
 1165query_result(done) -->          % user typed <CR>
 1166    extra_line.
 1167query_result(yes(Bindings, Delays, Residuals)) -->
 1168    result(Bindings, Delays, Residuals),
 1169    prompt(yes, Bindings, Delays, Residuals).
 1170query_result(more(Bindings, Delays, Residuals)) -->
 1171    result(Bindings, Delays, Residuals),
 1172    prompt(more, Bindings, Delays, Residuals).
 1173query_result(help) -->
 1174    [ nl, 'Actions:'-[], nl, nl,
 1175      '; (n, r, space, TAB): redo    t:          trace & redo'-[], nl,
 1176      'b:                    break   c (a, RET): exit'-[], nl,
 1177      'w:                    write   p           print'-[], nl,
 1178      'h (?):                help'-[],
 1179      nl, nl
 1180    ].
 1181query_result(action) -->
 1182    [ 'Action? '-[], flush ].
 1183query_result(confirm) -->
 1184    [ 'Please answer \'y\' or \'n\'? '-[], flush ].
 1185query_result(eof) -->
 1186    [ nl ].
 1187query_result(toplevel_open_line) -->
 1188    [].
 1189
 1190prompt(Answer, [], true, []-[]) -->
 1191    !,
 1192    prompt(Answer, empty).
 1193prompt(Answer, _, _, _) -->
 1194    !,
 1195    prompt(Answer, non_empty).
 1196
 1197prompt(yes, empty) -->
 1198    !,
 1199    [ ansi(truth(true), 'true.', []) ],
 1200    extra_line.
 1201prompt(yes, _) -->
 1202    !,
 1203    [ full_stop ],
 1204    extra_line.
 1205prompt(more, empty) -->
 1206    !,
 1207    [ ansi(truth(true), 'true ', []), flush ].
 1208prompt(more, _) -->
 1209    !,
 1210    [ ' '-[], flush ].
 1211
 1212result(Bindings, Delays, Residuals) -->
 1213    { current_prolog_flag(answer_write_options, Options0),
 1214      Options = [partial(true)|Options0],
 1215      GOptions = [priority(999)|Options0]
 1216    },
 1217    wfs_residual_program(Delays, GOptions),
 1218    bindings(Bindings, [priority(699)|Options]),
 1219    (   {Residuals == []-[]}
 1220    ->  bind_delays_sep(Bindings, Delays),
 1221        delays(Delays, GOptions)
 1222    ;   bind_res_sep(Bindings, Residuals),
 1223        residuals(Residuals, GOptions),
 1224        (   {Delays == true}
 1225        ->  []
 1226        ;   [','-[], nl],
 1227            delays(Delays, GOptions)
 1228        )
 1229    ).
 1230
 1231bindings([], _) -->
 1232    [].
 1233bindings([binding(Names,Skel,Subst)|T], Options) -->
 1234    { '$last'(Names, Name) },
 1235    var_names(Names), value(Name, Skel, Subst, Options),
 1236    (   { T \== [] }
 1237    ->  [ ','-[], nl ],
 1238        bindings(T, Options)
 1239    ;   []
 1240    ).
 1241
 1242var_names([Name]) -->
 1243    !,
 1244    [ '~w = '-[Name] ].
 1245var_names([Name1,Name2|T]) -->
 1246    !,
 1247    [ '~w = ~w, '-[Name1, Name2] ],
 1248    var_names([Name2|T]).
 1249
 1250
 1251value(Name, Skel, Subst, Options) -->
 1252    (   { var(Skel), Subst = [Skel=S] }
 1253    ->  { Skel = '$VAR'(Name) },
 1254        [ '~W'-[S, Options] ]
 1255    ;   [ '~W'-[Skel, Options] ],
 1256        substitution(Subst, Options)
 1257    ).
 1258
 1259substitution([], _) --> !.
 1260substitution([N=V|T], Options) -->
 1261    [ ', ', ansi(comment, '% where', []), nl,
 1262      '    ~w = ~W'-[N,V,Options] ],
 1263    substitutions(T, Options).
 1264
 1265substitutions([], _) --> [].
 1266substitutions([N=V|T], Options) -->
 1267    [ ','-[], nl, '    ~w = ~W'-[N,V,Options] ],
 1268    substitutions(T, Options).
 1269
 1270
 1271residuals(Normal-Hidden, Options) -->
 1272    residuals1(Normal, Options),
 1273    bind_res_sep(Normal, Hidden),
 1274    (   {Hidden == []}
 1275    ->  []
 1276    ;   [ansi(comment, '% with pending residual goals', []), nl]
 1277    ),
 1278    residuals1(Hidden, Options).
 1279
 1280residuals1([], _) -->
 1281    [].
 1282residuals1([G|Gs], Options) -->
 1283    (   { Gs \== [] }
 1284    ->  [ '~W,'-[G, Options], nl ],
 1285        residuals1(Gs, Options)
 1286    ;   [ '~W'-[G, Options] ]
 1287    ).
 1288
 1289wfs_residual_program(true, _Options) -->
 1290    !.
 1291wfs_residual_program(Goal, _Options) -->
 1292    { current_prolog_flag(toplevel_list_wfs_residual_program, true),
 1293      '$current_typein_module'(TypeIn),
 1294      (   current_predicate(delays_residual_program/2)
 1295      ->  true
 1296      ;   use_module(library(wfs), [delays_residual_program/2])
 1297      ),
 1298      delays_residual_program(TypeIn:Goal, TypeIn:Program),
 1299      Program \== []
 1300    },
 1301    !,
 1302    [ ansi(comment, '% WFS residual program', []), nl ],
 1303    [ ansi(wfs(residual_program), '~@', ['$messages':list_clauses(Program)]) ].
 1304wfs_residual_program(_, _) --> [].
 1305
 1306delays(true, _Options) -->
 1307    !.
 1308delays(Goal, Options) -->
 1309    { current_prolog_flag(toplevel_list_wfs_residual_program, true)
 1310    },
 1311    !,
 1312    [ ansi(truth(undefined), '~W', [Goal, Options]) ].
 1313delays(_, _Options) -->
 1314    [ ansi(truth(undefined), undefined, []) ].
 1315
 1316:- public list_clauses/1. 1317
 1318list_clauses([]).
 1319list_clauses([H|T]) :-
 1320    (   system_undefined(H)
 1321    ->  true
 1322    ;   portray_clause(user_output, H, [indent(4)])
 1323    ),
 1324    list_clauses(T).
 1325
 1326system_undefined((undefined :- tnot(undefined))).
 1327system_undefined((answer_count_restraint :- tnot(answer_count_restraint))).
 1328system_undefined((radial_restraint :- tnot(radial_restraint))).
 1329
 1330bind_res_sep(_, []) --> !.
 1331bind_res_sep(_, []-[]) --> !.
 1332bind_res_sep([], _) --> !.
 1333bind_res_sep(_, _) --> [','-[], nl].
 1334
 1335bind_delays_sep([], _) --> !.
 1336bind_delays_sep(_, true) --> !.
 1337bind_delays_sep(_, _) --> [','-[], nl].
 1338
 1339extra_line -->
 1340    { current_prolog_flag(toplevel_extra_white_line, true) },
 1341    !,
 1342    ['~N'-[]].
 1343extra_line -->
 1344    [].
 1345
 1346prolog_message(if_tty(Message)) -->
 1347    (   {current_prolog_flag(tty_control, true)}
 1348    ->  [ at_same_line | Message ]
 1349    ;   []
 1350    ).
 1351prolog_message(halt(Reason)) -->
 1352    [ '~w: halt'-[Reason] ].
 1353prolog_message(no_action(Char)) -->
 1354    [ 'Unknown action: ~c (h for help)'-[Char], nl ].
 1355
 1356prolog_message(history(help(Show, Help))) -->
 1357    [ 'History Commands:', nl,
 1358      '    !!.              Repeat last query', nl,
 1359      '    !nr.             Repeat query numbered <nr>', nl,
 1360      '    !str.            Repeat last query starting with <str>', nl,
 1361      '    !?str.           Repeat last query holding <str>', nl,
 1362      '    ^old^new.        Substitute <old> into <new> of last query', nl,
 1363      '    !nr^old^new.     Substitute in query numbered <nr>', nl,
 1364      '    !str^old^new.    Substitute in query starting with <str>', nl,
 1365      '    !?str^old^new.   Substitute in query holding <str>', nl,
 1366      '    ~w.~21|Show history list'-[Show], nl,
 1367      '    ~w.~21|Show this list'-[Help], nl, nl
 1368    ].
 1369prolog_message(history(no_event)) -->
 1370    [ '! No such event' ].
 1371prolog_message(history(bad_substitution)) -->
 1372    [ '! Bad substitution' ].
 1373prolog_message(history(expanded(Event))) -->
 1374    [ '~w.'-[Event] ].
 1375prolog_message(history(history(Events))) -->
 1376    history_events(Events).
 1377
 1378history_events([]) -->
 1379    [].
 1380history_events([Nr/Event|T]) -->
 1381    [ '~t~w   ~8|~W~W'-[ Nr,
 1382                         Event, [partial(true)],
 1383                         '.', [partial(true)]
 1384                       ],
 1385      nl
 1386    ],
 1387    history_events(T).
 1388
 1389
 1390user_version_messages([]) --> [].
 1391user_version_messages([H|T]) -->
 1392    user_version_message(H),
 1393    user_version_messages(T).
 user_version_message(+Term)
 1397user_version_message(Term) -->
 1398    translate_message2(Term), !, [nl].
 1399user_version_message(Atom) -->
 1400    [ '~w'-[Atom], nl ].
 1401
 1402
 1403                 /*******************************
 1404                 *       DEBUGGER MESSAGES      *
 1405                 *******************************/
 1406
 1407prolog_message(spy(Head)) -->
 1408    { goal_to_predicate_indicator(Head, Pred)
 1409    },
 1410    [ 'Spy point on ~p'-[Pred] ].
 1411prolog_message(nospy(Head)) -->
 1412    { goal_to_predicate_indicator(Head, Pred)
 1413    },
 1414    [ 'Spy point removed from ~p'-[Pred] ].
 1415prolog_message(trace_mode(OnOff)) -->
 1416    [ 'Trace mode switched to ~w'-[OnOff] ].
 1417prolog_message(debug_mode(OnOff)) -->
 1418    [ 'Debug mode switched to ~w'-[OnOff] ].
 1419prolog_message(debugging(OnOff)) -->
 1420    [ 'Debug mode is ~w'-[OnOff] ].
 1421prolog_message(spying([])) -->
 1422    !,
 1423    [ 'No spy points' ].
 1424prolog_message(spying(Heads)) -->
 1425    [ 'Spy points (see spy/1) on:', nl ],
 1426    predicate_list(Heads).
 1427prolog_message(trace(Head, [])) -->
 1428    !,
 1429    { goal_to_predicate_indicator(Head, Pred)
 1430    },
 1431    [ '        ~p: Not tracing'-[Pred], nl].
 1432prolog_message(trace(Head, Ports)) -->
 1433    { goal_to_predicate_indicator(Head, Pred)
 1434    },
 1435    [ '        ~p: ~w'-[Pred, Ports], nl].
 1436prolog_message(tracing([])) -->
 1437    !,
 1438    [ 'No traced predicates (see trace/1)' ].
 1439prolog_message(tracing(Heads)) -->
 1440    [ 'Trace points (see trace/1) on:', nl ],
 1441    tracing_list(Heads).
 1442
 1443predicate_list([]) -->                  % TBD: Share with dwim, etc.
 1444    [].
 1445predicate_list([H|T]) -->
 1446    { goal_to_predicate_indicator(H, Pred)
 1447    },
 1448    [ '        ~p'-[Pred], nl],
 1449    predicate_list(T).
 1450
 1451tracing_list([]) -->
 1452    [].
 1453tracing_list([trace(Head, Ports)|T]) -->
 1454    translate_message(trace(Head, Ports)),
 1455    tracing_list(T).
 1456
 1457prolog_message(frame(Frame, backtrace, _PC)) -->
 1458    !,
 1459    { prolog_frame_attribute(Frame, level, Level)
 1460    },
 1461    [ ansi(frame(level), '~t[~D] ~10|', [Level]) ],
 1462    frame_context(Frame),
 1463    frame_goal(Frame).
 1464prolog_message(frame(Frame, choice, PC)) -->
 1465    !,
 1466    prolog_message(frame(Frame, backtrace, PC)).
 1467prolog_message(frame(_, cut_call, _)) --> !, [].
 1468prolog_message(frame(Goal, trace(Port))) -->
 1469    !,
 1470    [ ' T ' ],
 1471    port(Port),
 1472    goal(Goal).
 1473prolog_message(frame(Frame, Port, _PC)) -->
 1474    frame_flags(Frame),
 1475    port(Port),
 1476    frame_level(Frame),
 1477    frame_context(Frame),
 1478    frame_depth_limit(Port, Frame),
 1479    frame_goal(Frame),
 1480    [ flush ].
 1481
 1482frame_goal(Frame) -->
 1483    { prolog_frame_attribute(Frame, goal, Goal)
 1484    },
 1485    goal(Goal).
 1486
 1487goal(Goal0) -->
 1488    { clean_goal(Goal0, Goal),
 1489      current_prolog_flag(debugger_write_options, Options)
 1490    },
 1491    [ '~W'-[Goal, Options] ].
 1492
 1493frame_level(Frame) -->
 1494    { prolog_frame_attribute(Frame, level, Level)
 1495    },
 1496    [ '(~D) '-[Level] ].
 1497
 1498frame_context(Frame) -->
 1499    (   { current_prolog_flag(debugger_show_context, true),
 1500          prolog_frame_attribute(Frame, context_module, Context)
 1501        }
 1502    ->  [ '[~w] '-[Context] ]
 1503    ;   []
 1504    ).
 1505
 1506frame_depth_limit(fail, Frame) -->
 1507    { prolog_frame_attribute(Frame, depth_limit_exceeded, true)
 1508    },
 1509    !,
 1510    [ '[depth-limit exceeded] ' ].
 1511frame_depth_limit(_, _) -->
 1512    [].
 1513
 1514frame_flags(Frame) -->
 1515    { prolog_frame_attribute(Frame, goal, Goal),
 1516      (   predicate_property(Goal, transparent)
 1517      ->  T = '^'
 1518      ;   T = ' '
 1519      ),
 1520      (   predicate_property(Goal, spying)
 1521      ->  S = '*'
 1522      ;   S = ' '
 1523      )
 1524    },
 1525    [ '~w~w '-[T, S] ].
 1526
 1527port(Port) -->
 1528    { port_name(Port, Name)
 1529    },
 1530    !,
 1531    [ ansi(port(Port), '~w: ', [Name]) ].
 1532
 1533port_name(call,      'Call').
 1534port_name(exit,      'Exit').
 1535port_name(fail,      'Fail').
 1536port_name(redo,      'Redo').
 1537port_name(unify,     'Unify').
 1538port_name(exception, 'Exception').
 1539
 1540clean_goal(M:Goal, Goal) :-
 1541    hidden_module(M),
 1542    !.
 1543clean_goal(M:Goal, Goal) :-
 1544    predicate_property(M:Goal, built_in),
 1545    !.
 1546clean_goal(Goal, Goal).
 1547
 1548
 1549                 /*******************************
 1550                 *        COMPATIBILITY         *
 1551                 *******************************/
 1552
 1553prolog_message(compatibility(renamed(Old, New))) -->
 1554    [ 'The predicate ~p has been renamed to ~p.'-[Old, New], nl,
 1555      'Please update your sources for compatibility with future versions.'
 1556    ].
 1557
 1558
 1559                 /*******************************
 1560                 *            THREADS           *
 1561                 *******************************/
 1562
 1563prolog_message(abnormal_thread_completion(Goal, exception(Ex))) -->
 1564    !,
 1565    [ 'Thread running "~p" died on exception: '-[Goal] ],
 1566    translate_message(Ex).
 1567prolog_message(abnormal_thread_completion(Goal, fail)) -->
 1568    [ 'Thread running "~p" died due to failure'-[Goal] ].
 1569prolog_message(threads_not_died(Running)) -->
 1570    [ 'The following threads wouldn\'t die: ~p'-[Running] ].
 1571
 1572
 1573                 /*******************************
 1574                 *             PACKS            *
 1575                 *******************************/
 1576
 1577prolog_message(pack(attached(Pack, BaseDir))) -->
 1578    [ 'Attached package ~w at ~q'-[Pack, BaseDir] ].
 1579prolog_message(pack(duplicate(Entry, OldDir, Dir))) -->
 1580    [ 'Package ~w already attached at ~q.'-[Entry,OldDir], nl,
 1581      '\tIgnoring version from ~q'- [Entry, OldDir, Dir]
 1582    ].
 1583prolog_message(pack(no_arch(Entry, Arch))) -->
 1584    [ 'Package ~w: no binary for architecture ~w'-[Entry, Arch] ].
 1585
 1586                 /*******************************
 1587                 *             MISC             *
 1588                 *******************************/
 1589
 1590prolog_message(null_byte_in_path(Component)) -->
 1591    [ '0-byte in PATH component: ~p (skipped directory)'-[Component] ].
 1592prolog_message(invalid_tmp_dir(Dir, Reason)) -->
 1593    [ 'Cannot use ~p as temporary file directory: ~w'-[Dir, Reason] ].
 1594prolog_message(ambiguous_stream_pair(Pair)) -->
 1595    [ 'Ambiguous operation on stream pair ~p'-[Pair] ].
 1596prolog_message(backcomp(init_file_moved(FoundFile))) -->
 1597    { absolute_file_name(app_config('init.pl'), InitFile,
 1598                         [ file_errors(fail)
 1599                         ])
 1600    },
 1601    [ 'The location of the config file has moved'-[], nl,
 1602      '  from "~w"'-[FoundFile], nl,
 1603      '  to   "~w"'-[InitFile], nl,
 1604      '  See https://www.swi-prolog.org/modified/config-files.html'-[]
 1605    ].
 1606
 1607		 /*******************************
 1608		 *          DEPRECATED		*
 1609		 *******************************/
 1610
 1611deprecated(Term) -->
 1612    prolog:deprecated(Term),
 1613    !.
 1614deprecated(set_prolog_stack(_Stack,limit)) -->
 1615    [ 'set_prolog_stack/2: limit(Size) sets the combined limit.'-[], nl,
 1616      'See https://www.swi-prolog.org/changes/stack-limit.html'
 1617    ].
 1618
 1619		 /*******************************
 1620		 *           TRIPWIRES		*
 1621		 *******************************/
 1622
 1623tripwire_message(Wire, Context) -->
 1624    [ 'Trapped tripwire ~w for '-[Wire] ],
 1625    tripwire_context(Wire, Context).
 1626
 1627tripwire_context(_, ATrie) -->
 1628    { '$is_answer_trie'(ATrie, _),
 1629      !,
 1630      '$tabling':atrie_goal(ATrie, QGoal),
 1631      user_predicate_indicator(QGoal, Goal)
 1632    },
 1633    [ '~p'-[Goal] ].
 1634tripwire_context(_, Ctx) -->
 1635    [ '~p'-[Ctx] ].
 1636
 1637
 1638		 /*******************************
 1639		 *        DEFAULT THEME		*
 1640		 *******************************/
 1641
 1642:- public default_theme/2. 1643
 1644default_theme(var,                    [fg(red)]).
 1645default_theme(code,                   [fg(blue)]).
 1646default_theme(comment,                [fg(green)]).
 1647default_theme(warning,                [fg(red)]).
 1648default_theme(error,                  [bold, fg(red)]).
 1649default_theme(truth(false),           [bold, fg(red)]).
 1650default_theme(truth(true),            [bold]).
 1651default_theme(truth(undefined),       [bold, fg(cyan)]).
 1652default_theme(wfs(residual_program),  [fg(cyan)]).
 1653default_theme(frame(level),           [bold]).
 1654default_theme(port(call),             [bold, fg(green)]).
 1655default_theme(port(exit),             [bold, fg(green)]).
 1656default_theme(port(fail),             [bold, fg(red)]).
 1657default_theme(port(redo),             [bold, fg(yellow)]).
 1658default_theme(port(unify),            [bold, fg(blue)]).
 1659default_theme(port(exception),        [bold, fg(magenta)]).
 1660default_theme(message(informational), [fg(green)]).
 1661default_theme(message(information),   [fg(green)]).
 1662default_theme(message(debug(_)),      [fg(blue)]).
 1663default_theme(message(Level),         Attrs) :-
 1664    nonvar(Level),
 1665    default_theme(Level, Attrs).
 1666
 1667
 1668                 /*******************************
 1669                 *      PRINTING MESSAGES       *
 1670                 *******************************/
 1671
 1672:- multifile
 1673    user:message_hook/3,
 1674    prolog:message_prefix_hook/2. 1675:- dynamic
 1676    user:message_hook/3,
 1677    prolog:message_prefix_hook/2. 1678:- thread_local
 1679    user:thread_message_hook/3.
 print_message(+Kind, +Term)
Print an error message using a term as generated by the exception system.
 1686print_message(Level, Term) :-
 1687    setup_call_cleanup(
 1688        push_msg(Term),
 1689        print_message_guarded(Level, Term),
 1690        pop_msg),
 1691    !.
 1692print_message(Level, Term) :-
 1693    (   Level \== silent
 1694    ->  format(user_error, 'Recursive ~w message: ~q~n', [Level, Term])
 1695    ;   true
 1696    ).
 1697
 1698push_msg(Term) :-
 1699    nb_current('$inprint_message', Messages),
 1700    !,
 1701    \+ ( '$member'(Msg, Messages),
 1702         Msg =@= Term
 1703       ),
 1704    b_setval('$inprint_message', [Term|Messages]).
 1705push_msg(Term) :-
 1706    b_setval('$inprint_message', [Term]).
 1707
 1708pop_msg :-
 1709    (   nb_current('$inprint_message', [_|Messages]),
 1710        Messages \== []
 1711    ->  b_setval('$inprint_message', Messages)
 1712    ;   nb_delete('$inprint_message')
 1713    ).
 1714
 1715print_message_guarded(Level, Term) :-
 1716    (   must_print(Level, Term)
 1717    ->  (   translate_message(Term, Lines, [])
 1718        ->  (   nonvar(Term),
 1719                (   notrace(user:thread_message_hook(Term, Level, Lines))
 1720                ->  true
 1721                ;   notrace(user:message_hook(Term, Level, Lines))
 1722                )
 1723            ->  true
 1724            ;   print_system_message(Term, Level, Lines)
 1725            )
 1726        )
 1727    ;   true
 1728    ).
 print_system_message(+Term, +Kind, +Lines)
Print the message if the user did not intecept the message. The first is used for errors and warnings that can be related to source-location. Note that syntax errors have their own source-location and should therefore not be handled this way.
 1737print_system_message(_, silent, _) :- !.
 1738print_system_message(_, informational, _) :-
 1739    current_prolog_flag(verbose, silent),
 1740    !.
 1741print_system_message(_, banner, _) :-
 1742    current_prolog_flag(verbose, silent),
 1743    !.
 1744print_system_message(_, _, []) :- !.
 1745print_system_message(Term, Kind, Lines) :-
 1746    catch(flush_output(user_output), _, true),      % may not exist
 1747    source_location(File, Line),
 1748    Term \= error(syntax_error(_), _),
 1749    msg_property(Kind, location_prefix(File:Line, LocPrefix, LinePrefix)),
 1750    !,
 1751    insert_prefix(Lines, LinePrefix, Ctx, PrefixLines),
 1752    '$append'([ begin(Kind, Ctx),
 1753                LocPrefix,
 1754                nl
 1755              | PrefixLines
 1756              ],
 1757              [ end(Ctx)
 1758              ],
 1759              AllLines),
 1760    msg_property(Kind, stream(Stream)),
 1761    ignore(stream_property(Stream, position(Pos))),
 1762    print_message_lines(Stream, AllLines),
 1763    (   \+ stream_property(Stream, position(Pos)),
 1764        msg_property(Kind, wait(Wait)),
 1765        Wait > 0
 1766    ->  sleep(Wait)
 1767    ;   true
 1768    ).
 1769print_system_message(_, Kind, Lines) :-
 1770    msg_property(Kind, stream(Stream)),
 1771    print_message_lines(Stream, kind(Kind), Lines).
 1772
 1773:- multifile
 1774    user:message_property/2. 1775
 1776msg_property(Kind, Property) :-
 1777    user:message_property(Kind, Property),
 1778    !.
 1779msg_property(Kind, prefix(Prefix)) :-
 1780    msg_prefix(Kind, Prefix),
 1781    !.
 1782msg_property(_, prefix('~N')) :- !.
 1783msg_property(query, stream(user_output)) :- !.
 1784msg_property(_, stream(user_error)) :- !.
 1785msg_property(error,
 1786             location_prefix(File:Line,
 1787                             '~NERROR: ~w:~d:'-[File,Line],
 1788                             '~NERROR:    ')) :- !.
 1789msg_property(warning,
 1790             location_prefix(File:Line,
 1791                             '~NWarning: ~w:~d:'-[File,Line],
 1792                             '~NWarning:    ')) :- !.
 1793msg_property(error,   wait(0.1)) :- !.
 1794
 1795msg_prefix(debug(_), Prefix) :-
 1796    msg_context('~N% ', Prefix).
 1797msg_prefix(warning, Prefix) :-
 1798    msg_context('~NWarning: ', Prefix).
 1799msg_prefix(error, Prefix) :-
 1800    msg_context('~NERROR: ', Prefix).
 1801msg_prefix(informational, '~N% ').
 1802msg_prefix(information,   '~N% ').
 msg_context(+Prefix0, -Prefix) is det
Add contextual information to a message. This uses the Prolog flag message_context. Recognised context terms are:

In addition, the hook message_prefix_hook/2 is called that allows for additional context information.

 1816msg_context(Prefix0, Prefix) :-
 1817    current_prolog_flag(message_context, Context),
 1818    is_list(Context),
 1819    !,
 1820    add_message_context(Context, Prefix0, Prefix).
 1821msg_context(Prefix, Prefix).
 1822
 1823add_message_context([], Prefix, Prefix).
 1824add_message_context([H|T], Prefix0, Prefix) :-
 1825    (   add_message_context1(H, Prefix0, Prefix1)
 1826    ->  true
 1827    ;   Prefix1 = Prefix0
 1828    ),
 1829    add_message_context(T, Prefix1, Prefix).
 1830
 1831add_message_context1(Context, Prefix0, Prefix) :-
 1832    prolog:message_prefix_hook(Context, Extra),
 1833    atomics_to_string([Prefix0, Extra, ' '], Prefix).
 1834add_message_context1(time, Prefix0, Prefix) :-
 1835    get_time(Now),
 1836    format_time(string(S), '%T.%3f ', Now),
 1837    string_concat(Prefix0, S, Prefix).
 1838add_message_context1(time(Format), Prefix0, Prefix) :-
 1839    get_time(Now),
 1840    format_time(string(S), Format, Now),
 1841    atomics_to_string([Prefix0, S, ' '], Prefix).
 1842add_message_context1(thread, Prefix0, Prefix) :-
 1843    thread_self(Id0),
 1844    Id0 \== main,
 1845    !,
 1846    (   atom(Id0)
 1847    ->  Id = Id0
 1848    ;   thread_property(Id0, id(Id))
 1849    ),
 1850    format(string(Prefix), '~w[Thread ~w] ', [Prefix0, Id]).
 print_message_lines(+Stream, +PrefixOrKind, +Lines)
Quintus compatibility predicate to print message lines using a prefix.
 1857print_message_lines(Stream, kind(Kind), Lines) :-
 1858    !,
 1859    msg_property(Kind, prefix(Prefix)),
 1860    insert_prefix(Lines, Prefix, Ctx, PrefixLines),
 1861    '$append'([ begin(Kind, Ctx)
 1862              | PrefixLines
 1863              ],
 1864              [ end(Ctx)
 1865              ],
 1866              AllLines),
 1867    print_message_lines(Stream, AllLines).
 1868print_message_lines(Stream, Prefix, Lines) :-
 1869    insert_prefix(Lines, Prefix, _, PrefixLines),
 1870    print_message_lines(Stream, PrefixLines).
 insert_prefix(+Lines, +Prefix, +Ctx, -PrefixedLines)
 1874insert_prefix([at_same_line|Lines0], Prefix, Ctx, Lines) :-
 1875    !,
 1876    prefix_nl(Lines0, Prefix, Ctx, Lines).
 1877insert_prefix(Lines0, Prefix, Ctx, [prefix(Prefix)|Lines]) :-
 1878    prefix_nl(Lines0, Prefix, Ctx, Lines).
 1879
 1880prefix_nl([], _, _, [nl]).
 1881prefix_nl([nl], _, _, [nl]) :- !.
 1882prefix_nl([flush], _, _, [flush]) :- !.
 1883prefix_nl([nl|T0], Prefix, Ctx, [nl, prefix(Prefix)|T]) :-
 1884    !,
 1885    prefix_nl(T0, Prefix, Ctx, T).
 1886prefix_nl([ansi(Attrs,Fmt,Args)|T0], Prefix, Ctx,
 1887          [ansi(Attrs,Fmt,Args,Ctx)|T]) :-
 1888    !,
 1889    prefix_nl(T0, Prefix, Ctx, T).
 1890prefix_nl([H|T0], Prefix, Ctx, [H|T]) :-
 1891    prefix_nl(T0, Prefix, Ctx, T).
 print_message_lines(+Stream, +Lines)
 1895print_message_lines(Stream, Lines) :-
 1896    with_output_to(
 1897        Stream,
 1898        notrace(print_message_lines_guarded(current_output, Lines))).
 1899
 1900print_message_lines_guarded(_, []) :- !.
 1901print_message_lines_guarded(S, [H|T]) :-
 1902    line_element(S, H),
 1903    print_message_lines_guarded(S, T).
 1904
 1905line_element(S, E) :-
 1906    prolog:message_line_element(S, E),
 1907    !.
 1908line_element(S, full_stop) :-
 1909    !,
 1910    '$put_token'(S, '.').           % insert space if needed.
 1911line_element(S, nl) :-
 1912    !,
 1913    nl(S).
 1914line_element(S, prefix(Fmt-Args)) :-
 1915    !,
 1916    safe_format(S, Fmt, Args).
 1917line_element(S, prefix(Fmt)) :-
 1918    !,
 1919    safe_format(S, Fmt, []).
 1920line_element(S, flush) :-
 1921    !,
 1922    flush_output(S).
 1923line_element(S, Fmt-Args) :-
 1924    !,
 1925    safe_format(S, Fmt, Args).
 1926line_element(S, ansi(_, Fmt, Args)) :-
 1927    !,
 1928    safe_format(S, Fmt, Args).
 1929line_element(S, ansi(_, Fmt, Args, _Ctx)) :-
 1930    !,
 1931    safe_format(S, Fmt, Args).
 1932line_element(_, begin(_Level, _Ctx)) :- !.
 1933line_element(_, end(_Ctx)) :- !.
 1934line_element(S, Fmt) :-
 1935    safe_format(S, Fmt, []).
 safe_format(+Stream, +Format, +Args) is det
 1939safe_format(S, Fmt, Args) :-
 1940    E = error(_,_),
 1941    catch(format(S,Fmt,Args), E,
 1942          format_failed(S,Fmt,Args,E)).
 1943
 1944format_failed(S, _Fmt, _Args, E) :-
 1945    E = error(io_error(_,S),_),
 1946    !,
 1947    throw(E).
 1948format_failed(S, Fmt, Args, error(E,_)) :-
 1949    format(S, '~N    [[ EXCEPTION while printing message ~q~n\c
 1950                        ~7|with arguments ~W:~n\c
 1951                        ~7|raised: ~W~n~4|]]~n',
 1952           [ Fmt,
 1953             Args, [quoted(true), max_depth(10)],
 1954             E, [quoted(true), max_depth(10)]
 1955           ]).
 message_to_string(+Term, -String)
Translate an error term into a string
 1961message_to_string(Term, Str) :-
 1962    translate_message(Term, Actions, []),
 1963    !,
 1964    actions_to_format(Actions, Fmt, Args),
 1965    format(string(Str), Fmt, Args).
 1966
 1967actions_to_format([], '', []) :- !.
 1968actions_to_format([nl], '', []) :- !.
 1969actions_to_format([Term, nl], Fmt, Args) :-
 1970    !,
 1971    actions_to_format([Term], Fmt, Args).
 1972actions_to_format([nl|T], Fmt, Args) :-
 1973    !,
 1974    actions_to_format(T, Fmt0, Args),
 1975    atom_concat('~n', Fmt0, Fmt).
 1976actions_to_format([ansi(_Attrs, Fmt0, Args0)|Tail], Fmt, Args) :-
 1977    !,
 1978    actions_to_format(Tail, Fmt1, Args1),
 1979    atom_concat(Fmt0, Fmt1, Fmt),
 1980    append_args(Args0, Args1, Args).
 1981actions_to_format([Fmt0-Args0|Tail], Fmt, Args) :-
 1982    !,
 1983    actions_to_format(Tail, Fmt1, Args1),
 1984    atom_concat(Fmt0, Fmt1, Fmt),
 1985    append_args(Args0, Args1, Args).
 1986actions_to_format([Skip|T], Fmt, Args) :-
 1987    action_skip(Skip),
 1988    !,
 1989    actions_to_format(T, Fmt, Args).
 1990actions_to_format([Term|Tail], Fmt, Args) :-
 1991    atomic(Term),
 1992    !,
 1993    actions_to_format(Tail, Fmt1, Args),
 1994    atom_concat(Term, Fmt1, Fmt).
 1995actions_to_format([Term|Tail], Fmt, Args) :-
 1996    actions_to_format(Tail, Fmt1, Args1),
 1997    atom_concat('~w', Fmt1, Fmt),
 1998    append_args([Term], Args1, Args).
 1999
 2000action_skip(at_same_line).
 2001action_skip(flush).
 2002action_skip(begin(_Level, _Ctx)).
 2003action_skip(end(_Ctx)).
 2004
 2005append_args(M:Args0, Args1, M:Args) :-
 2006    !,
 2007    strip_module(Args1, _, A1),
 2008    '$append'(Args0, A1, Args).
 2009append_args(Args0, Args1, Args) :-
 2010    strip_module(Args1, _, A1),
 2011    '$append'(Args0, A1, Args).
 2012
 2013
 2014                 /*******************************
 2015                 *    MESSAGES TO PRINT ONCE    *
 2016                 *******************************/
 2017
 2018:- dynamic
 2019    printed/2.
 print_once(Message, Level)
True for messages that must be printed only once.
 2025print_once(compatibility(_), _).
 2026print_once(null_byte_in_path(_), _).
 2027print_once(deprecated(_), _).
 must_print(+Level, +Message)
True if the message must be printed.
 2033must_print(Level, Message) :-
 2034    nonvar(Message),
 2035    print_once(Message, Level),
 2036    !,
 2037    \+ printed(Message, Level),
 2038    assert(printed(Message, Level)).
 2039must_print(_, _)