File 0501-beam_validator-Catch-insufficient-ensure_at_least-en.patch of Package erlang
From 0c8c04d24c281d579e2dc5132f609e4fc548de0b Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Thu, 16 Jan 2025 08:22:30 +0100
Subject: [PATCH 1/3] beam_validator: Catch insufficient
ensure_at_least/ensure_exactly
---
lib/compiler/src/beam_validator.erl | 46 +++++++++-----
lib/compiler/test/beam_validator_SUITE.erl | 73 +++++++++++++++++++++-
2 files changed, 103 insertions(+), 16 deletions(-)
diff --git a/lib/compiler/src/beam_validator.erl b/lib/compiler/src/beam_validator.erl
index 9d7d202caf..5814df2921 100644
--- a/lib/compiler/src/beam_validator.erl
+++ b/lib/compiler/src/beam_validator.erl
@@ -888,7 +888,7 @@ vi({bs_match,{f,Fail},Ctx0,{commands,List}}, Vst) ->
validate_failed_bs_match(List, Ctx, FailVst)
end,
fun(SuccVst) ->
- validate_bs_match(List, Ctx, 1, SuccVst)
+ validate_bs_match(List, Ctx, 0, 1, SuccVst)
end);
vi({bs_get_tail,Ctx,Dst,Live}, Vst0) ->
assert_type(#t_bs_context{}, Ctx, Vst0),
@@ -1600,34 +1600,46 @@ validate_bs_start_match({f,Fail}, Live, Src, Dst, Vst) ->
%% Validate the bs_match instruction.
%%
-validate_bs_match([I|Is], Ctx, Unit0, Vst0) ->
+validate_bs_match([I|Is], Ctx, Ensured, Unit0, Vst0) ->
case I of
- {ensure_at_least,_Size,Unit} ->
+ {ensure_at_least,Size,Unit} ->
Type = #t_bs_context{tail_unit=Unit},
Vst1 = update_bs_unit(Ctx, Unit, Vst0),
Vst = update_type(fun meet/2, Type, Ctx, Vst1),
- validate_bs_match(Is, Ctx, Unit, Vst);
- {ensure_exactly,_Stride} ->
- validate_bs_match(Is, Ctx, Unit0, Vst0);
+ validate_bs_match(Is, Ctx, Size, Unit, Vst);
+ {ensure_exactly, Size} ->
+ validate_bs_match(Is, Ctx, Size, Unit0, Vst0);
{'=:=',nil,Bits,Value} when Bits =< 64, is_integer(Value) ->
- validate_bs_match(Is, Ctx, Unit0, Vst0);
+ validate_bs_match(Is,
+ Ctx,
+ consume_bits(I, Bits, Ensured),
+ Unit0,
+ Vst0);
{Type0,Live,{literal,Flags},Size,Unit,Dst} when Type0 =:= binary;
Type0 =:= integer ->
+ true = is_integer(Size), %Assertion.
validate_ctx_live(Ctx, Live),
verify_live(Live, Vst0),
Vst1 = prune_x_regs(Live, Vst0),
Type = case Type0 of
integer ->
- true = is_integer(Size), %Assertion.
bs_integer_type({Size, Size}, Unit, Flags);
binary ->
SizeUnit = bsm_size_unit({integer,Size}, Unit),
#t_bitstring{size_unit=SizeUnit}
end,
Vst = extract_term(Type, bs_match, [Ctx], Dst, Vst1, Vst0),
- validate_bs_match(Is, Ctx, Unit0, Vst);
- {skip,_Stride} ->
- validate_bs_match(Is, Ctx, Unit0, Vst0);
+ validate_bs_match(Is,
+ Ctx,
+ consume_bits(I, Size, Ensured),
+ Unit0,
+ Vst);
+ {skip, Size} ->
+ validate_bs_match(Is,
+ Ctx,
+ consume_bits(I, Size, Ensured),
+ Unit0,
+ Vst0);
{get_tail,Live,_,Dst} ->
validate_ctx_live(Ctx, Live),
verify_live(Live, Vst0),
@@ -1635,12 +1647,18 @@ validate_bs_match([I|Is], Ctx, Unit0, Vst0) ->
#t_bs_context{tail_unit=Unit} = get_concrete_type(Ctx, Vst0),
Type = #t_bitstring{size_unit=Unit},
Vst = extract_term(Type, get_tail, [Ctx], Dst, Vst1, Vst0),
- %% In rare circumstance, there can be multiple `get_tail` sub commands.
- validate_bs_match(Is, Ctx, Unit, Vst)
+ %% In rare circumstances, there can be multiple `get_tail` sub
+ %% commands.
+ validate_bs_match(Is, Ctx, 0, Unit, Vst)
end;
-validate_bs_match([], _Ctx, _Unit, Vst) ->
+validate_bs_match([], _Ctx, _Ensured, _Unit, Vst) ->
Vst.
+consume_bits(I, Size, Ensured) when Size > Ensured ->
+ error({insufficient_bits, I, Size, Ensured});
+consume_bits(_I, Size, Ensured) ->
+ Ensured - Size.
+
validate_ctx_live({x,X}=Ctx, Live) when X >= Live ->
error({live_does_not_preserve_context,Live,Ctx});
validate_ctx_live(_, _) ->
diff --git a/lib/compiler/test/beam_validator_SUITE.erl b/lib/compiler/test/beam_validator_SUITE.erl
index 0f8c48777a..2da4e171e2 100644
--- a/lib/compiler/test/beam_validator_SUITE.erl
+++ b/lib/compiler/test/beam_validator_SUITE.erl
@@ -44,7 +44,7 @@
infer_relops/1,
not_equal_inference/1,bad_bin_unit/1,singleton_inference/1,
inert_update_type/1,range_inference/1,
- too_many_arguments/1]).
+ too_many_arguments/1,ensure_bits/1]).
-include_lib("common_test/include/ct.hrl").
@@ -82,7 +82,7 @@ groups() ->
container_performance,infer_relops,
not_equal_inference,bad_bin_unit,singleton_inference,
inert_update_type,range_inference,
- too_many_arguments]}].
+ too_many_arguments,ensure_bits]}].
init_per_suite(Config) ->
test_lib:recompile(?MODULE),
@@ -1183,5 +1183,74 @@ too_many_arguments(_Config) ->
{{too_many_arguments,t,0},invalid_function_header}] = Errors,
ok.
+%% GH-9304: Validator did not check that operations were preceded by
+%% ensure_at_least / ensure_exactly.
+ensure_bits(_Config) ->
+ M = {ensure,
+ [{t,1}],
+ [],
+ [{function,short_eal,1,2,
+ [{label,1},
+ {func_info,{atom,short_eal},{atom,short_eal},1},
+ {label,2},
+ {test,bs_start_match3,{f,3},1,[{x,0}],{x,0}},
+ {bs_match,{f,3},{x,0},
+ {commands,[{ensure_at_least,15,1}, %% One bit short.
+ {'=:=',nil,8,0},
+ {'=:=',nil,8,0}]}},
+ {move,{atom,yay},{x,0}},
+ return,
+ {label,3},
+ {move,{atom,boo},{x,0}},
+ return]},
+ {function,short_ex,1,6,
+ [{label,5},
+ {func_info,{atom,short_ex},{atom,short_ex},1},
+ {label,6},
+ {test,bs_start_match3,{f,7},1,[{x,0}],{x,0}},
+ {bs_match,{f,7},{x,0},
+ {commands,[{ensure_exactly,7},{'=:=',nil,8,0}]}},
+ {move,{atom,yay},{x,0}},
+ return,
+ {label,7},
+ {move,{atom,boo},{x,0}},
+ return]},
+ {function,missing_ensure,1,9,
+ [{label,8},
+ {func_info,{atom,missing_ensure},{atom,missing_ensure},1},
+ {label,9},
+ {test,bs_start_match3,{f,10},1,[{x,0}],{x,0}},
+ {bs_match,{f,10},{x,0},
+ {commands,[{'=:=',nil,8,0}]}},
+ {move,{atom,yay},{x,0}},
+ return,
+ {label,10},
+ {move,{atom,boo},{x,0}},
+ return]}],
+ 11},
+ Errors = beam_val(M),
+ [{{short_eal,short_eal,1},
+ {{bs_match,
+ {f,3},
+ {x,0},
+ {commands,
+ [{ensure_at_least,15,1},
+ {'=:=',nil,8,0},
+ {'=:=',nil,8,0}]}},
+ 5,
+ {insufficient_bits,{'=:=',nil,8,0},8,7}}},
+ {{short_ex,short_ex,1},
+ {{bs_match,
+ {f,7},
+ {x,0},
+ {commands,[{ensure_exactly,7},{'=:=',nil,8,0}]}},
+ 5,
+ {insufficient_bits,{'=:=',nil,8,0},8,7}}},
+ {{missing_ensure,missing_ensure,1},
+ {{bs_match,{f,10},{x,0},{commands,[{'=:=',nil,8,0}]}},
+ 5,
+ {insufficient_bits,{'=:=',nil,8,0},8,0}}}] = Errors,
+ ok.
+
id(I) ->
I.
--
2.43.0