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

 2149msg_context(Prefix0, Prefix) :-
 2150    current_prolog_flag(message_context, Context),
 2151    is_list(Context),
 2152    !,
 2153    add_message_context(Context, Prefix0, Prefix).
 2154msg_context(Prefix, Prefix).
 2155
 2156add_message_context([], Prefix, Prefix).
 2157add_message_context([H|T], Prefix0, Prefix) :-
 2158    (   add_message_context1(H, Prefix0, Prefix1)
 2159    ->  true
 2160    ;   Prefix1 = Prefix0
 2161    ),
 2162    add_message_context(T, Prefix1, Prefix).
 2163
 2164add_message_context1(Context, Prefix0, Prefix) :-
 2165    prolog:message_prefix_hook(Context, Extra),
 2166    atomics_to_string([Prefix0, Extra, ' '], Prefix).
 2167add_message_context1(time, Prefix0, Prefix) :-
 2168    get_time(Now),
 2169    format_time(string(S), '%T.%3f ', Now),
 2170    string_concat(Prefix0, S, Prefix).
 2171add_message_context1(time(Format), Prefix0, Prefix) :-
 2172    get_time(Now),
 2173    format_time(string(S), Format, Now),
 2174    atomics_to_string([Prefix0, S, ' '], Prefix).
 2175add_message_context1(thread, Prefix0, Prefix) :-
 2176    thread_self(Id0),
 2177    Id0 \== main,
 2178    !,
 2179    (   atom(Id0)
 2180    ->  Id = Id0
 2181    ;   thread_property(Id0, id(Id))
 2182    ),
 2183    format(string(Prefix), '~w[Thread ~w] ', [Prefix0, Id]).
 print_message_lines(+Stream, +PrefixOrKind, +Lines)
