File 1832-Fix-code-coverage-for-zip-generators.patch of Package erlang

From 56240a81342c13e37c9691ff5bdd2730c86c2379 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Sat, 16 Nov 2024 09:18:11 +0100
Subject: [PATCH] Fix code coverage for zip generators

---
 lib/compiler/src/compile.erl      |  1 +
 lib/compiler/src/sys_coverage.erl | 28 +++++++++++++++++++-----
 lib/compiler/test/zlc_SUITE.erl   | 36 ++++++++++++++++++++++++++++---
 3 files changed, 57 insertions(+), 8 deletions(-)

diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index 10ddb07f07..395c1506bf 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -1671,6 +1671,7 @@ abstr_passes(AbstrStatus) ->
          {delay,[{iff,debug_info,?pass(save_abstract_code)}]},
 
          {delay,[{iff,line_coverage,{pass,sys_coverage}}]},
+         {iff,'dcover',{src_listing,"cover"}},
 
          ?pass(expand_records),
          {iff,'dexp',{listing,"expand"}},
diff --git a/lib/compiler/src/sys_coverage.erl b/lib/compiler/src/sys_coverage.erl
index b3515f83e8..b5265ae855 100644
--- a/lib/compiler/src/sys_coverage.erl
+++ b/lib/compiler/src/sys_coverage.erl
@@ -574,11 +574,8 @@ munge_qs([{m_generate_strict,Anno,Pattern,Expr}|Qs], Vars0, MQs) ->
     {MExpr, Vars1} = munge_expr(Expr, Vars0),
     munge_qs1(Qs, A, {m_generate_strict,Anno,Pattern,MExpr}, Vars0, Vars1, MQs);
 munge_qs([{zip,Anno,Gs0}|Qs], Vars0, MQs) ->
-    {Gs1, Vars1} = munge_qualifiers(Gs0, Vars0),
-    %% Get rid of dummy filters inserted by munge_qualifiers/2 --
-    %% they are not allowed in the zip construct.
-    Gs = [G || G <- Gs1, element(1, G) =/= block],
-    munge_qs1(Qs, Anno, {zip,Anno,Gs}, Vars0, Vars1, MQs);
+    {Gs, Pre, Vars1} = munge_zip(Gs0, Vars0),
+    munge_qs1(Qs, Anno, {zip,Anno,Gs}, Vars0, Vars1, Pre ++ MQs);
 munge_qs([Expr|Qs], Vars0, MQs) ->
     A = element(2, Expr),
     {MungedExpr, Vars1} = munge_expr(Expr, Vars0),
@@ -586,6 +583,27 @@ munge_qs([Expr|Qs], Vars0, MQs) ->
 munge_qs([], Vars0, MQs) ->
     {reverse(MQs), Vars0}.
 
+munge_zip([G0|Gs0], Vars0) ->
+    {Gen,Anno,Pattern,Expr} = G0,
+    {MungedExpr, Vars1} = munge_expr(Expr, Vars0),
+    G1 = {Gen,Anno,Pattern,MungedExpr},
+    case munge_qs1([], Anno, G1, Vars0, Vars1, []) of
+        {[{block,_,_}=Blk,G], Vars2} ->
+            {Gs, Vars3} = munge_zip_1(Gs0, Vars2, [G]),
+            {Gs, [Blk], Vars3};
+        {[G], Vars2} ->
+            {Gs, Vars3} = munge_zip_1(Gs0, Vars2, [G]),
+            {Gs, [], Vars3}
+    end.
+
+munge_zip_1([G0|Gs], Vars0, Acc) ->
+    {Gen,Anno,Pattern,Expr} = G0,
+    {MungedExpr, Vars1} = munge_expr(Expr, Vars0),
+    G1 = {Gen,Anno,Pattern,MungedExpr},
+    munge_zip_1(Gs, Vars1, [G1|Acc]);
+munge_zip_1([], Vars, Acc) ->
+    {reverse(Acc), Vars}.
+
 munge_qs1(Qs, Anno, NQ, Vars0, Vars1, MQs) ->
     case new_bumps(Vars1, Vars0) of
         [_] ->
diff --git a/lib/compiler/test/zlc_SUITE.erl b/lib/compiler/test/zlc_SUITE.erl
index eb043d79a5..75a6dc2c7c 100644
--- a/lib/compiler/test/zlc_SUITE.erl
+++ b/lib/compiler/test/zlc_SUITE.erl
@@ -24,7 +24,8 @@
          init_per_testcase/2,end_per_testcase/2,
          basic/1,mixed_zlc/1,zmc/1,filter_guard/1,
          filter_pattern/1,cartesian/1,nomatch/1,bad_generators/1,
-         strict_list/1,strict_binary/1]).
+         strict_list/1,strict_binary/1,
+         cover/1]).
 
 -include_lib("common_test/include/ct.hrl").
 -include_lib("stdlib/include/assert.hrl").
@@ -47,7 +48,8 @@ groups() ->
        nomatch,
        bad_generators,
        strict_list,
-       strict_binary
+       strict_binary,
+       cover
       ]}].
 
 init_per_suite(Config) ->
@@ -287,7 +289,7 @@ strict_list(Config) when is_list(Config) ->
     NaN = <<-1:64>>,
     [] = strict_list_5(<<>>, <<>>),
     [3.14] = strict_list_5(<<0:1,1:1>>, <<32,0.0:32/float, 64,3.14:64/float>>),
-    [0.0,3.14] = strict_list_5(<<1:1,1:1>>, <<32,0.0:32/float, 64,3.14:64/float>>),
+    [+0.0,3.14] = strict_list_5(<<1:1,1:1>>, <<32,0.0:32/float, 64,3.14:64/float>>),
     {'EXIT',{{bad_generators,{<<>>,<<64,42.0/float>>}},_}} =
         catch strict_list_5(<<>>, <<64,42.0/float>>),
     {'EXIT',{{bad_generators,{<<0:1,1:1>>,
@@ -440,6 +442,34 @@ bad_generators(Config) when is_list(Config) ->
     end,
     ok.
 
+%% Cover some code in sys_coverage.
+cover(Config) when is_list(Config) ->
+    [] = do_cover_1([], []),
+    [11,12,13] = do_cover_1([1,2,3], [10,10,10]),
+
+    ok.
+
+do_cover_1(L1, L2) ->
+    Res = [A + B || A <- begin L1 end && B <- L2],
+    Res = [A + B || A <-
+                        begin L1 end &&
+                        B <- L2],
+    Res = [A + B ||
+              A <-
+                  begin L1 end &&
+                  B <-
+                  begin L2 end],
+    Res = [A + B ||
+              A <-
+                  begin
+                      L1
+                  end &&
+                  B <-
+                  begin
+                      L2
+                  end],
+    Res.
+
 -file("bad_zlc.erl", 1).
 bad_generators(L1,L2) ->                        %Line 2
     [{I1, I2} ||                                %Line 3
-- 
2.43.0

openSUSE Build Service is sponsored by