View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           https://www.swi-prolog.org
    6    Copyright (c)  2021-2025, SWI-Prolog Solutions b.v.
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(prolog_debug_tools,
   36          [ (spy)/1,                % :Spec (some users tend to define these as
   37            (nospy)/1,              % :Spec  an operator)
   38            nospyall/0,
   39            debugging/0,
   40            trap/1,                 % +Exception
   41            notrap/1                % +Exception
   42          ]).   43:- use_module(library(broadcast), [broadcast/1]).   44:- autoload(library(edinburgh), [debug/0]).   45:- autoload(library(gensym), [gensym/2]).   46
   47:- multifile
   48    trap_alias/2.   49
   50:- set_prolog_flag(generate_debug_info, false).

User level debugging tools

This library provides tools to control the Prolog debuggers. Traditionally this code was built-in. Because these tools are only required in (interactive) debugging sessions they have been moved into the library. */

 prolog:debug_control_hook(+Action)
Allow user-hooks in the Prolog debugger interaction. See the calls below for the provided hooks. We use a single predicate with action argument to avoid an uncontrolled poliferation of hooks.
   66:- multifile
   67    prolog:debug_control_hook/1.    % +Action
   68
   69:- meta_predicate
   70    spy(:),
   71    nospy(:).
 spy :Spec is det
 nospy :Spec is det
 nospyall is det
Set/clear spy-points. A successfully set or cleared spy-point is reported using print_message/2, level informational, with one of the following terms, where Spec is of the form M:Head.
See also
- spy/1 and nospy/1 call the hook prolog:debug_control_hook/1 to allow for alternative specifications of the thing to debug.
   88spy(Spec) :-
   89    '$notrace'(spy_(Spec)).
   90
   91spy_(_:X) :-
   92    var(X),
   93    throw(error(instantiation_error, _)).
   94spy_(_:[]) :- !.
   95spy_(M:[H|T]) :-
   96    !,
   97    spy(M:H),
   98    spy(M:T).
   99spy_(Spec) :-
  100    prolog:debug_control_hook(spy(Spec)),
  101    !.
  102spy_(Spec) :-
  103    '$find_predicate'(Spec, Preds),
  104    '$member'(PI, Preds),
  105        pi_to_head(PI, Head),
  106        '$define_predicate'(Head),
  107        set_spy_point(Head),
  108    fail.
  109spy_(_).
  110
  111set_spy_point(Head) :-
  112    '$get_predicate_attribute'(Head, spy, 1),
  113    !,
  114    print_message(informational, already_spying(Head)).
  115set_spy_point(Head) :-
  116    '$spy'(Head).
  117
  118nospy(Spec) :-
  119    notrace(nospy_(Spec)).
  120
  121nospy_(_:X) :-
  122    var(X),
  123    throw(error(instantiation_error, _)).
  124nospy_(_:[]) :- !.
  125nospy_(M:[H|T]) :-
  126    !,
  127    nospy(M:H),
  128    nospy(M:T).
  129nospy_(Spec) :-
  130    prolog:debug_control_hook(nospy(Spec)),
  131    !.
  132nospy_(Spec) :-
  133    '$find_predicate'(Spec, Preds),
  134    '$member'(PI, Preds),
  135         pi_to_head(PI, Head),
  136        '$nospy'(Head),
  137    fail.
  138nospy_(_).
  139
  140nospyall :-
  141    notrace(nospyall_).
  142
  143nospyall_ :-
  144    prolog:debug_control_hook(nospyall),
  145    fail.
  146nospyall_ :-
  147    spy_point(Head),
  148        '$nospy'(Head),
  149    fail.
  150nospyall_.
  151
  152pi_to_head(M:PI, M:Head) :-
  153    !,
  154    pi_to_head(PI, Head).
  155pi_to_head(Name/Arity, Head) :-
  156    functor(Head, Name, Arity).
 debugging is det
