File 0233-beam_validator-Don-t-fail-validation-on-empty-bs_get.patch of Package erlang

From b62bb55ff6118dc2ec2f60b086b56612244a5ccf Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Tue, 24 Nov 2020 18:56:17 +0100
Subject: [PATCH 1/2] beam_validator: Don't fail validation on empty bs_get_xyz

---
 lib/compiler/src/beam_validator.erl  | 43 +++++++++++++++++-----------
 lib/compiler/test/bs_match_SUITE.erl | 23 ++++++++-------
 2 files changed, 39 insertions(+), 27 deletions(-)

diff --git a/lib/compiler/src/beam_validator.erl b/lib/compiler/src/beam_validator.erl
index 8be5db35a7..a92f8e7685 100644
--- a/lib/compiler/src/beam_validator.erl
+++ b/lib/compiler/src/beam_validator.erl
@@ -887,16 +887,18 @@ vi({test,bs_get_binary2=Op,{f,Fail},Live,[Ctx,{atom,all},Unit,_],Dst}, Vst) ->
     Type = #t_bitstring{size_unit=Unit},
     validate_bs_get_all(Op, Fail, Ctx, Live, Unit, Type, Dst, Vst);
 vi({test,bs_get_binary2=Op,{f,Fail},Live,[Ctx,{integer,Sz},Unit,_],Dst}, Vst) ->
-    Stride = Unit * max(1, Sz),
-    Type = #t_bitstring{size_unit=Stride},
+    Stride = Unit * Sz,
+    Type = #t_bitstring{size_unit=max(1, Stride)},
     validate_bs_get(Op, Fail, Ctx, Live, Stride, Type, Dst, Vst);
 vi({test,bs_get_binary2=Op,{f,Fail},Live,[Ctx,_,Unit,_],Dst}, Vst) ->
-    Type = #t_bitstring{size_unit=Unit},
+    Type = #t_bitstring{size_unit=max(1, Unit)},
     validate_bs_get(Op, Fail, Ctx, Live, Unit, Type, Dst, Vst);
 vi({test,bs_get_integer2=Op,{f,Fail},Live,
     [Ctx,{integer,Sz},Unit,{field_flags,Flags}],Dst},Vst) ->
+
     NumBits = Unit * Sz,
-    Stride = max(1, NumBits),
+    Stride = NumBits,
+
     Type = case member(unsigned, Flags) of
                true when 0 =< NumBits, NumBits =< 64 ->
                    beam_types:make_integer(0, (1 bsl NumBits)-1);
