Skip to content

Commit

Permalink
Merge branch 'john/compiler/fix-ssa-throw-miscompilation/GH-7356/OTP-…
Browse files Browse the repository at this point in the history
…18626' into maint-26

* john/compiler/fix-ssa-throw-miscompilation/GH-7356/OTP-18626:
  beam_ssa_throw: Exceptions may escape modules through funs
  • Loading branch information
Erlang/OTP committed Jun 28, 2023
2 parents b54b86a + 36a9b97 commit 3cff1b6
Show file tree
Hide file tree
Showing 2 changed files with 43 additions and 2 deletions.
15 changes: 15 additions & 0 deletions lib/compiler/src/beam_ssa_throw.erl
Original file line number Diff line number Diff line change
Expand Up @@ -166,6 +166,21 @@ si_is([#b_set{op=raw_raise,args=[_,_,Stacktrace]} | Is],
si_is([#b_set{op=build_stacktrace,args=[Stacktrace]} | Is],
Id, Lbl, Last, Lst, Gst) ->
si_handler_end(Is, Id, Lbl, Last, Stacktrace, Lst, Gst);
si_is([#b_set{op=MakeFun,args=[#b_local{}=Callee | _]} | _Is],
_Id, _Lbl, _Last, Lst, Gst)
when MakeFun =:= make_fun;
MakeFun =:= old_make_fun ->
#gst{tlh_roots = Roots0} = Gst,

%% Funs may be called from anywhere which may result in a throw escaping
%% the module, so we'll add an unsuitable top-level handler to all funs.
Handlers = case gb_trees:lookup(Callee, Roots0) of
{value, Handlers0} -> gb_sets:add(unsuitable, Handlers0);
none -> gb_sets:singleton(unsuitable)
end,
Roots = gb_trees:enter(Callee, Handlers, Roots0),

{Lst, Gst#gst{tlh_roots=Roots}};
si_is([#b_set{op=call,
dst=Dst,
args=[#b_remote{mod=#b_literal{val=erlang},
Expand Down
30 changes: 28 additions & 2 deletions lib/compiler/test/trycatch_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,8 @@
no_return_in_try_block/1,
expression_export/1,
throw_opt_crash/1,
coverage/1]).
coverage/1,
throw_opt_funs/1]).

-include_lib("common_test/include/ct.hrl").

Expand All @@ -50,7 +51,8 @@ groups() ->
stacktrace,nested_stacktrace,raise,
no_return_in_try_block,expression_export,
throw_opt_crash,
coverage]}].
coverage,
throw_opt_funs]}].


init_per_suite(Config) ->
Expand Down Expand Up @@ -1672,4 +1674,28 @@ bad_class(Config) ->
_ -> also_bad
end.

%% GH-7356: Funs weren't considered when checking whether an exception could
%% escape the module, erroneously triggering the optimization in some cases.
throw_opt_funs(_Config) ->
try throw_opt_funs_1(id(a)) of
_ -> unreachable
catch
_:Val -> a = id(Val) %Assertion.
end,

F = id(fun throw_opt_funs_1/1),

try F(a) of
_ -> unreachable
catch
_:_:Stack -> true = length(Stack) > 0 %Assertion.
end,

ok.

throw_opt_funs_1(a) ->
throw(a);
throw_opt_funs_1(I) ->
I.

id(I) -> I.

0 comments on commit 3cff1b6

Please sign in to comment.