330330 get_test_engine /0 ]).
331331-export ([rand_plugin_aes_jump_2pow20 /1 ]).
332332
333- -deprecated ({rand_uniform , 2 , " use rand:uniform/1 instead" }).
333+ -deprecated (
334+ {rand_uniform , 2 ,
335+ " use rand_seed_s/0 with rand:uniform_s/2 instead" }).
334336
335337% % This should correspond to the similar macro in crypto.c
336338-define (MAX_BYTES_TO_NIF , 20000 ). % % Current value is: erlang:system_info(context_reductions) * 10
@@ -2024,48 +2026,64 @@ strong_rand_bytes_nif(_Bytes) -> ?nif_stub.
20242026
20252027
20262028-doc """
2027- Create a state object for [random number generation](`m:rand`), in order to
2028- generate cryptographically strong random numbers (based on OpenSSL's
2029- `BN_rand_range`) .
2029+ Equivalent to `rand_seed_s/0` but also saves the returned
2030+ state object (generator) in the process dictionary. That is,
2031+ it is equivalent to `rand:seed(rand_seed_s())` .
20302032
2031- Saves the state in the process dictionary before returning it as
2032- well. See also `rand:seed/1` and `rand_seed_s/0`.
2033+ See `rand:seed/1` and `rand_seed_s/0`.
20332034
2034- When using the state object from this function the `m:rand` functions using it
2035- may raise exception `error:low_entropy` in case the random generator failed due
2036- to lack of secure "randomness".
2037-
2038- _Example_
2035+ #### _Example_
20392036
20402037```erlang
20412038_ = crypto:rand_seed(),
2042- _IntegerValue = rand:uniform(42), % [1; 42]
2043- _FloatValue = rand:uniform(). % [0.0; 1.0[
2039+ IntegerValue = rand:uniform(42), % [1; 42]
2040+ FloatValue = rand:uniform(). % [0.0; 1.0[
20442041```
2042+
2043+ > ### Note {: .info }
2044+ >
2045+ > Note that when using the process dictionary for cryptographically
2046+ > secure random numbers one has to ensure that no code called
2047+ > between initializing the generator and between generating numbers
2048+ > accidentally alters the generator state in the process dictionary.
2049+ >
2050+ > The safe approach is to use the `m:rand` functions that
2051+ > don't use the process dictionary but take an explicit state argument;
2052+ > the ones suffixed `_s`. And thereby it is rather `rand_seed_s/0`
2053+ > that should be used instead of this function.
20452054""" .
2055+
20462056-doc (#{group => <<" Random API" >>,
20472057 since => <<" OTP 20.0" >>}).
20482058-spec rand_seed () -> rand :state ().
20492059rand_seed () ->
20502060 rand :seed (rand_seed_s ()).
20512061
20522062-doc """
2053- Create a state object for [random number generation](`m:rand`), in order to
2054- generate cryptographically strongly random numbers (based on OpenSSL's
2055- `BN_rand_range`). See also `rand:seed_s/1`.
2063+ Create a state object (generator) for [random number generation](`m:rand`),
2064+ which when used by the `m:rand` functions produce
2065+ cryptographically strong random numbers (based on OpenSSL's
2066+ `BN_rand_range` function). See also `rand:seed_s/1`, and for example
2067+ `rand:uniform_s/2`.
20562068
2057- When using the state object from this function the `m:rand` functions using it
2058- may raise exception `error:low_entropy` in case the random generator failed due
2059- to lack of secure "randomness".
2069+ #### _Example_
2070+
2071+ ``` erlang
2072+ S0 = crypto:rand_seed_s(),
2073+ {RandomInteger, S1} = rand:uniform_s(1000, S0).
2074+ ```
2075+
2076+ May cause the `m:rand` functions using this state object
2077+ to raise the exception `error:low_entropy` in case
2078+ the random generator failed due to lack of secure "randomness".
20602079
20612080> #### Note {: .info }
20622081>
20632082> The state returned from this function cannot be used to get a reproducible
2064- > random sequence as from the other `m:rand` functions, since reproducibility
2065- > does not match cryptographically safe.
2083+ > random sequence as from the other `m:rand` functions, since that would
2084+ > not be cryptographically safe.
20662085>
2067- > The only supported usage is to generate one distinct random sequence from this
2068- > start state.
2086+ > The only supported usage is to generate one distinct random sequence.
20692087""" .
20702088-doc (#{group => <<" Random API" >>,
20712089 since => <<" OTP 20.0" >>}).
@@ -2074,40 +2092,38 @@ rand_seed_s() ->
20742092 rand_seed_alg_s (? MODULE ).
20752093
20762094-doc """
2077- Create a state object for [random number generation](`m:rand`), in order to
2078- generate cryptographically strong random numbers.
2079-
2080- Saves the state in the process dictionary before returning it as well. See also
2081- `rand:seed/1` and `rand_seed_alg_s/1`.
2095+ Equivalent `rand_seed_alg_s/1` but also saves the returned
2096+ state object (generator) in the process dictionary. That is,
2097+ it is equivalent to `rand:seed(rand_seed_alg_s(Alg))`.
20822098
2083- When using the state object from this function the `m:rand` functions using it
2084- may raise exception `error:low_entropy` in case the random generator failed due
2085- to lack of secure "randomness".
2099+ See `rand:seed/1` and `rand_seed_alg_s/1`.
2100+ Note the warning about the process dictionary in `rand_seed/0`.
20862101
2087- _Example_
2102+ #### _Example_
20882103
20892104```erlang
20902105_ = crypto:rand_seed_alg(crypto_cache),
2091- _IntegerValue = rand:uniform(42), % [1; 42]
2092- _FloatValue = rand:uniform(). % [0.0; 1.0[
2106+ IntegerValue = rand:uniform(42), % [1; 42]
2107+ FloatValue = rand:uniform(). % [0.0; 1.0[
20932108```
20942109""" .
20952110-doc (#{group => <<" Random API" >>,
20962111 since => <<" OTP 21.0" >>}).
2097- -spec rand_seed_alg (Alg :: atom () ) ->
2098- {rand :alg_handler (),
2099- atom () | rand_cache_seed ()}.
2112+ -spec rand_seed_alg (Alg :: 'crypto' | 'crypto_cache' ) ->
2113+ {rand :alg_handler (),
2114+ atom () | rand_cache_seed ()}.
21002115rand_seed_alg (Alg ) ->
21012116 rand :seed (rand_seed_alg_s (Alg )).
21022117
21032118-doc """
2104- Creates a state object for [random number generation](`m:rand`), in order to
2105- generate cryptographically unpredictable random numbers.
2119+ Equivalent to `rand_seed_alg_s/2` but also saves the returned
2120+ state object (generator) in the process dictionary. That is,
2121+ it is equivalent to `rand:seed(rand_seed_alg_s(Alg, Seed))`.
21062122
2107- Saves the state in the process dictionary before returning it as well. See also
2108- `rand_seed_alg_s/2 `.
2123+ See `rand:seed/1` and `rand_seed_alg_s/2`.
2124+ Note the warning about the process dictionary in `rand_seed/0 `.
21092125
2110- _Example_
2126+ #### _Example_
21112127
21122128```erlang
21132129_ = crypto:rand_seed_alg(crypto_aes, "my seed"),
@@ -2120,9 +2136,9 @@ FloatValue = rand:uniform(). % again
21202136""" .
21212137-doc (#{group => <<" Random API" >>,
21222138 since => <<" OTP-22.0" >>}).
2123- -spec rand_seed_alg (Alg :: atom () , Seed :: term ()) ->
2124- {rand :alg_handler (),
2125- atom () | rand_cache_seed ()}.
2139+ -spec rand_seed_alg (Alg :: 'crypto_aes' , Seed :: term ()) ->
2140+ {rand :alg_handler (),
2141+ atom () | rand_cache_seed ()}.
21262142rand_seed_alg (Alg , Seed ) ->
21272143 rand :seed (rand_seed_alg_s (Alg , Seed )).
21282144
@@ -2131,20 +2147,29 @@ rand_seed_alg(Alg, Seed) ->
21312147
21322148-doc (#{group => <<" Random API" >>}).
21332149-doc """
2134- Create a state object for [random number generation](`m:rand`), in order to
2135- generate cryptographically strongly random numbers.
2150+ Create a state object (generator) for [random number generation](`m:rand`),
2151+ which when used by the `m:rand` functions produce
2152+ cryptographicaly strong random number.
21362153
2137- See also `rand:seed_s/1`.
2154+ See also `rand:seed_s/1` and for example `rand:uniform_s/2` .
21382155
2139- If `Alg` is `crypto` this function behaves exactly like `rand_seed_s/0`.
2156+ If `Alg` is `crypto` this function is equivalent to `rand_seed_s/0`.
21402157
2141- If `Alg` is `crypto_cache` this function fetches random data with OpenSSL's
2142- `RAND_bytes` and caches it for speed using an internal word size of 56 bits that
2143- makes calculations fast on 64 bit machines.
2158+ If `Alg` is `crypto_cache` the returned generator fetches random data
2159+ with OpenSSL's `RAND_bytes` and caches it as 56 bit numbers
2160+ which makes calculations fast on 64 bit machines.
21442161
2145- When using the state object from this function the `m:rand` functions using it
2146- may raise exception `error:low_entropy` in case the random generator failed due
2147- to lack of secure "randomness".
2162+ #### _Example_
2163+
2164+ ```erlang
2165+ S0 = crypto:rand_seed_alg_s(crypto_cache),
2166+ {IntegerValue, S1} = rand:uniform(42, S0), % [1; 42]
2167+ {FloatValue, S2} = rand:uniform(S1). % [0.0; 1.0[
2168+ ```
2169+
2170+ May cause the `m:rand` functions using this state object
2171+ to raise the exception `error:low_entropy` in case
2172+ the random generator failed due to lack of secure "randomness".
21482173
21492174The cache size can be changed from its default value using the
21502175[crypto app's ](crypto_app.md)configuration parameter `rand_cache_size`.
@@ -2155,28 +2180,29 @@ The cache size can be changed from its default value using the
21552180> random sequence as from the other `m:rand` functions, since reproducibility
21562181> does not match cryptographically safe.
21572182>
2158- > In fact since random data is cached some numbers may get reproduced if you
2183+ > In fact when random data is cached some numbers may get reproduced if you
21592184> try, but this is unpredictable.
21602185>
2161- > The only supported usage is to generate one distinct random sequence from this
2162- > start state.
2186+ > The only supported usage is to generate one distinct random sequence.
21632187""" .
21642188-doc (#{since => <<" OTP 21.0" >>}).
2165- -spec rand_seed_alg_s (Alg :: atom () ) ->
2166- {rand :alg_handler (),
2167- atom () | rand_cache_seed ()}.
2189+ -spec rand_seed_alg_s (Alg :: 'crypto' | 'crypto_cache' ) ->
2190+ {rand :alg_handler (),
2191+ atom () | rand_cache_seed ()}.
21682192rand_seed_alg_s ({AlgHandler , _AlgState } = State ) when is_map (AlgHandler ) ->
21692193 State ;
21702194rand_seed_alg_s ({Alg , AlgState }) when is_atom (Alg ) ->
21712195 {mk_alg_handler (Alg ),AlgState };
2172- rand_seed_alg_s (Alg ) when is_atom (Alg ) ->
2196+ rand_seed_alg_s (Alg ) when is_atom (Alg ) ->
21732197 {mk_alg_handler (Alg ),mk_alg_state (Alg )}.
2174- % %
2198+
21752199-doc """
2176- Create a state object for [random number generation](`m:rand`), in order to
2177- generate cryptographically unpredictable random numbers.
2200+ Create a state object (generator) for [random number generation](`m:rand`),
2201+ which when used by the `m:rand` functions produce
2202+ cryptographically unpredictable random numbers
21782203
2179- See also `rand_seed_alg/1`.
2204+ See also `rand:seed_s/1`, and for example `rand:uniform_s/2`.
2205+ Compare to `rand_seed_alg/1`.
21802206
21812207To get a long period the Xoroshiro928 generator from the `m:rand` module is used
21822208as a counter (with period 2^928 - 1) and the generator states are scrambled
@@ -2189,10 +2215,22 @@ since there is no re-keying schedule.
21892215
21902216- If you need cryptographically strong random numbers use `rand_seed_alg_s/1`
21912217 with `Alg =:= crypto` or `Alg =:= crypto_cache`.
2192- - If you need to be able to repeat the sequence use this function.
2218+ - If you need to be able to repeat the sequence use this function
2219+ with `Alg =:= crypto_aes`.
21932220- If you do not need the statistical quality of this function, there are faster
21942221 algorithms in the `m:rand` module.
21952222
2223+ #### _Example_
2224+
2225+ ```erlang
2226+ S0 = crypto:rand_seed_alg_s(crypto_aes, "my seed"),
2227+ {IntegerValue, S1} = rand:uniform(42, S0), % [1; 42]
2228+ {FloatValue, S2 = rand:uniform(S1), % [0.0; 1.0[
2229+ S3 = crypto:rand_seed_alg_s(crypto_aes, "my seed"),
2230+ {IntegerValue, S4} = rand:uniform(42, S3), % Same values
2231+ {FloatValue, S5} = rand:uniform(S4). % again
2232+ ```
2233+
21962234Thanks to the used generator the state object supports the
21972235[`rand:jump/0,1`](`rand:jump/0`) function with distance 2^512.
21982236
@@ -2202,9 +2240,9 @@ can be changed from its default value using the
22022240""" .
22032241-doc (#{group => <<" Random API" >>,
22042242 since => <<" OTP 22.0" >>}).
2205- -spec rand_seed_alg_s (Alg :: atom () , Seed :: term ()) ->
2206- {rand :alg_handler (),
2207- atom () | rand_cache_seed ()}.
2243+ -spec rand_seed_alg_s (Alg :: 'crypto_aes' , Seed :: term ()) ->
2244+ {rand :alg_handler (),
2245+ atom () | rand_cache_seed ()}.
22082246rand_seed_alg_s (Alg , Seed ) when is_atom (Alg ) ->
22092247 {mk_alg_handler (Alg ),mk_alg_state ({Alg ,Seed })}.
22102248
@@ -2398,6 +2436,20 @@ Generate a random integer number.
23982436
23992437The interval is `From =< N < To`. Uses the `crypto` library
24002438pseudo-random number generator. `To` must be larger than `From`.
2439+
2440+ > #### Note {: .info }
2441+ >
2442+ > This function is deprecated because in some openssl
2443+ > library versions it uses a pseudo random number generator
2444+ > that is not cryptographically safe.
2445+ >
2446+ > Instead use for example:
2447+ >
2448+ > ``` erlang
2449+ > S0 = crypto:rand_seed_s(),
2450+ > {Int, S1} = rand:uniform(To - From, S0),
2451+ > From + Int - 1.
2452+ > ```
24012453""" .
24022454-spec rand_uniform (crypto_integer (), crypto_integer ()) ->
24032455 crypto_integer ().
@@ -2431,7 +2483,8 @@ rand_uniform_nif(_From,_To) -> ?nif_stub.
24312483
24322484
24332485-doc """
2434- Set the seed for PRNG to the given binary.
2486+ Mixes in the bytes of the given binary into the internal state
2487+ of openssl's random number generator.
24352488
24362489This calls the RAND_seed function from openssl. Only use this if the system you
24372490are running on does not have enough "randomness" built in. Normally this is when
0 commit comments