File 0298-Eliminate-crash-for-nested-guards-in-record-initiali.patch of Package erlang

From 1b23ddb92aede36726b7715b0041e0bc96065467 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 27 Feb 2024 13:31:19 +0100
Subject: [PATCH] Eliminate crash for nested guards in record initialization

Also fix other bugs in the `erl_expand_records` pass hidden behind the
original bug.

Closes #8190
---
 lib/stdlib/src/erl_expand_records.erl        | 26 +++++---
 lib/stdlib/src/erl_lint.erl                  |  9 +--
 lib/stdlib/test/erl_expand_records_SUITE.erl | 65 ++++++++++++++++----
 3 files changed, 73 insertions(+), 27 deletions(-)

diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl
index dd0ab66486..d67e4e3796 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -56,11 +56,13 @@ module has no references to records, attributes, or code.
 %% Is is assumed that Fs is a valid list of forms. It should pass
 %% erl_lint without errors.
 module(Fs0, Opts0) ->
+    put(erl_expand_records_in_guard, false),
     Opts = compiler_options(Fs0) ++ Opts0,
     Dialyzer = lists:member(dialyzer, Opts),
     Calltype = init_calltype(Fs0),
     St0 = #exprec{compile = Opts, dialyzer = Dialyzer, calltype = Calltype},
     {Fs,_St} = forms(Fs0, St0),
+    erase(erl_expand_records_in_guard),
     Fs.
 
 compiler_options(Forms) ->
@@ -209,12 +211,18 @@ normalise_test(tuple, 1)     -> is_tuple;
 normalise_test(Name, _) -> Name.
 
 is_in_guard() ->
-    get(erl_expand_records_in_guard) =/= undefined.
+    get(erl_expand_records_in_guard).
 
 in_guard(F) ->
-    undefined = put(erl_expand_records_in_guard, true),
+    InGuard = put(erl_expand_records_in_guard, true),
     Res = F(),
-    true = erase(erl_expand_records_in_guard),
+    true = put(erl_expand_records_in_guard, InGuard),
+    Res.
+
+not_in_guard(F) ->
+    InGuard = put(erl_expand_records_in_guard, false),
+    Res = F(),
+    false = put(erl_expand_records_in_guard, InGuard),
     Res.
 
 %% record_test(Anno, Term, Name, Vs, St) -> TransformedExpr
@@ -370,11 +378,15 @@ expr({'fun',Anno,{function,F,A}}=Fun0, St0) ->
 expr({'fun',_,{function,_M,_F,_A}}=Fun, St) ->
     {Fun,St};
 expr({'fun',Anno,{clauses,Cs0}}, St0) ->
-    {Cs,St1} = clauses(Cs0, St0),
-    {{'fun',Anno,{clauses,Cs}},St1};
+    not_in_guard(fun() ->
+                         {Cs,St1} = clauses(Cs0, St0),
+                         {{'fun',Anno,{clauses,Cs}},St1}
+                 end);
 expr({named_fun,Anno,Name,Cs0}, St0) ->
-    {Cs,St1} = clauses(Cs0, St0),
-    {{named_fun,Anno,Name,Cs},St1};
+    not_in_guard(fun() ->
+                         {Cs,St1} = clauses(Cs0, St0),
+                         {{named_fun,Anno,Name,Cs},St1}
+                 end);
 expr({call,Anno,{atom,_,is_record},[A,{atom,_,Name}]}, St) ->
     record_test(Anno, A, Name, St);
 expr({call,Anno,{remote,_,{atom,_,erlang},{atom,_,is_record}},
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 5123a4941a..d7dfd57c63 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -2385,13 +2385,8 @@ is_guard_test(Expression, Forms, IsOverridden) ->
     %% processing the forms until we'll know that the record
     %% definitions are truly needed.
     F = fun() ->
-                St = foldl(fun({attribute, _, record, _}=Attr0, St0) ->
-                                   Attr = set_file(Attr0, "none"),
-                                   attribute_state(Attr, St0);
-                              (_, St0) ->
-                                   St0
-                           end, start(), Forms),
-                St#lint.records
+                #{Name => {A,Fs} ||
+                    {attribute, A, record, {Name, Fs}} <- Forms}
         end,
 
     is_guard_test2(NoFileExpression, {F,IsOverridden}).
diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl
index 13aaf0abdb..f9fd88a594 100644
--- a/lib/stdlib/test/erl_expand_records_SUITE.erl
+++ b/lib/stdlib/test/erl_expand_records_SUITE.erl
@@ -223,21 +223,56 @@ guard(Config) when is_list(Config) ->
 %% Wildcard initialisation.
 init(Config) when is_list(Config) ->
     Ts = [
-      <<"
-         -record(r, {a,b,c,d = foo}).
-
-         t() ->
-             R = #r{_ = init, b = b},
-             #r{c = init, b = b, a = init} = R,
-             case R of
-                 #r{b = b, _ = init} -> ok;
-                 _ -> not_ok
-             end.
-      ">>
-      ],
+          <<"-record(r, {a,b,c,d = foo}).
+
+t() ->
+    R = #r{_ = init, b = b},
+    #r{c = init, b = b, a = init} = R,
+    case R of
+        #r{b = b, _ = init} -> ok;
+        _ -> not_ok
+    end.
+">>,
+          <<"-record(r0, {a}).
+-record(r1, {rf1 = (#r0{a = #{ok => ok || ok}})}).
+
+t() ->
+    catch <<0 || #r1{}>>,
+    ok.
+">>,
+          <<"-record(r0, {a}).
+-record(r1, {
+             rf1 = fun
+                       (+0.0) ->
+                           (list_to_bitstring(ok))#r0.a;
+                       (_) when ok ->
+                           ok
+                   end
+            }).
+
+t() ->
+    catch <<0 || (#r1{})>>,
+    ok.
+">>,
+          <<"-record(r0, {a}).
+-record(r1, {
+             a = {
+                  ((ok)#r0{})#r0.a,
+                  case whatever of
+                        _ when cucumber ->
+                            banan
+                    end
+                   }
+            }).
+
+t() ->
+    catch #{ok => ok || #r1{}},
+    ok.
+">>
+         ],
     run(Config, Ts),
     ok.
-    
+
 %% Some patterns.
 pattern(Config) when is_list(Config) ->
     Ts = [
-- 
2.35.3

openSUSE Build Service is sponsored by