Skip to content

Commit

Permalink
beam_jump: Eliminate unsafe sharing of blocks
Browse files Browse the repository at this point in the history
Fixes #7477
  • Loading branch information
bjorng committed Aug 3, 2023
1 parent cc676e9 commit e0065b1
Show file tree
Hide file tree
Showing 2 changed files with 36 additions and 14 deletions.
38 changes: 24 additions & 14 deletions lib/compiler/src/beam_jump.erl
Original file line number Diff line number Diff line change
Expand Up @@ -487,22 +487,26 @@ is_shareable([]) -> true.
%% branches to them are located.
%%
%% If there is more than one scope in the function (that is, if there
%% try/catch or catch in the function), the scope identifiers will be
%% added to the line instructions. Recording the scope in the line
%% instructions makes beam_jump idempotent, ensuring that beam_jump
%% will not do any unsafe optimizations when when compiling from a .S
%% file.
%% is any try/catch or catch in the function), the scope identifiers
%% will be added to the line instructions. Recording the scope in the
%% line instructions makes beam_jump idempotent, ensuring that
%% beam_jump will not do any unsafe optimizations when compiling from
%% a .S file.
%%

classify_labels(Is) ->
classify_labels(Is, 0, #{}).

classify_labels([{'catch',_,_}|Is], Scope, Safe) ->
classify_labels(Is, Scope+1, Safe);
classify_labels([{'catch',_,{f,L}}|Is], Scope0, Safe0) ->
Scope = Scope0 + 1,
Safe = classify_add_label(L, Scope, Safe0),
classify_labels(Is, Scope, Safe);
classify_labels([{catch_end,_}|Is], Scope, Safe) ->
classify_labels(Is, Scope+1, Safe);
classify_labels([{'try',_,_}|Is], Scope, Safe) ->
classify_labels(Is, Scope+1, Safe);
classify_labels([{'try',_,{f,L}}|Is], Scope0, Safe0) ->
Scope = Scope0 + 1,
Safe = classify_add_label(L, Scope, Safe0),
classify_labels(Is, Scope, Safe);
classify_labels([{'try_end',_}|Is], Scope, Safe) ->
classify_labels(Is, Scope+1, Safe);
classify_labels([{'try_case',_}|Is], Scope, Safe) ->
Expand All @@ -512,11 +516,7 @@ classify_labels([{'try_case_end',_}|Is], Scope, Safe) ->
classify_labels([I|Is], Scope, Safe0) ->
Labels = instr_labels(I),
Safe = foldl(fun(L, A) ->
case A of
#{L := [Scope]} -> A;
#{L := Other} -> A#{L => ordsets:add_element(Scope, Other)};
#{} -> A#{L => [Scope]}
end
classify_add_label(L, Scope, A)
end, Safe0, Labels),
classify_labels(Is, Scope, Safe);
classify_labels([], Scope, Safe) ->
Expand All @@ -529,6 +529,16 @@ classify_labels([], Scope, Safe) ->
Safe
end.

classify_add_label(L, Scope, Map) ->
case Map of
#{L := [Scope]} ->
Map;
#{L := [_|_]=Set} ->
Map#{L => ordsets:add_element(Scope, Set)};
#{} ->
Map#{L => [Scope]}
end.

%% Eliminate all fallthroughs. Return the result reversed.

eliminate_fallthroughs([{label,L}=Lbl|Is], [I|_]=Acc) ->
Expand Down
12 changes: 12 additions & 0 deletions lib/compiler/test/trycatch_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1126,6 +1126,8 @@ grab_bag(_Config) ->

{'EXIT',_} = (catch grab_bag_3()),

true = grab_bag_4(),

ok.

grab_bag_1(V) ->
Expand Down Expand Up @@ -1180,6 +1182,16 @@ grab_bag_3() ->
%% would not return two values as expected.
end =:= (V0 = 42).

grab_bag_4() ->
try
erlang:yield()
after
%% beam_jump would do an unsafe sharing of blocks, resulting
%% in an ambiguous_catch_try_state diagnostic from beam_validator.
catch <<>> = size(catch ([_ | _] = ok))
end.


stacktrace(_Config) ->
V = [make_ref()|self()],
case ?MODULE:module_info(native) of
Expand Down

0 comments on commit e0065b1

Please sign in to comment.