File 0344-Handle-negative-zeros-on-unary-minus.patch of Package erlang

From 200842d9ae5b75ccc2f982de36742003e231c0bb Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co>
Date: Thu, 3 Dec 2020 09:39:07 +0100
Subject: [PATCH] Handle negative zeros on unary minus

Before this patch, unary minus "-value" was implemented
as "0 - value" but that is not equivalent for floats when
0.0 is given.

This patch addresses this issue by implementing unary
minus as its own operation and improves the coverage.
---
 erts/emulator/beam/emu/arith_instrs.tab | 39 +++++++++++++
 erts/emulator/beam/emu/ops.tab          |  4 +-
 erts/emulator/beam/erl_arith.c          | 67 +++++++++++++++++++++-
 erts/emulator/beam/global.h             |  1 +
 erts/emulator/beam/jit/beam_asm.hpp     |  2 +
 erts/emulator/beam/jit/instr_arith.cpp  | 76 +++++++++++++++++++++++++
 erts/emulator/beam/jit/ops.tab          |  4 +-
 erts/emulator/test/float_SUITE.erl      | 19 ++++++-
 8 files changed, 207 insertions(+), 5 deletions(-)

diff --git a/erts/emulator/beam/erl_arith.c b/erts/emulator/beam/erl_arith.c
index 27a158b27d..fc0ec253fd 100644
--- a/erts/emulator/beam/erl_arith.c
+++ b/erts/emulator/beam/erl_arith.c
@@ -79,7 +79,7 @@ BIF_RETTYPE splus_2(BIF_ALIST_2)
 
 BIF_RETTYPE sminus_1(BIF_ALIST_1)
 {
-    BIF_RET(erts_mixed_minus(BIF_P, make_small(0), BIF_ARG_1));
+    BIF_RET(erts_unary_minus(BIF_P, BIF_ARG_1));
 } 
 
 BIF_RETTYPE sminus_2(BIF_ALIST_2)
@@ -461,6 +461,71 @@ erts_mixed_plus(Process* p, Eterm arg1, Eterm arg2)
     }
 }
 
