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)  2004-2018, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(prolog_stack,
   37          [ get_prolog_backtrace/2,     % +MaxDepth, -Stack
   38            get_prolog_backtrace/3,     % +Frame, +MaxDepth, -Stack
   39            prolog_stack_frame_property/2, % +Frame, ?Property
   40            print_prolog_backtrace/2,   % +Stream, +Stack
   41            print_prolog_backtrace/3,   % +Stream, +Stack, +Options
   42            backtrace/1                 % +MaxDepth
   43          ]).   44:- use_module(library(prolog_clause)).   45:- use_module(library(debug)).   46:- use_module(library(error)).   47:- use_module(library(lists)).   48:- use_module(library(option)).   49
   50:- dynamic stack_guard/1.   51:- multifile stack_guard/1.   52
   53:- predicate_options(print_prolog_backtrace/3, 3,
   54                     [ subgoal_positions(boolean)
   55                     ]).

Examine the Prolog stack

This module defines high-level primitives for examining the Prolog stack, primarily intended to support debugging. It provides the following functionality:

This library may be enabled by default to improve interactive debugging, for example by adding the lines below to your ~/swiplrc (swipl.ini in Windows) to decorate uncaught exceptions:

:- use_module(library(prolog_stack)).
bug
-
Use of this library may negatively impact performance of applications that process (error-)exceptions frequently as part of their normal processing. */
   87:- create_prolog_flag(backtrace,            true, [type(boolean), keep(true)]).   88:- create_prolog_flag(backtrace_depth,      20,   [type(integer), keep(true)]).   89:- create_prolog_flag(backtrace_goal_depth, 3,    [type(integer), keep(true)]).   90:- create_prolog_flag(backtrace_show_lines, true, [type(boolean), keep(true)]).
 get_prolog_backtrace(+MaxDepth, -Backtrace) is det
 get_prolog_backtrace(+MaxDepth, -Backtrace, +Options) is det
Obtain a backtrace from the current location. The backtrace is a list of frames. Each frame is an opaque term that can be inspected using the predicate prolog_stack_frame_property/2 can be used to extract information from these frames. Most use scenarios will pass the stack to print_prolog_backtrace/2. The following options are provided:
frame(+Frame)
Start at Frame instead of the current frame.
goal_depth(+Depth)
If Depth > 0, include a shallow copy of the goal arguments into the stack. Default is set by the Prolog flag backtrace_goal_depth, set to 2 initially, showing the goal and toplevel of any argument.
guard(+Guard)
Do not show stack frames above Guard. See stack_guard/1.
Arguments:
Frame- is the frame to start from. See prolog_current_frame/1.
MaxDepth- defines the maximum number of frames returned.
Compatibility
- get_prolog_backtrace/3 used to have the parameters +Frame, +MaxDepth, -Backtrace. A call that matches this signature is mapped to get_prolog_backtrace(MaxDepth, Backtrace, [frame(Frame)]).
  119get_prolog_backtrace(MaxDepth, Stack) :-
  120    get_prolog_backtrace(MaxDepth, Stack, []).
  121
  122get_prolog_backtrace(Fr, MaxDepth, Stack) :-
  123    integer(Fr), integer(MaxDepth), var(Stack),
  124    !,
  125    get_prolog_backtrace_lc(MaxDepth, Stack, [frame(Fr)]),
  126    nlc.
  127get_prolog_backtrace(MaxDepth, Stack, Options) :-
  128    get_prolog_backtrace_lc(MaxDepth, Stack, Options),
  129    nlc.            % avoid last-call-optimization, such that
  130                        % the top of the stack is always a nice Prolog
  131                        % frame
  132
  133nlc.
  134
  135get_prolog_backtrace_lc(MaxDepth, Stack, Options) :-
  136    (   option(frame(Fr), Options)
  137    ->  PC = call
  138    ;   prolog_current_frame(Fr0),
  139        prolog_frame_attribute(Fr0, pc, PC),
  140        prolog_frame_attribute(Fr0, parent, Fr)
  141    ),
  142    (   option(goal_term_depth(GoalDepth), Options)
  143    ->  true
  144    ;   current_prolog_flag(backtrace_goal_depth, GoalDepth)
  145    ),
  146    option(guard(Guard), Options, none),
  147    must_be(nonneg, GoalDepth),
  148    backtrace(MaxDepth, Fr, PC, GoalDepth, Guard, Stack).
  149
  150backtrace(0, _, _, _, _, []) :- !.
  151backtrace(MaxDepth, Fr, PC, GoalDepth, Guard,
  152          [frame(Level, Where, Goal)|Stack]) :-
  153    prolog_frame_attribute(Fr, level, Level),
  154    (   PC == foreign
  155    ->  prolog_frame_attribute(Fr, predicate_indicator, Pred),
  156        Where = foreign(Pred)
  157    ;   PC == call
  158    ->  prolog_frame_attribute(Fr, predicate_indicator, Pred),
  159        Where = call(Pred)
  160    ;   prolog_frame_attribute(Fr, clause, Clause)
  161    ->  Where = clause(Clause, PC)
  162    ;   Where = meta_call
  163    ),
  164    (   Where == meta_call
  165    ->  Goal = 0
  166    ;   copy_goal(GoalDepth, Fr, Goal)
  167    ),
  168    (   prolog_frame_attribute(Fr, pc, PC2)
  169    ->  true
  170    ;   PC2 = foreign
  171    ),
  172    (   prolog_frame_attribute(Fr, parent, Parent),
  173        prolog_frame_attribute(Parent, predicate_indicator, PI),
  174        PI == Guard                             % last frame
  175    ->  backtrace(1, Parent, PC2, GoalDepth, Guard, Stack)
  176    ;   prolog_frame_attribute(Fr, parent, Parent),
  177        more_stack(Parent)
  178    ->  D2 is MaxDepth - 1,
  179        backtrace(D2, Parent, PC2, GoalDepth, Guard, Stack)
  180    ;   Stack = []
  181    ).
  182
  183more_stack(Parent) :-
  184    prolog_frame_attribute(Parent, predicate_indicator, PI),
  185    \+ (   PI = '$toplevel':G,
  186           G \== (toplevel_call/1)
  187       ),
  188    !.
  189more_stack(_) :-
  190    current_prolog_flag(break_level, Break),
  191    Break >= 1.
 copy_goal(+TermDepth, +Frame, -Goal) is det
