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-2021, University of Amsterdam 7 VU University Amsterdam 8 SWI-Prolog Solutions b.v. 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(prolog_stack, 38 [ get_prolog_backtrace/2, % +MaxDepth, -Stack 39 get_prolog_backtrace/3, % +MaxDepth, -Stack, +Options 40 prolog_stack_frame_property/2, % +Frame, ?Property 41 print_prolog_backtrace/2, % +Stream, +Stack 42 print_prolog_backtrace/3, % +Stream, +Stack, +Options 43 backtrace/1, % +MaxDepth 44 print_last_choicepoint/0, 45 print_last_choicepoint/2 % +Choice, +Options 46 ]). 47:- autoload(library(debug),[debug/3]). 48:- autoload(library(error),[must_be/2]). 49:- autoload(library(lists),[nth1/3,append/3]). 50:- autoload(library(option),[option/2,option/3,merge_options/3]). 51:- autoload(library(prolog_clause), 52 [clause_name/2,predicate_name/2,clause_info/4]). 53 54 55:- dynamic stack_guard/1. 56:- multifile stack_guard/1. 57 58:- predicate_options(print_prolog_backtrace/3, 3, 59 [ subgoal_positions(boolean) 60 ]).
92:- create_prolog_flag(backtrace, true, [type(boolean), keep(true)]). 93:- create_prolog_flag(backtrace_depth, 20, [type(integer), keep(true)]). 94:- create_prolog_flag(backtrace_goal_depth, 3, [type(integer), keep(true)]). 95:- create_prolog_flag(backtrace_show_lines, true, [type(boolean), keep(true)]).
backtrace_goal_depth
, set to 3
initially, showing the
goal and toplevel of any argument.Clause+PC
or as a location term that
does not use clause references, allowing the exception to
be printed safely in a different context.128get_prolog_backtrace(MaxDepth, Stack) :- 129 get_prolog_backtrace(MaxDepth, Stack, []). 130 131get_prolog_backtrace(Fr, MaxDepth, Stack) :- 132 integer(Fr), integer(MaxDepth), var(Stack), 133 !, 134 get_prolog_backtrace_lc(MaxDepth, Stack, [frame(Fr)]), 135 nlc. 136get_prolog_backtrace(MaxDepth, Stack, Options) :- 137 get_prolog_backtrace_lc(MaxDepth, Stack, Options), 138 nlc. % avoid last-call-optimization, such that 139 % the top of the stack is always a nice Prolog 140 % frame 141 142nlc. 143 144get_prolog_backtrace_lc(MaxDepth, Stack, Options) :- 145 ( option(frame(Fr), Options) 146 -> PC = call 147 ; prolog_current_frame(Fr0), 148 prolog_frame_attribute(Fr0, pc, PC), 149 prolog_frame_attribute(Fr0, parent, Fr) 150 ), 151 ( option(goal_term_depth(GoalDepth), Options) 152 -> true 153 ; current_prolog_flag(backtrace_goal_depth, GoalDepth) 154 ), 155 option(guard(Guard), Options, none), 156 ( def_no_clause_refs(Guard) 157 -> DefClauseRefs = false 158 ; DefClauseRefs = true 159 ), 160 option(clause_references(ClauseRefs), Options, DefClauseRefs), 161 must_be(nonneg, GoalDepth), 162 backtrace(MaxDepth, Fr, PC, GoalDepth, Guard, ClauseRefs, Stack, Options). 163 164def_no_clause_refs(system:catch_with_backtrace/3). 165 166backtrace(0, _, _, _, _, _, [], _) :- !. 167backtrace(MaxDepth, Fr, PC, GoalDepth, Guard, ClauseRefs, 168 [frame(Level, Where, Goal)|Stack], Options) :- 169 prolog_frame_attribute(Fr, level, Level), 170 ( PC == foreign 171 -> prolog_frame_attribute(Fr, predicate_indicator, Pred), 172 Where = foreign(Pred) 173 ; PC == call 174 -> prolog_frame_attribute(Fr, predicate_indicator, Pred), 175 Where = call(Pred) 176 ; prolog_frame_attribute(Fr, clause, Clause) 177 -> clause_where(ClauseRefs, Clause, PC, Where, Options) 178 ; Where = meta_call 179 ), 180 ( Where == meta_call 181 -> Goal = 0 182 ; copy_goal(GoalDepth, Fr, Goal) 183 ), 184 ( prolog_frame_attribute(Fr, pc, PC2) 185 -> true 186 ; PC2 = foreign 187 ), 188 ( prolog_frame_attribute(Fr, parent, Parent), 189 prolog_frame_attribute(Parent, predicate_indicator, PI), 190 PI == Guard % last frame 191 -> backtrace(1, Parent, PC2, GoalDepth, Guard, ClauseRefs, Stack, Options) 192 ; prolog_frame_attribute(Fr, parent, Parent), 193 more_stack(Parent) 194 -> D2 is MaxDepth - 1, 195 backtrace(D2, Parent, PC2, GoalDepth, Guard, ClauseRefs, Stack, Options) 196 ; Stack = [] 197 ). 198 199more_stack(Parent) :- 200 prolog_frame_attribute(Parent, predicate_indicator, PI), 201 \+ ( PI = ('$toplevel':G), 202 G \== (toplevel_call/1) 203 ), 204 !. 205more_stack(_) :- 206 current_prolog_flag(break_level, Break), 207 Break >= 1.
true
, this is the a term
clause(Clause,PC)
, providing all abvailable information to the
caller at low time overhead. If however the exception need to be
printed in an environment where the clause references may differ,
for example because the program is not loaded, it is printed in a
different thread and contains references to dynamic predicates, etc,
it is better to use the information inside the clause here.220clause_where(true, Clause, PC, clause(Clause, PC), _). 221clause_where(false, Clause, PC, pred_line(PredName, File:Line), Options) :- 222 option(subgoal_positions(true), Options, true), 223 subgoal_position(Clause, PC, File, CharA, _CharZ), 224 File \= @(_), % XPCE Object reference 225 lineno(File, CharA, Line), 226 clause_predicate_name(Clause, PredName), 227 !. 228clause_where(false, Clause, _PC, pred_line(PredName, File:Line), _Options) :- 229 clause_property(Clause, file(File)), 230 clause_property(Clause, line_count(Line)), 231 clause_predicate_name(Clause, PredName), 232 !. 233clause_where(false, Clause, _PC, clause_name(ClauseName), _Options) :- 234 clause_name(Clause, ClauseName).
name(A1, ..., A16, <skipped Skipped of Arity>, An)
246copy_goal(0, _, 0) :- !. % 0 is not a valid goal 247copy_goal(D, Fr, Goal) :- 248 prolog_frame_attribute(Fr, goal, Goal0), 249 ( Goal0 = Module:Goal1 250 -> copy_term_limit(D, Goal1, Goal2), 251 ( hidden_module(Module) 252 -> Goal = Goal2 253 ; Goal = Module:Goal2 254 ) 255 ; copy_term_limit(D, Goal0, Goal) 256 ). 257 (system). 259hidden_module(user). 260 261copy_term_limit(0, In, '...') :- 262 compound(In), 263 !. 264copy_term_limit(N, In, Out) :- 265 is_dict(In), 266 !, 267 dict_pairs(In, Tag, PairsIn), 268 N2 is N - 1, 269 MaxArity = 16, 270 copy_pairs(PairsIn, N2, MaxArity, PairsOut), 271 dict_pairs(Out, Tag, PairsOut). 272copy_term_limit(N, In, Out) :- 273 compound(In), 274 !, 275 compound_name_arity(In, Functor, Arity), 276 N2 is N - 1, 277 MaxArity = 16, 278 ( Arity =< MaxArity 279 -> compound_name_arity(Out, Functor, Arity), 280 copy_term_args(0, Arity, N2, In, Out) 281 ; OutArity is MaxArity+2, 282 compound_name_arity(Out, Functor, OutArity), 283 copy_term_args(0, MaxArity, N2, In, Out), 284 SkipArg is MaxArity+1, 285 Skipped is Arity - MaxArity - 1, 286 format(atom(Msg), '<skipped ~D of ~D>', [Skipped, Arity]), 287 arg(SkipArg, Out, Msg), 288 arg(Arity, In, InA), 289 arg(OutArity, Out, OutA), 290 copy_term_limit(N2, InA, OutA) 291 ). 292copy_term_limit(_, In, Out) :- 293 copy_term_nat(In, Out). 294 295copy_term_args(I, Arity, Depth, In, Out) :- 296 I < Arity, 297 !, 298 I2 is I + 1, 299 arg(I2, In, InA), 300 arg(I2, Out, OutA), 301 copy_term_limit(Depth, InA, OutA), 302 copy_term_args(I2, Arity, Depth, In, Out). 303copy_term_args(_, _, _, _, _). 304 305copy_pairs([], _, _, []) :- !. 306copy_pairs(Pairs, _, 0, ['<skipped>'-Skipped]) :- 307 !, 308 length(Pairs, Skipped). 309copy_pairs([K-V0|T0], N, MaxArity, [K-V|T]) :- 310 copy_term_limit(N, V0, V), 311 MaxArity1 is MaxArity - 1, 312 copy_pairs(T0, N, MaxArity1, T).
level(Level)
predicate(PI)
location(File:Line)
325prolog_stack_frame_property(frame(Level,_,_), level(Level)). 326prolog_stack_frame_property(frame(_,Where,_), predicate(PI)) :- 327 frame_predicate(Where, PI). 328prolog_stack_frame_property(frame(_,clause(Clause,PC),_), location(File:Line)) :- 329 subgoal_position(Clause, PC, File, CharA, _CharZ), 330 File \= @(_), % XPCE Object reference 331 lineno(File, CharA, Line). 332prolog_stack_frame_property(frame(_,_,_,Goal), goal(Goal)) :- 333 Goal \== 0. 334 335 336frame_predicate(foreign(PI), PI). 337frame_predicate(call(PI), PI). 338frame_predicate(clause(Clause, _PC), PI) :- 339 clause_property(Clause, PI). 340 341default_backtrace_options(Options) :- 342 ( current_prolog_flag(backtrace_show_lines, true), 343 current_prolog_flag(iso, false) 344 -> Options = [] 345 ; Options = [subgoal_positions(false)] 346 ).
true
, print subgoal line numbers. The default depends
on the Prolog flag backtrace_show_lines
.360print_prolog_backtrace(Stream, Backtrace) :- 361 print_prolog_backtrace(Stream, Backtrace, []). 362 363print_prolog_backtrace(Stream, Backtrace, Options) :- 364 default_backtrace_options(DefOptions), 365 merge_options(Options, DefOptions, FinalOptions), 366 phrase(message(Backtrace, FinalOptions), Lines), 367 print_message_lines(Stream, '', Lines). 368 369:- public % Called from some handlers 370 message//1. 371 372message(Backtrace) --> 373 {default_backtrace_options(Options)}, 374 message(Backtrace, Options). 375 376message(Backtrace, Options) --> 377 message_frames(Backtrace, Options), 378 warn_nodebug(Backtrace). 379 380message_frames([], _) --> 381 []. 382message_frames([H|T], Options) --> 383 message_frames(H, Options), 384 ( {T == []} 385 -> [] 386 ; [nl], 387 message_frames(T, Options) 388 ). 389 390message_frames(frame(Level, Where, 0), Options) --> 391 !, 392 level(Level), 393 where_no_goal(Where, Options). 394message_frames(frame(Level, _Where, '$toplevel':toplevel_call(_)), _) --> 395 !, 396 level(Level), 397 [ '<user>'-[] ]. 398message_frames(frame(Level, Where, Goal), Options) --> 399 level(Level), 400 [ ansi(code, '~p', [Goal]) ], 401 where_goal(Where, Options). 402 403where_no_goal(foreign(PI), _) --> 404 [ '~w <foreign>'-[PI] ]. 405where_no_goal(call(PI), _) --> 406 [ '~w'-[PI] ]. 407where_no_goal(pred_line(PredName, File:Line), _) --> 408 !, 409 [ '~w at '-[PredName], url(File:Line) ]. 410where_no_goal(clause_name(ClauseName), _) --> 411 !, 412 [ '~w <no source>'-[ClauseName] ]. 413where_no_goal(clause(Clause, PC), Options) --> 414 { nonvar(Clause), 415 !, 416 clause_where(false, Clause, PC, Where, Options) 417 }, 418 where_no_goal(Where, Options). 419where_no_goal(meta_call, _) --> 420 [ '<meta call>' ]. 421 422where_goal(foreign(_), _) --> 423 [ ' <foreign>'-[] ], 424 !. 425where_goal(pred_line(_PredName, File:Line), _) --> 426 !, 427 [ ' at ', url(File:Line) ]. 428where_goal(clause_name(ClauseName), _) --> 429 !, 430 [ '~w <no source>'-[ClauseName] ]. 431where_goal(clause(Clause, PC), Options) --> 432 { nonvar(Clause), 433 !, 434 clause_where(false, Clause, PC, Where, Options) 435 }, 436 where_goal(Where, Options). 437where_goal(clause(Clause, _PC), _) --> 438 { clause_property(Clause, file(File)), 439 clause_property(Clause, line_count(Line)) 440 }, 441 !, 442 [ ' at ', url(File:Line) ]. 443where_goal(clause(Clause, _PC), _) --> 444 { clause_name(Clause, ClauseName) 445 }, 446 !, 447 [ ' ~w <no source>'-[ClauseName] ]. 448where_goal(_, _) --> 449 []. 450 451level(Level) --> 452 [ '~|~t[~D]~6+ '-[Level] ]. 453 454warn_nodebug(Backtrace) --> 455 { contiguous(Backtrace) }, 456 !. 457warn_nodebug(_Backtrace) --> 458 [ nl,nl, 459 'Note: some frames are missing due to last-call optimization.'-[], nl, 460 'Re-run your program in debug mode (:- debug.) to get more detail.'-[] 461 ]. 462 463contiguous([frame(D0,_,_)|Frames]) :- 464 contiguous(Frames, D0). 465 466contiguous([], _). 467contiguous([frame(D1,_,_)|Frames], D0) :- 468 D1 =:= D0-1, 469 contiguous(Frames, D1).
477:- multifile 478 user:prolog_clause_name/2. 479 480clause_predicate_name(Clause, PredName) :- 481 user:prolog_clause_name(Clause, PredName), 482 !. 483clause_predicate_name(Clause, PredName) :- 484 nth_clause(Head, _N, Clause), 485 !, 486 predicate_name(user:Head, PredName).
493backtrace(MaxDepth) :- 494 get_prolog_backtrace_lc(MaxDepth, Stack, []), 495 print_prolog_backtrace(user_error, Stack). 496 497 498subgoal_position(ClauseRef, PC, File, CharA, CharZ) :- 499 debug(backtrace, 'Term-position in ~p at PC=~w:', [ClauseRef, PC]), 500 clause_info(ClauseRef, File, TPos, _), 501 '$clause_term_position'(ClauseRef, PC, List), 502 debug(backtrace, '\t~p~n', [List]), 503 find_subgoal(List, TPos, PosTerm), 504 arg(1, PosTerm, CharA), 505 arg(2, PosTerm, CharZ).
511find_subgoal(_, Pos, Pos) :- 512 var(Pos), 513 !. 514find_subgoal([A|T], term_position(_, _, _, _, PosL), SPos) :- 515 nth1(A, PosL, Pos), 516 !, 517 find_subgoal(T, Pos, SPos). 518find_subgoal([1|T], brace_term_position(_,_,Pos), SPos) :- 519 !, 520 find_subgoal(T, Pos, SPos). 521find_subgoal(List, parentheses_term_position(_,_,Pos), SPos) :- 522 !, 523 find_subgoal(List, Pos, SPos). 524find_subgoal(_, Pos, Pos).
533lineno(File, Char, Line) :- 534 setup_call_cleanup( 535 ( prolog_clause:try_open_source(File, Fd), 536 set_stream(Fd, newline(detect)) 537 ), 538 lineno_(Fd, Char, Line), 539 close(Fd)). 540 541lineno_(Fd, Char, L) :- 542 stream_property(Fd, position(Pos)), 543 stream_position_data(char_count, Pos, C), 544 C > Char, 545 !, 546 stream_position_data(line_count, Pos, L0), 547 L is L0-1. 548lineno_(Fd, Char, L) :- 549 skip(Fd, 0'\n), 550 lineno_(Fd, Char, L). 551 552 553 /******************************* 554 * CHOICEPOINTS * 555 *******************************/
561print_last_choicepoint :- 562 prolog_current_choice(ChI0), % Choice in print_last_choicepoint/0 563 prolog_choice_attribute(ChI0, parent, ChI1), 564 print_last_choicepoint(ChI1, []). 565print_last_choicepoint.
569print_last_choicepoint(ChI1, Options) :- 570 real_choice(ChI1, ChI), 571 prolog_choice_attribute(ChI, frame, F), 572 prolog_frame_attribute(F, goal, Goal), 573 Goal \= '$execute_goal2'(_,_,_), % Toplevel REPL choicepoint 574 !, 575 option(message_level(Level), Options, warning), 576 get_prolog_backtrace(2, [_|Stack], [frame(F)]), 577 ( predicate_property(Goal, foreign) 578 -> print_message(Level, choicepoint(foreign(Goal), Stack)) 579 ; prolog_frame_attribute(F, clause, Clause), 580 ( prolog_choice_attribute(ChI, pc, PC) 581 -> Ctx = jump(PC) 582 ; prolog_choice_attribute(ChI, clause, Next) 583 -> Ctx = clause(Next) 584 ), 585 print_message(Level, choicepoint(clause(Goal, Clause, Ctx), Stack)) 586 ). 587print_last_choicepoint(_, _). 588 589real_choice(Ch0, Ch) :- 590 prolog_choice_attribute(Ch0, type, Type), 591 dummy_type(Type), 592 !, 593 prolog_choice_attribute(Ch0, parent, Ch1), 594 real_choice(Ch1, Ch). 595real_choice(Ch, Ch). 596 597dummy_type(debug). 598dummy_type(none). 599 600prologmessage(choicepoint(Choice, Stack)) --> 601 choice(Choice), 602 [ nl, 'Called from', nl ], 603 message(Stack). 604 605choice(foreign(Goal)) --> 606 success_goal(Goal, 'a foreign choice point'). 607choice(clause(Goal, ClauseRef, clause(Next))) --> 608 success_goal(Goal, 'a choice point in alternate clause'), 609 [ nl ], 610 [ ' ' ], clause_descr(ClauseRef), [': clause succeeded', nl], 611 [ ' ' ], clause_descr(Next), [': next candidate clause' ]. 612choice(clause(Goal, ClauseRef, jump(PC))) --> 613 { clause_where(false, ClauseRef, PC, Where, 614 [subgoal_positions(true)]) 615 }, 616 success_goal(Goal, 'an in-clause choice point'), 617 [ nl, ' ' ], 618 where_no_goal(Where). 619 620success_goal(Goal, Reason) --> 621 [ ansi(code, '~p', [Goal]), 622 ' left ~w (after success)'-[Reason] 623 ]. 624 625where_no_goal(pred_line(_PredName, File:Line)) --> 626 !, 627 [ url(File:Line) ]. 628where_no_goal(clause_name(ClauseName)) --> 629 !, 630 [ '~w <no source>'-[ClauseName] ]. 631 632clause_descr(ClauseRef) --> 633 { clause_property(ClauseRef, file(File)), 634 clause_property(ClauseRef, line_count(Line)) 635 }, 636 !, 637 [ url(File:Line) ]. 638clause_descr(ClauseRef) --> 639 { clause_name(ClauseRef, Name) 640 }, 641 [ '~w'-[Name] ]. 642 643 644 /******************************* 645 * DECORATE ERRORS * 646 *******************************/
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
.682:- multifile 683 user:prolog_exception_hook/4. 684:- dynamic 685 user:prolog_exception_hook/4. 686 687user:prolog_exception_hook(error(E, context(Ctx0,Msg)), 688 error(E, context(prolog_stack(Stack),Msg)), 689 Fr, GuardSpec) :- 690 current_prolog_flag(backtrace, true), 691 \+ is_stack(Ctx0, _Frames), 692 ( atom(GuardSpec) 693 -> debug(backtrace, 'Got uncaught (guard = ~q) exception ~p (Ctx0=~p)', 694 [GuardSpec, E, Ctx0]), 695 stack_guard(GuardSpec), 696 Guard = GuardSpec 697 ; prolog_frame_attribute(GuardSpec, predicate_indicator, Guard), 698 debug(backtrace, 'Got exception ~p (Ctx0=~p, Catcher=~p)', 699 [E, Ctx0, Guard]), 700 stack_guard(Guard) 701 ), 702 ( current_prolog_flag(backtrace_depth, Depth) 703 -> Depth > 0 704 ; Depth = 20 % Thread created before lib was loaded 705 ), 706 get_prolog_backtrace(Depth, Stack0, 707 [ frame(Fr), 708 guard(Guard) 709 ]), 710 debug(backtrace, 'Stack = ~p', [Stack0]), 711 clean_stack(Stack0, Stack1), 712 join_stacks(Ctx0, Stack1, Stack). 713 714clean_stack(List, List) :- 715 stack_guard(X), var(X), 716 !. % Do not stop if we catch all 717clean_stack(List, Clean) :- 718 clean_stack2(List, Clean). 719 720clean_stack2([], []). 721clean_stack2([H|_], [H]) :- 722 guard_frame(H), 723 !. 724clean_stack2([H|T0], [H|T]) :- 725 clean_stack2(T0, T). 726 727guard_frame(frame(_,clause(ClauseRef, _, _))) :- 728 nth_clause(M:Head, _, ClauseRef), 729 functor(Head, Name, Arity), 730 stack_guard(M:Name/Arity). 731 732join_stacks(Ctx0, Stack1, Stack) :- 733 nonvar(Ctx0), 734 Ctx0 = prolog_stack(Stack0), 735 is_list(Stack0), !, 736 append(Stack0, Stack1, Stack). 737join_stacks(_, Stack, Stack).
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.749stack_guard(none). 750stack_guard(system:catch_with_backtrace/3). 751 752 753 /******************************* 754 * MESSAGES * 755 *******************************/ 756 757:- multifile 758 prolog:message//1. 759 760prologmessage(error(Error, context(Stack, Message))) --> 761 { Message \== 'DWIM could not correct goal', 762 is_stack(Stack, Frames) 763 }, 764 !, 765 '$messages':translate_message(error(Error, context(_, Message))), 766 [ nl, 'In:', nl ], 767 ( {is_list(Frames)} 768 -> message(Frames) 769 ; ['~w'-[Frames]] 770 ). 771 772is_stack(Stack, Frames) :- 773 nonvar(Stack), 774 Stack = prolog_stack(Frames)
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
<config>/init.pl
to decorate uncaught exceptions: