File 1123-Optimize-in-guards.patch of Package erlang

From 7619825313cd827c6d079794596f983690b3e7a7 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Sat, 2 Sep 2023 08:04:45 +0200
Subject: [PATCH 03/25] Optimize `>=` in guards

---
 erts/emulator/beam/jit/arm/instr_common.cpp | 38 +++++++++++++++++++++
 erts/emulator/beam/jit/x86/instr_common.cpp | 33 +++++++++++++++++-
 erts/emulator/test/op_SUITE.erl             | 11 ++++++
 3 files changed, 81 insertions(+), 1 deletion(-)

diff --git a/erts/emulator/beam/jit/arm/instr_common.cpp b/erts/emulator/beam/jit/arm/instr_common.cpp
index 4c540a4d1e..cef3c81cf1 100644
--- a/erts/emulator/beam/jit/arm/instr_common.cpp
+++ b/erts/emulator/beam/jit/arm/instr_common.cpp
@@ -1844,6 +1844,44 @@ void BeamModuleAssembler::emit_is_ge(const ArgLabel &Fail,
         a.cmp(lhs.reg, rhs.reg);
         a.b_lt(resolve_beam_label(Fail, disp1MB));
         a.bind(next);
+    } else if (exact_type<BeamTypeId::Integer>(LHS) && always_small(RHS)) {
+        Label big = a.newLabel(), next = a.newLabel();
+        comment("simplified small test for known integer");
+        emit_is_not_boxed(big, lhs.reg);
+        a.cmp(lhs.reg, rhs.reg);
+        a.b_ge(next);
+        a.b(resolve_beam_label(Fail, disp128MB));
+
+        a.bind(big);
+        {
+            arm::Gp boxed_ptr = emit_ptr_val(TMP1, lhs.reg);
+            const int bitNumber = 2;
+            const int bitValue = NEG_BIG_SUBTAG - POS_BIG_SUBTAG;
+            a.ldur(TMP1, emit_boxed_val(boxed_ptr));
+            ERTS_CT_ASSERT((1 << bitNumber) == bitValue);
+            /* Fail if the bignum is negative. */
+            a.tbnz(TMP1, imm(bitNumber), resolve_beam_label(Fail, disp32K));
+        }
+        a.bind(next);
+    } else if (always_small(LHS) && exact_type<BeamTypeId::Integer>(RHS)) {
+        Label big = a.newLabel(), next = a.newLabel();
+        comment("simplified small test for known integer");
+        emit_is_not_boxed(big, rhs.reg);
+        a.cmp(lhs.reg, rhs.reg);
+        a.b_ge(next);
+        a.b(resolve_beam_label(Fail, disp128MB));
+
+        a.bind(big);
+        {
+            arm::Gp boxed_ptr = emit_ptr_val(TMP1, rhs.reg);
+            const int bitNumber = 2;
+            const int bitValue = NEG_BIG_SUBTAG - POS_BIG_SUBTAG;
+            a.ldur(TMP1, emit_boxed_val(boxed_ptr));
+            ERTS_CT_ASSERT((1 << bitNumber) == bitValue);
+            /* Fail if the bignum is positive. */
+            a.tbz(TMP1, imm(bitNumber), resolve_beam_label(Fail, disp32K));
+        }
+        a.bind(next);
     } else if (always_one_of<BeamTypeId::Integer, BeamTypeId::AlwaysBoxed>(
                        LHS) &&
                always_one_of<BeamTypeId::Integer, BeamTypeId::AlwaysBoxed>(
diff --git a/erts/emulator/beam/jit/x86/instr_common.cpp b/erts/emulator/beam/jit/x86/instr_common.cpp
index 9d5614f73a..7a406d5d55 100644
--- a/erts/emulator/beam/jit/x86/instr_common.cpp
+++ b/erts/emulator/beam/jit/x86/instr_common.cpp
@@ -1803,7 +1803,8 @@ void BeamModuleAssembler::emit_is_ge(const ArgLabel &Fail,
         return;
     }
 
-    Label generic = a.newLabel(), do_jl = a.newLabel(), next = a.newLabel();
+    Label generic = a.newLabel(), small = a.newLabel(), do_jl = a.newLabel(),
+          next = a.newLabel();
     bool need_generic = !both_small;
 
     mov_arg(ARG2, RHS); /* May clobber ARG1 */
@@ -1833,6 +1834,35 @@ void BeamModuleAssembler::emit_is_ge(const ArgLabel &Fail,
                 "bignum");
         need_generic = false;
         emit_is_not_boxed(next, ARG1, dShort);
+    } else if (exact_type<BeamTypeId::Integer>(LHS) && always_small(RHS)) {
+        x86::Gp boxed_ptr;
+        int sign_bit = NEG_BIG_SUBTAG - POS_BIG_SUBTAG;
+        ERTS_CT_ASSERT(NEG_BIG_SUBTAG > POS_BIG_SUBTAG);
+
+        comment("simplified small test for known integer");
+        need_generic = false;
+        emit_is_boxed(small, ARG1, dShort);
+
+        boxed_ptr = emit_ptr_val(ARG1, ARG1);
+        a.mov(RETd, emit_boxed_val(boxed_ptr, 0, sizeof(Uint32)));
+        a.test(RETb, imm(sign_bit));
+        /* Fail if bignum is negative. */
+        a.jne(resolve_beam_label(Fail));
+        a.short_().jmp(next);
+    } else if (always_small(LHS) && exact_type<BeamTypeId::Integer>(RHS)) {
+        x86::Gp boxed_ptr;
+
+        comment("simplified small test for known integer");
+        need_generic = false;
+        emit_is_boxed(small, ARG2, dShort);
+
+        boxed_ptr = emit_ptr_val(ARG2, ARG2);
+        a.mov(RETd, emit_boxed_val(boxed_ptr, 0, sizeof(Uint32)));
+        a.and_(RETb, imm(_TAG_HEADER_MASK));
+        ERTS_CT_ASSERT(_TAG_HEADER_NEG_BIG > _TAG_HEADER_POS_BIG);
+        a.cmp(RETb, imm(_TAG_HEADER_NEG_BIG));
+        /* Fail if bignum is positive. */
+        a.short_().jmp(do_jl);
     } else if (always_one_of<BeamTypeId::Integer, BeamTypeId::AlwaysBoxed>(
                        LHS) &&
                always_one_of<BeamTypeId::Integer, BeamTypeId::AlwaysBoxed>(
@@ -1872,6 +1902,7 @@ void BeamModuleAssembler::emit_is_ge(const ArgLabel &Fail,
     }
 
     /* Both arguments are smalls. */
+    a.bind(small);
     a.cmp(ARG1, ARG2);
     if (need_generic) {
         a.short_().jmp(do_jl);
diff --git a/erts/emulator/test/op_SUITE.erl b/erts/emulator/test/op_SUITE.erl
index 528cbea778..358c2e0df6 100644
--- a/erts/emulator/test/op_SUITE.erl
+++ b/erts/emulator/test/op_SUITE.erl
@@ -953,6 +953,12 @@ typed_relop(Config) when is_list(Config) ->
     {error,<<0:9>>} = compare_bitstring({binary, <<0:9>>, 0}),
     {binary, 42} = compare_bitstring({binary, <<0:3>>, 42}),
 
+    negative = classify_value(id(-1 bsl 128)),
+    other = classify_value(id(0)),
+    other = classify_value(id(42)),
+    other = classify_value(id(1 bsl 64)),
+    other = classify_value(id(a)),
+
     ok.
 
 compare_integer_pid(N) when is_integer(N) ->
@@ -974,6 +980,11 @@ compare_bitstring({binary, _Res, Data}) ->
 compare_bitstring({text, _Res, Data}) ->
     {text, Data}.
 
+classify_value(N) when is_integer(N), N < 0 ->
+    negative;
+classify_value(_N) ->
+    other.
+
 %%%
 %%% Utilities.
 %%%
-- 
2.35.3

openSUSE Build Service is sponsored by