File 2038-ssl-TLS-1.2-clients-will-now-always-send-hello-messa.patch of Package erlang

From edab501fe7bffe3f19871157ebd1851e6dad1bc5 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 21 Apr 2017 10:22:26 +0200
Subject: [PATCH] ssl: TLS-1.2 clients will now always send hello messages on
 its own format.

Note this is a change form how it works for earlier versions that will
send the first hello message on the lowest supported version.

From RFC 5246

Appendix E.  Backward Compatibility

E.1.  Compatibility with TLS 1.0/1.1 and SSL 3.0

   Since there are various versions of TLS (1.0, 1.1, 1.2, and any
   future versions) and SSL (2.0 and 3.0), means are needed to negotiate
   the specific protocol version to use.  The TLS protocol provides a
   built-in mechanism for version negotiation so as not to bother other
   protocol components with the complexities of version selection.

   TLS versions 1.0, 1.1, and 1.2, and SSL 3.0 are very similar, and use
   compatible ClientHello messages; thus, supporting all of them is
   relatively easy.  Similarly, servers can easily handle clients trying
   to use future versions of TLS as long as the ClientHello format
   remains compatible, and the client supports the highest protocol
   version available in the server.

   A TLS 1.2 client who wishes to negotiate with such older servers will
   send a normal TLS 1.2 ClientHello, containing { 3, 3 } (TLS 1.2) in
   ClientHello.client_version.  If the server does not support this
   version, it will respond with a ServerHello containing an older
   version number.  If the client agrees to use this version, the
   negotiation will proceed as appropriate for the negotiated protocol.

   If the version chosen by the server is not supported by the client
   (or not acceptable), the client MUST send a "protocol_version" alert
   message and close the connection.

   If a TLS server receives a ClientHello containing a version number
   greater than the highest version supported by the server, it MUST
   reply according to the highest version supported by the server.

   A TLS server can also receive a ClientHello containing a version
   number smaller than the highest supported version.  If the server
   wishes to negotiate with old clients, it will proceed as appropriate

   for the highest version supported by the server that is not greater
   than ClientHello.client_version.  For example, if the server supports
   TLS 1.0, 1.1, and 1.2, and client_version is TLS 1.0, the server will
   proceed with a TLS 1.0 ServerHello.  If server supports (or is
   willing to use) only versions greater than client_version, it MUST
   send a "protocol_version" alert message and close the connection.

   Whenever a client already knows the highest protocol version known to
   a server (for example, when resuming a session), it SHOULD initiate
   the connection in that native protocol.

   Note: some server implementations are known to implement version
   negotiation incorrectly.  For example, there are buggy TLS 1.0
   servers that simply close the connection when the client offers a
   version newer than TLS 1.0.  Also, it is known that some servers will
   refuse the connection if any TLS extensions are included in
   ClientHello.  Interoperability with such buggy servers is a complex
   topic beyond the scope of this document, and may require multiple
   connection attempts by the client.

   Earlier versions of the TLS specification were not fully clear on
   what the record layer version number (TLSPlaintext.version) should
   contain when sending ClientHello (i.e., before it is known which
   version of the protocol will be employed).  Thus, TLS servers
   compliant with this specification MUST accept any value {03,XX} as
   the record layer version number for ClientHello.

   TLS clients that wish to negotiate with older servers MAY send any
   value {03,XX} as the record layer version number.  Typical values
   would be {03,00}, the lowest version number supported by the client,
   and the value of ClientHello.client_version.  No single value will
   guarantee interoperability with all old servers, but this is a
   complex topic beyond the scope of this document.
---
 lib/ssl/src/dtls_connection.erl |  2 +-
 lib/ssl/src/dtls_handshake.erl  |  4 ++--
 lib/ssl/src/dtls_record.erl     | 11 ++++++++++-
 lib/ssl/src/ssl.erl             |  6 +++---
 lib/ssl/src/ssl_connection.erl  |  2 +-
 lib/ssl/src/ssl_handshake.erl   | 26 ++++++++++----------------
 lib/ssl/src/tls_connection.erl  |  2 +-
 lib/ssl/src/tls_record.erl      |  8 +++++++-
 8 files changed, 35 insertions(+), 26 deletions(-)