Create a shallow copy of the frame's goal to help debugging. In addition to shallow copying, high-arity terms are represented as below. Currently the 16 first arguments are hardcoded.
name(A1, ..., A16, <skipped Skipped of Arity>, An)
  203copy_goal(0, _, 0) :- !.                        % 0 is not a valid goal
  204copy_goal(D, Fr, Goal) :-
  205    prolog_frame_attribute(Fr, goal, Goal0),
  206    (   Goal0 = Module:Goal1
  207    ->  copy_term_limit(D, Goal1, Goal2),
  208        (   hidden_module(Module)
  209        ->  Goal = Goal2
  210        ;   Goal = Module:Goal2
  211        )
  212    ;   copy_term_limit(D, Goal0, Goal)
  213    ).
  214
  215hidden_module(system).
  216hidden_module(user).
  217
  218copy_term_limit(0, In, '...') :-
  219    compound(In),
  220    !.
  221copy_term_limit(N, In, Out) :-
  222    is_dict(In),
  223    !,
  224    dict_pairs(In, Tag, PairsIn),
  225    N2 is N - 1,
  226    MaxArity = 16,
  227    copy_pairs(PairsIn, N2, MaxArity, PairsOut),
  228    dict_pairs(Out, Tag, PairsOut).
  229copy_term_limit(N, In, Out) :-
  230    compound(In),
  231    !,
  232    compound_name_arity(In, Functor, Arity),
  233    N2 is N - 1,
  234    MaxArity = 16,
  235    (   Arity =< MaxArity
  236    ->  compound_name_arity(Out, Functor, Arity),
  237        copy_term_args(0, Arity, N2, In, Out)
  238    ;   OutArity is MaxArity+2,
  239        compound_name_arity(Out, Functor, OutArity),
  240        copy_term_args(0, MaxArity, N2, In, Out),
  241        SkipArg is MaxArity+1,
  242        Skipped is Arity - MaxArity - 1,
  243        format(atom(Msg), '<skipped ~D of ~D>', [Skipped, Arity]),
  244        arg(SkipArg, Out, Msg),
  245        arg(Arity, In, InA),
  246        arg(OutArity, Out, OutA),
  247        copy_term_limit(N2, InA, OutA)
  248    ).
  249copy_term_limit(_, In, Out) :-
  250    copy_term_nat(In, Out).
  251
  252copy_term_args(I, Arity, Depth, In, Out) :-
  253    I < Arity,
  254    !,
  255    I2 is I + 1,
  256    arg(I2, In, InA),
  257    arg(I2, Out, OutA),
  258    copy_term_limit(Depth, InA, OutA),
  259    copy_term_args(I2, Arity, Depth, In, Out).
  260copy_term_args(_, _, _, _, _).
  261
  262copy_pairs([], _, _, []) :- !.
  263copy_pairs(Pairs, _, 0, ['<skipped>'-Skipped]) :-
  264    !,
  265    length(Pairs, Skipped).
  266copy_pairs([K-V0|T0], N, MaxArity, [K-V|T]) :-
  267    copy_term_limit(N, V0, V),
  268    MaxArity1 is MaxArity - 1,
  269    copy_pairs(T0, N, MaxArity1, T).
 prolog_stack_frame_property(+Frame, ?Property) is nondet