Quintus compatibility predicate to print message lines using a prefix.
 2190print_message_lines(Stream, kind(Kind), Lines) :-
 2191    !,
 2192    msg_property(Kind, prefix(Prefix)),
 2193    insert_prefix(Lines, Prefix, Ctx, PrefixLines),
 2194    '$append'([ begin(Kind, Ctx)
 2195              | PrefixLines
 2196              ],
 2197              [ end(Ctx)
 2198              ],
 2199              AllLines),
 2200    print_message_lines(Stream, AllLines).
 2201print_message_lines(Stream, Prefix, Lines) :-
 2202    insert_prefix(Lines, Prefix, _, PrefixLines),
 2203    print_message_lines(Stream, PrefixLines).
 insert_prefix(+Lines, +Prefix, +Ctx, -PrefixedLines)
 2207insert_prefix([at_same_line|Lines0], Prefix, Ctx, Lines) :-
 2208    !,
 2209    prefix_nl(Lines0, Prefix, Ctx, Lines).
 2210insert_prefix(Lines0, Prefix, Ctx, [prefix(Prefix)|Lines]) :-
 2211    prefix_nl(Lines0, Prefix, Ctx, Lines).
 2212
 2213prefix_nl([], _, _, [nl]).
 2214prefix_nl([nl], _, _, [nl]) :- !.
 2215prefix_nl([flush], _, _, [flush]) :- !.
 2216prefix_nl([nl|T0], Prefix, Ctx, [nl, prefix(Prefix)|T]) :-
 2217    !,
 2218    prefix_nl(T0, Prefix, Ctx, T).
 2219prefix_nl([ansi(Attrs,Fmt,Args)|T0], Prefix, Ctx,
 2220          [ansi(Attrs,Fmt,Args,Ctx)|T]) :-
 2221    !,
 2222    prefix_nl(T0, Prefix, Ctx, T).
 2223prefix_nl([H|T0], Prefix, Ctx, [H|T]) :-
 2224    prefix_nl(T0, Prefix, Ctx, T).
 print_message_lines(+Stream, +Lines)
 2228print_message_lines(Stream, Lines) :-
 2229    with_output_to(
 2230        Stream,
 2231        notrace(print_message_lines_guarded(current_output, Lines))).
 2232
 2233print_message_lines_guarded(_, []) :- !.
 2234print_message_lines_guarded(S, [H|T]) :-
 2235    line_element(S, H),
 2236    print_message_lines_guarded(S, T).
 2237
 2238line_element(S, E) :-
 2239    prolog:message_line_element(S, E),
 2240    !.
 2241line_element(S, full_stop) :-
 2242    !,
 2243    '$put_token'(S, '.').           % insert space if needed.
 2244line_element(S, nl) :-
 2245    !,
 2246    nl(S).
 2247line_element(S, prefix(Fmt-Args)) :-
 2248    !,
 2249    safe_format(S, Fmt, Args).
 2250line_element(S, prefix(Fmt)) :-
 2251    !,
 2252    safe_format(S, Fmt, []).
 2253line_element(S, flush) :-
 2254    !,
 2255    flush_output(S).
 2256line_element(S, Fmt-Args) :-
 2257    !,
 2258    safe_format(S, Fmt, Args).
 2259line_element(S, ansi(_, Fmt, Args)) :-
 2260    !,
 2261    safe_format(S, Fmt, Args).
 2262line_element(S, ansi(_, Fmt, Args, _Ctx)) :-
 2263    !,
 2264    safe_format(S, Fmt, Args).
 2265line_element(S, url(URL)) :-
 2266    !,
 2267    print_link(S, URL).
 2268line_element(S, url(_URL, Fmt-Args)) :-
 2269    !,
 2270    safe_format(S, Fmt, Args).
 2271line_element(S, url(_URL, Fmt)) :-
 2272    !,
 2273    safe_format(S, Fmt, []).
 2274line_element(_, begin(_Level, _Ctx)) :- !.
 2275line_element(_, end(_Ctx)) :- !.
 2276line_element(S, Fmt) :-
 2277    safe_format(S, Fmt, []).
 2278
 2279print_link(S, File:Line:Column) :-
 2280    !,
 2281    safe_format(S, '~w:~d:~d', [File, Line, Column]).
 2282print_link(S, File:Line) :-
 2283    !,
 2284    safe_format(S, '~w:~d', [File, Line]).
 2285print_link(S, File) :-
 2286    safe_format(S, '~w', [File]).
 safe_format(+Stream, +Format, +Args) is det
 2290safe_format(S, Fmt, Args) :-
 2291    E = error(_,_),
 2292    catch(format(S,Fmt,Args), E,
 2293          format_failed(S,Fmt,Args,E)).
 2294
 2295format_failed(S, _Fmt, _Args, E) :-
 2296    stream_property(S, error(true)),
 2297    !,
 2298    throw(E).
 2299format_failed(S, Fmt, Args, error(E,_)) :-
 2300    format(S, '~N    [[ EXCEPTION while printing message ~q~n\c
 2301                        ~7|with arguments ~W:~n\c
 2302                        ~7|raised: ~W~n~4|]]~n',
 2303           [ Fmt,
 2304             Args, [quoted(true), max_depth(10)],
 2305             E, [quoted(true), max_depth(10)]
 2306           ]).
 message_to_string(+Term, -String)
