@@ -1996,11 +1996,9 @@ alias1_rev(C) -> C.
19961996
19971997% %%================================================================
19981998% %%
1999- % %% RAND - pseudo random numbers using RN_ and BN_ functions in crypto lib
1999+ % %% RANDOM - pseudo random numbers using RN_ and BN_ functions in crypto lib
20002000% %%
20012001% %%================================================================
2002- -type rand_cache_seed () ::
2003- nonempty_improper_list (non_neg_integer (), binary ()).
20042002
20052003-doc """
20062004Generate bytes with randomly uniform values 0..255.
@@ -2025,7 +2023,93 @@ strong_rand_bytes(Bytes) ->
20252023strong_rand_bytes_nif (_Bytes ) -> ? nif_stub .
20262024
20272025
2026+ -doc (#{group => <<" Random API" >>}).
2027+ -doc """
2028+ Generate a random integer number.
2029+
2030+ The interval is `From =< N < To`. Uses the `crypto` library
2031+ pseudo-random number generator. `To` must be larger than `From`.
2032+
2033+ > #### Note {: .info }
2034+ >
2035+ > This function is deprecated because it originally used
2036+ > the OpenSSL method BN_pseudo_rand_range that was not
2037+ > cryptographically strong and could not run out of entropy.
2038+ > That behaviour changed in OpenSSL and this function
2039+ > cannot be fixed without making it raise `error:low_entropy`,
2040+ > which is not backwards compatible.
2041+ >
2042+ > Instead, use for example:
2043+ >
2044+ > ``` erlang
2045+ > S0 = crypto:rand_seed_s(),
2046+ > {Int, S1} = rand:uniform(To - From, S0),
2047+ > From + Int - 1.
2048+ > ```
2049+ >
2050+ > Beware of the possible `error:low_entropy` exception.
2051+ """ .
2052+ -spec rand_uniform (crypto_integer (), crypto_integer ()) ->
2053+ crypto_integer ().
2054+ rand_uniform (From , To ) when is_binary (From ), is_binary (To ) ->
2055+ case rand_uniform_nif (From ,To ) of
2056+ <<Len :32 /integer , MSB , Rest /binary >> when MSB > 127 ->
2057+ <<(Len + 1 ):32 /integer , 0 , MSB , Rest /binary >>;
2058+ Whatever ->
2059+ Whatever
2060+ end ;
2061+ rand_uniform (From ,To ) when is_integer (From ),is_integer (To ) ->
2062+ if From < 0 ->
2063+ rand_uniform_pos (0 , To - From ) + From ;
2064+ true ->
2065+ rand_uniform_pos (From , To )
2066+ end .
2067+
2068+ rand_uniform_pos (From ,To ) when From < To ->
2069+ BinFrom = mpint (From ),
2070+ BinTo = mpint (To ),
2071+ case rand_uniform (BinFrom , BinTo ) of
2072+ Result when is_binary (Result ) ->
2073+ erlint (Result );
2074+ Other ->
2075+ Other
2076+ end ;
2077+ rand_uniform_pos (_ ,_ ) ->
2078+ error (badarg ).
2079+
2080+ rand_uniform_nif (_From ,_To ) -> ? nif_stub .
2081+
2082+
2083+ -doc """
2084+ Mixes in the bytes of the given binary into the internal state
2085+ of OpenSSL's random number generator.
2086+
2087+ This calls the RAND_seed function from OpenSSL. Only use this if
2088+ the system you are running on does not have enough "randomness" built in.
2089+ Normally this is when `strong_rand_bytes/1` or a generator
2090+ from `rand_seed_alg_s/1` raises `error:low_entropy`.
2091+ """ .
2092+ -doc (#{group => <<" Random API" >>,
2093+ since => <<" OTP 17.0" >>}).
2094+ -spec rand_seed (binary ()) -> ok .
2095+ rand_seed (Seed ) when is_binary (Seed ) ->
2096+ rand_seed_nif (Seed ).
2097+
2098+ rand_seed_nif (_Seed ) -> ? nif_stub .
2099+
2100+
2101+ % %%================================================================
2102+ % %%
2103+ % %% RAND - Plug-In Generators for the `rand` module
2104+ % %%
2105+ % %%================================================================
2106+
2107+ -type rand_cache_seed () ::
2108+ nonempty_improper_list (non_neg_integer (), binary ()).
2109+
20282110-doc """
2111+ Create a generator for `m:rand` and save it in the process dictionary.
2112+
20292113Equivalent to `rand_seed_s/0` but also saves the returned
20302114state object (generator) in the process dictionary. That is,
20312115it is equivalent to `rand:seed(rand_seed_s())`.
@@ -2053,13 +2137,15 @@ FloatValue = rand:uniform(). % [0.0; 1.0)
20532137> that should be used instead of this function.
20542138""" .
20552139
2056- -doc (#{group => <<" Random API " >>,
2140+ -doc (#{group => <<" Plug-In Generators " >>,
20572141 since => <<" OTP 20.0" >>}).
20582142-spec rand_seed () -> rand :state ().
20592143rand_seed () ->
20602144 rand :seed (rand_seed_s ()).
20612145
20622146-doc """
2147+ Create a generator for `m:rand`.
2148+
20632149Create a state object (generator) for [random number generation](`m:rand`),
20642150which when used by the `m:rand` functions produce
20652151**cryptographically strong** random numbers (based on OpenSSL's
@@ -2085,13 +2171,16 @@ the random generator failed due to lack of secure "randomness".
20852171>
20862172> The only supported usage is to generate one distinct random sequence.
20872173""" .
2088- -doc (#{group => <<" Random API " >>,
2174+ -doc (#{group => <<" Plug-In Generators " >>,
20892175 since => <<" OTP 20.0" >>}).
20902176-spec rand_seed_s () -> rand :state ().
20912177rand_seed_s () ->
20922178 rand_seed_alg_s (? MODULE ).
20932179
20942180-doc """
2181+ Create a generator for `m:rand` with specified algorithm,
2182+ and save it in the process dictionary.
2183+
20952184Equivalent `rand_seed_alg_s/1` but also saves the returned
20962185state object (generator) in the process dictionary. That is,
20972186it is equivalent to `rand:seed(rand_seed_alg_s(Alg))`.
@@ -2107,7 +2196,7 @@ IntegerValue = rand:uniform(42), % 1 .. 42
21072196FloatValue = rand:uniform(). % [0.0; 1.0)
21082197```
21092198""" .
2110- -doc (#{group => <<" Random API " >>,
2199+ -doc (#{group => <<" Plug-In Generators " >>,
21112200 since => <<" OTP 21.0" >>}).
21122201-spec rand_seed_alg (Alg :: 'crypto' | 'crypto_cache' ) ->
21132202 {rand :alg_handler (),
@@ -2116,6 +2205,9 @@ rand_seed_alg(Alg) ->
21162205 rand :seed (rand_seed_alg_s (Alg )).
21172206
21182207-doc """
2208+ Create and seed a generator for `m:rand` with specified algorithm,
2209+ and save it in the process dictionary.
2210+
21192211Equivalent to `rand_seed_alg_s/2` but also saves the returned
21202212state object (generator) in the process dictionary. That is,
21212213it is equivalent to `rand:seed(rand_seed_alg_s(Alg, Seed))`.
@@ -2134,7 +2226,7 @@ IntegerValue = rand:uniform(42), % Same values
21342226FloatValue = rand:uniform(). % again
21352227```
21362228""" .
2137- -doc (#{group => <<" Random API " >>,
2229+ -doc (#{group => <<" Plug-In Generators " >>,
21382230 since => <<" OTP-22.0" >>}).
21392231-spec rand_seed_alg (Alg :: 'crypto_aes' , Seed :: term ()) ->
21402232 {rand :alg_handler (),
@@ -2145,8 +2237,10 @@ rand_seed_alg(Alg, Seed) ->
21452237-define (CRYPTO_CACHE_BITS , 56 ).
21462238-define (CRYPTO_AES_BITS , 58 ).
21472239
2148- -doc (#{group => <<" Random API " >>}).
2240+ -doc (#{group => <<" Plug-In Generators " >>}).
21492241-doc """
2242+ Create a generator for `m:rand` with specified algorithm.
2243+
21502244Create a state object (generator) for [random number generation](`m:rand`),
21512245which when used by the `m:rand` functions produce
21522246**cryptographically strong** random number.
@@ -2197,6 +2291,8 @@ rand_seed_alg_s(Alg) when is_atom(Alg) ->
21972291 {mk_alg_handler (Alg ),mk_alg_state (Alg )}.
21982292
21992293-doc """
2294+ Create and seed a generator for `m:rand` with specified algorithm.
2295+
22002296Create a state object (generator) for [random number generation](`m:rand`),
22012297which when used by the `m:rand` functions produce
22022298**cryptographically unpredictable** random numbers
@@ -2239,7 +2335,7 @@ Numbers are generated in batches and cached for speed reasons. The cache size
22392335can be changed from its default value using the
22402336[crypto app's ](crypto_app.md)configuration parameter `rand_cache_size`.
22412337""" .
2242- -doc (#{group => <<" Random API " >>,
2338+ -doc (#{group => <<" Plug-In Generators " >>,
22432339 since => <<" OTP 22.0" >>}).
22442340-spec rand_seed_alg_s (Alg :: 'crypto_aes' , Seed :: term ()) ->
22452341 {rand :alg_handler (),
@@ -2431,78 +2527,6 @@ strong_rand_float() ->
24312527 WholeRange = strong_rand_range (1 bsl 53 ),
24322528 ? HALF_DBL_EPSILON * bytes_to_integer (WholeRange ).
24332529
2434- -doc (#{group => <<" Random API" >>}).
2435- -doc """
2436- Generate a random integer number.
2437-
2438- The interval is `From =< N < To`. Uses the `crypto` library
2439- pseudo-random number generator. `To` must be larger than `From`.
2440-
2441- > #### Note {: .info }
2442- >
2443- > This function is deprecated because it originally used
2444- > the OpenSSL method BN_pseudo_rand_range that was not
2445- > cryptographically strong and could not run out of entropy.
2446- > Although that function has been deprecated in later versions of OpenSSL,
2447- > this function cannot be fixed without making it possibly raise
2448- > `error:low_entropy`, which is not backwards compatible.
2449- >
2450- > Instead use for example:
2451- >
2452- > ``` erlang
2453- > S0 = crypto:rand_seed_s(),
2454- > {Int, S1} = rand:uniform(To - From, S0),
2455- > From + Int - 1.
2456- > ```
2457- """ .
2458- -spec rand_uniform (crypto_integer (), crypto_integer ()) ->
2459- crypto_integer ().
2460- rand_uniform (From , To ) when is_binary (From ), is_binary (To ) ->
2461- case rand_uniform_nif (From ,To ) of
2462- <<Len :32 /integer , MSB , Rest /binary >> when MSB > 127 ->
2463- <<(Len + 1 ):32 /integer , 0 , MSB , Rest /binary >>;
2464- Whatever ->
2465- Whatever
2466- end ;
2467- rand_uniform (From ,To ) when is_integer (From ),is_integer (To ) ->
2468- if From < 0 ->
2469- rand_uniform_pos (0 , To - From ) + From ;
2470- true ->
2471- rand_uniform_pos (From , To )
2472- end .
2473-
2474- rand_uniform_pos (From ,To ) when From < To ->
2475- BinFrom = mpint (From ),
2476- BinTo = mpint (To ),
2477- case rand_uniform (BinFrom , BinTo ) of
2478- Result when is_binary (Result ) ->
2479- erlint (Result );
2480- Other ->
2481- Other
2482- end ;
2483- rand_uniform_pos (_ ,_ ) ->
2484- error (badarg ).
2485-
2486- rand_uniform_nif (_From ,_To ) -> ? nif_stub .
2487-
2488-
2489- -doc """
2490- Mixes in the bytes of the given binary into the internal state
2491- of openssl's random number generator.
2492-
2493- This calls the RAND_seed function from openssl. Only use this if
2494- the system you are running on does not have enough "randomness" built in.
2495- Normally this is when `strong_rand_bytes/1` or a generator
2496- from `rand_seed_alg_s/1` raises `error:low_entropy`.
2497- """ .
2498- -doc (#{group => <<" Random API" >>,
2499- since => <<" OTP 17.0" >>}).
2500- -spec rand_seed (binary ()) -> ok .
2501- rand_seed (Seed ) when is_binary (Seed ) ->
2502- rand_seed_nif (Seed ).
2503-
2504- rand_seed_nif (_Seed ) -> ? nif_stub .
2505-
25062530% %%================================================================
25072531% %%
25082532% %% Sign/verify
0 commit comments