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)  2002-2018, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(prolog_debug,
   38          [ debug/3,                    % +Topic, +Format, :Args
   39            debug/1,                    % +Topic
   40            nodebug/1,                  % +Topic
   41            debugging/1,                % ?Topic
   42            debugging/2,                % ?Topic, ?Bool
   43            list_debug_topics/0,
   44            debug_message_context/1,    % (+|-)What
   45
   46            assertion/1                 % :Goal
   47          ]).   48:- autoload(library(lists),[append/3,delete/3,selectchk/3,member/2]).   49:- autoload(library(prolog_stack),[backtrace/1]).   50
   51:- set_prolog_flag(generate_debug_info, false).   52
   53:- meta_predicate
   54    assertion(0),
   55    debug(+,+,:).   56
   57:- multifile prolog:assertion_failed/2.   58:- dynamic   prolog:assertion_failed/2.   59
   60/*:- use_module(library(prolog_stack)).*/ % We use the autoloader if needed
   61
   62%:- set_prolog_flag(generate_debug_info, false).
   63
   64:- dynamic
   65    debugging/3.                    % Topic, Enabled, To
   66
   67/** <module> Print debug messages and test assertions
   68
   69This library is a replacement for  format/3 for printing debug messages.
   70Messages are assigned a _topic_. By   dynamically  enabling or disabling
   71topics the user can  select  desired   messages.  Debug  statements  are
   72removed when the code is compiled for optimization.
   73
   74See manual for details. With XPCE, you can use the call below to start a
   75graphical monitoring tool.
   76
   77==
   78?- prolog_ide(debug_monitor).
   79==
   80
   81Using the predicate assertion/1 you  can   make  assumptions  about your
   82program explicit, trapping the debugger if the condition does not hold.
   83
   84@author Jan Wielemaker
   85*/
   86
   87%!  debugging(+Topic) is semidet.
   88%!  debugging(-Topic) is nondet.
   89%!  debugging(?Topic, ?Bool) is nondet.
   90%
   91%   Examine debug topics. The form debugging(+Topic)  may be used to
   92%   perform more complex debugging tasks.   A typical usage skeleton
   93%   is:
   94%
   95%     ==
   96%           (   debugging(mytopic)
   97%           ->  <perform debugging actions>
   98%           ;   true
   99%           ),
  100%           ...
  101%     ==
  102%
  103%   The other two calls are intended to examine existing and enabled
  104%   debugging tokens and are typically not used in user programs.
  105
  106debugging(Topic) :-
  107    debugging(Topic, true, _To).
  108
  109debugging(Topic, Bool) :-
  110    debugging(Topic, Bool, _To).
  111
  112%!  debug(+Topic) is det.
  113%!  nodebug(+Topic) is det.
  114%
  115%   Add/remove a topic from being   printed.  nodebug(_) removes all
  116%   topics. Gives a warning if the topic is not defined unless it is
  117%   used from a directive. The latter allows placing debug topics at
  118%   the start of a (load-)file without warnings.
  119%
  120%   For debug/1, Topic can be  a  term   Topic  >  Out, where Out is
  121%   either a stream or  stream-alias  or   a  filename  (atom). This
  122%   redirects debug information on this topic to the given output.
  123
  124debug(Topic) :-
  125    with_mutex(prolog_debug, debug(Topic, true)).
  126nodebug(Topic) :-
  127    with_mutex(prolog_debug, debug(Topic, false)).
  128
  129debug(Spec, Val) :-
  130    debug_target(Spec, Topic, Out),
  131    (   (   retract(debugging(Topic, Enabled0, To0))
  132        *-> update_debug(Enabled0, To0, Val, Out, Enabled, To),
  133            assert(debugging(Topic, Enabled, To)),
  134            fail
  135        ;   (   prolog_load_context(file, _)
  136            ->  true
  137            ;   print_message(warning, debug_no_topic(Topic))
  138            ),
  139            update_debug(false, [], Val, Out, Enabled, To),
  140            assert(debugging(Topic, Enabled, To))
  141        )
  142    ->  true
  143    ;   true
  144    ).
  145
  146debug_target(Spec, Topic, To) :-
  147    nonvar(Spec),
  148    Spec = (Topic > To),
  149    !.
  150debug_target(Topic, Topic, -).
  151
  152update_debug(_, To0, true, -, true, To) :-
  153    !,
  154    ensure_output(To0, To).
  155update_debug(true, To0, true, Out, true, Output) :-
  156    !,
  157    (   memberchk(Out, To0)
  158    ->  Output = To0
  159    ;   append(To0, [Out], Output)
  160    ).
  161update_debug(false, _, true, Out, true, [Out]) :- !.
  162update_debug(_, _, false, -, false, []) :- !.
  163update_debug(true, [Out], false, Out, false, []) :- !.
  164update_debug(true, To0, false, Out, true, Output) :-
  165    !,
  166    delete(To0, Out, Output).
  167
  168ensure_output([], [user_error]) :- !.
  169ensure_output(List, List).
  170
  171%!  debug_topic(+Topic) is det.
  172%
  173%   Declare a topic for debugging.  This can be used to find all
  174%   topics available for debugging.
  175
  176debug_topic(Topic) :-
  177    (   debugging(Registered, _, _),
  178        Registered =@= Topic
  179    ->  true
  180    ;   assert(debugging(Topic, false, []))
  181    ).
  182
  183%!  list_debug_topics is det.
  184%
  185%   List currently known debug topics and their setting.
  186
  187list_debug_topics :-
  188    format(user_error, '~`-t~45|~n', []),
  189    format(user_error, '~w~t ~w~35| ~w~n',
  190           ['Debug Topic', 'Activated', 'To']),
  191    format(user_error, '~`-t~45|~n', []),
  192    (   debugging(Topic, Value, To),
  193        numbervars(Topic, 0, _, [singletons(true)]),
  194        format(user_error, '~W~t ~w~35| ~w~n',
  195               [Topic, [quoted(true), numbervars(true)], Value, To]),
  196        fail
  197    ;   true
  198    ).
  199
  200%!  debug_message_context(+What) is det.
  201%
  202%   Specify additional context for debug messages.
  203%
  204%   @deprecated New code should use   the Prolog flag `message_context`.
  205%   This predicates adds or deletes topics from this list.
  206
  207debug_message_context(+Topic) :-
  208    current_prolog_flag(message_context, List),
  209    (   memberchk(Topic, List)
  210    ->  true
  211    ;   append(List, [Topic], List2),
  212        set_prolog_flag(message_context, List2)
  213    ).
  214debug_message_context(-Topic) :-
  215    current_prolog_flag(message_context, List),
  216    (   selectchk(Topic, List, Rest)
  217    ->  set_prolog_flag(message_context, Rest)
  218    ;   true
  219    ).
  220
  221%!  debug(+Topic, +Format, :Args) is det.
  222%
  223%   Format a message if debug topic  is enabled. Similar to format/3
  224%   to =user_error=, but only prints if   Topic is activated through
  225%   debug/1. Args is a  meta-argument  to   deal  with  goal for the
  226%   @-command.   Output   is   first    handed     to    the    hook
  227%   prolog:debug_print_hook/3.  If  this  fails,    Format+Args   is
  228%   translated  to  text   using    the   message-translation   (see
  229%   print_message/2) for the  term  debug(Format,   Args)  and  then
  230%   printed to every matching destination   (controlled  by debug/1)
  231%   using print_message_lines/3.
  232%
  233%   The message is preceded by '% ' and terminated with a newline.
  234%
  235%   @see    format/3.
  236
  237debug(Topic, Format, Args) :-
  238    debugging(Topic, true, To),
  239    !,
  240    print_debug(Topic, To, Format, Args).
  241debug(_, _, _).
  242
  243
  244%!  prolog:debug_print_hook(+Topic, +Format, +Args) is semidet.
  245%
  246%   Hook called by debug/3.  This  hook   is  used  by the graphical
  247%   frontend that can be activated using prolog_ide/1:
  248%
  249%     ==
  250%     ?- prolog_ide(debug_monitor).
  251%     ==
  252
  253:- multifile
  254    prolog:debug_print_hook/3.  255
  256print_debug(_Topic, _To, _Format, _Args) :-
  257    nb_current(prolog_debug_printing, true),
  258    !.
  259print_debug(Topic, To, Format, Args) :-
  260    setup_call_cleanup(
  261        nb_setval(prolog_debug_printing, true),
  262        print_debug_guarded(Topic, To, Format, Args),
  263        nb_delete(prolog_debug_printing)).
  264
  265print_debug_guarded(Topic, _To, Format, Args) :-
  266    prolog:debug_print_hook(Topic, Format, Args),
  267    !.
  268print_debug_guarded(_, [], _, _) :- !.
  269print_debug_guarded(Topic, To, Format, Args) :-
  270    phrase('$messages':translate_message(debug(Format, Args)), Lines),
  271    (   member(T, To),
  272        debug_output(T, Stream),
  273        with_output_to(
  274            Stream,
  275            print_message_lines(current_output, kind(debug(Topic)), Lines)),
  276        fail
  277    ;   true
  278    ).
  279
  280
  281debug_output(user, user_error) :- !.
  282debug_output(Stream, Stream) :-
  283    is_stream(Stream),
  284    !.
  285debug_output(File, Stream) :-
  286    open(File, append, Stream,
  287         [ close_on_abort(false),
  288           alias(File),
  289           buffer(line)
  290         ]).
  291
  292
  293                 /*******************************
  294                 *           ASSERTION          *
  295                 *******************************/
  296
  297%!  assertion(:Goal) is det.
  298%
  299%   Acts similar to C assert()  macro.  It   has  no  effect if Goal
  300%   succeeds. If Goal fails or throws    an exception, the following
  301%   steps are taken:
  302%
  303%     * call prolog:assertion_failed/2.  If prolog:assertion_failed/2
  304%       fails, then:
  305%
  306%       - If this is an interactive toplevel thread, print a
  307%         message, the stack-trace, and finally trap the debugger.
  308%       - Otherwise, throw error(assertion_error(Reason, G),_) where
  309%         Reason is one of =fail= or the exception raised.
  310
  311assertion(G) :-
  312    \+ \+ catch(G,
  313                Error,
  314                assertion_failed(Error, G)),
  315
  316    !.
  317assertion(G) :-
  318    assertion_failed(fail, G),
  319    assertion_failed.               % prevent last call optimization.
  320
  321assertion_failed(Reason, G) :-
  322    prolog:assertion_failed(Reason, G),
  323    !.
  324assertion_failed(Reason, _) :-
  325    assertion_rethrow(Reason),
  326    !,
  327    throw(Reason).
  328assertion_failed(Reason, G) :-
  329    print_message(error, assertion_failed(Reason, G)),
  330    backtrace(10),
  331    (   current_prolog_flag(break_level, _) % interactive thread
  332    ->  trace
  333    ;   throw(error(assertion_error(Reason, G), _))
  334    ).
  335
  336assertion_failed.
  337
  338assertion_rethrow(time_limit_exceeded).
  339assertion_rethrow('$aborted').
  340
  341%!  assume(:Goal) is det.
  342%
  343%   Acts similar to C assert() macro.  It has no effect of Goal
  344%   succeeds.  If Goal fails it prints a message, a stack-trace
  345%   and finally traps the debugger.
  346%
  347%   @deprecated     Use assertion/1 in new code.
  348
  349                 /*******************************
  350                 *           EXPANSION          *
  351                 *******************************/
  352
  353%       The optimise_debug flag  defines whether  Prolog  optimizes
  354%       away assertions and  debug/3 statements.  Values are =true=
  355%       (debug is optimized away),  =false= (debug is retained) and
  356%       =default= (debug optimization is dependent on the optimise
  357%       flag).
  358
  359optimise_debug :-
  360    (   current_prolog_flag(optimise_debug, true)
  361    ->  true
  362    ;   current_prolog_flag(optimise_debug, default),
  363        current_prolog_flag(optimise, true)
  364    ->  true
  365    ).
  366
  367:- multifile
  368    system:goal_expansion/2.  369
  370system:goal_expansion(debug(Topic,_,_), true) :-
  371    (   optimise_debug
  372    ->  true
  373    ;   debug_topic(Topic),
  374        fail
  375    ).
  376system:goal_expansion(debugging(Topic), fail) :-
  377    (   optimise_debug
  378    ->  true
  379    ;   debug_topic(Topic),
  380        fail
  381    ).
  382system:goal_expansion(assertion(_), true) :-
  383    optimise_debug.
  384system:goal_expansion(assume(_), true) :-
  385    print_message(informational,
  386                  compatibility(renamed(assume/1, assertion/1))),
  387    optimise_debug.
  388
  389
  390                 /*******************************
  391                 *            MESSAGES          *
  392                 *******************************/
  393
  394:- multifile
  395    prolog:message/3.  396
  397prolog:message(assertion_failed(_, G)) -->
  398    [ 'Assertion failed: ~q'-[G] ].
  399prolog:message(debug(Fmt, Args)) -->
  400    [ Fmt-Args ].
  401prolog:message(debug_no_topic(Topic)) -->
  402    [ '~q: no matching debug topic (yet)'-[Topic] ].
  403
  404
  405                 /*******************************
  406                 *             HOOKS            *
  407                 *******************************/
  408
  409%!  prolog:assertion_failed(+Reason, +Goal) is semidet.
  410%
  411%   This hook is called if the Goal  of assertion/1 fails. Reason is
  412%   unified with either =fail= if Goal simply failed or an exception
  413%   call otherwise. If this hook  fails,   the  default behaviour is
  414%   activated.  If  the  hooks  throws  an   exception  it  will  be
  415%   propagated into the caller of assertion/1.
  416
  417
  418                 /*******************************
  419                 *            SANDBOX           *
  420                 *******************************/
  421
  422:- multifile sandbox:safe_meta/2.  423
  424sandbox:safe_meta(prolog_debug:assertion(X), [X])