Skip to content

Commit ae08744

Browse files
authored
Merge pull request #2403 from bjorng/bjorn/compiler/fix-beam_ssa_bool/ERL-1054
Correct an internal compiler error
2 parents c1b3819 + 8391048 commit ae08744

File tree

2 files changed

+90
-8
lines changed

2 files changed

+90
-8
lines changed

lib/compiler/src/beam_ssa_bool.erl

Lines changed: 73 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -610,7 +610,7 @@ bool_opt_rewrite(Bool, From, Br, Blocks0, St0) ->
610610

611611
%% Make sure that every variable that is used will be defined
612612
%% on every path to its use.
613-
ensure_init(Root, G),
613+
ensure_init(Root, G, G0),
614614

615615
%% Delete the original blocks. This is important so that we will not
616616
%% try optimize the already optimized code. That would not work
@@ -1258,23 +1258,27 @@ eval_literal_args([], Acc) ->
12581258
%%% `bif:is_boolean` are not initialized on all paths.
12591259
%%%
12601260

1261-
ensure_init(Root, G) ->
1261+
ensure_init(Root, G, G0) ->
12621262
Vs = dg_vertices(G),
12631263

1264+
%% Build an ordset of a all variables used by the code
1265+
%% before the optimization.
1266+
Used = ensure_init_used(G0),
1267+
12641268
%% Build a map of all variables that are set by instructions in
12651269
%% the digraph. Variables not included in this map have been
12661270
%% defined by code before the code in the digraph.
12671271
Vars = maps:from_list([{Dst,unset} ||
12681272
{_,#b_set{dst=Dst}} <- Vs]),
12691273
RPO = dg_reverse_postorder(G, [Root]),
1270-
ensure_init_1(RPO, G, #{Root=>Vars}).
1274+
ensure_init_1(RPO, Used, G, #{Root=>Vars}).
12711275

1272-
ensure_init_1([V|Vs], G, InitMaps0) ->
1273-
InitMaps = ensure_init_instr(V, G, InitMaps0),
1274-
ensure_init_1(Vs, G, InitMaps);
1275-
ensure_init_1([], _, _) -> ok.
1276+
ensure_init_1([V|Vs], Used, G, InitMaps0) ->
1277+
InitMaps = ensure_init_instr(V, Used, G, InitMaps0),
1278+
ensure_init_1(Vs, Used, G, InitMaps);
1279+
ensure_init_1([], _, _, _) -> ok.
12761280

1277-
ensure_init_instr(Vtx, G, InitMaps0) ->
1281+
ensure_init_instr(Vtx, Used, G, InitMaps0) ->
12781282
VarMap0 = map_get(Vtx, InitMaps0),
12791283
case dg_vertex(G, Vtx) of
12801284
#b_set{dst=Dst}=I ->
@@ -1283,11 +1287,69 @@ ensure_init_instr(Vtx, G, InitMaps0) ->
12831287
VarMap = VarMap0#{Dst=>set},
12841288
InitMaps = InitMaps0#{Vtx:=VarMap},
12851289
ensure_init_successors(OutVs, G, VarMap, InitMaps);
1290+
{external,_} ->
1291+
%% We have reached the success or failure node.
1292+
%% If the code we have been optimizing does not
1293+
%% originate from a guard, it is possible that a
1294+
%% variable set in the optimized code will be used
1295+
%% here.
1296+
case [V || {V,unset} <- maps:to_list(VarMap0)] of
1297+
[] ->
1298+
InitMaps0;
1299+
[_|_]=Unset0 ->
1300+
%% There are some variables that are not always
1301+
%% set when this node is reached. We must make
1302+
%% sure that they are not used at this node or
1303+
%% one of its successors.
1304+
Unset = ordsets:from_list(Unset0),
1305+
case ordsets:is_subset(Unset, Used) of
1306+
true ->
1307+
%% Note that all of the potentially unset
1308+
%% variables are only used once (otherwise
1309+
%% the optimization would have been
1310+
%% aborted earlier). Therefore, since all
1311+
%% variables are used in the optimized code,
1312+
%% they cannot be used in this node or in one
1313+
%% of its successors.
1314+
InitMaps0;
1315+
false ->
1316+
%% The original code probably did not
1317+
%% originate from a guard. One of the
1318+
%% potentially unset variables are not
1319+
%% used in the optimized code. That means
1320+
%% that it must be used at this node or in
1321+
%% one of its successors. (Or that it was
1322+
%% not used at all in the original code,
1323+
%% but that basically only happens in test
1324+
%% cases.)
1325+
not_possible()
1326+
end
1327+
end;
12861328
_ ->
12871329
OutVs = dg_out_neighbours(G, Vtx),
12881330
ensure_init_successors(OutVs, G, VarMap0, InitMaps0)
12891331
end.
12901332

1333+
ensure_init_used(G) ->
1334+
Vs = dg_vertices(G),
1335+
ensure_init_used_1(Vs, G, []).
1336+
1337+
ensure_init_used_1([{Vtx,#b_set{dst=Dst}=I}|Vs], G, Acc0) ->
1338+
Acc1 = [beam_ssa:used(I)|Acc0],
1339+
case dg_out_degree(G, Vtx) of
1340+
2 ->
1341+
Acc = [[Dst]|Acc1],
1342+
ensure_init_used_1(Vs, G, Acc);
1343+
_ ->
1344+
ensure_init_used_1(Vs, G, Acc1)
1345+
end;
1346+
ensure_init_used_1([{_Vtx,{br,Bool}}|Vs], G, Acc) ->
1347+
ensure_init_used_1(Vs, G, [[Bool]|Acc]);
1348+
ensure_init_used_1([_|Vs], G, Acc) ->
1349+
ensure_init_used_1(Vs, G, Acc);
1350+
ensure_init_used_1([], _G, Acc) ->
1351+
ordsets:union(Acc).
1352+
12911353
do_ensure_init_instr(#b_set{op=phi,args=Args},
12921354
_VarMap, InitMaps) ->
12931355
_ = [ensure_init_used(Var, map_get(From, InitMaps)) ||
@@ -1594,6 +1656,9 @@ dg_add_edge(Dg, From, To, Label) ->
15941656
OutEsMap = dg__edge_map_add(From, Name, OutEsMap0),
15951657
Dg#dg{in_es=InEsMap,out_es=OutEsMap}.
15961658

1659+
dg_out_degree(#dg{out_es=OutEsMap}, V) ->
1660+
length(map_get(V, OutEsMap)).
1661+
15971662
dg_out_edges(#dg{out_es=OutEsMap}, V) ->
15981663
map_get(V, OutEsMap).
15991664

lib/compiler/test/guard_SUITE.erl

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2271,6 +2271,7 @@ beam_bool_SUITE(_Config) ->
22712271
cover_shortcut_branches(),
22722272
wrong_order(),
22732273
megaco(),
2274+
looks_like_a_guard(),
22742275
ok.
22752276

22762277
before_and_inside_if() ->
@@ -2481,6 +2482,22 @@ megaco(Top, SelPrio)
24812482
megaco(_, _) ->
24822483
error.
24832484

2485+
%% ERL-1054.
2486+
looks_like_a_guard() ->
2487+
ok = looks_like_a_guard(0),
2488+
ok = looks_like_a_guard(1),
2489+
ok.
2490+
2491+
looks_like_a_guard(N) ->
2492+
GuessPosition = id(42),
2493+
%% The matching of `true` would look like a guard to
2494+
%% beam_ssa_bool. The optimized code would not be safe.
2495+
case {1 >= N, GuessPosition == 0} of
2496+
{true, _} -> ok;
2497+
{_, true} -> ok;
2498+
_ -> looks_like_a_guard(N)
2499+
end.
2500+
24842501
%%%
24852502
%%% End of beam_bool_SUITE tests.
24862503
%%%

0 commit comments

Comments
 (0)