File 6441-Fix-compiler-crash-for-named-fun-expression-with-con.patch of Package erlang

From afd9ec71c86d425e1f7319682175f670b56678de Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 28 Nov 2022 08:28:45 +0100
Subject: [PATCH] Fix compiler crash for named fun expression with convoluted
 scoping

Closes #6515
---
 lib/compiler/src/v3_core.erl    | 19 ++++++++++---
 lib/compiler/test/fun_SUITE.erl | 48 ++++++++++++++++++++++++++++++---
 2 files changed, 59 insertions(+), 8 deletions(-)

diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index 16b3ac340f..e4a6550b01 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -2448,7 +2448,7 @@ known_bind(#known{}=K, _) -> K.
 %%  Update the known variables to only the set of variables that
 %%  should be known when entering the fun.
 
-known_in_fun(#known{base=[BaseKs|_],ks=Ks0,prev_ks=[PrevKs|_]}=K) ->
+known_in_fun(#known{base=[BaseKs|_],ks=Ks0,prev_ks=[PrevKs|_]}=K, Name) ->
     %% Within a group of bodies that see the same bindings, calculate
     %% the known variables for a fun. Example:
     %%
@@ -2461,9 +2461,20 @@ known_in_fun(#known{base=[BaseKs|_],ks=Ks0,prev_ks=[PrevKs|_]}=K) ->
     %%
     %% Thus, only `A` is known when entering the fun.
 
-    Ks = union(BaseKs, subtract(Ks0, PrevKs)),
+    Ks1 = union(BaseKs, subtract(Ks0, PrevKs)),
+    Ks = case Name of
+             unnamed -> Ks1;
+             {named,FName} -> union(Ks1, [FName])
+         end,
     K#known{base=[],ks=Ks,prev_ks=[]};
-known_in_fun(#known{}=K) -> K.
+known_in_fun(#known{ks=Ks0}=K, Name) ->
+    case Name of
+        unnamed ->
+            K;
+        {named,FName} ->
+            Ks = union(Ks0, [FName]),
+            K#known{ks=Ks}
+    end.
 
 %%%
 %%% End of abstract data type for known variables.
@@ -2735,7 +2746,7 @@ uexpr(#ifun{anno=A0,id=Id,vars=As,clauses=Cs0,fc=Fc0,name=Name}=Fun0, Ks0, St0)
               {named,FName} -> known_union(Ks0, subtract([FName], Avs))
           end,
     Ks2 = known_union(Ks1, Avs),
-    KnownInFun = known_in_fun(Ks2),
+    KnownInFun = known_in_fun(Ks2, Name),
     {Cs3,St3} = ufun_clauses(Cs2, KnownInFun, St2),
     {Fc1,St4} = ufun_clause(Fc0, KnownInFun, St3),
     Used = subtract(intersection(used_in_any(Cs3), known_get(Ks1)), Avs),
diff --git a/lib/compiler/test/fun_SUITE.erl b/lib/compiler/test/fun_SUITE.erl
index d9608ef7d1..f781fe4fe0 100644
--- a/lib/compiler/test/fun_SUITE.erl
+++ b/lib/compiler/test/fun_SUITE.erl
@@ -22,7 +22,7 @@
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 	 init_per_group/2,end_per_group/2,
 	 test1/1,overwritten_fun/1,otp_7202/1,bif_fun/1,
-         external/1,eep37/1,eep37_dup/1,badarity/1,badfun/1,
+         external/1,eep37/1,badarity/1,badfun/1,
          duplicated_fun/1,unused_fun/1,parallel_scopes/1]).
 
 %% Internal exports.
@@ -39,7 +39,7 @@ all() ->
 groups() ->
     [{p,[parallel],
       [test1,overwritten_fun,otp_7202,bif_fun,external,eep37,
-       eep37_dup,badarity,badfun,duplicated_fun,unused_fun,
+       badarity,badfun,duplicated_fun,unused_fun,
        parallel_scopes]}].
 
 init_per_suite(Config) ->
@@ -223,7 +223,14 @@ bad_external_fun() ->
     fun V0:V0/V0,                               %Should fail.
     never_reached.
 
-eep37(Config) when is_list(Config) ->
+%% Named funs.
+eep37(_Config) ->
+    eep37_basic(),
+    eep37_dup(),
+    eep37_gh6515(),
+    ok.
+
+eep37_basic() ->
     F = fun Fact(N) when N > 0 -> N * Fact(N - 1); Fact(0) -> 1 end,
     Add = fun _(N) -> N + 1 end,
     UnusedName = fun _BlackAdder(N) -> N + 42 end,
@@ -232,7 +239,7 @@ eep37(Config) when is_list(Config) ->
     50 = UnusedName(8),
     ok.
 
-eep37_dup(Config) when is_list(Config) ->
+eep37_dup() ->
     dup1 = (dup1())(),
     dup2 = (dup2())(),
     ok.
@@ -243,6 +250,39 @@ dup1() ->
 dup2() ->
     fun _F() -> dup2 end.
 
+eep37_gh6515() ->
+    {0,F1} = eep37_gh6515_1(),
+    F1 = F1(),
+
+    [0,F2] = eep37_gh6515_2(),
+    1 = F2(0),
+    120 = F2(5),
+
+    ok.
+
+eep37_gh6515_1() ->
+    {case [] of
+         #{} ->
+             X = 0;
+         X ->
+             0
+     end,
+     fun X() ->
+             X
+     end}.
+
+eep37_gh6515_2() ->
+    [case [] of
+         #{} ->
+             Fact = 0;
+         Fact ->
+             0
+     end,
+     fun Fact(N) when N > 0 ->
+             N * Fact(N - 1);
+         Fact(0) -> 1
+     end].
+
 badarity(Config) when is_list(Config) ->
     {'EXIT',{{badarity,{_,[]}},_}} = (catch (fun badarity/1)()),
     {'EXIT',{{badarity,_},_}} = (catch fun() -> 42 end(0)),
-- 
2.35.3

openSUSE Build Service is sponsored by