+/*
+ * While "-value" is generally the same as "0 - value",
+ * that's not true for floats due to positive and negative
+ * zeros, so we implement unary minus as its own operation.
+ */
+Eterm
+erts_unary_minus(Process* p, Eterm arg)
+{
+    Eterm hdr, res;
+    FloatDef f;
+    dsize_t sz;
+    int need_heap;
+    Eterm* hp;
+    Sint ires;
+
+    ERTS_FP_CHECK_INIT(p);
+    switch (arg & _TAG_PRIMARY_MASK) {
+    case TAG_PRIMARY_IMMED1:
+        switch ((arg & _TAG_IMMED1_MASK) >> _TAG_PRIMARY_SIZE) {
+        case (_TAG_IMMED1_SMALL >> _TAG_PRIMARY_SIZE):
+            ires = -signed_val(arg);
+            if (IS_SSMALL(ires)) {
+                return make_small(ires);
+            } else {
+                hp = HeapFragOnlyAlloc(p, 2);
+                res = small_to_big(ires, hp);
+                return res;
+            }
+        default:
+        badarith:
+            p->freason = BADARITH;
+            return THE_NON_VALUE;
+        }
+    case TAG_PRIMARY_BOXED:
+        hdr = *boxed_val(arg);
+        switch ((hdr & _TAG_HEADER_MASK) >> _TAG_PRIMARY_SIZE) {
+        case (_TAG_HEADER_POS_BIG >> _TAG_PRIMARY_SIZE):
+        case (_TAG_HEADER_NEG_BIG >> _TAG_PRIMARY_SIZE): {
+            Eterm zero_buf[2] = {make_pos_bignum_header(1), 0};
+            Eterm zero = make_big(zero_buf);
+            sz = big_size(arg);
+            need_heap = BIG_NEED_SIZE(sz);
+            hp = HeapFragOnlyAlloc(p, need_heap);
+            res = big_minus(zero, arg, hp);
+            maybe_shrink(p, hp, res, need_heap);
+            ASSERT(is_not_nil(res));
+            return res;
+        }
+        case (_TAG_HEADER_FLOAT >> _TAG_PRIMARY_SIZE):
+            GET_DOUBLE(arg, f);
+            f.fd = -f.fd;
+            ERTS_FP_ERROR(p, f.fd, goto badarith);
+            hp = HeapFragOnlyAlloc(p, FLOAT_SIZE_OBJECT);
+            res = make_float(hp);
+            PUT_DOUBLE(f, hp);
+            return res;
+        default:
+            goto badarith;
+        }
+    default:
+        goto badarith;
+    }
+}
+
+
 Eterm
 erts_mixed_minus(Process* p, Eterm arg1, Eterm arg2)
 {
diff --git a/erts/emulator/beam/global.h b/erts/emulator/beam/global.h
index c8421849d4..f47347d7a5 100644
--- a/erts/emulator/beam/global.h
+++ b/erts/emulator/beam/global.h
@@ -1448,6 +1448,7 @@ Eterm collect_memory(Process *);
 void dump_memory_to_fd(int);
 int dump_memory_data(const char *);
 
+Eterm erts_unary_minus(Process* p, Eterm arg1);
 Eterm erts_mixed_plus(Process* p, Eterm arg1, Eterm arg2);
 Eterm erts_mixed_minus(Process* p, Eterm arg1, Eterm arg2);
 Eterm erts_mixed_times(Process* p, Eterm arg1, Eterm arg2);
diff --git a/erts/emulator/test/float_SUITE.erl b/erts/emulator/test/float_SUITE.erl
index 4098aa9c6a..4c450c4398 100644
--- a/erts/emulator/test/float_SUITE.erl
+++ b/erts/emulator/test/float_SUITE.erl
@@ -24,7 +24,7 @@
 
 -export([all/0, suite/0, groups/0,
          fpe/1,fp_drv/1,fp_drv_thread/1,denormalized/1,match/1,
-         t_mul_add_ops/1,
+         t_mul_add_ops/1,negative_zero/1,
          bad_float_unpack/1, write/1, cmp_zero/1, cmp_integer/1, cmp_bignum/1]).
 -export([otp_7178/1]).
 -export([hidden_inf/1]).
@@ -37,7 +37,7 @@ suite() ->
 all() -> 
     [fpe, fp_drv, fp_drv_thread, otp_7178, denormalized,
      match, bad_float_unpack, write, {group, comparison}
-     ,hidden_inf
+     ,hidden_inf, negative_zero
      ,arith, t_mul_add_ops].
 
 groups() -> 
@@ -56,6 +56,21 @@ otp_7178(Config) when is_list(Config) ->
     {'EXIT', {badarg,_}} = (catch list_to_float("1.0e83291083210")),
     ok.
 
+negative_zero(Config) when is_list(Config) ->
+    <<16#8000000000000000:64>> = do_negative_zero('-', [0.0]),
+    <<16#8000000000000000:64>> = do_negative_zero('*', [-1, 0.0]),
+    <<16#8000000000000000:64>> = do_negative_zero('*', [-1.0, 0.0]),
+    <<16#8000000000000000:64>> = do_negative_zero('*', [-1.0, 0]),
+    ok.
+
+do_negative_zero(Op, Ops) ->
+    Res = <<(my_apply(erlang, Op, Ops))/float>>,
+    Res = <<(case {Op, Ops} of
+                 {'-', [A]} -> -A;
+                 {'*', [A, B]} -> A * B
+             end)/float>>,
+    Res.
+
 %% Forces floating point exceptions and tests that subsequent, legal,
 %% operations are calculated correctly.  Original version by Sebastian
 %% Strollo.
-- 
2.26.2

openSUSE Build Service is sponsored by