diff --git a/lib/ssl/src/dtls_connection.erl b/lib/ssl/src/dtls_connection.erl
index 440607e99..14d802085 100644
--- a/lib/ssl/src/dtls_connection.erl
+++ b/lib/ssl/src/dtls_connection.erl
@@ -250,7 +250,7 @@ init({call, From}, {start, Timeout},
 					Cache, CacheCb, Renegotiation, Cert),
 
     Version = Hello#client_hello.client_version,
-    HelloVersion = dtls_record:lowest_protocol_version(SslOpts#ssl_options.versions),
+    HelloVersion = dtls_record:hello_version(Version, SslOpts#ssl_options.versions),
     State1 = prepare_flight(State0#state{negotiated_version = Version}),
     {State2, Actions} = send_handshake(Hello, State1#state{negotiated_version = HelloVersion}),  
     State3 = State2#state{negotiated_version = Version, %% Requested version
diff --git a/lib/ssl/src/dtls_handshake.erl b/lib/ssl/src/dtls_handshake.erl
index d3ba90a22..5fb1b6148 100644
--- a/lib/ssl/src/dtls_handshake.erl
+++ b/lib/ssl/src/dtls_handshake.erl
@@ -66,7 +66,7 @@ client_hello(Host, Port, Cookie, ConnectionStates,
     CipherSuites = ssl_handshake:available_suites(UserSuites, TLSVersion),
 
     Extensions = ssl_handshake:client_hello_extensions(Host, TLSVersion, CipherSuites,
-						SslOpts, ConnectionStates, Renegotiation),
+                                                       SslOpts, ConnectionStates, Renegotiation),
 
     Id = ssl_session:client_id({Host, Port, SslOpts}, Cache, CacheCb, OwnCert),
 
@@ -252,7 +252,7 @@ enc_handshake(#server_hello{} = HandshakeMsg, Version) ->
     {Type,  <<?BYTE(DTLSMajor), ?BYTE(DTLSMinor), Rest/binary>>};
 
 enc_handshake(HandshakeMsg, Version) ->
-    ssl_handshake:encode_handshake(HandshakeMsg, Version).
+    ssl_handshake:encode_handshake(HandshakeMsg, dtls_v1:corresponding_tls_version(Version)).
 
 bin_fragments(Bin, Size) ->
      bin_fragments(Bin, byte_size(Bin), Size, 0, []).
diff --git a/lib/ssl/src/dtls_record.erl b/lib/ssl/src/dtls_record.erl
index 049f83e49..de6b6e400 100644
--- a/lib/ssl/src/dtls_record.erl
+++ b/lib/ssl/src/dtls_record.erl
@@ -44,7 +44,7 @@
 -export([protocol_version/1, lowest_protocol_version/1, lowest_protocol_version/2,
 	 highest_protocol_version/1, highest_protocol_version/2,
 	 is_higher/2, supported_protocol_versions/0,
-	 is_acceptable_version/2]).
+	 is_acceptable_version/2, hello_version/2]).
 
 -export([save_current_connection_state/2, next_epoch/2]).
 
@@ -402,6 +402,15 @@ current_connection_state_epoch(#{current_write := #{epoch := Epoch}},
 			       write) ->
     Epoch.
 
+-spec hello_version(dtls_version(), [dtls_version()]) -> dtls_version().
+hello_version(Version, Versions) ->
+    case dtls_v1:corresponding_tls_version(Version) of
+        TLSVersion when TLSVersion >= {3, 3} ->
+            Version;
+        _ ->
+            lowest_protocol_version(Versions)
+    end.
+
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl
index b3d08bdfb..de5ca3ddd 100644
--- a/lib/ssl/src/ssl.erl
+++ b/lib/ssl/src/ssl.erl
@@ -1031,15 +1031,15 @@ validate_option(protocol, Value = dtls) ->
 validate_option(Opt, Value) ->
     throw({error, {options, {Opt, Value}}}).
 
-handle_hashsigns_option(Value, {Major, Minor} = Version) when is_list(Value) 
-							      andalso Major >= 3 andalso Minor >= 3->
+handle_hashsigns_option(Value, Version) when is_list(Value) 
+                                             andalso Version >= {3, 3} ->
     case tls_v1:signature_algs(Version, Value) of
 	[] ->
 	    throw({error, {options, no_supported_algorithms, {signature_algs, Value}}});
 	_ ->	
 	    Value
     end;
-handle_hashsigns_option(_, {Major, Minor} = Version) when Major >= 3 andalso Minor >= 3->
+handle_hashsigns_option(_, Version) when Version >= {3, 3} ->
     handle_hashsigns_option(tls_v1:default_signature_algs(Version), Version);
 handle_hashsigns_option(_, _Version) ->
     undefined.
diff --git a/lib/ssl/src/ssl_connection.erl b/lib/ssl/src/ssl_connection.erl
index df9b9e8a6..cc77aa6bf 100644
--- a/lib/ssl/src/ssl_connection.erl
+++ b/lib/ssl/src/ssl_connection.erl
@@ -1689,7 +1689,7 @@ request_client_cert(#state{ssl_options = #ssl_options{verify = verify_peer,
 	ssl_record:pending_connection_state(ConnectionStates0, read),
     TLSVersion =  ssl:tls_version(Version),
     HashSigns = ssl_handshake:available_signature_algs(SupportedHashSigns, 
-						       TLSVersion, [TLSVersion]),
+						       TLSVersion),
     Msg = ssl_handshake:certificate_request(CipherSuite, CertDbHandle, CertDbRef, 
 					    HashSigns, TLSVersion),
     State = Connection:queue_handshake(Msg, State0),
diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl
index cb61c8233..954b0875c 100644
--- a/lib/ssl/src/ssl_handshake.erl
+++ b/lib/ssl/src/ssl_handshake.erl
@@ -64,7 +64,7 @@
 	]).
 
 %% Cipher suites handling
--export([available_suites/2, available_signature_algs/3, cipher_suites/2,
+-export([available_suites/2, available_signature_algs/2, cipher_suites/2,
 	 select_session/11, supported_ecc/1, available_signature_algs/4]).
 
 %% Extensions handling
@@ -121,8 +121,7 @@ server_hello_done() ->
 
 client_hello_extensions(Host, Version, CipherSuites, 
 			#ssl_options{signature_algs = SupportedHashSigns,
-				     eccs = SupportedECCs,
-				     versions = AllVersions} = SslOpts, ConnectionStates, Renegotiation) ->
+				     eccs = SupportedECCs} = SslOpts, ConnectionStates, Renegotiation) ->
     {EcPointFormats, EllipticCurves} =
 	case advertises_ec_ciphers(lists:map(fun ssl_cipher:suite_definition/1, CipherSuites)) of
 	    true ->
