File 1060-Fix-crash-when-compiling-binary-comprehensions.patch of Package erlang

From fd5c39100754832e4d4cf478a3e597e795772c32 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 1 Dec 2020 15:28:52 +0100
Subject: [PATCH] Fix crash when compiling binary comprehensions

Fix a bug that would cause the compiler to crash when compiling
a binary comprehension where one generator depended on another
generator. Example:

    << <<X>> || L <- [[1]], X <- L >>

https://bugs.erlang.org/browse/ERL-1427
---
 lib/compiler/src/v3_core.erl           | 13 +++++++++++--
 lib/compiler/test/bs_bincomp_SUITE.erl | 19 +++++++++++--------
 2 files changed, 22 insertions(+), 10 deletions(-)

diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index d318fab15c..2be6568977 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -1717,8 +1717,17 @@ bc_add_list_1([H|T], Pre, E, St0) ->
 bc_add_list_1([], Pre, E, St) ->
     {E,reverse(Pre),St}.
 
-bc_gen_size(Q, EVs, St) ->
-    bc_gen_size_1(Q, EVs, #c_literal{val=1}, [], St).
+bc_gen_size([_]=Q, EVs, St) ->
+    %% Single generator.
+    bc_gen_size_1(Q, EVs, #c_literal{val=1}, [], St);
+bc_gen_size(_, _, _) ->
+    %% There are multiple generators (or there are filters).
+    %% To avoid introducing unbound variables in the size
+    %% calculation when one generator references a
+    %% variable bound by a previous generator, we will
+    %% not do any size calculation. This issue will be
+    %% handled in a cleaner way in OTP 24.
+    throw(impossible).
 
 bc_gen_size_1([{generate,L,El,Gen}|Qs], EVs, E0, Pre0, St0) ->
     bc_verify_non_filtering(El, EVs),
diff --git a/lib/compiler/test/bs_bincomp_SUITE.erl b/lib/compiler/test/bs_bincomp_SUITE.erl
index 2218b007d8..0d129a4a48 100644
--- a/lib/compiler/test/bs_bincomp_SUITE.erl
+++ b/lib/compiler/test/bs_bincomp_SUITE.erl
@@ -101,26 +101,26 @@ extended_bit_aligned(Config) when is_list(Config) ->
 mixed(Config) when is_list(Config) ->
     cs_init(),
     <<2,3,3,4,4,5,5,6>> =
-	cs(<< <<(X+Y)>> || <<X>> <= <<1,2,3,4>>, <<Y>> <= <<1,2>> >>),
+	cs_default(<< <<(X+Y)>> || <<X>> <= <<1,2,3,4>>, <<Y>> <= <<1,2>> >>),
     <<2,3,3,4,4,5,5,6>> =
-	<< <<(X+Y)>> || <<X>> <= <<1,2,3,4>>, Y <- [1,2] >>,
+	cs_default(<< <<(X+Y)>> || <<X>> <= <<1,2,3,4>>, Y <- [1,2] >>),
     <<2,3,3,4,4,5,5,6>> =
-	cs(<< <<(X+Y)>> || X <- [1,2,3,4], Y <- [1,2] >>),
+	cs_default(<< <<(X+Y)>> || X <- [1,2,3,4], Y <- [1,2] >>),
     One = id([1,2,3,4]),
     Two = id([1,2]),
     <<2,3,3,4,4,5,5,6>> =
-	cs(<< <<(X+Y)>> || X <- One, Y <- Two >>),
+	cs_default(<< <<(X+Y)>> || X <- One, Y <- Two >>),
     [2,3,3,4,4,5,5,6] =
 	[(X+Y) || <<X>> <= <<1,2,3,4>>, <<Y>> <= <<1,2>>],
     [2,3,3,4,4,5,5,6] =
 	[(X+Y) || <<X>> <= <<1,2,3,4>>, Y <- [1,2]],
     <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> =
-	cs(<< <<(X+Y):3>> || <<X:3>> <= <<1:3,2:3,3:3,4:3>>,
-			     <<Y:3>> <= <<1:3,2:3>> >>),
+	cs_default(<< <<(X+Y):3>> || <<X:3>> <= <<1:3,2:3,3:3,4:3>>,
+                                     <<Y:3>> <= <<1:3,2:3>> >>),
     <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> =
-	cs(<< <<(X+Y):3>> || <<X:3>> <= <<1:3,2:3,3:3,4:3>>, Y <- [1,2] >>),
+	cs_default(<< <<(X+Y):3>> || <<X:3>> <= <<1:3,2:3,3:3,4:3>>, Y <- [1,2] >>),
     <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> =
-	cs(<< <<(X+Y):3>> || X <- [1,2,3,4], Y <- [1,2] >>),
+	cs_default(<< <<(X+Y):3>> || X <- [1,2,3,4], Y <- [1,2] >>),
     <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> =
 	cs_default(<< <<(X+Y):3>> || {X,Y} <- [{1,1},{1,2},{2,1},{2,2},
 					       {3,1},{3,2},{4,1},{4,2}] >>),
@@ -131,6 +131,9 @@ mixed(Config) when is_list(Config) ->
 
     %% OTP-16899: Nested binary comprehensions would fail to load.
     <<0,1,0,2,0,3,99>> = mixed_nested([1,2,3]),
+
+    <<1>> = cs_default(<< <<X>> || L <- [[1]], X <- L >>),
+
     cs_end().
 
 mixed_nested(L) ->
-- 
2.26.2

openSUSE Build Service is sponsored by