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-2025, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9                              SWI-Prolog Solutions b.v.
   10    All rights reserved.
   11
   12    Redistribution and use in source and binary forms, with or without
   13    modification, are permitted provided that the following conditions
   14    are met:
   15
   16    1. Redistributions of source code must retain the above copyright
   17       notice, this list of conditions and the following disclaimer.
   18
   19    2. Redistributions in binary form must reproduce the above copyright
   20       notice, this list of conditions and the following disclaimer in
   21       the documentation and/or other materials provided with the
   22       distribution.
   23
   24    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   25    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   26    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   27    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   28    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   29    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   30    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   31    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   32    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   33    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   34    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   35    POSSIBILITY OF SUCH DAMAGE.
   36*/
   37
   38:- module('$messages',
   39          [ print_message/2,            % +Kind, +Term
   40            print_message_lines/3,      % +Stream, +Prefix, +Lines
   41            message_to_string/2         % +Term, -String
   42          ]).   43
   44:- multifile
   45    prolog:message//1,              % entire message
   46    prolog:error_message//1,        % 1-st argument of error term
   47    prolog:message_context//1,      % Context of error messages
   48    prolog:deprecated//1,	    % Deprecated features
   49    prolog:message_location//1,     % (File) location of error messages
   50    prolog:message_line_element/2.  % Extend printing
   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)).   58% Lang, Term versions
   59:- multifile
   60    prolog:message//2,              % entire message
   61    prolog:error_message//2,        % 1-st argument of error term
   62    prolog:message_context//2,      % Context of error messages
   63    prolog:message_location//2,	    % (File) location of error messages
   64    prolog:deprecated//2.	    % Deprecated features
   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,           % +Message (deprecated)
   77    prolog:translate_message//1.    % +Message
   78
   79:- 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)
ansi(Code, Fmt, Args)
Use ansi_format/3 for color output.
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)
deprecated
- Use code for message translation should call translate_message//1.
  103prolog:translate_message(Term) -->
  104    translate_message(Term).
 translate_message(+Term)// is det
Translate a message term into message lines. This version may be called from user and library definitions for message translation.
  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) :- % deal with old C-warning()
  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).
 term_message(+Term)//
Deal with the formal argument of error(Format, ImplDefined) exception terms. The ImplDefined argument is handled by swi_location//2.
  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))) --> % not ISO
  218    [ 'Module ', ansi(code, '~q', [M]), ' does not export ',
  219      ansi(code, '~q', [PI]) ].
  220iso_message(existence_error(Type, Object, In)) --> % not ISO
  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] ].
 permission_error(Action, Type, Object)//
Translate permission errors. Most follow te pattern "No permission to Action Type Object", but some are a bit different.
  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
  321type_error_comment(_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] ].
 tabling_existence_error(+Ball, +Context)//
Called on invalid shift/1 calls. Track those that result from tabling errors.
  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)).
 dwim_predicates(+PI, -Dwims)
Find related predicate indicators.
  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)) --> % Message = dlerror()
  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'- [] ].
 swi_location(+Term)// is det
Print location information for error(Formal, ImplDefined) from the ImplDefined term.
  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] ].
 swi_extra(+Term)// is det
