File 3851-compiler-Change-some-bifs-to-guard-bifs-in-try-catch.patch of Package erlang
From ad10c978ea7738f5cb58ead131d40186cbac906d Mon Sep 17 00:00:00 2001
From: lucioleKi <isabell@erlang.org>
Date: Wed, 6 Nov 2024 14:51:50 +0100
Subject: [PATCH] compiler: Change some bifs to guard bifs in try/catch
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`, `binary_to_existing_atom/2`,
`list_to_atom/1`, `list_to_existing_atom/1`.
---
erts/emulator/beam/bif.tab | 8 ++--
lib/compiler/src/beam_ssa.erl | 14 ++++++
lib/compiler/src/beam_ssa_opt.erl | 18 +++++++
lib/compiler/src/beam_ssa_pre_codegen.erl | 3 +-
.../non_throwing_bifs.erl | 48 +++++++++++++++++++
lib/compiler/test/bif_SUITE.erl | 24 +++++++++-
6 files changed, 108 insertions(+), 7 deletions(-)
create mode 100644 lib/compiler/test/beam_ssa_check_SUITE_data/non_throwing_bifs.erl
diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab
index 41998c51e1..c7aa2bff1c 100644
--- a/erts/emulator/beam/bif.tab
+++ b/erts/emulator/beam/bif.tab
@@ -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
@@ -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
@@ -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
diff --git a/lib/compiler/src/beam_ssa.erl b/lib/compiler/src/beam_ssa.erl
index dac4211134..1773ada4b4 100644
--- a/lib/compiler/src/beam_ssa.erl
+++ b/lib/compiler/src/beam_ssa.erl
@@ -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,
@@ -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.
diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl
index f70085b23d..82bde660df 100644
--- a/lib/compiler/src/beam_ssa_opt.erl
+++ b/lib/compiler/src/beam_ssa_opt.erl
@@ -1893,6 +1893,24 @@ 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_(existing_)atom/1 call to binary_to_(existing_)atom/2.
+ {I1, Args1} = if {M, F, A} =:= {erlang, binary_to_atom, 1} orelse
+ {M, F, A} =:= {erlang, binary_to_existing_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;
diff --git a/lib/compiler/src/beam_ssa_pre_codegen.erl b/lib/compiler/src/beam_ssa_pre_codegen.erl
index 6da00829dc..1a4223d173 100644
--- a/lib/compiler/src/beam_ssa_pre_codegen.erl
+++ b/lib/compiler/src/beam_ssa_pre_codegen.erl
@@ -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
diff --git a/lib/compiler/test/beam_ssa_check_SUITE_data/non_throwing_bifs.erl b/lib/compiler/test/beam_ssa_check_SUITE_data/non_throwing_bifs.erl
new file mode 100644
index 0000000000..571a7b1972
--- /dev/null
+++ b/lib/compiler/test/beam_ssa_check_SUITE_data/non_throwing_bifs.erl
@@ -0,0 +1,48 @@
+%% %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(non_throwing_bifs).
+-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.
diff --git a/lib/compiler/test/bif_SUITE.erl b/lib/compiler/test/bif_SUITE.erl
index 41afebcfdf..24cc12d7cf 100644
--- a/lib/compiler/test/bif_SUITE.erl
+++ b/lib/compiler/test/bif_SUITE.erl
@@ -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]}].
@@ -43,7 +44,8 @@ groups() ->
cover_safe_and_pure_bifs,
cover_trim,
head_tail,
- min_max
+ min_max,
+ non_throwing
]}].
init_per_suite(Config) ->
@@ -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 = try binary_to_atom(<<"a">>)
+ catch _:_ -> []
+ end,
+ l = try list_to_existing_atom([108])
+ catch _:_ -> []
+ end,
+ [] = try list_to_existing_atom([a])
+ catch _:_ -> []
+ end,
+ 'Erlang' = try binary_to_atom(<<"Erlang">>, unicode)
+ catch _:_ -> []
+ end,
+ [] = try binary_to_existing_atom(a, unicode)
+ catch _:_ -> []
+ end,
+ ok.
+
%%%
%%% Common utilities.
%%%
--
2.43.0