Skip to content

Commit

Permalink
Merge pull request #7207 from frej/frej/private-append-fix
Browse files Browse the repository at this point in the history
Fix bug in private-append transform
  • Loading branch information
bjorng authored May 5, 2023
2 parents 5bf2632 + 5277d99 commit 2fedd1f
Show file tree
Hide file tree
Showing 4 changed files with 65 additions and 4 deletions.
5 changes: 3 additions & 2 deletions lib/compiler/src/beam_ssa_check.erl
Original file line number Diff line number Diff line change
Expand Up @@ -285,8 +285,9 @@ env_post1(_Pattern, _Actual, _Env) ->
?DP("Failed to match ~p <-> ~p~n", [_Pattern, _Actual]),
error({internal_pattern_match_error,env_post1}).

post_bitstring(Bytes, Actual, _Env) ->
Actual = build_bitstring(Bytes, <<>>).
post_bitstring(Bytes, Actual, Env) ->
Actual = build_bitstring(Bytes, <<>>),
Env.

%% Convert the parsed literal binary to an actual bitstring.
build_bitstring([{integer,_,V}|Bytes], Acc) ->
Expand Down
21 changes: 21 additions & 0 deletions lib/compiler/src/beam_ssa_private_append.erl
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,17 @@ find_appends_blk([{_Lbl,#b_blk{is=Is}}|Linear], Fun, Found0) ->
find_appends_blk([], _, Found) ->
Found.

find_appends_is([#b_set{dst=Dst, op=bs_create_bin,
args=[#b_literal{val=append},
_,
Lit=#b_literal{val= <<>>}|_]}|Is],
Fun, Found0) ->
%% Special case for when the first fragment is a literal <<>> as
%% it won't be annotated as unique nor will it die with the
%% instruction.
AlreadyFound = maps:get(Fun, Found0, []),
Found = Found0#{Fun => [{append,Dst,Lit}|AlreadyFound]},
find_appends_is(Is, Fun, Found);
find_appends_is([#b_set{dst=Dst, op=bs_create_bin,
args=[#b_literal{val=append},SegmentInfo,Var|_],
anno=#{first_fragment_dies:=Dies}=Anno}|Is],
Expand Down Expand Up @@ -468,6 +479,16 @@ patch_appends_is([I0=#b_set{dst=Dst}|Rest], PD0, Cnt0, Acc, BlockAdditions0)
Ps = keysort(1, map(ExtractOpargs, Patches)),
{Is, Cnt} = patch_opargs(I0, Ps, Cnt0),
patch_appends_is(Rest, PD, Cnt, Is++Acc, BlockAdditions0);
[{append,Dst,#b_literal{val= <<>>}=Lit}] ->
%% Special case for when the first fragment is a literal
%% <<>> and it has to be replaced with a bs_init_writable.
#b_set{op=bs_create_bin,dst=Dst,args=Args0}=I0,
[#b_literal{val=append},SegInfo,Lit|OtherArgs] = Args0,
{V,Cnt} = new_var(Cnt0),
Init = #b_set{op=bs_init_writable,dst=V,args=[#b_literal{val=256}]},
I = I0#b_set{args=[#b_literal{val=private_append},
SegInfo,V|OtherArgs]},
patch_appends_is(Rest, PD, Cnt, [I,Init|Acc], BlockAdditions0);
[{append,Dst,_}] ->
#b_set{op=bs_create_bin,dst=Dst,args=Args0}=I0,
[#b_literal{val=append}|OtherArgs] = Args0,
Expand Down
27 changes: 26 additions & 1 deletion lib/compiler/test/beam_ssa_check_SUITE_data/private_append.erl
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,8 @@
%%
-module(private_append).

-feature(maybe_expr, enable).

-export([transformable0/1,
transformable1/1,
transformable1b/1,
Expand Down Expand Up @@ -76,7 +78,9 @@
not_transformable14/0,
not_transformable15/2,

id/1]).
id/1,

bs_create_bin_on_literal/0]).

%% Trivial smoke test
transformable0(L) ->
Expand Down Expand Up @@ -977,3 +981,24 @@ not_transformable15(_, V) ->

id(I) ->
I.

%% Check that we don't try to private_append to something created by
%% bs_create_bin `append`, _, `<<>>`, ...
bs_create_bin_on_literal() ->
%ssa% () when post_ssa_opt ->
%ssa% X = bs_init_writable(_),
%ssa% Y = bs_create_bin(private_append, _, X, ...),
%ssa% Z = bs_create_bin(private_append, _, Y, ...),
%ssa% ret(Z).
<<
<<
(maybe
2147483647 ?= ok
else
<<_>> ->
ok;
_ ->
<<>>
end)/bytes
>>/binary
>>.
16 changes: 15 additions & 1 deletion lib/compiler/test/beam_ssa_check_SUITE_data/sanity_checks.erl
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,8 @@

-module(sanity_checks).

-compile(no_ssa_opt_private_append).

-export([check_fail/0,
check_wrong_pass/0,
check_xfail/0,
Expand All @@ -33,7 +35,9 @@
t25/0, t26/0, t27/0, t28/0, t29/0,
t30/0, t31/0, t32/1, t33/1, t34/1,
t35/1, t36/0, t37/0, t38/0, t39/1,
t40/0, t41/0, t42/0, t43/0, t44/0]).
t40/0, t41/0, t42/0, t43/0, t44/0,

check_env/0]).

%% Check that we do not trigger on the wrong pass
check_wrong_pass() ->
Expand Down Expand Up @@ -325,3 +329,13 @@ t44() ->
%ssa% () when post_ssa_opt ->
%ssa% _ = call(fun e:f0/1, {...}).
e:f0({}).

%% Ensure bug which trashed the environment after matching a literal
%% bitstring stays fixed.
check_env() ->
%ssa% () when post_ssa_opt ->
%ssa% X = bs_create_bin(append, _, <<>>, ...),
%ssa% ret(X).
A = <<>>,
B = ex:f(),
<<A/binary, B/binary>>.

0 comments on commit 2fedd1f

Please sign in to comment.