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-2017, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module('$messages',
   37          [ print_message/2,            % +Kind, +Term
   38            print_message_lines/3,      % +Stream, +Prefix, +Lines
   39            message_to_string/2         % +Term, -String
   40          ]).   41
   42:- multifile
   43    prolog:message//1,              % entire message
   44    prolog:error_message//1,        % 1-st argument of error term
   45    prolog:message_context//1,      % Context of error messages
   46    prolog:message_location//1,     % (File) location of error messages
   47    prolog:message_line_element/2.  % Extend printing
   48:- discontiguous
   49    prolog_message/3.   50
   51:- public
   52    translate_message//1.   53
   54%!  translate_message(+Term)// is det.
   55%
   56%   Translate a message Term into message lines. The produced lines
   57%   is a list of
   58%
   59%       * nl
   60%       Emit a newline
   61%       * Fmt-Args
   62%       Emit the result of format(Fmt, Args)
   63%       * Fmt
   64%       Emit the result of format(Fmt)
   65%       * flush
   66%       Used only as last element of the list.   Simply flush the
   67%       output instead of producing a final newline.
   68%       * at_same_line
   69%       Start the messages at the same line (instead of using ~N)
   70
   71translate_message(Term) -->
   72    translate_message2(Term),
   73    !.
   74translate_message(Term) -->
   75    { Term = error(_, _) },
   76    [ 'Unknown exception: ~p'-[Term] ].
   77translate_message(Term) -->
   78    [ 'Unknown message: ~p'-[Term] ].
   79
   80translate_message2(Term) -->
   81    {var(Term)},
   82    !,
   83    [ 'Unknown message: ~p'-[Term] ].
   84translate_message2(Term) -->
   85    prolog:message(Term).
   86translate_message2(Term) -->
   87    prolog_message(Term).
   88translate_message2(error(resource_error(stack), Name)) -->
   89    [ 'Out of ~w stack'-[Name] ].
   90translate_message2(error(resource_error(Missing), _)) -->
   91    [ 'Not enough resources: ~w'-[Missing] ].
   92translate_message2(error(ISO, SWI)) -->
   93    swi_location(SWI),
   94    term_message(ISO),
   95    swi_extra(SWI).
   96translate_message2('$aborted') -->
   97    [ 'Execution Aborted' ].
   98translate_message2(message_lines(Lines), L, T) :- % deal with old C-warning()
   99    make_message_lines(Lines, L, T).
  100translate_message2(format(Fmt, Args)) -->
  101    [ Fmt-Args ].
  102
  103make_message_lines([], T, T) :- !.
  104make_message_lines([Last],  ['~w'-[Last]|T], T) :- !.
  105make_message_lines([L0|LT], ['~w'-[L0],nl|T0], T) :-
  106    make_message_lines(LT, T0, T).
  107
  108term_message(Term) -->
  109    {var(Term)},
  110    !,
  111    [ 'Unknown error term: ~p'-[Term] ].
  112term_message(Term) -->
  113    prolog:error_message(Term).
  114term_message(Term) -->
  115    iso_message(Term).
  116term_message(Term) -->
  117    swi_message(Term).
  118term_message(Term) -->
  119    [ 'Unknown error term: ~p'-[Term] ].
  120
  121iso_message(type_error(evaluable, Actual)) -->
  122    { callable(Actual) },
  123    [ 'Arithmetic: `~p'' is not a function'-[Actual] ].
  124iso_message(type_error(free_of_attvar, Actual)) -->
  125    [ 'Type error: `~W'' contains attributed variables'-
  126      [Actual,[portray(true), attributes(portray)]] ].
  127iso_message(type_error(Expected, Actual)) -->
  128    [ 'Type error: `~w'' expected, found `~p'''-[Expected, Actual] ],
  129    type_error_comment(Expected, Actual).
  130iso_message(domain_error(Domain, Actual)) -->
  131    [ 'Domain error: '-[] ], domain(Domain),
  132    [ ' expected, found `~p'''-[Actual] ].
  133iso_message(instantiation_error) -->
  134    [ 'Arguments are not sufficiently instantiated' ].
  135iso_message(uninstantiation_error(Var)) -->
  136    [ 'Uninstantiated argument expected, found ~p'-[Var] ].
  137iso_message(representation_error(What)) -->
  138    [ 'Cannot represent due to `~w'''-[What] ].
  139iso_message(permission_error(Action, Type, Object)) -->
  140    permission_error(Action, Type, Object).
  141iso_message(evaluation_error(Which)) -->
  142    [ 'Arithmetic: evaluation error: `~p'''-[Which] ].
  143iso_message(existence_error(procedure, Proc)) -->
  144    [ 'Undefined procedure: ~q'-[Proc] ],
  145    undefined_proc_msg(Proc).
  146iso_message(existence_error(answer_variable, Var)) -->
  147    [ '$~w was not bound by a previous query'-[Var] ].
  148iso_message(existence_error(Type, Object)) -->
  149    [ '~w `~p'' does not exist'-[Type, Object] ].
  150iso_message(existence_error(Type, Object, In)) --> % not ISO
  151    [ '~w `~p'' does not exist in ~p'-[Type, Object, In] ].
  152iso_message(busy(Type, Object)) -->
  153    [ '~w `~p'' is busy'-[Type, Object] ].
  154iso_message(syntax_error(swi_backslash_newline)) -->
  155    [ 'Deprecated ... \\<newline><white>*.  Use \\c' ].
  156iso_message(syntax_error(Id)) -->
  157    [ 'Syntax error: ' ],
  158    syntax_error(Id).
  159iso_message(occurs_check(Var, In)) -->
  160    [ 'Cannot unify ~p with ~p: would create an infinite tree'-[Var, In] ].
  161
  162%!  permission_error(Action, Type, Object)//
  163%
  164%   Translate  permission  errors.  Most  follow    te  pattern  "No
  165%   permission to Action Type Object", but some are a bit different.
  166
  167permission_error(Action, built_in_procedure, Pred) -->
  168    { user_predicate_indicator(Pred, PI)
  169    },
  170    [ 'No permission to ~w built-in predicate `~p'''-[Action, PI] ],
  171    (   {Action \== export}
  172    ->  [ nl,
  173          'Use :- redefine_system_predicate(+Head) if redefinition is intended'
  174        ]
  175    ;   []
  176    ).
  177permission_error(import_into(Dest), procedure, Pred) -->
  178    [ 'No permission to import ~p into ~w'-[Pred, Dest] ].
  179permission_error(Action, static_procedure, Proc) -->
  180    [ 'No permission to ~w static procedure `~p'''-[Action, Proc] ],
  181    defined_definition('Defined', Proc).
  182permission_error(input, stream, Stream) -->
  183    [ 'No permission to read from output stream `~p'''-[Stream] ].
  184permission_error(output, stream, Stream) -->
  185    [ 'No permission to write to input stream `~p'''-[Stream] ].
  186permission_error(input, text_stream, Stream) -->
  187    [ 'No permission to read bytes from TEXT stream `~p'''-[Stream] ].
  188permission_error(output, text_stream, Stream) -->
  189    [ 'No permission to write bytes to TEXT stream `~p'''-[Stream] ].
  190permission_error(input, binary_stream, Stream) -->
  191    [ 'No permission to read characters from binary stream `~p'''-[Stream] ].
  192permission_error(output, binary_stream, Stream) -->
  193    [ 'No permission to write characters to binary stream `~p'''-[Stream] ].
  194permission_error(open, source_sink, alias(Alias)) -->
  195    [ 'No permission to reuse alias "~p": already taken'-[Alias] ].
  196permission_error(Action, Type, Object) -->
  197    [ 'No permission to ~w ~w `~p'''-[Action, Type, Object] ].
  198
  199
  200undefined_proc_msg(_:(^)/2) -->
  201    !,
  202    undefined_proc_msg((^)/2).
  203undefined_proc_msg((^)/2) -->
  204    !,
  205    [nl, '  ^/2 can only appear as the 2nd argument of setof/3 and bagof/3'].
  206undefined_proc_msg((:-)/2) -->
  207    !,
  208    [nl, '  Rules must be loaded from a file'],
  209    faq('ToplevelMode').
  210undefined_proc_msg((:-)/1) -->
  211    !,
  212    [nl, '  Directives must be loaded from a file'],
  213    faq('ToplevelMode').
  214undefined_proc_msg((?-)/1) -->
  215    !,
  216    [nl, '  ?- is the Prolog prompt'],
  217    faq('ToplevelMode').
  218undefined_proc_msg(Proc) -->
  219    { dwim_predicates(Proc, Dwims) },
  220    (   {Dwims \== []}
  221    ->  [nl, '  However, there are definitions for:', nl],
  222        dwim_message(Dwims)
  223    ;   []
  224    ).
  225
  226faq(Page) -->
  227    [nl, '  See FAQ at http://www.swi-prolog.org/FAQ/', Page, '.txt' ].
  228
  229type_error_comment(_Expected, Actual) -->
  230    { type_of(Actual, Type),
  231      (   sub_atom(Type, 0, 1, _, First),
  232          memberchk(First, [a,e,i,o,u])
  233      ->  Article = an
  234      ;   Article = a
  235      )
  236    },
  237    [ ' (~w ~w)'-[Article, Type] ].
  238
  239type_of(Term, Type) :-
  240    (   attvar(Term)      -> Type = attvar
  241    ;   var(Term)         -> Type = var
  242    ;   atom(Term)        -> Type = atom
  243    ;   integer(Term)     -> Type = integer
  244    ;   string(Term)      -> Type = string
  245    ;   Term == []        -> Type = empty_list
  246    ;   blob(Term, BlobT) -> blob_type(BlobT, Type)
  247    ;   rational(Term)    -> Type = rational
  248    ;   float(Term)       -> Type = float
  249    ;   is_stream(Term)   -> Type = stream
  250    ;   is_dict(Term)     -> Type = dict
  251    ;   is_list(Term)     -> Type = list
  252    ;   cyclic_term(Term) -> Type = cyclic
  253    ;   compound(Term)    -> Type = compound
  254    ;                        Type = unknown
  255    ).
  256
  257blob_type(BlobT, Type) :-
  258    atom_concat(BlobT, '_reference', Type).
  259
  260syntax_error(end_of_clause) -->
  261    [ 'Unexpected end of clause' ].
  262syntax_error(end_of_clause_expected) -->
  263    [ 'End of clause expected' ].
  264syntax_error(end_of_file) -->
  265    [ 'Unexpected end of file' ].
  266syntax_error(end_of_file_in_block_comment) -->
  267    [ 'End of file in /* ... */ comment' ].
  268syntax_error(end_of_file_in_quoted(Quote)) -->
  269    [ 'End of file in quoted ' ],
  270    quoted_type(Quote).
  271syntax_error(illegal_number) -->
  272    [ 'Illegal number' ].
  273syntax_error(long_atom) -->
  274    [ 'Atom too long (see style_check/1)' ].
  275syntax_error(long_string) -->
  276    [ 'String too long (see style_check/1)' ].
  277syntax_error(operator_clash) -->
  278    [ 'Operator priority clash' ].
  279syntax_error(operator_expected) -->
  280    [ 'Operator expected' ].
  281syntax_error(operator_balance) -->
  282    [ 'Unbalanced operator' ].
  283syntax_error(quoted_punctuation) -->
  284    [ 'Operand expected, unquoted comma or bar found' ].
  285syntax_error(list_rest) -->
  286    [ 'Unexpected comma or bar in rest of list' ].
  287syntax_error(cannot_start_term) -->
  288    [ 'Illegal start of term' ].
  289syntax_error(punct(Punct, End)) -->
  290    [ 'Unexpected `~w\' before `~w\''-[Punct, End] ].
  291syntax_error(undefined_char_escape(C)) -->
  292    [ 'Undefined character escape in quoted atom or string: `\\~w\''-[C] ].
  293syntax_error(void_not_allowed) -->
  294    [ 'Empty argument list "()"' ].
  295syntax_error(Message) -->
  296    [ '~w'-[Message] ].
  297
  298quoted_type('\'') --> [atom].
  299quoted_type('\"') --> { current_prolog_flag(double_quotes, Type) }, [Type-[]].
  300quoted_type('\`') --> { current_prolog_flag(back_quotes, Type) }, [Type-[]].
  301
  302domain(range(Low,High)) -->
  303    !,
  304    ['[~q..~q]'-[Low,High] ].
  305domain(Domain) -->
  306    ['`~w\''-[Domain] ].
  307
  308dwim_predicates(Module:Name/_Arity, Dwims) :-
  309    !,
  310    findall(Dwim, dwim_predicate(Module:Name, Dwim), Dwims).
  311dwim_predicates(Name/_Arity, Dwims) :-
  312    findall(Dwim, dwim_predicate(user:Name, Dwim), Dwims).
  313
  314dwim_message([]) --> [].
  315dwim_message([M:Head|T]) -->
  316    { hidden_module(M),
  317      !,
  318      functor(Head, Name, Arity)
  319    },
  320    [ '        ~q'-[Name/Arity], nl ],
  321    dwim_message(T).
  322dwim_message([Module:Head|T]) -->
  323    !,
  324    { functor(Head, Name, Arity)
  325    },
  326    [ '        ~q'-[Module:Name/Arity], nl],
  327    dwim_message(T).
  328dwim_message([Head|T]) -->
  329    {functor(Head, Name, Arity)},
  330    [ '        ~q'-[Name/Arity], nl],
  331    dwim_message(T).
  332
  333
  334swi_message(io_error(Op, Stream)) -->
  335    [ 'I/O error in ~w on stream ~p'-[Op, Stream] ].
  336swi_message(shell(execute, Cmd)) -->
  337    [ 'Could not execute `~w'''-[Cmd] ].
  338swi_message(shell(signal(Sig), Cmd)) -->
  339    [ 'Caught signal ~d on `~w'''-[Sig, Cmd] ].
  340swi_message(format(Fmt, Args)) -->
  341    [ Fmt-Args ].
  342swi_message(signal(Name, Num)) -->
  343    [ 'Caught signal ~d (~w)'-[Num, Name] ].
  344swi_message(limit_exceeded(Limit, MaxVal)) -->
  345    [ 'Exceeded ~w limit (~w)'-[Limit, MaxVal] ].
  346swi_message(goal_failed(Goal)) -->
  347    [ 'goal unexpectedly failed: ~p'-[Goal] ].
  348swi_message(shared_object(_Action, Message)) --> % Message = dlerror()
  349    [ '~w'-[Message] ].
  350swi_message(system_error(Error)) -->
  351    [ 'error in system call: ~w'-[Error]
  352    ].
  353swi_message(system_error) -->
  354    [ 'error in system call'
  355    ].
  356swi_message(failure_error(Goal)) -->
  357    [ 'Goal failed: ~p'-[Goal] ].
  358swi_message(timeout_error(Op, Stream)) -->
  359    [ 'Timeout in ~w from ~p'-[Op, Stream] ].
  360swi_message(not_implemented(Type, What)) -->
  361    [ '~w `~p\' is not implemented in this version'-[Type, What] ].
  362swi_message(context_error(nodirective, Goal)) -->
  363    { goal_to_predicate_indicator(Goal, PI) },
  364    [ 'Wrong context: ~p can only be used in a directive'-[PI] ].
  365swi_message(context_error(edit, no_default_file)) -->
  366    (   { current_prolog_flag(windows, true) }
  367    ->  [ 'Edit/0 can only be used after opening a \c
  368               Prolog file by double-clicking it' ]
  369    ;   [ 'Edit/0 can only be used with the "-s file" commandline option'
  370        ]
  371    ),
  372    [ nl, 'Use "?- edit(Topic)." or "?- emacs."' ].
  373swi_message(context_error(function, meta_arg(S))) -->
  374    [ 'Functions are not (yet) supported for meta-arguments of type ~q'-[S] ].
  375swi_message(format_argument_type(Fmt, Arg)) -->
  376    [ 'Illegal argument to format sequence ~~~w: ~p'-[Fmt, Arg] ].
  377swi_message(format(Msg)) -->
  378    [ 'Format error: ~w'-[Msg] ].
  379swi_message(conditional_compilation_error(unterminated, Where)) -->
  380    [ 'Unterminated conditional compilation from '-[] ],
  381    cond_location(Where).
  382swi_message(conditional_compilation_error(no_if, What)) -->
  383    [ ':- ~w without :- if'-[What] ].
  384swi_message(duplicate_key(Key)) -->
  385    [ 'Duplicate key: ~p'-[Key] ].
  386swi_message(initialization_error(failed, Goal, File:Line)) -->
  387    !,
  388    [ '~w:~w: ~p: false'-[File, Line, Goal] ].
  389swi_message(initialization_error(Error, Goal, File:Line)) -->
  390    [ '~w:~w: ~p '-[File, Line, Goal] ],
  391    translate_message(Error).
  392
  393cond_location(File:Line) -->
  394    { file_base_name(File, Base) },
  395    [ '~w:~d'-[Base, Line] ].
  396
  397swi_location(X) -->
  398    { var(X)
  399    },
  400    !,
  401    [].
  402swi_location(Context) -->
  403    prolog:message_location(Context),
  404    !.
  405swi_location(context(Caller, _Msg)) -->
  406    { ground(Caller)
  407    },
  408    !,
  409    caller(Caller).
  410swi_location(file(Path, Line, -1, _CharNo)) -->
  411    !,
  412    [ '~w:~d: '-[Path, Line] ].
  413swi_location(file(Path, Line, LinePos, _CharNo)) -->
  414    [ '~w:~d:~d: '-[Path, Line, LinePos] ].
  415swi_location(stream(Stream, Line, LinePos, CharNo)) -->
  416    (   { is_stream(Stream),
  417          stream_property(Stream, file_name(File))
  418        }
  419    ->  swi_location(file(File, Line, LinePos, CharNo))
  420    ;   [ 'Stream ~w:~d:~d '-[Stream, Line, LinePos] ]
  421    ).
  422swi_location(_) -->
  423    [].
  424
  425caller(system:'$record_clause'/3) -->
  426    !,
  427    [].
  428caller(Module:Name/Arity) -->
  429    !,
  430    (   { \+ hidden_module(Module) }
  431    ->  [ '~q:~q/~w: '-[Module, Name, Arity] ]
  432    ;   [ '~q/~w: '-[Name, Arity] ]
  433    ).
  434caller(Name/Arity) -->
  435    [ '~q/~w: '-[Name, Arity] ].
  436caller(Caller) -->
  437    [ '~p: '-[Caller] ].
  438
  439
  440swi_extra(X) -->
  441    { var(X)
  442    },
  443    !,
  444    [].
  445swi_extra(Context) -->
  446    prolog:message_context(Context).
  447swi_extra(context(_, Msg)) -->
  448    { nonvar(Msg),
  449      Msg \== ''
  450    },
  451    !,
  452    swi_comment(Msg).
  453swi_extra(string(String, CharPos)) -->
  454    { sub_string(String, 0, CharPos, _, Before),
  455      sub_string(String, CharPos, _, 0, After)
  456    },
  457    [ nl, '~w'-[Before], nl, '** here **', nl, '~w'-[After] ].
  458swi_extra(_) -->
  459    [].
  460
  461swi_comment(already_from(Module)) -->
  462    !,
  463    [ ' (already imported from ~q)'-[Module] ].
  464swi_comment(directory(_Dir)) -->
  465    !,
  466    [ ' (is a directory)' ].
  467swi_comment(not_a_directory(_Dir)) -->
  468    !,
  469    [ ' (is not a directory)' ].
  470swi_comment(Msg) -->
  471    [ ' (~w)'-[Msg] ].
  472
  473
  474thread_context -->
  475    { thread_self(Me), Me \== main, thread_property(Me, id(Id)) },
  476    !,
  477    ['[Thread ~w] '-[Id]].
  478thread_context -->
  479    [].
  480
  481                 /*******************************
  482                 *        NORMAL MESSAGES       *
  483                 *******************************/
  484
  485prolog_message(initialization_error(_, E, File:Line)) -->
  486    !,
  487    [ '~w:~d: '-[File, Line],
  488      'Initialization goal raised exception:', nl
  489    ],
  490    translate_message(E).
  491prolog_message(initialization_error(Goal, E, _)) -->
  492    [ 'Initialization goal ~p raised exception:'-[Goal], nl ],
  493    translate_message(E).
  494prolog_message(initialization_failure(_Goal, File:Line)) -->
  495    !,
  496    [ '~w:~d: '-[File, Line],
  497      'Initialization goal failed'-[]
  498    ].
  499prolog_message(initialization_failure(Goal, _)) -->
  500    [ 'Initialization goal failed: ~p'-[Goal]
  501    ].
  502prolog_message(initialization_exception(E)) -->
  503    [ 'Prolog initialisation failed:', nl ],
  504    translate_message(E).
  505prolog_message(init_goal_syntax(Error, Text)) -->
  506    !,
  507    [ '-g ~w: '-[Text] ],
  508    translate_message(Error).
  509prolog_message(init_goal_failed(failed, @(Goal,File:Line))) -->
  510    !,
  511    [ '~w:~w: ~p: false'-[File, Line, Goal] ].
  512prolog_message(init_goal_failed(Error, @(Goal,File:Line))) -->
  513    !,
  514    [ '~w:~w: ~p '-[File, Line, Goal] ],
  515    translate_message(Error).
  516prolog_message(init_goal_failed(failed, Text)) -->
  517    !,
  518    [ '-g ~w: false'-[Text] ].
  519prolog_message(init_goal_failed(Error, Text)) -->
  520    !,
  521    [ '-g ~w: '-[Text] ],
  522    translate_message(Error).
  523prolog_message(unhandled_exception(E)) -->
  524    [ 'Unhandled exception: ' ],
  525    (   translate_message2(E)
  526    ->  []
  527    ;   [ '~p'-[E] ]
  528    ).
  529prolog_message(goal_failed(Context, Goal)) -->
  530    [ 'Goal (~w) failed: ~p'-[Context, Goal] ].
  531prolog_message(no_current_module(Module)) -->
  532    [ '~w is not a current module (created)'-[Module] ].
  533prolog_message(commandline_arg_type(Flag, Arg)) -->
  534    [ 'Bad argument to commandline option -~w: ~w'-[Flag, Arg] ].
  535prolog_message(missing_feature(Name)) -->
  536    [ 'This version of SWI-Prolog does not support ~w'-[Name] ].
  537prolog_message(singletons(List)) -->
  538    [ 'Singleton variables: ~w'-[List] ].
  539prolog_message(multitons(List)) -->
  540    [ 'Singleton-marked variables appearing more than once: ~w'-[List] ].
  541prolog_message(profile_no_cpu_time) -->
  542    [ 'No CPU-time info.  Check the SWI-Prolog manual for details' ].
  543prolog_message(non_ascii(Text, Type)) -->
  544    [ 'Unquoted ~w with non-portable characters: ~w'-[Type, Text] ].
  545prolog_message(io_warning(Stream, Message)) -->
  546    { stream_property(Stream, position(Position)),
  547      !,
  548      stream_position_data(line_count, Position, LineNo),
  549      stream_position_data(line_position, Position, LinePos),
  550      (   stream_property(Stream, file_name(File))
  551      ->  Obj = File
  552      ;   Obj = Stream
  553      )
  554    },
  555    [ '~p:~d:~d: ~w'-[Obj, LineNo, LinePos, Message] ].
  556prolog_message(io_warning(Stream, Message)) -->
  557    [ 'stream ~p: ~w'-[Stream, Message] ].
  558prolog_message(option_usage(pldoc)) -->
  559    [ 'Usage: --pldoc[=port]' ].
  560prolog_message(interrupt(begin)) -->
  561    [ 'Action (h for help) ? ', flush ].
  562prolog_message(interrupt(end)) -->
  563    [ 'continue' ].
  564prolog_message(interrupt(trace)) -->
  565    [ 'continue (trace mode)' ].
  566prolog_message(unknown_in_module_user) -->
  567    [ 'Using a non-error value for unknown in the global module', nl,
  568      'causes most of the development environment to stop working.', nl,
  569      'Please use :- dynamic or limit usage of unknown to a module.', nl,
  570      'See http://www.swi-prolog.org/howto/database.html'
  571    ].
  572
  573
  574                 /*******************************
  575                 *         LOADING FILES        *
  576                 *******************************/
  577
  578prolog_message(modify_active_procedure(Who, What)) -->
  579    [ '~p: modified active procedure ~p'-[Who, What] ].
  580prolog_message(load_file(failed(user:File))) -->
  581    [ 'Failed to load ~p'-[File] ].
  582prolog_message(load_file(failed(Module:File))) -->
  583    [ 'Failed to load ~p into module ~p'-[File, Module] ].
  584prolog_message(load_file(failed(File))) -->
  585    [ 'Failed to load ~p'-[File] ].
  586prolog_message(mixed_directive(Goal)) -->
  587    [ 'Cannot pre-compile mixed load/call directive: ~p'-[Goal] ].
  588prolog_message(cannot_redefine_comma) -->
  589    [ 'Full stop in clause-body?  Cannot redefine ,/2' ].
  590prolog_message(illegal_autoload_index(Dir, Term)) -->
  591    [ 'Illegal term in INDEX file of directory ~w: ~w'-[Dir, Term] ].
  592prolog_message(redefined_procedure(Type, Proc)) -->
  593    [ 'Redefined ~w procedure ~p'-[Type, Proc] ],
  594    defined_definition('Previously defined', Proc).
  595prolog_message(declare_module(Module, abolish(Predicates))) -->
  596    [ 'Loading module ~w abolished: ~p'-[Module, Predicates] ].
  597prolog_message(import_private(Module, Private)) -->
  598    [ 'import/1: ~p is not exported (still imported into ~q)'-
  599      [Private, Module]
  600    ].
  601prolog_message(ignored_weak_import(Into, From:PI)) -->
  602    [ 'Local definition of ~p overrides weak import from ~q'-
  603      [Into:PI, From]
  604    ].
  605prolog_message(undefined_export(Module, PI)) -->
  606    [ 'Exported procedure ~q:~q is not defined'-[Module, PI] ].
  607prolog_message(no_exported_op(Module, Op)) -->
  608    [ 'Operator ~q:~q is not exported (still defined)'-[Module, Op] ].
  609prolog_message(discontiguous((-)/2,_)) -->
  610    prolog_message(minus_in_identifier).
  611prolog_message(discontiguous(Proc,Current)) -->
  612    [ 'Clauses of ~p are not together in the source-file'-[Proc], nl ],
  613    current_definition(Proc, '  Earlier definition at '),
  614    [ '  Current predicate: ~p'-[Current], nl,
  615      '  Use :- discontiguous ~p. to suppress this message'-[Proc]
  616    ].
  617prolog_message(decl_no_effect(Goal)) -->
  618    [ 'Deprecated declaration has no effect: ~p'-[Goal] ].
  619prolog_message(load_file(start(Level, File))) -->
  620    [ '~|~t~*+Loading '-[Level] ],
  621    load_file(File),
  622    [ ' ...' ].
  623prolog_message(include_file(start(Level, File))) -->
  624    [ '~|~t~*+include '-[Level] ],
  625    load_file(File),
  626    [ ' ...' ].
  627prolog_message(include_file(done(Level, File))) -->
  628    [ '~|~t~*+included '-[Level] ],
  629    load_file(File).
  630prolog_message(load_file(done(Level, File, Action, Module, Time, Clauses))) -->
  631    [ '~|~t~*+'-[Level] ],
  632    load_file(File),
  633    [ ' ~w'-[Action] ],
  634    load_module(Module),
  635    [ ' ~2f sec, ~D clauses'-[Time, Clauses] ].
  636prolog_message(dwim_undefined(Goal, Alternatives)) -->
  637    { goal_to_predicate_indicator(Goal, Pred)
  638    },
  639    [ 'Undefined procedure: ~q'-[Pred], nl,
  640      '    However, there are definitions for:', nl
  641    ],
  642    dwim_message(Alternatives).
  643prolog_message(dwim_correct(Into)) -->
  644    [ 'Correct to: ~q? '-[Into], flush ].
  645prolog_message(error(loop_error(Spec), file_search(Used))) -->
  646    [ 'File search: too many levels of indirections on: ~p'-[Spec], nl,
  647      '    Used alias expansions:', nl
  648    ],
  649    used_search(Used).
  650prolog_message(minus_in_identifier) -->
  651    [ 'The "-" character should not be used to seperate words in an', nl,
  652      'identifier.  Check the SWI-Prolog FAQ for details.'
  653    ].
  654prolog_message(qlf(removed_after_error(File))) -->
  655    [ 'Removed incomplete QLF file ~w'-[File] ].
  656prolog_message(redefine_module(Module, OldFile, File)) -->
  657    [ 'Module "~q" already loaded from ~w.'-[Module, OldFile], nl,
  658      'Wipe and reload from ~w? '-[File], flush
  659    ].
  660prolog_message(redefine_module_reply) -->
  661    [ 'Please answer y(es), n(o) or a(bort)' ].
  662prolog_message(reloaded_in_module(Absolute, OldContext, LM)) -->
  663    [ '~w was previously loaded in module ~w'-[Absolute, OldContext], nl,
  664      '\tnow it is reloaded into module ~w'-[LM] ].
  665prolog_message(expected_layout(Expected, Pos)) -->
  666    [ 'Layout data: expected ~w, found: ~p'-[Expected, Pos] ].
  667
  668defined_definition(Message, Spec) -->
  669    { strip_module(user:Spec, M, Name/Arity),
  670      functor(Head, Name, Arity),
  671      predicate_property(M:Head, file(File)),
  672      predicate_property(M:Head, line_count(Line))
  673    },
  674    !,
  675    [ nl, '~w at ~w:~d'-[Message, File,Line] ].
  676defined_definition(_, _) --> [].
  677
  678used_search([]) -->
  679    [].
  680used_search([Alias=Expanded|T]) -->
  681    [ '        file_search_path(~p, ~p)'-[Alias, Expanded], nl ],
  682    used_search(T).
  683
  684load_file(file(Spec, _Path)) -->
  685    (   {atomic(Spec)}
  686    ->  [ '~w'-[Spec] ]
  687    ;   [ '~p'-[Spec] ]
  688    ).
  689%load_file(file(_, Path)) -->
  690%       [ '~w'-[Path] ].
  691
  692load_module(user) --> !.
  693load_module(system) --> !.
  694load_module(Module) -->
  695    [ ' into ~w'-[Module] ].
  696
  697goal_to_predicate_indicator(Goal, PI) :-
  698    strip_module(Goal, Module, Head),
  699    callable_name_arity(Head, Name, Arity),
  700    user_predicate_indicator(Module:Name/Arity, PI).
  701
  702callable_name_arity(Goal, Name, Arity) :-
  703    compound(Goal),
  704    !,
  705    compound_name_arity(Goal, Name, Arity).
  706callable_name_arity(Goal, Goal, 0) :-
  707    atom(Goal).
  708
  709user_predicate_indicator(Module:PI, PI) :-
  710    hidden_module(Module),
  711    !.
  712user_predicate_indicator(PI, PI).
  713
  714hidden_module(user) :- !.
  715hidden_module(system) :- !.
  716hidden_module(M) :-
  717    sub_atom(M, 0, _, _, $).
  718
  719current_definition(Proc, Prefix) -->
  720    { pi_head(Proc, Head),
  721      predicate_property(Head, file(File)),
  722      predicate_property(Head, line_count(Line))
  723    },
  724    [ '~w'-[Prefix], '~w:~d'-[File,Line], nl ].
  725current_definition(_, _) --> [].
  726
  727pi_head(Module:Name/Arity, Module:Head) :-
  728    !,
  729    atom(Module), atom(Name), integer(Arity),
  730    functor(Head, Name, Arity).
  731pi_head(Name/Arity, user:Head) :-
  732    atom(Name), integer(Arity),
  733    functor(Head, Name, Arity).
  734
  735prolog_message(file_search(cache(Spec, _Cond), Path)) -->
  736    [ 'File search: ~p --> ~p (cache)'-[Spec, Path] ].
  737prolog_message(file_search(found(Spec, Cond), Path)) -->
  738    [ 'File search: ~p --> ~p OK ~p'-[Spec, Path, Cond] ].
  739prolog_message(file_search(tried(Spec, Cond), Path)) -->
  740    [ 'File search: ~p --> ~p NO ~p'-[Spec, Path, Cond] ].
  741
  742                 /*******************************
  743                 *              GC              *
  744                 *******************************/
  745
  746prolog_message(gc(start)) -->
  747    thread_context,
  748    [ 'GC: ', flush ].
  749prolog_message(gc(done(G, T, Time, UG, UT, RG, RT))) -->
  750    [ at_same_line,
  751      'gained ~D+~D in ~3f sec; used ~D+~D; free ~D+~D'-
  752      [G, T, Time, UG, UT, RG, RT]
  753    ].
  754prolog_message(shift_stacks(start(_L,_G,_T))) -->
  755    thread_context,
  756    [ 'Stack-shift: ', flush ].
  757prolog_message(shift_stacks(done(Time, L, G, T))) -->
  758    { LKB is L//1024,
  759      GKB is G//1024,
  760      TKB is T//1024
  761    },
  762    [ at_same_line,
  763      'local: ~DKB, global: ~DKB, trail: ~DKB bytes (~2f sec)'-
  764      [LKB, GKB, TKB, Time]
  765    ].
  766prolog_message(agc(start)) -->
  767    thread_context,
  768    [ 'AGC: ', flush ].
  769prolog_message(agc(done(Collected, Remaining, Time))) -->
  770    [ at_same_line,
  771      'reclaimed ~D atoms in ~3f sec. (remaining: ~D)'-
  772      [Collected, Time, Remaining]
  773    ].
  774prolog_message(cgc(start)) -->
  775    thread_context,
  776    [ 'CGC: ', flush ].
  777prolog_message(cgc(done(CollectedClauses, _CollectedBytes,
  778                        RemainingBytes, Time))) -->
  779    [ at_same_line,
  780      'reclaimed ~D clauses in ~3f sec. (pending: ~D bytes)'-
  781      [CollectedClauses, Time, RemainingBytes]
  782    ].
  783
  784
  785
  786                 /*******************************
  787                 *        MAKE/AUTOLOAD         *
  788                 *******************************/
  789
  790prolog_message(make(reload(Files))) -->
  791    { length(Files, N)
  792    },
  793    [ 'Make: reloading ~D files'-[N] ].
  794prolog_message(make(done(_Files))) -->
  795    [ 'Make: finished' ].
  796prolog_message(make(library_index(Dir))) -->
  797    [ 'Updating index for library ~w'-[Dir] ].
  798prolog_message(autoload(Pred, File)) -->
  799    thread_context,
  800    [ 'autoloading ~p from ~w'-[Pred, File] ].
  801prolog_message(autoload(read_index(Dir))) -->
  802    [ 'Loading autoload index for ~w'-[Dir] ].
  803
  804
  805                 /*******************************
  806                 *       COMPILER WARNINGS      *
  807                 *******************************/
  808
  809% print warnings about dubious code raised by the compiler.
  810% TBD: pass in PC to produce exact error locations.
  811
  812prolog_message(compiler_warnings(Clause, Warnings0)) -->
  813    {   print_goal_options(DefOptions),
  814        (   prolog_load_context(variable_names, VarNames)
  815        ->  warnings_with_named_vars(Warnings0, VarNames, Warnings),
  816            Options = [variable_names(VarNames)|DefOptions]
  817        ;   Options = DefOptions,
  818            Warnings = Warnings0
  819        )
  820    },
  821    compiler_warnings(Warnings, Clause, Options).
  822
  823warnings_with_named_vars([], _, []).
  824warnings_with_named_vars([H|T0], VarNames, [H|T]) :-
  825    term_variables(H, Vars),
  826    '$member'(V1, Vars),
  827    '$member'(_=V2, VarNames),
  828    V1 == V2,
  829    !,
  830    warnings_with_named_vars(T0, VarNames, T).
  831warnings_with_named_vars([_|T0], VarNames, T) :-
  832    warnings_with_named_vars(T0, VarNames, T).
  833
  834
  835compiler_warnings([], _, _) --> [].
  836compiler_warnings([H|T], Clause, Options) -->
  837    (   compiler_warning(H, Clause, Options)
  838    ->  []
  839    ;   [ 'Unknown compiler warning: ~W'-[H,Options] ]
  840    ),
  841    (   {T==[]}
  842    ->  []
  843    ;   [nl]
  844    ),
  845    compiler_warnings(T, Clause, Options).
  846
  847compiler_warning(eq_vv(A,B), _Clause, Options) -->
  848    (   { A == B }
  849    ->  [ 'Test is always true: ~W'-[A==B, Options] ]
  850    ;   [ 'Test is always false: ~W'-[A==B, Options] ]
  851    ).
  852compiler_warning(eq_singleton(A,B), _Clause, Options) -->
  853    [ 'Test is always false: ~W'-[A==B, Options] ].
  854compiler_warning(neq_vv(A,B), _Clause, Options) -->
  855    (   { A \== B }
  856    ->  [ 'Test is always true: ~W'-[A\==B, Options] ]
  857    ;   [ 'Test is always false: ~W'-[A\==B, Options] ]
  858    ).
  859compiler_warning(neq_singleton(A,B), _Clause, Options) -->
  860    [ 'Test is always true: ~W'-[A\==B, Options] ].
  861compiler_warning(unify_singleton(A,B), _Clause, Options) -->
  862    [ 'Unified variable is not used: ~W'-[A=B, Options] ].
  863compiler_warning(always(Bool, Pred, Arg), _Clause, Options) -->
  864    { Goal =.. [Pred,Arg] },
  865    [ 'Test is always ~w: ~W'-[Bool, Goal, Options] ].
  866compiler_warning(unbalanced_var(V), _Clause, Options) -->
  867    [ 'Variable not introduced in all branches: ~W'-[V, Options] ].
  868compiler_warning(branch_singleton(V), _Clause, Options) -->
  869    [ 'Singleton variable in branch: ~W'-[V, Options] ].
  870compiler_warning(negation_singleton(V), _Clause, Options) -->
  871    [ 'Singleton variable in \\+: ~W'-[V, Options] ].
  872compiler_warning(multiton(V), _Clause, Options) -->
  873    [ 'Singleton-marked variable appears more than once: ~W'-[V, Options] ].
  874
  875print_goal_options(
  876    [ quoted(true),
  877      portray(true)
  878    ]).
  879
  880
  881                 /*******************************
  882                 *      TOPLEVEL MESSAGES       *
  883                 *******************************/
  884
  885prolog_message(version) -->
  886    { current_prolog_flag(version_git, Version) },
  887    !,
  888    [ '~w'-[Version] ].
  889prolog_message(version) -->
  890    { current_prolog_flag(version_data, swi(Major,Minor,Patch,Options))
  891    },
  892    (   { memberchk(tag(Tag), Options) }
  893    ->  [ '~w.~w.~w-~w'-[Major, Minor, Patch, Tag] ]
  894    ;   [ '~w.~w.~w'-[Major, Minor, Patch] ]
  895    ).
  896prolog_message(address_bits) -->
  897    { current_prolog_flag(address_bits, Bits)
  898    },
  899    !,
  900    [ '~d bits, '-[Bits] ].
  901prolog_message(threads) -->
  902    { current_prolog_flag(threads, true)
  903    },
  904    !,
  905    [ 'threaded, ' ].
  906prolog_message(threads) -->
  907    [].
  908prolog_message(copyright) -->
  909    [ 'SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.', nl,
  910      'Please run ?- license. for legal details.'
  911    ].
  912prolog_message(user_versions) -->
  913    { findall(Msg, prolog:version_msg(Msg), Msgs) },
  914    user_version_messages(Msgs).
  915prolog_message(documentaton) -->
  916    [ 'For online help and background, visit http://www.swi-prolog.org', nl,
  917      'For built-in help, use ?- help(Topic). or ?- apropos(Word).'
  918    ].
  919prolog_message(author) -->
  920    [ 'Jan Wielemaker (jan@swi-prolog.org)' ].
  921prolog_message(welcome) -->
  922    [ 'Welcome to SWI-Prolog (' ],
  923    prolog_message(threads),
  924    prolog_message(address_bits),
  925    ['version ' ],
  926    prolog_message(version),
  927    [ ')', nl ],
  928    prolog_message(copyright),
  929    [ nl ],
  930    prolog_message(user_versions),
  931    [ nl ],
  932    prolog_message(documentaton),
  933    [ nl, nl ].
  934prolog_message(about) -->
  935    [ 'SWI-Prolog version ' ],
  936    prolog_message(version),
  937    [ ' by ' ],
  938    prolog_message(author),
  939    [ nl ],
  940    prolog_message(copyright).
  941prolog_message(halt) -->
  942    [ 'halt' ].
  943prolog_message(break(begin, Level)) -->
  944    [ 'Break level ~d'-[Level] ].
  945prolog_message(break(end, Level)) -->
  946    [ 'Exit break level ~d'-[Level] ].
  947prolog_message(var_query(_)) -->
  948    [ '... 1,000,000 ............ 10,000,000 years later', nl, nl,
  949      '~t~8|>> 42 << (last release gives the question)'
  950    ].
  951prolog_message(close_on_abort(Stream)) -->
  952    [ 'Abort: closed stream ~p'-[Stream] ].
  953prolog_message(cancel_halt(Reason)) -->
  954    [ 'Halt cancelled: ~p'-[Reason] ].
  955
  956prolog_message(query(QueryResult)) -->
  957    query_result(QueryResult).
  958
  959query_result(no) -->            % failure
  960    [ ansi([bold,fg(red)], 'false.', []) ],
  961    extra_line.
  962query_result(yes([])) -->      % prompt_alternatives_on: groundness
  963    !,
  964    [ ansi(bold, 'true.', []) ],
  965    extra_line.
  966query_result(yes(Residuals)) -->
  967    result([], Residuals),
  968    extra_line.
  969query_result(done) -->          % user typed <CR>
  970    extra_line.
  971query_result(yes(Bindings, Residuals)) -->
  972    result(Bindings, Residuals),
  973    prompt(yes, Bindings, Residuals).
  974query_result(more(Bindings, Residuals)) -->
  975    result(Bindings, Residuals),
  976    prompt(more, Bindings, Residuals).
  977query_result(help) -->
  978    [ nl, 'Actions:'-[], nl, nl,
  979      '; (n, r, space, TAB): redo    t:          trace & redo'-[], nl,
  980      'b:                    break   c (a, RET): exit'-[], nl,
  981      'w:                    write   p           print'-[], nl,
  982      'h (?):                help'-[],
  983      nl, nl
  984    ].
  985query_result(action) -->
  986    [ 'Action? '-[], flush ].
  987query_result(confirm) -->
  988    [ 'Please answer \'y\' or \'n\'? '-[], flush ].
  989query_result(eof) -->
  990    [ nl ].
  991query_result(toplevel_open_line) -->
  992    [].
  993
  994prompt(Answer, [], []-[]) -->
  995    !,
  996    prompt(Answer, empty).
  997prompt(Answer, _, _) -->
  998    !,
  999    prompt(Answer, non_empty).
 1000
 1001prompt(yes, empty) -->
 1002    !,
 1003    [ ansi(bold, 'true.', []) ],
 1004    extra_line.
 1005prompt(yes, _) -->
 1006    !,
 1007    [ full_stop ],
 1008    extra_line.
 1009prompt(more, empty) -->
 1010    !,
 1011    [ ansi(bold, 'true ', []), flush ].
 1012prompt(more, _) -->
 1013    !,
 1014    [ ' '-[], flush ].
 1015
 1016result(Bindings, Residuals) -->
 1017    { current_prolog_flag(answer_write_options, Options0),
 1018      Options = [partial(true)|Options0]
 1019    },
 1020    bindings(Bindings, [priority(699)|Options]),
 1021    bind_res_sep(Bindings, Residuals),
 1022    residuals(Residuals, [priority(999)|Options]).
 1023
 1024bindings([], _) -->
 1025    [].
 1026bindings([binding(Names,Skel,Subst)|T], Options) -->
 1027    { '$last'(Names, Name) },
 1028    var_names(Names), value(Name, Skel, Subst, Options),
 1029    (   { T \== [] }
 1030    ->  [ ','-[], nl ],
 1031        bindings(T, Options)
 1032    ;   []
 1033    ).
 1034
 1035var_names([Name]) -->
 1036    !,
 1037    [ '~w = '-[Name] ].
 1038var_names([Name1,Name2|T]) -->
 1039    !,
 1040    [ '~w = ~w, '-[Name1, Name2] ],
 1041    var_names([Name2|T]).
 1042
 1043
 1044value(Name, Skel, Subst, Options) -->
 1045    (   { var(Skel), Subst = [Skel=S] }
 1046    ->  { Skel = '$VAR'(Name) },
 1047        [ '~W'-[S, Options] ]
 1048    ;   [ '~W'-[Skel, Options] ],
 1049        substitution(Subst, Options)
 1050    ).
 1051
 1052substitution([], _) --> !.
 1053substitution([N=V|T], Options) -->
 1054    [ ', ', ansi(fg(green), '% where', []), nl,
 1055      '    ~w = ~W'-[N,V,Options] ],
 1056    substitutions(T, Options).
 1057
 1058substitutions([], _) --> [].
 1059substitutions([N=V|T], Options) -->
 1060    [ ','-[], nl, '    ~w = ~W'-[N,V,Options] ],
 1061    substitutions(T, Options).
 1062
 1063
 1064residuals(Normal-Hidden, Options) -->
 1065    residuals1(Normal, Options),
 1066    bind_res_sep(Normal, Hidden),
 1067    (   {Hidden == []}
 1068    ->  []
 1069    ;   [ansi(fg(green), '% with pending residual goals', []), nl]
 1070    ),
 1071    residuals1(Hidden, Options).
 1072
 1073residuals1([], _) -->
 1074    [].
 1075residuals1([G|Gs], Options) -->
 1076    (   { Gs \== [] }
 1077    ->  [ '~W,'-[G, Options], nl ],
 1078        residuals1(Gs, Options)
 1079    ;   [ '~W'-[G, Options] ]
 1080    ).
 1081
 1082bind_res_sep(_, []) --> !.
 1083bind_res_sep(_, []-[]) --> !.
 1084bind_res_sep([], _) --> !.
 1085bind_res_sep(_, _) --> [','-[], nl].
 1086
 1087extra_line -->
 1088    { current_prolog_flag(toplevel_extra_white_line, true) },
 1089    !,
 1090    ['~N'-[]].
 1091extra_line -->
 1092    [].
 1093
 1094prolog_message(if_tty(Message)) -->
 1095    (   {current_prolog_flag(tty_control, true)}
 1096    ->  [ at_same_line | Message ]
 1097    ;   []
 1098    ).
 1099prolog_message(halt(Reason)) -->
 1100    [ '~w: halt'-[Reason] ].
 1101prolog_message(no_action(Char)) -->
 1102    [ 'Unknown action: ~c (h for help)'-[Char], nl ].
 1103
 1104prolog_message(history(help(Show, Help))) -->
 1105    [ 'History Commands:', nl,
 1106      '    !!.              Repeat last query', nl,
 1107      '    !nr.             Repeat query numbered <nr>', nl,
 1108      '    !str.            Repeat last query starting with <str>', nl,
 1109      '    !?str.           Repeat last query holding <str>', nl,
 1110      '    ^old^new.        Substitute <old> into <new> of last query', nl,
 1111      '    !nr^old^new.     Substitute in query numbered <nr>', nl,
 1112      '    !str^old^new.    Substitute in query starting with <str>', nl,
 1113      '    !?str^old^new.   Substitute in query holding <str>', nl,
 1114      '    ~w.~21|Show history list'-[Show], nl,
 1115      '    ~w.~21|Show this list'-[Help], nl, nl
 1116    ].
 1117prolog_message(history(no_event)) -->
 1118    [ '! No such event' ].
 1119prolog_message(history(bad_substitution)) -->
 1120    [ '! Bad substitution' ].
 1121prolog_message(history(expanded(Event))) -->
 1122    [ '~w.'-[Event] ].
 1123prolog_message(history(history(Events))) -->
 1124    history_events(Events).
 1125
 1126history_events([]) -->
 1127    [].
 1128history_events([Nr/Event|T]) -->
 1129    [ '~t~w   ~8|~W~W'-[ Nr,
 1130                         Event, [partial(true)],
 1131                         '.', [partial(true)]
 1132                       ],
 1133      nl
 1134    ],
 1135    history_events(T).
 1136
 1137
 1138user_version_messages([]) --> [].
 1139user_version_messages([H|T]) -->
 1140    user_version_message(H),
 1141    user_version_messages(T).
 1142
 1143%!  user_version_message(+Term)
 1144
 1145user_version_message(Term) -->
 1146    translate_message2(Term), !, [nl].
 1147user_version_message(Atom) -->
 1148    [ '~w'-[Atom], nl ].
 1149
 1150
 1151                 /*******************************
 1152                 *       DEBUGGER MESSAGES      *
 1153                 *******************************/
 1154
 1155prolog_message(spy(Head)) -->
 1156    { goal_to_predicate_indicator(Head, Pred)
 1157    },
 1158    [ 'Spy point on ~p'-[Pred] ].
 1159prolog_message(nospy(Head)) -->
 1160    { goal_to_predicate_indicator(Head, Pred)
 1161    },
 1162    [ 'Spy point removed from ~p'-[Pred] ].
 1163prolog_message(trace_mode(Bool)) -->
 1164    [ 'Trace mode switched to ~w'-[Bool] ].
 1165prolog_message(debug_mode(Bool)) -->
 1166    [ 'Debug mode switched to ~w'-[Bool] ].
 1167prolog_message(debugging(Bool)) -->
 1168    [ 'Debug mode is ~w'-[Bool] ].
 1169prolog_message(spying([])) -->
 1170    !,
 1171    [ 'No spy points' ].
 1172prolog_message(spying(Heads)) -->
 1173    [ 'Spy points (see spy/1) on:', nl ],
 1174    predicate_list(Heads).
 1175prolog_message(trace(Head, [])) -->
 1176    !,
 1177    { goal_to_predicate_indicator(Head, Pred)
 1178    },
 1179    [ '        ~p: Not tracing'-[Pred], nl].
 1180prolog_message(trace(Head, Ports)) -->
 1181    { goal_to_predicate_indicator(Head, Pred)
 1182    },
 1183    [ '        ~p: ~w'-[Pred, Ports], nl].
 1184prolog_message(tracing([])) -->
 1185    !,
 1186    [ 'No traced predicates (see trace/1)' ].
 1187prolog_message(tracing(Heads)) -->
 1188    [ 'Trace points (see trace/1) on:', nl ],
 1189    tracing_list(Heads).
 1190
 1191predicate_list([]) -->                  % TBD: Share with dwim, etc.
 1192    [].
 1193predicate_list([H|T]) -->
 1194    { goal_to_predicate_indicator(H, Pred)
 1195    },
 1196    [ '        ~p'-[Pred], nl],
 1197    predicate_list(T).
 1198
 1199tracing_list([]) -->
 1200    [].
 1201tracing_list([trace(Head, Ports)|T]) -->
 1202    translate_message(trace(Head, Ports)),
 1203    tracing_list(T).
 1204
 1205prolog_message(frame(Frame, backtrace, _PC)) -->
 1206    !,
 1207    { prolog_frame_attribute(Frame, level, Level)
 1208    },
 1209    [ ansi(bold, '~t[~D] ~10|', [Level]) ],
 1210    frame_context(Frame),
 1211    frame_goal(Frame).
 1212prolog_message(frame(Frame, choice, PC)) -->
 1213    !,
 1214    prolog_message(frame(Frame, backtrace, PC)).
 1215prolog_message(frame(_, cut_call, _)) --> !, [].
 1216prolog_message(frame(Frame, trace(Port), _PC)) -->
 1217    !,
 1218    [ ' T ' ],
 1219    port(Port),
 1220    frame_level(Frame),
 1221    frame_context(Frame),
 1222    frame_goal(Frame).
 1223prolog_message(frame(Frame, Port, _PC)) -->
 1224    frame_flags(Frame),
 1225    port(Port),
 1226    frame_level(Frame),
 1227    frame_context(Frame),
 1228    frame_depth_limit(Port, Frame),
 1229    frame_goal(Frame),
 1230    [ flush ].
 1231
 1232frame_goal(Frame) -->
 1233    { prolog_frame_attribute(Frame, goal, Goal0),
 1234      clean_goal(Goal0, Goal),
 1235      current_prolog_flag(debugger_write_options, Options)
 1236    },
 1237    [ '~W'-[Goal, Options] ].
 1238
 1239frame_level(Frame) -->
 1240    { prolog_frame_attribute(Frame, level, Level)
 1241    },
 1242    [ '(~D) '-[Level] ].
 1243
 1244frame_context(Frame) -->
 1245    (   { current_prolog_flag(debugger_show_context, true),
 1246          prolog_frame_attribute(Frame, context_module, Context)
 1247        }
 1248    ->  [ '[~w] '-[Context] ]
 1249    ;   []
 1250    ).
 1251
 1252frame_depth_limit(fail, Frame) -->
 1253    { prolog_frame_attribute(Frame, depth_limit_exceeded, true)
 1254    },
 1255    !,
 1256    [ '[depth-limit exceeded] ' ].
 1257frame_depth_limit(_, _) -->
 1258    [].
 1259
 1260frame_flags(Frame) -->
 1261    { prolog_frame_attribute(Frame, goal, Goal),
 1262      (   predicate_property(Goal, transparent)
 1263      ->  T = '^'
 1264      ;   T = ' '
 1265      ),
 1266      (   predicate_property(Goal, spying)
 1267      ->  S = '*'
 1268      ;   S = ' '
 1269      )
 1270    },
 1271    [ '~w~w '-[T, S] ].
 1272
 1273port(Port) -->
 1274    { port_name(Port, Colour, Name)
 1275    },
 1276    !,
 1277    [ ansi([bold,fg(Colour)], '~w: ', [Name]) ].
 1278
 1279port_name(call,      green,   'Call').
 1280port_name(exit,      green,   'Exit').
 1281port_name(fail,      red,     'Fail').
 1282port_name(redo,      yellow,  'Redo').
 1283port_name(unify,     blue,    'Unify').
 1284port_name(exception, magenta, 'Exception').
 1285
 1286clean_goal(M:Goal, Goal) :-
 1287    hidden_module(M),
 1288    !.
 1289clean_goal(M:Goal, Goal) :-
 1290    predicate_property(M:Goal, built_in),
 1291    !.
 1292clean_goal(Goal, Goal).
 1293
 1294
 1295                 /*******************************
 1296                 *        COMPATIBILITY         *
 1297                 *******************************/
 1298
 1299prolog_message(compatibility(renamed(Old, New))) -->
 1300    [ 'The predicate ~p has been renamed to ~p.'-[Old, New], nl,
 1301      'Please update your sources for compatibility with future versions.'
 1302    ].
 1303
 1304
 1305                 /*******************************
 1306                 *            THREADS           *
 1307                 *******************************/
 1308
 1309prolog_message(abnormal_thread_completion(Goal, exception(Ex))) -->
 1310    !,
 1311    [ 'Thread running "~p" died on exception: '-[Goal] ],
 1312    translate_message(Ex).
 1313prolog_message(abnormal_thread_completion(Goal, fail)) -->
 1314    [ 'Thread running "~p" died due to failure'-[Goal] ].
 1315prolog_message(threads_not_died(Running)) -->
 1316    [ 'The following threads wouldn\'t die: ~p'-[Running] ].
 1317
 1318
 1319                 /*******************************
 1320                 *             PACKS            *
 1321                 *******************************/
 1322
 1323prolog_message(pack(attached(Pack, BaseDir))) -->
 1324    [ 'Attached package ~w at ~q'-[Pack, BaseDir] ].
 1325prolog_message(pack(duplicate(Entry, OldDir, Dir))) -->
 1326    [ 'Package ~w already attached at ~q.'-[Entry,OldDir], nl,
 1327      '\tIgnoring version from ~q'- [Entry, OldDir, Dir]
 1328    ].
 1329prolog_message(pack(no_arch(Entry, Arch))) -->
 1330    [ 'Package ~w: no binary for architecture ~w'-[Entry, Arch] ].
 1331
 1332                 /*******************************
 1333                 *             MISC             *
 1334                 *******************************/
 1335
 1336prolog_message(null_byte_in_path(Component)) -->
 1337    [ '0-byte in PATH component: ~p (skipped directory)'-[Component] ].
 1338prolog_message(invalid_tmp_var(Var, Value, Reason)) -->
 1339    [ 'Cannot use '-[] ], env(Var),
 1340    [ ' as temporary file directory: ~p: ~w'-[Value, Reason] ].
 1341prolog_message(ambiguous_stream_pair(Pair)) -->
 1342    [ 'Ambiguous operation on stream pair ~p'-[Pair] ].
 1343
 1344env(Name) -->
 1345    { current_prolog_flag(windows, true) },
 1346    [ '%~w%'-[Name] ].
 1347env(Name) -->
 1348    [ '$~w'-[Name] ].
 1349
 1350                 /*******************************
 1351                 *      PRINTING MESSAGES       *
 1352                 *******************************/
 1353
 1354:- multifile
 1355    user:message_hook/3. 1356:- dynamic
 1357    user:message_hook/3. 1358:- thread_local
 1359    user:thread_message_hook/3. 1360
 1361%!  print_message(+Kind, +Term)
 1362%
 1363%   Print an error message using a term as generated by the exception
 1364%   system.
 1365
 1366print_message(Level, Term) :-
 1367    (   must_print(Level, Term)
 1368    ->  (   translate_message(Term, Lines, [])
 1369        ->  (   nonvar(Term),
 1370                (   notrace(user:thread_message_hook(Term, Level, Lines))
 1371                ->  true
 1372                ;   notrace(user:message_hook(Term, Level, Lines))
 1373                )
 1374            ->  true
 1375            ;   print_system_message(Term, Level, Lines)
 1376            )
 1377        )
 1378    ;   true
 1379    ).
 1380
 1381%!  print_system_message(+Term, +Kind, +Lines)
 1382%
 1383%   Print the message if the user did not intecept the message.
 1384%   The first is used for errors and warnings that can be related
 1385%   to source-location.  Note that syntax errors have their own
 1386%   source-location and should therefore not be handled this way.
 1387
 1388print_system_message(_, silent, _) :- !.
 1389print_system_message(_, informational, _) :-
 1390    current_prolog_flag(verbose, silent),
 1391    !.
 1392print_system_message(_, banner, _) :-
 1393    current_prolog_flag(verbose, silent),
 1394    !.
 1395print_system_message(_, _, []) :- !.
 1396print_system_message(Term, Kind, Lines) :-
 1397    catch(flush_output(user_output), _, true),      % may not exist
 1398    source_location(File, Line),
 1399    Term \= error(syntax_error(_), _),
 1400    msg_property(Kind, location_prefix(File:Line, LocPrefix, LinePrefix)),
 1401    !,
 1402    insert_prefix(Lines, LinePrefix, PrefixLines),
 1403    '$append'([ begin(Kind, Ctx),
 1404                LocPrefix,
 1405                nl
 1406              | PrefixLines
 1407              ],
 1408              [ end(Ctx)
 1409              ],
 1410              AllLines),
 1411    msg_property(Kind, stream(Stream)),
 1412    ignore(stream_property(Stream, position(Pos))),
 1413    print_message_lines(Stream, AllLines),
 1414    (   \+ stream_property(Stream, position(Pos)),
 1415        msg_property(Kind, wait(Wait)),
 1416        Wait > 0
 1417    ->  sleep(Wait)
 1418    ;   true
 1419    ).
 1420print_system_message(_, Kind, Lines) :-
 1421    msg_property(Kind, stream(Stream)),
 1422    print_message_lines(Stream, kind(Kind), Lines).
 1423
 1424:- multifile
 1425    user:message_property/2. 1426
 1427msg_property(Kind, Property) :-
 1428    user:message_property(Kind, Property),
 1429    !.
 1430msg_property(Kind, prefix(Prefix)) :-
 1431    msg_prefix(Kind, Prefix),
 1432    !.
 1433msg_property(_, prefix('~N')) :- !.
 1434msg_property(query, stream(user_output)) :- !.
 1435msg_property(_, stream(user_error)) :- !.
 1436msg_property(error,
 1437             location_prefix(File:Line,
 1438                             '~NERROR: ~w:~d:'-[File,Line], '~N\t')) :- !.
 1439msg_property(warning,
 1440             location_prefix(File:Line,
 1441                             '~NWarning: ~w:~d:'-[File,Line], '~N\t')) :- !.
 1442msg_property(error,   wait(0.1)) :- !.
 1443
 1444msg_prefix(debug(_),      '~N% ').
 1445msg_prefix(warning,           Prefix) :-
 1446    (   thread_message_id(Id)
 1447    ->  Prefix = '~NWarning: [Thread ~w] '-Id
 1448    ;   Prefix = '~NWarning: '
 1449    ).
 1450msg_prefix(error,             Prefix) :-
 1451    (   thread_message_id(Id)
 1452    ->  Prefix = '~NERROR: [Thread ~w] '-Id
 1453    ;   Prefix = '~NERROR: '
 1454    ).
 1455msg_prefix(informational, '~N% ').
 1456msg_prefix(information,   '~N% ').
 1457
 1458thread_message_id(Id) :-
 1459    thread_self(Id0),
 1460    Id0 \== main,
 1461    \+ current_prolog_flag(thread_message_prefix, false),
 1462    (   atom(Id0)
 1463    ->  Id = Id0
 1464    ;   thread_property(Id0, id(Id))
 1465    ).
 1466
 1467%!  print_message_lines(+Stream, +PrefixOrKind, +Lines)
 1468%
 1469%   Quintus compatibility predicate to print message lines using
 1470%   a prefix.
 1471
 1472print_message_lines(Stream, kind(Kind), Lines) :-
 1473    !,
 1474    msg_property(Kind, prefix(Prefix)),
 1475    insert_prefix(Lines, Prefix, PrefixLines),
 1476    '$append'([ begin(Kind, Ctx)
 1477              | PrefixLines
 1478              ],
 1479              [ end(Ctx)
 1480              ],
 1481              AllLines),
 1482    print_message_lines(Stream, AllLines).
 1483print_message_lines(Stream, Prefix, Lines) :-
 1484    insert_prefix(Lines, Prefix, PrefixLines),
 1485    print_message_lines(Stream, PrefixLines).
 1486
 1487%!  insert_prefix(+Lines, +Prefix, -PrefixedLines)
 1488
 1489insert_prefix([at_same_line|Lines0], Prefix, Lines) :-
 1490    !,
 1491    prefix_nl(Lines0, Prefix, Lines).
 1492insert_prefix(Lines0, Prefix, [prefix(Prefix)|Lines]) :-
 1493    prefix_nl(Lines0, Prefix, Lines).
 1494
 1495prefix_nl([], _, [nl]).
 1496prefix_nl([nl], _, [nl]) :- !.
 1497prefix_nl([flush], _, [flush]) :- !.
 1498prefix_nl([nl|T0], Prefix, [nl, prefix(Prefix)|T]) :-
 1499    !,
 1500    prefix_nl(T0, Prefix, T).
 1501prefix_nl([H|T0], Prefix, [H|T]) :-
 1502    prefix_nl(T0, Prefix, T).
 1503
 1504%!  print_message_lines(+Stream, +Lines)
 1505
 1506print_message_lines(Stream, Lines) :-
 1507    with_output_to(
 1508        Stream,
 1509        notrace(print_message_lines_guarded(current_output, Lines))).
 1510
 1511print_message_lines_guarded(_, []) :- !.
 1512print_message_lines_guarded(S, [H|T]) :-
 1513    line_element(S, H),
 1514    print_message_lines_guarded(S, T).
 1515
 1516line_element(S, E) :-
 1517    prolog:message_line_element(S, E),
 1518    !.
 1519line_element(S, full_stop) :-
 1520    !,
 1521    '$put_token'(S, '.').           % insert space if needed.
 1522line_element(S, nl) :-
 1523    !,
 1524    nl(S).
 1525line_element(S, prefix(Fmt-Args)) :-
 1526    !,
 1527    format(S, Fmt, Args).
 1528line_element(S, prefix(Fmt)) :-
 1529    !,
 1530    format(S, Fmt, []).
 1531line_element(S, flush) :-
 1532    !,
 1533    flush_output(S).
 1534line_element(S, Fmt-Args) :-
 1535    !,
 1536    format(S, Fmt, Args).
 1537line_element(S, ansi(_, Fmt, Args)) :-
 1538    !,
 1539    format(S, Fmt, Args).
 1540line_element(_, begin(_Level, _Ctx)) :- !.
 1541line_element(_, end(_Ctx)) :- !.
 1542line_element(S, Fmt) :-
 1543    format(S, Fmt, []).
 1544
 1545
 1546%!  message_to_string(+Term, -String)
 1547%
 1548%   Translate an error term into a string
 1549
 1550message_to_string(Term, Str) :-
 1551    translate_message(Term, Actions, []),
 1552    !,
 1553    actions_to_format(Actions, Fmt, Args),
 1554    format(string(Str), Fmt, Args).
 1555
 1556actions_to_format([], '', []) :- !.
 1557actions_to_format([nl], '', []) :- !.
 1558actions_to_format([Term, nl], Fmt, Args) :-
 1559    !,
 1560    actions_to_format([Term], Fmt, Args).
 1561actions_to_format([nl|T], Fmt, Args) :-
 1562    !,
 1563    actions_to_format(T, Fmt0, Args),
 1564    atom_concat('~n', Fmt0, Fmt).
 1565actions_to_format([Skip|T], Fmt, Args) :-
 1566    action_skip(Skip),
 1567    !,
 1568    actions_to_format(T, Fmt, Args).
 1569actions_to_format([Fmt0-Args0|Tail], Fmt, Args) :-
 1570    !,
 1571    actions_to_format(Tail, Fmt1, Args1),
 1572    atom_concat(Fmt0, Fmt1, Fmt),
 1573    append_args(Args0, Args1, Args).
 1574actions_to_format([Term|Tail], Fmt, Args) :-
 1575    atomic(Term),
 1576    !,
 1577    actions_to_format(Tail, Fmt1, Args),
 1578    atom_concat(Term, Fmt1, Fmt).
 1579actions_to_format([Term|Tail], Fmt, Args) :-
 1580    actions_to_format(Tail, Fmt1, Args1),
 1581    atom_concat('~w', Fmt1, Fmt),
 1582    append_args([Term], Args1, Args).
 1583
 1584action_skip(at_same_line).
 1585action_skip(flush).
 1586action_skip(ansi(_Attrs, _Fmt, _Args)).
 1587action_skip(begin(_Level, _Ctx)).
 1588action_skip(end(_Ctx)).
 1589
 1590append_args(M:Args0, Args1, M:Args) :-
 1591    !,
 1592    strip_module(Args1, _, A1),
 1593    '$append'(Args0, A1, Args).
 1594append_args(Args0, Args1, Args) :-
 1595    strip_module(Args1, _, A1),
 1596    '$append'(Args0, A1, Args).
 1597
 1598
 1599                 /*******************************
 1600                 *    MESSAGES TO PRINT ONCE    *
 1601                 *******************************/
 1602
 1603:- dynamic
 1604    printed/2. 1605
 1606%!  print_once(Message, Level)
 1607%
 1608%   True for messages that must be printed only once.
 1609
 1610print_once(compatibility(_), _).
 1611print_once(null_byte_in_path(_), _).
 1612
 1613%!  must_print(+Level, +Message)
 1614%
 1615%   True if the message must be printed.
 1616
 1617must_print(Level, Message) :-
 1618    nonvar(Message),
 1619    print_once(Message, Level),
 1620    !,
 1621    \+ printed(Message, Level),
 1622    assert(printed(Message, Level)).
 1623must_print(_, _)