Skip to content

Commit

Permalink
FIXED: Partial unification while searching for a matching catch/3.
Browse files Browse the repository at this point in the history
As the partial unification is not undone, we may fail to find the
right catch frame.
  • Loading branch information
JanWielemaker committed Oct 4, 2024
1 parent d119fc5 commit 03619a3
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 4 deletions.
6 changes: 6 additions & 0 deletions src/Tests/core/test_call.pl
Original file line number Diff line number Diff line change
Expand Up @@ -373,5 +373,11 @@
test(exit_nondet, fail) :-
catch((true;throw(homer_simpson(38))),_E,true),
fail.
test(partial_unification, X == 1) :-
t1(X).

t1(X) :- catch(t2(X), f(1,2), X = 1).
t2(X) :- catch(t3, f(2,1), X = 2).
t3 :- throw(f(_,2)).

:- end_tests(catch).
2 changes: 1 addition & 1 deletion src/pl-vmi.c
Original file line number Diff line number Diff line change
Expand Up @@ -5060,7 +5060,7 @@ VMH(b_throw, 0, (), ())

again:
SAVE_REGISTERS(QID);
catchfr_ref = findCatcher(FR, LD->choicepoints, exception_term);
catchfr_ref = findCatcher(fid, FR, LD->choicepoints, exception_term);
LOAD_REGISTERS(QID);
DEBUG(MSG_THROW,
{ if ( catchfr_ref )
Expand Down
9 changes: 6 additions & 3 deletions src/pl-wam.c
Original file line number Diff line number Diff line change
Expand Up @@ -1977,9 +1977,9 @@ findCatcher() can do GC/shift! The return value is a local-frame
reference, so we can deal with relocation of the local stack.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */

#define findCatcher(fr, ch, ex) LDFUNC(findCatcher, fr, ch, ex)
#define findCatcher(fid, fr, ch, ex) LDFUNC(findCatcher, fid, fr, ch, ex)
static term_t
findCatcher(DECL_LD LocalFrame fr, Choice ch, term_t ex)
findCatcher(DECL_LD fid_t fid, LocalFrame fr, Choice ch, term_t ex)
{ Definition catch3 = PROCEDURE_catch3->definition;

for(; fr; fr = fr->parent)
Expand All @@ -2004,6 +2004,9 @@ findCatcher(DECL_LD LocalFrame fr, Choice ch, term_t ex)
set(fr, FR_CATCHED);
return consTermRef(fr);
}

if ( fid )
PL_rewind_foreign_frame(fid);
}

return 0;
Expand Down Expand Up @@ -2106,7 +2109,7 @@ print_unhandled_exception(DECL_LD qid_t qid, term_t ex)

return printMessage(ATOM_error,
PL_FUNCTOR_CHARS, "unhandled_exception", 1,
PL_TERM, ex);
PL_TERM, ex);
}


Expand Down

0 comments on commit 03619a3

Please sign in to comment.