File 3001-OTP-16584-andy-ssl-srp-username-otp-16584.patch of Package erlang

From 2cbf6e434b4fdd271c9aa3e5415b0663018fffa5 Mon Sep 17 00:00:00 2001
From: Ao Song <andy@erlang.org>
Date: Mon, 20 Apr 2020 17:43:48 +0200
Subject: [PATCH 1/2] OTP-16584: andy/ssl/srp-username/otp-16584

Add srp_username in ssl:connection_information/1
---
 lib/ssl/doc/src/ssl.xml        | 37 +++++++++++++++++++++
 lib/ssl/src/ssl.erl            | 41 +++++++++++++++++++----
 lib/ssl/src/ssl_connection.erl |  8 +++--
 lib/ssl/test/ssl_api_SUITE.erl | 74 ++++++++++++++++++++++++++++++++++++++++--
 lib/ssl/test/ssl_test_lib.erl  | 11 +++++++
 5 files changed, 160 insertions(+), 11 deletions(-)

diff --git a/lib/ssl/doc/src/ssl.xml b/lib/ssl/doc/src/ssl.xml
index 4177b2e5cc..ef984a636f 100644
--- a/lib/ssl/doc/src/ssl.xml
+++ b/lib/ssl/doc/src/ssl.xml
@@ -1259,6 +1259,43 @@ fun(srp, Username :: binary(), UserState :: term()) ->
 	  </p></note>
 	</desc>
       </datatype>
+
+      <datatype>
+        <name name="connection_info"/>
+      </datatype>
+
+      <datatype>
+        <name name="common_info"/>
+      </datatype>
+
+      <datatype>
+        <name name="curve_info"/>
+      </datatype>
+
+      <datatype>
+        <name name="ssl_options_info"/>
+      </datatype>
+
+      <datatype>
+        <name name="security_info"/>
+      </datatype>
+
+      <datatype>
+        <name name="old_erl_cipher_suite"/>
+      </datatype>
+
+      <datatype>
+        <name name="connection_info_items"/>
+      </datatype>
+
+      <datatype>
+        <name name="connection_info_item"/>
+      </datatype>
+
+      <datatype>
+        <name name="tls_options_name"/>
+      </datatype>
+
     </datatypes>
 
 <!--
diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl
index 2e6acd5abe..b51eac6121 100644
--- a/lib/ssl/src/ssl.erl
+++ b/lib/ssl/src/ssl.erl
@@ -469,6 +469,37 @@
                                   elliptic_curves => [public_key:oid()],
                                   sni => hostname()}. % exported
 %% -------------------------------------------------------------------------------------------------------
+-type connection_info() :: [common_info() | curve_info() | ssl_options_info() | security_info()].
+-type common_info() :: {protocol, protocol_version()} |
+                       {session_id, session_id()} |
+                       {session_resumption, boolean()} |
+                       {cipher_suite, old_erl_cipher_suite()} |
+                       {selected_cipher_suite, erl_cipher_suite()} |
+                       {sni_hostname, term()} |
+                       {srp_username, term()}.
+-type curve_info() :: {ecc, {named_curve, term()}}.
+-type ssl_options_info() :: tls_option().
+-type security_info() :: {client_random, binary()} |
+                         {server_random, binary()} |
+                         {master_secret, binary()}.
+-type old_erl_cipher_suite() :: {kex_algo(), null | cipher(), null | hash()} |
+                                {kex_algo(), null | cipher(), null | hash(),
+                                 null | hash() | default_prf}.
+-type connection_info_items() :: [connection_info_item()].
+-type connection_info_item() :: protocol |
+                                session_id |
+                                session_resumption |
+                                cipher_suite |
+                                selected_cipher_suite |
+                                sni_hostname |
+                                srp_username |
+                                ecc |
+                                client_random |
+                                server_random |
+                                master_secret |
+                                tls_options_name().
+-type tls_options_name() :: atom().
+%% -------------------------------------------------------------------------------------------------------
 
 %%%--------------------------------------------------------------------
 %%% API