Extract information from the second argument of an error(Formal, ImplDefined) that is printed after the core of the message.
See also
- swi_location//1 uses the same term to insert context before the core of the message.
  601swi_extra(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
  625swi_comment(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		 /*******************************
  646		 *        UNWIND MESSAGES	*
  647		 *******************************/
  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                 /*******************************
  663                 *        NORMAL MESSAGES       *
  664                 *******************************/
  665
  666prolog_message(welcome) -->
  667    [ 'Welcome to SWI-Prolog (' ],
  668    prolog_message(threads),
  669    prolog_message(address_bits),
  670    ['version ' ],
  671    prolog_message(version),
  672    [ ')', nl ],
  673    prolog_message(copyright),
  674    [ nl ],
  675    translate_message(user_versions),
  676    [ nl ],
  677    prolog_message(documentaton),
  678    [ nl, nl ].
  679prolog_message(user_versions) -->
  680    (   { findall(Msg, prolog:version_msg(Msg), Msgs),
  681          Msgs \== []
  682        }
  683    ->  [nl],
  684        user_version_messages(Msgs)
  685    ;   []
  686    ).
  687prolog_message(deprecated(Term)) -->
  688    { nonvar(Term) },
  689    (   { message_lang(Lang) },
  690        prolog:deprecated(Lang, Term)
  691    ->  []
  692    ;   prolog:deprecated(Term)
  693    ->  []
  694    ;   deprecated(Term)
  695    ).
  696prolog_message(unhandled_exception(E)) -->
  697    { nonvar(E) },
  698    [ 'Unhandled exception: ' ],
  699    (   translate_message(E)
  700    ->  []
  701    ;   [ '~p'-[E] ]
  702    ).
 prolog_message(+Term)//
  706prolog_message(initialization_error(_, E, File:Line)) -->
  707    !,
  708    [ url(File:Line),
  709      ': Initialization goal raised exception:', nl
  710    ],
  711    translate_message(E).
  712prolog_message(initialization_error(Goal, E, _)) -->
  713    [ 'Initialization goal ~p raised exception:'-[Goal], nl ],
  714    translate_message(E).
  715prolog_message(initialization_failure(_Goal, File:Line)) -->
  716    !,
  717    [ url(File:Line),
  718      ': Initialization goal failed'-[]
  719    ].
  720prolog_message(initialization_failure(Goal, _)) -->
  721    [ 'Initialization goal failed: ~p'-[Goal]
  722    ].
  723prolog_message(initialization_exception(E)) -->
  724    [ 'Prolog initialisation failed:', nl ],
  725    translate_message(E).
  726prolog_message(init_goal_syntax(Error, Text)) -->
  727    !,
  728    [ '-g ~w: '-[Text] ],
  729    translate_message(Error).
  730prolog_message(init_goal_failed(failed, @(Goal,File:Line))) -->
  731    !,
  732    [ url(File:Line), ': ~p: false'-[Goal] ].
  733prolog_message(init_goal_failed(Error, @(Goal,File:Line))) -->
  734    !,
  735    [ url(File:Line), ': ~p '-[Goal] ],
  736    translate_message(Error).
  737prolog_message(init_goal_failed(failed, Text)) -->
  738    !,
  739    [ '-g ~w: false'-[Text] ].
  740prolog_message(init_goal_failed(Error, Text)) -->
  741    !,
  742    [ '-g ~w: '-[Text] ],
  743    translate_message(Error).
  744prolog_message(goal_failed(Context, Goal)) -->
  745    [ 'Goal (~w) failed: ~p'-[Context, Goal] ].
  746prolog_message(no_current_module(Module)) -->
  747    [ '~w is not a current module (created)'-[Module] ].
  748prolog_message(commandline_arg_type(Flag, Arg)) -->
  749    [ 'Bad argument to commandline option -~w: ~w'-[Flag, Arg] ].
  750prolog_message(missing_feature(Name)) -->
  751    [ 'This version of SWI-Prolog does not support ~w'-[Name] ].
  752prolog_message(singletons(_Term, List)) -->
  753    [ 'Singleton variables: ~w'-[List] ].
  754prolog_message(multitons(_Term, List)) -->
  755    [ 'Singleton-marked variables appearing more than once: ~w'-[List] ].
  756prolog_message(profile_no_cpu_time) -->
  757    [ 'No CPU-time info.  Check the SWI-Prolog manual for details' ].
  758prolog_message(non_ascii(Text, Type)) -->
  759    [ 'Unquoted ~w with non-portable characters: ~w'-[Type, Text] ].
  760prolog_message(io_warning(Stream, Message)) -->
  761    { stream_property(Stream, position(Position)),
  762      !,
  763      stream_position_data(line_count, Position, LineNo),
  764      stream_position_data(line_position, Position, LinePos),
  765      (   stream_property(Stream, file_name(File))
  766      ->  Obj = File
  767      ;   Obj = Stream
  768      )
  769    },
  770    [ '~p:~d:~d: ~w'-[Obj, LineNo, LinePos, Message] ].
  771prolog_message(io_warning(Stream, Message)) -->
  772    [ 'stream ~p: ~w'-[Stream, Message] ].
  773prolog_message(option_usage(pldoc)) -->
  774    [ 'Usage: --pldoc[=port]' ].
  775prolog_message(interrupt(begin)) -->
  776    [ 'Action (h for help) ? ', flush ].
  777prolog_message(interrupt(end)) -->
  778    [ 'continue' ].
  779prolog_message(interrupt(trace)) -->
  780    [ 'continue (trace mode)' ].
  781prolog_message(unknown_in_module_user) -->
  782    [ 'Using a non-error value for unknown in the global module', nl,
  783      'causes most of the development environment to stop working.', nl,
  784      'Please use :- dynamic or limit usage of unknown to a module.', nl,
  785      'See https://www.swi-prolog.org/howto/database.html'
  786    ].
  787prolog_message(untable(PI)) -->
  788    [ 'Reconsult: removed tabling for ~p'-[PI] ].
  789prolog_message(unknown_option(Set, Opt)) -->
  790    [ 'Unknown ~w option: ~p'-[Set, Opt] ].
  791
  792
  793                 /*******************************
  794                 *         LOADING FILES        *
  795                 *******************************/
  796
  797prolog_message(modify_active_procedure(Who, What)) -->
  798    [ '~p: modified active procedure ~p'-[Who, What] ].
  799prolog_message(load_file(failed(user:File))) -->
  800    [ 'Failed to load ~p'-[File] ].
  801prolog_message(load_file(failed(Module:File))) -->
  802    [ 'Failed to load ~p into module ~p'-[File, Module] ].
  803prolog_message(load_file(failed(File))) -->
  804    [ 'Failed to load ~p'-[File] ].
  805prolog_message(mixed_directive(Goal)) -->
  806    [ 'Cannot pre-compile mixed load/call directive: ~p'-[Goal] ].
  807prolog_message(cannot_redefine_comma) -->
  808    [ 'Full stop in clause-body?  Cannot redefine ,/2' ].
  809prolog_message(illegal_autoload_index(Dir, Term)) -->
  810    [ 'Illegal term in INDEX file of directory ~w: ~w'-[Dir, Term] ].
  811prolog_message(redefined_procedure(Type, Proc)) -->
  812    [ 'Redefined ~w procedure ~p'-[Type, Proc] ],
  813    defined_definition('Previously defined', Proc).
  814prolog_message(declare_module(Module, abolish(Predicates))) -->
  815    [ 'Loading module ~w abolished: ~p'-[Module, Predicates] ].
  816prolog_message(import_private(Module, Private)) -->
  817    [ 'import/1: ~p is not exported (still imported into ~q)'-
  818      [Private, Module]
  819    ].
  820prolog_message(ignored_weak_import(Into, From:PI)) -->
  821    [ 'Local definition of ~p overrides weak import from ~q'-
  822      [Into:PI, From]
  823    ].
  824prolog_message(undefined_export(Module, PI)) -->
  825    [ 'Exported procedure ~q:~q is not defined'-[Module, PI] ].
  826prolog_message(no_exported_op(Module, Op)) -->
  827    [ 'Operator ~q:~q is not exported (still defined)'-[Module, Op] ].
  828prolog_message(discontiguous((-)/2,_)) -->
  829    prolog_message(minus_in_identifier).
  830prolog_message(discontiguous(Proc,Current)) -->
  831    [ 'Clauses of ', ansi(code, '~p', [Proc]),
  832      ' are not together in the source-file', nl ],
  833    current_definition(Proc, 'Earlier definition at '),
  834    [ 'Current predicate: ', ansi(code, '~p', [Current]), nl,
  835      'Use ', ansi(code, ':- discontiguous ~p.', [Proc]),
  836      ' to suppress this message'
  837    ].
  838prolog_message(decl_no_effect(Goal)) -->
  839    [ 'Deprecated declaration has no effect: ~p'-[Goal] ].
  840prolog_message(load_file(start(Level, File))) -->
  841    [ '~|~t~*+Loading '-[Level] ],
  842    load_file(File),
  843    [ ' ...' ].
  844prolog_message(include_file(start(Level, File))) -->
  845    [ '~|~t~*+include '-[Level] ],
  846    load_file(File),
  847    [ ' ...' ].
  848prolog_message(include_file(done(Level, File))) -->
  849    [ '~|~t~*+included '-[Level] ],
  850    load_file(File).
  851prolog_message(load_file(done(Level, File, Action, Module, Time, Clauses))) -->
  852    [ '~|~t~*+'-[Level] ],
  853    load_file(File),
  854    [ ' ~w'-[Action] ],
  855    load_module(Module),
  856    [ ' ~2f sec, ~D clauses'-[Time, Clauses] ].
  857prolog_message(dwim_undefined(Goal, Alternatives)) -->
  858    { goal_to_predicate_indicator(Goal, Pred)
  859    },
  860    [ 'Unknown procedure: ~q'-[Pred], nl,
  861      '    However, there are definitions for:', nl
  862    ],
  863    dwim_message(Alternatives).
  864prolog_message(dwim_correct(Into)) -->
  865    [ 'Correct to: ~q? '-[Into], flush ].
  866prolog_message(error(loop_error(Spec), file_search(Used))) -->
  867    [ 'File search: too many levels of indirections on: ~p'-[Spec], nl,
  868      '    Used alias expansions:', nl
  869    ],
  870    used_search(Used).
  871prolog_message(minus_in_identifier) -->
  872    [ 'The "-" character should not be used to separate words in an', nl,
  873      'identifier.  Check the SWI-Prolog FAQ for details.'
  874    ].
  875prolog_message(qlf(removed_after_error(File))) -->
  876    [ 'Removed incomplete QLF file ~w'-[File] ].
  877prolog_message(qlf(recompile(Spec,_Pl,_Qlf,Reason))) -->
  878    [ '~p: recompiling QLF file'-[Spec] ],
  879    qlf_recompile_reason(Reason).
  880prolog_message(qlf(can_not_recompile(Spec,QlfFile,_Reason))) -->
  881    [ '~p: can not recompile "~w" (access denied)'-[Spec, QlfFile], nl,
  882      '\tLoading from source'-[]
  883    ].
  884prolog_message(qlf(system_lib_out_of_date(Spec,QlfFile))) -->
  885    [ '~p: can not recompile "~w" (access denied)'-[Spec, QlfFile], nl,
  886      '\tLoading QlfFile'-[]
  887    ].
  888prolog_message(redefine_module(Module, OldFile, File)) -->
  889    [ 'Module "~q" already loaded from ~w.'-[Module, OldFile], nl,
  890      'Wipe and reload from ~w? '-[File], flush
  891    ].
  892prolog_message(redefine_module_reply) -->
  893    [ 'Please answer y(es), n(o) or a(bort)' ].
  894prolog_message(reloaded_in_module(Absolute, OldContext, LM)) -->
  895    [ '~w was previously loaded in module ~w'-[Absolute, OldContext], nl,
  896      '\tnow it is reloaded into module ~w'-[LM] ].
  897prolog_message(expected_layout(Expected, Pos)) -->
  898    [ 'Layout data: expected ~w, found: ~p'-[Expected, Pos] ].
  899
  900defined_definition(Message, Spec) -->
  901    { strip_module(user:Spec, M, Name/Arity),
  902      functor(Head, Name, Arity),
  903      predicate_property(M:Head, file(File)),
  904      predicate_property(M:Head, line_count(Line))
  905    },
  906    !,
  907    [ nl, '~w at '-[Message], url(File:Line) ].
  908defined_definition(_, _) --> [].
  909
  910used_search([]) -->
  911    [].
  912used_search([Alias=Expanded|T]) -->
  913    [ '        file_search_path(~p, ~p)'-[Alias, Expanded], nl ],
  914    used_search(T).
  915
  916load_file(file(Spec, _Path)) -->
  917    (   {atomic(Spec)}
  918    ->  [ '~w'-[Spec] ]
  919    ;   [ '~p'-[Spec] ]
  920    ).
  921%load_file(file(_, Path)) -->
  922%       [ '~w'-[Path] ].
  923
  924load_module(user) --> !.
  925load_module(system) --> !.
  926load_module(Module) -->
  927    [ ' into ~w'-[Module] ].
  928
  929goal_to_predicate_indicator(Goal, PI) :-
  930    strip_module(Goal, Module, Head),
  931    callable_name_arity(Head, Name, Arity),
  932    user_predicate_indicator(Module:Name/Arity, PI).
  933
  934callable_name_arity(Goal, Name, Arity) :-
  935    compound(Goal),
  936    !,
  937    compound_name_arity(Goal, Name, Arity).
  938callable_name_arity(Goal, Goal, 0) :-
  939    atom(Goal).
  940
  941user_predicate_indicator(Module:PI, PI) :-
  942    hidden_module(Module),
  943    !.
  944user_predicate_indicator(PI, PI).
  945
  946hidden_module(user) :- !.
  947hidden_module(system) :- !.
  948hidden_module(M) :-
  949    sub_atom(M, 0, _, _, $).
  950
  951current_definition(Proc, Prefix) -->
  952    { pi_uhead(Proc, Head),
  953      predicate_property(Head, file(File)),
  954      predicate_property(Head, line_count(Line))
  955    },
  956    [ '~w'-[Prefix], url(File:Line), nl ].
  957current_definition(_, _) --> [].
  958
  959pi_uhead(Module:Name/Arity, Module:Head) :-
  960    !,
  961    atom(Module), atom(Name), integer(Arity),
  962    functor(Head, Name, Arity).
  963pi_uhead(Name/Arity, user:Head) :-
  964    atom(Name), integer(Arity),
  965    functor(Head, Name, Arity).
  966
  967qlf_recompile_reason(old) -->
  968    !,
  969    [ ' (out of date)'-[] ].
  970qlf_recompile_reason(_) -->
  971    [ ' (incompatible with current Prolog version)'-[] ].
  972
  973prolog_message(file_search(cache(Spec, _Cond), Path)) -->
  974    [ 'File search: ~p --> ~p (cache)'-[Spec, Path] ].
  975prolog_message(file_search(found(Spec, Cond), Path)) -->
  976    [ 'File search: ~p --> ~p OK ~p'-[Spec, Path, Cond] ].
  977prolog_message(file_search(tried(Spec, Cond), Path)) -->
  978    [ 'File search: ~p --> ~p NO ~p'-[Spec, Path, Cond] ].
  979
  980                 /*******************************
  981                 *              GC              *
  982                 *******************************/
  983
  984prolog_message(agc(start)) -->
  985    thread_context,
  986    [ 'AGC: ', flush ].
  987prolog_message(agc(done(Collected, Remaining, Time))) -->
  988    [ at_same_line,
  989      'reclaimed ~D atoms in ~3f sec. (remaining: ~D)'-
  990      [Collected, Time, Remaining]
  991    ].
  992prolog_message(cgc(start)) -->
  993    thread_context,
  994    [ 'CGC: ', flush ].
  995prolog_message(cgc(done(CollectedClauses, _CollectedBytes,
  996                        RemainingBytes, Time))) -->
  997    [ at_same_line,
  998      'reclaimed ~D clauses in ~3f sec. (pending: ~D bytes)'-
  999      [CollectedClauses, Time, RemainingBytes]
 1000    ].
 1001
 1002		 /*******************************
 1003		 *        STACK OVERFLOW	*
 1004		 *******************************/
 1005
 1006out_of_stack(Context) -->
 1007    { human_stack_size(Context.localused,   Local),
 1008      human_stack_size(Context.globalused,  Global),
 1009      human_stack_size(Context.trailused,   Trail),
 1010      human_stack_size(Context.stack_limit, Limit),
 1011      LCO is (100*(Context.depth - Context.environments))/Context.depth
 1012    },
 1013    [ 'Stack limit (~s) exceeded'-[Limit], nl,
 1014      '  Stack sizes: local: ~s, global: ~s, trail: ~s'-[Local,Global,Trail], nl,
 1015      '  Stack depth: ~D, last-call: ~0f%, Choice points: ~D'-
 1016         [Context.depth, LCO, Context.choicepoints], nl
 1017    ],
 1018    overflow_reason(Context, Resolve),
 1019    resolve_overflow(Resolve).
 1020
 1021human_stack_size(Size, String) :-
 1022    Size < 100,
 1023    format(string(String), '~dKb', [Size]).
 1024human_stack_size(Size, String) :-
 1025    Size < 100 000,
 1026    Value is Size / 1024,
 1027    format(string(String), '~1fMb', [Value]).
 1028human_stack_size(Size, String) :-
 1029    Value is Size / (1024*1024),
 1030    format(string(String), '~1fGb', [Value]).
 1031
 1032overflow_reason(Context, fix) -->
 1033    show_non_termination(Context),
 1034    !.
 1035overflow_reason(Context, enlarge) -->
 1036    { Stack = Context.get(stack) },
 1037    !,
 1038    [ '  In:'-[], nl ],
 1039    stack(Stack).
 1040overflow_reason(_Context, enlarge) -->
 1041    [ '  Insufficient global stack'-[] ].
 1042
 1043show_non_termination(Context) -->
 1044    (   { Stack = Context.get(cycle) }
 1045    ->  [ '  Probable infinite recursion (cycle):'-[], nl ]
 1046    ;   { Stack = Context.get(non_terminating) }
 1047    ->  [ '  Possible non-terminating recursion:'-[], nl ]
 1048    ),
 1049    stack(Stack).
 1050
 1051stack([]) --> [].
 1052stack([frame(Depth, M:Goal, _)|T]) -->
 1053    [ '    [~D] ~q:'-[Depth, M] ],
 1054    stack_goal(Goal),
 1055    [ nl ],
 1056    stack(T).
 1057
 1058stack_goal(Goal) -->
 1059    { compound(Goal),
 1060      !,
 1061      compound_name_arity(Goal, Name, Arity)
 1062    },
 1063    [ '~q('-[Name] ],
 1064    stack_goal_args(1, Arity, Goal),
 1065    [ ')'-[] ].
 1066stack_goal(Goal) -->
 1067    [ '~q'-[Goal] ].
 1068
 1069stack_goal_args(I, Arity, Goal) -->
 1070    { I =< Arity,
 1071      !,
 1072      arg(I, Goal, A),
 1073      I2 is I + 1
 1074    },
 1075    stack_goal_arg(A),
 1076    (   { I2 =< Arity }
 1077    ->  [ ', '-[] ],
 1078        stack_goal_args(I2, Arity, Goal)
 1079    ;   []
 1080    ).
 1081stack_goal_args(_, _, _) -->
 1082    [].
 1083
 1084stack_goal_arg(A) -->
 1085    { nonvar(A),
 1086      A = [Len|T],
 1087      !
 1088    },
 1089    (   {Len == cyclic_term}
 1090    ->  [ '[cyclic list]'-[] ]
 1091    ;   {T == []}
 1092    ->  [ '[length:~D]'-[Len] ]
 1093    ;   [ '[length:~D|~p]'-[Len, T] ]
 1094    ).
 1095stack_goal_arg(A) -->
 1096    { nonvar(A),
 1097      A = _/_,
 1098      !
 1099    },
 1100    [ '<compound ~p>'-[A] ].
 1101stack_goal_arg(A) -->
 1102    [ '~p'-[A] ].
 1103
 1104resolve_overflow(fix) -->
 1105    [].
 1106resolve_overflow(enlarge) -->
 1107    { current_prolog_flag(stack_limit, LimitBytes),
 1108      NewLimit is LimitBytes * 2
 1109    },
 1110    [ nl,
 1111      'Use the --stack_limit=size[KMG] command line option or'-[], nl,
 1112      '?- set_prolog_flag(stack_limit, ~I). to double the limit.'-[NewLimit]
 1113    ].
 out_of_c_stack
The thread's C-stack limit was exceeded. Give some advice on how to resolve this.
 1120out_of_c_stack -->
 1121    { statistics(c_stack, Limit), Limit > 0 },
 1122    !,
 1123    [ 'C-stack limit (~D bytes) exceeded.'-[Limit], nl ],
 1124    resolve_c_stack_overflow(Limit).
 1125out_of_c_stack -->
 1126    { statistics(c_stack, Limit), Limit > 0 },
 1127    [ 'C-stack limit exceeded.'-[Limit], nl ],
 1128    resolve_c_stack_overflow(Limit).
 1129
 1130resolve_c_stack_overflow(_Limit) -->
 1131    { thread_self(main) },
 1132    [ 'Use the shell command ' ], code('~w', 'ulimit -s size'),
 1133    [ ' to enlarge the limit.' ].
 1134resolve_c_stack_overflow(_Limit) -->
 1135    [ 'Use the ' ], code('~w', 'c_stack(KBytes)'),
 1136    [ ' option of '], code(thread_create/3), [' to enlarge the limit.' ].
 1137
 1138
 1139                 /*******************************
 1140                 *        MAKE/AUTOLOAD         *
 1141                 *******************************/
 1142
 1143prolog_message(make(reload(Files))) -->
 1144    { length(Files, N)
 1145    },
 1146    [ 'Make: reloading ~D files'-[N] ].
 1147prolog_message(make(done(_Files))) -->
 1148    [ 'Make: finished' ].
 1149prolog_message(make(library_index(Dir))) -->
 1150    [ 'Updating index for library ~w'-[Dir] ].
 1151prolog_message(autoload(Pred, File)) -->
 1152    thread_context,
 1153    [ 'autoloading ~p from ~w'-[Pred, File] ].
 1154prolog_message(autoload(read_index(Dir))) -->
 1155    [ 'Loading autoload index for ~w'-[Dir] ].
 1156prolog_message(autoload(disabled(Loaded))) -->
 1157    [ 'Disabled autoloading (loaded ~D files)'-[Loaded] ].
 1158prolog_message(autoload(already_defined(PI, From))) -->
 1159    code(PI),
 1160    (   { '$pi_head'(PI, Head),
 1161          predicate_property(Head, built_in)
 1162        }
 1163    ->  [' is a built-in predicate']
 1164    ;   [ ' is already imported from module ' ],
 1165        code(From)
 1166    ).
 1167
 1168swi_message(autoload(Msg)) -->
 1169    [ nl, '  ' ],
 1170    autoload_message(Msg).
 1171
 1172autoload_message(not_exported(PI, Spec, _FullFile, _Exports)) -->
 1173    [ ansi(code, '~w', [Spec]),
 1174      ' does not export ',
 1175      ansi(code, '~p', [PI])
 1176    ].
 1177autoload_message(no_file(Spec)) -->
 1178    [ ansi(code, '~p', [Spec]), ': No such file' ].
 1179
 1180
 1181                 /*******************************
 1182                 *       COMPILER WARNINGS      *
 1183                 *******************************/
 1184
 1185% print warnings about dubious code raised by the compiler.
 1186% TBD: pass in PC to produce exact error locations.
 1187
 1188prolog_message(compiler_warnings(Clause, Warnings0)) -->
 1189    {   print_goal_options(DefOptions),
 1190        (   prolog_load_context(variable_names, VarNames)
 1191        ->  warnings_with_named_vars(Warnings0, VarNames, Warnings),
 1192            Options = [variable_names(VarNames)|DefOptions]
 1193        ;   Options = DefOptions,
 1194            Warnings = Warnings0
 1195        )
 1196    },
 1197    compiler_warnings(Warnings, Clause, Options).
 1198
 1199warnings_with_named_vars([], _, []).
 1200warnings_with_named_vars([H|T0], VarNames, [H|T]) :-
 1201    term_variables(H, Vars),
 1202    '$member'(V1, Vars),
 1203    '$member'(_=V2, VarNames),
 1204    V1 == V2,
 1205    !,
 1206    warnings_with_named_vars(T0, VarNames, T).
 1207warnings_with_named_vars([_|T0], VarNames, T) :-
 1208    warnings_with_named_vars(T0, VarNames, T).
 1209
 1210
 1211compiler_warnings([], _, _) --> [].
 1212compiler_warnings([H|T], Clause, Options) -->
 1213    (   compiler_warning(H, Clause, Options)
 1214    ->  []
 1215    ;   [ 'Unknown compiler warning: ~W'-[H,Options] ]
 1216    ),
 1217    (   {T==[]}
 1218    ->  []
 1219    ;   [nl]
 1220    ),
 1221    compiler_warnings(T, Clause, Options).
 1222
 1223compiler_warning(eq_vv(A,B), _Clause, Options) -->
 1224    (   { A == B }
 1225    ->  [ 'Test is always true: ~W'-[A==B, Options] ]
 1226    ;   [ 'Test is always false: ~W'-[A==B, Options] ]
 1227    ).
 1228compiler_warning(eq_singleton(A,B), _Clause, Options) -->
 1229    [ 'Test is always false: ~W'-[A==B, Options] ].
 1230compiler_warning(neq_vv(A,B), _Clause, Options) -->
 1231    (   { A \== B }
 1232    ->  [ 'Test is always true: ~W'-[A\==B, Options] ]
 1233    ;   [ 'Test is always false: ~W'-[A\==B, Options] ]
 1234    ).
 1235compiler_warning(neq_singleton(A,B), _Clause, Options) -->
 1236    [ 'Test is always true: ~W'-[A\==B, Options] ].
 1237compiler_warning(unify_singleton(A,B), _Clause, Options) -->
 1238    [ 'Unified variable is not used: ~W'-[A=B, Options] ].
 1239compiler_warning(always(Bool, Pred, Arg), _Clause, Options) -->
 1240    { Goal =.. [Pred,Arg] },
 1241    [ 'Test is always ~w: ~W'-[Bool, Goal, Options] ].
 1242compiler_warning(unbalanced_var(V), _Clause, Options) -->
 1243    [ 'Variable not introduced in all branches: ~W'-[V, Options] ].
 1244compiler_warning(branch_singleton(V), _Clause, Options) -->
 1245    [ 'Singleton variable in branch: ~W'-[V, Options] ].
 1246compiler_warning(negation_singleton(V), _Clause, Options) -->
 1247    [ 'Singleton variable in \\+: ~W'-[V, Options] ].
 1248compiler_warning(multiton(V), _Clause, Options) -->
 1249    [ 'Singleton-marked variable appears more than once: ~W'-[V, Options] ].
 1250
 1251print_goal_options(
 1252    [ quoted(true),
 1253      portray(true)
 1254    ]).
 1255
 1256
 1257                 /*******************************
 1258                 *      TOPLEVEL MESSAGES       *
 1259                 *******************************/
 1260
 1261prolog_message(version) -->
 1262    { current_prolog_flag(version_git, Version) },
 1263    !,
 1264    [ '~w'-[Version] ].
 1265prolog_message(version) -->
 1266    { current_prolog_flag(version_data, swi(Major,Minor,Patch,Options))
 1267    },
 1268    (   { memberchk(tag(Tag), Options) }
 1269    ->  [ '~w.~w.~w-~w'-[Major, Minor, Patch, Tag] ]
 1270    ;   [ '~w.~w.~w'-[Major, Minor, Patch] ]
 1271    ).
 1272prolog_message(address_bits) -->
 1273    { current_prolog_flag(address_bits, Bits)
 1274    },
 1275    !,
 1276    [ '~d bits, '-[Bits] ].
 1277prolog_message(threads) -->
 1278    { current_prolog_flag(threads, true)
 1279    },
 1280    !,
 1281    [ 'threaded, ' ].
 1282prolog_message(threads) -->
 1283    [].
 1284prolog_message(copyright) -->
 1285    [ 'SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.', nl,
 1286      'Please run ', ansi(code, '?- license.', []), ' for legal details.'
 1287    ].
 1288prolog_message(documentaton) -->
 1289    [ 'For online help and background, visit ', url('https://www.swi-prolog.org') ],
 1290    (   { exists_source(library(help)) }
 1291    ->  [ nl,
 1292          'For built-in help, use ', ansi(code, '?- help(Topic).', []),
 1293          ' or ', ansi(code, '?- apropos(Word).', [])
 1294        ]
 1295    ;   []
 1296    ).
 1297prolog_message(about) -->
 1298    [ 'SWI-Prolog version (' ],
 1299    prolog_message(threads),
 1300    prolog_message(address_bits),
 1301    ['version ' ],
 1302    prolog_message(version),
 1303    [ ')', nl ],
 1304    prolog_message(copyright).
 1305prolog_message(halt) -->
 1306    [ 'halt' ].
 1307prolog_message(break(begin, Level)) -->
 1308    [ 'Break level ~d'-[Level] ].
 1309prolog_message(break(end, Level)) -->
 1310    [ 'Exit break level ~d'-[Level] ].
 1311prolog_message(var_query(_)) -->
 1312    [ '... 1,000,000 ............ 10,000,000 years later', nl, nl,
 1313      '~t~8|>> 42 << (last release gives the question)'
 1314    ].
 1315prolog_message(close_on_abort(Stream)) -->
 1316    [ 'Abort: closed stream ~p'-[Stream] ].
 1317prolog_message(cancel_halt(Reason)) -->
 1318    [ 'Halt cancelled: ~p'-[Reason] ].
 1319prolog_message(on_error(halt(Status))) -->
 1320    { statistics(errors, Errors),
 1321      statistics(warnings, Warnings)
 1322    },
 1323    [ 'Halting with status ~w due to ~D errors and ~D warnings'-
 1324      [Status, Errors, Warnings] ].
 1325
 1326prolog_message(query(QueryResult)) -->
 1327    query_result(QueryResult).
 1328
 1329query_result(no) -->            % failure
 1330    [ ansi(truth(false), 'false.', []) ],
 1331    extra_line.
 1332query_result(yes(true, [])) -->      % prompt_alternatives_on: groundness
 1333    !,
 1334    [ ansi(truth(true), 'true.', []) ],
 1335    extra_line.
 1336query_result(yes(Delays, Residuals)) -->
 1337    result([], Delays, Residuals),
 1338    extra_line.
 1339query_result(done) -->          % user typed <CR>
 1340    extra_line.
 1341query_result(yes(Bindings, Delays, Residuals)) -->
 1342    result(Bindings, Delays, Residuals),
 1343    prompt(yes, Bindings, Delays, Residuals).
 1344query_result(more(Bindings, Delays, Residuals)) -->
 1345    result(Bindings, Delays, Residuals),
 1346    prompt(more, Bindings, Delays, Residuals).
 1347:- if(current_prolog_flag(emscripten, true)). 1348query_result(help) -->
 1349    [ ansi(bold, '  Possible actions:', []), nl,
 1350      '  ; (n,r,space): redo              | t:       trace&redo'-[], nl,
 1351      '  *:             show choicepoint  | . (c,a): stop'-[], nl,
 1352      '  w:             write             | p:       print'-[], nl,
 1353      '  +:             max_depth*5       | -:       max_depth//5'-[], nl,
 1354      '  h (?):         help'-[],
 1355      nl, nl
 1356    ].
 1357:- else. 1358query_result(help) -->
 1359    [ ansi(bold, '  Possible actions:', []), nl,
 1360      '  ; (n,r,space,TAB): redo              | t:           trace&redo'-[], nl,
 1361      '  *:                 show choicepoint  | . (c,a,RET): stop'-[], nl,
 1362      '  w:                 write             | p:           print'-[], nl,
 1363      '  +:                 max_depth*5       | -:           max_depth//5'-[], nl,
 1364      '  b:                 break             | h (?):       help'-[],
 1365      nl, nl
 1366    ].
 1367:- endif. 1368query_result(action) -->
 1369    [ 'Action? '-[], flush ].
 1370query_result(confirm) -->
 1371    [ 'Please answer \'y\' or \'n\'? '-[], flush ].
 1372query_result(eof) -->
 1373    [ nl ].
 1374query_result(toplevel_open_line) -->
 1375    [].
 1376
 1377prompt(Answer, [], true, []-[]) -->
 1378    !,
 1379    prompt(Answer, empty).
 1380prompt(Answer, _, _, _) -->
 1381    !,
 1382    prompt(Answer, non_empty).
 1383
 1384prompt(yes, empty) -->
 1385    !,
 1386    [ ansi(truth(true), 'true.', []) ],
 1387    extra_line.
 1388prompt(yes, _) -->
 1389    !,
 1390    [ full_stop ],
 1391    extra_line.
 1392prompt(more, empty) -->
 1393    !,
 1394    [ ansi(truth(true), 'true ', []), flush ].
 1395prompt(more, _) -->
 1396    !,
 1397    [ ' '-[], flush ].
 1398
 1399result(Bindings, Delays, Residuals) -->
 1400    { current_prolog_flag(answer_write_options, Options0),
 1401      Options = [partial(true)|Options0],
 1402      GOptions = [priority(999)|Options0]
 1403    },
 1404    wfs_residual_program(Delays, GOptions),
 1405    bindings(Bindings, [priority(699)|Options]),
 1406    (   {Residuals == []-[]}
 1407    ->  bind_delays_sep(Bindings, Delays),
 1408        delays(Delays, GOptions)
 1409    ;   bind_res_sep(Bindings, Residuals),
 1410        residuals(Residuals, GOptions),
 1411        (   {Delays == true}
 1412        ->  []
 1413        ;   [','-[], nl],
 1414            delays(Delays, GOptions)
 1415        )
 1416    ).
 1417
 1418bindings([], _) -->
 1419    [].
 1420bindings([binding(Names,Skel,Subst)|T], Options) -->
 1421    { '$last'(Names, Name) },
 1422    var_names(Names), value(Name, Skel, Subst, Options),
 1423    (   { T \== [] }
 1424    ->  [ ','-[], nl ],
 1425        bindings(T, Options)
 1426    ;   []
 1427    ).
 1428
 1429var_names([Name]) -->
 1430    !,
 1431    [ '~w = '-[Name] ].
 1432var_names([Name1,Name2|T]) -->
 1433    !,
 1434    [ '~w = ~w, '-[Name1, Name2] ],
 1435    var_names([Name2|T]).
 1436
 1437
 1438value(Name, Skel, Subst, Options) -->
 1439    (   { var(Skel), Subst = [Skel=S] }
 1440    ->  { Skel = '$VAR'(Name) },
 1441        [ '~W'-[S, Options] ]
 1442    ;   [ '~W'-[Skel, Options] ],
 1443        substitution(Subst, Options)
 1444    ).
 1445
 1446substitution([], _) --> !.
 1447substitution([N=V|T], Options) -->
 1448    [ ', ', ansi(comment, '% where', []), nl,
 1449      '    ~w = ~W'-[N,V,Options] ],
 1450    substitutions(T, Options).
 1451
 1452substitutions([], _) --> [].
 1453substitutions([N=V|T], Options) -->
 1454    [ ','-[], nl, '    ~w = ~W'-[N,V,Options] ],
 1455    substitutions(T, Options).
 1456
 1457
 1458residuals(Normal-Hidden, Options) -->
 1459    residuals1(Normal, Options),
 1460    bind_res_sep(Normal, Hidden),
 1461    (   {Hidden == []}
 1462    ->  []
 1463    ;   [ansi(comment, '% with pending residual goals', []), nl]
 1464    ),
 1465    residuals1(Hidden, Options).
 1466
 1467residuals1([], _) -->
 1468    [].
 1469residuals1([G|Gs], Options) -->
 1470    (   { Gs \== [] }
 1471    ->  [ '~W,'-[G, Options], nl ],
 1472        residuals1(Gs, Options)
 1473    ;   [ '~W'-[G, Options] ]
 1474    ).
 1475
 1476wfs_residual_program(true, _Options) -->
 1477    !.
 1478wfs_residual_program(Goal, _Options) -->
 1479    { current_prolog_flag(toplevel_list_wfs_residual_program, true),
 1480      '$current_typein_module'(TypeIn),
 1481      (   current_predicate(delays_residual_program/2)
 1482      ->  true
 1483      ;   use_module(library(wfs), [delays_residual_program/2])
 1484      ),
 1485      delays_residual_program(TypeIn:Goal, TypeIn:Program),
 1486      Program \== []
 1487    },
 1488    !,
 1489    [ ansi(comment, '% WFS residual program', []), nl ],
 1490    [ ansi(wfs(residual_program), '~@', ['$messages':list_clauses(Program)]) ].
 1491wfs_residual_program(_, _) --> [].
 1492
 1493delays(true, _Options) -->
 1494    !.
 1495delays(Goal, Options) -->
 1496    { current_prolog_flag(toplevel_list_wfs_residual_program, true)
 1497    },
 1498    !,
 1499    [ ansi(truth(undefined), '~W', [Goal, Options]) ].
 1500delays(_, _Options) -->
 1501    [ ansi(truth(undefined), undefined, []) ].
 1502
 1503:- public list_clauses/1. 1504
 1505list_clauses([]).
 1506list_clauses([H|T]) :-
 1507    (   system_undefined(H)
 1508    ->  true
 1509    ;   portray_clause(user_output, H, [indent(4)])
 1510    ),
 1511    list_clauses(T).
 1512
 1513system_undefined((undefined :- tnot(undefined))).
 1514system_undefined((answer_count_restraint :- tnot(answer_count_restraint))).
 1515system_undefined((radial_restraint :- tnot(radial_restraint))).
 1516
 1517bind_res_sep(_, []) --> !.
 1518bind_res_sep(_, []-[]) --> !.
 1519bind_res_sep([], _) --> !.
 1520bind_res_sep(_, _) --> [','-[], nl].
 1521
 1522bind_delays_sep([], _) --> !.
 1523bind_delays_sep(_, true) --> !.
 1524bind_delays_sep(_, _) --> [','-[], nl].
 1525
 1526extra_line -->
 1527    { current_prolog_flag(toplevel_extra_white_line, true) },
 1528    !,
 1529    ['~N'-[]].
 1530extra_line -->
 1531    [].
 1532
 1533prolog_message(if_tty(Message)) -->
 1534    (   {current_prolog_flag(tty_control, true)}
 1535    ->  [ at_same_line ], list(Message)
 1536    ;   []
 1537    ).
 1538prolog_message(halt(Reason)) -->
 1539    [ '~w: halt'-[Reason] ].
 1540prolog_message(no_action(Char)) -->
 1541    [ 'Unknown action: ~c (h for help)'-[Char], nl ].
 1542
 1543prolog_message(history(help(Show, Help))) -->
 1544    [ 'History Commands:', nl,
 1545      '    !!.              Repeat last query', nl,
 1546      '    !nr.             Repeat query numbered <nr>', nl,
 1547      '    !str.            Repeat last query starting with <str>', nl,
 1548      '    !?str.           Repeat last query holding <str>', nl,
 1549      '    ^old^new.        Substitute <old> into <new> of last query', nl,
 1550      '    !nr^old^new.     Substitute in query numbered <nr>', nl,
 1551      '    !str^old^new.    Substitute in query starting with <str>', nl,
 1552      '    !?str^old^new.   Substitute in query holding <str>', nl,
 1553      '    ~w.~21|Show history list'-[Show], nl,
 1554      '    ~w.~21|Show this list'-[Help], nl, nl
 1555    ].
 1556prolog_message(history(no_event)) -->
 1557    [ '! No such event' ].
 1558prolog_message(history(bad_substitution)) -->
 1559    [ '! Bad substitution' ].
 1560prolog_message(history(expanded(Event))) -->
 1561    [ '~w.'-[Event] ].
 1562prolog_message(history(history(Events))) -->
 1563    history_events(Events).
 1564
 1565history_events([]) -->
 1566    [].
 1567history_events([Nr/Event|T]) -->
 1568    [ '~t~w   ~8|~W~W'-[ Nr,
 1569                         Event, [partial(true)],
 1570                         '.', [partial(true)]
 1571                       ],
 1572      nl
 1573    ],
 1574    history_events(T).
 user_version_messages(+Terms)//
Helper for the welcome message to print information registered using version/1.
 1582user_version_messages([]) --> [].
 1583user_version_messages([H|T]) -->
 1584    user_version_message(H),
 1585    user_version_messages(T).
 user_version_message(+Term)
 1589user_version_message(Term) -->
 1590    translate_message(Term), !, [nl].
 1591user_version_message(Atom) -->
 1592    [ '~w'-[Atom], nl ].
 1593
 1594
 1595                 /*******************************
 1596                 *       DEBUGGER MESSAGES      *
 1597                 *******************************/
 1598
 1599prolog_message(spy(Head)) -->
 1600    { goal_to_predicate_indicator(Head, Pred)
 1601    },
 1602    [ 'Spy point on ~p'-[Pred] ].
 1603prolog_message(nospy(Head)) -->
 1604    { goal_to_predicate_indicator(Head, Pred)
 1605    },
 1606    [ 'Spy point removed from ~p'-[Pred] ].
 1607prolog_message(trace_mode(OnOff)) -->
 1608    [ 'Trace mode switched to ~w'-[OnOff] ].
 1609prolog_message(debug_mode(OnOff)) -->
 1610    [ 'Debug mode switched to ~w'-[OnOff] ].
 1611prolog_message(debugging(OnOff)) -->
 1612    [ 'Debug mode is ~w'-[OnOff] ].
 1613prolog_message(spying([])) -->
 1614    !,
 1615    [ 'No spy points' ].
 1616prolog_message(spying(Heads)) -->
 1617    [ 'Spy points (see spy/1) on:', nl ],
 1618    predicate_list(Heads).
 1619prolog_message(trace(Head, [])) -->
 1620    !,
 1621    [ '    ' ], goal_predicate(Head), [ ' Not tracing'-[], nl].
 1622prolog_message(trace(Head, Ports)) -->
 1623    { '$member'(Port, Ports), compound(Port),
 1624      !,
 1625      numbervars(Head+Ports, 0, _, [singletons(true)])
 1626    },
 1627    [ '    ~p: ~p'-[Head,Ports] ].
 1628prolog_message(trace(Head, Ports)) -->
 1629    [ '    ' ], goal_predicate(Head), [ ': ~w'-[Ports], nl].
 1630prolog_message(tracing([])) -->
 1631    !,
 1632    [ 'No traced predicates (see trace/1,2)' ].
 1633prolog_message(tracing(Heads)) -->
 1634    [ 'Trace points (see trace/1,2) on:', nl ],
 1635    tracing_list(Heads).
 1636
 1637goal_predicate(Head) -->
 1638    { predicate_property(Head, file(File)),
 1639      predicate_property(Head, line_count(Line)),
 1640      goal_to_predicate_indicator(Head, PI),
 1641      term_string(PI, PIS, [quoted(true)])
 1642    },
 1643    [ url(File:Line, PIS) ].
 1644goal_predicate(Head) -->
 1645    { goal_to_predicate_indicator(Head, PI)
 1646    },
 1647    [ '~p'-[PI] ].
 1648
 1649
 1650predicate_list([]) -->                  % TBD: Share with dwim, etc.
 1651    [].
 1652predicate_list([H|T]) -->
 1653    [ '    ' ], goal_predicate(H), [nl],
 1654    predicate_list(T).
 1655
 1656tracing_list([]) -->
 1657    [].
 1658tracing_list([trace(Head, Ports)|T]) -->
 1659    translate_message(trace(Head, Ports)),
 1660    tracing_list(T).
 1661
 1662% frame(+Frame, +Choice, +Port, +PC) - Print for the debugger.
 1663prolog_message(frame(Frame, _Choice, backtrace, _PC)) -->
 1664    !,
 1665    { prolog_frame_attribute(Frame, level, Level)
 1666    },
 1667    [ ansi(frame(level), '~t[~D] ~10|', [Level]) ],
 1668    frame_context(Frame),
 1669    frame_goal(Frame).
 1670prolog_message(frame(Frame, _Choice, choice, PC)) -->
 1671    !,
 1672    prolog_message(frame(Frame, backtrace, PC)).
 1673prolog_message(frame(_, _Choice, cut_call(_PC), _)) --> !.
 1674prolog_message(frame(Frame, _Choice, Port, _PC)) -->
 1675    frame_flags(Frame),
 1676    port(Port),
 1677    frame_level(Frame),
 1678    frame_context(Frame),
 1679    frame_depth_limit(Port, Frame),
 1680    frame_goal(Frame),
 1681    [ flush ].
 1682
 1683% frame(:Goal, +Trace)		- Print for trace/2
 1684prolog_message(frame(Goal, trace(Port))) -->
 1685    !,
 1686    thread_context,
 1687    [ ' T ' ],
 1688    port(Port),
 1689    goal(Goal).
 1690prolog_message(frame(Goal, trace(Port, Id))) -->
 1691    !,
 1692    thread_context,
 1693    [ ' T ' ],
 1694    port(Port, Id),
 1695    goal(Goal).
 1696
 1697frame_goal(Frame) -->
 1698    { prolog_frame_attribute(Frame, goal, Goal)
 1699    },
 1700    goal(Goal).
 1701
 1702goal(Goal0) -->
 1703    { clean_goal(Goal0, Goal),
 1704      current_prolog_flag(debugger_write_options, Options)
 1705    },
 1706    [ '~W'-[Goal, Options] ].
 1707
 1708frame_level(Frame) -->
 1709    { prolog_frame_attribute(Frame, level, Level)
 1710    },
 1711    [ '(~D) '-[Level] ].
 1712
 1713frame_context(Frame) -->
 1714    (   { current_prolog_flag(debugger_show_context, true),
 1715          prolog_frame_attribute(Frame, context_module, Context)
 1716        }
 1717    ->  [ '[~w] '-[Context] ]
 1718    ;   []
 1719    ).
 1720
 1721frame_depth_limit(fail, Frame) -->
 1722    { prolog_frame_attribute(Frame, depth_limit_exceeded, true)
 1723    },
 1724    !,
 1725    [ '[depth-limit exceeded] ' ].
 1726frame_depth_limit(_, _) -->
 1727    [].
 1728
 1729frame_flags(Frame) -->
 1730    { prolog_frame_attribute(Frame, goal, Goal),
 1731      (   predicate_property(Goal, transparent)
 1732      ->  T = '^'
 1733      ;   T = ' '
 1734      ),
 1735      (   predicate_property(Goal, spying)
 1736      ->  S = '*'
 1737      ;   S = ' '
 1738      )
 1739    },
 1740    [ '~w~w '-[T, S] ].
 1741
 1742% trace/1 context handling
 1743port(Port, Dict) -->
 1744    { _{level:Level, start:Time} :< Dict
 1745    },
 1746    (   { Port \== call,
 1747          get_time(Now),
 1748          Passed is (Now - Time)*1000.0
 1749        }
 1750    ->  [ '[~d +~1fms] '-[Level, Passed] ]
 1751    ;   [ '[~d] '-[Level] ]
 1752    ),
 1753    port(Port).
 1754port(Port, _Id-Level) -->
 1755    [ '[~d] '-[Level] ],
 1756    port(Port).
 1757
 1758port(PortTerm) -->
 1759    { functor(PortTerm, Port, _),
 1760      port_name(Port, Name)
 1761    },
 1762    !,
 1763    [ ansi(port(Port), '~w: ', [Name]) ].
 1764
 1765port_name(call,      'Call').
 1766port_name(exit,      'Exit').
 1767port_name(fail,      'Fail').
 1768port_name(redo,      'Redo').
 1769port_name(unify,     'Unify').
 1770port_name(exception, 'Exception').
 1771
 1772clean_goal(M:Goal, Goal) :-
 1773    hidden_module(M),
 1774    !.
 1775clean_goal(M:Goal, Goal) :-
 1776    predicate_property(M:Goal, built_in),
 1777    !.
 1778clean_goal(Goal, Goal).
 1779
 1780
 1781                 /*******************************
 1782                 *        COMPATIBILITY         *
 1783                 *******************************/
 1784
 1785prolog_message(compatibility(renamed(Old, New))) -->
 1786    [ 'The predicate ~p has been renamed to ~p.'-[Old, New], nl,
 1787      'Please update your sources for compatibility with future versions.'
 1788    ].
 1789
 1790
 1791                 /*******************************
 1792                 *            THREADS           *
 1793                 *******************************/
 1794
 1795prolog_message(abnormal_thread_completion(Goal, exception(Ex))) -->
 1796    !,
 1797    [ 'Thread running "~p" died on exception: '-[Goal] ],
 1798    translate_message(Ex).
 1799prolog_message(abnormal_thread_completion(Goal, fail)) -->
 1800    [ 'Thread running "~p" died due to failure'-[Goal] ].
 1801prolog_message(threads_not_died(Running)) -->
 1802    [ 'The following threads wouldn\'t die: ~p'-[Running] ].
 1803
 1804
 1805                 /*******************************
 1806                 *             PACKS            *
 1807                 *******************************/
 1808
 1809prolog_message(pack(attached(Pack, BaseDir))) -->
 1810    [ 'Attached package ~w at ~q'-[Pack, BaseDir] ].
 1811prolog_message(pack(duplicate(Entry, OldDir, Dir))) -->
 1812    [ 'Package ~w already attached at ~q.'-[Entry,OldDir], nl,
 1813      '\tIgnoring version from ~q'- [Dir]
 1814    ].
 1815prolog_message(pack(no_arch(Entry, Arch))) -->
 1816    [ 'Package ~w: no binary for architecture ~w'-[Entry, Arch] ].
 1817
 1818                 /*******************************
 1819                 *             MISC             *
 1820                 *******************************/
 1821
 1822prolog_message(null_byte_in_path(Component)) -->
 1823    [ '0-byte in PATH component: ~p (skipped directory)'-[Component] ].
 1824prolog_message(invalid_tmp_dir(Dir, Reason)) -->
 1825    [ 'Cannot use ~p as temporary file directory: ~w'-[Dir, Reason] ].
 1826prolog_message(ambiguous_stream_pair(Pair)) -->
 1827    [ 'Ambiguous operation on stream pair ~p'-[Pair] ].
 1828prolog_message(backcomp(init_file_moved(FoundFile))) -->
 1829    { absolute_file_name(app_config('init.pl'), InitFile,
 1830                         [ file_errors(fail)
 1831                         ])
 1832    },
 1833    [ 'The location of the config file has moved'-[], nl,
 1834      '  from "~w"'-[FoundFile], nl,
 1835      '  to   "~w"'-[InitFile], nl,
 1836      '  See https://www.swi-prolog.org/modified/config-files.html'-[]
 1837    ].
 1838prolog_message(not_accessed_flags(List)) -->
 1839    [ 'The following Prolog flags have been set but not used:', nl ],
 1840    flags(List).
 1841prolog_message(prolog_flag_invalid_preset(Flag, Preset, _Type, New)) -->
 1842    [ 'Prolog flag ', ansi(code, '~q', Flag), ' has been (re-)created with a type that is \c
 1843       incompatible with its value.', nl,
 1844      'Value updated from ', ansi(code, '~p', [Preset]), ' to default (',
 1845      ansi(code, '~p', [New]), ')'
 1846    ].
 1847
 1848
 1849flags([H|T]) -->
 1850    ['  ', ansi(code, '~q', [H])],
 1851    (   {T == []}
 1852    ->  []
 1853    ;   [nl],
 1854        flags(T)
 1855    ).
 1856
 1857
 1858		 /*******************************
 1859		 *          DEPRECATED		*
 1860		 *******************************/
 1861
 1862deprecated(set_prolog_stack(_Stack,limit)) -->
 1863    [ 'set_prolog_stack/2: limit(Size) sets the combined limit.'-[], nl,
 1864      'See https://www.swi-prolog.org/changes/stack-limit.html'
 1865    ].
 1866deprecated(autoload(TargetModule, File, _M:PI, expansion)) -->
 1867    !,
 1868    [ 'Auto-loading ', ansi(code, '~p', [PI]), ' from ' ],
 1869    load_file(File), [ ' into ' ],
 1870    target_module(TargetModule),
 1871    [ ' is deprecated due to term- or goal-expansion' ].
 1872deprecated(source_search_working_directory(File, _FullFile)) -->
 1873    [ 'Found file ', ansi(code, '~w', [File]),
 1874      ' relative to the current working directory.', nl,
 1875      'This behaviour is deprecated but still supported by', nl,
 1876      'the Prolog flag ',
 1877      ansi(code, source_search_working_directory, []), '.', nl
 1878    ].
 1879
 1880load_file(File) -->
 1881    { file_base_name(File, Base),
 1882      absolute_file_name(library(Base), File, [access(read), file_errors(fail)]),
 1883      file_name_extension(Clean, pl, Base)
 1884    },
 1885    !,
 1886    [ ansi(code, '~p', [library(Clean)]) ].
 1887load_file(File) -->
 1888    [ url(File) ].
 1889
 1890target_module(Module) -->
 1891    { module_property(Module, file(File)) },
 1892    !,
 1893    load_file(File).
 1894target_module(Module) -->
 1895    [ 'module ', ansi(code, '~p', [Module]) ].
 1896
 1897
 1898
 1899		 /*******************************
 1900		 *           TRIPWIRES		*
 1901		 *******************************/
 1902
 1903tripwire_message(max_integer_size, Bytes) -->
 1904    !,
 1905    [ 'Trapped tripwire max_integer_size: big integers and \c
 1906       rationals are limited to ~D bytes'-[Bytes] ].
 1907tripwire_message(Wire, Context) -->
 1908    [ 'Trapped tripwire ~w for '-[Wire] ],
 1909    tripwire_context(Wire, Context).
 1910
 1911tripwire_context(_, ATrie) -->
 1912    { '$is_answer_trie'(ATrie, _),
 1913      !,
 1914      '$tabling':atrie_goal(ATrie, QGoal),
 1915      user_predicate_indicator(QGoal, Goal)
 1916    },
 1917    [ '~p'-[Goal] ].
 1918tripwire_context(_, Ctx) -->
 1919    [ '~p'-[Ctx] ].
 1920
 1921
 1922		 /*******************************
 1923		 *     INTERNATIONALIZATION	*
 1924		 *******************************/
 1925
 1926:- create_prolog_flag(message_language, default, []).
 message_lang(-Lang) is multi
True when Lang is a language id preferred for messages. Starts with the most specific language (e.g., nl_BE) and ends with en.
 1933message_lang(Lang) :-
 1934    current_message_lang(Lang0),
 1935    (   Lang0 == en
 1936    ->  Lang = en
 1937    ;   sub_atom(Lang0, 0, _, _, en_)
 1938    ->  longest_id(Lang0, Lang)
 1939    ;   (   longest_id(Lang0, Lang)
 1940        ;   Lang = en
 1941        )
 1942    ).
 1943
 1944longest_id(Lang, Id) :-
 1945    split_string(Lang, "_-", "", [H|Components]),
 1946    longest_prefix(Components, Taken),
 1947    atomic_list_concat([H|Taken], '_', Id).
 1948
 1949longest_prefix([H|T0], [H|T]) :-
 1950    longest_prefix(T0, T).
 1951longest_prefix(_, []).
 current_message_lang(-Lang) is det
Get the current language for messages.
 1957current_message_lang(Lang) :-
 1958    (   current_prolog_flag(message_language, Lang0),
 1959        Lang0 \== default
 1960    ->  Lang = Lang0
 1961    ;   os_user_lang(Lang0)
 1962    ->  clean_encoding(Lang0, Lang1),
 1963        set_prolog_flag(message_language, Lang1),
 1964        Lang = Lang1
 1965    ;   Lang = en
 1966    ).
 1967
 1968os_user_lang(Lang) :-
 1969    current_prolog_flag(windows, true),
 1970    win_get_user_preferred_ui_languages(name, [Lang|_]).
 1971os_user_lang(Lang) :-
 1972    catch(setlocale(messages, _, ''), _, fail),
 1973    setlocale(messages, Lang, Lang).
 1974os_user_lang(Lang) :-
 1975    getenv('LANG', Lang).
 1976
 1977
 1978clean_encoding(Lang0, Lang) :-
 1979    (   sub_atom(Lang0, A, _, _, '.')
 1980    ->  sub_atom(Lang0, 0, A, _, Lang)
 1981    ;   Lang = Lang0
 1982    ).
 1983
 1984		 /*******************************
 1985		 *          PRIMITIVES		*
 1986		 *******************************/
 1987
 1988code(Term) -->
 1989    code('~p', Term).
 1990
 1991code(Format, Term) -->
 1992    [ ansi(code, Format, [Term]) ].
 1993
 1994list([]) --> [].
 1995list([H|T]) --> [H], list(T).
 1996
 1997
 1998		 /*******************************
 1999		 *        DEFAULT THEME		*
 2000		 *******************************/
 2001
 2002:- public default_theme/2. 2003
 2004default_theme(var,                    [fg(red)]).
 2005default_theme(code,                   [fg(blue)]).
 2006default_theme(comment,                [fg(green)]).
 2007default_theme(warning,                [fg(red)]).
 2008default_theme(error,                  [bold, fg(red)]).
 2009default_theme(truth(false),           [bold, fg(red)]).
 2010default_theme(truth(true),            [bold]).
 2011default_theme(truth(undefined),       [bold, fg(cyan)]).
 2012default_theme(wfs(residual_program),  [fg(cyan)]).
 2013default_theme(frame(level),           [bold]).
 2014default_theme(port(call),             [bold, fg(green)]).
 2015default_theme(port(exit),             [bold, fg(green)]).
 2016default_theme(port(fail),             [bold, fg(red)]).
 2017default_theme(port(redo),             [bold, fg(yellow)]).
 2018default_theme(port(unify),            [bold, fg(blue)]).
 2019default_theme(port(exception),        [bold, fg(magenta)]).
 2020default_theme(message(informational), [fg(green)]).
 2021default_theme(message(information),   [fg(green)]).
 2022default_theme(message(debug(_)),      [fg(blue)]).
 2023default_theme(message(Level),         Attrs) :-
 2024    nonvar(Level),
 2025    default_theme(Level, Attrs).
 2026
 2027
 2028                 /*******************************
 2029                 *      PRINTING MESSAGES       *
 2030                 *******************************/
 2031
 2032:- multifile
 2033    user:message_hook/3,
 2034    prolog:message_prefix_hook/2. 2035:- dynamic
 2036    user:message_hook/3,
 2037    prolog:message_prefix_hook/2. 2038:- thread_local
 2039    user:thread_message_hook/3. 2040:- '$notransact'((user:message_hook/3,
 2041                  prolog:message_prefix_hook/2,
 2042                  user:thread_message_hook/3)).
 print_message(+Kind, +Term)
Print an error message using a term as generated by the exception system.
 2049print_message(Level, _Term) :-
 2050    msg_property(Level, stream(S)),
 2051    stream_property(S, error(true)),
 2052    !.
 2053print_message(Level, Term) :-
 2054    setup_call_cleanup(
 2055        notrace(push_msg(Term, Stack)),
 2056        ignore(print_message_guarded(Level, Term)),
 2057        notrace(pop_msg(Stack))),
 2058    !.
 2059print_message(Level, Term) :-
 2060    (   Level \== silent
 2061    ->  format(user_error, 'Recursive ~w message: ~q~n', [Level, Term]),
 2062        backtrace(20)
 2063    ;   true
 2064    ).
 2065
 2066push_msg(Term, Messages) :-
 2067    nb_current('$inprint_message', Messages),
 2068    !,
 2069    \+ ( '$member'(Msg, Messages),
 2070         Msg =@= Term
 2071       ),
 2072    Stack = [Term|Messages],
 2073    b_setval('$inprint_message', Stack).
 2074push_msg(Term, []) :-
 2075    b_setval('$inprint_message', [Term]).
 2076
 2077pop_msg(Stack) :-
 2078    nb_delete('$inprint_message'),              % delete history
 2079    b_setval('$inprint_message', Stack).
 2080
 2081print_message_guarded(Level, Term) :-
 2082    (   must_print(Level, Term)
 2083    ->  (   translate_message(Term, Lines, [])
 2084        ->  (   nonvar(Term),
 2085                (   notrace(user:thread_message_hook(Term, Level, Lines))
 2086                ->  true
 2087                ;   notrace(user:message_hook(Term, Level, Lines))
 2088                )
 2089            ->  true
 2090            ;   '$inc_message_count'(Level),
 2091                print_system_message(Term, Level, Lines),
 2092                maybe_halt_on_error(Level)
 2093            )
 2094        )
 2095    ;   true
 2096    ).
 2097
 2098maybe_halt_on_error(error) :-
 2099    current_prolog_flag(on_error, halt),
 2100    !,
 2101    halt(1).
 2102maybe_halt_on_error(warning) :-
 2103    current_prolog_flag(on_warning, halt),
 2104    !,
 2105    halt(1).
 2106maybe_halt_on_error(_).
 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.
 2116print_system_message(_, silent, _) :- !.
 2117print_system_message(_, informational, _) :-
 2118    current_prolog_flag(verbose, silent),
 2119    !.
 2120print_system_message(_, banner, _) :-
 2121    current_prolog_flag(verbose, silent),
 2122    !.
 2123print_system_message(_, _, []) :- !.
 2124print_system_message(Term, Kind, Lines) :-
 2125    catch(flush_output(user_output), _, true),      % may not exist
 2126    source_location(File, Line),
 2127    Term \= error(syntax_error(_), _),
 2128    msg_property(Kind, location_prefix(File:Line, LocPrefix, LinePrefix)),
 2129    !,
 2130    to_list(LocPrefix, LocPrefixL),
 2131    insert_prefix(Lines, LinePrefix, Ctx, PrefixLines),
 2132    '$append'([ [begin(Kind, Ctx)],
 2133                LocPrefixL,
 2134                [nl],
 2135                PrefixLines,
 2136                [end(Ctx)]
 2137              ],
 2138              AllLines),
 2139    msg_property(Kind, stream(Stream)),
 2140    ignore(stream_property(Stream, position(Pos))),
 2141    print_message_lines(Stream, AllLines),
 2142    (   \+ stream_property(Stream, position(Pos)),
 2143        msg_property(Kind, wait(Wait)),
 2144        Wait > 0
 2145    ->  sleep(Wait)
 2146    ;   true
 2147    ).
 2148print_system_message(_, Kind, Lines) :-
 2149    msg_property(Kind, stream(Stream)),
 2150    print_message_lines(Stream, kind(Kind), Lines).
 2151
 2152to_list(ListIn, List) :-
 2153    is_list(ListIn),
 2154    !,
 2155    List = ListIn.
 2156to_list(NonList, [NonList]).
 2157
 2158:- multifile
 2159    user:message_property/2. 2160
 2161msg_property(Kind, Property) :-
 2162    notrace(user:message_property(Kind, Property)),
 2163    !.
 2164msg_property(Kind, prefix(Prefix)) :-
 2165    msg_prefix(Kind, Prefix),
 2166    !.
 2167msg_property(_, prefix('~N')) :- !.
 2168msg_property(query, stream(user_output)) :- !.
 2169msg_property(_, stream(user_error)) :- !.
 2170msg_property(error, tag('ERROR')).
 2171msg_property(warning, tag('Warning')).
 2172msg_property(Level,
 2173             location_prefix(File:Line,
 2174                             ['~N~w: '-[Tag], url(File:Line), ':'],
 2175                             '~N~w:    '-[Tag])) :-
 2176    include_msg_location(Level),
 2177    msg_property(Level, tag(Tag)).
 2178msg_property(error,   wait(0.1)) :- !.
 2179
 2180include_msg_location(warning).
 2181include_msg_location(error).
 2182
 2183msg_prefix(debug(_), Prefix) :-
 2184    msg_context('~N% ', Prefix).
 2185msg_prefix(Level, Prefix) :-
 2186    msg_property(Level, tag(Tag)),
 2187    atomics_to_string(['~N', Tag, ': '], Prefix0),
 2188    msg_context(Prefix0, Prefix).
 2189msg_prefix(informational, '~N% ').
 2190msg_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.

 2204msg_context(Prefix0, Prefix) :-
 2205    current_prolog_flag(message_context, Context),
 2206    is_list(Context),
 2207    !,
 2208    add_message_context(Context, Prefix0, Prefix).
 2209msg_context(Prefix, Prefix).
 2210
 2211add_message_context([], Prefix, Prefix).
 2212add_message_context([H|T], Prefix0, Prefix) :-
 2213    (   add_message_context1(H, Prefix0, Prefix1)
 2214    ->  true
 2215    ;   Prefix1 = Prefix0
 2216    ),
 2217    add_message_context(T, Prefix1, Prefix).
 2218
 2219add_message_context1(Context, Prefix0, Prefix) :-
 2220    prolog:message_prefix_hook(Context, Extra),
 2221    atomics_to_string([Prefix0, Extra, ' '], Prefix).
 2222add_message_context1(time, Prefix0, Prefix) :-
 2223    get_time(Now),
 2224    format_time(string(S), '%T.%3f ', Now),
 2225    string_concat(Prefix0, S, Prefix).
 2226add_message_context1(time(Format), Prefix0, Prefix) :-
 2227    get_time(Now),
 2228    format_time(string(S), Format, Now),
 2229    atomics_to_string([Prefix0, S, ' '], Prefix).
 2230add_message_context1(thread, Prefix0, Prefix) :-
 2231    thread_self(Id0),
 2232    Id0 \== main,
 2233    !,
 2234    (   atom(Id0)
 2235    ->  Id = Id0
 2236    ;   thread_property(Id0, id(Id))
 2237    ),
 2238    format(string(Prefix), '~w[Thread ~w] ', [Prefix0, Id]).
 print_message_lines(+Stream, +PrefixOrKind, +Lines)
Quintus compatibility predicate to print message lines using a prefix.
 2245print_message_lines(Stream, kind(Kind), Lines) :-
 2246    !,
 2247    msg_property(Kind, prefix(Prefix)),
 2248    insert_prefix(Lines, Prefix, Ctx, PrefixLines),
 2249    '$append'([ begin(Kind, Ctx)
 2250              | PrefixLines
 2251              ],
 2252              [ end(Ctx)
 2253              ],
 2254              AllLines),
 2255    print_message_lines(Stream, AllLines).
 2256print_message_lines(Stream, Prefix, Lines) :-
 2257    insert_prefix(Lines, Prefix, _, PrefixLines),
 2258    print_message_lines(Stream, PrefixLines).
 insert_prefix(+Lines, +Prefix, +Ctx, -PrefixedLines)
 2262insert_prefix([at_same_line|Lines0], Prefix, Ctx, Lines) :-
 2263    !,
 2264    prefix_nl(Lines0, Prefix, Ctx, Lines).
 2265insert_prefix(Lines0, Prefix, Ctx, [prefix(Prefix)|Lines]) :-
 2266    prefix_nl(Lines0, Prefix, Ctx, Lines).
 2267
 2268prefix_nl([], _, _, [nl]).
 2269prefix_nl([nl], _, _, [nl]) :- !.
 2270prefix_nl([flush], _, _, [flush]) :- !.
 2271prefix_nl([nl|T0], Prefix, Ctx, [nl, prefix(Prefix)|T]) :-
 2272    !,
 2273    prefix_nl(T0, Prefix, Ctx, T).
 2274prefix_nl([ansi(Attrs,Fmt,Args)|T0], Prefix, Ctx,
 2275          [ansi(Attrs,Fmt,Args,Ctx)|T]) :-
 2276    !,
 2277    prefix_nl(T0, Prefix, Ctx, T).
 2278prefix_nl([H|T0], Prefix, Ctx, [H|T]) :-
 2279    prefix_nl(T0, Prefix, Ctx, T).
 print_message_lines(+Stream, +Lines)
 2283print_message_lines(Stream, Lines) :-
 2284    with_output_to(
 2285        Stream,
 2286        notrace(print_message_lines_guarded(current_output, Lines))).
 2287
 2288print_message_lines_guarded(_, []) :- !.
 2289print_message_lines_guarded(S, [H|T]) :-
 2290    line_element(S, H),
 2291    print_message_lines_guarded(S, T).
 2292
 2293line_element(S, E) :-
 2294    prolog:message_line_element(S, E),
 2295    !.
 2296line_element(S, full_stop) :-
 2297    !,
 2298    '$put_token'(S, '.').           % insert space if needed.
 2299line_element(S, nl) :-
 2300    !,
 2301    nl(S).
 2302line_element(S, prefix(Fmt-Args)) :-
 2303    !,
 2304    safe_format(S, Fmt, Args).
 2305line_element(S, prefix(Fmt)) :-
 2306    !,
 2307    safe_format(S, Fmt, []).
 2308line_element(S, flush) :-
 2309    !,
 2310    flush_output(S).
 2311line_element(S, Fmt-Args) :-
 2312    !,
 2313    safe_format(S, Fmt, Args).
 2314line_element(S, ansi(_, Fmt, Args)) :-
 2315    !,
 2316    safe_format(S, Fmt, Args).
 2317line_element(S, ansi(_, Fmt, Args, _Ctx)) :-
 2318    !,
 2319    safe_format(S, Fmt, Args).
 2320line_element(S, url(URL)) :-
 2321    !,
 2322    print_link(S, URL).
 2323line_element(S, url(_URL, Fmt-Args)) :-
 2324    !,
 2325    safe_format(S, Fmt, Args).
 2326line_element(S, url(_URL, Fmt)) :-
 2327    !,
 2328    safe_format(S, Fmt, []).
 2329line_element(_, begin(_Level, _Ctx)) :- !.
 2330line_element(_, end(_Ctx)) :- !.
 2331line_element(S, Fmt) :-
 2332    safe_format(S, Fmt, []).
 2333
 2334print_link(S, File:Line:Column) :-
 2335    !,
 2336    safe_format(S, '~w:~d:~d', [File, Line, Column]).
 2337print_link(S, File:Line) :-
 2338    !,
 2339    safe_format(S, '~w:~d', [File, Line]).
 2340print_link(S, File) :-
 2341    safe_format(S, '~w', [File]).
 safe_format(+Stream, +Format, +Args) is det
 2345safe_format(S, Fmt, Args) :-
 2346    E = error(_,_),
 2347    catch(format(S,Fmt,Args), E,
 2348          format_failed(S,Fmt,Args,E)).
 2349
 2350format_failed(S, _Fmt, _Args, E) :-
 2351    stream_property(S, error(true)),
 2352    !,
 2353    throw(E).
 2354format_failed(S, Fmt, Args, error(E,_)) :-
 2355    format(S, '~N    [[ EXCEPTION while printing message ~q~n\c
 2356                        ~7|with arguments ~W:~n\c
 2357                        ~7|raised: ~W~n~4|]]~n',
 2358           [ Fmt,
 2359             Args, [quoted(true), max_depth(10)],
 2360             E, [quoted(true), max_depth(10)]
 2361           ]).
 message_to_string(+Term, -String)
Translate an error term into a string
 2367message_to_string(Term, Str) :-
 2368    translate_message(Term, Actions, []),
 2369    !,
 2370    actions_to_format(Actions, Fmt, Args),
 2371    format(string(Str), Fmt, Args).
 2372
 2373actions_to_format([], '', []) :- !.
 2374actions_to_format([nl], '', []) :- !.
 2375actions_to_format([Term, nl], Fmt, Args) :-
 2376    !,
 2377    actions_to_format([Term], Fmt, Args).
 2378actions_to_format([nl|T], Fmt, Args) :-
 2379    !,
 2380    actions_to_format(T, Fmt0, Args),
 2381    atom_concat('~n', Fmt0, Fmt).
 2382actions_to_format([ansi(_Attrs, Fmt0, Args0)|Tail], Fmt, Args) :-
 2383    !,
 2384    actions_to_format(Tail, Fmt1, Args1),
 2385    atom_concat(Fmt0, Fmt1, Fmt),
 2386    append_args(Args0, Args1, Args).
 2387actions_to_format([url(Pos)|Tail], Fmt, Args) :-
 2388    !,
 2389    actions_to_format(Tail, Fmt1, Args1),
 2390    url_actions_to_format(url(Pos), Fmt1, Args1, Fmt, Args).
 2391actions_to_format([url(URL, Label)|Tail], Fmt, Args) :-
 2392    !,
 2393    actions_to_format(Tail, Fmt1, Args1),
 2394    url_actions_to_format(url(URL, Label), Fmt1, Args1, Fmt, Args).
 2395actions_to_format([Fmt0-Args0|Tail], Fmt, Args) :-
 2396    !,
 2397    actions_to_format(Tail, Fmt1, Args1),
 2398    atom_concat(Fmt0, Fmt1, Fmt),
 2399    append_args(Args0, Args1, Args).
 2400actions_to_format([Skip|T], Fmt, Args) :-
 2401    action_skip(Skip),
 2402    !,
 2403    actions_to_format(T, Fmt, Args).
 2404actions_to_format([Term|Tail], Fmt, Args) :-
 2405    atomic(Term),
 2406    !,
 2407    actions_to_format(Tail, Fmt1, Args),
 2408    atom_concat(Term, Fmt1, Fmt).
 2409actions_to_format([Term|Tail], Fmt, Args) :-
 2410    actions_to_format(Tail, Fmt1, Args1),
 2411    atom_concat('~w', Fmt1, Fmt),
 2412    append_args([Term], Args1, Args).
 2413
 2414action_skip(at_same_line).
 2415action_skip(flush).
 2416action_skip(begin(_Level, _Ctx)).
 2417action_skip(end(_Ctx)).
 2418
 2419url_actions_to_format(url(File:Line:Column), Fmt1, Args1, Fmt, Args) :-
 2420    !,
 2421    atom_concat('~w:~d:~d', Fmt1, Fmt),
 2422    append_args([File,Line,Column], Args1, Args).
 2423url_actions_to_format(url(File:Line), Fmt1, Args1, Fmt, Args) :-
 2424    !,
 2425    atom_concat('~w:~d', Fmt1, Fmt),
 2426    append_args([File,Line], Args1, Args).
 2427url_actions_to_format(url(File), Fmt1, Args1, Fmt, Args) :-
 2428    !,
 2429    atom_concat('~w', Fmt1, Fmt),
 2430    append_args([File], Args1, Args).
 2431url_actions_to_format(url(_URL, Label), Fmt1, Args1, Fmt, Args) :-
 2432    !,
 2433    atom_concat('~w', Fmt1, Fmt),
 2434    append_args([Label], Args1, Args).
 2435
 2436
 2437append_args(M:Args0, Args1, M:Args) :-
 2438    !,
 2439    strip_module(Args1, _, A1),
 2440    to_list(Args0, Args01),
 2441    '$append'(Args01, A1, Args).
 2442append_args(Args0, Args1, Args) :-
 2443    strip_module(Args1, _, A1),
 2444    to_list(Args0, Args01),
 2445    '$append'(Args01, A1, Args).
 2446
 2447                 /*******************************
 2448                 *    MESSAGES TO PRINT ONCE    *
 2449                 *******************************/
 2450
 2451:- dynamic
 2452    printed/2.
 print_once(Message, Level)
True for messages that must be printed only once.
 2458print_once(compatibility(_), _).
 2459print_once(null_byte_in_path(_), _).
 2460print_once(deprecated(_), _).
 must_print(+Level, +Message)
True if the message must be printed.
 2466must_print(Level, Message) :-
 2467    nonvar(Message),
 2468    print_once(Message, Level),
 2469    !,
 2470    \+ printed(Message, Level),
 2471    assert(printed(Message, Level)).
 2472must_print(_, _)