File 2963-Change-the-fast-scrambler-to-return-32-bits.patch of Package erlang
From 321fb73053988180661e032e99fd08c2aec043f4 Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Tue, 10 May 2022 15:55:30 +0200
Subject: [PATCH 3/8] Change the fast scrambler to return 32 bits
It is no point in returning more, since the high bits of the 32
are the best, so multiply-and-shift is the preferred way of
generating in a small range anyway.
The bits above 32 bits could have been valuable if range capping
would be done with `rem`, but that is only a good idea if it
had been the low bits that were the better...
---
lib/stdlib/doc/src/rand.xml | 69 ++++++++++++++----------------
lib/stdlib/src/rand.erl | 10 ++---
lib/stdlib/test/rand_SUITE.erl | 76 ++++++++--------------------------
3 files changed, 53 insertions(+), 102 deletions(-)
diff --git a/lib/stdlib/doc/src/rand.xml b/lib/stdlib/doc/src/rand.xml
index 10e2133720..7eb6a164c8 100644
--- a/lib/stdlib/doc/src/rand.xml
+++ b/lib/stdlib/doc/src/rand.xml
@@ -917,14 +917,13 @@ end.</pre>
the generator state.
</p>
<p>
- To create an output value, the state should be scrambled.
+ To create an output value, the quality improves much
+ if the state is scrambled.
Function
- <seemfa marker="#mwc59_fast_value/1">
- <c>mwc59_fast_value</c>
+ <seemfa marker="#mwc59_value32/1">
+ <c>mwc59_value32</c>
</seemfa>
- is a fast scrambler that returns a 59-bit number with
- 32 decent bits, but still some problems in 2- and
- 3-dimensional collision tests show through.
+ is a fast scrambler that returns a decent 32-bit number.
The slightly slower
<seemfa marker="#mwc59_value/1">
<c>mwc59_value</c>
@@ -933,6 +932,15 @@ end.</pre>
<seemfa marker="#mwc59_float/1"><c>mwc59_float</c></seemfa>
returns a <c>float()</c> of very good quality.
</p>
+ <p>
+ The low bits of the base generator are surprisingly good,
+ so the lowest 16 bits actually passes fairly strict PRNG tests,
+ despite the generator's weaknesses that lies in the high
+ bits of the 32-bit MWC "digit". It is recommended
+ to use <c>rem</c> on the the generator state,
+ or bit mask on the lowest bits to produce numbers
+ in a range 16 bits or less.
+ </p>
<p>
On a typical 64 bit Erlang VM this generator executes
in below 8% (1/13) of the time
@@ -941,8 +949,8 @@ end.</pre>
plug-in framework API
</seeerl>
of this module. With the
- <seemfa marker="#mwc59_fast_value/1">
- <c>mwc59_fast_value</c>
+ <seemfa marker="#mwc59_value32/1">
+ <c>mwc59_value32</c>
</seemfa>
scrambler the total time becomes 16% (1/6),
and with
@@ -970,41 +978,31 @@ end.</pre>
</desc>
</func>
<func>
- <name name="mwc59_fast_value" arity="1" since="OTP 25.0"/>
+ <name name="mwc59_value32" arity="1" since="OTP 25.0"/>
<fsummary>Return the generator value.</fsummary>
<desc>
<p>
- Returns a 59-bit value <c><anno>V</anno></c>
+ Returns a 32-bit value <c><anno>V</anno></c>
from a generator state <c><anno>CX</anno></c>.
The generator state is scrambled using
an 8-bit xorshift which masks
the statistical imperfecions of the base generator
<seemfa marker="#mwc59/1"><c>mwc59</c></seemfa>
- enough that the 32 low bits are of decent quality.
- </p>
- <p>
- Be careful to not accidentaly create a bignum
- when handling the value <c><anno>V</anno></c>.
+ enough to produce numbers of decent quality.
+ Still some problems in 2- and 3-dimensional
+ birthday spacing and collision tests show through.
</p>
<p>
To extract a power of two number it is recommended
- to use the high of the decent 32 bits.
- </p>
- <p>
- For an arbitrary range less than 32 bits
- a <c>rem</c> operation on the whole value can be used,
- but that is a rather slow operation.
+ to use the high bits which helps in hiding
+ the remaining base generator problems.
</p>
<p>
For a small arbitrary range less than about 16 bits
(to not get too much bias and to avoid bignums)
multiply-and-shift can be used,
which is much faster than using <c>rem</c>:
- <c>(Range*(<anno>V</anno> band ((1 bsl 32)-1))) bsr 32</c>.
- </p>
- <p>
- It is not recommended to generate numbers
- in a range > 2^32 with this function.
+ <c>(Range*<anno>V</anno>) bsr 32</c>.
</p>
</desc>
</func>
@@ -1026,25 +1024,18 @@ end.</pre>
when handling the value <c><anno>V</anno></c>.
</p>
<p>
- To extract a power of two number it is recommended
- to shift down the high bits.
- </p>
- <p>
- For an arbitrary range a <c>rem</c> operation
- on the whole value can be used but that is
- a rather slow operation. Beware of bias
- in the generated numbers if generating in a range
- above about 2^30 (getting too close to 2^59).
+ To extract a power of two number it is slightly better
+ to shift down the high bits than to mask the low.
</p>
<p>
- For a small arbitrary range less than about 20 bits
+ For an arbitrary range less than about 29 bits
(to not get too much bias and to avoid bignums)
multiply-and-shift can be used,
which is much faster than using <c>rem</c>.
- Example for range 1000000;
- the range is 20 bits, we use 39 bits from the generator,
+ Example for range 1'000'000'000;
+ the range is 30 bits, we use 29 bits from the generator,
adding up to 59 bits, which is not a bignum:
- <c>(1000000 * (<anno>V</anno> bsr (59-39))) bsr 39</c>.
+ <c>(1000000000 * (<anno>V</anno> bsr (59-29))) bsr 29</c>.
<em>
</em>
</p>
diff --git a/lib/stdlib/src/rand.erl b/lib/stdlib/src/rand.erl
index 95fb011160..14e4f7eb74 100644
--- a/lib/stdlib/src/rand.erl
+++ b/lib/stdlib/src/rand.erl
@@ -38,7 +38,7 @@
%% Utilities
-export([exsp_next/1, exsp_jump/1, splitmix64_next/1,
- mwc59/1, mwc59_fast_value/1, mwc59_value/1, mwc59_float/1,
+ mwc59/1, mwc59_value32/1, mwc59_value/1, mwc59_float/1,
mwc59_seed/0, mwc59_seed/1]).
%% Test, dev and internal
@@ -1520,10 +1520,10 @@ mwc59(CX0) -> % when is_integer(CX0), 1 =< CX0, CX0 < ?MWC59_P ->
%%% CX0 = mwc59_r(CX1),
%%% mwc59(CX1, N - 1).
--spec mwc59_fast_value(CX :: mwc59_state()) -> V :: 0..?MASK(59).
-mwc59_fast_value(CX1) -> % when is_integer(CX1), 1 =< CX1, CX1 < ?MWC59_P ->
- CX = ?MASK(59, CX1),
- CX bxor ?BSL(59, CX, ?MWC59_XS).
+-spec mwc59_value32(CX :: mwc59_state()) -> V :: 0..?MASK(32).
+mwc59_value32(CX1) -> % when is_integer(CX1), 1 =< CX1, CX1 < ?MWC59_P ->
+ CX = ?MASK(32, CX1),
+ CX bxor ?BSL(32, CX, ?MWC59_XS).
-spec mwc59_value(CX :: mwc59_state()) -> V :: 0..?MASK(59).
mwc59_value(CX1) -> % when is_integer(CX1), 1 =< CX1, CX1 < ?MWC59_P ->
diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl
index 34da9c25a9..e84689ea69 100644
--- a/lib/stdlib/test/rand_SUITE.erl
+++ b/lib/stdlib/test/rand_SUITE.erl
@@ -230,8 +230,8 @@ mwc59_api(Config) when is_list(Config) ->
mwc59_api(CX0, 0) ->
CX = 394988924775693874,
{CX, CX} = {CX0, CX},
- V0 = rand:mwc59_fast_value(CX0),
- V = 446733510867799090,
+ V0 = rand:mwc59_value32(CX0),
+ V = 3767127090,
{V, V} = {V0, V},
W0 = rand:mwc59_value(CX0),
W = 418709302640385298,
@@ -242,11 +242,11 @@ mwc59_api(CX0, 0) ->
ok;
mwc59_api(CX, N)
when is_integer(CX), 1 =< CX, CX < (16#7fa6502 bsl 32) - 1 ->
- V = rand:mwc59_fast_value(CX),
+ V = rand:mwc59_value32(CX),
W = rand:mwc59_value(CX),
F = rand:mwc59_float(CX),
true = 0 =< V,
- true = V < 1 bsl 59,
+ true = V < 1 bsl 32,
true = 0 =< W,
true = W < 1 bsl 59,
true = 0.0 =< F,
@@ -1136,21 +1136,6 @@ do_measure(Iterations) ->
end,
{mwc59,raw_mod}, Iterations,
TMarkUniformRange10000, OverheadUniformRange1000),
- _ =
- measure_1(
- fun (_Mod, _State) ->
- Range = 10000,
- fun (St0) ->
- St1 = rand:mwc59(St0),
- %% Just a 'rem' with slightly skewed distribution
- case (rand:mwc59_fast_value(St1) rem Range) + 1 of
- R when is_integer(R), 0 < R, R =< Range ->
- St1
- end
- end
- end,
- {mwc59,fast_mod}, Iterations,
- TMarkUniformRange10000, OverheadUniformRange1000),
_ =
measure_1(
fun (_Mod, _State) ->
@@ -1187,31 +1172,9 @@ do_measure(Iterations) ->
Range = 10000,
fun (St0) ->
St1 = rand:mwc59(St0),
- %% Fixpoint inversion, slightly skewed
- case
- ( (Range * ((St1 band ((1 bsl 32)-1))))
- bsr 32 )
- + 1
- of
- R when is_integer(R), 0 < R, R =< Range ->
- St1
- end
- end
- end,
- {mwc59,raw_mas}, Iterations,
- TMarkUniformRange10000, OverheadUniformRange1000),
- _ =
- measure_1(
- fun (_Mod, _State) ->
- Range = 10000,
- fun (St0) ->
- St1 = rand:mwc59(St0),
- %% Fixpoint inversion, slightly skewed
+ %% Multiply-and-shift, slightly skewed
case
- ( (Range *
- ((rand:mwc59_fast_value(St1)
- band ((1 bsl 32)-1) )) )
- bsr 32 )
+ ((Range * rand:mwc59_value32(St1)) bsr 32)
+ 1
of
R when is_integer(R), 0 < R, R =< Range ->
@@ -1227,7 +1190,7 @@ do_measure(Iterations) ->
Range = 10000, % 14 bits
fun (St0) ->
St1 = rand:mwc59(St0),
- %% Fixpoint inversion, slightly skewed
+ %% Multiply-and-shift, slightly skewed
case
( (Range *
(rand:mwc59_value(St1) bsr 14) )
@@ -1247,7 +1210,7 @@ do_measure(Iterations) ->
Range = 10000,
fun (St0) ->
{V,St1} = rand:exsp_next(St0),
- %% Fixpoint inversion, slightly skewed
+ %% Multiply-and-shift, slightly skewed
case
((Range * (V bsr 14)) bsr (58-14)) + 1
of
@@ -1322,16 +1285,13 @@ do_measure(Iterations) ->
Range = 1 bsl 32,
fun (St0) ->
St1 = rand:mwc59(St0),
- case
- rand:mwc59_fast_value(St1)
- band ((1 bsl 32)-1)
- of
+ case rand:mwc59_value32(St1) of
R when is_integer(R), 0 =< R, R < Range ->
St1
end
end
end,
- {mwc59,fast_mask}, Iterations,
+ {mwc59,fast}, Iterations,
TMarkUniform32Bit, OverheadUniform32Bit),
_ =
measure_1(
@@ -1460,10 +1420,10 @@ do_measure(Iterations) ->
_ =
measure_1(
fun (_Mod, _State) ->
- Range = (1 bsl 59) - 1,
+ Range = (1 bsl 32) - 1,
fun (St0) ->
St1 = rand:mwc59(St0),
- V = rand:mwc59_fast_value(St1),
+ V = rand:mwc59_value32(St1),
if
is_integer(V), 0 =< V, V =< Range ->
St1
@@ -1882,19 +1842,19 @@ mwc59_bytes(N, R0, Bin) when is_integer(N), 7*4 =< N ->
R3 = rand:mwc59(R2),
R4 = rand:mwc59(R3),
Shift = 59 - 56,
- V1 = rand:mwc59_fast_value(R1) bsr Shift,
- V2 = rand:mwc59_fast_value(R2) bsr Shift,
- V3 = rand:mwc59_fast_value(R3) bsr Shift,
- V4 = rand:mwc59_fast_value(R4) bsr Shift,
+ V1 = rand:mwc59_value(R1) bsr Shift,
+ V2 = rand:mwc59_value(R2) bsr Shift,
+ V3 = rand:mwc59_value(R3) bsr Shift,
+ V4 = rand:mwc59_value(R4) bsr Shift,
mwc59_bytes(N-7*4, R4, <<Bin/binary, V1:56, V2:56, V3:56, V4:56>>);
mwc59_bytes(N, R0, Bin) when is_integer(N), 7 =< N ->
R1 = rand:mwc59(R0),
- V = rand:mwc59_fast_value(R1) bsr (59-56),
+ V = rand:mwc59_value(R1) bsr (59-56),
mwc59_bytes(N-7, R1, <<Bin/binary, V:56>>);
mwc59_bytes(N, R0, Bin) when is_integer(N), 0 < N ->
R1 = rand:mwc59(R0),
Bits = N bsl 3,
- V = rand:mwc59_fast_value(R1) bsr (59-Bits),
+ V = rand:mwc59_value(R1) bsr (59-Bits),
{<<Bin/binary, V:Bits>>, R1};
mwc59_bytes(0, R0, Bin) ->
{Bin, R0}.
--
2.35.3