File 2746-Fix-crash-when-compiling-binary-comprehension.patch of Package erlang

From 826ac62f2590e0fb668bc669b10f829ef66c47e1 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Sat, 5 Dec 2020 06:22:46 +0100
Subject: [PATCH] Fix crash when compiling binary comprehension

https://bugs.erlang.org/browse/ERL-1434
---
 lib/compiler/src/beam_ssa_bc_size.erl  | 48 ++++++++++++++++++++------
 lib/compiler/test/bs_bincomp_SUITE.erl | 18 ++++++++--
 2 files changed, 52 insertions(+), 14 deletions(-)

diff --git a/lib/compiler/src/beam_ssa_bc_size.erl b/lib/compiler/src/beam_ssa_bc_size.erl
index 2c3be55bc6..57318f2558 100644
--- a/lib/compiler/src/beam_ssa_bc_size.erl
+++ b/lib/compiler/src/beam_ssa_bc_size.erl
@@ -38,7 +38,7 @@
 -module(beam_ssa_bc_size).
 -export([opt/1]).
 
--import(lists, [any/2,reverse/1,sort/1]).
+-import(lists, [any/2,member/2,reverse/1,sort/1]).
 
 -include("beam_ssa_opt.hrl").
 
@@ -53,8 +53,9 @@ opt([Id|Ids], StMap0) ->
 opt([], StMap) -> StMap.
 
 opt_function(Id, StMap) ->
