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

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