True when Property is a property of Frame. Frame is an element of a stack-trace as produced by get_prolog_backtrace/2. Defined properties are:
  282prolog_stack_frame_property(frame(Level,_,_), level(Level)).
  283prolog_stack_frame_property(frame(_,Where,_), predicate(PI)) :-
  284    frame_predicate(Where, PI).
  285prolog_stack_frame_property(frame(_,clause(Clause,PC),_), location(File:Line)) :-
  286    subgoal_position(Clause, PC, File, CharA, _CharZ),
  287    File \= @(_),                   % XPCE Object reference
  288    lineno(File, CharA, Line).
  289prolog_stack_frame_property(frame(_,_,_,Goal), goal(Goal)) :-
  290    Goal \== 0.
  291
  292
  293frame_predicate(foreign(PI), PI).
  294frame_predicate(call(PI), PI).
  295frame_predicate(clause(Clause, _PC), PI) :-
  296    clause_property(Clause, PI).
  297
  298default_backtrace_options(Options) :-
  299    (   current_prolog_flag(backtrace_show_lines, true)
  300    ->  Options = []
  301    ;   Options = [subgoal_positions(false)]
  302    ).
 print_prolog_backtrace(+Stream, +Backtrace) is det
 print_prolog_backtrace(+Stream, +Backtrace, +Options) is det
Print a stacktrace in human readable form to Stream. Options is an option list that accepts:
subgoal_positions(+Boolean)
If true, print subgoal line numbers. The default depends on the Prolog flag backtrace_show_lines.
Arguments:
Backtrace- is a list of frame(Depth,Location,Goal) terms.
  316print_prolog_backtrace(Stream, Backtrace) :-
  317    print_prolog_backtrace(Stream, Backtrace, []).
  318
  319print_prolog_backtrace(Stream, Backtrace, Options) :-
  320    default_backtrace_options(DefOptions),
  321    merge_options(Options, DefOptions, FinalOptions),
  322    phrase(message(Backtrace, FinalOptions), Lines),
  323    print_message_lines(Stream, '', Lines).
  324
  325:- public                               % Called from some handlers
  326    message//1.  327
  328message(Backtrace) -->
  329    {default_backtrace_options(Options)},
  330    message(Backtrace, Options).
  331
  332message(Backtrace, Options) -->
  333    message_frames(Backtrace, Options),
  334    warn_nodebug(Backtrace).
  335
  336message_frames([], _) -->
  337    [].
  338message_frames([H|T], Options) -->
  339    message_frames(H, Options),
  340    (   {T == []}
  341    ->  []
  342    ;   [nl],
  343        message_frames(T, Options)
  344    ).
  345
  346message_frames(frame(Level, Where, 0), Options) -->
  347    !,
  348    level(Level),
  349    where_no_goal(Where, Options).
  350message_frames(frame(Level, _Where, '$toplevel':toplevel_call(_)), _) -->
  351    !,
  352    level(Level),
  353    [ '<user>'-[] ].
  354message_frames(frame(Level, Where, Goal), Options) -->
  355    level(Level),
  356    [ '~p'-[Goal] ],
  357    where_goal(Where, Options).
  358
  359where_no_goal(foreign(PI), _) -->
  360    [ '~w <foreign>'-[PI] ].
  361where_no_goal(call(PI), _) -->
  362    [ '~w'-[PI] ].
  363where_no_goal(clause(Clause, PC), Options) -->
  364    { option(subgoal_positions(true), Options, true),
  365      subgoal_position(Clause, PC, File, CharA, _CharZ),
  366      File \= @(_),                 % XPCE Object reference
  367      lineno(File, CharA, Line),
  368      clause_predicate_name(Clause, PredName)
  369    },
  370    !,
  371    [ '~w at ~w:~d'-[PredName, File, Line] ].
  372where_no_goal(clause(Clause, _PC), _) -->
  373    { clause_property(Clause, file(File)),
  374      clause_property(Clause, line_count(Line)),
  375      clause_predicate_name(Clause, PredName)
  376    },
  377    !,
  378    [ '~w at ~w:~d'-[PredName, File, Line] ].
  379where_no_goal(clause(Clause, _PC), _) -->
  380    { clause_name(Clause, ClauseName)
  381    },
  382    [ '~w <no source>'-[ClauseName] ].
  383where_no_goal(meta_call, _) -->
  384    [ '<meta call>' ].
  385
  386where_goal(foreign(_), _) -->
  387    [ ' <foreign>'-[] ],
  388    !.
  389where_goal(clause(Clause, PC), Options) -->
  390    { option(subgoal_positions(true), Options, true),
  391      subgoal_position(Clause, PC, File, CharA, _CharZ),
  392      File \= @(_),                 % XPCE Object reference
  393      lineno(File, CharA, Line)
  394    },
  395    !,
  396    [ ' at ~w:~d'-[File, Line] ].
  397where_goal(clause(Clause, _PC), _) -->
  398    { clause_property(Clause, file(File)),
  399      clause_property(Clause, line_count(Line))
  400    },
  401    !,
  402    [ ' at ~w:~d'-[ File, Line] ].
  403where_goal(clause(Clause, _PC), _) -->
  404    { clause_name(Clause, ClauseName)
  405    },
  406    !,
  407    [ ' ~w <no source>'-[ClauseName] ].
  408where_goal(_, _) -->
  409    [].
  410
  411level(Level) -->
  412    [ '~|~t[~D]~6+ '-[Level] ].
  413
  414warn_nodebug(Backtrace) -->
  415    { contiguous(Backtrace) },
  416    !.
  417warn_nodebug(_Backtrace) -->
  418    [ nl,nl,
  419      'Note: some frames are missing due to last-call optimization.'-[], nl,
  420      'Re-run your program in debug mode (:- debug.) to get more detail.'-[]
  421    ].
  422
  423contiguous([frame(D0,_,_)|Frames]) :-
  424    contiguous(Frames, D0).
  425
  426contiguous([], _).
  427contiguous([frame(D1,_,_)|Frames], D0) :-
  428    D1 =:= D0-1,
  429    contiguous(Frames, D1).
 clause_predicate_name(+ClauseRef, -Predname) is det
