prolog_stack.pl -- 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:
- get_prolog_backtrace/2 gets a Prolog representation of the Prolog stack. This can be used for printing, but also to enrich exceptions using prolog_exception_hook/4. Decorating exceptions is provided by this library and controlled by the hook stack_guard/1.
- print_prolog_backtrace/2 prints a backtrace as returned by get_prolog_backtrace/2
- The shorthand backtrace/1 fetches and prints a backtrace.
This library may be enabled by default to improve interactive debugging,
for example by adding the lines below to your <config>/init.pl
to
decorate uncaught exceptions:
:- use_module(library(prolog_stack)).
- 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 to2
initially, showing the goal and toplevel of any argument. - guard(+Guard)
- Do not show stack frames above Guard. See stack_guard/1.
- clause_references(+Bool)
- Report locations as
Clause+PC
or as a location term that does not use clause references, allowing the exception to be printed safely in a different context.
- 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:
level(Level)
predicate(PI)
location(File:Line)
- 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 flagbacktrace_show_lines
.
- backtrace(+MaxDepth)
- Get and print a stacktrace to the user_error stream.
- prolog_stack:stack_guard(+PI) is semidet[multifile]
- 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 termcontext(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 clausestack_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
.
- stack_guard(+Reason) is semidet[multifile]
- 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 shapeerror(Formal, context(Stack, Msg))
. The default is to catchnone
, uncaught exceptions.'C'
implies that the callback from C will handle the exception.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.