Skip to content

Commit a2b40d2

Browse files
committed
Publish crypto:strong_rand_range/1
1 parent 147f8ff commit a2b40d2

File tree

2 files changed

+65
-42
lines changed

2 files changed

+65
-42
lines changed

lib/crypto/src/crypto.erl

Lines changed: 49 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -158,7 +158,7 @@ end
158158
-export([sign/4, sign/5, verify/5, verify/6]).
159159
-export([generate_key/2, generate_key/3, compute_key/4]).
160160
-export([encapsulate_key/2, decapsulate_key/3]).
161-
-export([exor/2, strong_rand_bytes/1, mod_pow/3]).
161+
-export([exor/2, strong_rand_bytes/1, strong_rand_range/1, mod_pow/3]).
162162
-export([rand_seed/0, rand_seed_alg/1, rand_seed_alg/2]).
163163
-export([rand_seed_s/0, rand_seed_alg_s/1, rand_seed_alg_s/2]).
164164
-export([rand_plugin_next/1]).
@@ -331,13 +331,12 @@ end
331331
-export([rand_plugin_aes_jump_2pow20/1]).
332332

333333
-deprecated(
334-
{rand_uniform, 2,
335-
"use rand_seed_s/0 with rand:uniform_s/2 instead"}).
334+
{rand_uniform, 2, "use strong_rand_range/1 instead"}).
336335

337336
%% This should correspond to the similar macro in crypto.c
338337
-define(MAX_BYTES_TO_NIF, 20000). %% Current value is: erlang:system_info(context_reductions) * 10
339338

340-
%% Used by strong_rand_float/0
339+
%% Used by rand_plugin_uniform/1
341340
-define(HALF_DBL_EPSILON, 1.1102230246251565e-16). % math:pow(2, -53)
342341

343342

@@ -2020,6 +2019,7 @@ strong_rand_bytes(Bytes) ->
20202019
false -> erlang:error(low_entropy);
20212020
Bin -> Bin
20222021
end.
2022+
20232023
strong_rand_bytes_nif(_Bytes) -> ?nif_stub.
20242024

20252025

