File 2185-ssl-Remove-use-of-crypto-rand_bytes-1.patch of Package erlang

From f1db2eb29768eca2d7affdfd95753b477df05beb Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 15 Apr 2016 11:02:02 +0200
Subject: [PATCH 2/6] ssl: Remove use of crypto:rand_bytes/1

ssl already used crypto:strong_rand_bytes/1 for most operations as
its use cases are mostly cryptographical. Now crypto:strong_rand_bytes/1
will be used everywhere.

However crypto:rand_bytes/1 was used as fallback if
crypto:strong_rand_bytes/1 throws low_entropy, this
will no longer be the case. This is a potential incompatibility.
The fallback was introduced a long time ago for interoperability reasons.
Now days this should not be a problem, and if it is, the security
compromise is not acceptable anyway.
---
 lib/ssl/src/ssl.erl              | 18 +-----------------
 lib/ssl/src/ssl_cipher.erl       | 22 +++++++++++++++++-----
 lib/ssl/src/ssl_connection.erl   |  4 ++--
 lib/ssl/src/ssl_manager.erl      |  2 +-
 lib/ssl/src/ssl_record.erl       |  2 +-
 lib/ssl/test/ssl_basic_SUITE.erl |  2 +-
 lib/ssl/test/ssl_dist_SUITE.erl  |  2 +-
 lib/ssl/test/ssl_test_lib.erl    |  2 +-
 8 files changed, 25 insertions(+), 29 deletions(-)

diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl
index 4bcd6dd..61afdce 100644
--- a/lib/ssl/src/ssl.erl
+++ b/lib/ssl/src/ssl.erl
@@ -42,7 +42,7 @@
      renegotiate/1, prf/5, negotiated_protocol/1, negotiated_next_protocol/1,
 	 connection_information/1, connection_information/2]).
 %% Misc
--export([random_bytes/1, handle_options/2]).
+-export([handle_options/2]).
 
 -deprecated({negotiated_next_protocol, 1, next_major_release}).
 -deprecated({connection_info, 1, next_major_release}).
@@ -581,22 +581,6 @@ format_error(Error) ->
             Other
     end.
 
-%%--------------------------------------------------------------------
--spec random_bytes(integer()) -> binary().
-
-%%
-%% Description: Generates cryptographically secure random sequence if possible
-%% fallbacks on pseudo random function
-%%--------------------------------------------------------------------
-random_bytes(N) ->
-    try crypto:strong_rand_bytes(N) of
-	RandBytes ->
-	    RandBytes
-    catch
-	error:low_entropy ->
-	    crypto:rand_bytes(N)
-    end.
-
 %%%--------------------------------------------------------------
 %%% Internal functions
 %%%--------------------------------------------------------------------
diff --git a/lib/ssl/src/ssl_cipher.erl b/lib/ssl/src/ssl_cipher.erl
index e66f253..f58533b 100644
--- a/lib/ssl/src/ssl_cipher.erl
+++ b/lib/ssl/src/ssl_cipher.erl
@@ -1,4 +1,4 @@
-%%
+%
 %% %CopyrightBegin%
 %%
 %% Copyright Ericsson AB 2007-2015. All Rights Reserved.
@@ -39,7 +39,8 @@
 	 suite/1, suites/1, all_suites/1, 
 	 ec_keyed_suites/0, anonymous_suites/1, psk_suites/1, srp_suites/0,
 	 rc4_suites/1, openssl_suite/1, openssl_suite_name/1, filter/2, filter_suites/1,
