File 2075-erts-Fix-float_to_list-F-decimals-D.patch of Package erlang

From 9091e0fc630913999e3a51e860a2c4e07c6143c1 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Fri, 16 Mar 2018 19:34:42 +0100
Subject: [PATCH 1/2] erts: Fix float_to_list(F, [{decimals,D}])

to better conform with io_lib:format("~.*f", [D,F])
---
 erts/emulator/sys/common/erl_sys_common_misc.c | 184 +++++++++----------------
 erts/emulator/test/num_bif_SUITE.erl           |  25 ++++
 2 files changed, 91 insertions(+), 118 deletions(-)

diff --git a/erts/emulator/sys/common/erl_sys_common_misc.c b/erts/emulator/sys/common/erl_sys_common_misc.c
index 96bdbacb9e..826307c077 100644
--- a/erts/emulator/sys/common/erl_sys_common_misc.c
+++ b/erts/emulator/sys/common/erl_sys_common_misc.c
@@ -142,7 +142,16 @@ sys_double_to_chars(double fp, char *buffer, size_t buffer_size)
     return sys_double_to_chars_ext(fp, buffer, buffer_size, SYS_DEFAULT_FLOAT_DECIMALS);
 }
 
-/* Convert float to string using fixed point notation.
+
+#if SIZEOF_LONG == 8
+# define round_int64 lround
+#elif SIZEOF_LONG_LONG == 8
+# define round_int64 llround
+#else
+# error "No 64-bit integer type?"
+#endif
+
+/* Convert float to string
  *   decimals must be >= 0
  *   if compact != 0, the trailing 0's will be truncated
  */
@@ -154,80 +163,35 @@ sys_double_to_chars_fast(double f, char *buffer, int buffer_size, int decimals,
     #define FRAC_SIZE            52
     #define EXP_SIZE             11
     #define EXP_MASK             (((Uint64)1 << EXP_SIZE) - 1)
-    #define MAX_DECIMALS         (sizeof(cs_sys_double_pow10) \
-				   / sizeof(cs_sys_double_pow10[0]))
+    #define MAX_DECIMALS         (sizeof(pow10v) / sizeof(pow10v[0]))
     #define FRAC_MASK            (((Uint64)1 << FRAC_SIZE) - 1)
     #define FRAC_MASK2           (((Uint64)1 << (FRAC_SIZE + 1)) - 1)
     #define MAX_FLOAT            ((Uint64)1 << (FRAC_SIZE+1))
 
