View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  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

Print debug messages and test assertions

This library is a replacement for format/3 for printing debug messages. Messages are assigned a topic. By dynamically enabling or disabling topics the user can select desired messages. Debug statements are removed when the code is compiled for optimization.

See manual for details. With XPCE, you can use the call below to start a graphical monitoring tool.

?- prolog_ide(debug_monitor).

Using the predicate assertion/1 you can make assumptions about your program explicit, trapping the debugger if the condition does not hold.

author
- Jan Wielemaker */
 debugging(+Topic) is semidet
debugging(-Topic) is nondet
 debugging(?Topic, ?Bool) is nondet
Examine debug topics. The form debugging(+Topic) may be used to perform more complex debugging tasks. A typical usage skeleton is:
      (   debugging(mytopic)
      ->  <perform debugging actions>
      ;   true
      ),
      ...

The other two calls are intended to examine existing and enabled debugging tokens and are typically not used in user programs.

  106debugging(Topic) :-
  107    debugging(Topic, true, _To).
  108
  109debugging(Topic, Bool) :-
  110    debugging(Topic, Bool, _To).
 debug(+Topic) is det
 nodebug(+Topic) is det
Add/remove a topic from being printed. nodebug(_) removes all topics. Gives a warning if the topic is not defined unless it is used from a directive. The latter allows placing debug topics at the start of a (load-)file without warnings.

For debug/1, Topic can be a term Topic > Out, where Out is either a stream or stream-alias or a filename (atom). This redirects debug information on this topic to the given output.

  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).
 debug_topic(+Topic) is det
Declare a topic for debugging. This can be used to find all topics available for debugging.
  176debug_topic(Topic) :-
  177    (   debugging(Registered, _, _),
  178        Registered =@= Topic
  179    ->  true
  180    ;   assert(debugging(Topic, false, []))
  181    ).
 list_debug_topics is det
List currently known debug topics and their setting.
  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    ).
 debug_message_context(+What) is det
Specify additional context for debug messages.
deprecated
- New code should use the Prolog flag message_context. This predicates adds or deletes topics from this list.
  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    ).
 debug(+Topic, +Format, :Args) is det
Format a message if debug topic is enabled. Similar to format/3 to user_error, but only prints if Topic is activated through debug/1. Args is a meta-argument to deal with goal for the @-command. Output is first handed to the hook prolog:debug_print_hook/3. If this fails, Format+Args is translated to text using the message-translation (see print_message/2) for the term debug(Format, Args) and then printed to every matching destination (controlled by debug/1) using print_message_lines/3.

The message is preceded by '% ' and terminated with a newline.

See also
- format/3.
  237debug(Topic, Format, Args) :-
  238    debugging(Topic, true, To),
  239    !,
  240    print_debug(Topic, To, Format, Args).
  241debug(_, _, _).
 prolog:debug_print_hook(+Topic, +Format, +Args) is semidet
Hook called by debug/3. This hook is used by the graphical frontend that can be activated using prolog_ide/1:
?- prolog_ide(debug_monitor).
  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                 *******************************/
 assertion(:Goal) is det
Acts similar to C assert() macro. It has no effect if Goal succeeds. If Goal fails or throws an exception, the following steps are taken:
  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').
 assume(:Goal) is det
Acts similar to C assert() macro. It has no effect of Goal succeeds. If Goal fails it prints a message, a stack-trace and finally traps the debugger.
deprecated
- Use assertion/1 in new code.
  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                 *******************************/
 prolog:assertion_failed(+Reason, +Goal) is semidet
This hook is called if the Goal of assertion/1 fails. Reason is unified with either fail if Goal simply failed or an exception call otherwise. If this hook fails, the default behaviour is activated. If the hooks throws an exception it will be propagated into the caller of assertion/1.
  418                 /*******************************
  419                 *            SANDBOX           *
  420                 *******************************/
  421
  422:- multifile sandbox:safe_meta/2.  423
  424sandbox:safe_meta(prolog_debug:assertion(X), [X])