Skip to content

Commit af39938

Browse files
committed
Handle rare compiler crash in ssa_opt_destructive_update
Resolves #10077
1 parent c388a2d commit af39938

File tree

3 files changed

+64
-0
lines changed

3 files changed

+64
-0
lines changed

lib/compiler/src/beam_ssa_codegen.erl

Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1177,6 +1177,27 @@ cg_block([#cg_set{op=bs_create_bin,dst=Dst0,args=Args0,anno=Anno}=I,
11771177
end,
11781178
Is = [Line,{bs_create_bin,Fail,Alloc,Live,Unit,Dst,{list,Args}}],
11791179
{Is++TypeInfo,St};
1180+
cg_block([#cg_set{op=bs_create_bin,
1181+
anno=#{append_string_to_writable := true}=Anno,
1182+
dst=Dst0,args=Args0}=I|Is0],
1183+
Context, St0) ->
1184+
%% This instruction originates from a literal patched by the
1185+
%% beam_ssa_destructive_update pass.
1186+
{Is1,St} = cg_block(Is0, Context, St0),
1187+
Args1 = typed_args(Args0, Anno, St0),
1188+
Fail = {f,0},
1189+
Line = line(Anno),
1190+
Alloc = map_get(alloc, Anno),
1191+
Live = get_live(I),
1192+
Dst = beam_arg(Dst0, St0),
1193+
Args = bs_args(Args1),
1194+
Unit = 256,
1195+
TypeInfo = [{'%',{var_info,Dst,
1196+
[{type,#t_bitstring{size_unit=Unit,
1197+
appendable=true}}]}}],
1198+
Is2 = [Line,{bs_create_bin,Fail,Alloc,Live,Unit,Dst,{list,Args}}],
1199+
Is = Is2 ++ TypeInfo ++ Is1,
1200+
{Is,St};
11801201
cg_block([#cg_set{op=bs_start_match,
11811202
dst=Ctx0,
11821203
args=[#b_literal{val=new},Bin0]}=I,

lib/compiler/src/beam_ssa_destructive_update.erl

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -906,6 +906,28 @@ patch_literal_term(<<>>, {self,init_writable}, Cnt0) ->
906906
{V,Cnt} = new_var(Cnt0),
907907
I = #b_set{op=bs_init_writable,dst=V,args=[#b_literal{val=256}]},
908908
{V,[I],Cnt};
909+
patch_literal_term(<<Bits/bits>>, {self,init_writable}, Cnt0) ->
910+
{VWr,Cnt1} = new_var(Cnt0),
911+
{VAppend,Cnt} = new_var(Cnt1),
912+
I = #b_set{op=bs_init_writable,dst=VWr,args=[#b_literal{val=256}]},
913+
914+
%% Normally a `bs_create_bin` instruction must be followed by a
915+
%% `succeeded` instruction and a `br` terminator. Currently,
916+
%% without extensive refactoring, we are unable to generate such
917+
%% instruction sequences here. Therefore, since we KNOW that this
918+
%% instruction cannot be used in a guard and cannot fail, we can
919+
%% cheat by omitting the `succeeded` instruction and instead
920+
%% extend beam_ssa_codegen to handle this special case.
921+
Segments = [#b_literal{val=private_append},
922+
#b_literal{val=[1,{segment,1}]},VWr,
923+
#b_literal{val=all},
924+
#b_literal{val=binary},
925+
#b_literal{val=[1,{segment,2}]},#b_literal{val=Bits},
926+
#b_literal{val=all}],
927+
Anno = #{append_string_to_writable => true,
928+
arg_types => #{2 => #t_bitstring{size_unit=256,appendable=true}}},
929+
Append = #b_set{op=bs_create_bin,anno=Anno,dst=VAppend,args=Segments},
930+
{VAppend,[Append,I],Cnt};
909931
patch_literal_term(Lst, {hd,_,_}=E, Cnt0) ->
910932
patch_literal_list(Lst, E, Cnt0);
911933
patch_literal_term(Lit, [], Cnt) ->

lib/compiler/test/bs_construct_SUITE.erl

Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -763,6 +763,9 @@ private_append(_Config) ->
763763
<<>> = private_append_2(false),
764764
{'EXIT', _} = catch private_append_2(true),
765765

766+
{ok,<<>>} = private_append_3(id(<<>>)),
767+
{error,<<"wrong parity">>} = private_append_3(id(<<1>>)),
768+
766769
ok.
767770

768771
%% GH-7121: Alias analysis would not mark fun arguments as aliased,
@@ -777,3 +780,21 @@ private_append_1(M) when is_map(M) ->
777780
%% GH-7142: The private append pass crashed on oddly structured code.
778781
private_append_2(Boolean) ->
779782
<<<<(id(Boolean) orelse <<>>)/binary>>/binary>>.
783+
784+
%% GH-10077. Would crash when attempting patch the
785+
%% {error, <<"wrong parity">>} tuple.
786+
private_append_3(Input) ->
787+
private_append_3(Input, {ok, <<>>}).
788+
789+
private_append_3(_, {error, Msg}) ->
790+
{error, Msg};
791+
private_append_3(<<>>, {ok, Acc}) ->
792+
{ok, Acc};
793+
private_append_3(<<B/bitstring>>, {ok, Acc}) ->
794+
case B of
795+
<<>> ->
796+
private_append_3(<<>>, {ok, <<Acc/bitstring>>});
797+
_ ->
798+
%% The compiler would fail to patch this tuple.
799+
private_append_3(<<>>, {error, <<"wrong parity">>})
800+
end.

0 commit comments

Comments
 (0)