Translate an error term into a string
 2312message_to_string(Term, Str) :-
 2313    translate_message(Term, Actions, []),
 2314    !,
 2315    actions_to_format(Actions, Fmt, Args),
 2316    format(string(Str), Fmt, Args).
 2317
 2318actions_to_format([], '', []) :- !.
 2319actions_to_format([nl], '', []) :- !.
 2320actions_to_format([Term, nl], Fmt, Args) :-
 2321    !,
 2322    actions_to_format([Term], Fmt, Args).
 2323actions_to_format([nl|T], Fmt, Args) :-
 2324    !,
 2325    actions_to_format(T, Fmt0, Args),
 2326    atom_concat('~n', Fmt0, Fmt).
 2327actions_to_format([ansi(_Attrs, Fmt0, Args0)|Tail], Fmt, Args) :-
 2328    !,
 2329    actions_to_format(Tail, Fmt1, Args1),
 2330    atom_concat(Fmt0, Fmt1, Fmt),
 2331    append_args(Args0, Args1, Args).
 2332actions_to_format([url(Pos)|Tail], Fmt, Args) :-
 2333    !,
 2334    actions_to_format(Tail, Fmt1, Args1),
 2335    url_actions_to_format(url(Pos), Fmt1, Args1, Fmt, Args).
 2336actions_to_format([url(URL, Label)|Tail], Fmt, Args) :-
 2337    !,
 2338    actions_to_format(Tail, Fmt1, Args1),
 2339    url_actions_to_format(url(URL, Label), Fmt1, Args1, Fmt, Args).
 2340actions_to_format([Fmt0-Args0|Tail], Fmt, Args) :-
 2341    !,
 2342    actions_to_format(Tail, Fmt1, Args1),
 2343    atom_concat(Fmt0, Fmt1, Fmt),
 2344    append_args(Args0, Args1, Args).
 2345actions_to_format([Skip|T], Fmt, Args) :-
 2346    action_skip(Skip),
 2347    !,
 2348    actions_to_format(T, Fmt, Args).
 2349actions_to_format([Term|Tail], Fmt, Args) :-
 2350    atomic(Term),
 2351    !,
 2352    actions_to_format(Tail, Fmt1, Args),
 2353    atom_concat(Term, Fmt1, Fmt).
 2354actions_to_format([Term|Tail], Fmt, Args) :-
 2355    actions_to_format(Tail, Fmt1, Args1),
 2356    atom_concat('~w', Fmt1, Fmt),
 2357    append_args([Term], Args1, Args).
 2358
 2359action_skip(at_same_line).
 2360action_skip(flush).
 2361action_skip(begin(_Level, _Ctx)).
 2362action_skip(end(_Ctx)).
 2363
 2364url_actions_to_format(url(File:Line:Column), Fmt1, Args1, Fmt, Args) :-
 2365    !,
 2366    atom_concat('~w:~d:~d', Fmt1, Fmt),
 2367    append_args([File,Line,Column], Args1, Args).
 2368url_actions_to_format(url(File:Line), Fmt1, Args1, Fmt, Args) :-
 2369    !,
 2370    atom_concat('~w:~d', Fmt1, Fmt),
 2371    append_args([File,Line], Args1, Args).
 2372url_actions_to_format(url(File), Fmt1, Args1, Fmt, Args) :-
 2373    !,
 2374    atom_concat('~w', Fmt1, Fmt),
 2375    append_args([File], Args1, Args).
 2376url_actions_to_format(url(_URL, Label), Fmt1, Args1, Fmt, Args) :-
 2377    !,
 2378    atom_concat('~w', Fmt1, Fmt),
 2379    append_args([Label], Args1, Args).
 2380
 2381
 2382append_args(M:Args0, Args1, M:Args) :-
 2383    !,
 2384    strip_module(Args1, _, A1),
 2385    to_list(Args0, Args01),
 2386    '$append'(Args01, A1, Args).
 2387append_args(Args0, Args1, Args) :-
 2388    strip_module(Args1, _, A1),
 2389    to_list(Args0, Args01),
 2390    '$append'(Args01, A1, Args).
 2391
 2392                 /*******************************
 2393                 *    MESSAGES TO PRINT ONCE    *
 2394                 *******************************/
 2395
 2396:- dynamic
 2397    printed/2.
 print_once(Message, Level)
True for messages that must be printed only once.
 2403print_once(compatibility(_), _).
 2404print_once(null_byte_in_path(_), _).
 2405print_once(deprecated(_), _).
 must_print(+Level, +Message)
True if the message must be printed.
 2411must_print(Level, Message) :-
 2412    nonvar(Message),
 2413    print_once(Message, Level),
 2414    !,
 2415    \+ printed(Message, Level),
 2416    assert(printed(Message, Level)).
 2417must_print(_, _)