Skip to content

Commit

Permalink
compiler: Change some bifs to guard bifs in try/catch
Browse files Browse the repository at this point in the history
When put in a try, calling a guard bif with no side-effects is already
optimized to remove the try/catch. However, there are bifs with side-effects
that can be safely optimized in the same way in order to gain performance.

Example code:
    try binary_to_atom(A, utf8)
        catch _:_ -> []
        end.

Before, SSA for the bif call after optimizations:
    _6 = call (`erlang`:`binary_to_atom`/2), _0, `utf8`
    _14 = succeeded:body _6

Now, SSA for the bif call after optimizations:
    _6 = bif:binary_to_atom _0, `utf8`
    _14 = succeeded:guard _6

Bifs that are optimized for try/catch in this change: `binary_to_atom/1`,
`binary_to_atom/2`, `binary_to_existing_atom/1`, `list_to_atom/1`,
`list_to_existing_atom/1`.
  • Loading branch information
lucioleKi committed Nov 8, 2024
1 parent 115761f commit 51eea9a
Show file tree
Hide file tree
Showing 6 changed files with 109 additions and 7 deletions.
8 changes: 4 additions & 4 deletions erts/emulator/beam/bif.tab
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ ubif erlang:hd/1
bif erlang:integer_to_list/1
ubif erlang:length/1
bif erlang:link/1
bif erlang:list_to_atom/1
ubif erlang:list_to_atom/1
bif erlang:list_to_binary/1
bif erlang:list_to_float/1
bif erlang:list_to_pid/1
Expand Down Expand Up @@ -478,7 +478,7 @@ bif string:list_to_float/1
bif erlang:make_fun/3
bif erlang:iolist_size/1
bif erlang:iolist_to_binary/1
bif erlang:list_to_existing_atom/1
ubif erlang:list_to_existing_atom/1