-	 hash_algorithm/1, sign_algorithm/1, is_acceptable_hash/2, is_fallback/1]).
+	 hash_algorithm/1, sign_algorithm/1, is_acceptable_hash/2, is_fallback/1,
+	 random_bytes/1]).
 
 -export_type([cipher_suite/0,
 	      erl_cipher_suite/0, openssl_cipher_suite/0,
@@ -49,7 +50,8 @@
 			   | aes_128_cbc |  aes_256_cbc | aes_128_gcm | aes_256_gcm | chacha20_poly1305.
 -type hash()              :: null | sha | md5 | sha224 | sha256 | sha384 | sha512.
 -type sign_algo()         :: rsa | dsa | ecdsa.
--type key_algo()          :: null | rsa | dhe_rsa | dhe_dss | ecdhe_ecdsa| ecdh_ecdsa | ecdh_rsa| srp_rsa| srp_dss | psk | dhe_psk | rsa_psk | dh_anon | ecdh_anon | srp_anon.
+-type key_algo()          :: null | rsa | dhe_rsa | dhe_dss | ecdhe_ecdsa| ecdh_ecdsa | ecdh_rsa| srp_rsa| srp_dss | 
+			     psk | dhe_psk | rsa_psk | dh_anon | ecdh_anon | srp_anon.
 -type erl_cipher_suite()  :: {key_algo(), cipher(), hash()} % Pre TLS 1.2 
 			     %% TLS 1.2, internally PRE TLS 1.2 will use default_prf
 			   | {key_algo(), cipher(), hash(), hash() | default_prf}. 
@@ -102,7 +104,7 @@ cipher_init(?RC4, IV, Key) ->
     State = crypto:stream_init(rc4, Key),
     #cipher_state{iv = IV, key = Key, state = State};
 cipher_init(?AES_GCM, IV, Key) ->
-    <<Nonce:64>> = ssl:random_bytes(8),
+    <<Nonce:64>> = random_bytes(8),
     #cipher_state{iv = IV, key = Key, nonce = Nonce};
 cipher_init(_BCA, IV, Key) ->
     #cipher_state{iv = IV, key = Key}.
@@ -1472,6 +1474,16 @@ is_acceptable_prf(Prf, Algos) ->
 is_fallback(CipherSuites)->
     lists:member(?TLS_FALLBACK_SCSV, CipherSuites).
 
+
+%%--------------------------------------------------------------------
+-spec random_bytes(integer()) -> binary().
+
+%%
+%% Description: Generates cryptographically secure random sequence 
+%%--------------------------------------------------------------------
+random_bytes(N) ->
+    crypto:strong_rand_bytes(N).
+
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
@@ -1712,7 +1724,7 @@ get_padding_aux(BlockSize, PadLength) ->
 
 random_iv(IV) ->
     IVSz = byte_size(IV),
-    ssl:random_bytes(IVSz).
+    random_bytes(IVSz).
 
 next_iv(Bin, IV) ->
     BinSz = byte_size(Bin),
diff --git a/lib/ssl/src/ssl_connection.erl b/lib/ssl/src/ssl_connection.erl
index 1568e85..0073e86 100644
--- a/lib/ssl/src/ssl_connection.erl
+++ b/lib/ssl/src/ssl_connection.erl
@@ -502,7 +502,7 @@ certify(#server_hello_done{},
 	       role = client,
 	       key_algorithm = Alg} = State0, Connection)
   when Alg == rsa_psk ->
-    Rand = ssl:random_bytes(?NUM_OF_PREMASTERSECRET_BYTES-2),
+    Rand = ssl_cipher:random_bytes(?NUM_OF_PREMASTERSECRET_BYTES-2),
     RSAPremasterSecret = <<?BYTE(Major), ?BYTE(Minor), Rand/binary>>,
     case ssl_handshake:premaster_secret({Alg, PSKIdentity}, PSKLookup, RSAPremasterSecret) of
 	#alert{} = Alert ->
@@ -1885,7 +1885,7 @@ handle_resumed_session(SessId, #state{connection_states = ConnectionStates0,
     end.
 
 make_premaster_secret({MajVer, MinVer}, rsa) ->
-    Rand = ssl:random_bytes(?NUM_OF_PREMASTERSECRET_BYTES-2),
+    Rand = ssl_cipher:random_bytes(?NUM_OF_PREMASTERSECRET_BYTES-2),
     <<?BYTE(MajVer), ?BYTE(MinVer), Rand/binary>>;
 make_premaster_secret(_, _) ->
     undefined.
diff --git a/lib/ssl/src/ssl_manager.erl b/lib/ssl/src/ssl_manager.erl
index e273581..2349158 100644
--- a/lib/ssl/src/ssl_manager.erl
+++ b/lib/ssl/src/ssl_manager.erl
@@ -551,7 +551,7 @@ last_delay_timer({_,_}, TRef, {_, LastClient}) ->
 new_id(_, 0, _, _) ->
     <<>>;
 new_id(Port, Tries, Cache, CacheCb) ->
-    Id = crypto:rand_bytes(?NUM_OF_SESSION_ID_BYTES),
+    Id = ssl_cipher:random_bytes(?NUM_OF_SESSION_ID_BYTES),
     case CacheCb:lookup(Cache, {Port, Id}) of
 	undefined ->
 	    Now = erlang:monotonic_time(),
diff --git a/lib/ssl/src/ssl_record.erl b/lib/ssl/src/ssl_record.erl
index ecff950..866bfce 100644
--- a/lib/ssl/src/ssl_record.erl
+++ b/lib/ssl/src/ssl_record.erl
@@ -460,7 +460,7 @@ empty_security_params(ConnectionEnd = ?SERVER) ->
 random() ->
     Secs_since_1970 = calendar:datetime_to_gregorian_seconds(
 			calendar:universal_time()) - 62167219200,
-    Random_28_bytes = crypto:rand_bytes(28),
+    Random_28_bytes = ssl_cipher:random_bytes(28),
     <<?UINT32(Secs_since_1970), Random_28_bytes/binary>>.
 
 dtls_next_epoch(#connection_state{epoch = undefined}) -> %% SSL/TLS
diff --git a/lib/ssl/test/ssl_basic_SUITE.erl b/lib/ssl/test/ssl_basic_SUITE.erl
index 50313e6..829ab12 100644
--- a/lib/ssl/test/ssl_basic_SUITE.erl
+++ b/lib/ssl/test/ssl_basic_SUITE.erl
@@ -1555,7 +1555,7 @@ tcp_connect_big(Config) when is_list(Config) ->
     {_, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
     TcpOpts = [binary, {reuseaddr, true}],
 
-    Rand = crypto:rand_bytes(?MAX_CIPHER_TEXT_LENGTH+1),
+    Rand = crypto:strong_rand_bytes(?MAX_CIPHER_TEXT_LENGTH+1),
     Server = ssl_test_lib:start_upgrade_server_error([{node, ServerNode}, {port, 0},
 						      {from, self()},
 						      {timeout, 5000},
diff --git a/lib/ssl/test/ssl_dist_SUITE.erl b/lib/ssl/test/ssl_dist_SUITE.erl
index bd0ddde..e7cbfa6 100644
--- a/lib/ssl/test/ssl_dist_SUITE.erl
+++ b/lib/ssl/test/ssl_dist_SUITE.erl
@@ -194,7 +194,7 @@ payload(Config) when is_list(Config) ->
 	     ok = apply_on_ssl_node(
 		    NH2,
 		    fun () ->
-			    Msg = crypto:rand_bytes(100000),
+			    Msg = crypto:strong_rand_bytes(100000),
 			    SslPid ! {self(), Msg},
 			    receive
 				{SslPid, Msg} ->
diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl
index 2cd23eb..7e6562f 100644
--- a/lib/ssl/test/ssl_test_lib.erl
+++ b/lib/ssl/test/ssl_test_lib.erl
@@ -349,7 +349,7 @@ wait_for_result(Pid, Msg) ->
 user_lookup(psk, _Identity, UserState) ->
     {ok, UserState};
 user_lookup(srp, Username, _UserState) ->
-    Salt = ssl:random_bytes(16),
+    Salt = ssl_cipher:random_bytes(16),
     UserPassHash = crypto:hash(sha, [Salt, crypto:hash(sha, [Username, <<$:>>, <<"secret">>])]),
     {ok, {srp_1024, Salt, UserPassHash}}.
 
-- 
2.1.4

openSUSE Build Service is sponsored by