Report current status of the debugger.
  162:- '$hide'(debugging/0).  163debugging :-
  164    current_prolog_flag(debug, DebugMode),
  165    notrace(debugging_(DebugMode)).
  166
  167debugging_(DebugMode) :-
  168    prolog:debug_control_hook(debugging(DebugMode)),
  169    !.
  170debugging_(DebugMode) :-
  171    print_message(informational, debugging(DebugMode)),
  172    (   DebugMode == true
  173    ->  findall(H, spy_point(H), SpyPoints),
  174        print_message(informational, spying(SpyPoints))
  175    ;   true
  176    ),
  177    trapping,
  178    forall(debugging_hook(DebugMode), true).
  179
  180spy_point(Module:Head) :-
  181    current_predicate(_, Module:Head),
  182    '$get_predicate_attribute'(Module:Head, spy, 1),
  183    \+ predicate_property(Module:Head, imported_from(_)).
 debugging_hook(+DebugMode)
Multifile hook that is called as forall(debugging_hook(DebugMode), true) and that may be used to extend the information printed from other debugging libraries.
  191:- multifile debugging_hook/1.  192
  193
  194		 /*******************************
  195		 *           EXCEPTIONS		*
  196		 *******************************/
 trap(+Formal) is det
 notrap(+Formal) is det
Install a trap on error(Formal, Context) exceptions that unify. The tracer is started when a matching exception is raised. This predicate enables debug mode using debug/0 to get more context about the exception. Even with debug mode disabled exceptions are still trapped and thus one may call nodebug/0 to run in normal mode after installing a trap. Exceptions are trapped in any thread. Debug mode is only enabled in the calling thread. To enable debug mode in all threads use tdebug/0.

Calling debugging/0 lists the enabled traps. The predicate notrap/1 removes matching (unifying) traps.

In many cases debugging an exception that is caught is as simple as below (assuming run/0 starts your program).

?- trap(_).
?- run.

The multifile hook trap_alias/2 allow for defining short hands for commonly used traps. Currently this defines

det
Trap determinism exceptions raised as a result of the det/1 directive.
=>
Trap rule existence error exceptions.
See also
- gtrap/1 to trap using the graphical debugger.
- Edit exceptions menu in PceEmacs and the graphical debugger that provide a graphical frontend to trap exceptions.
  234:- dynamic
  235    exception/4,                    % Name, Term, NotCaught, Caught
  236    installed/1.                    % ClauseRef
  237
  238trap(Error) :-
  239    '$notrace'(trap_(Error)).
  240
  241trap_(Spec) :-
  242    expand_trap(Spec, Formal),
  243    gensym(ex, Rule),
  244    asserta(exception(Rule, error(Formal, _), true, true)),
  245    print_message(informational, trap(Rule, error(Formal, _), true, true)),
  246    install_exception_hook,
  247    debug.
  248
  249notrap(Error) :-
  250    '$notrace'(notrap_(Error)).
  251
  252notrap_(Spec) :-
  253    expand_trap(Spec, Formal),
  254    Exception = error(Formal, _),
  255    findall(exception(Name, Exception, NotCaught, Caught),
  256            retract(exception(Name, error(Formal, _), Caught, NotCaught)),
  257            Trapping),
  258    print_message(informational, notrap(Trapping)).
  259
  260expand_trap(Var, _Formal), var(Var) =>
  261    true.
  262expand_trap(Alias, Formal), trap_alias(Alias, For) =>
  263    Formal = For.
  264expand_trap(Explicit, Formal) =>
  265    Formal = Explicit.
 trap_alias(+Alias, -Error)