-    #opt_st{ssa=Linear0,cnt=Count0} = OptSt0 = map_get(Id, StMap),
-    try opt_blks(Linear0, StMap, unchanged, Count0, []) of
+    #opt_st{anno=Anno,ssa=Linear0,cnt=Count0} = OptSt0 = map_get(Id, StMap),
+    ParamInfo = maps:get(parameter_info, Anno, #{}),
+    try opt_blks(Linear0, ParamInfo, StMap, unchanged, Count0, []) of
         {Linear,Count} ->
             OptSt = OptSt0#opt_st{ssa=Linear,cnt=Count},
             StMap#{Id := OptSt};
@@ -67,29 +68,30 @@ opt_function(Id, StMap) ->
             erlang:raise(Class, Error, Stack)
     end.
 
-opt_blks([{L,#b_blk{is=Is}=Blk}|Blks], StMap, AnyChange, Count0, Acc0) ->
+opt_blks([{L,#b_blk{is=Is}=Blk}|Blks], ParamInfo, StMap, AnyChange, Count0, Acc0) ->
     case Is of
         [#b_set{op=bs_init_writable,dst=Dst}] ->
             Bs = #{st_map => StMap, Dst => {writable,#b_literal{val=0}}},
-            try opt_writable(Bs, L, Blk, Blks, Count0, Acc0) of
+            try opt_writable(Bs, L, Blk, Blks, ParamInfo, Count0, Acc0) of
                 {Acc,Count} ->
-                    opt_blks(Blks, StMap, changed, Count, Acc)
+                    opt_blks(Blks, ParamInfo, StMap, changed, Count, Acc)
             catch
                 throw:not_possible ->
-                    opt_blks(Blks, StMap, AnyChange, Count0, [{L,Blk}|Acc0])
+                    opt_blks(Blks, ParamInfo, StMap, AnyChange, Count0, [{L,Blk}|Acc0])
             end;
         _ ->
-            opt_blks(Blks, StMap, AnyChange, Count0, [{L,Blk}|Acc0])
+            opt_blks(Blks, ParamInfo, StMap, AnyChange, Count0, [{L,Blk}|Acc0])
     end;
-opt_blks([], _StMap, changed, Count, Acc) ->
+opt_blks([], _ParamInfo, _StMap, changed, Count, Acc) ->
     {reverse(Acc),Count};
-opt_blks([], _StMap, unchanged, _Count, _Acc) ->
+opt_blks([], _ParamInfo, _StMap, unchanged, _Count, _Acc) ->
     none.
 
-opt_writable(Bs0, L, Blk, Blks, Count0, Acc0) ->
+opt_writable(Bs0, L, Blk, Blks, ParamInfo, Count0, Acc0) ->
     case {Blk,Blks} of
         {#b_blk{last=#b_br{succ=Next,fail=Next}},
          [{Next,#b_blk{is=[#b_set{op=call,args=[_|Args],dst=Dst}=Call|_]}}|_]} ->
+            ensure_not_match_context(Call, ParamInfo),
             ArgTypes = maps:from_list([{Arg,{arg,Arg}} || Arg <- Args]),
             Bs = maps:merge(ArgTypes, Bs0),
             Result = map_get(Dst, call_size_func(Call, Bs)),
@@ -99,6 +101,30 @@ opt_writable(Bs0, L, Blk, Blks, Count0, Acc0) ->
             throw(not_possible)
     end.
 
+ensure_not_match_context(#b_set{anno=Anno,args=[_|Args]}, ParamInfo) ->
+    case maps:get(bsm_info, Anno, []) of
+        context_reused ->
+            %% The generator is a match context. The optimization is
+            %% not safe. Example:
+            %%
+            %%     f(<<B/binary>>) ->
+            %%          << <<V>> || <<V>> <= B >>.
+            throw(not_possible);
+        _ ->
+            case any(fun(V) ->
+                             member(accepts_match_context,
+                                    maps:get(V, ParamInfo, []))
+                     end, Args) of
+                true ->
+                    %% Match context is passed from the calling function. Example:
+                    %%    f0(<<B/binary>>) -> f1(B).
+                    %%    f1(B) -> << <<V>> || <<V>> <= B >>.
+                    throw(not_possible);
+                false ->
+                    ok
+            end
+    end.
+
 %%%
 %%% Traverse the SSA code of the binary comprehension functions to
 %%% figure out the exact size for the writable binary. This algorithm
diff --git a/lib/compiler/test/bs_bincomp_SUITE.erl b/lib/compiler/test/bs_bincomp_SUITE.erl
index 15fed1d4a9..a3900c7a9a 100644
--- a/lib/compiler/test/bs_bincomp_SUITE.erl
+++ b/lib/compiler/test/bs_bincomp_SUITE.erl
@@ -143,6 +143,9 @@ mixed(Config) when is_list(Config) ->
     gen_data(256),
     gen_data(512),
 
+    <<1,2,3>> = cs_default(match_context_1(<<1,2,3>>)),
+    <<4,5,6>> = cs_default(match_context_2(<<4,5,6>>)),
+
     cs_end().
 
 mixed_nested(L) ->
@@ -174,6 +177,15 @@ gen_data(Size) ->
     Data = << <<C>> || _ <- lists:seq(1, Size div 256),
                        C <- lists:seq(0, 255) >>.
 
+match_context_1(<<B/binary>>) ->
+    << <<V>> || <<V>> <= B >>.
+
+match_context_2(<<B/binary>>) ->
+    do_match_context_2(B).
+
+do_match_context_2(B) ->
+    << <<V>> || <<V>> <= B >>.
+
 filters(Config) when is_list(Config) ->
     cs_init(),
     <<"BDF">> =
@@ -329,14 +341,14 @@ sizes(Config) when is_list(Config) ->
     %% Binary generators.
 
     Fun10 = fun(Bin) ->
-		    cs(<< <<E:16>> || <<E:8>> <= Bin >>)
+		    cs(<< <<E:16>> || <<E:8>> <= id(Bin) >>)
             end,
     <<>> = Fun10(<<>>),
     <<1:16>> = Fun10(<<1>>),
     <<1:16,2:16>> = Fun10(<<1,2>>),
 
     Fun11 = fun(Bin) ->
-		    cs(<< <<E:8>> || <<E:16>> <= Bin >>)
+		    cs(<< <<E:8>> || <<E:16>> <= id(Bin) >>)
             end,
     <<>> = Fun11(<<>>),
     <<1>> = Fun11(<<1:16>>),
@@ -348,7 +360,7 @@ sizes(Config) when is_list(Config) ->
     <<1,2>> = Fun11(<<1:16,2:16,255:15>>),
 
     Fun12 = fun(Bin, Sz1, Sz2) ->
-		    cs(<< <<E:Sz1>> || <<E:Sz2>> <= Bin >>)
+		    cs(<< <<E:Sz1>> || <<E:Sz2>> <= id(Bin) >>)
 	    end,
     <<>> = Fun12(<<>>, 1, 1),
     Binary = list_to_binary(lists:seq(0, 255)),
-- 
2.26.2

openSUSE Build Service is sponsored by