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-2023, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9                              SWI-Prolog Solutions b.v.
   10    All rights reserved.
   11
   12    Redistribution and use in source and binary forms, with or without
   13    modification, are permitted provided that the following conditions
   14    are met:
   15
   16    1. Redistributions of source code must retain the above copyright
   17       notice, this list of conditions and the following disclaimer.
   18
   19    2. Redistributions in binary form must reproduce the above copyright
   20       notice, this list of conditions and the following disclaimer in
   21       the documentation and/or other materials provided with the
   22       distribution.
   23
   24    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   25    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   26    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   27    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   28    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   29    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   30    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   31    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   32    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   33    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   34    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   35    POSSIBILITY OF SUCH DAMAGE.
   36*/
   37
   38:- module(prolog_debug,
   39          [ debug/3,                    % +Topic, +Format, :Args
   40            debug/1,                    % +Topic
   41            nodebug/1,                  % +Topic
   42            debugging/1,                % ?Topic
   43            debugging/2,                % ?Topic, ?Bool
   44            list_debug_topics/0,
   45            list_debug_topics/1,        % +Options
   46            debug_message_context/1,    % (+|-)What
   47
   48            assertion/1                 % :Goal
   49          ]).   50:- autoload(library(lists),[append/3,delete/3,selectchk/3,member/2]).   51:- autoload(library(prolog_stack),[backtrace/1]).   52:- autoload(library(option), [option/3, option/2]).   53:- autoload(library(dcg/high_order), [sequence/5]).   54
   55:- set_prolog_flag(generate_debug_info, false).   56:- create_prolog_flag(optimise_debug, default,
   57                      [ keep(true),
   58                        type(oneof([default,false,true]))
   59                      ]).   60
   61:- meta_predicate
   62    assertion(0),
   63    debug(+,+,:).   64
   65:- multifile prolog:assertion_failed/2.   66:- dynamic   prolog:assertion_failed/2.   67
   68/*:- use_module(library(prolog_stack)).*/ % We use the autoloader if needed
   69
   70%:- set_prolog_flag(generate_debug_info, false).
   71
   72:- dynamic
   73    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. Calls to debug/3 and assertion/1 are removed when the code is compiled for optimization unless the Prolog flag optimise_debug is set to true.

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

Output and actions by these predicates can be configured using hooks to fit your environment. With XPCE, you can use the call below to start a graphical monitoring tool.

?- prolog_ide(debug_monitor).

*/

 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.

  112debugging(Topic) :-
  113    debugging(Topic, true, _To).
  114
  115debugging(Topic, Bool) :-
  116    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 (an atom). This redirects debug information on this topic to the given output. On Linux systems redirection can be used to make the message appear, even if the user_error stream is redefined using

?- debug(Topic > '/proc/self/fd/2').

A platform independent way to get debug messages in the current console (for example, a swipl-win window, or login using ssh to Prolog running an SSH server from the libssh pack) is to use:

?- stream_property(S, alias(user_error)),
   debug(Topic > S).

Do not forget to disable the debugging using nodebug/1 before quitting the console if Prolog must remain running.

  144debug(Topic) :-
  145    with_mutex(prolog_debug, debug(Topic, true)).
  146nodebug(Topic) :-
  147    with_mutex(prolog_debug, debug(Topic, false)).
  148
  149debug(Spec, Val) :-
  150    debug_target(Spec, Topic, Out),
  151    (   (   retract(debugging(Topic, Enabled0, To0))
  152        *-> update_debug(Enabled0, To0, Val, Out, Enabled, To),
  153            assert(debugging(Topic, Enabled, To)),
  154            fail
  155        ;   (   prolog_load_context(file, _)
  156            ->  true
  157            ;   print_message(warning, debug_no_topic(Topic))
  158            ),
  159            update_debug(false, [], Val, Out, Enabled, To),
  160            assert(debugging(Topic, Enabled, To))
  161        )
  162    ->  true
  163    ;   true
  164    ).
  165
  166debug_target(Spec, Topic, To) :-
  167    nonvar(Spec),
  168    Spec = (Topic > To),
  169    !.
  170debug_target(Topic, Topic, -).
  171
  172update_debug(_, To0, true, -, true, To) :-
  173    !,
  174    ensure_output(To0, To).
  175update_debug(true, To0, true, Out, true, Output) :-
  176    !,
  177    (   memberchk(Out, To0)
  178    ->  Output = To0
  179    ;   append(To0, [Out], Output)
  180    ).
  181update_debug(false, _, true, Out, true, [Out]) :- !.
  182update_debug(_, _, false, -, false, []) :- !.
  183update_debug(true, [Out], false, Out, false, []) :- !.
  184update_debug(true, To0, false, Out, true, Output) :-
  185    !,
  186    delete(To0, Out, Output).
  187
  188ensure_output([], [user_error]) :- !.
  189ensure_output(List, List).
 debug_topic(+Topic) is det