Define short hands for commonly used exceptions.
  271trap_alias(det,                  determinism_error(_Pred, _Declared, _Observed, property)).
  272trap_alias(=>,			 existence_error(rule, _)).
  273trap_alias(existence_error,      existence_error(_,_)).
  274trap_alias(type_error,           type_error(_,_)).
  275trap_alias(domain_error,         domain_error(_,_)).
  276trap_alias(permission_error,     permission_error(_,_,_)).
  277trap_alias(representation_error, representation_error(_)).
  278trap_alias(resource_error,       resource_error(_)).
  279trap_alias(syntax_error,         syntax_error(_)).
  280
  281trapping :-
  282    findall(exception(Name, Term, NotCaught, Caught),
  283            exception(Name, Term, NotCaught, Caught),
  284            Trapping),
  285    print_message(information, trapping(Trapping)).
  286
  287:- dynamic   prolog:prolog_exception_hook/5.  288:- multifile prolog:prolog_exception_hook/5.
 exception_hook(+ExIn, -ExOut, +Frame, +Catcher, +DebugMode) is failure
Trap exceptions and consider whether or not to start the tracer.
  295:- public exception_hook/5.  296
  297exception_hook(Ex, Ex, Frame, Catcher, _Debug) :-
  298    thread_self(Me),
  299    thread_property(Me, debug(true)),
  300    broadcast(debug(exception(Ex))),
  301    exception(_, Ex, NotCaught, Caught),
  302    !,
  303    (   Caught == true
  304    ->  true
  305    ;   Catcher == none,
  306        NotCaught == true
  307    ),
  308    \+ direct_catch(Frame),
  309    trace, fail.
 direct_catch(+Frame) is semidet
True if we are dealing with a catch(SytemPred, _, _), i.e., a catch directly wrapped around a call to a built-in. In that case it is highly unlikely that we want the debugger to step in.
  317direct_catch(Frame) :-
  318    prolog_frame_attribute(Frame, parent, Parent),
  319    prolog_frame_attribute(Parent, predicate_indicator, system:catch/3),
  320    prolog_frame_attribute(Frame, level, MyLevel),
  321    prolog_frame_attribute(Parent, level, CatchLevel),
  322    MyLevel =:= CatchLevel+1.
 install_exception_hook
Make sure our handler is the first of the hook predicate.
  328install_exception_hook :-
  329    installed(Ref),
  330    (   nth_clause(_, I, Ref)
  331    ->  I == 1, !                   % Ok, we are the first
  332    ;   retractall(installed(Ref)),
  333        erase(Ref),                 % Someone before us!
  334        fail
  335    ).
  336install_exception_hook :-
  337    asserta((prolog:prolog_exception_hook(Ex, Out, Frame, Catcher, Debug) :-
  338                    exception_hook(Ex, Out, Frame, Catcher, Debug)), Ref),
  339    assert(installed(Ref)).
  340
  341
  342		 /*******************************
  343		 *            MESSAGES		*
  344		 *******************************/
  345
  346:- multifile
  347    prolog:message//1.  348
  349prolog:message(trapping([])) -->
  350    [ 'No exception traps'-[] ].
  351prolog:message(trapping(Trapping)) -->
  352    [ 'Exception traps on'-[], nl ],
  353    trapping(Trapping).
  354prolog:message(trap(_Rule, Error, _Caught, _NotCaught)) -->
  355    [ 'Installed trap for exception '-[] ],
  356    exception(Error),
  357    [ nl ].
  358prolog:message(notrap([])) -->
  359    [ 'No matching traps'-[] ].
  360prolog:message(notrap(Trapping)) -->
  361    [ 'Removed traps from exceptions'-[], nl ],
  362    trapping(Trapping).
  363
  364trapping([]) --> [].
  365trapping([exception(_Rule, Error, _Caught, _NotCaught)|T]) -->
  366    [ '  '-[] ],
  367    exception(Error),
  368    [ nl ],
  369    trapping(T).
  370
  371exception(Term) -->
  372    { copy_term(Term, T2),
  373      numbervars(T2, 0, _, [singletons(true)])
  374    },
  375    [ '~p'-[T2] ]