File 2184-crypto-Deprecate-rand_bytes-1.patch of Package erlang

From 1ad18832cb21fac5a5b513005f1e6a5ffd7d0329 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 15 Apr 2016 10:29:31 +0200
Subject: [PATCH 1/6] crypto: Deprecate rand_bytes/1

OpenSSL has deprecated the function RAND_pseudo_bytes used by
crypto:rand_bytes/1, so this function is now deprecated in OTP too.

rand_bytes/3 also used this function, but was not documented
so we can remove it right away.

This commit also removes the fallback in generate_key to use
rand_bytes/1 if strong_rand_bytes/1 throws low entropy.
This is a potential incompatibility but we think it is desirable
as crypto should provide cryptographically secure functions.
---
 lib/crypto/c_src/crypto.c            | 22 ----------------------
 lib/crypto/doc/src/crypto.xml        | 18 ++----------------
 lib/crypto/src/crypto.erl            | 21 ++++++---------------
 lib/crypto/test/crypto_SUITE.erl     |  5 ++---
 lib/crypto/test/old_crypto_SUITE.erl |  4 ++--
 lib/stdlib/src/otp_internal.erl      |  7 ++++++-
 6 files changed, 18 insertions(+), 59 deletions(-)

diff --git a/lib/crypto/c_src/crypto.c b/lib/crypto/c_src/crypto.c
index 1be22a0..067e220 100644
--- a/lib/crypto/c_src/crypto.c
+++ b/lib/crypto/c_src/crypto.c
@@ -214,7 +214,6 @@ static ERL_NIF_TERM aes_ctr_stream_init(ErlNifEnv* env, int argc, const ERL_NIF_
 static ERL_NIF_TERM aes_ctr_stream_encrypt(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
 static ERL_NIF_TERM rand_bytes_1(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
 static ERL_NIF_TERM strong_rand_bytes_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
-static ERL_NIF_TERM rand_bytes_3(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
 static ERL_NIF_TERM strong_rand_mpint_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
 static ERL_NIF_TERM rand_uniform_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
 static ERL_NIF_TERM mod_exp_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[]);
@@ -285,7 +284,6 @@ static ErlNifFunc nif_funcs[] = {
     {"aes_ctr_stream_decrypt", 2, aes_ctr_stream_encrypt},
     {"rand_bytes", 1, rand_bytes_1},
     {"strong_rand_bytes_nif", 1, strong_rand_bytes_nif},
-    {"rand_bytes", 3, rand_bytes_3},
     {"strong_rand_mpint_nif", 3, strong_rand_mpint_nif},
     {"rand_uniform_nif", 2, rand_uniform_nif},
     {"mod_exp_nif", 4, mod_exp_nif},
@@ -1927,27 +1925,7 @@ static ERL_NIF_TERM strong_rand_bytes_nif(ErlNifEnv* env, int argc, const ERL_NI
     return ret;
 }
 
-static ERL_NIF_TERM rand_bytes_3(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
-{/* (Bytes, TopMask, BottomMask) */    
-    unsigned bytes;
-    unsigned char* data;
-    unsigned top_mask, bot_mask;
-    ERL_NIF_TERM ret;
 
-    if (!enif_get_uint(env, argv[0], &bytes)
-	|| !enif_get_uint(env, argv[1], &top_mask)
-	|| !enif_get_uint(env, argv[2], &bot_mask)) {
-	return enif_make_badarg(env);
-    }
-    data = enif_make_new_binary(env, bytes, &ret);
-    RAND_pseudo_bytes(data, bytes);
-    ERL_VALGRIND_MAKE_MEM_DEFINED(data, bytes);
-    if (bytes > 0) {
-	data[bytes-1] |= top_mask;
-	data[0] |= bot_mask;
-    }
-    return ret;
-}
 static ERL_NIF_TERM strong_rand_mpint_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 {/* (Bytes, TopMask, BottomMask) */    
     unsigned bits;
diff --git a/lib/crypto/doc/src/crypto.xml b/lib/crypto/doc/src/crypto.xml
index e0b9894..5a56277 100644
--- a/lib/crypto/doc/src/crypto.xml
+++ b/lib/crypto/doc/src/crypto.xml
@@ -308,6 +308,8 @@
       <desc>
 	<p>Generates public keys of type <c>Type</c>.
 	See also <seealso marker="public_key:public_key#generate_key-1">public_key:generate_key/1</seealso>
+	May throw exception <c>low_entropy</c> in case the random generator
+	failed due to lack of secure "randomness".
 	</p>
       </desc>
     </func>
@@ -596,22 +598,6 @@
     </func>
 
     <func>
-      <name>rand_bytes(N) -> binary()</name>
-      <fsummary>Generate a binary of random bytes</fsummary>
-      <type>
-        <v>N = integer()</v>
-      </type>
-      <desc>
-        <p>Generates N bytes randomly uniform 0..255, and returns the
-        result in a binary. Uses the <c>crypto</c> library pseudo-random
-        number generator.</p>
-        <p>This function is not recommended for cryptographic purposes.
-        Please use <seealso marker="#strong_rand_bytes/1">
-        strong_rand_bytes/1</seealso> instead.</p>
-      </desc>
-    </func>
-
-    <func>
       <name>rand_seed(Seed) -> ok</name>
       <fsummary>Set the seed for random bytes generation</fsummary>
       <type>
diff --git a/lib/crypto/src/crypto.erl b/lib/crypto/src/crypto.erl
index a154476..025d57e 100644
--- a/lib/crypto/src/crypto.erl
+++ b/lib/crypto/src/crypto.erl
@@ -28,7 +28,7 @@
 -export([generate_key/2, generate_key/3, compute_key/4]).
 -export([hmac/3, hmac/4, hmac_init/2, hmac_update/2, hmac_final/1, hmac_final_n/2]).
 -export([exor/2, strong_rand_bytes/1, mod_pow/3]).
--export([rand_bytes/1, rand_bytes/3, rand_uniform/2]).
+-export([rand_uniform/2]).
 -export([block_encrypt/3, block_decrypt/3, block_encrypt/4, block_decrypt/4]).
 -export([next_iv/2, next_iv/3]).
 -export([stream_init/2, stream_init/3, stream_encrypt/2, stream_decrypt/2]).
@@ -39,6 +39,9 @@
 -export([rand_seed/1]).
 
 %% DEPRECATED
+-export([rand_bytes/1]).
+-deprecated({rand_bytes, 1, next_major_release}).
+
 %% Replaced by hash_*
 -export([md4/1, md4_init/0, md4_update/2, md4_final/1]).
 -export([md5/1, md5_init/0, md5_update/2, md5_final/1]).
@@ -407,8 +410,6 @@ strong_rand_bytes(Bytes) ->
     end.
 strong_rand_bytes_nif(_Bytes) -> ?nif_stub.
 
-rand_bytes(_Bytes, _Topmask, _Bottommask) -> ?nif_stub.
-
 
 rand_uniform(From,To) when is_binary(From), is_binary(To) ->
     case rand_uniform_nif(From,To) of
@@ -546,7 +547,7 @@ generate_key(dh, DHParameters, PrivateKey) ->
 generate_key(srp, {host, [Verifier, Generator, Prime, Version]}, PrivArg)
   when is_binary(Verifier), is_binary(Generator), is_binary(Prime), is_atom(Version) ->
     Private = case PrivArg of
-		  undefined -> random_bytes(32);
+		  undefined -> strong_rand_bytes(32);
 		  _ -> ensure_int_as_bin(PrivArg)
 	      end,
     host_srp_gen_key(Private, Verifier, Generator, Prime, Version);
@@ -554,7 +555,7 @@ generate_key(srp, {host, [Verifier, Generator, Prime, Version]}, PrivArg)
 generate_key(srp, {user, [Generator, Prime, Version]}, PrivateArg)
   when is_binary(Generator), is_binary(Prime), is_atom(Version) ->
     Private = case PrivateArg of
-		  undefined -> random_bytes(32);
+		  undefined -> strong_rand_bytes(32);
 		  _ -> PrivateArg
 	      end,
     user_srp_gen_key(Private, Generator, Prime);
@@ -606,16 +607,6 @@ compute_key(ecdh, Others, My, Curve) ->
 			 nif_curve_params(Curve),
 			 ensure_int_as_bin(My)).
 
-
-random_bytes(N) ->
-    try strong_rand_bytes(N) of
-	RandBytes ->
-	    RandBytes
-    catch
-	error:low_entropy ->
-	    rand_bytes(N)
-    end.
-
 %%--------------------------------------------------------------------
 %%% On load
 %%--------------------------------------------------------------------
diff --git a/lib/crypto/test/crypto_SUITE.erl b/lib/crypto/test/crypto_SUITE.erl
index 0d18cd8..6732f27 100644
--- a/lib/crypto/test/crypto_SUITE.erl
+++ b/lib/crypto/test/crypto_SUITE.erl
@@ -269,7 +269,6 @@ rand_uniform() ->
     [{doc, "rand_uniform and random_bytes testing"}].
 rand_uniform(Config) when is_list(Config) ->
     rand_uniform_aux_test(10),
-    10 = byte_size(crypto:rand_bytes(10)),
     10 = byte_size(crypto:strong_rand_bytes(10)).
 
 %%--------------------------------------------------------------------
@@ -649,8 +648,8 @@ ipow(A, B, M, Prod)  ->
 do_exor(B) ->
     Z1 = zero_bin(B),
     Z1 = crypto:exor(B, B),
-    B1 = crypto:rand_bytes(100),
-    B2 = crypto:rand_bytes(100),
+    B1 = crypto:strong_rand_bytes(100),
+    B2 = crypto:strong_rand_bytes(100),
     Z2 = zero_bin(B1),
     Z2 = crypto:exor(B1, B1),
     Z2 = crypto:exor(B2, B2),
diff --git a/lib/crypto/test/old_crypto_SUITE.erl b/lib/crypto/test/old_crypto_SUITE.erl
index f57e9ff..0d97290 100644
--- a/lib/crypto/test/old_crypto_SUITE.erl
+++ b/lib/crypto/test/old_crypto_SUITE.erl
@@ -2068,8 +2068,8 @@ exor_test(Config) when is_list(Config) ->
     B = <<1, 2, 3, 4, 5, 6, 7, 8, 9, 10>>,
     Z1 = zero_bin(B),
     Z1 = crypto:exor(B, B),
-    B1 = crypto:rand_bytes(100),
-    B2 = crypto:rand_bytes(100),
+    B1 = crypto:strong_rand_bytes(100),
+    B2 = crypto:strong_rand_bytes(100),
     Z2 = zero_bin(B1),
     Z2 = crypto:exor(B1, B1),
     Z2 = crypto:exor(B2, B2),
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index 052dffd..7a59523 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -58,7 +58,12 @@ obsolete_1(erlang, now, 0) ->
 obsolete_1(calendar, local_time_to_universal_time, 1) ->
     {deprecated, {calendar, local_time_to_universal_time_dst, 1}};
 
-%% *** CRYPTO add in R16B01 ***
+%% *** CRYPTO added in OTP 19 ***
+
+obsolete_1(crypto, rand_bytes, 1) ->
+    {deprecated, {crypto, strong_rand_bytes, 1}};
+
+%% *** CRYPTO added in R16B01 ***
 
 obsolete_1(crypto, md4, 1) ->
     {deprecated, {crypto, hash, 2}};
-- 
2.1.4

openSUSE Build Service is sponsored by