Skip to content

Commit

Permalink
beam_ssa_opt: Intersect CSE candidates on failure path
Browse files Browse the repository at this point in the history
  • Loading branch information
jhogberg committed Sep 20, 2024
1 parent 9ae2ef5 commit 519b1e6
Show file tree
Hide file tree
Showing 2 changed files with 31 additions and 9 deletions.
18 changes: 9 additions & 9 deletions lib/compiler/src/beam_ssa_opt.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1089,18 +1089,18 @@ cse_successors_1([L|Ls], Es0, M) ->
end;
cse_successors_1([], _, M) -> M.

cse_successor_fail(Fail, Src, Es0, M) ->
cse_successor_fail(Fail, Src, LHS0, M) ->
case M of
#{Fail := Es1} when map_size(Es1) =:= 0 ->
#{Fail := RHS} when map_size(RHS) =:= 0 ->
M;
#{Fail := Es1} ->
Es = #{Var => Val || Var := Val <- Es0,
is_map_key(Var, Es1),
Val =/= Src},
M#{Fail := Es};
#{Fail := RHS} ->
LHS = #{Var => Val || Var := Val <- LHS0,
is_map_key(Var, RHS),
Val =/= Src},
M#{Fail := cse_intersection(LHS, RHS)};
#{} ->
Es = #{Var => Val || Var := Val <- Es0, Val =/= Src},
M#{Fail => Es}
LHS = #{Var => Val || Var := Val <- LHS0, Val =/= Src},
M#{Fail => LHS}
end.

%% Calculate the intersection of the two maps. Both keys and values
Expand Down
22 changes: 22 additions & 0 deletions lib/compiler/test/beam_ssa_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -942,6 +942,8 @@ grab_bag(_Config) ->
{reply,{ok,foo_bar},#{page_title := foo_bar}} =
grab_bag_23(id(#{page_title => unset})),

ok = grab_bag_24(),

ok.

grab_bag_1() ->
Expand Down Expand Up @@ -1243,6 +1245,26 @@ grab_bag_23(#{page_title := unset} = State1) ->
end},
State2}.


-record(test, {a,b,c}).
-record(test_a, {a}).

%% GH-8818: The CSE pass in beam_ssa_opt failed to intersect candidates on
%% the failure path, crashing the type optimization pass.
grab_bag_24() ->
{'EXIT', _} = catch do_grab_bag_24(id(0), id(0), id(0), id(0)),
ok.

do_grab_bag_24(A, B, C, D) ->
A#test.a,
{E, F} = ext:ernal(D#test_a.a),
if
D#test_a.a == 0 andalso (B < E * A#test.a) orelse (B > F * A#test.a) ->
false;
(C =:= A#test.b) orelse (C =:= A#test.a) ->
true
end.

redundant_br(_Config) ->
{false,{x,y,z}} = redundant_br_1(id({x,y,z})),
{true,[[a,b,c]]} = redundant_br_1(id([[[a,b,c]]])),
Expand Down

0 comments on commit 519b1e6

Please sign in to comment.