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

 2232msg_context(Prefix0, Prefix) :-
 2233    current_prolog_flag(message_context, Context),
 2234    is_list(Context),
 2235    !,
 2236    add_message_context(Context, Prefix0, Prefix).
 2237msg_context(Prefix, Prefix).
 2238
 2239add_message_context([], Prefix, Prefix).
 2240add_message_context([H|T], Prefix0, Prefix) :-
 2241    (   add_message_context1(H, Prefix0, Prefix1)
 2242    ->  true
 2243    ;   Prefix1 = Prefix0
 2244    ),
 2245    add_message_context(T, Prefix1, Prefix).
 2246
 2247add_message_context1(Context, Prefix0, Prefix) :-
 2248    prolog:message_prefix_hook(Context, Extra),
 2249    atomics_to_string([Prefix0, Extra, ' '], Prefix).
 2250add_message_context1(time, Prefix0, Prefix) :-
 2251    get_time(Now),
 2252    format_time(string(S), '%T.%3f ', Now),
 2253    string_concat(Prefix0, S, Prefix).
 2254add_message_context1(time(Format), Prefix0, Prefix) :-
 2255    get_time(Now),
 2256    format_time(string(S), Format, Now),
 2257    atomics_to_string([Prefix0, S, ' '], Prefix).
 2258add_message_context1(thread, Prefix0, Prefix) :-
 2259    \+ current_prolog_flag(toplevel_thread, true),
 2260    thread_self(Id0),
 2261    !,
 2262    (   atom(Id0)
 2263    ->  Id = Id0
 2264    ;   thread_property(Id0, id(Id))
 2265    ),
 2266    format(string(Prefix), '~w[Thread ~w] ', [Prefix0, Id]).
 print_message_lines(+Stream, +PrefixOrKind, +Lines)