-    static const double cs_sys_double_pow10[] = {
-        SYS_DOUBLE_RND_CONST / 1e0,
-        SYS_DOUBLE_RND_CONST / 1e1,
-        SYS_DOUBLE_RND_CONST / 1e2,
-        SYS_DOUBLE_RND_CONST / 1e3,
-        SYS_DOUBLE_RND_CONST / 1e4,
-        SYS_DOUBLE_RND_CONST / 1e5,
-        SYS_DOUBLE_RND_CONST / 1e6,
-        SYS_DOUBLE_RND_CONST / 1e7,
-        SYS_DOUBLE_RND_CONST / 1e8,
-        SYS_DOUBLE_RND_CONST / 1e9,
-        SYS_DOUBLE_RND_CONST / 1e10,
-        SYS_DOUBLE_RND_CONST / 1e11,
-        SYS_DOUBLE_RND_CONST / 1e12,
-        SYS_DOUBLE_RND_CONST / 1e13,
-        SYS_DOUBLE_RND_CONST / 1e14,
-        SYS_DOUBLE_RND_CONST / 1e15,
-        SYS_DOUBLE_RND_CONST / 1e16,
-        SYS_DOUBLE_RND_CONST / 1e17,
-        SYS_DOUBLE_RND_CONST / 1e18
+    static const double pow10v[] = {
+        1e0,  1e1,  1e2,  1e3,  1e4,  1e5,  1e6,  1e7,  1e8, 1e9,
+        1e10, 1e11, 1e12, 1e13, 1e14, 1e15, 1e16, 1e17, 1e18
     };
 
-    Uint64 mantissa, int_part, frac_part;
-    int exp;
-    int fbits;
-    int max;
+    double af;
+    Uint64 int_part, frac_part;
     int neg;
-    double fr;
-    union { Uint64 L; double F; } x;
     char *p = buffer;
 
     if (decimals < 0)
         return -1;
 
-    if (f >= 0) {
-        neg = 0;
-        fr  = decimals < MAX_DECIMALS ? (f + cs_sys_double_pow10[decimals]) : f;
-        x.F = fr;
-    } else {
+    if (f < 0) {
         neg = 1;
-        fr  = decimals < MAX_DECIMALS ? (f - cs_sys_double_pow10[decimals]) : f;
-        x.F = -fr;
+        af = -f;
     }
-
-    exp      = (x.L >> FRAC_SIZE) & EXP_MASK;
-    mantissa = x.L & FRAC_MASK;
-
-    if (exp == EXP_MASK) {
-        if (mantissa == 0) {
-            if (neg)
-                *p++ = '-';
-            *p++ = 'i';
-            *p++ = 'n';
-            *p++ = 'f';
-        } else {
-            *p++ = 'n';
-            *p++ = 'a';
-            *p++ = 'n';
-        }
-        *p = '\0';
-        return p - buffer;
+    else {
+        neg = 0;
+        af = f;
     }
 
-    exp      -= EXP_MASK >> 1;
-    mantissa |= ((Uint64)1 << FRAC_SIZE);
-
     /* Don't bother with optimizing too large numbers or too large precision */
-    if (x.F > MAX_FLOAT || decimals >= MAX_DECIMALS) {
+    if (af > MAX_FLOAT || decimals >= MAX_DECIMALS) {
         int len = erts_snprintf(buffer, buffer_size, "%.*f", decimals, f);
         char* p = buffer + len;
         if (len >= buffer_size)
@@ -237,77 +201,61 @@ sys_double_to_chars_fast(double f, char *buffer, int buffer_size, int decimals,
             p = find_first_trailing_zero(p);
         *p = '\0';
         return p - buffer;
-    } else if (exp >= FRAC_SIZE) {
-        int_part  = mantissa << (exp - FRAC_SIZE);
-        frac_part = 0;
-        fbits = FRAC_SIZE;  /* not important as frac_part==0 */
-    } else if (exp >= 0) {
-        fbits = FRAC_SIZE - exp;
-        int_part  = mantissa >> fbits;
-        frac_part = mantissa & (((Uint64)1 << fbits) -1);
-    } else /* if (exp < 0) */ {
-        int_part = 0;
-        frac_part = mantissa;
-        fbits = FRAC_SIZE - exp;
-    }
-
-    if (!int_part) {
-        if (neg)
-            *p++ = '-';
-        *p++ = '0';
-    } else {
-        int ret, i, n;
-        while (int_part != 0) {
-            *p++ = (char)((int_part % 10) + '0');
-            int_part /= 10;
-        }
-        if (neg)
-            *p++ = '-';
-        /* Reverse string */
-        ret = p - buffer;
-        for (i = 0, n = ret/2; i < n; i++) {
-            int  j = ret - i - 1;
-            char c = buffer[i];
-            buffer[i] = buffer[j];
-            buffer[j] = c;
-        }
     }
 
-    if (decimals > 0) {
-        int i;
-        *p++ = '.';
+    if (decimals) {
+        double int_f = floor(af);
+        double frac_f = round((af - int_f) * pow10v[decimals]);
 
-        max = buffer_size - (p - buffer) - 1 /* leave room for trailing '\0' */;
+        int_part = (Uint64)int_f;
+        frac_part = (Uint64)frac_f;
 
-        if (decimals > max)
-            return -1;  /* the number is not large enough to fit in the buffer */
-
-        max = decimals;
+        if (frac_f >= pow10v[decimals]) {
+            /* rounding overflow carry into int_part */
+            int_part++;
+            frac_part = 0;
+        }
 
-        for (i = 0; i < max; i++) {
-            if (frac_part > (ERTS_UINT64_MAX/5)) {
-                frac_part >>= 3;
-                fbits -= 3;
+        do {
+            if (!frac_part) {
+                do {
+                    *p++ = '0';
+                } while (--decimals);
+                break;
             }
+            *p++ = (char)((frac_part % 10) + '0');
+            frac_part /= 10;
+        } while (--decimals);
 
-            /* Multiply by 10 (5*2) to extract decimal digit as integer part */
-            frac_part *= 5;
-            fbits--;
+        *p++ = '.';
+    }
+    else
+        int_part = (Uint64)round_int64(af);
 
-            if (fbits >= 64) {
-                *p++ = '0';
-            }
-            else {
-                *p++ = (char)((frac_part >> fbits) + '0');
-                frac_part &= ((Uint64)1 << fbits) - 1;
-            }
+    if (!int_part) {
+        *p++ = '0';
+    } else {
+        do {
+            *p++ = (char)((int_part % 10) + '0');
+            int_part /= 10;
+        }while (int_part);
+    }
+    if (neg)
+        *p++ = '-';
+
+    {/* Reverse string */
+        int i = 0;
+        int j = p - buffer - 1;
+        for ( ; i < j; i++, j--) {
+            char tmp = buffer[i];
+            buffer[i] = buffer[j];
+            buffer[j] = tmp;
         }
-
-        /* Delete trailing zeroes */
-        if (compact)
-            p = find_first_trailing_zero(p);
     }
 
+    /* Delete trailing zeroes */
+    if (compact)
+        p = find_first_trailing_zero(p);
     *p = '\0';
     return p - buffer;
 }
diff --git a/erts/emulator/test/num_bif_SUITE.erl b/erts/emulator/test/num_bif_SUITE.erl
index 592542405f..104bd37817 100644
--- a/erts/emulator/test/num_bif_SUITE.erl
+++ b/erts/emulator/test/num_bif_SUITE.erl
@@ -213,6 +213,20 @@ fts_rand_float_decimals(N) ->
     [begin
          F0 = rand_float_reasonable(),
          L0 = float_to_list(F0, [{decimals, D}]),
+         case conform_with_io_lib_format(F0,D) of
+             false -> ok;
+             true ->
+                 IOL = lists:flatten(io_lib:format("~.*f", [D, F0])),
+                 true = case L0 =:= IOL of
+                            true -> true;
+                            false ->
+                                io:format("F0 = ~w ~w\n",  [F0, <<F0/float>>]),
+                                io:format("decimals = ~w\n",  [D]),
+                                io:format("float_to_list = ~s\n",  [L0]),
+                                io:format("io_lib:format = ~s\n",  [IOL]),
+                                false
+                        end
+         end,
          L1 = case D of
                   0 -> L0 ++ ".0";
                   _ -> L0
@@ -234,6 +248,17 @@ fts_rand_float_decimals(N) ->
 
     fts_rand_float_decimals(N-1).
 
+conform_with_io_lib_format(_, 0) ->
+    %% io_lib:format("~.*f") does not support zero decimals
+    false;
+conform_with_io_lib_format(_, D) when D > 10 ->
+    %% Seems float_to_list gets it slightly wrong sometimes for many decimals
+    false;
+conform_with_io_lib_format(F, D) ->
+    %% io_lib:format prints '0' for input bits beyond mantissa precision
+    %% float_to_list treats those unknown input bits as if they were zeros.
+    math:log2(abs(F) * math:pow(10,D)) < 54.
+
 max_diff_decimals(F, D) ->
     IntBits = floor(math:log2(abs(F))) + 1,
     FracBits = (52 - IntBits),
-- 
2.16.3

openSUSE Build Service is sponsored by