File 0175-Eliminate-redundant-test-for-empty-binary.patch of Package erlang
From a7d9aad3e0cb1333201e15fd1a0cf04f409a6675 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 5 Mar 2024 06:35:03 +0100
Subject: [PATCH 2/2] Eliminate redundant test for empty binary
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit
Consider this module:
-module(test).
-export([test/1]).
test(Bin) when is_binary(Bin) ->
test1(Bin).
test1(<<_, Rest/binary>>) -> test1(Rest);
test1(<<>>) -> ok.
The only way the first clause of `test1/1` can fail is when the input
binary is empty. Therefore, testing for an empty binary in the second
clause is redundant. The compiler still generates a test for
an empty binary and code to raise a `function_clause` exception if the
binary is not empty. Because an exception can be raised, the compiler
also needs to insert a book-keeping instruction (`bs_set_position`)
into the code for the first clause. That extra instruction has a
measurable impact on performance.
This commit eliminates the test for an empty binary and the extra
`bs_set_position` instruction when it is safe to do so.
Thanks to Michał Muskała for noticing this issue.
---
lib/compiler/src/beam_ssa_opt.erl | 92 +++++++++++++++++++++++++++-
lib/compiler/src/beam_ssa_type.erl | 2 +
lib/compiler/test/bs_match_SUITE.erl | 39 +++++++++++-
3 files changed, 130 insertions(+), 3 deletions(-)
diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl
index d3530bf723..a17dd8c8d3 100644
--- a/lib/compiler/src/beam_ssa_opt.erl
+++ b/lib/compiler/src/beam_ssa_opt.erl
@@ -2112,7 +2112,8 @@ ssa_opt_bsm_shortcut({#opt_st{ssa=Linear0}=St, FuncDb}) ->
%% No binary matching instructions.
{St, FuncDb};
_ ->
- Linear = bsm_shortcut(Linear0, Positions),
+ Linear1 = bsm_shortcut(Linear0, Positions),
+ Linear = bsm_tail(Linear1, #{}),
ssa_opt_live({St#opt_st{ssa=Linear}, FuncDb})
end.
@@ -2187,6 +2188,95 @@ bsm_shortcut([{L,#b_blk{is=Is,last=Last0}=Blk}|Bs], PosMap0) ->
end;
bsm_shortcut([], _PosMap) -> [].
+%% Remove `bs_test_tail` instructions that are known to always
+%% succeed, such as in the following example:
+%%
+%% m(Bin) when is_binary(Bin) ->
+%% m1(Bin).
+%% m1(<<_, Rest/binary>>) -> m1(Rest);
+%% m1(<<>>) -> ok.
+%%
+%% The second clause of `m1/1` does not need to check for an empty
+%% binary.
+
+bsm_tail([{L,#b_blk{is=Is0,last=Last0}=Blk0}|Bs], Map0) ->
+ {Is,Last,Map} = bsm_tail_is(Is0, Last0, L, Map0, []),
+ Blk = Blk0#b_blk{is=Is,last=Last},
+ [{L,Blk}|bsm_tail(Bs, Map)];
+bsm_tail([], _Map) ->
+ [].
+
+bsm_tail_is([#b_set{op=bs_start_match,anno=Anno,dst=Dst}=I|Is], Last, L, Map0, Acc) ->
+ case Anno of
+ #{arg_types := #{1 := Type}} ->
+ case beam_types:get_bs_matchable_unit(Type) of
+ error ->
+ bsm_tail_is(Is, Last, L, Map0, [I|Acc]);
+ Unit when is_integer(Unit) ->
+ Map = Map0#{Dst => Unit},
+ bsm_tail_is(Is, Last, L, Map, [I|Acc])
+ end;
+ #{} ->
+ bsm_tail_is(Is, Last, L, Map0, [I|Acc])
+ end;
+bsm_tail_is([#b_set{op=bs_match,dst=Dst,args=Args},
+ #b_set{op={succeeded,guard},dst=SuccDst,args=[Dst]}|_]=Is,
+ #b_br{bool=SuccDst,fail=Fail}=Last,
+ _L, Map0, Acc) ->
+ case bsm_tail_num_matched(Args, Map0) of
+ unknown ->
+ %% Unknown number of bits or the match operation will fail
+ %% to match certain values.
+ Map = Map0#{Fail => unknown},
+ {reverse(Acc, Is),Last,Map};
+ Bits when is_integer(Bits) ->
+ case Map0 of
+ #{Fail := Bits} ->
+ {reverse(Acc, Is),Last,Map0};
+ #{Fail := _} ->
+ Map = Map0#{Fail => unknown},
+ {reverse(Acc, Is),Last,Map};
+ #{} ->
+ Map = Map0#{Fail => Bits},
+ {reverse(Acc, Is),Last,Map}
+ end
+ end;
+bsm_tail_is([#b_set{op=bs_test_tail,args=[_,#b_literal{val=0}],dst=Dst}]=Is,
+ #b_br{bool=Dst,succ=Succ}=Last0, L, Map0, Acc) ->
+ case Map0 of
+ #{L := Bits} when is_integer(Bits) ->
+ %% The `bs_match` instruction targeting this block on failure
+ %% will only fail when the end of the binary has been reached.
+ %% There is no need for the test.
+ Last = beam_ssa:normalize(Last0#b_br{fail=Succ}),
+ {reverse(Acc, Is),Last,Map0};
+ #{} ->
+ {reverse(Acc, Is),Last0,Map0}
+ end;
+bsm_tail_is([#b_set{}=I|Is], Last, L, Map, Acc) ->
+ bsm_tail_is(Is, Last, L, Map, [I|Acc]);
+bsm_tail_is([], Last, _L, Map0, Acc) ->
+ Map = foldl(fun(F, A) ->
+ A#{F => unknown}
+ end, Map0, beam_ssa:successors(#b_blk{is=[],last=Last})),
+ {reverse(Acc),Last,Map}.
+
+bsm_tail_num_matched([#b_literal{val=skip},Ctx,Type,Flags,Size,Unit], Map) ->
+ bsm_tail_num_matched([Type,Ctx,Flags,Size,Unit], Map);
+bsm_tail_num_matched([#b_literal{val=Type},Ctx,#b_literal{},
+ #b_literal{val=Size},#b_literal{val=Unit}], Map)
+ when (Type =:= integer orelse Type =:= binary),
+ is_integer(Size), is_integer(Unit) ->
+ Bits = Size * Unit,
+ case Map of
+ #{Ctx := Bits} when is_integer(Bits) ->
+ Bits;
+ #{} ->
+ unknown
+ end;
+bsm_tail_num_matched(_Args, _Map) ->
+ unknown.
+
%%%
%%% Optimize binary construction.
%%%
diff --git a/lib/compiler/src/beam_ssa_type.erl b/lib/compiler/src/beam_ssa_type.erl
index fe8efa5f3a..a833425693 100644
--- a/lib/compiler/src/beam_ssa_type.erl
+++ b/lib/compiler/src/beam_ssa_type.erl
@@ -637,6 +637,8 @@ benefits_from_type_anno(bs_create_bin, _Args) ->
true;
benefits_from_type_anno(bs_match, _Args) ->
true;
+benefits_from_type_anno(bs_start_match, _Args) ->
+ true;
benefits_from_type_anno(is_tagged_tuple, _Args) ->
true;
benefits_from_type_anno(call, [#b_var{} | _]) ->
diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl
index 45103ed6aa..5641f86d10 100644
--- a/lib/compiler/test/bs_match_SUITE.erl
+++ b/lib/compiler/test/bs_match_SUITE.erl
@@ -54,6 +54,7 @@
trim_bs_start_match_resume/1,
gh_6410/1,bs_match/1,
binary_aliases/1,gh_6923/1,
+ bs_test_tail/1,
otp_19019/1]).
-export([coverage_id/1,coverage_external_ignore/2]).
@@ -96,6 +97,7 @@ groups() ->
trim_bs_start_match_resume,
gh_6410,bs_match,binary_aliases,
gh_6923,
+ bs_test_tail,
otp_19019]}].
init_per_suite(Config) ->
@@ -3220,6 +3222,39 @@ gh_6923(_Config) ->
do_gh_6923([<<"abc">>, A]) when is_integer(A) -> first;
do_gh_6923([<<"abc">>, A]) when is_tuple(A) -> second.
+bs_test_tail(Config) ->
+ Bin = term_to_binary(Config),
+
+ ok = bs_test_tail_skip(Bin),
+
+ "abc" = bs_test_tail_int(<<(id(<<"abc">>))/binary>>),
+
+ [2.0,3.0] = bs_test_tail_float(<<(id(2.0)):64/float,(id(3.0)):64/float>>),
+ {'EXIT',{function_clause,_}} = catch bs_test_tail_float(<<(id(-1)):128>>),
+
+ ok = bs_test_partial_tail(<<(id(0))>>),
+ {'EXIT',{function_clause,_}} = catch bs_test_partial_tail(<<(id(1))>>),
+
+ ok.
+
+%% No bs_test_tail instruction is needed.
+bs_test_tail_skip(<<_, T/binary>>) -> bs_test_tail_skip(T);
+bs_test_tail_skip(<<>>) -> ok.
+
+%% No bs_test_tail instruction is needed.
+bs_test_tail_int(<<H:8, T/binary>>) ->
+ [H|bs_test_tail_int(T)];
+bs_test_tail_int(<<>>) -> [].
+
+%% The bs_test_tail instruction is needed.
+bs_test_tail_float(<<F:64/float, T/binary>>) ->
+ [F|bs_test_tail_float(T)];
+bs_test_tail_float(<<>>) -> [].
+
+%% The bs_test_tail instruction is needed.
+bs_test_partial_tail(<<0:8, T/binary>>) -> bs_test_partial_tail(T);
+bs_test_partial_tail(<<>>) -> ok.
+
otp_19019(_Config) ->
ok = do_otp_19019(id(<<42>>)),
<<>> = do_otp_19019(id(<<>>)),
--
2.35.3