Declare a topic for debugging. This can be used to find all topics available for debugging.
  196debug_topic(Topic) :-
  197    (   debugging(Registered, _, _),
  198        Registered =@= Topic
  199    ->  true
  200    ;   assert(debugging(Topic, false, []))
  201    ).
 list_debug_topics is det
 list_debug_topics(+Options) is det
List currently known topics for debug/3 and their setting. Options is either an atom or string, which is a shorthand for [search(String)] or a normal option list. Defined options are:
search(String)
Only show topics that match String. Match is case insensitive on the printed representation of the term.
active(+Boolean)
Only print topics that are active (true) or inactive (false).
output(+To)
Only print topics whose target location matches To. This option implicitly restricts the output to active topics.
  220list_debug_topics :-
  221    list_debug_topics([]).
  222
  223list_debug_topics(Options) :-
  224    (   atom(Options)
  225    ;   string(Options)
  226    ),
  227    !,
  228    list_debug_topics([search(Options)]).
  229list_debug_topics(Options) :-
  230    option(active(Activated), Options, _),
  231    findall(debug_topic(Topic, String, Activated, To),
  232            matching_topic(Topic, String, Activated, To, Options),
  233            Tuples),
  234    print_message(information, debug_topics(Tuples)).
  235
  236matching_topic(Topic, String, Activated, To, Options) :-
  237    debugging(Topic, Activated, To),
  238    (   option(output(Stream), Options)
  239    ->  memberchk(Stream, To)
  240    ;   true
  241    ),
  242    topic_to_string(Topic, String),
  243    (   option(search(Search), Options)
  244    ->  sub_atom_icasechk(String, _, Search)
  245    ;   true
  246    ).
  247
  248topic_to_string(Topic, String) :-
  249    numbervars(Topic, 0, _, [singletons(true)]),
  250    term_string(Topic, String, [quoted(true), numbervars(true)]).
  251
  252:- multifile
  253    prolog_debug_tools:debugging_hook/0.  254
  255prolog_debug_tools:debugging_hook :-
  256    (   debugging(_, true, _)
  257    ->  list_debug_topics([active(true)])
  258    ).
 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.
  268debug_message_context(+Topic) :-
  269    current_prolog_flag(message_context, List),
  270    (   memberchk(Topic, List)
  271    ->  true
  272    ;   append(List, [Topic], List2),
  273        set_prolog_flag(message_context, List2)
  274    ).
  275debug_message_context(-Topic) :-
  276    current_prolog_flag(message_context, List),
  277    (   selectchk(Topic, List, Rest)
  278    ->  set_prolog_flag(message_context, Rest)
  279    ;   true
  280    ).
 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.
  298debug(Topic, Format, Args) :-
  299    debugging(Topic, true, To),
  300    !,
  301    print_debug(Topic, To, Format, Args).
  302debug(_, _, _).
 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).
  314:- multifile
  315    prolog:debug_print_hook/3.  316
  317print_debug(_Topic, _To, _Format, _Args) :-
  318    nb_current(prolog_debug_printing, true),
  319    !.
  320print_debug(Topic, To, Format, Args) :-
  321    setup_call_cleanup(
  322        nb_setval(prolog_debug_printing, true),
  323        print_debug_guarded(Topic, To, Format, Args),
  324        nb_delete(prolog_debug_printing)).
  325
  326print_debug_guarded(Topic, _To, Format, Args) :-
  327    prolog:debug_print_hook(Topic, Format, Args),
  328    !.
  329print_debug_guarded(_, [], _, _) :- !.
  330print_debug_guarded(Topic, To, Format, Args) :-
  331    phrase('$messages':translate_message(debug(Format, Args)), Lines),
  332    (   member(T, To),
  333        debug_output(T, Stream),
  334        with_output_to(
  335            Stream,
  336            print_message_lines(current_output, kind(debug(Topic)), Lines)),
  337        fail
  338    ;   true
  339    ).
  340
  341
  342debug_output(user, user_error) :- !.
  343debug_output(Stream, Stream) :-
  344    is_stream(Stream),
  345    !.
  346debug_output(File, Stream) :-
  347    open(File, append, Stream,
  348         [ close_on_abort(false),
  349           alias(File),
  350           buffer(line)
  351         ]).
  352
  353
  354                 /*******************************
  355                 *           ASSERTION          *
  356                 *******************************/
 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:
  372assertion(G) :-
  373    \+ \+ catch(G,
  374                Error,
  375                assertion_failed(Error, G)),
  376
  377    !.
  378assertion(G) :-
  379    assertion_failed(fail, G),
  380    assertion_failed.               % prevent last call optimization.
  381
  382assertion_failed(Reason, G) :-
  383    prolog:assertion_failed(Reason, G),
  384    !.
  385assertion_failed(Reason, _) :-
  386    assertion_rethrow(Reason),
  387    !,
  388    throw(Reason).
  389assertion_failed(Reason, G) :-
  390    print_message(error, assertion_failed(Reason, G)),
  391    backtrace(10),
  392    (   current_prolog_flag(break_level, _) % interactive thread
  393    ->  trace
  394    ;   throw(error(assertion_error(Reason, G), _))
  395    ).
  396
  397assertion_failed.
  398
  399assertion_rethrow(time_limit_exceeded).
  400assertion_rethrow('$aborted').
  401
  402
  403                 /*******************************
  404                 *           EXPANSION          *
  405                 *******************************/
  406
  407%       The optimise_debug flag  defines whether  Prolog  optimizes
  408%       away assertions and  debug/3 statements.  Values are =true=
  409%       (debug is optimized away),  =false= (debug is retained) and
  410%       =default= (debug optimization is dependent on the optimise
  411%       flag).
  412
  413optimise_debug :-
  414    (   current_prolog_flag(optimise_debug, true)
  415    ->  true
  416    ;   current_prolog_flag(optimise_debug, default),
  417        current_prolog_flag(optimise, true)
  418    ->  true
  419    ).
  420
  421:- multifile
  422    system:goal_expansion/2.  423
  424system:goal_expansion(debug(Topic,_,_), true) :-
  425    (   optimise_debug
  426    ->  true
  427    ;   debug_topic(Topic),
  428        fail
  429    ).
  430system:goal_expansion(debugging(Topic), fail) :-
  431    (   optimise_debug
  432    ->  true
  433    ;   debug_topic(Topic),
  434        fail
  435    ).
  436system:goal_expansion(assertion(_), true) :-
  437    optimise_debug.
  438system:goal_expansion(assume(_), true) :-
  439    print_message(informational,
  440                  compatibility(renamed(assume/1, assertion/1))),
  441    optimise_debug.
  442
  443
  444                 /*******************************
  445                 *            MESSAGES          *
  446                 *******************************/
  447
  448:- multifile
  449    prolog:message/3.  450
  451prolog:message(assertion_failed(_, G)) -->
  452    [ 'Assertion failed: ~q'-[G] ].
  453prolog:message(debug(Fmt, Args)) -->
  454    [ Fmt-Args ].
  455prolog:message(debug_no_topic(Topic)) -->
  456    [ '~q: no matching debug topic (yet)'-[Topic] ].
  457prolog:message(debug_topics(Tuples)) -->
  458    [ ansi(bold, '~w~t ~w~35| ~w~n', ['Debug Topic', 'Activated', 'To']),
  459      '~`\u2015t~48|', nl
  460    ],
  461    sequence(debug_topic, [nl], Tuples).
  462
  463debug_topic(debug_topic(_, TopicString, true, [user_error])) -->
  464    [ ansi(bold, '~s~t \u2714~35|', [TopicString]) ].
  465debug_topic(debug_topic(_, TopicString, true, To)) -->
  466    [ ansi(bold, '~s~t \u2714~35| ~q', [TopicString, To]) ].
  467debug_topic(debug_topic(_, TopicString, false, _To)) -->
  468    [ '~s~t -~35|'-[TopicString] ].
  469
  470
  471                 /*******************************
  472                 *             HOOKS            *
  473                 *******************************/
 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.
  484                 /*******************************
  485                 *            SANDBOX           *
  486                 *******************************/
  487
  488:- multifile sandbox:safe_meta/2.  489
  490sandbox:safe_meta(prolog_debug:assertion(X), [X])