File 2174-beam_ssa_throw-Exceptions-may-escape-modules-through.patch of Package erlang

From 36a9b9791e35b986a08a260dd12e513c77b200e0 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Sat, 3 Jun 2023 20:05:35 +0200
Subject: [PATCH] beam_ssa_throw: Exceptions may escape modules through funs

We need to suppress the throw optimization for funs because they
can be called from anywhere and we don't know whether the caller
will inspect the stack trace.

Fixes #7356
---
 lib/compiler/src/beam_ssa_throw.erl  | 15 ++++++++++++++
 lib/compiler/test/trycatch_SUITE.erl | 30 ++++++++++++++++++++++++++--
 2 files changed, 43 insertions(+), 2 deletions(-)

diff --git a/lib/compiler/src/beam_ssa_throw.erl b/lib/compiler/src/beam_ssa_throw.erl
index c2dc552119..1805163308 100644
--- a/lib/compiler/src/beam_ssa_throw.erl
+++ b/lib/compiler/src/beam_ssa_throw.erl
@@ -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},
diff --git a/lib/compiler/test/trycatch_SUITE.erl b/lib/compiler/test/trycatch_SUITE.erl
index 6466234a91..1160172a02 100644
--- a/lib/compiler/test/trycatch_SUITE.erl
+++ b/lib/compiler/test/trycatch_SUITE.erl
@@ -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").
 
@@ -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) ->
@@ -1579,4 +1581,28 @@ cst_raw() ->
 
 cst_raw_1() -> throw(id(gurka)).
 
+%% 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.
-- 
2.35.3

openSUSE Build Service is sponsored by