Skip to content

Commit

Permalink
Merge branch 'bjorn/compiler/fix-bs_ensure/GH-8280/OTP-19035' into ma…
Browse files Browse the repository at this point in the history
…int-26

* bjorn/compiler/fix-bs_ensure/GH-8280/OTP-19035:
  Fix failing binary match
  • Loading branch information
Erlang/OTP committed Apr 12, 2024
2 parents 64445c8 + d0dc1eb commit 8e70878
Show file tree
Hide file tree
Showing 3 changed files with 23 additions and 2 deletions.
4 changes: 4 additions & 0 deletions lib/compiler/src/beam_ssa_codegen.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2260,6 +2260,10 @@ bs_translate([]) -> [].

bs_translate_collect([I|Is]=Is0, Ctx, Fail, Acc) ->
case bs_translate_instr(I) of
{Ctx,_,{ensure_at_least,_,_}} ->
%% There should only be a single `ensure_at_least`
%% instruction in each `bs_match` instruction.
{bs_translate_fixup(Acc),Fail,Is0};
{Ctx,Fail,Instr} ->
bs_translate_collect(Is, Ctx, Fail, [Instr|Acc]);
{Ctx,{f,0},Instr} ->
Expand Down
13 changes: 11 additions & 2 deletions lib/compiler/src/beam_ssa_opt.erl
Original file line number Diff line number Diff line change
Expand Up @@ -304,8 +304,8 @@ late_epilogue_passes(Opts) ->
?PASS(ssa_opt_sink),
?PASS(ssa_opt_blockify),
?PASS(ssa_opt_redundant_br),
?PASS(ssa_opt_bs_ensure),
?PASS(ssa_opt_merge_blocks),
?PASS(ssa_opt_bs_ensure),
?PASS(ssa_opt_try),
?PASS(ssa_opt_get_tuple_element),
?PASS(ssa_opt_tail_literals),
Expand Down Expand Up @@ -3321,14 +3321,23 @@ redundant_br_safe_bool(Is, Bool) ->
end.

%%%
%%% Add the bs_ensure instruction before a sequence of `bs_match`
%%% Add the `bs_ensure` instruction before a sequence of `bs_match`
%%% (SSA) instructions, each having a literal size and the
%%% same failure label.
%%%
%%% This is the first part of building the `bs_match` (BEAM)
%%% instruction that can match multiple segments having the same
%%% failure label.
%%%
%%% It is beneficial but not essential to run this pass after
%%% the `merge_blocks/1` pass. For the following example, two separate
%%% `bs_match/1` instructions will emitted if blocks have not been
%%% merged before this pass:
%%%
%%% A = 0,
%%% B = <<1, 2, 3>>,
%%% <<A, B:(byte_size(B))/binary>> = <<0, 1, 2, 3>>
%%%

ssa_opt_bs_ensure({#opt_st{ssa=Blocks0,cnt=Count0}=St, FuncDb}) when is_map(Blocks0) ->
RPO = beam_ssa:rpo(Blocks0),
Expand Down
8 changes: 8 additions & 0 deletions lib/compiler/test/bs_match_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2726,6 +2726,8 @@ bs_match(_Config) ->

{'EXIT',{{badmatch,<<>>},_}} = catch do_bs_match_gh_7467(<<>>),

{0,<<1,2,3>>} = do_bs_match_gh_8280(),

ok.

do_bs_match_1(_, X) ->
Expand Down Expand Up @@ -2800,6 +2802,12 @@ do_bs_match_gh_6755(B) ->
do_bs_match_gh_7467(A) ->
do_bs_match_gh_7467(<<_:1/bits>> = A).

do_bs_match_gh_8280() ->
A = 0,
B = <<1, 2, 3>>,
<<A, B:(byte_size(B))/binary>> = id(<<0, 1, 2, 3>>),
{A, B}.

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

Expand Down

0 comments on commit 8e70878

Please sign in to comment.