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

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