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