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

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