Quintus compatibility predicate to print message lines using a prefix.
 2273print_message_lines(Stream, kind(Kind), Lines) :-
 2274    !,
 2275    msg_property(Kind, prefix(Prefix)),
 2276    insert_prefix(Lines, Prefix, Ctx, PrefixLines),
 2277    '$append'([ begin(Kind, Ctx)
 2278              | PrefixLines
 2279              ],
 2280              [ end(Ctx)
 2281              ],
 2282              AllLines),
 2283    print_message_lines(Stream, AllLines).
 2284print_message_lines(Stream, Prefix, Lines) :-
 2285    insert_prefix(Lines, Prefix, _, PrefixLines),
 2286    print_message_lines(Stream, PrefixLines).
 insert_prefix(+Lines, +Prefix, +Ctx, -PrefixedLines)
 2290insert_prefix([at_same_line|Lines0], Prefix, Ctx, Lines) :-
 2291    !,
 2292    prefix_nl(Lines0, Prefix, Ctx, Lines).
 2293insert_prefix(Lines0, Prefix, Ctx, [prefix(Prefix)|Lines]) :-
 2294    prefix_nl(Lines0, Prefix, Ctx, Lines).
 2295
 2296prefix_nl([], _, _, [nl]).
 2297prefix_nl([nl], _, _, [nl]) :- !.
 2298prefix_nl([flush], _, _, [flush]) :- !.
 2299prefix_nl([nl|T0], Prefix, Ctx, [nl, prefix(Prefix)|T]) :-
 2300    !,
 2301    prefix_nl(T0, Prefix, Ctx, T).
 2302prefix_nl([ansi(Attrs,Fmt,Args)|T0], Prefix, Ctx,
 2303          [ansi(Attrs,Fmt,Args,Ctx)|T]) :-
 2304    !,
 2305    prefix_nl(T0, Prefix, Ctx, T).
 2306prefix_nl([H|T0], Prefix, Ctx, [H|T]) :-
 2307    prefix_nl(T0, Prefix, Ctx, T).
 print_message_lines(+Stream, +Lines)
 2311print_message_lines(Stream, Lines) :-
 2312    with_output_to(
 2313        Stream,
 2314        notrace(print_message_lines_guarded(current_output, Lines))).
 2315
 2316print_message_lines_guarded(_, []) :- !.
 2317print_message_lines_guarded(S, [H|T]) :-
 2318    line_element(S, H),
 2319    print_message_lines_guarded(S, T).
 2320
 2321line_element(S, E) :-
 2322    prolog:message_line_element(S, E),
 2323    !.
 2324line_element(S, full_stop) :-
 2325    !,
 2326    '$put_token'(S, '.').           % insert space if needed.
 2327line_element(S, nl) :-
 2328    !,
 2329    nl(S).
 2330line_element(S, prefix(Fmt-Args)) :-
 2331    !,
 2332    safe_format(S, Fmt, Args).
 2333line_element(S, prefix(Fmt)) :-
 2334    !,
 2335    safe_format(S, Fmt, []).
 2336line_element(S, flush) :-
 2337    !,
 2338    flush_output(S).
 2339line_element(S, Fmt-Args) :-
 2340    !,
 2341    safe_format(S, Fmt, Args).
 2342line_element(S, ansi(_, Fmt, Args)) :-
 2343    !,
 2344    safe_format(S, Fmt, Args).
 2345line_element(S, ansi(_, Fmt, Args, _Ctx)) :-
 2346    !,
 2347    safe_format(S, Fmt, Args).
 2348line_element(S, url(URL)) :-
 2349    !,
 2350    print_link(S, URL).
 2351line_element(S, url(_URL, Fmt-Args)) :-
 2352    !,
 2353    safe_format(S, Fmt, Args).
 2354line_element(S, url(_URL, Fmt)) :-
 2355    !,
 2356    safe_format(S, Fmt, []).
 2357line_element(_, begin(_Level, _Ctx)) :- !.
 2358line_element(_, end(_Ctx)) :- !.
 2359line_element(S, Fmt) :-
 2360    safe_format(S, Fmt, []).
 2361
 2362print_link(S, File:Line:Column) :-
 2363    !,
 2364    safe_format(S, '~w:~d:~d', [File, Line, Column]).
 2365print_link(S, File:Line) :-
 2366    !,
 2367    safe_format(S, '~w:~d', [File, Line]).
 2368print_link(S, File) :-
 2369    safe_format(S, '~w', [File]).
 safe_format(+Stream, +Format, +Args) is det
 2373safe_format(S, Fmt, Args) :-
 2374    E = error(_,_),
 2375    catch(format(S,Fmt,Args), E,
 2376          format_failed(S,Fmt,Args,E)).
 2377
 2378format_failed(S, _Fmt, _Args, E) :-
 2379    stream_property(S, error(true)),
 2380    !,
 2381    throw(E).
 2382format_failed(S, Fmt, Args, error(E,_)) :-
 2383    format(S, '~N    [[ EXCEPTION while printing message ~q~n\c
 2384                        ~7|with arguments ~W:~n\c
 2385                        ~7|raised: ~W~n~4|]]~n',
 2386           [ Fmt,
 2387             Args, [quoted(true), max_depth(10)],
 2388             E, [quoted(true), max_depth(10)]
 2389           ]).
 message_to_string(+Term, -String)
