Skip to content

Commit

Permalink
Eliminate internal error in beam_validator
Browse files Browse the repository at this point in the history
`beam_validator` and `beam_disasm` assumed that there could only
be one `get_tail` command in a `bs_match` instruction. That assumption
is wrong. In rare circumstances, there can be more than one.

Closes #6551
  • Loading branch information
bjorng committed Dec 15, 2022
1 parent 6cbbb5d commit 8df1a6c
Show file tree
Hide file tree
Showing 3 changed files with 37 additions and 10 deletions.
4 changes: 2 additions & 2 deletions lib/compiler/src/beam_disasm.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1363,8 +1363,8 @@ resolve_bs_match_commands([{atom,'=:='},nil,Bits,Value|Rest]) ->
[{'=:=',nil,Bits,Value} | resolve_bs_match_commands(Rest)];
resolve_bs_match_commands([{atom,skip},Stride|Rest]) ->
[{skip,Stride} | resolve_bs_match_commands(Rest)];
resolve_bs_match_commands([{atom,get_tail},Live,Src,Dst]) ->
[{get_tail,Live,Src,Dst}];
resolve_bs_match_commands([{atom,get_tail},Live,Src,Dst|Rest]) ->
[{get_tail,Live,Src,Dst} | resolve_bs_match_commands(Rest)];
resolve_bs_match_commands([]) ->
[].

Expand Down
18 changes: 10 additions & 8 deletions lib/compiler/src/beam_validator.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1705,13 +1705,6 @@ validate_bs_start_match({f,Fail}, Live, Src, Dst, Vst) ->
%% Validate the bs_match instruction.
%%

validate_bs_match([{get_tail,Live,_,Dst}], Ctx, _, Vst0) ->
validate_ctx_live(Ctx, Live),
verify_live(Live, Vst0),
Vst = prune_x_regs(Live, Vst0),
#t_bs_context{tail_unit=Unit} = get_concrete_type(Ctx, Vst0),
Type = #t_bitstring{size_unit=Unit},
extract_term(Type, get_tail, [Ctx], Dst, Vst, Vst0);
validate_bs_match([I|Is], Ctx, Unit0, Vst0) ->
case I of
{ensure_at_least,_Size,Unit} ->
Expand Down Expand Up @@ -1739,7 +1732,16 @@ validate_bs_match([I|Is], Ctx, Unit0, Vst0) ->
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, Unit0, Vst0);
{get_tail,Live,_,Dst} ->
validate_ctx_live(Ctx, Live),
verify_live(Live, Vst0),
Vst1 = prune_x_regs(Live, 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)
end;
validate_bs_match([], _Ctx, _Unit, Vst) ->
Vst.
Expand Down
25 changes: 25 additions & 0 deletions lib/compiler/test/bs_match_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2675,6 +2675,13 @@ bs_match(_Config) ->
<<1,0>> = do_bs_match_1(whatever, <<1,0>>),
<<1,1>> = do_bs_match_1(whatever, <<1,1>>),
{a,b,c} = do_bs_match_1(whatever, {a,b,c}),

{'EXIT',{badarg,_}} = catch do_bs_match_gh_6551a(<<>>),
false = do_bs_match_gh_6551a(<<42>>),

{0,0} = do_bs_match_gh_6551b(0),
{<<42>>,<<42>>} = do_bs_match_gh_6551b(<<42>>),

ok.

do_bs_match_1(_, X) ->
Expand All @@ -2686,6 +2693,24 @@ do_bs_match_1(_, X) ->
end,
X.

do_bs_match_gh_6551a(X) ->
case X of
<<>> ->
true -- [];
<<_>> ->
X
end /= X.


do_bs_match_gh_6551b(X) ->
{X,
case X of
0 ->
0;
<<_>> ->
X
end}.

%% GH-6348/OTP-18297: Allow aliases for binaries.
-record(ba_foo, {a,b,c}).

Expand Down

0 comments on commit 8df1a6c

Please sign in to comment.