Produce a name (typically Functor/Arity) for a predicate to which Clause belongs.
  437clause_predicate_name(Clause, PredName) :-
  438    user:prolog_clause_name(Clause, PredName),
  439    !.
  440clause_predicate_name(Clause, PredName) :-
  441    nth_clause(Head, _N, Clause),
  442    !,
  443    predicate_name(user:Head, PredName).
 backtrace(+MaxDepth)
Get and print a stacktrace to the user_error stream.
  450backtrace(MaxDepth) :-
  451    get_prolog_backtrace_lc(MaxDepth, Stack, []),
  452    print_prolog_backtrace(user_error, Stack).
  453
  454
  455subgoal_position(ClauseRef, PC, File, CharA, CharZ) :-
  456    debug(backtrace, 'Term-position in ~p at PC=~w:', [ClauseRef, PC]),
  457    clause_info(ClauseRef, File, TPos, _),
  458    '$clause_term_position'(ClauseRef, PC, List),
  459    debug(backtrace, '\t~p~n', [List]),
  460    find_subgoal(List, TPos, PosTerm),
  461    arg(1, PosTerm, CharA),
  462    arg(2, PosTerm, CharZ).
  463
  464find_subgoal([A|T], term_position(_, _, _, _, PosL), SPos) :-
  465    is_list(PosL),
  466    nth1(A, PosL, Pos),
  467    nonvar(Pos),
  468    !,
  469    find_subgoal(T, Pos, SPos).
  470find_subgoal([], Pos, Pos).
 lineno(+File, +Char, -Line)