@@ -907,9 +938,7 @@ controlling_process(#sslsocket{pid = {Listen,
 %%--------------------------------------------------------------------
 -spec connection_information(SslSocket) -> {ok, Result} | {error, reason()} when
       SslSocket :: sslsocket(),
-      Result :: [{OptionName, OptionValue}],
-      OptionName :: atom(),
-      OptionValue :: any().
+      Result :: connection_info().
 %%
 %% Description: Return SSL information for the connection
 %%--------------------------------------------------------------------
@@ -928,10 +957,8 @@ connection_information(#sslsocket{pid = {dtls,_}}) ->
 %%--------------------------------------------------------------------
 -spec connection_information(SslSocket, Items) -> {ok, Result} | {error, reason()} when
       SslSocket :: sslsocket(),
-      Items :: [OptionName],
-      Result :: [{OptionName, OptionValue}],
-      OptionName :: atom(),
-      OptionValue :: any().
+      Items :: connection_info_items(),
+      Result :: connection_info().
 %%
 %% Description: Return SSL information for the connection
 %%--------------------------------------------------------------------
diff --git a/lib/ssl/src/ssl_connection.erl b/lib/ssl/src/ssl_connection.erl
index 8e2e794280..0ca5d2268f 100644
--- a/lib/ssl/src/ssl_connection.erl
+++ b/lib/ssl/src/ssl_connection.erl
@@ -1652,7 +1652,9 @@ connection_info(#state{static_env = #static_env{protocol_cb = Connection},
                        handshake_env = #handshake_env{sni_hostname = SNIHostname,
                                                       resumption = Resumption},
                        session = #session{session_id = SessionId,
-                                          cipher_suite = CipherSuite, ecc = ECCCurve},
+                                          cipher_suite = CipherSuite,
+                                          srp_username = SrpUsername,
+                                          ecc = ECCCurve},
 		       connection_env = #connection_env{negotiated_version =  {_,_} = Version}, 
 		       ssl_options = Opts}) ->
     RecordCB = record_cb(Connection),
