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