@@ -136,7 +135,7 @@ client_hello_extensions(Host, Version, CipherSuites,
        renegotiation_info = renegotiation_info(tls_record, client,
 					       ConnectionStates, Renegotiation),
        srp = SRP,
-       signature_algs = available_signature_algs(SupportedHashSigns, Version, AllVersions),
+       signature_algs = available_signature_algs(SupportedHashSigns, Version),
        ec_point_formats = EcPointFormats,
        elliptic_curves = EllipticCurves,
        alpn = encode_alpn(SslOpts#ssl_options.alpn_advertised_protocols, Renegotiation),
@@ -2150,16 +2149,11 @@ is_member(Suite, SupportedSuites) ->
 select_compression(_CompressionMetodes) ->
     ?NULL.
 
-available_signature_algs(undefined, _, _)  ->
+available_signature_algs(undefined, _)  ->
     undefined;
-available_signature_algs(SupportedHashSigns, {Major, Minor}, AllVersions) when Major >= 3 andalso Minor >= 3 ->
-    case tls_record:lowest_protocol_version(AllVersions) of
-	{3, 3} ->
-	    #hash_sign_algos{hash_sign_algos = SupportedHashSigns};
-	_ ->
-	    undefined
-    end;	
-available_signature_algs(_, _, _) ->
+available_signature_algs(SupportedHashSigns, Version) when Version >= {3, 3} ->
+    #hash_sign_algos{hash_sign_algos = SupportedHashSigns};
+available_signature_algs(_, _) ->
     undefined.
 
 psk_secret(PSKIdentity, PSKLookup) ->
@@ -2346,11 +2340,11 @@ bad_key(#'RSAPrivateKey'{}) ->
 bad_key(#'ECPrivateKey'{}) ->
     unacceptable_ecdsa_key.
 
-available_signature_algs(undefined, SupportedHashSigns, _, {Major, Minor}) when 
-      (Major >= 3) andalso (Minor >= 3) ->
+available_signature_algs(undefined, SupportedHashSigns, _, Version) when 
+      Version >= {3,3} ->
     SupportedHashSigns;
 available_signature_algs(#hash_sign_algos{hash_sign_algos = ClientHashSigns}, SupportedHashSigns, 
-		     _, {Major, Minor}) when (Major >= 3) andalso (Minor >= 3) ->
+                         _, Version) when Version >= {3,3} ->
     sets:to_list(sets:intersection(sets:from_list(ClientHashSigns), 
 				   sets:from_list(SupportedHashSigns)));
 available_signature_algs(_, _, _, _) -> 
diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl
index bda6bf034..ce440d1e7 100644
--- a/lib/ssl/src/tls_connection.erl
+++ b/lib/ssl/src/tls_connection.erl
@@ -220,7 +220,7 @@ init({call, From}, {start, Timeout},
 				       Cache, CacheCb, Renegotiation, Cert),
     
     Version = Hello#client_hello.client_version,
-    HelloVersion = tls_record:lowest_protocol_version(SslOpts#ssl_options.versions),
+    HelloVersion = tls_record:hello_version(Version, SslOpts#ssl_options.versions),
     Handshake0 = ssl_handshake:init_handshake_history(),
     {BinMsg, ConnectionStates, Handshake} =
         encode_handshake(Hello,  HelloVersion, ConnectionStates0, Handshake0, V2HComp),
diff --git a/lib/ssl/src/tls_record.erl b/lib/ssl/src/tls_record.erl
index 065c6dc8a..2d6407677 100644
--- a/lib/ssl/src/tls_record.erl
+++ b/lib/ssl/src/tls_record.erl
@@ -43,7 +43,7 @@
 -export([protocol_version/1,  lowest_protocol_version/1, lowest_protocol_version/2,
 	 highest_protocol_version/1, highest_protocol_version/2,
 	 is_higher/2, supported_protocol_versions/0,
-	 is_acceptable_version/1, is_acceptable_version/2]).
+	 is_acceptable_version/1, is_acceptable_version/2, hello_version/2]).
 
 %% Decoding
 -export([decode_cipher_text/3]).
@@ -277,6 +277,7 @@ supported_protocol_versions([_|_] = Vsns) ->
 		    NewVsns
 	    end
     end.
+
 %%--------------------------------------------------------------------
 %%     
 %% Description: ssl version 2 is not acceptable security risks are too big.
@@ -296,6 +297,11 @@ is_acceptable_version({N,_} = Version, Versions)
 is_acceptable_version(_,_) ->
     false.
 
+-spec hello_version(tls_version(), [tls_version()]) -> tls_version().
+hello_version(Version, _) when Version >= {3, 3} ->
+    Version;
+hello_version(_, Versions) ->
+    lowest_protocol_version(Versions).
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
-- 
2.12.2

openSUSE Build Service is sponsored by