@@ -904,11 +906,12 @@ vi({test,bs_get_integer2=Op,{f,Fail},Live,
                    %% Signed integer, way too large, or negative size.
                    #t_integer{}
            end,
+
     validate_bs_get(Op, Fail, Ctx, Live, Stride, Type, Dst, Vst);
 vi({test,bs_get_integer2=Op,{f,Fail},Live,[Ctx,_Sz,Unit,_Flags],Dst},Vst) ->
     validate_bs_get(Op, Fail, Ctx, Live, Unit, #t_integer{}, Dst, Vst);
 vi({test,bs_get_float2=Op,{f,Fail},Live,[Ctx,{integer,Sz},Unit,_],Dst},Vst) ->
-    Stride = Unit * max(1, Sz),
+    Stride = Unit * Sz,
     validate_bs_get(Op, Fail, Ctx, Live, Stride, #t_float{}, Dst, Vst);
 vi({test,bs_get_float2=Op,{f,Fail},Live,[Ctx,_,_,_],Dst}, Vst) ->
     validate_bs_get(Op, Fail, Ctx, Live, 32, #t_float{}, Dst, Vst);
@@ -1530,14 +1533,17 @@ validate_bs_skip_1(Fail, Ctx, Stride, Live, Vst) ->
                    prune_x_regs(Live, SuccVst)
            end).
 
+advance_bs_context(_Ctx, 0, Vst) ->
+    %% We _KNOW_ we're not moving anywhere. Retain our current position and
+    %% type.
+    Vst;
+advance_bs_context(_Ctx, Stride, _Vst) when Stride < 0 ->
+    %% We _KNOW_ we'll fail at runtime.
+    throw({invalid_argument, {negative_stride, Stride}});
 advance_bs_context(Ctx, Stride, Vst0) ->
-    %% slots/valid must remain untouched to support +r21, and the prior unit
-    %% must be retained if we _KNOW_ we won't advance.
+    %% slots/valid must remain untouched to support +r21.
     CtxType0 = get_raw_type(Ctx, Vst0),
-    CtxType = case Stride of
-                  0 -> CtxType0;
-                  N -> CtxType0#t_bs_context{ tail_unit=N }
-              end,
+    CtxType = CtxType0#t_bs_context{ tail_unit=Stride },
 
     Vst = update_type(fun join/2, CtxType, Ctx, Vst0),
 
@@ -2507,7 +2513,7 @@ get_literal_type(T) ->
 %% is taken, and the "success" fun returns the state where it's not.
 %%
 %% If either path is known not to be taken at runtime (eg. due to a type
-%% conflict), it will simply be discarded.
+%% conflict or argument errors), it will simply be discarded.
 -spec branch(Lbl :: label(),
              Original :: #vst{},
              FailFun :: BranchFun,
@@ -2524,16 +2530,19 @@ branch(Lbl, Vst0, FailFun, SuccFun) ->
             try SuccFun(Vst) of
                 V -> V
             catch
+                %% The instruction is guaranteed to fail; kill the state.
                 {type_conflict, _, _} ->
-                    %% The instruction is guaranteed to fail; kill the state.
+                    kill_state(Vst);
+                {invalid_argument, _} ->
                     kill_state(Vst)
             end
     catch
+        %% This instruction is guaranteed not to fail, so we run the success
+        %% branch *without* catching further errors to avoid hiding bugs in the
+        %% validator itself; one of the branches must succeed.
         {type_conflict, _, _} ->
-            %% This instruction is guaranteed not to fail, so we run the
-            %% success branch *without* catching type conflicts to avoid hiding
-            %% errors in the validator itself; one of the branches must
-            %% succeed.
+            SuccFun(Vst0);
+        {invalid_argument, _} ->
             SuccFun(Vst0)
     end.
 
diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl
index 8748cc8f46..8770477ed4 100644
--- a/lib/compiler/test/bs_match_SUITE.erl
+++ b/lib/compiler/test/bs_match_SUITE.erl
@@ -48,7 +48,7 @@
          exceptions_after_match_failure/1,
          bad_phi_paths/1,many_clauses/1,
          combine_empty_segments/1,hangs_forever/1,
-         bs_saved_position_units/1,empty_get_binary/1]).
+         bs_saved_position_units/1,empty_matches/1]).
 
 -export([coverage_id/1,coverage_external_ignore/2]).
 
@@ -87,7 +87,7 @@ groups() ->
        matching_meets_apply,bs_start_match2_defs,
        exceptions_after_match_failure,bad_phi_paths,
        many_clauses,combine_empty_segments,hangs_forever,
-       bs_saved_position_units,empty_get_binary]}].
+       bs_saved_position_units,empty_matches]}].
 
 init_per_suite(Config) ->
     test_lib:recompile(?MODULE),
@@ -2396,17 +2396,20 @@ bspu_1(<<Bin/binary>> = Bin) ->
     [Chunk || <<Chunk:5/binary>> <= Bin].
 
 
-empty_get_binary(Config) when is_list(Config) ->
-    {<<>>, <<1,2,3,4:4>>} = egb_1(<<1,2,3,4:4>>),
-    {<<>>, <<1,2,3>>} = egb_1(<<1,2,3>>),
-    {<<>>, <<>>} = egb_1(<<>>),
+empty_matches(Config) when is_list(Config) ->
+    {<<>>, <<1,2,3,4:4>>} = em_1(<<1,2,3,4:4>>),
+    {<<>>, <<1,2,3>>} = em_1(<<1,2,3>>),
+    {<<>>, <<>>} = em_1(<<>>),
 
-    <<0,1,0,2,0,3>> = egb_2(id(<<1,2,3>>)),
-    <<>> = egb_2(id(<<>>)),
+    <<0,1,0,2,0,3>> = em_2(id(<<1,2,3>>)),
+    <<>> = em_2(id(<<>>)),
+
+    <<Zero:0/unit:1>> = id(<<>>),
+    0 = id(Zero),
 
     ok.
 
-egb_1(Bytes) ->
+em_1(Bytes) ->
     {Term, Bytes} = begin
                         <<V2@V0:0/binary-unit:8,V2@Buf1/bitstring>> = Bytes,
                         V2@Conv2 = binary:copy(V2@V0),
@@ -2414,7 +2417,7 @@ egb_1(Bytes) ->
                     end,
     {Term, Bytes}.
 
-egb_2(Bin) ->
+em_2(Bin) ->
     <<
       <<K,N>> || <<K:0,N>> <= Bin
     >>.
-- 
2.26.2

openSUSE Build Service is sponsored by