File 4551-ssl-Fix-TLS-1.2-RSASSA-PSS-negotiation.patch of Package erlang

From 4f226461af371dc075fb2cbdd3098d8525c18b7b Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 8 Oct 2021 14:11:08 +0200
Subject: [PATCH 1/2] ssl: Fix TLS-1.2 RSASSA-PSS negotiation

Closes #5255

Due to test case allowing fallback algorithms PSS algorithms where not
properly selected all the way in TLS-1.2 and some algorithm handling
code was missing.
---
 lib/ssl/src/ssl_certificate.erl            |  4 +-
 lib/ssl/src/ssl_cipher.erl                 | 19 ++++++++
 lib/ssl/src/ssl_handshake.erl              | 22 +++++++--
 lib/ssl/test/openssl_client_cert_SUITE.erl | 52 +++++++++++++++++-----
 lib/ssl/test/ssl_cert_SUITE.erl            | 48 ++++++--------------
 lib/ssl/test/ssl_test_lib.erl              | 10 ++++-
 6 files changed, 102 insertions(+), 53 deletions(-)

diff --git a/lib/ssl/src/ssl_certificate.erl b/lib/ssl/src/ssl_certificate.erl
index ebaa9a6bec..375a416b95 100644
--- a/lib/ssl/src/ssl_certificate.erl
+++ b/lib/ssl/src/ssl_certificate.erl
@@ -548,10 +548,10 @@ is_supported_signature_algorithm_1_2(#'OTPCertificate'{signatureAlgorithm =
 is_supported_signature_algorithm_1_2(#'OTPCertificate'{signatureAlgorithm = SignAlg}, SignAlgs) ->
     Scheme = ssl_cipher:signature_algorithm_to_scheme(SignAlg),
     {Hash, Sign, _ } = ssl_cipher:scheme_to_components(Scheme),
-    lists:member({pre_1_3_hash(Hash), pre_1_3_sign(Sign)}, SignAlgs).
+    ssl_cipher:is_supported_sign({pre_1_3_hash(Hash), pre_1_3_sign(Sign)}, ssl_cipher:signature_schemes_1_2(SignAlgs)).
 is_supported_signature_algorithm_1_3(#'OTPCertificate'{signatureAlgorithm = SignAlg}, SignAlgs) ->
     Scheme = ssl_cipher:signature_algorithm_to_scheme(SignAlg),
-    lists:member(Scheme, SignAlgs).
+    ssl_cipher:is_supported_sign(Scheme, SignAlgs).
 
 pre_1_3_sign(rsa_pkcs1) ->
     rsa;
diff --git a/lib/ssl/src/ssl_cipher.erl b/lib/ssl/src/ssl_cipher.erl
index 35b2da773b..5c3df1feb9 100644
--- a/lib/ssl/src/ssl_cipher.erl
+++ b/lib/ssl/src/ssl_cipher.erl
@@ -58,7 +58,9 @@
          calc_mac_hash/4, 
          calc_mac_hash/6,
          is_stream_ciphersuite/1, 
+         is_supported_sign/2,
          signature_scheme/1,
+         signature_schemes_1_2/1,
          scheme_to_components/1, 
          hash_size/1, 
          effective_key_bits/1,
@@ -564,6 +566,23 @@ hash_size(sha384) ->
 hash_size(sha512) ->
     64.
 
+is_supported_sign({Hash, rsa} = SignAlgo, HashSigns) -> %% PRE TLS-1.3
+    lists:member(SignAlgo, HashSigns) orelse
+        lists:member({Hash, rsa_pss_rsae}, HashSigns);
+is_supported_sign(rsa_pkcs1_sha256 = SignAlgo, HashSigns) -> %% TLS-1.3 leagcy
+    lists:member(SignAlgo, HashSigns) orelse
+        lists:member(rsa_pss_rsae_sha256, HashSigns);
+is_supported_sign(rsa_pkcs1_sha384 = SignAlgo, HashSigns) -> %% TLS-1.3 leagcy
+    lists:member(SignAlgo, HashSigns) orelse
+        lists:member(rsa_pss_rsae_sha384, HashSigns);
+is_supported_sign(rsa_pkcs1_sha512 = SignAlgo, HashSigns) -> %% TLS-1.3 leagcy
+    lists:member(SignAlgo, HashSigns) orelse
+        lists:member(rsa_pss_rsae_sha384, HashSigns);
+is_supported_sign(SignAlgo, HashSigns) -> %% PRE TLS-1.3 SignAlgo::tuple() TLS-1.3 SignAlgo::atom()
+    lists:member(SignAlgo, HashSigns).
+
+
+
 %%--------------------------------------------------------------------
 %%% Internal functions
 %%--------------------------------------------------------------------
diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl
index 63fbf5ffff..e7bbea3591 100644
--- a/lib/ssl/src/ssl_handshake.erl
+++ b/lib/ssl/src/ssl_handshake.erl
@@ -997,8 +997,15 @@ available_signature_algs(_, _) ->
 available_signature_algs(undefined, SupportedHashSigns, _, Version) when 
       Version >= {3,3} ->
     SupportedHashSigns;
-available_signature_algs(#hash_sign_algos{hash_sign_algos = ClientHashSigns}, SupportedHashSigns, 
+available_signature_algs(#hash_sign_algos{hash_sign_algos = ClientHashSigns}, SupportedHashSigns0, 
                          _, Version) when Version >= {3,3} ->
+    SupportedHashSigns =
+        case (Version == {3,3}) andalso contains_scheme(SupportedHashSigns0) of
+            true ->
+                ssl_cipher:signature_schemes_1_2(SupportedHashSigns0);
+            false ->
+                SupportedHashSigns0
+        end,
     sets:to_list(sets:intersection(sets:from_list(ClientHashSigns), 
 				   sets:from_list(SupportedHashSigns)));
 available_signature_algs(_, _, _, _) -> 
@@ -3278,6 +3285,15 @@ filter_hashsigns([Suite | Suites], [#{key_exchange := KeyExchange} | Algos], Has
     %% In this case hashsigns is not used as the kexchange is anonaymous
     filter_hashsigns(Suites, Algos, HashSigns, Version, [Suite| Acc]).
 
+do_filter_hashsigns(rsa = SignAlgo, Suite, Suites, Algos, HashSigns, {3,3} = Version, Acc) ->
+    case (lists:keymember(SignAlgo, 2, HashSigns) orelse
+          lists:keymember(rsa_pss_rsae, 2, HashSigns) orelse
+          lists:keymember(rsa_pss_pss, 2, HashSigns)) of
+	true ->
+	    filter_hashsigns(Suites, Algos, HashSigns, Version, [Suite| Acc]);
+	false ->
+	    filter_hashsigns(Suites, Algos, HashSigns, Version, Acc)
+    end;
 do_filter_hashsigns(SignAlgo, Suite, Suites, Algos, HashSigns, Version, Acc) ->
     case lists:keymember(SignAlgo, 2, HashSigns) of
 	true ->
@@ -3390,8 +3406,7 @@ is_acceptable_cert_type(Sign, Types) ->
 
 %% signature_algorithms_cert = undefined
 is_supported_sign(SignAlgo, _, HashSigns, []) ->
-    lists:member(SignAlgo, HashSigns);
-
+    ssl_cipher:is_supported_sign(SignAlgo, HashSigns);
 %% {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}
 is_supported_sign({Hash, Sign}, 'NULL', _, SignatureSchemes) ->
     Fun = fun (Scheme, Acc) ->
@@ -3408,7 +3423,6 @@ is_supported_sign({Hash, Sign}, 'NULL', _, SignatureSchemes) ->
                               Hash =:= H1)
           end,
     lists:foldl(Fun, false, SignatureSchemes);
-
 %% TODO: Implement validation for the curve used in the signature
 %% RFC 3279 - 2.2.3 ECDSA Signature Algorithm
 %% When the ecdsa-with-SHA1 algorithm identifier appears as the
diff --git a/lib/ssl/test/openssl_client_cert_SUITE.erl b/lib/ssl/test/openssl_client_cert_SUITE.erl
index ad00f2da1f..c78bd9eadc 100644
--- a/lib/ssl/test/openssl_client_cert_SUITE.erl
+++ b/lib/ssl/test/openssl_client_cert_SUITE.erl
@@ -82,7 +82,7 @@ groups() ->
     [
      {openssl_client, [], protocol_groups()},
      {'tlsv1.3', [], tls_1_3_protocol_groups()},
-     {'tlsv1.2', [], pre_tls_1_3_protocol_groups()},
+     {'tlsv1.2', [], pre_tls_1_3_protocol_groups()}, %% Seems to be broken in OpenSSL [{group, rsa_pss_rsae}, {group, rsa_pss_pss}]},
      {'tlsv1.1', [], pre_tls_1_3_protocol_groups()},
      {'tlsv1', [], pre_tls_1_3_protocol_groups()},
      {'dtlsv1.2', [], pre_tls_1_3_protocol_groups()},
@@ -92,8 +92,10 @@ groups() ->
      {dsa, [], all_version_tests()},
      {rsa_1_3, [], all_version_tests() ++ tls_1_3_tests() ++ [unsupported_sign_algo_client_auth,
                                                               unsupported_sign_algo_cert_client_auth]},
-     {rsa_pss_rsae, [], all_version_tests() ++ tls_1_3_tests()},
+     {rsa_pss_rsae, [], all_version_tests()},
      {rsa_pss_pss, [], all_version_tests() ++ tls_1_3_tests()},
+     {rsa_pss_rsae_1_3, [], all_version_tests() ++ tls_1_3_tests()},
+     {rsa_pss_pss_1_3, [], all_version_tests() ++ tls_1_3_tests()},
      {ecdsa_1_3, [], all_version_tests() ++ tls_1_3_tests()},
      {eddsa_1_3, [], all_version_tests() ++ tls_1_3_tests()}
     ].
@@ -122,8 +124,8 @@ pre_tls_1_3_protocol_groups() ->
 
 tls_1_3_protocol_groups() ->
     [{group, rsa_1_3},
-     {group, rsa_pss_rsae},
-     {group, rsa_pss_pss},
+     {group, rsa_pss_rsae_1_3},
+     {group, rsa_pss_pss_1_3},
      {group, ecdsa_1_3},
      {group, eddsa_1_3}
     ].
@@ -198,23 +200,26 @@ init_per_group(Group, Config0) when Group == rsa;
         [] ->
             {skip, {no_sup, Group, Version}}
     end;
-init_per_group(Alg, Config) when Alg == rsa_pss_rsae;
-                                 Alg == rsa_pss_pss ->
+init_per_group(Alg, Config) when 
+      Alg == rsa_pss_rsae;
+      Alg == rsa_pss_pss;
+      Alg == rsa_pss_rsae_1_3;
+      Alg == rsa_pss_pss_1_3 ->
     Supports = crypto:supports(),
     RSAOpts = proplists:get_value(rsa_opts, Supports),
     
     case lists:member(rsa_pkcs1_pss_padding, RSAOpts) 
         andalso lists:member(rsa_pss_saltlen, RSAOpts) 
         andalso lists:member(rsa_mgf1_md, RSAOpts)
-        andalso ssl_test_lib:is_sane_oppenssl_pss(Alg)
+        andalso ssl_test_lib:is_sane_oppenssl_pss(rsa_alg(Alg))
     of
         true ->
             #{client_config := COpts,
-              server_config := SOpts} = ssl_test_lib:make_rsa_pss_pem(Alg, [], Config, ""),
-            [{cert_key_alg, Alg} |
+              server_config := SOpts} = ssl_test_lib:make_rsa_pss_pem(rsa_alg(Alg), [], Config, ""),
+            [{cert_key_alg, rsa_alg(Alg)} |
              lists:delete(cert_key_alg,
-                          [{client_cert_opts, COpts},
-                           {server_cert_opts, SOpts} |
+                          [{client_cert_opts, openssl_sig_algs(Alg) ++ COpts},
+                           {server_cert_opts, sig_algs(rsa_alg(Alg)) ++ SOpts} |
                            lists:delete(server_cert_opts,
                                         lists:delete(client_cert_opts, Config))])];
         false ->
@@ -433,3 +438,28 @@ hello_retry_client_auth_empty_cert_rejected() ->
     ssl_cert_tests:hello_retry_client_auth_empty_cert_rejected().
 hello_retry_client_auth_empty_cert_rejected(Config) ->
    ssl_cert_tests:hello_retry_client_auth_empty_cert_rejected(Config).
+
+rsa_alg(rsa_pss_rsae_1_3) ->
+    rsa_pss_rsae;
+rsa_alg(rsa_pss_pss_1_3) ->
+    rsa_pss_pss;
+rsa_alg(Atom) ->
+    Atom.
+
+sig_algs(rsa_pss_pss) ->
+    [{signature_algs, [rsa_pss_pss_sha512,
+                       rsa_pss_pss_sha384,
+                       rsa_pss_pss_sha256]}];
+sig_algs(rsa_pss_rsae) ->
+    [{signature_algs,[rsa_pss_rsae_sha512,
+                      rsa_pss_rsae_sha384,
+                      rsa_pss_rsae_sha256]}].
+
+openssl_sig_algs(rsa_pss_pss) ->
+    [{sigalgs, "rsa_pss_pss_sha256"}];
+openssl_sig_algs(rsa_pss_rsae) ->
+    [{sigalgs,"rsa_pss_rsae_sha256"}];
+openssl_sig_algs(rsa_pss_pss_1_3) ->
+    [{sigalgs, "rsa_pss_rsae_sha512:rsa_pss_rsae_sha384:rsa_pss_pss_sha256"}];
+openssl_sig_algs(rsa_pss_rsae_1_3) ->
+    [{sigalgs,"rsa_pss_rsae_sha512:rsa_pss_rsae_sha384:rsa_pss_rsae_sha256"}].
diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl
index 42c44e4855..1eef4a48be 100644
--- a/lib/ssl/test/ssl_cert_SUITE.erl
+++ b/lib/ssl/test/ssl_cert_SUITE.erl
@@ -146,11 +146,11 @@ groups() ->
      {'tlsv1', [], ssl_protocol_groups()},
      {'dtlsv1.2', [], tls_1_2_protocol_groups()},
      {'dtlsv1', [], ssl_protocol_groups()},
-     {rsa, [], all_version_tests() ++ rsa_tests() ++ pre_tls_1_3_rsa_tests()},
+     {rsa, [], all_version_tests() ++ rsa_tests() ++ pre_tls_1_3_rsa_tests() ++ [client_auth_seelfsigned_peer]},
      {ecdsa, [], all_version_tests()},
      {dsa, [], all_version_tests()},
      {rsa_1_3, [], all_version_tests() ++ rsa_tests() ++
-          tls_1_3_tests() ++ tls_1_3_rsa_tests() ++ [basic_rsa_1024]},
+          tls_1_3_tests() ++ tls_1_3_rsa_tests() ++ [client_auth_seelfsigned_peer, basic_rsa_1024]},
      {rsa_pss_rsae, [], all_version_tests() ++ tls_1_2_rsa_tests()},
      {rsa_pss_rsae_1_3, [], all_version_tests() ++ rsa_tests() ++ tls_1_3_tests() ++ tls_1_3_rsa_tests()},
      {rsa_pss_pss, [], all_version_tests()},
@@ -226,7 +226,6 @@ all_version_tests() ->
      client_auth_do_not_allow_partial_chain,
      client_auth_partial_chain_fun_fail,
      client_auth_sni,
-     client_auth_seelfsigned_peer,
      missing_root_cert_no_auth,
      missing_root_cert_auth,
      missing_root_cert_auth_user_verify_fun_accept,
@@ -296,37 +295,9 @@ do_init_per_group(Alg, Config) when Alg == rsa_pss_rsae;
         true ->
             #{client_config := COpts,
               server_config := SOpts} = ssl_test_lib:make_rsa_pss_pem(rsa_alg(Alg), [], Config, ""),
-            [{cert_key_alg, rsa_alg(Alg)},
-             {extra_client, [{signature_algs, [rsa_pss_pss_sha512,
-                                               rsa_pss_pss_sha384,
-                                               rsa_pss_pss_sha256,
-                                               rsa_pss_rsae_sha512,
-                                               rsa_pss_rsae_sha384,
-                                               rsa_pss_rsae_sha256,
-                                               rsa_pkcs1_sha512,
-                                               rsa_pkcs1_sha384,
-                                               rsa_pkcs1_sha256,
-                                               rsa_pkcs1_sha1,
-                                               {sha512, rsa},
-                                               {sha384, rsa},
-                                               {sha256, rsa},
-                                               {sha224, rsa}
-                                              ]}]},
-             {extra_server, [{signature_algs, [rsa_pss_pss_sha512,
-                                               rsa_pss_pss_sha384,
-                                               rsa_pss_pss_sha256,
-                                               rsa_pss_rsae_sha512,
-                                               rsa_pss_rsae_sha384,
-                                               rsa_pss_rsae_sha256,
-                                               {sha512, ecdsa},
-                                               {sha512, rsa},
-                                               {sha384, ecdsa},
-                                               {sha384, rsa},
-                                               {sha256, ecdsa},
-                                               {sha256, rsa},
-                                               {sha224, ecdsa},
-                                               {sha224, rsa}
-                                              ]}]} |
+            [{cert_key_alg, Alg},
+             {extra_client, sig_algs(Alg)},
+             {extra_server, sig_algs(Alg)} |
              lists:delete(cert_key_alg,
                           [{client_cert_opts, COpts},
                            {server_cert_opts, SOpts} |
@@ -1317,3 +1288,12 @@ chain_and_root(Config) ->
     {ok, ExtractedCAs} = ssl_pkix_db:extract_trusted_certs({der, proplists:get_value(cacerts, Config)}),
     {ok, Root, Chain} = ssl_certificate:certificate_chain(OwnCert, ets:new(foo, []), ExtractedCAs, [], encoded),
     {Chain, Root}.
+
+sig_algs(rsa_pss_pss) ->
+    [{signature_algs, [rsa_pss_pss_sha512,
+                       rsa_pss_pss_sha384,
+                       rsa_pss_pss_sha256]}];
+sig_algs(rsa_pss_rsae) ->
+    [{signature_algs, [rsa_pss_rsae_sha512,
+                       rsa_pss_rsae_sha384,
+                       rsa_pss_rsae_sha256]}].
diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl
index e4c23c22cf..183899e5f2 100644
--- a/lib/ssl/test/ssl_test_lib.erl
+++ b/lib/ssl/test/ssl_test_lib.erl
@@ -2080,6 +2080,7 @@ start_client(openssl, Port, ClientOpts, Config) ->
     Ciphers = proplists:get_value(ciphers, ClientOpts, ssl:cipher_suites(default,Version)),
     Groups0 = proplists:get_value(groups, ClientOpts),
     CertArgs = openssl_cert_options(ClientOpts, client),
+    SigAlgs = openssl_sigalgs(proplists:get_value(sigalgs, ClientOpts, undefined)),
     AlpnArgs = openssl_alpn_options(proplists:get_value(alpn, ClientOpts, undefined)),
     NpnArgs =  openssl_npn_options(proplists:get_value(np, ClientOpts, undefined)),                          
     Reconnect = openssl_reconect_option(proplists:get_value(reconnect, ClientOpts, false)),  
@@ -2096,7 +2097,7 @@ start_client(openssl, Port, ClientOpts, Config) ->
                       "-connect", hostname_format(HostName) ++ ":" ++ integer_to_list(Port), cipher_flag(Version),
                       ciphers(Ciphers, Version),
                       version_flag(Version)]
-                         ++ CertArgs ++ AlpnArgs ++ NpnArgs ++ Reconnect ++ MaxFragLen ++ SessionArgs
+                         ++ CertArgs ++ SigAlgs ++ AlpnArgs ++ NpnArgs ++ Reconnect ++ MaxFragLen ++ SessionArgs
                          ++ Debug;
                  Group ->
                      ["s_client",
@@ -2104,7 +2105,7 @@ start_client(openssl, Port, ClientOpts, Config) ->
                       "-connect", hostname_format(HostName) ++ ":" ++ integer_to_list(Port), cipher_flag(Version),
                       ciphers(Ciphers, Version), "-groups", Group,
                       version_flag(Version)]
-                         ++ CertArgs ++ AlpnArgs ++ NpnArgs ++ Reconnect ++ MaxFragLen ++ SessionArgs
+                         ++ CertArgs ++ SigAlgs ++ AlpnArgs ++ NpnArgs ++ Reconnect ++ MaxFragLen ++ SessionArgs
                          ++ Debug
                  end,
     Args = maybe_force_ipv4(Args0),
@@ -2347,6 +2348,11 @@ cert_option("-cert_chain", Value) ->
 cert_option(Opt, Value) ->
     [Opt, Value].
 
+openssl_sigalgs(undefined) ->
+    [];
+openssl_sigalgs(SigAlgs) ->
+    ["-sigalgs", SigAlgs].
+
 supported_eccs(Opts) ->
     ToCheck = proplists:get_value(eccs, Opts, []),
     Supported = ssl:eccs(),
-- 
2.31.1

openSUSE Build Service is sponsored by