@@ -1665,12 +1667,14 @@ connection_info(#state{static_env = #static_env{protocol_cb = Connection},
 		    _ ->
 			[]
 		end,
+
     [{protocol, RecordCB:protocol_version(Version)},
      {session_id, SessionId},
      {session_resumption, Resumption},
      {cipher_suite, ssl_cipher_format:suite_legacy(CipherSuiteDef)},
      {selected_cipher_suite, CipherSuiteDef},
-     {sni_hostname, SNIHostname} | CurveInfo] ++ ssl_options_list(Opts).
+     {sni_hostname, SNIHostname},
+     {srp_username, SrpUsername} | CurveInfo] ++ ssl_options_list(Opts).
 
 security_info(#state{connection_states = ConnectionStates}) ->
     #{security_parameters :=
diff --git a/lib/ssl/test/ssl_api_SUITE.erl b/lib/ssl/test/ssl_api_SUITE.erl
index a80363227f..467c034bdc 100644
--- a/lib/ssl/test/ssl_api_SUITE.erl
+++ b/lib/ssl/test/ssl_api_SUITE.erl
@@ -68,7 +68,8 @@ since_1_2() ->
 
 pre_1_3() ->
     [
-     default_reject_anonymous
+     default_reject_anonymous,
+     connection_information_with_srp
     ].
 gen_api_tests() ->
     [
@@ -197,6 +198,14 @@ init_per_testcase(handshake_continue_tls13_client, Config) ->
         false ->
             {skip, "Missing crypto support: TLS 1.3 not supported"}
     end;
+init_per_testcase(connection_information_with_srp, Config) ->
+    PKAlg = proplists:get_value(public_keys, crypto:supports()),
+    case lists:member(srp, PKAlg) of
+        true ->
+            Config;
+        false ->
+            {skip, "Missing SRP crypto support"}
+    end;
 init_per_testcase(_TestCase, Config) ->
     ssl_test_lib:ct_log_supported_protocol_versions(Config),
     ct:timetrap({seconds, 10}),
@@ -304,6 +313,56 @@ connection_information(Config) when is_list(Config) ->
     
     ssl_test_lib:close(Server),
     ssl_test_lib:close(Client).
+
+%%--------------------------------------------------------------------
+connection_information_with_srp() ->
+    [{doc,"Test the result of API function ssl:connection_information/1"
+          "includes srp_username."}].
+connection_information_with_srp(Config) when is_list(Config) ->
+    run_conn_info_srp_test(srp_anon, 'aes_128_cbc', Config).
+
+run_conn_info_srp_test(Kex, Cipher, Config) ->
+    Version = ssl_test_lib:protocol_version(Config),
+    TestCiphers = ssl_test_lib:test_ciphers(Kex, Cipher, Version),
+
+    case TestCiphers of
+        [] ->
+            {skip, {not_sup, Kex, Cipher, Version}};
+        [TestCipher | _T] ->
+            do_run_conn_info_srp_test(TestCipher, Version, Config)
+    end.
+
+do_run_conn_info_srp_test(ErlangCipherSuite, Version, Config) ->
+    {ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
+
+    SOpts = [{user_lookup_fun, {fun ssl_test_lib:user_lookup/3, undefined}}],
+    COpts = [{srp_identity, {"Test-User", "secret"}}],
+
+    ServerOpts = ssl_test_lib:ssl_options(SOpts, Config),
+    ClientOpts = ssl_test_lib:ssl_options(COpts, Config),
+
+    ct:log("Erlang Cipher Suite is: ~p~n", [ErlangCipherSuite]),
+
+    Server = ssl_test_lib:start_server([
+        {node, ServerNode}, {port, 0},
+		{from, self()},
+        {mfa, {?MODULE, check_srp_in_connection_information, [<<"Test-User">>, server]}},
+        {options, [{versions, [Version]}, {ciphers, [ErlangCipherSuite]} |
+                   ServerOpts]}]),
+    Port = ssl_test_lib:inet_port(Server),
+    Client = ssl_test_lib:start_client(
+        [{node, ClientNode}, {port, Port},
+		 {host, Hostname},
+		 {from, self()},
+		 {mfa, {?MODULE, check_srp_in_connection_information, [<<"Test-User">>, client]}},
+		 {options, [{versions, [Version]}, {ciphers, [ErlangCipherSuite]} |
+                    ClientOpts]}]),
+
+    ssl_test_lib:check_result(Server, ok, Client, ok),
+
+    ssl_test_lib:close(Server),
+    ssl_test_lib:close(Client).
+
 %%--------------------------------------------------------------------
 
 secret_connection_info() ->
@@ -1875,7 +1934,18 @@ secret_connection_info_result(Socket) ->
     {ok, [{protocol, Protocol}]} = ssl:connection_information(Socket, [protocol]),
     {ok, ConnInfo} = ssl:connection_information(Socket, [client_random, server_random, master_secret]),
     check_connection_info(Protocol, ConnInfo).
-  
+
+check_srp_in_connection_information(_Socket, _Username, client) ->
+    ok;
+check_srp_in_connection_information(Socket, Username, server) ->
+    {ok, Info} = ssl:connection_information(Socket),
+    ct:log("Info ~p~n", [Info]),
+    case proplists:get_value(srp_username, Info, not_found) of
+        Username ->
+	        ok;
+        not_found ->
+            ct:fail(srp_username_not_found)
+    end.
 
 %% In TLS 1.3 the master_secret field is used to store multiple secrets from the key schedule and it is a tuple.
 %% client_random and server_random are not used in the TLS 1.3 key schedule.
diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl
index 49784a36a0..5addb1122a 100644
--- a/lib/ssl/test/ssl_test_lib.erl
+++ b/lib/ssl/test/ssl_test_lib.erl
@@ -3424,3 +3424,15 @@ pss_params(sha256) ->
         _ ->
             []
     end.
+
+test_ciphers(Kex, Cipher, Version) ->
+    ssl:filter_cipher_suites(
+        ssl:cipher_suites(all, Version) ++ ssl:cipher_suites(anonymous, Version),
+        [{key_exchange,
+          fun(K) when K == Kex -> true;
+             (_) -> false
+          end},
+         {cipher,
+          fun(C) when C == Cipher -> true;
+             (_) -> false
+          end}]).
\ No newline at end of file
-- 
2.16.4

openSUSE Build Service is sponsored by