Skip to content

Commit ac2129f

Browse files
committed
Revert "Try the speed of mwc59 in particular for shuffle"
This reverts commit 7a0c4af.
1 parent c879505 commit ac2129f

File tree

2 files changed

+14
-71
lines changed

2 files changed

+14
-71
lines changed

lib/stdlib/src/rand.erl

Lines changed: 12 additions & 69 deletions
Original file line numberDiff line numberDiff line change
@@ -2056,11 +2056,6 @@ mk_alg(exro928ss) ->
20562056
uniform_n=>fun exro928ss_uniform/2,
20572057
jump=>fun exro928_jump/1},
20582058
fun exro928_seed/1};
2059-
mk_alg(mwc59) ->
2060-
{#{type=>mwc59, bits=>58, next=>fun mwc59_plugin_next/1,
2061-
uniform=>fun mwc59_plugin_uniform/1,
2062-
uniform_n=>fun mwc59_plugin_uniform/2},
2063-
fun mwc59_plugin_seed/1};
20642059
mk_alg(dummy=Name) ->
20652060
{#{type=>Name, bits=>58, next=>fun dummy_next/1,
20662061
uniform=>fun dummy_uniform/1,
@@ -2991,15 +2986,10 @@ is 60% of the time for the default algorithm generating a `t:float/0`.
29912986
""".
29922987
-doc(#{group => <<"Niche algorithms API">>,since => <<"OTP 25.0">>}).
29932988
-spec mwc59(CX0 :: mwc59_state()) -> CX1 :: mwc59_state().
2994-
-define(
2995-
mwc59(CX, C, X),
2996-
begin
2997-
C = (CX) bsr ?MWC59_B,
2998-
X = ?MASK(?MWC59_B, (CX)),
2999-
?MWC59_A * X + C
3000-
end).
30012989
mwc59(CX) when is_integer(CX), 1 =< CX, CX < ?MWC59_P ->
3002-
?mwc59(CX, C, X).
2990+
C = CX bsr ?MWC59_B,
2991+
X = ?MASK(?MWC59_B, CX),
2992+
?MWC59_A * X + C.
30032993

30042994
%%% %% Verification by equivalent MCG generator
30052995
%%% mwc59_r(CX1) ->
@@ -3099,10 +3089,10 @@ adding up to 59 bits, which is not a bignum (on a 64-bit VM ):
30993089
-doc(#{group => <<"Niche algorithms API">>,since => <<"OTP 25.0">>}).
31003090
-spec mwc59_value(CX :: mwc59_state()) -> V :: 0..?MASK(59).
31013091
-define(
3102-
mwc59_value(CX0, Tmp),
3092+
mwc59_value(CX0, CX1),
31033093
begin
3104-
Tmp = (CX0) bxor ?BSL(59, (CX0), ?MWC59_XS1),
3105-
Tmp bxor ?BSL(59, Tmp, ?MWC59_XS2)
3094+
CX1 = (CX0) bxor ?BSL(59, (CX0), ?MWC59_XS1),
3095+
CX1 bxor ?BSL(59, CX1, ?MWC59_XS2)
31063096
end).
31073097
mwc59_value(CX0) when is_integer(CX0), 1 =< CX0, CX0 < ?MWC59_P ->
31083098
?mwc59_value(CX0, CX1).
@@ -3151,8 +3141,11 @@ just like [`seed_s(atom())`](`seed_s/1`).
31513141
-doc(#{group => <<"Niche algorithms API">>,since => <<"OTP 25.0">>}).
31523142
-spec mwc59_seed() -> CX :: mwc59_state().
31533143
mwc59_seed() ->
3154-
mwc59_plugin_seed(default_seed()).
3155-
3144+
{A1, A2, A3} = default_seed(),
3145+
X1 = hash58(A1),
3146+
X2 = hash58(A2),
3147+
X3 = hash58(A3),
3148+
(X1 bxor X2 bxor X3) + 1.
31563149

31573150
-doc """
31583151
Create a [MWC59 generator state](`t:mwc59_state/0`).
@@ -3177,57 +3170,6 @@ to avoid that similar seeds create similar sequences.
31773170
mwc59_seed(S) when is_integer(S), 0 =< S, S =< ?MASK(58) ->
31783171
hash58(S) + 1.
31793172

3180-
3181-
%% -------
3182-
3183-
mwc59_plugin_seed([]) ->
3184-
erlang:error(zero_seed);
3185-
mwc59_plugin_seed([S]) ->
3186-
if
3187-
is_integer(S) ->
3188-
case ?MASK(59, S) of
3189-
0 ->
3190-
erlang:error(zero_seed);
3191-
R ->
3192-
R
3193-
end;
3194-
true ->
3195-
erlang:error(non_integer_seed)
3196-
end;
3197-
mwc59_plugin_seed([_ | _]) ->
3198-
erlang:error(too_many_seed_integers);
3199-
%%
3200-
mwc59_plugin_seed(S) when is_integer(S) ->
3201-
hash58(S) + 1;
3202-
%%
3203-
mwc59_plugin_seed({A1, A2, A3}) ->
3204-
X1 = hash58(A1),
3205-
X2 = hash58(A2),
3206-
X3 = hash58(A3),
3207-
(X1 bxor X2 bxor X3) + 1.
3208-
3209-
mwc59_plugin_next(CX0)
3210-
when is_integer(CX0), 1 =< CX0, CX0 < ?MWC59_P ->
3211-
CX1 = ?mwc59(CX0, C, X),
3212-
V = ?MASK(58, ?mwc59_value(CX1, Tmp)),
3213-
{V, CX1}.
3214-
3215-
mwc59_plugin_uniform({AlgHandler, CX0})
3216-
when is_integer(CX0), 1 =< CX0, CX0 < ?MWC59_P ->
3217-
CX1 = ?mwc59(CX0, C, X),
3218-
V = ?MASK(53, ?mwc59_value(CX1, Tmp)) * ?TWO_POW_MINUS53,
3219-
{V, {AlgHandler, CX1}}.
3220-
3221-
mwc59_plugin_uniform(Range, {AlgHandler, CX0})
3222-
when is_integer(Range), 0 < Range,
3223-
is_integer(CX0), 1 =< CX0, CX0 < ?MWC59_P ->
3224-
CX1 = ?mwc59(CX0, C, X),
3225-
V = ?MASK(58, ?mwc59_value(CX1, Tmp)),
3226-
MaxMinusRange = ?BIT(58) - Range,
3227-
?uniform_range(Range, AlgHandler, CX1, V, MaxMinusRange, I).
3228-
3229-
%% -------
3230-
32313173
%% Constants a'la SplitMix64, MurMurHash, etc.
32323174
%% Not that critical, just mix the bits using bijections
32333175
%% (reversible mappings) to not have any two user input seeds
@@ -3239,6 +3181,7 @@ hash58(X) ->
32393181
X2 = ?MASK(58, (X1 bxor (X1 bsr 29)) * 16#0ceb9fe1a85ec53),
32403182
X2 bxor (X2 bsr 29).
32413183

3184+
32423185
%% =====================================================================
32433186
%% Mask and fill state list, ensure not all zeros
32443187
%% =====================================================================

lib/stdlib/test/rand_SUITE.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -112,7 +112,7 @@ test() ->
112112
end, Tests).
113113

114114
algs() ->
115-
[exsss, exrop, exsp, mwc59, exs1024s, exs64, exsplus, exs1024, exro928ss].
115+
[exsss, exrop, exsp, exs1024s, exs64, exsplus, exs1024, exro928ss].
116116

117117
crypto_support() ->
118118
try crypto:strong_rand_bytes(1) of
@@ -538,7 +538,7 @@ measure_shuffle(Config) when is_list(Config) ->
538538
end;
539539
measure_shuffle(Effort) when is_integer(Effort) ->
540540
Algs =
541-
[exsss, mwc59, exs1024 |
541+
[exsss, exs1024 |
542542
case crypto_support() of
543543
ok -> [crypto];
544544
_ -> []

0 commit comments

Comments
 (0)