@@ -2039,15 +2039,9 @@ pseudo-random number generator. `To` must be larger than `From`.
20392039
> cannot be fixed without making it raise `error:low_entropy`,
20402040
> which is not backwards compatible.
20412041
>
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-
> ```
2042+
> Instead, use `strong_rand_range(To - From) + From`
20492043
>
2050-
> Beware of the possible `error:low_entropy` exception.
2044+
> Be aware of the possible `error:low_entropy` exception.
20512045
""".
20522046
-spec rand_uniform(crypto_integer(), crypto_integer()) ->
20532047
crypto_integer().
@@ -2098,6 +2092,45 @@ rand_seed(Seed) when is_binary(Seed) ->
20982092
rand_seed_nif(_Seed) -> ?nif_stub.
20992093

21002094

2095+
-doc(#{group => <<"Random API">>,
2096+
since => <<"OTP @OTP-19841@">>}).
2097+
-doc """
2098+
Generate a random integer in a specified range.
2099+
2100+
The returned random integer is in the interval is `0` =< `N` < `Range`.
2101+
2102+
Uses the `crypto` library random number generator BN_rand_range.
2103+
2104+
If the `Range` argument is a `pos_integer/0` the return value
2105+
is a `non_neg_integer/0`. If the `Range` argument is a positive integer
2106+
in a `binary/0`, the return value is a non-negative integer in a `binary/0`.
2107+
2108+
May raise exception `error:low_entropy` in case the random generator failed due
2109+
to lack of secure "randomness".
2110+
""".
2111+
-spec strong_rand_range(Range :: pos_integer()) -> N :: non_neg_integer();
2112+
(Range :: binary()) -> N :: binary().
2113+
%% BN_rand_range
2114+
strong_rand_range(Range) when is_integer(Range), Range > 0 ->
2115+
bin_to_int(strong_rand_range(int_to_bin(Range)));
2116+
strong_rand_range(BinRange) when is_binary(BinRange) ->
2117+
case strong_rand_range_nif(BinRange) of
2118+
false ->
2119+
V = bin_to_int(BinRange),
2120+
if
2121+
0 < V ->
2122+
erlang:error(low_entropy);
2123+
true ->
2124+
error(badarg, [BinRange])
2125+
end;
2126+
<<BinResult/binary>> ->
2127+
BinResult
2128+
end;
2129+
strong_rand_range(Range) ->
2130+
error(badarg, [Range]).
2131+
2132+
strong_rand_range_nif(_BinRange) -> ?nif_stub.
2133+
21012134
%%%================================================================
21022135
%%%
21032136
%%% RAND - Plug-In Generators for the `rand` module
@@ -2388,15 +2421,16 @@ rand_cache_size() ->
23882421

23892422
-doc false.
23902423
rand_plugin_next(Seed) ->
2391-
{bytes_to_integer(strong_rand_range(1 bsl 64)), Seed}.
2424+
{strong_rand_range(1 bsl 64), Seed}.
23922425

23932426
-doc false.
23942427
rand_plugin_uniform(State) ->
2395-
{strong_rand_float(), State}.
2428+
Value = ?HALF_DBL_EPSILON * strong_rand_range(1 bsl 53),
2429+
{Value, State}.
23962430

23972431
-doc false.
23982432
rand_plugin_uniform(Max, State) ->
2399-
{bytes_to_integer(strong_rand_range(Max)) + 1, State}.
2433+
{strong_rand_range(Max) + 1, State}.
24002434

24012435

24022436
-doc false.
@@ -2511,22 +2545,6 @@ aes_cache(
25112545
[V|aes_cache(Encrypted, Cache)].
25122546

25132547

2514-
strong_rand_range(Range) when is_integer(Range), Range > 0 ->
2515-
BinRange = int_to_bin(Range),
2516-
strong_rand_range(BinRange);
2517-
strong_rand_range(BinRange) when is_binary(BinRange) ->
2518-
case strong_rand_range_nif(BinRange) of
2519-
false ->
2520-
erlang:error(low_entropy);
2521-
<<BinResult/binary>> ->
2522-
BinResult
2523-
end.
2524-
strong_rand_range_nif(_BinRange) -> ?nif_stub.
2525-
2526-
strong_rand_float() ->
2527-
WholeRange = strong_rand_range(1 bsl 53),
2528-
?HALF_DBL_EPSILON * bytes_to_integer(WholeRange).
2529-
25302548
%%%================================================================
25312549
%%%
25322550
%%% Sign/verify

lib/crypto/test/crypto_SUITE.erl

Lines changed: 16 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -2155,19 +2155,24 @@ rand_uniform_aux_test(0) ->
21552155
rand_uniform_aux_test(N) ->
21562156
L = N*1000,
21572157
H = N*100000+1,
2158-
crypto_rand_uniform(L, H),
2159-
crypto_rand_uniform(-L, L),
2160-
crypto_rand_uniform(-H, -L),
2161-
crypto_rand_uniform(-H, L),
2158+
crypto_rand_range(L, H),
2159+
crypto_rand_range(-L, L),
2160+
crypto_rand_range(-H, -L),
2161+
crypto_rand_range(-H, L),
21622162
rand_uniform_aux_test(N-1).
21632163

2164-
crypto_rand_uniform(L,H) ->
2165-
R1 = (L-1) + rand:uniform(H-L),
2166-
case (R1 >= L) and (R1 < H) of
2167-
true ->
2168-
ok;
2169-
false ->
2170-
ct:fail({"Not in interval", R1, L, H})
2164+
crypto_rand_range(L,H) ->
2165+
Range = H-L,
2166+
R1 = crypto:strong_rand_range(Range),
2167+
case crypto:strong_rand_range(<<Range:32>>) of
2168+
Bin when is_binary(Bin) ->
2169+
<<R2:(bit_size(Bin))/integer>> = Bin,
2170+
if
2171+
is_integer(R1), 0 =< R1, R1 < Range, 0 =< R2, R2 < Range ->
2172+
ok;
2173+
true ->
2174+
ct:fail({"Not in range", R1, R2, Range})
2175+
end
21712176
end.
21722177

21732178
foldallmap(_Fun, AccN, []) ->

0 commit comments

Comments
 (0)