File 5132-Recognize-arithmetic-instructions-that-can-t-fail.patch of Package erlang

From 8a738bdf0b5188165020178a560a058ab0f055fa Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 9 Feb 2022 06:19:12 +0100
Subject: [PATCH 2/2] Recognize arithmetic instructions that can't fail

Knowing that arithmetic operations can't fail makes it possible to
remove dead code and redundant tests, for example the check for a bad
size in this code:

    <<X:(S-4)>> = Bin

An early pass of the compiler (v3_core) rewrites this code to
essentially:

    NewS = try
               S-4
           catch
               _:_ ->
                   bad_size
           end,
    <<X:NewS>> = Bin

If it is known that the expression `S-4` can't fail, the code can be
simplified to:

    NewS = S-4,
    <<X:NewS>> = Bin
---
 lib/compiler/src/beam_call_types.erl      | 35 +++++++++++++++++++++++
 lib/compiler/src/beam_ssa_pre_codegen.erl |  1 +
 2 files changed, 36 insertions(+)

diff --git a/lib/compiler/src/beam_call_types.erl b/lib/compiler/src/beam_call_types.erl
index dab4455a7e..b1a5e80366 100644
--- a/lib/compiler/src/beam_call_types.erl
+++ b/lib/compiler/src/beam_call_types.erl
@@ -40,6 +40,20 @@
       ArgTypes :: [normal_type()],
       Result :: yes | no | maybe.
 
+will_succeed(erlang, Op, [LHS, RHS])
+  when Op =:= '+'; Op =:= '-'; Op =:= '*' ->
+    succeeds_if_smallish(LHS, RHS);
+will_succeed(erlang, Op, [#t_integer{elements={_,_}},
+                          #t_integer{elements={Div,_}}])
+  when (Op =:= 'div' orelse Op =:= 'rem'), Div > 0 ->
+    yes;
+will_succeed(erlang, 'bsr', [#t_integer{elements={_,_}},
+                             #t_integer{elements={S,_}}])
+  when S >= 0 ->
+    yes;
+will_succeed(erlang, 'bsl', [#t_integer{}=LHS,#t_integer{elements={S,_}}])
+  when S < 64 ->
+    succeeds_if_smallish(LHS);
 will_succeed(erlang, '++', [LHS, _RHS]) ->
     succeeds_if_type(LHS, proper_list());
 will_succeed(erlang, '--', [LHS, RHS]) ->
@@ -53,6 +67,14 @@ will_succeed(erlang, bit_size, [Arg]) ->
     succeeds_if_type(Arg, #t_bitstring{});
 will_succeed(erlang, byte_size, [Arg]) ->
     succeeds_if_type(Arg, #t_bitstring{});
+will_succeed(erlang, element, [Pos, #t_tuple{size=Sz}] = Args) when Sz > 0 ->
+    SizeType = #t_integer{elements={1,Sz}},
+    case beam_types:meet(Pos, SizeType) of
+        Pos ->
+            yes;
+        _ ->
+            fails_on_conflict(Args, [#t_integer{}, #t_tuple{}])
+    end;
 will_succeed(erlang, hd, [Arg]) ->
     succeeds_if_type(Arg, #t_cons{});
 will_succeed(erlang, is_function, [_,#t_integer{elements={Min,_}}])
@@ -131,6 +153,19 @@ succeeds_if_type(ArgType, Required) ->
         _ -> maybe
     end.
 
+succeeds_if_smallish(#t_integer{elements={Min,Max}})
+  when abs(Min) bsr 128 =:= 0, abs(Max) bsr 128 =:= 0 ->
+    yes;
+succeeds_if_smallish(_) ->
+    maybe.
+
+succeeds_if_smallish(LHS, RHS) ->
+    case {succeeds_if_smallish(LHS),
+          succeeds_if_smallish(RHS)} of
+        {yes, yes} -> yes;
+        {_, _} -> maybe
+    end.
+
 %%
 %% Returns the inferred return and argument types for known functions, and
 %% whether it's safe to subtract argument types on failure.
diff --git a/lib/compiler/src/beam_ssa_pre_codegen.erl b/lib/compiler/src/beam_ssa_pre_codegen.erl
index 33dacad296..5a40377738 100644
--- a/lib/compiler/src/beam_ssa_pre_codegen.erl
+++ b/lib/compiler/src/beam_ssa_pre_codegen.erl
@@ -2531,6 +2531,7 @@ use_zreg(wait_timeout) -> yes;
 %% There's no way we can combine these into a test instruction, so we must
 %% avoid using a z register if their result is used directly in a branch.
 use_zreg(call) -> no;
+use_zreg({bif,element}) -> no;
 use_zreg({bif,is_map_key}) -> no;
 use_zreg({bif,is_record}) -> no;
 use_zreg({bif,map_get}) -> no;
-- 
2.34.1

openSUSE Build Service is sponsored by