File 2472-Benchmark-for-io_lib_format-fwrite_g-1-for-doubles-t.patch of Package erlang

From e71ce6ee01de76ce60a1a684f127cd361eb0fbde Mon Sep 17 00:00:00 2001
From: Thomas Depierre <depierre.thomas@gmail.com>
Date: Mon, 18 Jan 2021 16:07:49 +0100
Subject: [PATCH 2/2] Benchmark for io_lib_format:fwrite_g/1 for doubles that
 round-trip to a string with a low number of digits.

This is done in preparation for moving this function to the Ryu
algorithm, which historically has performance problems with these.
---
 lib/stdlib/test/stdlib_bench_SUITE.erl | 48 ++++++++++++++++++++------
 1 file changed, 37 insertions(+), 11 deletions(-)

diff --git a/lib/stdlib/test/stdlib_bench_SUITE.erl b/lib/stdlib/test/stdlib_bench_SUITE.erl
index 713c614ec2..f2a35e733c 100644
--- a/lib/stdlib/test/stdlib_bench_SUITE.erl
+++ b/lib/stdlib/test/stdlib_bench_SUITE.erl
@@ -284,26 +284,52 @@ mbb(N, Acc) ->
 
 -define(MAX_DOUBLE, (1 bsl 62) - 1).
 -define(DOUBLE_SAMPLE, 10000).
+-define(SMALL_DIGITS, 6).
 
 double_random_to_list(_Config) ->
-    comment(test_double(io_lib_format, fwrite_g)).
+    comment(test_double(io_lib_format, fwrite_g, 0)).
 
-double() ->
+double_small_digit_to_list(_Config) ->
+    comment(test_double(io_lib_format, fwrite_g, ?SMALL_DIGITS)).
+
+double(0) ->
     Int = rand:uniform(?MAX_DOUBLE),
     <<F:64/float>> = <<Int:64/unsigned-integer>>,
-    F.
+    F;
+% Example:
+% SmallDigits is 3
+% Lower is 100
+% Upper is 1000
+% R % (1000 - 100) + 100;
+% R % 900 + 100;
+% R1 is [0, 899] + 100
+% R1 is [100, 999]
+% R1 / 100 is [1.00, 9.99]
+double(SmallDigits) ->
+    F = double(0),
+    Lower = exp10(SmallDigits),
+    Upper = Lower * 10,
+    F1 = (F rem (Upper - Lower)) + Lower,
+    F1 / float(Lower).
+
+exp10(X) ->
+    exp10(1, X).
+exp10(Acc, 0) ->
+    Acc;
+exp10(Acc, X) ->
+    exp10(Acc, X - 1).
 
-test_double(Mod, Fun) ->
-    test_double(?DOUBLE_SAMPLE, Mod, Fun).
-test_double(Iter, Mod, Fun) ->
-    F = fun() -> loop_double(Iter, Mod, Fun) end,
+test_double(Mod, Fun, SmallDigits) ->
+    test_double(?DOUBLE_SAMPLE, Mod, Fun, SmallDigits).
+test_double(Iter, Mod, Fun, SmallDigits) ->
+    F = fun() -> loop_double(Iter, Mod, Fun, SmallDigits) end,
     {Time, ok} = timer:tc(fun() -> lspawn(F) end),
     report_mfa(Iter, Time, Mod).
 
-loop_double(0, _M, _F) -> garbage_collect(), ok;
-loop_double(N, M, F) ->
-    _ = apply(M, F, [double()]),
-    loop_double(N - 1, M, F).
+loop_double(0, _M, _F, _SmallDigits) -> garbage_collect(), ok;
+loop_double(N, M, F, SmallDigits) ->
+    _ = apply(M, F, [double(SmallDigits)]),
+    loop_double(N - 1, M, F, SmallDigits).
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-- 
2.26.2

openSUSE Build Service is sponsored by