Translate a character location to a line-number.
  477lineno(File, Char, Line) :-
  478    setup_call_cleanup(
  479        ( open(File, read, Fd),
  480          set_stream(Fd, newline(detect))
  481        ),
  482        lineno_(Fd, Char, Line),
  483        close(Fd)).
  484
  485lineno_(Fd, Char, L) :-
  486    stream_property(Fd, position(Pos)),
  487    stream_position_data(char_count, Pos, C),
  488    C > Char,
  489    !,
  490    stream_position_data(line_count, Pos, L0),
  491    L is L0-1.
  492lineno_(Fd, Char, L) :-
  493    skip(Fd, 0'\n),
  494    lineno_(Fd, Char, L).
  495
  496
  497                 /*******************************
  498                 *        DECORATE ERRORS       *
  499                 *******************************/
 prolog_stack:stack_guard(+PI) is semidet
Dynamic multifile hook that is normally not defined. The hook is called with PI equal to none if the exception is not caught and with a fully qualified (e.g., Module:Name/Arity) predicate indicator of the predicate that called catch/3 if the exception is caught.

The exception is of the form error(Formal, ImplDef) and this hook succeeds, ImplDef is unified to a term context(prolog_stack(StackData), Message). This context information is used by the message printing system to print a human readable representation of the stack when the exception was raised.

For example, using a clause stack_guard(none) prints contexts for uncaught exceptions only. Using a clause stack_guard(_) prints a full stack-trace for any error exception if the exception is given to print_message/2. See also library(http/http_error), which limits printing of exceptions to exceptions in user-code called from the HTTP server library.

Details of the exception decoration is controlled by two Prolog flags:

backtrace_depth
Integer that controls the maximum number of frames collected. Default is 20. If a guard is specified, callers of the guard are removed from the stack-trace.
backtrace_show_lines
Boolean that indicates whether the library tries to find line numbers for the calls. Default is true.
  535:- multifile
  536    user:prolog_exception_hook/4.  537:- dynamic
  538    user:prolog_exception_hook/4.  539
  540user:prolog_exception_hook(error(E, context(Ctx0,Msg)),
  541                           error(E, context(prolog_stack(Stack),Msg)),
  542                           Fr, GuardSpec) :-
  543    current_prolog_flag(backtrace, true),
  544    \+ is_stack(Ctx0, _Frames),
  545    (   atom(GuardSpec)
  546    ->  debug(backtrace, 'Got uncaught (guard = ~q) exception ~p (Ctx0=~p)',
  547              [GuardSpec, E, Ctx0]),
  548        stack_guard(GuardSpec),
  549        Guard = GuardSpec
  550    ;   prolog_frame_attribute(GuardSpec, predicate_indicator, Guard),
  551        debug(backtrace, 'Got exception ~p (Ctx0=~p, Catcher=~p)',
  552              [E, Ctx0, Guard]),
  553        stack_guard(Guard)
  554    ),
  555    (   current_prolog_flag(backtrace_depth, Depth)
  556    ->  Depth > 0
  557    ;   Depth = 20                  % Thread created before lib was loaded
  558    ),
  559    get_prolog_backtrace(Depth, Stack0,
  560                         [ frame(Fr),
  561                           guard(Guard)
  562                         ]),
  563    debug(backtrace, 'Stack = ~p', [Stack0]),
  564    clean_stack(Stack0, Stack1),
  565    join_stacks(Ctx0, Stack1, Stack).
  566
  567clean_stack(List, List) :-
  568    stack_guard(X), var(X),
  569    !.      % Do not stop if we catch all
  570clean_stack(List, Clean) :-
  571    clean_stack2(List, Clean).
  572
  573clean_stack2([], []).
  574clean_stack2([H|_], [H]) :-
  575    guard_frame(H),
  576    !.
  577clean_stack2([H|T0], [H|T]) :-
  578    clean_stack2(T0, T).
  579
  580guard_frame(frame(_,clause(ClauseRef, _, _))) :-
  581    nth_clause(M:Head, _, ClauseRef),
  582    functor(Head, Name, Arity),
  583    stack_guard(M:Name/Arity).
  584
  585join_stacks(Ctx0, Stack1, Stack) :-
  586    nonvar(Ctx0),
  587    Ctx0 = prolog_stack(Stack0),
  588    is_list(Stack0), !,
  589    append(Stack0, Stack1, Stack).
  590join_stacks(_, Stack, Stack).
 stack_guard(+Reason) is semidet
Dynamic multifile predicate. It is called with none, 'C' or the predicate indicator of the guard, the predicate calling catch/3. The exception must be of compatible with the shape error(Formal, context(Stack, Msg)). The default is to catch none, uncaught exceptions. 'C' implies that the callback from C will handle the exception.
  602stack_guard(none).
  603stack_guard(system:catch_with_backtrace/3).
  604
  605
  606                 /*******************************
  607                 *           MESSAGES           *
  608                 *******************************/
  609
  610:- multifile
  611    prolog:message//1.  612
  613prolog:message(error(Error, context(Stack, Message))) -->
  614    { Message \== 'DWIM could not correct goal',
  615      is_stack(Stack, Frames)
  616    },
  617    !,
  618    '$messages':translate_message(error(Error, context(_, Message))),
  619    [ nl, 'In:', nl ],
  620    (   {is_list(Frames)}
  621    ->  message(Frames)
  622    ;   ['~w'-[Frames]]
  623    ).
  624
  625is_stack(Stack, Frames) :-
  626    nonvar(Stack),
  627    Stack = prolog_stack(Frames)