
prolog_stack.pl -- Examine the Prolog stackThis 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)).
get_prolog_backtrace(+MaxDepth, -Backtrace) is det
get_prolog_backtrace(+MaxDepth, -Backtrace, +Options) is detbacktrace_goal_depth, set to 2 initially, showing the
goal and toplevel of any argument.
copy_goal(+TermDepth, +Frame, -Goal) is det[private]name(A1, ..., A16, <skipped Skipped of Arity>, An)
prolog_stack_frame_property(+Frame, ?Property) is nondetlevel(Level)predicate(PI)location(File:Line)
print_prolog_backtrace(+Stream, +Backtrace) is det
print_prolog_backtrace(+Stream, +Backtrace, +Options) is dettrue, print subgoal line numbers. The default depends
on the Prolog flag backtrace_show_lines.
clause_predicate_name(+ClauseRef, -Predname) is det[private]
backtrace(+MaxDepth)
lineno(+File, +Char, -Line)[private]
prolog_stack:stack_guard(+PI) is semidet[multifile]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:
true.
stack_guard(+Reason) is semidet[multifile]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.
get_prolog_backtrace(+MaxDepth, -Backtrace) is det
get_prolog_backtrace(+MaxDepth, -Backtrace, +Options) is detbacktrace_goal_depth, set to 2 initially, showing the
goal and toplevel of any argument.
print_prolog_backtrace(+Stream, +Backtrace) is det
print_prolog_backtrace(+Stream, +Backtrace, +Options) is dettrue, print subgoal line numbers. The default depends
on the Prolog flag backtrace_show_lines.