Skip to content

Commit 62c2a75

Browse files
committed
Update after feedback
1 parent 5789f32 commit 62c2a75

File tree

1 file changed

+20
-17
lines changed

1 file changed

+20
-17
lines changed

lib/stdlib/src/rand.erl

Lines changed: 20 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -338,11 +338,15 @@ The current _default algorithm_ is
338338
[`exsss` (Xorshift116\*\*)](#algorithms). If a specific algorithm is
339339
required, ensure to always use `seed/1` to initialize the state.
340340

341-
Which algorithm that is the default may change between Erlang/OTP releases,
342-
and is selected to be one with high speed, small state and "good enough"
343-
statistical properties. So to ensure that the same sequence is reproduced
344-
on a later Erlang/OTP release, use a `seed/2` or `seed_s/2` to select
345-
both a specific algorithm and the seed value.
341+
In many API functions in this module, the atom `default` can be used
342+
instead of an algorithm name, and is currently an alias for `exsss`.
343+
In a future Erlang/OTP release this might be a different algorithm.
344+
The _default algorithm_ is selected to be one with high speed,
345+
small state and "good enough" statistical properties.
346+
347+
If it is essential to reproduce the same PRNG sequence
348+
on a later Erlang/OTP release, use `seed/2` or `seed_s/2`
349+
to select *both* a specific algorithm and the seed value.
346350

347351
#### Old Algorithms
348352

@@ -956,7 +960,7 @@ that has been implemented *(Since OTP 24.0)*.
956960
> #### Note {: .info }
957961
>
958962
> Using `Alg = default` is *not* perfectly predictable since
959-
> which algorithm that is the default may change in a future
963+
>`default` may be an alias for a different algorithm in a future
960964
> OTP release.
961965
""".
962966
-doc(#{group => <<"Plug-in framework API">>,since => <<"OTP 18.0">>}).
@@ -985,7 +989,7 @@ that has been implemented *since OTP 24.0*.
985989
> #### Note {: .info }
986990
>
987991
> Using `Alg = default` is *not* perfectly predictable since
988-
> which algorithm that is the default may change in a future
992+
>`default` may be an alias for a different algorithm in a future
989993
> OTP release.
990994
""".
991995
-doc(#{group => <<"Plug-in framework API">>,since => <<"OTP 18.0">>}).
@@ -1928,7 +1932,7 @@ shuffle_r([], Acc0, P0, S0, Zero, One, Two, Three) ->
19281932
{Acc3, P3, S3} = shuffle_r(Two, Acc2, P2, S2),
19291933
shuffle_r(Three, Acc3, P3, S3);
19301934
shuffle_r([X | L], Acc, P0, S, Zero, One, Two, Three)
1931-
when is_integer(P0), ?BIT(2) =< P0, P0 =< ?MASK(59) ->
1935+
when is_integer(P0, ?BIT(2), ?MASK(59)) ->
19321936
P1 = P0 bsr 2,
19331937
case ?MASK(2, P0) of
19341938
0 -> shuffle_r(L, Acc, P1, S, [X | Zero], One, Two, Three);
@@ -1942,7 +1946,7 @@ shuffle_r([_ | _] = L, Acc, _P, S0, Zero, One, Two, Three) ->
19421946

19431947
%% Permute 2 elements
19441948
shuffle_r_2(X, Acc, P, S, Y)
1945-
when is_integer(P), ?BIT(1) =< P, P =< ?MASK(59) ->
1949+
when is_integer(P, ?BIT(1), ?MASK(59)) ->
19461950
{case ?MASK(1, P) of
19471951
0 -> [Y, X | Acc];
19481952
1 -> [X, Y | Acc]
@@ -1957,7 +1961,7 @@ shuffle_r_2(X, Acc, _P, S0, Y) ->
19571961
%% to reject and retry, which on average is 3 * 4/3
19581962
%% (infinite sum of (1/4)^k) = 4 bits per permutation
19591963
shuffle_r_3(X, Acc, P0, S, Y, Z)
1960-
when is_integer(P0), ?BIT(3) =< P0, P0 =< ?MASK(59) ->
1964+
when is_integer(P0, ?BIT(3), ?MASK(59)) ->
19611965
P1 = P0 bsr 3,
19621966
case ?MASK(3, P0) of
19631967
0 -> {[Z, Y, X | Acc], P1, S};
@@ -1994,8 +1998,7 @@ shuffle_init_bitstream(R, Next, Shift, Mask0) ->
19941998
-dialyzer({no_improper_lists, shuffle_new_bits/1}).
19951999
%%
19962000
shuffle_new_bits([R0|{Next,Shift,Mask}=W])
1997-
when is_integer(Shift), 0 =< Shift, Shift =< 3,
1998-
is_integer(Mask), 0 < Mask, Mask =< ?MASK(58) ->
2001+
when is_integer(Shift, 0, 3), is_integer(Mask, 0, ?MASK(58)) ->
19992002
case Next(R0) of
20002003
{V, R1} when is_integer(V) ->
20012004
%% Setting the top bit here provides the marker
@@ -2986,7 +2989,7 @@ is 60% of the time for the default algorithm generating a `t:float/0`.
29862989
""".
29872990
-doc(#{group => <<"Niche algorithms API">>,since => <<"OTP 25.0">>}).
29882991
-spec mwc59(CX0 :: mwc59_state()) -> CX1 :: mwc59_state().
2989-
mwc59(CX) when is_integer(CX), 1 =< CX, CX < ?MWC59_P ->
2992+
mwc59(CX) when is_integer(CX, 1, ?MWC59_P-1) ->
29902993
C = CX bsr ?MWC59_B,
29912994
X = ?MASK(?MWC59_B, CX),
29922995
?MWC59_A * X + C.
@@ -3043,7 +3046,7 @@ that is: `(Range*V) bsr 32`, which is much faster than using `rem`.
30433046
""".
30443047
-doc(#{group => <<"Niche algorithms API">>,since => <<"OTP 25.0">>}).
30453048
-spec mwc59_value32(CX :: mwc59_state()) -> V :: 0..?MASK(32).
3046-
mwc59_value32(CX1) when is_integer(CX1), 1 =< CX1, CX1 < ?MWC59_P ->
3049+
mwc59_value32(CX1) when is_integer(CX1, 1, ?MWC59_P-1) ->
30473050
CX = ?MASK(32, CX1),
30483051
CX bxor ?BSL(32, CX, ?MWC59_XS).
30493052

@@ -3094,7 +3097,7 @@ adding up to 59 bits, which is not a bignum (on a 64-bit VM ):
30943097
CX1 = (CX0) bxor ?BSL(59, (CX0), ?MWC59_XS1),
30953098
CX1 bxor ?BSL(59, CX1, ?MWC59_XS2)
30963099
end).
3097-
mwc59_value(CX0) when is_integer(CX0), 1 =< CX0, CX0 < ?MWC59_P ->
3100+
mwc59_value(CX0) when is_integer(CX0, 1, ?MWC59_P-1) ->
30983101
?mwc59_value(CX0, CX1).
30993102

31003103
-doc """
@@ -3119,7 +3122,7 @@ The generator state is scrambled as with
31193122
""".
31203123
-doc(#{group => <<"Niche algorithms API">>,since => <<"OTP 25.0">>}).
31213124
-spec mwc59_float(CX :: mwc59_state()) -> V :: float().
3122-
mwc59_float(CX0) when is_integer(CX0), 1 =< CX0, CX0 < ?MWC59_P ->
3125+
mwc59_float(CX0) when is_integer(CX0, 1, ?MWC59_P-1) ->
31233126
?MASK(53, ?mwc59_value(CX0, CX1)) * ?TWO_POW_MINUS53.
31243127

31253128
-doc """
@@ -3167,7 +3170,7 @@ to avoid that similar seeds create similar sequences.
31673170
""".
31683171
-doc(#{group => <<"Niche algorithms API">>,since => <<"OTP 25.0">>}).
31693172
-spec mwc59_seed(S :: 0..?MASK(58)) -> CX :: mwc59_state().
3170-
mwc59_seed(S) when is_integer(S), 0 =< S, S =< ?MASK(58) ->
3173+
mwc59_seed(S) when is_integer(S, 0, ?MASK(58)) ->
31713174
hash58(S) + 1.
31723175

31733176
%% Constants a'la SplitMix64, MurMurHash, etc.

0 commit comments

Comments
 (0)