File 0231-ssl-Make-sure-client-hostname-check-is-run.patch of Package erlang

From db8d19bbfb53d3c3c40ce6067f05710108b47f9d Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 24 Apr 2020 11:43:59 +0200
Subject: [PATCH] ssl: Make sure client hostname check is run

Fix so that the client runs the host name check
also when it uses its own verify_fun.
---
 lib/ssl/src/ssl_certificate.erl |  2 +-
 lib/ssl/src/ssl_handshake.erl   | 15 +++++++++++++--
 lib/ssl/test/ssl_cert_SUITE.erl |  7 +++++++
 lib/ssl/test/ssl_cert_tests.erl | 33 +++++++++++++++++++++++++++++++++
 4 files changed, 54 insertions(+), 3 deletions(-)

diff --git a/lib/ssl/src/ssl_certificate.erl b/lib/ssl/src/ssl_certificate.erl
index e4a95001fe..ade1d396cd 100644
--- a/lib/ssl/src/ssl_certificate.erl
+++ b/lib/ssl/src/ssl_certificate.erl
@@ -133,7 +133,7 @@ file_to_crls(File, DbHandle) ->
     [Bin || {'CertificateList', Bin, not_encrypted} <- List].
 
 %%--------------------------------------------------------------------
--spec validate(term(), {extension, #'Extension'{}} | {bad_cert, atom()} | valid,
+-spec validate(term(), {extension, #'Extension'{}} | {bad_cert, atom()} | valid | valid_peer,
 	       term()) -> {valid, term()} |
 			  {fail, tuple()} |
 			  {unknown, term()}.
diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl
index d32ef0d45c..b02a030452 100644
--- a/lib/ssl/src/ssl_handshake.erl
+++ b/lib/ssl/src/ssl_handshake.erl
@@ -1683,9 +1683,10 @@ validation_fun_and_state(undefined, Role, CertDbHandle, CertDbRef,
 				      SslState)
      end, {Role, CertDbHandle, CertDbRef, {ServerNameIndication, CustomizeHostCheck}, CRLCheck, CRLDbHandle}}.
 
-apply_user_fun(Fun, OtpCert, VerifyResult, UserState0, 
+apply_user_fun(Fun, OtpCert, VerifyResult0, UserState0, 
 	       {_, CertDbHandle, CertDbRef, _, CRLCheck, CRLDbHandle} = SslState, CertPath, LogLevel) when
-      (VerifyResult == valid) or (VerifyResult == valid_peer) ->
+      (VerifyResult0 == valid) or (VerifyResult0 == valid_peer) ->
+    VerifyResult = maybe_check_hostname(OtpCert, VerifyResult0, SslState),
     case Fun(OtpCert, VerifyResult, UserState0) of
 	{Valid, UserState} when (Valid == valid) or (Valid == valid_peer) ->
 	    case crl_check(OtpCert, CRLCheck, CertDbHandle, CertDbRef, 
@@ -1708,6 +1709,16 @@ apply_user_fun(Fun, OtpCert, ExtensionOrError, UserState0, SslState, _CertPath,
 	    {unknown, {SslState, UserState}}
     end.
 
+maybe_check_hostname(OtpCert, valid_peer, SslState) ->
+    case ssl_certificate:validate(OtpCert, valid_peer, SslState) of 
+        {valid, _} ->
+            valid_peer;
+        {fail, Reason} ->
+            Reason
+    end;
+maybe_check_hostname(_, valid, _) ->
+    valid.
+
 handle_path_validation_error({bad_cert, unknown_ca} = Reason, PeerCert, Chain,  
                              Opts, Options, CertDbHandle, CertsDbRef) ->
     handle_incomplete_chain(PeerCert, Chain, Opts, Options, CertDbHandle, CertsDbRef, Reason);
diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl
index 000d8e6ca5..40bfb0939a 100644
--- a/lib/ssl/test/ssl_cert_SUITE.erl
+++ b/lib/ssl/test/ssl_cert_SUITE.erl
@@ -113,6 +113,7 @@ all_version_tests() ->
      client_auth_allow_partial_chain,
      client_auth_do_not_allow_partial_chain,
      client_auth_partial_chain_fun_fail,
+     client_auth_sni,
      missing_root_cert_no_auth,
      missing_root_cert_auth,
      missing_root_cert_auth_user_verify_fun_accept,
@@ -297,6 +298,12 @@ client_auth_partial_chain_fun_fail() ->
 client_auth_partial_chain_fun_fail(Config) when is_list(Config) ->
     ssl_cert_tests:client_auth_partial_chain_fun_fail(Config).
 
+%%--------------------------------------------------------------------
+client_auth_sni() ->
+   ssl_cert_tests:client_auth_sni().
+client_auth_sni(Config) when is_list(Config) ->
+    ssl_cert_tests:client_auth_sni(Config).
+
 %%--------------------------------------------------------------------
 missing_root_cert_no_auth() ->
    ssl_cert_tests:missing_root_cert_no_auth().
diff --git a/lib/ssl/test/ssl_cert_tests.erl b/lib/ssl/test/ssl_cert_tests.erl
index c88daa2185..657ccd2079 100644
--- a/lib/ssl/test/ssl_cert_tests.erl
+++ b/lib/ssl/test/ssl_cert_tests.erl
@@ -161,6 +161,39 @@ client_auth_partial_chain_fun_fail(Config) when is_list(Config) ->
     
     ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, unknown_ca).
 
+%%--------------------------------------------------------------------
+client_auth_sni() ->
+    [{doc, "Check that sni check works with user verify_fun"}].
+client_auth_sni(Config) when is_list(Config) ->
+    ServerOpts0 = ssl_test_lib:ssl_options(server_cert_opts, Config),
+
+    FunAndState = {fun(valid_peer, {bad_cert, unknown_ca}, UserState) ->
+                           {valid_peer, UserState};
+                      (_,{bad_cert, _} = Reason, _) ->                         
+                           {fail, Reason};
+                      (_,{extension, _}, UserState) ->
+                           {unknown, UserState};
+                      (_, valid, UserState) ->
+                           {valid, UserState};
+                      (_, valid_peer, UserState) ->
+                           {valid, UserState}
+                   end, []},
+
+    ClientOpts0 = ssl_test_lib:ssl_options(client_cert_opts, Config),
+    ClientOpts = [{verify, verify_peer}, {verify_fun, FunAndState
+                                         }, {server_name_indication, "localhost"} | ClientOpts0], 
+
+    {ok, ServerCAs} = file:read_file(proplists:get_value(cacertfile, ServerOpts0)),
+    [{_,_,_}, {_, IntermidiateCA, _} | _] = public_key:pem_decode(ServerCAs),
+
+    ServerOpts = [{cacerts, [IntermidiateCA]} |
+                  proplists:delete(cacertfile, ServerOpts0)],
+    %% Basic test if hostname check is not performed the connection will succeed
+    ssl_test_lib:basic_alert(ClientOpts, ServerOpts0, Config, handshake_failure),
+    %% Also test that user verify_fun is run.
+    %% If user verify fun is not used the ALERT will be unknown_ca
+    ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, handshake_failure).
+
 %%--------------------------------------------------------------------
 missing_root_cert_no_auth() ->
      [{doc,"Test that the client succeds if the ROOT CA is unknown in verify_none mode"}].
-- 
2.16.4

openSUSE Build Service is sponsored by