#
# New Bifs in R12B-0
Expand Down Expand Up @@ -510,8 +510,8 @@ bif unicode:bin_is_7bit/1
# New Bifs in R13A.
#
bif erlang:atom_to_binary/2
bif erlang:binary_to_atom/2
bif erlang:binary_to_existing_atom/2
ubif erlang:binary_to_atom/2
ubif erlang:binary_to_existing_atom/2
bif net_kernel:dflag_unicode_io/1
#
# New Bifs in R13B-1
Expand Down
14 changes: 14 additions & 0 deletions lib/compiler/src/beam_ssa.erl
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,7 @@
merge_blocks/2,
normalize/1,
no_side_effect/1,
can_be_guard_bif/3,
predecessors/1,
rename_vars/3,
rpo/1,rpo/2,
Expand Down Expand Up @@ -234,6 +235,19 @@ no_side_effect(#b_set{op=Op}) ->
_ -> false
end.

-spec can_be_guard_bif(atom(), atom(), integer()) -> boolean().

can_be_guard_bif(M, F, A) ->
case {M,F,A} of
{erlang, binary_to_atom, 2} -> true;
{erlang, binary_to_existing_atom, 2} -> true;
{erlang, list_to_atom, 1} -> true;
{erlang, list_to_existing_atom, 1} -> true;
{_,_,_} -> false
end.



%% insert_on_edges(Insertions, BlockMap, Count) -> {BlockMap, Count}.
%% Inserts instructions on the specified normal edges. It will not work on
%% exception edges.
Expand Down
17 changes: 17 additions & 0 deletions lib/compiler/src/beam_ssa_opt.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1893,6 +1893,23 @@ reduce_try_is([#b_set{op={succeeded,body}}=I0|Is], Acc) ->
%% succeeded to the `guard`, since the try/catch will be removed.
I = I0#b_set{op={succeeded,guard}},
reduce_try_is(Is, [I|Acc]);
reduce_try_is([#b_set{op=call,args=[#b_remote{mod=#b_literal{val=M},
name=#b_literal{val=F},
arity=A}=R0|Args0]}=I0|Is],
Acc) ->
%% Rewrite binary_to_atom/1 call to binary_to_atom/2.
{I1, Args1} = if {M, F, A} =:= {erlang, binary_to_atom, 1} ->
Args = Args0++[#b_literal{val=utf8}],
{I0#b_set{args=[R0#b_remote{arity=2}|Args]},Args};
true -> {I0, Args0}
end,
%% Remove try-catch for bifs that can be written as guards.
case beam_ssa:can_be_guard_bif(M, F, A) of
true ->
I = I1#b_set{op={bif,F},args=Args1},
reduce_try_is(Is, [I|Acc]);
false -> unsafe
end;
reduce_try_is([#b_set{op=Op}=I|Is], Acc) ->
IsSafe = case Op of
phi -> true;
Expand Down
3 changes: 2 additions & 1 deletion lib/compiler/src/beam_ssa_pre_codegen.erl
Original file line number Diff line number Diff line change
Expand Up @@ -929,7 +929,8 @@ sanitize_instr({bif,Bif}, [#b_literal{val=Lit}], _I) ->
end
end;
sanitize_instr({bif,Bif}, [#b_literal{val=Lit1},#b_literal{val=Lit2}], _I) ->
true = erl_bifs:is_pure(erlang, Bif, 2), %Assertion.
true = erl_bifs:is_pure(erlang, Bif, 2) orelse
beam_ssa:can_be_guard_bif(erlang, Bif, 2), %Assertion.
try
{subst,#b_literal{val=erlang:Bif(Lit1, Lit2)}}
catch
Expand Down
50 changes: 50 additions & 0 deletions lib/compiler/test/beam_ssa_check_SUITE_data/non_throwing_bifs.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,50 @@
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2024. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
%%
%% http://www.apache.org/licenses/LICENSE-2.0
%%
%% Unless required by applicable law or agreed to in writing, software
%% distributed under the License is distributed on an "AS IS" BASIS,
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%
%% %CopyrightEnd%
%%
%% This module tests functions which have previously crashed the
%% compiler when the `no_type_opt` option was used.
%%

-module(no_type_info).
-export([try_bif1/1, try_bif2/2, try_bif3/1]).



try_bif1(B) ->
%ssa% () when post_ssa_opt ->
%ssa% X = bif:binary_to_atom(B),
%ssa% _ = succeeded:guard(X).
try binary_to_atom(B)
catch _:_ -> []
end.

try_bif2(A, B) ->
%ssa% () when post_ssa_opt ->
%ssa% X = bif:binary_to_atom(A, B),
%ssa% _ = succeeded:guard(X).
try binary_to_atom(A, B)
catch _:_ -> []
end.

try_bif3(A) ->
%ssa% () when post_ssa_opt ->
%ssa% X = erlang:float_to_list(A),
%ssa% _ = succeeded:body(X).
try float_to_list(A)
catch _:_ -> []
end.
24 changes: 22 additions & 2 deletions lib/compiler/test/bif_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,8 @@
beam_validator/1,trunc_and_friends/1,cover_safe_and_pure_bifs/1,
cover_trim/1,
head_tail/1,
min_max/1]).
min_max/1,
non_throwing/1]).

suite() ->
[{ct_hooks,[ts_install_cth]}].
Expand All @@ -43,7 +44,8 @@ groups() ->
cover_safe_and_pure_bifs,
cover_trim,
head_tail,
min_max
min_max,
non_throwing
]}].

init_per_suite(Config) ->
Expand Down Expand Up @@ -292,6 +294,24 @@ int_clamped_add(A) when is_integer(A) ->
num_clamped_add(A) ->
min(max(A, 0), 10) + 100.

non_throwing(_Config) ->
a = with_try(fun binary_to_atom/1, <<"a">>),
l = with_try(fun list_to_existing_atom/1, [108]),
[] = with_try(fun list_to_atom/1, [a]),
'Erlang' = with_try_2(fun binary_to_atom/2, <<"Erlang">>, unicode),
[] = with_try_2(fun binary_to_existing_atom/2, a, unicode),
ok.

with_try(Fun, A) ->
try Fun(A)
catch _:_ -> []
end.

with_try_2(Fun, A, B) ->
try Fun(A, B)
catch _:_ -> []
end.

%%%
%%% Common utilities.
%%%
Expand Down

0 comments on commit 51eea9a

Please sign in to comment.