Translate an error term into a string
 2395message_to_string(Term, Str) :-
 2396    translate_message(Term, Actions, []),
 2397    !,
 2398    actions_to_format(Actions, Fmt, Args),
 2399    format(string(Str), Fmt, Args).
 2400
 2401actions_to_format([], '', []) :- !.
 2402actions_to_format([nl], '', []) :- !.
 2403actions_to_format([Term, nl], Fmt, Args) :-
 2404    !,
 2405    actions_to_format([Term], Fmt, Args).
 2406actions_to_format([nl|T], Fmt, Args) :-
 2407    !,
 2408    actions_to_format(T, Fmt0, Args),
 2409    atom_concat('~n', Fmt0, Fmt).
 2410actions_to_format([ansi(_Attrs, Fmt0, Args0)|Tail], Fmt, Args) :-
 2411    !,
 2412    actions_to_format(Tail, Fmt1, Args1),
 2413    atom_concat(Fmt0, Fmt1, Fmt),
 2414    append_args(Args0, Args1, Args).
 2415actions_to_format([url(Pos)|Tail], Fmt, Args) :-
 2416    !,
 2417    actions_to_format(Tail, Fmt1, Args1),
 2418    url_actions_to_format(url(Pos), Fmt1, Args1, Fmt, Args).
 2419actions_to_format([url(URL, Label)|Tail], Fmt, Args) :-
 2420    !,
 2421    actions_to_format(Tail, Fmt1, Args1),
 2422    url_actions_to_format(url(URL, Label), Fmt1, Args1, Fmt, Args).
 2423actions_to_format([Fmt0-Args0|Tail], Fmt, Args) :-
 2424    !,
 2425    actions_to_format(Tail, Fmt1, Args1),
 2426    atom_concat(Fmt0, Fmt1, Fmt),
 2427    append_args(Args0, Args1, Args).
 2428actions_to_format([Skip|T], Fmt, Args) :-
 2429    action_skip(Skip),
 2430    !,
 2431    actions_to_format(T, Fmt, Args).
 2432actions_to_format([Term|Tail], Fmt, Args) :-
 2433    atomic(Term),
 2434    !,
 2435    actions_to_format(Tail, Fmt1, Args),
 2436    atom_concat(Term, Fmt1, Fmt).
 2437actions_to_format([Term|Tail], Fmt, Args) :-
 2438    actions_to_format(Tail, Fmt1, Args1),
 2439    atom_concat('~w', Fmt1, Fmt),
 2440    append_args([Term], Args1, Args).
 2441
 2442action_skip(at_same_line).
 2443action_skip(flush).
 2444action_skip(begin(_Level, _Ctx)).
 2445action_skip(end(_Ctx)).
 2446
 2447url_actions_to_format(url(File:Line:Column), Fmt1, Args1, Fmt, Args) :-
 2448    !,
 2449    atom_concat('~w:~d:~d', Fmt1, Fmt),
 2450    append_args([File,Line,Column], Args1, Args).
 2451url_actions_to_format(url(File:Line), Fmt1, Args1, Fmt, Args) :-
 2452    !,
 2453    atom_concat('~w:~d', Fmt1, Fmt),
 2454    append_args([File,Line], Args1, Args).
 2455url_actions_to_format(url(File), Fmt1, Args1, Fmt, Args) :-
 2456    !,
 2457    atom_concat('~w', Fmt1, Fmt),
 2458    append_args([File], Args1, Args).
 2459url_actions_to_format(url(_URL, Label), Fmt1, Args1, Fmt, Args) :-
 2460    !,
 2461    atom_concat('~w', Fmt1, Fmt),
 2462    append_args([Label], Args1, Args).
 2463
 2464
 2465append_args(M:Args0, Args1, M:Args) :-
 2466    !,
 2467    strip_module(Args1, _, A1),
 2468    to_list(Args0, Args01),
 2469    '$append'(Args01, A1, Args).
 2470append_args(Args0, Args1, Args) :-
 2471    strip_module(Args1, _, A1),
 2472    to_list(Args0, Args01),
 2473    '$append'(Args01, A1, Args).
 2474
 2475                 /*******************************
 2476                 *    MESSAGES TO PRINT ONCE    *
 2477                 *******************************/
 2478
 2479:- dynamic
 2480    printed/2.
 print_once(Message, Level)
True for messages that must be printed only once.
 2486print_once(compatibility(_), _).
 2487print_once(null_byte_in_path(_), _).
 2488print_once(deprecated(_), _).
 must_print(+Level, +Message)
True if the message must be printed.
 2494must_print(Level, Message) :-
 2495    nonvar(Message),
 2496    print_once(Message, Level),
 2497    !,
 2498    \+ printed(Message, Level),
 2499    assert(printed(Message, Level)).
 2500must_print(_, _)