File 4521-ssl-Add-support-for-RSASSA-PSS-in-TLS-1.2.patch of Package erlang
From defc7aaf14924d145ec32f34d9f761960b0d0084 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Mon, 26 Jul 2021 15:29:00 +0200
Subject: [PATCH 1/4] ssl: Add support for RSASSA-PSS in TLS-1.2
closes #5029
Also optimizes sign/verify handling so that hash calculation can be done in same
call to crypto as sign/verify when possible.
---
lib/ssl/doc/src/ssl.xml | 161 ++++++++----
lib/ssl/doc/src/standards_compliance.xml | 4 +-
lib/ssl/src/dtls_connection.erl | 2 +-
lib/ssl/src/dtls_handshake.erl | 13 +-
lib/ssl/src/ssl.erl | 31 ++-
lib/ssl/src/ssl_certificate.erl | 44 +++-
lib/ssl/src/ssl_cipher.erl | 16 +-
lib/ssl/src/ssl_handshake.erl | 312 ++++++++++++++---------
lib/ssl/src/tls_dtls_connection.erl | 39 +--
lib/ssl/src/tls_handshake.erl | 24 +-
lib/ssl/src/tls_handshake_1_3.erl | 18 +-
lib/ssl/src/tls_v1.erl | 78 ++++--
lib/ssl/test/ssl_cert_SUITE.erl | 168 +++++++-----
lib/ssl/test/ssl_cert_tests.erl | 54 ++--
lib/ssl/test/ssl_handshake_SUITE.erl | 16 +-
lib/ssl/test/ssl_test_lib.erl | 5 +
16 files changed, 612 insertions(+), 373 deletions(-)
diff --git a/lib/ssl/doc/src/ssl.xml b/lib/ssl/doc/src/ssl.xml
index 29d2a4670d..807d292c63 100644
--- a/lib/ssl/doc/src/ssl.xml
+++ b/lib/ssl/doc/src/ssl.xml
@@ -196,10 +196,6 @@
<name name="old_cipher_suite"/>
</datatype>
- <datatype>
- <name name="signature_algs"/>
- </datatype>
-
<datatype>
<name name="sign_algo"/>
</datatype>
@@ -208,6 +204,14 @@
<name name="sign_scheme"/>
</datatype>
+ <datatype>
+ <name name="rsassa_pss_scheme"/>
+ </datatype>
+
+ <datatype>
+ <name name="sign_scheme_legacy"/>
+ </datatype>
+
<datatype>
<name name="group"/>
</datatype>
@@ -393,9 +397,103 @@
</p>
</desc>
</datatype>
-
+
+
+ <datatype>
+ <name name="signature_algs"/>
+ <desc>
+
+ <p>Explicitly list acceptable signature algorithms for certificates and handshake messages
+ in the preferred order. The client will send its list as the client hello <c>signature_algorithm</c> extension
+ introduced in TLS-1.2, see <url href="http://www.ietf.org/rfc/rfc5246.txt">Section 7.4.1.4.1 in RFC 5246</url>.
+ Previously these algorithms where implicitly chosen and partly derived from the cipher suite. </p>
+
+ <p>In TLS-1.2 a somewhat more explicit negotiation is made possible using a list of
+ {<seetype marker="#hash">hash()</seetype>, <seetype marker="#signature_algs">sign_algo()</seetype>} pairs.
+ </p>
+
+ <p>In TLS-1.3 these algorithm pairs are
+ replaced by so called signature schemes <seetype marker="#sign_scheme">sign_scheme()</seetype>
+ and completely decoupled from the cipher suite.
+ </p>
+
+ <p>Signature algorithms used for certificates may be overridden by the
+ <seetype marker="#sign_schemes">signature schemes</seetype> (algorithms) supplied by the <c>signature_algs_cert</c> option.</p>
+
+ <p>TLS-1.2 default is</p>
+
+ <p><c>Default_TLS_12_Alg_Pairs =</c></p>
+ <code>[
+%% SHA2
+{sha512, ecdsa},
+{sha512, rsa},
+{sha384, ecdsa},
+{sha384, rsa},
+{sha256, ecdsa},
+{sha256, rsa},
+{sha224, ecdsa},
+{sha224, rsa},
+%% SHA
+{sha, ecdsa},
+{sha, rsa},
+{sha, dsa}
+]
+ </code>
+
+ <p>Support for {md5, rsa} was removed from the the TLS-1.2 default in ssl-8.0 (OTP-22) </p>
+
+
+ <p><c> TLS_13 _Legacy_Schemes =</c></p>
+ <code> [
+ %% Legacy algorithms only applicable to certificate signatures
+rsa_pkcs1_sha512, %% Corresponds to {sha512, rsa}
+rsa_pkcs1_sha384, %% Corresponds to {sha384, rsa}
+rsa_pkcs1_sha256, %% Corresponds to {sha256, rsa}
+ecdsa_sha1, %% Corresponds to {sha, ecdsa}
+rsa_pkcs1_sha1 %% Corresponds to {sha, rsa}
+]
+</code>
+
+ <p><c> Default_TLS_13_Schemes =</c></p>
+ <code> [
+%% ECDSA
+ecdsa_secp521r1_sha512,
+ecdsa_secp384r1_sha384,
+ecdsa_secp256r1_sha256,
+%% RSASSA-PSS
+rsa_pss_pss_sha512,
+rsa_pss_pss_sha384,
+rsa_pss_pss_sha256,
+rsa_pss_rsae_sha512,
+rsa_pss_rsae_sha384,
+rsa_pss_rsae_sha256,
+%% EDDSA
+eddsa_ed25519,
+eddsa_ed448]
+</code>
+
+<p>TLS-1.3 default is</p>
+<code>Default_TLS_13_Schemes ++ Legacy_TLS_13_Schemes </code>
+
+<p>If both TLS-1.3 and TLS-1.2 are supported the default will be</p>
+<code>Default_TLS_13_Schemes ++ Default_TLS_12_Alg_Pairs </code>
+
+<p>so appropriate algorithms can be chosen for the negotiated
+version.
+</p>
+
+<note> <p> TLS-1.2 algorithms will not be negotiated for TLS-1.3, but TLS-1.3 RSASSA-PSS <seetype marker="#rsassa_pss_scheme">rsassa_pss_scheme()</seetype>
+ signature schemes may be negotiated also for TLS-1.2 from @OTP-16590@
+ However if TLS-1.3 is negotiated when both TLS-1.3 and TLS-1.2 is supported using defaults, the corresponding TLS-1.2 algorithms
+ to the TLS-1.3 legacy signature schemes will be considered as the legacy schemes and applied only to certificate signatures.
+ </p>
+ </note>
+
+ </desc>
+ </datatype>
+
<datatype>
- <name name="signature_schemes"/>
+ <name name="sign_schemes"/>
<desc>
<p>
In addition to the signature_algorithms extension from TLS 1.2,
@@ -973,43 +1071,7 @@ fun(srp, Username :: binary(), UserState :: term()) ->
</p></warning>
</desc>
</datatype>
-
- <datatype>
- <name name="client_signature_algs"/>
- <desc>
- <p>In addition to the algorithms negotiated by the cipher
- suite used for key exchange, payload encryption, message
- authentication and pseudo random calculation, the TLS signature
- algorithm extension <url
- href="http://www.ietf.org/rfc/rfc5246.txt">Section 7.4.1.4.1 in RFC 5246</url> may be
- used, from TLS 1.2, to negotiate which signature algorithm to use during the
- TLS handshake. If no lower TLS versions than 1.2 are supported,
- the client will send a TLS signature algorithm extension
- with the algorithms specified by this option.
- Defaults to</p>
-
- <code>[
-%% SHA2
-{sha512, ecdsa},
-{sha512, rsa},
-{sha384, ecdsa},
-{sha384, rsa},
-{sha256, ecdsa},
-{sha256, rsa},
-{sha224, ecdsa},
-{sha224, rsa},
-%% SHA
-{sha, ecdsa},
-{sha, rsa},
-{sha, dsa},
-]</code>
-<p>
- The algorithms should be in the preferred order.
- Selected signature algorithm can restrict which hash functions
- that may be selected. Default support for {md5, rsa} removed in ssl-8.0
- </p>
- </desc>
- </datatype>
+
<datatype>
<name name="client_session_tickets"/>
@@ -1273,19 +1335,6 @@ fun(srp, Username :: binary(), UserState :: term()) ->
</desc>
</datatype>
- <datatype>
- <name name="server_signature_algs"/>
- <desc><p> The algorithms specified by this option will be the
- ones accepted by the server in a signature algorithm
- negotiation, introduced in TLS-1.2. The algorithms will also
- be offered to the client if a client certificate is
- requested. For more details see the <seetype
- marker="#client_signature_algs">corresponding client
- option</seetype>.
- </p>
- </desc>
- </datatype>
-
<datatype>
<name name="server_session_tickets"/>
<desc>
diff --git a/lib/ssl/doc/src/standards_compliance.xml b/lib/ssl/doc/src/standards_compliance.xml
index 7b12a15261..0fe67b8734 100644
--- a/lib/ssl/doc/src/standards_compliance.xml
+++ b/lib/ssl/doc/src/standards_compliance.xml
@@ -177,8 +177,8 @@
<row>
<cell align="left" valign="middle"></cell>
<cell align="left" valign="middle">RSASSA-PSS signature schemes</cell>
- <cell align="left" valign="middle"><em>PC</em></cell>
- <cell align="left" valign="middle"><em>23</em></cell>
+ <cell align="left" valign="middle"><em>C</em></cell>
+ <cell align="left" valign="middle"><em>@OTP-16590@</em></cell>
</row>
<row>
<cell align="left" valign="middle"></cell>
diff --git a/lib/ssl/src/dtls_connection.erl b/lib/ssl/src/dtls_connection.erl
index 78348826e4..1a4f001273 100644
--- a/lib/ssl/src/dtls_connection.erl
+++ b/lib/ssl/src/dtls_connection.erl
@@ -650,7 +650,7 @@ handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State
connection_env = CEnv#connection_env{negotiated_version = Version},
handshake_env = HsEnv#handshake_env{
hashsign_algorithm = HashSign,
- client_hello_version = ClientVersion,
+ client_hello_version = ClientVersion,
negotiated_protocol = Protocol},
session = Session}),
{next_state, hello, State, [{next_event, internal, {common_client_hello, Type, ServerHelloExt}}]}
diff --git a/lib/ssl/src/dtls_handshake.erl b/lib/ssl/src/dtls_handshake.erl
index b8f9d7f42b..9999933d90 100644
--- a/lib/ssl/src/dtls_handshake.erl
+++ b/lib/ssl/src/dtls_handshake.erl
@@ -76,11 +76,14 @@ client_hello(_Host, _Port, Cookie, ConnectionStates,
TLSVersion = dtls_v1:corresponding_tls_version(Version),
CipherSuites = ssl_handshake:available_suites(UserSuites, TLSVersion),
- Extensions = ssl_handshake:client_hello_extensions(TLSVersion, CipherSuites,
- SslOpts, ConnectionStates,
- Renegotiation, undefined,
- undefined, OcspNonce),
-
+ Extensions = ssl_handshake:client_hello_extensions(TLSVersion,
+ CipherSuites,
+ SslOpts,
+ ConnectionStates,
+ Renegotiation,
+ undefined,
+ undefined,
+ OcspNonce),
#client_hello{session_id = Id,
client_version = Version,
cipher_suites =
diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl
index b6a5bf20a4..17e6b7fcb2 100644
--- a/lib/ssl/src/ssl.erl
+++ b/lib/ssl/src/ssl.erl
@@ -190,22 +190,29 @@
-type sign_algo() :: rsa | dsa | ecdsa | eddsa. % exported
+-type sign_schemes() :: [sign_scheme()].
+
-type sign_scheme() :: eddsa_ed25519
| eddsa_ed448
| ecdsa_secp256r1_sha256
| ecdsa_secp384r1_sha384
| ecdsa_secp521r1_sha512
- | rsa_pss_rsae_sha256
+ | rsassa_pss_scheme()
+ | sign_scheme_legacy() . % exported
+
+-type rsassa_pss_scheme() :: rsa_pss_rsae_sha256
| rsa_pss_rsae_sha384
| rsa_pss_rsae_sha512
| rsa_pss_pss_sha256
| rsa_pss_pss_sha384
- | rsa_pss_pss_sha512
- | rsa_pkcs1_sha256
+ | rsa_pss_pss_sha512.
+
+-type sign_scheme_legacy() :: rsa_pkcs1_sha256
| rsa_pkcs1_sha384
| rsa_pkcs1_sha512
| rsa_pkcs1_sha1
- | ecdsa_sha1. % exported
+ | ecdsa_sha1.
+
-type kex_algo() :: rsa |
dhe_rsa | dhe_dss |
@@ -306,7 +313,8 @@
{password, key_password()} |
{ciphers, cipher_suites()} |
{eccs, [named_curve()]} |
- {signature_algs_cert, signature_schemes()} |
+ {signature_algs, signature_algs()} |
+ {signature_algs_cert, sign_schemes()} |
{supported_groups, supported_groups()} |
{secure_renegotiate, secure_renegotiation()} |
{keep_secrets, keep_secrets()} |
@@ -359,8 +367,7 @@
-type hibernate_after() :: timeout().
-type root_fun() :: fun().
-type protocol_versions() :: [protocol_version()].
--type signature_algs() :: [{hash(), sign_algo()}].
--type signature_schemes() :: [sign_scheme()].
+-type signature_algs() :: [{hash(), sign_algo()} | sign_scheme()].
-type supported_groups() :: [group()].
-type custom_user_lookup() :: {Lookupfun :: fun(), UserState :: any()}.
-type padding_check() :: boolean().
@@ -399,7 +406,6 @@
{server_name_indication, sni()} |
{max_fragment_length, max_fragment_length()} |
{customize_hostname_check, customize_hostname_check()} |
- {signature_algs, client_signature_algs()} |
{fallback, fallback()} |
{session_tickets, client_session_tickets()} |
{use_ticket, use_ticket()} |
@@ -425,7 +431,6 @@
-type customize_hostname_check() :: list().
-type sni() :: HostName :: hostname() | disable.
-type max_fragment_length() :: undefined | 512 | 1024 | 2048 | 4096.
--type client_signature_algs() :: signature_algs().
-type fallback() :: boolean().
-type ssl_imp() :: new | old.
%% -type ocsp_stapling() :: boolean().
@@ -450,7 +455,6 @@
{honor_cipher_order, honor_cipher_order()} |
{honor_ecc_order, honor_ecc_order()} |
{client_renegotiation, client_renegotiation()}|
- {signature_algs, server_signature_algs()} |
{session_tickets, server_session_tickets()} |
{anti_replay, anti_replay()} |
{cookie, cookie()} |
@@ -465,7 +469,6 @@
-type dh_file() :: file:filename().
-type server_verify_type() :: verify_type().
-type fail_if_no_peer_cert() :: boolean().
--type server_signature_algs() :: signature_algs().
-type server_reuse_session() :: fun().
-type server_reuse_sessions() :: boolean().
-type sni_hosts() :: [{hostname(), [server_option() | common_option()]}].
@@ -1782,12 +1785,12 @@ handle_option(session_tickets = Option, Value0, #{versions := Versions} = Option
assert_option_dependency(Option, versions, Versions, ['tlsv1.3']),
Value = validate_option(Option, Value0, Role),
OptionsMap#{Option => Value};
-handle_option(signature_algs = Option, unbound, #{versions := [HighestVersion|_]} = OptionsMap, #{role := Role}) ->
+handle_option(signature_algs = Option, unbound, #{versions := [HighestVersion | _] = Versions} = OptionsMap, #{role := Role}) ->
Value =
handle_hashsigns_option(
default_option_role_sign_algs(
server,
- tls_v1:default_signature_algs(HighestVersion),
+ tls_v1:default_signature_algs(Versions),
Role,
HighestVersion),
tls_version(HighestVersion)),
@@ -2434,7 +2437,7 @@ handle_hashsigns_option(Value, Version) when is_list(Value)
Value
end;
handle_hashsigns_option(_, Version) when Version =:= {3, 3} ->
- handle_hashsigns_option(tls_v1:default_signature_algs(Version), Version);
+ handle_hashsigns_option(tls_v1:default_signature_algs([Version]), Version);
handle_hashsigns_option(_, _Version) ->
undefined.
diff --git a/lib/ssl/src/ssl_certificate.erl b/lib/ssl/src/ssl_certificate.erl
index 6afad3b9c0..cbeb4e4521 100644
--- a/lib/ssl/src/ssl_certificate.erl
+++ b/lib/ssl/src/ssl_certificate.erl
@@ -263,16 +263,21 @@ extensions_list(Extensions) ->
Extensions.
%%--------------------------------------------------------------------
--spec public_key_type(term()) -> rsa | dsa | ec.
+-spec public_key_type(term()) -> rsa | rsa_pss_pss | dsa | ecdsa | eddsa.
%%
%% Description:
%%--------------------------------------------------------------------
+public_key_type(?'id-RSASSA-PSS') ->
+ rsa_pss_pss;
public_key_type(?'rsaEncryption') ->
rsa;
public_key_type(?'id-dsa') ->
dsa;
public_key_type(?'id-ecPublicKey') ->
- ec.
+ ecdsa;
+public_key_type(Oid) ->
+ {_, Sign} = public_key:pkix_sign_types(Oid),
+ Sign.
%%--------------------------------------------------------------------
-spec foldl_db(fun(), db_handle() | {extracted, list()}, list()) ->
@@ -519,21 +524,34 @@ verify_cert_extensions(Cert, UserState, [_|Exts], Context) ->
verify_sign(_, #{version := {_, Minor}}) when Minor < 3 ->
%% This verification is not applicable pre TLS-1.2
true;
-verify_sign(Cert, #{signature_algs := SignAlgs,
+verify_sign(Cert, #{version := {3, 3},
+ signature_algs := SignAlgs,
signature_algs_cert := undefined}) ->
- is_supported_signature_algorithm(Cert, SignAlgs);
-verify_sign(Cert, #{signature_algs_cert := SignAlgs}) ->
- is_supported_signature_algorithm(Cert, SignAlgs).
-
-is_supported_signature_algorithm(#'OTPCertificate'{signatureAlgorithm =
- #'SignatureAlgorithm'{algorithm = ?'id-dsa-with-sha1'}},
- [{_,_}|_] = SignAlgs) ->
+ is_supported_signature_algorithm_1_2(Cert, SignAlgs);
+verify_sign(Cert, #{version := {3, 3},
+ signature_algs_cert := SignAlgs}) ->
+ is_supported_signature_algorithm_1_2(Cert, SignAlgs);
+verify_sign(Cert, #{version := {3, 4},
+ signature_algs := SignAlgs,
+ signature_algs_cert := undefined}) ->
+ is_supported_signature_algorithm_1_3(Cert, SignAlgs);
+verify_sign(Cert, #{version := {3, 4},
+ signature_algs_cert := SignAlgs}) ->
+ is_supported_signature_algorithm_1_3(Cert, SignAlgs).
+
+is_supported_signature_algorithm_1_2(#'OTPCertificate'{signatureAlgorithm =
+ #'SignatureAlgorithm'{algorithm = ?'id-dsa-with-sha1'}},
+ SignAlgs) ->
lists:member({sha, dsa}, SignAlgs);
-is_supported_signature_algorithm(#'OTPCertificate'{signatureAlgorithm = SignAlg}, [{_,_}|_] = SignAlgs) ->
+is_supported_signature_algorithm_1_2(#'OTPCertificate'{signatureAlgorithm =
+ #'SignatureAlgorithm'{algorithm = ?'id-RSASSA-PSS'}} = Cert,
+ SignAlgs) ->
+ is_supported_signature_algorithm_1_3(Cert, SignAlgs);
+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);
-is_supported_signature_algorithm(#'OTPCertificate'{signatureAlgorithm = SignAlg}, SignAlgs) ->
+ lists:member({pre_1_3_hash(Hash), pre_1_3_sign(Sign)}, SignAlgs).
+is_supported_signature_algorithm_1_3(#'OTPCertificate'{signatureAlgorithm = SignAlg}, SignAlgs) ->
Scheme = ssl_cipher:signature_algorithm_to_scheme(SignAlg),
lists:member(Scheme, SignAlgs).
diff --git a/lib/ssl/src/ssl_cipher.erl b/lib/ssl/src/ssl_cipher.erl
index 8e08fb2a4e..93d077a0a4 100644
--- a/lib/ssl/src/ssl_cipher.erl
+++ b/lib/ssl/src/ssl_cipher.erl
@@ -555,11 +555,15 @@ filter(DerCert, Ciphers0, Version) ->
SigAlg = OtpCert#'OTPCertificate'.signatureAlgorithm,
PubKeyInfo = OtpCert#'OTPCertificate'.tbsCertificate#'OTPTBSCertificate'.subjectPublicKeyInfo,
PubKeyAlg = PubKeyInfo#'OTPSubjectPublicKeyInfo'.algorithm,
-
- Ciphers = filter_suites_pubkey(
- ssl_certificate:public_key_type(PubKeyAlg#'PublicKeyAlgorithm'.algorithm),
- Ciphers0, Version, OtpCert),
- {_, Sign} = public_key:pkix_sign_types(SigAlg#'SignatureAlgorithm'.algorithm),
+ Type = case ssl_certificate:public_key_type(PubKeyAlg#'PublicKeyAlgorithm'.algorithm) of
+ rsa_pss_pss ->
+ rsa;
+ Other ->
+ Other
+ end,
+ Ciphers = filter_suites_pubkey(Type, Ciphers0, Version, OtpCert),
+ SigAlgo = SigAlg#'SignatureAlgorithm'.algorithm,
+ Sign = ssl_certificate:public_key_type(SigAlgo),
filter_suites_signature(Sign, Ciphers, Version).
%%--------------------------------------------------------------------
@@ -1174,7 +1178,7 @@ filter_suites_pubkey(dsa, Ciphers, _, OtpCert) ->
NotECRSAKeyed = (Ciphers -- rsa_keyed_suites(Ciphers)) -- ec_keyed_suites(Ciphers),
filter_keyuse_suites(digitalSignature, KeyUses, NotECRSAKeyed,
dss_dhe_suites(Ciphers));
-filter_suites_pubkey(ec, Ciphers, _, OtpCert) ->
+filter_suites_pubkey(ecdsa, Ciphers, _, OtpCert) ->
Uses = key_uses(OtpCert),
NotRSADSAKeyed = (Ciphers -- rsa_keyed_suites(Ciphers)) -- dss_keyed_suites(Ciphers),
CiphersSuites = filter_keyuse_suites(digitalSignature, Uses, NotRSADSAKeyed,
diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl
index 32436fdae0..dd226c3c56 100644
--- a/lib/ssl/src/ssl_handshake.erl
+++ b/lib/ssl/src/ssl_handshake.erl
@@ -371,8 +371,8 @@ certificate_verify(_, _, _, undefined, _, _) ->
certificate_verify(Signature, PublicKeyInfo, Version,
HashSign = {HashAlgo, _}, MasterSecret, {_, Handshake}) ->
- Hash = calc_certificate_verify(Version, HashAlgo, MasterSecret, Handshake),
- case verify_signature(Version, Hash, HashSign, Signature, PublicKeyInfo) of
+ Msg = calc_certificate_verify(Version, HashAlgo, MasterSecret, Handshake),
+ case verify_signature(Version, Msg, HashSign, Signature, PublicKeyInfo) of
true ->
valid;
_ ->
@@ -384,39 +384,32 @@ certificate_verify(Signature, PublicKeyInfo, Version,
%%
%% Description: Checks that a public_key signature is valid.
%%--------------------------------------------------------------------
-verify_signature({3, 4}, Hash, {HashAlgo, SignAlgo}, Signature,
+verify_signature(_, Msg, {HashAlgo, SignAlgo}, Signature,
{_, PubKey, PubKeyParams}) when SignAlgo == rsa_pss_rsae;
SignAlgo == rsa_pss_pss ->
Options = verify_options(SignAlgo, HashAlgo, PubKeyParams),
- public_key:verify(Hash, HashAlgo, Signature, PubKey, Options);
-verify_signature({3, 3}, Hash, {HashAlgo, SignAlgo}, Signature,
- {_, PubKey, PubKeyParams}) when SignAlgo == rsa_pss_rsae;
- SignAlgo == rsa_pss_pss ->
- Options = verify_options(SignAlgo, HashAlgo, PubKeyParams),
- public_key:verify({digest, Hash}, HashAlgo, Signature, PubKey, Options);
-verify_signature({3, Minor}, Hash, {HashAlgo, SignAlgo}, Signature, {?rsaEncryption, PubKey, PubKeyParams})
+ public_key:verify(Msg, HashAlgo, Signature, PubKey, Options);
+verify_signature({3, Minor}, Msg, {HashAlgo, SignAlgo}, Signature, {?rsaEncryption, PubKey, PubKeyParams})
when Minor >= 3 ->
Options = verify_options(SignAlgo, HashAlgo, PubKeyParams),
- public_key:verify({digest, Hash}, HashAlgo, Signature, PubKey, Options);
-verify_signature({3, Minor}, Hash, _HashAlgo, Signature, {?rsaEncryption, PubKey, _PubKeyParams}) when Minor =< 2 ->
+ public_key:verify(Msg, HashAlgo, Signature, PubKey, Options);
+verify_signature({3, Minor}, {digest, Digest}, _HashAlgo, Signature, {?rsaEncryption, PubKey, _PubKeyParams}) when Minor =< 2 ->
case public_key:decrypt_public(Signature, PubKey,
[{rsa_pad, rsa_pkcs1_padding}]) of
- Hash -> true;
+ Digest -> true;
_ -> false
end;
-verify_signature({3, 4}, Hash, {HashAlgo, _SignAlgo}, Signature, {?'id-ecPublicKey', PubKey, PubKeyParams}) ->
- public_key:verify(Hash, HashAlgo, Signature, {PubKey, PubKeyParams});
verify_signature({3, 4}, Msg, {_, eddsa}, Signature, {?'id-Ed25519', PubKey, PubKeyParams}) ->
public_key:verify(Msg, none, Signature, {PubKey, PubKeyParams});
verify_signature({3, 4}, Msg, {_, eddsa}, Signature, {?'id-Ed448', PubKey, PubKeyParams}) ->
public_key:verify(Msg, none, Signature, {PubKey, PubKeyParams});
-verify_signature(_, Hash, {HashAlgo, _SignAlg}, Signature,
+verify_signature(_, Msg, {HashAlgo, _SignAlg}, Signature,
{?'id-ecPublicKey', PublicKey, PublicKeyParams}) ->
- public_key:verify({digest, Hash}, HashAlgo, Signature, {PublicKey, PublicKeyParams});
-verify_signature({3, Minor}, _Hash, {_HashAlgo, anon}, _Signature, _) when Minor =< 3 ->
+ public_key:verify(Msg, HashAlgo, Signature, {PublicKey, PublicKeyParams});
+verify_signature({3, Minor}, _Msg, {_HashAlgo, anon}, _Signature, _) when Minor =< 3 ->
true;
-verify_signature({3, Minor}, Hash, {HashAlgo, dsa}, Signature, {?'id-dsa', PublicKey, PublicKeyParams}) when Minor =< 3->
- public_key:verify({digest, Hash}, HashAlgo, Signature, {PublicKey, PublicKeyParams}).
+verify_signature({3, Minor}, Msg, {HashAlgo, dsa}, Signature, {?'id-dsa', PublicKey, PublicKeyParams}) when Minor =< 3->
+ public_key:verify(Msg, HashAlgo, Signature, {PublicKey, PublicKeyParams}).
%%--------------------------------------------------------------------
-spec master_secret(ssl_record:ssl_version(), #session{} | binary(), ssl_record:connection_states(),
@@ -454,17 +447,18 @@ master_secret(Version, PremasterSecret, ConnectionStates, Role) ->
end.
%%--------------------------------------------------------------------
--spec server_key_exchange_hash(md5sha | md5 | sha | sha224 |sha256 | sha384 | sha512, binary()) -> binary().
+-spec server_key_exchange_hash(md5sha | sha | sha224 |sha256 | sha384 | sha512, binary()) -> binary() | {digest, binary()}.
%%
-%% Description: Calculate server key exchange hash
+%% Description: Calculate the digest of the server key exchange hash if it is complex
%%--------------------------------------------------------------------
server_key_exchange_hash(md5sha, Value) ->
MD5 = crypto:hash(md5, Value),
SHA = crypto:hash(sha, Value),
- <<MD5/binary, SHA/binary>>;
+ {digest, <<MD5/binary, SHA/binary>>};
-server_key_exchange_hash(Hash, Value) ->
- crypto:hash(Hash, Value).
+server_key_exchange_hash(_, Value) ->
+ %% Optimization: Let crypto calculate the hash in sign/verify call
+ Value.
%%--------------------------------------------------------------------
-spec verify_connection(ssl_record:ssl_version(), #finished{}, client | server, integer(), binary(),
@@ -509,10 +503,11 @@ verify_server_key(#server_key_params{params_bin = EncParams,
ssl_record:pending_connection_state(ConnectionStates, read),
#security_parameters{client_random = ClientRandom,
server_random = ServerRandom} = SecParams,
+
Hash = server_key_exchange_hash(HashAlgo,
- <<ClientRandom/binary,
- ServerRandom/binary,
- EncParams/binary>>),
+ <<ClientRandom/binary,
+ ServerRandom/binary,
+ EncParams/binary>>),
verify_signature(Version, Hash, HashSign, Signature, PubKeyInfo).
select_version(RecordCB, ClientVersion, Versions) ->
@@ -567,8 +562,9 @@ encode_handshake(#certificate_request{certificate_types = CertTypes,
certificate_authorities = CertAuths},
{Major, Minor})
when Major == 3, Minor >= 3 ->
- HashSigns= << <<(ssl_cipher:hash_algorithm(Hash)):8, (ssl_cipher:sign_algorithm(Sign)):8>> ||
- {Hash, Sign} <- HashSignAlgos >>,
+
+ HashSigns = << <<(ssl_cipher:signature_scheme(SignatureScheme)):16 >> ||
+ SignatureScheme <- HashSignAlgos >>,
CertTypesLen = byte_size(CertTypes),
HashSignsLen = byte_size(HashSigns),
CertAuthsLen = byte_size(CertAuths),
@@ -863,13 +859,12 @@ decode_handshake(_Version, ?CERTIFICATE_STATUS, <<?BYTE(?CERTIFICATE_STATUS_TYPE
response = ASN1OcspResponse};
decode_handshake(_Version, ?SERVER_KEY_EXCHANGE, Keys) ->
#server_key_exchange{exchange_keys = Keys};
-decode_handshake({Major, Minor}, ?CERTIFICATE_REQUEST,
+decode_handshake({Major, Minor} = Version, ?CERTIFICATE_REQUEST,
<<?BYTE(CertTypesLen), CertTypes:CertTypesLen/binary,
?UINT16(HashSignsLen), HashSigns:HashSignsLen/binary,
?UINT16(CertAuthsLen), CertAuths:CertAuthsLen/binary>>)
when Major >= 3, Minor >= 3 ->
- HashSignAlgos = [{ssl_cipher:hash_algorithm(Hash), ssl_cipher:sign_algorithm(Sign)} ||
- <<?BYTE(Hash), ?BYTE(Sign)>> <= HashSigns],
+ HashSignAlgos = decode_sign_alg(Version, HashSigns),
#certificate_request{certificate_types = CertTypes,
hashsign_algorithms = #hash_sign_algos{hash_sign_algos = HashSignAlgos},
certificate_authorities = CertAuths};
@@ -991,7 +986,12 @@ available_suites(ServerCert, UserSuites, Version, HashSigns, Curve) ->
available_signature_algs(undefined, _) ->
undefined;
available_signature_algs(SupportedHashSigns, Version) when Version >= {3, 3} ->
- #hash_sign_algos{hash_sign_algos = SupportedHashSigns};
+ case contains_scheme(SupportedHashSigns) of
+ true ->
+ #signature_algorithms{signature_scheme_list = SupportedHashSigns};
+ false ->
+ #hash_sign_algos{hash_sign_algos = SupportedHashSigns}
+ end;
available_signature_algs(_, _) ->
undefined.
available_signature_algs(undefined, SupportedHashSigns, _, Version) when
@@ -1004,6 +1004,13 @@ available_signature_algs(#hash_sign_algos{hash_sign_algos = ClientHashSigns}, Su
available_signature_algs(_, _, _, _) ->
undefined.
+contains_scheme([]) ->
+ false;
+contains_scheme([Scheme | _]) when is_atom(Scheme) ->
+ true;
+contains_scheme([_| Rest]) ->
+ contains_scheme(Rest).
+
cipher_suites(Suites, Renegotiation, true) ->
%% TLS_FALLBACK_SCSV should be placed last -RFC7507
cipher_suites(Suites, Renegotiation) ++ [?TLS_FALLBACK_SCSV];
@@ -1505,18 +1512,16 @@ select_hashsign(_, _, KeyExAlgo, _, _Version) when KeyExAlgo == dh_anon;
%% The signature_algorithms extension was introduced with TLS 1.2. Ignore it if we have
%% negotiated a lower version.
select_hashsign({ClientHashSigns, ClientSignatureSchemes},
- Cert, KeyExAlgo, undefined, {Major, Minor} = Version)
- when Major >= 3 andalso Minor >= 3->
+ Cert, KeyExAlgo, undefined, {3, 3} = Version) ->
select_hashsign({ClientHashSigns, ClientSignatureSchemes}, Cert, KeyExAlgo,
- tls_v1:default_signature_algs(Version), Version);
+ tls_v1:default_signature_algs([Version]), Version);
select_hashsign({#hash_sign_algos{hash_sign_algos = ClientHashSigns},
ClientSignatureSchemes0},
- Cert, KeyExAlgo, SupportedHashSigns, {Major, Minor})
- when Major >= 3 andalso Minor >= 3 ->
+ Cert, KeyExAlgo, SupportedHashSigns, {3, 3}) ->
ClientSignatureSchemes = get_signature_scheme(ClientSignatureSchemes0),
{SignAlgo0, Param, PublicKeyAlgo0, _, _} = get_cert_params(Cert),
- SignAlgo = sign_algo(SignAlgo0),
- PublicKeyAlgo = public_key_algo(PublicKeyAlgo0),
+ SignAlgo = sign_algo(SignAlgo0, Param),
+ PublicKeyAlgo = ssl_certificate:public_key_type(PublicKeyAlgo0),
%% RFC 5246 (TLS 1.2)
%% If the client provided a "signature_algorithms" extension, then all
@@ -1536,15 +1541,17 @@ select_hashsign({#hash_sign_algos{hash_sign_algos = ClientHashSigns},
%% signatures appearing in certificates.
case is_supported_sign(SignAlgo, Param, ClientHashSigns, ClientSignatureSchemes) of
true ->
- case lists:filter(fun({_, S} = Algos) when S == PublicKeyAlgo ->
- is_acceptable_hash_sign(Algos, KeyExAlgo, SupportedHashSigns);
- (_) ->
- false
- end, ClientHashSigns) of
- [] ->
- ?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY, no_suitable_signature_algorithm);
- [HashSign | _] ->
- HashSign
+ case
+ (KeyExAlgo == psk) orelse
+ (KeyExAlgo == dhe_psk) orelse
+ (KeyExAlgo == ecdhe_psk) orelse
+ (KeyExAlgo == srp_anon) orelse
+ (KeyExAlgo == dh_anon) orelse
+ (KeyExAlgo == ecdhe_anon) of
+ true ->
+ ClientHashSigns;
+ false ->
+ do_select_hashsign(ClientHashSigns, PublicKeyAlgo, SupportedHashSigns)
end;
false ->
?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY, no_suitable_signature_algorithm)
@@ -1569,30 +1576,19 @@ select_hashsign(#certificate_request{
SupportedHashSigns,
{Major, Minor}) when Major >= 3 andalso Minor >= 3->
{SignAlgo0, Param, PublicKeyAlgo0, _, _} = get_cert_params(Cert),
- SignAlgo = sign_algo(SignAlgo0),
- PublicKeyAlgo = public_key_algo(PublicKeyAlgo0),
-
+ SignAlgo = {_, KeyType} = sign_algo(SignAlgo0, Param),
+ PublicKeyAlgo = ssl_certificate:public_key_type(PublicKeyAlgo0),
+ SignatureSchemes = [Scheme || Scheme <- HashSigns, is_atom(Scheme), (KeyType == rsa_pss_pss) or (KeyType == rsa)],
case is_acceptable_cert_type(PublicKeyAlgo, Types) andalso
- %% certificate_request has no "signature_algorithms_cert"
- %% extension in TLS 1.2.
- is_supported_sign(SignAlgo, Param, HashSigns, undefined) of
+ is_supported_sign(SignAlgo, Param, HashSigns, SignatureSchemes) of
true ->
- case lists:filter(fun({_, S} = Algos) when S == PublicKeyAlgo ->
- is_acceptable_hash_sign(Algos, SupportedHashSigns);
- (_) ->
- false
- end, HashSigns) of
- [] ->
- ?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY, no_suitable_signature_algorithm);
- [HashSign | _] ->
- HashSign
- end;
+ do_select_hashsign(HashSigns, PublicKeyAlgo, SupportedHashSigns);
false ->
?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY, no_suitable_signature_algorithm)
end;
select_hashsign(#certificate_request{certificate_types = Types}, Cert, _, Version) ->
{_, _, PublicKeyAlgo0, _, _} = get_cert_params(Cert),
- PublicKeyAlgo = public_key_algo(PublicKeyAlgo0),
+ PublicKeyAlgo = ssl_certificate:public_key_type(PublicKeyAlgo0),
%% Check cert even for TLS 1.0/1.1
case is_acceptable_cert_type(PublicKeyAlgo, Types) of
@@ -1603,6 +1599,23 @@ select_hashsign(#certificate_request{certificate_types = Types}, Cert, _, Versio
end.
+do_select_hashsign(HashSigns, PublicKeyAlgo, SupportedHashSigns) ->
+ case lists:filter(fun({H, rsa_pss_pss = S}) when S == PublicKeyAlgo ->
+ is_acceptable_hash_sign(list_to_existing_atom(atom_to_list(S) ++ "_" ++ atom_to_list(H)), SupportedHashSigns);
+ ({H, rsa_pss_rsae = S}) when PublicKeyAlgo == rsa ->
+ is_acceptable_hash_sign(list_to_existing_atom(atom_to_list(S) ++ "_" ++ atom_to_list(H)), SupportedHashSigns);
+ ({_, S} = Algos) when S == PublicKeyAlgo ->
+ is_acceptable_hash_sign(Algos, SupportedHashSigns);
+ (_A) ->
+ false
+ end, HashSigns) of
+ [] ->
+ ?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY, no_suitable_signature_algorithm);
+ [HashSign | _] ->
+ HashSign
+ end.
+
+
%% Gets the relevant parameters of a certificate:
%% - signature algorithm
%% - parameters of the signature algorithm
@@ -1723,7 +1736,7 @@ select_own_cert(undefined) ->
undefined.
get_signature_scheme(undefined) ->
- undefined;
+ [];
get_signature_scheme(#signature_algorithms_cert{
signature_scheme_list = ClientSignatureSchemes}) ->
ClientSignatureSchemes.
@@ -1751,10 +1764,9 @@ get_signature_scheme(#signature_algorithms_cert{
%% ECDHE_ECDSA), behave as if the client had sent value {sha1,ecdsa}.
%%--------------------------------------------------------------------
-select_hashsign_algs(HashSign, _, {Major, Minor}) when HashSign =/= undefined andalso
- Major >= 3 andalso Minor >= 3 ->
+select_hashsign_algs(HashSign, _, {3, 3}) when HashSign =/= undefined ->
HashSign;
-select_hashsign_algs(undefined, ?rsaEncryption, {Major, Minor}) when Major >= 3 andalso Minor >= 3 ->
+select_hashsign_algs(undefined, ?rsaEncryption, {3,3}) ->
{sha, rsa};
select_hashsign_algs(undefined,?'id-ecPublicKey', _) ->
{sha, ecdsa};
@@ -1989,8 +2001,9 @@ path_validation_alert({bad_cert, unknown_ca}) ->
path_validation_alert(Reason) ->
?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, Reason).
-digitally_signed(Version, Hashes, HashAlgo, PrivateKey, SignAlgo) ->
- try do_digitally_signed(Version, Hashes, HashAlgo, PrivateKey, SignAlgo) of
+
+digitally_signed(Version, Msg, HashAlgo, PrivateKey, SignAlgo) ->
+ try do_digitally_signed(Version, Msg, HashAlgo, PrivateKey, SignAlgo) of
Signature ->
Signature
catch
@@ -1998,36 +2011,26 @@ digitally_signed(Version, Hashes, HashAlgo, PrivateKey, SignAlgo) ->
throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, bad_key(PrivateKey)))
end.
-do_digitally_signed({3, Minor}, Hash, _,
+do_digitally_signed({3, Minor}, Msg, HashAlgo, {#'RSAPrivateKey'{} = Key,
+ #'RSASSA-PSS-params'{}}, SignAlgo) when Minor >= 3 ->
+ Options = signature_options(SignAlgo, HashAlgo),
+ public_key:sign(Msg, HashAlgo, Key, Options);
+do_digitally_signed({3, Minor}, {digest, Digest}, _HashAlgo, #'RSAPrivateKey'{} = Key, rsa) when Minor =< 2 ->
+ public_key:encrypt_private(Digest, Key,
+ [{rsa_pad, rsa_pkcs1_padding}]);
+do_digitally_signed({3, Minor}, {digest, Digest}, _,
#{algorithm := rsa} = Engine, rsa) when Minor =< 2->
- crypto:private_encrypt(rsa, Hash, maps:remove(algorithm, Engine),
+ crypto:private_encrypt(rsa, Digest, maps:remove(algorithm, Engine),
rsa_pkcs1_padding);
-do_digitally_signed({3, Minor}, Hash, HashAlgo, #{algorithm := Alg} = Engine, SignAlgo)
- when Minor > 3 ->
- Options = signature_options(SignAlgo, HashAlgo),
- crypto:sign(Alg, HashAlgo, Hash, maps:remove(algorithm, Engine), Options);
-do_digitally_signed({3, Minor}, Hash, HashAlgo, #{algorithm := Alg} = Engine, SignAlgo)
- when Minor > 3 ->
- Options = signature_options(SignAlgo, HashAlgo),
- crypto:sign(Alg, HashAlgo, Hash, maps:remove(algorithm, Engine), Options);
-do_digitally_signed({3, 3}, Hash, HashAlgo, #{algorithm := Alg} = Engine, SignAlgo) ->
+do_digitally_signed(_, Msg, HashAlgo, #{algorithm := Alg} = Engine, SignAlgo) ->
Options = signature_options(SignAlgo, HashAlgo),
- crypto:sign(Alg, HashAlgo, {digest, Hash}, maps:remove(algorithm, Engine), Options);
-do_digitally_signed({3, 4}, Hash, HashAlgo, {#'RSAPrivateKey'{} = Key,
- #'RSASSA-PSS-params'{}}, SignAlgo) ->
+ crypto:sign(Alg, HashAlgo, Msg, maps:remove(algorithm, Engine), Options);
+do_digitally_signed({3, Minor}, {digest, _} = Msg , HashAlgo, Key, _) when Minor =< 2 ->
+ public_key:sign(Msg, HashAlgo, Key);
+do_digitally_signed(_, Msg, HashAlgo, Key, SignAlgo) ->
Options = signature_options(SignAlgo, HashAlgo),
- public_key:sign(Hash, HashAlgo, Key, Options);
-do_digitally_signed({3, 4}, Hash, HashAlgo, Key, SignAlgo) ->
- Options = signature_options(SignAlgo, HashAlgo),
- public_key:sign(Hash, HashAlgo, Key, Options);
-do_digitally_signed({3, Minor}, Hash, HashAlgo, Key, SignAlgo) when Minor >= 3 ->
- Options = signature_options(HashAlgo, SignAlgo),
- public_key:sign({digest,Hash}, HashAlgo, Key, Options);
-do_digitally_signed({3, Minor}, Hash, _HashAlgo, #'RSAPrivateKey'{} = Key, rsa) when Minor =< 2 ->
- public_key:encrypt_private(Hash, Key,
- [{rsa_pad, rsa_pkcs1_padding}]);
-do_digitally_signed(_Version, Hash, HashAlgo, Key, _SignAlgo) ->
- public_key:sign({digest, Hash}, HashAlgo, Key).
+ public_key:sign(Msg, HashAlgo, Key, Options).
+
signature_options(SignAlgo, HashAlgo) when SignAlgo =:= rsa_pss_rsae orelse
SignAlgo =:= rsa_pss_pss ->
@@ -2401,6 +2404,10 @@ enc_sign(_HashSign, Sign, _Version) ->
SignLen = byte_size(Sign),
<<?UINT16(SignLen), Sign/binary>>.
+enc_hashsign(HashAlgo, SignAlgo) when SignAlgo == rsa_pss_pss;
+ SignAlgo == rsa_pss_rsae ->
+ Sign = ssl_cipher:signature_scheme(list_to_existing_atom(atom_to_list(SignAlgo) ++ "_" ++ atom_to_list(HashAlgo))),
+ <<?UINT16(Sign)>>;
enc_hashsign(HashAlgo, SignAlgo) ->
Hash = ssl_cipher:hash_algorithm(HashAlgo),
Sign = ssl_cipher:sign_algorithm(SignAlgo),
@@ -2421,8 +2428,8 @@ enc_server_key_exchange(Version, Params, {HashAlgo, SignAlgo},
signature = <<>>};
_ ->
Hash =
- server_key_exchange_hash(HashAlgo, <<ClientRandom/binary,
- ServerRandom/binary,
+ server_key_exchange_hash(HashAlgo, <<ClientRandom/binary,
+ ServerRandom/binary,
EncParams/binary>>),
Signature = digitally_signed(Version, Hash, HashAlgo, PrivateKey, SignAlgo),
#server_key_params{params = Params,
@@ -2729,7 +2736,7 @@ decode_extensions(<<?UINT16(?SRP_EXT), ?UINT16(Len), ?BYTE(SRPLen),
decode_extensions(<<?UINT16(?SIGNATURE_ALGORITHMS_EXT), ?UINT16(Len),
ExtData:Len/binary, Rest/binary>>, Version, MessageType, Acc)
- when Version < {3,4} ->
+ when Version < {3,3} ->
SignAlgoListLen = Len - 2,
<<?UINT16(SignAlgoListLen), SignAlgoList/binary>> = ExtData,
HashSignAlgos = [{ssl_cipher:hash_algorithm(Hash), ssl_cipher:sign_algorithm(Sign)} ||
@@ -2738,6 +2745,26 @@ decode_extensions(<<?UINT16(?SIGNATURE_ALGORITHMS_EXT), ?UINT16(Len),
Acc#{signature_algs =>
#hash_sign_algos{hash_sign_algos =
HashSignAlgos}});
+decode_extensions(<<?UINT16(?SIGNATURE_ALGORITHMS_EXT), ?UINT16(Len),
+ ExtData:Len/binary, Rest/binary>>, Version, MessageType, Acc)
+ when Version =:= {3,3} ->
+ SignSchemeListLen = Len - 2,
+ <<?UINT16(SignSchemeListLen), SignSchemeList/binary>> = ExtData,
+ HashSigns = decode_sign_alg(Version, SignSchemeList),
+ decode_extensions(Rest, Version, MessageType,
+ Acc#{signature_algs =>
+ #hash_sign_algos{
+ hash_sign_algos = HashSigns}});
+decode_extensions(<<?UINT16(?SIGNATURE_ALGORITHMS_EXT), ?UINT16(Len),
+ ExtData:Len/binary, Rest/binary>>, Version, MessageType, Acc)
+ when Version =:= {3,4} ->
+ SignSchemeListLen = Len - 2,
+ <<?UINT16(SignSchemeListLen), SignSchemeList/binary>> = ExtData,
+ SignSchemes = decode_sign_alg(Version, SignSchemeList),
+ decode_extensions(Rest, Version, MessageType,
+ Acc#{signature_algs =>
+ #signature_algorithms{
+ signature_scheme_list = SignSchemes}});
decode_extensions(<<?UINT16(?SIGNATURE_ALGORITHMS_EXT), ?UINT16(Len),
ExtData:Len/binary, Rest/binary>>, Version, MessageType, Acc)
@@ -2968,8 +2995,56 @@ decode_extensions(<<?UINT16(_), ?UINT16(Len), _Unknown:Len/binary, Rest/binary>>
decode_extensions(_, _, _, Acc) ->
Acc.
-dec_hashsign(<<?BYTE(HashAlgo), ?BYTE(SignAlgo)>>) ->
- {ssl_cipher:hash_algorithm(HashAlgo), ssl_cipher:sign_algorithm(SignAlgo)}.
+decode_sign_alg({3,3}, SignSchemeList) ->
+ %% Ignore unknown signature algorithms
+ Fun = fun(Elem) ->
+ case ssl_cipher:signature_scheme(Elem) of
+ unassigned ->
+ false;
+ Value when is_atom(Value)->
+ case ssl_cipher:scheme_to_components(Value) of
+ {Hash, rsa_pss_rsae = Sign, _} ->
+ {true, {Hash, Sign}};
+ {Hash, rsa_pss_pss = Sign, _} ->
+ {true,{Hash, Sign}};
+ {sha1, rsa_pkcs1, _} ->
+ {true,{sha, rsa}};
+ {Hash, rsa_pkcs1, _} ->
+ {true,{Hash, rsa}};
+ {sha1, ecdsa, _} ->
+ {true,{sha, ecdsa}};
+ {sha512,ecdsa, _} ->
+ {true,{sha512, ecdsa}};
+ {sha384,ecdsa, _} ->
+ {true,{sha384, ecdsa}};
+ {sha256,ecdsa, _}->
+ {true,{sha256, ecdsa}};
+ _ ->
+ false
+ end;
+ Value ->
+ {true, Value}
+ end
+ end,
+ lists:filtermap(Fun, [SignScheme ||
+ <<?UINT16(SignScheme)>> <= SignSchemeList]);
+decode_sign_alg({3,4}, SignSchemeList) ->
+ %% Ignore unknown signature algorithms
+ Fun = fun(Elem) ->
+ case ssl_cipher:signature_scheme(Elem) of
+ unassigned ->
+ false;
+ Value ->
+ {true, Value}
+ end
+ end,
+ lists:filtermap(Fun, [SignScheme ||
+ <<?UINT16(SignScheme)>> <= SignSchemeList]).
+
+dec_hashsign(Value) ->
+ [HashSign] = decode_sign_alg({3,3}, Value),
+ HashSign.
+
%% Ignore unknown names (only host_name is supported)
dec_sni(<<?BYTE(?SNI_NAMETYPE_HOST_NAME), ?UINT16(Len),
@@ -3162,7 +3237,6 @@ handle_psk_identity(_PSKIdentity, LookupFun)
handle_psk_identity(PSKIdentity, {Fun, UserState}) ->
Fun(psk, PSKIdentity, UserState).
-
filter_hashsigns([], [], _, _, Acc) ->
lists:reverse(Acc);
filter_hashsigns([Suite | Suites], [#{key_exchange := KeyExchange} | Algos], HashSigns, Version,
@@ -3306,18 +3380,6 @@ handle_srp_extension(undefined, Session) ->
handle_srp_extension(#srp{username = Username}, Session) ->
Session#session{srp_username = Username}.
-is_acceptable_hash_sign( _, KeyExAlgo, _) when
- KeyExAlgo == psk;
- KeyExAlgo == dhe_psk;
- KeyExAlgo == ecdhe_psk;
- KeyExAlgo == srp_anon;
- KeyExAlgo == dh_anon;
- KeyExAlgo == ecdhe_anon
- ->
- true;
-is_acceptable_hash_sign(Algos,_, SupportedHashSigns) ->
- is_acceptable_hash_sign(Algos, SupportedHashSigns).
-
is_acceptable_hash_sign(Algos, SupportedHashSigns) ->
lists:member(Algos, SupportedHashSigns).
@@ -3325,7 +3387,7 @@ is_acceptable_cert_type(Sign, Types) ->
lists:member(sign_type(Sign), binary_to_list(Types)).
%% signature_algorithms_cert = undefined
-is_supported_sign(SignAlgo, _, HashSigns, undefined) ->
+is_supported_sign(SignAlgo, _, HashSigns, []) ->
lists:member(SignAlgo, HashSigns);
%% {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}
@@ -3371,14 +3433,6 @@ is_supported_sign({Hash, Sign}, _Param, _, SignatureSchemes) ->
end,
lists:foldl(Fun, false, SignatureSchemes).
-%% SupportedPublicKeyAlgorithms PUBLIC-KEY-ALGORITHM-CLASS ::= {
-%% dsa | rsa-encryption | dh | kea | ec-public-key }
-public_key_algo(?rsaEncryption) ->
- rsa;
-public_key_algo(?'id-ecPublicKey') ->
- ecdsa;
-public_key_algo(?'id-dsa') ->
- dsa.
%% SupportedSignatureAlgorithms SIGNATURE-ALGORITHM-CLASS ::= {
%% dsa-with-sha1 | dsaWithSHA1 | md2-with-rsa-encryption |
@@ -3392,7 +3446,11 @@ public_key_algo(?'id-dsa') ->
%% ecdsa-with-sha256 |
%% ecdsa-with-sha384 |
%% ecdsa-with-sha512 }
-sign_algo(Alg) ->
+sign_algo(?'id-RSASSA-PSS', #'RSASSA-PSS-params'{maskGenAlgorithm =
+ #'MaskGenAlgorithm'{algorithm = ?'id-mgf1',
+ parameters = #'HashAlgorithm'{algorithm = HashOid}}}) ->
+ {public_key:pkix_hash_type(HashOid), rsa_pss_pss};
+sign_algo(Alg, _) ->
public_key:pkix_sign_types(Alg).
sign_type(rsa) ->
diff --git a/lib/ssl/src/tls_dtls_connection.erl b/lib/ssl/src/tls_dtls_connection.erl
index 5afeef59f7..0174850758 100644
--- a/lib/ssl/src/tls_dtls_connection.erl
+++ b/lib/ssl/src/tls_dtls_connection.erl
@@ -433,19 +433,29 @@ certify(internal, #certificate_request{},
certify(internal, #certificate_request{} = CertRequest,
#state{static_env = #static_env{role = client,
protocol_cb = Connection},
- handshake_env = HsEnv,
+ handshake_env = #handshake_env{hashsign_algorithm = NegotiatedHashSign} = HsEnv,
connection_env = #connection_env{negotiated_version = Version},
session = #session{own_certificates = [Cert|_]},
ssl_options = #{signature_algs := SupportedHashSigns}} = State) ->
- case ssl_handshake:select_hashsign(CertRequest, Cert,
- SupportedHashSigns, ssl:tls_version(Version)) of
- #alert {} = Alert ->
- ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State);
- NegotiatedHashSign ->
- Connection:next_event(?FUNCTION_NAME, no_record,
- State#state{client_certificate_status = requested,
- handshake_env = HsEnv#handshake_env{cert_hashsign_algorithm = NegotiatedHashSign}})
- end;
+
+ TLSVersion = ssl:tls_version(Version),
+ case NegotiatedHashSign of
+ {Hash, Sign} when TLSVersion == {3,3} andalso Hash =/= undefined andalso
+ Sign =/= undefined ->
+ Connection:next_event(?FUNCTION_NAME, no_record,
+ State#state{client_certificate_status = requested,
+ handshake_env = HsEnv#handshake_env{cert_hashsign_algorithm = NegotiatedHashSign}});
+ _ ->
+ case ssl_handshake:select_hashsign(CertRequest, Cert,
+ SupportedHashSigns, TLSVersion) of
+ #alert {} = Alert ->
+ ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State);
+ SelectedHashSign ->
+ Connection:next_event(?FUNCTION_NAME, no_record,
+ State#state{client_certificate_status = requested,
+ handshake_env = HsEnv#handshake_env{cert_hashsign_algorithm = SelectedHashSign}})
+ end
+ end;
%% PSK and RSA_PSK might bypass the Server-Key-Exchange
certify(internal, #server_hello_done{},
#state{static_env = #static_env{role = client,
@@ -682,10 +692,10 @@ gen_handshake(StateName, Type, Event,
Result ->
Result
catch
- _:_ ->
- ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
- malformed_handshake_data),
- Version, StateName, State)
+ _:_ ->
+ ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
+ malformed_handshake_data),
+ Version, StateName, State)
end.
%%--------------------------------------------------------------------
@@ -899,7 +909,6 @@ verify_client_cert(#state{static_env = #static_env{role = client},
client_certificate_status = requested,
session = #session{master_secret = MasterSecret,
own_certificates = OwnCerts}} = State, Connection) ->
-
case ssl_handshake:client_certificate_verify(OwnCerts, MasterSecret,
ssl:tls_version(Version), HashSign, PrivateKey, Hist) of
#certificate_verify{} = Verified ->
diff --git a/lib/ssl/src/tls_handshake.erl b/lib/ssl/src/tls_handshake.erl
index d7c899c7cf..05cf1a7339 100644
--- a/lib/ssl/src/tls_handshake.erl
+++ b/lib/ssl/src/tls_handshake.erl
@@ -83,13 +83,14 @@ client_hello(_Host, _Port, ConnectionStates,
#{security_parameters := SecParams} =
ssl_record:pending_connection_state(ConnectionStates, read),
AvailableCipherSuites = ssl_handshake:available_suites(UserSuites, Version),
- Extensions = ssl_handshake:client_hello_extensions(Version,
+ Extensions = ssl_handshake:client_hello_extensions(Version,
AvailableCipherSuites,
- SslOpts, ConnectionStates,
- Renegotiation,
- KeyShare,
- TicketData,
- OcspNonce),
+ SslOpts,
+ ConnectionStates,
+ Renegotiation,
+ KeyShare,
+ TicketData,
+ OcspNonce),
CipherSuites = ssl_handshake:cipher_suites(AvailableCipherSuites, Renegotiation, Fallback),
#client_hello{session_id = Id,
client_version = LegacyVersion,
@@ -247,7 +248,7 @@ hello(#client_hello{client_version = _ClientVersion,
_:_ ->
?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data)
end;
-
+
hello(#client_hello{client_version = ClientVersion,
cipher_suites = CipherSuites} = Hello,
#{versions := Versions} = SslOpts,
@@ -257,12 +258,11 @@ hello(#client_hello{client_version = ClientVersion,
do_hello(Version, Versions, CipherSuites, Hello, SslOpts, Info, Renegotiation)
catch
error:{case_clause,{asn1, Asn1Reason}} ->
- %% ASN-1 decode of certificate somehow failed
+ %% ASN-1 decode of certificate somehow failed
?ALERT_REC(?FATAL, ?INTERNAL_ERROR, {failed_to_decode_own_certificate, Asn1Reason});
- _:_ ->
- ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data)
- end.
-
+ _:_ ->
+ ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data)
+ end.
%%--------------------------------------------------------------------
%%% Handshake encodeing
diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl
index f15e1d90bd..5778413ff3 100644
--- a/lib/ssl/src/tls_handshake_1_3.erl
+++ b/lib/ssl/src/tls_handshake_1_3.erl
@@ -232,9 +232,21 @@ add_signature_algorithms_cert(Extensions, SignAlgsCert) ->
filter_tls13_algs(undefined) -> undefined;
filter_tls13_algs(Algo) ->
- lists:filter(fun is_atom/1, Algo).
-
-
+ lists:foldl(fun(Atom, Acc) when is_atom(Atom) ->
+ [Atom | Acc];
+ ({sha512, rsa}, Acc) ->
+ [rsa_pkcs1_sha512 | Acc];
+ ({sha384, rsa}, Acc) ->
+ [rsa_pkcs1_sha384 | Acc];
+ ({sha256, rsa}, Acc) ->
+ [rsa_pkcs1_sha256 | Acc];
+ ({sha, rsa}, Acc) ->
+ [rsa_pkcs1_sha1 | Acc];
+ ({sha, ecdsa}, Acc) ->
+ [ecdsa_sha1| Acc];
+ (_, Acc) ->
+ Acc
+ end, [], Algo).
%% enum {
%% X509(0),
%% RawPublicKey(2),
diff --git a/lib/ssl/src/tls_v1.erl b/lib/ssl/src/tls_v1.erl
index 14c1311a52..85fe7e5512 100644
--- a/lib/ssl/src/tls_v1.erl
+++ b/lib/ssl/src/tls_v1.erl
@@ -44,8 +44,8 @@
enum_to_oid/1,
default_signature_algs/1,
signature_algs/2,
- default_signature_schemes/1,
signature_schemes/2,
+ rsa_schemes/0,
groups/1,
groups/2,
group_to_enum/1,
@@ -196,12 +196,15 @@ finished(Role, Version, PrfAlgo, MasterSecret, Handshake)
certificate_verify(md5sha, _Version, Handshake) ->
MD5 = crypto:hash(md5, Handshake),
SHA = crypto:hash(sha, Handshake),
- <<MD5/binary, SHA/binary>>;
+ {digest, <<MD5/binary, SHA/binary>>};
%% TLS 1.0 -1.1 ---------------------------------------------------
%% TLS 1.2 ---------------------------------------------------
-certificate_verify(HashAlgo, _Version, Handshake) ->
- crypto:hash(HashAlgo, Handshake).
+certificate_verify(_HashAlgo, _Version, Handshake) ->
+ %% crypto:hash(HashAlgo, Handshake).
+ %% Optimization: Let crypto calculate the hash in sign/verify call
+ Handshake.
+
%% TLS 1.2 ---------------------------------------------------
-spec setup_keys(integer(), integer(), binary(), binary(), binary(), integer(),
@@ -585,6 +588,7 @@ signature_algs({3, 3}, HashSigns) ->
CryptoSupports = crypto:supports(),
Hashes = proplists:get_value(hashs, CryptoSupports),
PubKeys = proplists:get_value(public_keys, CryptoSupports),
+ Schemes = rsa_schemes(),
Supported = lists:foldl(fun({Hash, dsa = Sign} = Alg, Acc) ->
case proplists:get_bool(dss, PubKeys)
andalso proplists:get_bool(Hash, Hashes)
@@ -604,15 +608,23 @@ signature_algs({3, 3}, HashSigns) ->
[Alg | Acc];
false ->
Acc
+ end;
+ (Alg, Acc) when is_atom(Alg) ->
+ case lists:member(Alg, Schemes) of
+ true ->
+ [NewAlg] = signature_schemes({3,4}, [Alg]),
+ [NewAlg| Acc];
+ false ->
+ Acc
end
end, [], HashSigns),
lists:reverse(Supported).
-default_signature_algs({3, 4} = Version) ->
- %% TLS 1.3 servers shall be prepared to process TLS 1.2 ClientHellos
- %% containing legacy hash-sign tuples.
- default_signature_schemes(Version) ++ default_signature_algs({3,3});
-default_signature_algs({3, 3} = Version) ->
+default_signature_algs([{3, 4} = Version]) ->
+ default_signature_schemes(Version) ++ legacy_signature_schemes(Version);
+default_signature_algs([{3, 4}, {3,3} | _]) ->
+ default_signature_schemes({3,4}) ++ default_signature_algs([{3,3}]);
+default_signature_algs([{3, 3} = Version |_]) ->
Default = [%% SHA2
{sha512, ecdsa},
{sha512, rsa},
@@ -631,7 +643,7 @@ default_signature_algs(_) ->
undefined.
-signature_schemes(Version, SignatureSchemes) when is_tuple(Version)
+signature_schemes(Version, [_|_] =SignatureSchemes) when is_tuple(Version)
andalso Version >= {3, 3} ->
CryptoSupports = crypto:supports(),
Hashes = proplists:get_value(hashs, CryptoSupports),
@@ -710,22 +722,42 @@ default_signature_schemes(Version) ->
rsa_pss_rsae_sha384,
rsa_pss_rsae_sha256,
eddsa_ed25519,
- eddsa_ed448,
-
- %% These values refer solely to signatures
- %% which appear in certificates (see Section 4.4.2.2) and are not
- %% defined for use in signed TLS handshake messages, although they
- %% MAY appear in "signature_algorithms" and
- %% "signature_algorithms_cert" for backward compatibility with
- %% TLS 1.2.
- rsa_pkcs1_sha512,
- rsa_pkcs1_sha384,
- rsa_pkcs1_sha256,
- ecdsa_sha1,
- rsa_pkcs1_sha1
+ eddsa_ed448
],
signature_schemes(Version, Default).
+legacy_signature_schemes(Version) ->
+ %% These values refer solely to signatures
+ %% which appear in certificates (see Section 4.4.2.2) and are not
+ %% defined for use in signed TLS handshake messages, although they
+ %% MAY appear in "signature_algorithms" and
+ %% "signature_algorithms_cert" for backward compatibility with
+ %% TLS 1.2.
+ LegacySchemes =
+ [rsa_pkcs1_sha512,
+ rsa_pkcs1_sha384,
+ rsa_pkcs1_sha256,
+ ecdsa_sha1,
+ rsa_pkcs1_sha1],
+ signature_schemes(Version, LegacySchemes).
+
+rsa_schemes() ->
+ 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) of
+ true ->
+ [rsa_pss_pss_sha512,
+ rsa_pss_pss_sha384,
+ rsa_pss_pss_sha256,
+ rsa_pss_rsae_sha512,
+ rsa_pss_rsae_sha384,
+ rsa_pss_rsae_sha256];
+ false ->
+ []
+ end.
%%--------------------------------------------------------------------
%%% Internal functions
diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl
index a824c2ef22..2550fce21b 100644
--- a/lib/ssl/test/ssl_cert_SUITE.erl
+++ b/lib/ssl/test/ssl_cert_SUITE.erl
@@ -141,19 +141,19 @@ all() ->
groups() ->
[
{'tlsv1.3', [], tls_1_3_protocol_groups()},
- {'tlsv1.2', [], tls_1_2_protocol_groups() -- [{group,rsa_pss_pss}]},
+ {'tlsv1.2', [], tls_1_2_protocol_groups()},
{'tlsv1.1', [], ssl_protocol_groups()},
{'tlsv1', [], ssl_protocol_groups()},
- {'dtlsv1.2', [], tls_1_2_protocol_groups() -- [{group,rsa_pss_rsae}, {group,rsa_pss_pss}]},
+ {'dtlsv1.2', [], tls_1_2_protocol_groups()},
{'dtlsv1', [], ssl_protocol_groups()},
{rsa, [], all_version_tests() ++ rsa_tests() ++ pre_tls_1_3_rsa_tests()},
{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]},
- {rsa_pss_rsae, [], all_version_tests() ++ rsa_tests()},
+ {rsa_pss_rsae, [], all_version_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() ++ rsa_tests()},
+ {rsa_pss_pss, [], all_version_tests()},
{rsa_pss_pss_1_3, [], all_version_tests() ++ rsa_tests() ++ tls_1_3_tests() ++ tls_1_3_rsa_tests()},
{ecdsa_1_3, [], all_version_tests() ++ tls_1_3_tests() ++
[signature_algorithms_bad_curve_secp256r1,
@@ -279,11 +279,58 @@ do_init_per_group(Group, Config0) when Group == rsa;
{server_cert_opts, SOpts} |
lists:delete(server_cert_opts,
lists:delete(client_cert_opts, Config))])];
-
do_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 ->
+ Alg == rsa_pss_pss ->
+ 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) of
+ 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}
+ ]}]} |
+ lists:delete(cert_key_alg,
+ [{client_cert_opts, COpts},
+ {server_cert_opts, SOpts} |
+ lists:delete(server_cert_opts,
+ lists:delete(client_cert_opts, Config))])];
+ false ->
+ {skip, "Missing EC crypto support"}
+ end;
+do_init_per_group(Alg, Config) when Alg == rsa_pss_rsae_1_3;
+ Alg == rsa_pss_pss_1_3 ->
Supports = crypto:supports(),
RSAOpts = proplists:get_value(rsa_opts, Supports),
@@ -468,7 +515,7 @@ missing_root_cert_no_auth(Config) when is_list(Config) ->
missing_root_cert_auth() ->
[{doc,"Must have ROOT certs to be able to verify verify peer"}].
missing_root_cert_auth(Config) when is_list(Config) ->
- ServerOpts = proplists:delete(cacertfile, ssl_test_lib:ssl_options(server_cert_opts, Config)),
+ ServerOpts = proplists:delete(cacertfile, ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)),
{ClientNode, ServerNode, _} = ssl_test_lib:run_where(Config),
Version = proplists:get_value(version, Config),
Server = ssl_test_lib:start_server_error([{node, ServerNode}, {port, 0},
@@ -478,7 +525,7 @@ missing_root_cert_auth(Config) when is_list(Config) ->
ssl_test_lib:check_result(Server, {error, {options, {cacertfile, ""}}}),
- ClientOpts = proplists:delete(cacertfile, ssl_test_lib:ssl_options(client_cert_opts, Config)),
+ ClientOpts = proplists:delete(cacertfile, ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config)),
Client = ssl_test_lib:start_client_error([{node, ClientNode}, {port, 0},
{from, self()},
{options, [{verify, verify_peer}
@@ -492,7 +539,7 @@ missing_root_cert_auth_user_verify_fun_accept() ->
" with a verify_fun that accepts the unknown CA error"}].
missing_root_cert_auth_user_verify_fun_accept(Config) ->
- ServerOpts = ssl_test_lib:ssl_options(server_cert_opts, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config),
FunAndState = {fun(_,{bad_cert, unknown_ca}, UserState) ->
{valid, UserState};
(_,{bad_cert, _} = Reason, _) ->
@@ -504,8 +551,8 @@ missing_root_cert_auth_user_verify_fun_accept(Config) ->
(_, valid_peer, UserState) ->
{valid, UserState}
end, []},
- ClientOpts = ssl_test_lib:ssl_options([{verify, verify_peer},
- {verify_fun, FunAndState}], Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, [{verify, verify_peer},
+ {verify_fun, FunAndState}], Config),
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
%%--------------------------------------------------------------------
@@ -513,7 +560,7 @@ missing_root_cert_auth_user_backwardscompatibility_verify_fun_accept() ->
[{doc, "Test old style verify fun"}].
missing_root_cert_auth_user_backwardscompatibility_verify_fun_accept(Config) ->
- ServerOpts = ssl_test_lib:ssl_options(server_cert_opts, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config),
AcceptBadCa = fun({bad_cert,unknown_ca}, Acc) -> Acc;
(Other, Acc) -> [Other | Acc]
end,
@@ -524,9 +571,8 @@ missing_root_cert_auth_user_backwardscompatibility_verify_fun_accept(Config) ->
[_|_] -> false
end
end,
-
- ClientOpts = ssl_test_lib:ssl_options([{verify, verify_peer},
- {verify_fun, VerifyFun}], Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, [{verify, verify_peer},
+ {verify_fun, VerifyFun}], Config),
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
%%--------------------------------------------------------------------
@@ -535,7 +581,7 @@ missing_root_cert_auth_user_verify_fun_reject() ->
" with a verify_fun that rejects the unknown CA error"}].
missing_root_cert_auth_user_verify_fun_reject(Config) ->
- ServerOpts = ssl_test_lib:ssl_options(server_cert_opts, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config),
FunAndState = {fun(_,{bad_cert, unknown_ca} = Reason, _UserState) ->
{fail, Reason};
(_,{bad_cert, _} = Reason, _) ->
@@ -547,8 +593,8 @@ missing_root_cert_auth_user_verify_fun_reject(Config) ->
(_, valid_peer, UserState) ->
{valid, UserState}
end, []},
- ClientOpts = ssl_test_lib:ssl_options([{verify, verify_peer},
- {verify_fun, FunAndState}], Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, [{verify, verify_peer},
+ {verify_fun, FunAndState}], Config),
ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, unknown_ca).
%%--------------------------------------------------------------------
incomplete_chain_auth() ->
@@ -563,12 +609,12 @@ incomplete_chain_auth(Config) when is_list(Config) ->
{client_chain, DefaultCertConf}]),
[ServerRoot| _] = ServerCas = proplists:get_value(cacerts, ServerOpts0),
ClientCas = proplists:get_value(cacerts, ClientOpts0),
- ClientOpts = ssl_test_lib:ssl_options([{verify, verify_peer},
- {cacerts, ServerCas ++ ClientCas} |
- proplists:delete(cacerts, ClientOpts0)], Config),
- ServerOpts = ssl_test_lib:ssl_options([{verify, verify_peer},
- {cacerts, [ServerRoot]} |
- proplists:delete(cacerts, ServerOpts0)], Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, [{verify, verify_peer},
+ {cacerts, ServerCas ++ ClientCas} |
+ proplists:delete(cacerts, ClientOpts0)], Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, [{verify, verify_peer},
+ {cacerts, [ServerRoot]} |
+ proplists:delete(cacerts, ServerOpts0)], Config),
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
%%--------------------------------------------------------------------
@@ -577,8 +623,8 @@ verify_fun_always_run_client() ->
"valid_peer not only unknown_extension)"}].
verify_fun_always_run_client(Config) when is_list(Config) ->
- ClientOpts = ssl_test_lib:ssl_options(client_cert_opts, Config),
- ServerOpts = ssl_test_lib:ssl_options(server_cert_opts, Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
Version = proplists:get_value(version, Config),
Server = ssl_test_lib:start_server_error([{node, ServerNode}, {port, 0},
@@ -618,8 +664,8 @@ verify_fun_always_run_server() ->
[{doc,"Verify that user verify_fun is always run (for valid and "
"valid_peer not only unknown_extension)"}].
verify_fun_always_run_server(Config) when is_list(Config) ->
- ClientOpts = ssl_test_lib:ssl_options(client_cert_opts, Config),
- ServerOpts = ssl_test_lib:ssl_options(server_cert_opts, Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
%% If user verify fun is called correctly we fail the connection.
@@ -681,8 +727,8 @@ critical_extension_auth(Config) when is_list(Config) ->
[{server_chain,
[[],[],[{extensions, Ext}]]},
{client_chain, DefaultCertConf}]),
- ClientOpts = ssl_test_lib:ssl_options(ClientOpts0, Config),
- ServerOpts = ssl_test_lib:ssl_options(ServerOpts0, Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, ServerOpts0, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
Version = proplists:get_value(version, Config),
@@ -713,8 +759,8 @@ critical_extension_client_auth(Config) when is_list(Config) ->
[{client_chain,
[[],[],[{extensions, Ext}]]},
{server_chain, DefaultCertConf}]),
- ClientOpts = ssl_test_lib:ssl_options(ClientOpts0, Config),
- ServerOpts = ssl_test_lib:ssl_options(ServerOpts0, Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, ServerOpts0, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
Version = proplists:get_value(version, Config),
@@ -748,8 +794,8 @@ critical_extension_no_auth(Config) when is_list(Config) ->
[{server_chain,
[[],[], [{extensions, Ext}]]},
{client_chain, DefaultCertConf}]),
- ClientOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(ClientOpts0, Config)],
- ServerOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(ServerOpts0, Config)],
+ ClientOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config)],
+ ServerOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(extra_server, ServerOpts0, Config)],
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
@@ -769,8 +815,8 @@ extended_key_usage_auth(Config) when is_list(Config) ->
[[],[], [{extensions, Ext}]]},
{client_chain, DefaultCertConf}
]),
- ClientOpts = ssl_test_lib:ssl_options(ClientOpts0, Config),
- ServerOpts = ssl_test_lib:ssl_options(ServerOpts0, Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, ServerOpts0, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
Version = proplists:get_value(version, Config),
@@ -804,8 +850,8 @@ extended_key_usage_client_auth(Config) when is_list(Config) ->
server_config := ServerOpts0} = ssl_test_lib:make_cert_chains_der(proplists:get_value(cert_key_alg, Config),
[{client_chain, [[],[],[{extensions, ClientExt}]]},
{server_chain, [[],[],[{extensions, ServerExt}]]}]),
- ClientOpts = ssl_test_lib:ssl_options(ClientOpts0, Config),
- ServerOpts = ssl_test_lib:ssl_options(ServerOpts0, Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, ServerOpts0, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
Version = proplists:get_value(version, Config),
@@ -842,8 +888,8 @@ cert_expired(Config) when is_list(Config) ->
[]
]},
{client_chain, DefaultCertConf}]),
- ClientOpts = ssl_test_lib:ssl_options(ClientOpts0, Config),
- ServerOpts = ssl_test_lib:ssl_options(ServerOpts0, Config),
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config),
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, ServerOpts0, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
Version = proplists:get_value(version, Config),
@@ -869,8 +915,8 @@ no_auth_key_identifier_ext(Config) when is_list(Config) ->
ssl_test_lib:make_cert_chains_der(proplists:get_value(cert_key_alg, Config),
[{client_chain, DefaultCertConf},
{server_chain, DefaultCertConf}]),
- ClientOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(ClientOpts0, Config)],
- ServerOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(ServerOpts0, Config)],
+ ClientOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config)],
+ ServerOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(extra_server, ServerOpts0, Config)],
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
@@ -889,8 +935,8 @@ no_auth_key_identifier_ext_keyEncipherment(Config) when is_list(Config) ->
[[],[],[{extensions, ClientExt}]]},
{server_chain, DefaultCertConf}
]),
- ClientOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(ClientOpts0, Config)],
- ServerOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(ServerOpts0, Config)],
+ ClientOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config)],
+ ServerOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(extra_server, ServerOpts0, Config)],
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
@@ -909,10 +955,10 @@ key_auth_ext_sign_only(Config) when is_list(Config) ->
{server_chain, DefaultCertConf}
]),
Version = proplists:get_value(version, Config),
- ClientOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(ClientOpts0, Config)],
+ ClientOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config)],
ServerOpts = [{verify, verify_peer}, {ciphers,
ssl_test_lib:rsa_non_signed_suites(n_version(Version))}
- | ssl_test_lib:ssl_options(ServerOpts0, Config)],
+ | ssl_test_lib:ssl_options(extra_server, ServerOpts0, Config)],
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
@@ -933,9 +979,9 @@ longer_chain(Config) when is_list(Config) ->
[ServerRoot| _] = ServerCas = proplists:get_value(cacerts, ServerOpts0),
ClientCas = proplists:get_value(cacerts, ClientOpts0),
- ServerOpts = ssl_test_lib:ssl_options([{verify, verify_peer}, {cacerts, [ServerRoot]} |
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, [{verify, verify_peer}, {cacerts, [ServerRoot]} |
proplists:delete(cacerts, ServerOpts0)], Config),
- ClientOpts = ssl_test_lib:ssl_options([{verify, verify_peer},
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, [{verify, verify_peer},
{depth, 5},
{cacerts, ServerCas ++ ClientCas} |
proplists:delete(cacerts, ClientOpts0)], Config),
@@ -972,21 +1018,21 @@ cross_signed_chain(Config)
{[_Peer,CI1New,CI2New,CRNew], CRNew} = chain_and_root(ClientOptsNew),
ServerCas = [CRNew|ServerCas0 -- [CROld]],
- ServerOpts = ssl_test_lib:ssl_options([{verify, verify_peer} |
- lists:keyreplace(cacerts, 1, ServerOpts0, {cacerts, ServerCas})],
+ ServerOpts = ssl_test_lib:ssl_options(extra_server, [{verify, verify_peer} |
+ lists:keyreplace(cacerts, 1, ServerOpts0, {cacerts, ServerCas})],
Config),
- ClientOpts = ssl_test_lib:ssl_options([{verify, verify_peer} |
- lists:keyreplace(cacerts, 1,
- lists:keyreplace(cert, 1, ClientOpts0,
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, [{verify, verify_peer} |
+ lists:keyreplace(cacerts, 1,
+ lists:keyreplace(cert, 1, ClientOpts0,
{cert, [Peer,CI1New,CI2New,CI1,CI2,CRNew,CROld]}),
- {cacerts, ClientCas0})],
+ {cacerts, ClientCas0})],
Config),
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config),
- ClientOpts2 = ssl_test_lib:ssl_options([{verify, verify_peer} |
- lists:keyreplace(cacerts, 1,
- lists:keyreplace(cert, 1, ClientOpts0,
- {cert, [Peer,CI1,CI1New,CI2,CI2New,CROld,CRNew]}),
- {cacerts, ClientCas0})],
+ ClientOpts2 = ssl_test_lib:ssl_options(extra_client, [{verify, verify_peer} |
+ lists:keyreplace(cacerts, 1,
+ lists:keyreplace(cert, 1, ClientOpts0,
+ {cert, [Peer,CI1,CI1New,CI2,CI2New,CROld,CRNew]}),
+ {cacerts, ClientCas0})],
Config),
ssl_test_lib:basic_test(ClientOpts2, ServerOpts, Config),
ok.
diff --git a/lib/ssl/test/ssl_cert_tests.erl b/lib/ssl/test/ssl_cert_tests.erl
index d9d535106a..2b71998b11 100644
--- a/lib/ssl/test/ssl_cert_tests.erl
+++ b/lib/ssl/test/ssl_cert_tests.erl
@@ -78,8 +78,8 @@ no_auth() ->
[{doc,"Test connection without authentication"}].
no_auth(Config) ->
- ClientOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(client_cert_opts, Config)],
- ServerOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(server_cert_opts, Config)],
+ ClientOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config)],
+ ServerOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)],
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
%%--------------------------------------------------------------------
@@ -87,8 +87,8 @@ auth() ->
[{doc,"Test connection with mutual authentication"}].
auth(Config) ->
- ClientOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(client_cert_opts, Config)],
- ServerOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(server_cert_opts, Config)],
+ ClientOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config)],
+ ServerOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)],
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
@@ -100,8 +100,8 @@ client_auth_empty_cert_accepted() ->
client_auth_empty_cert_accepted(Config) ->
ClientOpts = proplists:delete(keyfile,
proplists:delete(certfile,
- ssl_test_lib:ssl_options(client_cert_opts, Config))),
- ServerOpts0 = ssl_test_lib:ssl_options(server_cert_opts, Config),
+ ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config))),
+ ServerOpts0 = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config),
ServerOpts = [{verify, verify_peer},
{fail_if_no_peer_cert, false} | ServerOpts0],
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
@@ -112,8 +112,8 @@ client_auth_empty_cert_rejected() ->
client_auth_empty_cert_rejected(Config) ->
ServerOpts = [{verify, verify_peer}, {fail_if_no_peer_cert, true}
- | ssl_test_lib:ssl_options(server_cert_opts, Config)],
- ClientOpts0 = ssl_test_lib:ssl_options([], Config),
+ | ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)],
+ ClientOpts0 = ssl_test_lib:ssl_options(extra_client, [], Config),
%% Delete Client Cert and Key
ClientOpts1 = proplists:delete(certfile, ClientOpts0),
ClientOpts = proplists:delete(keyfile, ClientOpts1),
@@ -131,8 +131,8 @@ client_auth_partial_chain() ->
client_auth_partial_chain(Config) when is_list(Config) ->
ServerOpts = [{verify, verify_peer}, {fail_if_no_peer_cert, true}
- | ssl_test_lib:ssl_options(server_cert_opts, Config)],
- ClientOpts0 = ssl_test_lib:ssl_options(client_cert_opts, Config),
+ | ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)],
+ ClientOpts0 = ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config),
{ok, ClientCAs} = file:read_file(proplists:get_value(cacertfile, ClientOpts0)),
[{_,RootCA,_} | _] = public_key:pem_decode(ClientCAs),
ClientOpts = [{cacerts, [RootCA]} |
@@ -145,8 +145,8 @@ client_auth_allow_partial_chain() ->
client_auth_allow_partial_chain(Config) when is_list(Config) ->
ServerOpts0 = [{verify, verify_peer}, {fail_if_no_peer_cert, true}
- | ssl_test_lib:ssl_options(server_cert_opts, Config)],
- ClientOpts = ssl_test_lib:ssl_options(client_cert_opts, Config),
+ | ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)],
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config),
{ok, ClientCAs} = file:read_file(proplists:get_value(cacertfile, ClientOpts)),
[{_,_,_}, {_, IntermidiateCA, _} | _] = public_key:pem_decode(ClientCAs),
@@ -171,8 +171,8 @@ client_auth_do_not_allow_partial_chain() ->
client_auth_do_not_allow_partial_chain(Config) when is_list(Config) ->
ServerOpts0 = [{verify, verify_peer}, {fail_if_no_peer_cert, true}
- | ssl_test_lib:ssl_options(server_cert_opts, Config)],
- ClientOpts = ssl_test_lib:ssl_options(client_cert_opts, Config),
+ | ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)],
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config),
{ok, ServerCAs} = file:read_file(proplists:get_value(cacertfile, ServerOpts0)),
[{_,_,_}, {_, IntermidiateCA, _} | _] = public_key:pem_decode(ServerCAs),
@@ -190,8 +190,8 @@ client_auth_partial_chain_fun_fail() ->
client_auth_partial_chain_fun_fail(Config) when is_list(Config) ->
ServerOpts0 = [{verify, verify_peer}, {fail_if_no_peer_cert, true}
- | ssl_test_lib:ssl_options(server_cert_opts, Config)],
- ClientOpts = ssl_test_lib:ssl_options(client_cert_opts, Config),
+ | ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)],
+ ClientOpts = ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config),
{ok, ServerCAs} = file:read_file(proplists:get_value(cacertfile, ServerOpts0)),
[{_,_,_}, {_, IntermidiateCA, _} | _] = public_key:pem_decode(ServerCAs),
@@ -209,7 +209,7 @@ client_auth_partial_chain_fun_fail(Config) when is_list(Config) ->
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),
+ ServerOpts0 = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config),
FunAndState = {fun(valid_peer, {bad_cert, unknown_ca}, UserState) ->
{valid_peer, UserState};
@@ -223,7 +223,7 @@ client_auth_sni(Config) when is_list(Config) ->
{valid, UserState}
end, []},
- ClientOpts0 = ssl_test_lib:ssl_options(client_cert_opts, Config),
+ ClientOpts0 = ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config),
ClientOpts = [{verify, verify_peer}, {verify_fun, FunAndState
}, {server_name_indication, "localhost"} | ClientOpts0],
@@ -247,16 +247,16 @@ client_auth_seelfsigned_peer(Config) when is_list(Config) ->
key := Key} = public_key:pkix_test_root_cert("OTP test server ROOT", [{key, ssl_test_lib:hardcode_rsa_key(6)},
{extensions, Ext}]),
DerKey = public_key:der_encode('RSAPrivateKey', Key),
- ssl_test_lib:basic_alert(ssl_test_lib:ssl_options([{verify, verify_peer}, {cacerts , [Cert]}], Config),
- ssl_test_lib:ssl_options([{cert, Cert},
- {key, {'RSAPrivateKey', DerKey}}], Config), Config, bad_certificate).
+ ssl_test_lib:basic_alert(ssl_test_lib:ssl_options(extra_client, [{verify, verify_peer}, {cacerts , [Cert]}], Config),
+ ssl_test_lib:ssl_options(extra_server, [{cert, Cert},
+ {key, {'RSAPrivateKey', DerKey}}], Config), Config, bad_certificate).
%%--------------------------------------------------------------------
missing_root_cert_no_auth() ->
[{doc,"Test that the client succeeds if the ROOT CA is unknown in verify_none mode"}].
missing_root_cert_no_auth(Config) ->
- ClientOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(client_cert_opts, Config)],
- ServerOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(server_cert_opts, Config)],
+ ClientOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config)],
+ ServerOpts = [{verify, verify_none} | ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)],
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
@@ -265,8 +265,8 @@ invalid_signature_client() ->
[{doc,"Test server with invalid signature"}].
invalid_signature_client(Config) when is_list(Config) ->
- ClientOpts0 = ssl_test_lib:ssl_options(client_cert_opts, Config),
- ServerOpts0 = ssl_test_lib:ssl_options(server_cert_opts, Config),
+ ClientOpts0 = ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config),
+ ServerOpts0 = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config),
PrivDir = proplists:get_value(priv_dir, Config),
KeyFile = proplists:get_value(keyfile, ClientOpts0),
@@ -289,8 +289,8 @@ invalid_signature_server() ->
[{doc,"Test client with invalid signature"}].
invalid_signature_server(Config) when is_list(Config) ->
- ClientOpts0 = ssl_test_lib:ssl_options(client_cert_opts, Config),
- ServerOpts0 = ssl_test_lib:ssl_options(server_cert_opts, Config),
+ ClientOpts0 = ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config),
+ ServerOpts0 = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config),
PrivDir = proplists:get_value(priv_dir, Config),
KeyFile = proplists:get_value(keyfile, ServerOpts0),
diff --git a/lib/ssl/test/ssl_handshake_SUITE.erl b/lib/ssl/test/ssl_handshake_SUITE.erl
index df8f867f24..d5a591db01 100644
--- a/lib/ssl/test/ssl_handshake_SUITE.erl
+++ b/lib/ssl/test/ssl_handshake_SUITE.erl
@@ -193,10 +193,10 @@ ignore_hassign_extension_pre_tls_1_2(Config) ->
CertFile = proplists:get_value(certfile, Opts),
[{_, Cert, _}] = ssl_test_lib:pem_to_der(CertFile),
HashSigns = #hash_sign_algos{hash_sign_algos = [{sha512, rsa}, {sha, dsa}, {sha256, rsa}]},
- {sha512, rsa} = ssl_handshake:select_hashsign({HashSigns, undefined}, Cert, ecdhe_rsa, tls_v1:default_signature_algs({3,3}), {3,3}),
+ {sha512, rsa} = ssl_handshake:select_hashsign({HashSigns, undefined}, Cert, ecdhe_rsa, tls_v1:default_signature_algs([{3,3}]), {3,3}),
%%% Ignore
- {md5sha, rsa} = ssl_handshake:select_hashsign({HashSigns, undefined}, Cert, ecdhe_rsa, tls_v1:default_signature_algs({3,2}), {3,2}),
- {md5sha, rsa} = ssl_handshake:select_hashsign({HashSigns, undefined}, Cert, ecdhe_rsa, tls_v1:default_signature_algs({3,0}), {3,0}).
+ {md5sha, rsa} = ssl_handshake:select_hashsign({HashSigns, undefined}, Cert, ecdhe_rsa, tls_v1:default_signature_algs([{3,2}]), {3,2}),
+ {md5sha, rsa} = ssl_handshake:select_hashsign({HashSigns, undefined}, Cert, ecdhe_rsa, tls_v1:default_signature_algs([{3,0}]), {3,0}).
encode_decode_srp(_Config) ->
Exts = #{srp => #srp{username = <<"foo">>},
@@ -238,7 +238,7 @@ signature_algorithms(Config) ->
{sha512, rsa} = ssl_handshake:select_hashsign(
{HashSigns0, Schemes0},
Cert, ecdhe_rsa,
- tls_v1:default_signature_algs({3,3}),
+ tls_v1:default_signature_algs([{3,3}]),
{3,3}),
HashSigns1 = #hash_sign_algos{
hash_sign_algos = [{sha, dsa},
@@ -246,7 +246,7 @@ signature_algorithms(Config) ->
{sha256, rsa} = ssl_handshake:select_hashsign(
{HashSigns1, Schemes0},
Cert, ecdhe_rsa,
- tls_v1:default_signature_algs({3,3}),
+ tls_v1:default_signature_algs([{3,3}]),
{3,3}),
Schemes1 = #signature_algorithms_cert{
signature_scheme_list = [rsa_pkcs1_sha1,
@@ -255,13 +255,13 @@ signature_algorithms(Config) ->
#alert{} = ssl_handshake:select_hashsign(
{HashSigns1, Schemes1},
Cert, ecdhe_rsa,
- tls_v1:default_signature_algs({3,3}),
+ tls_v1:default_signature_algs([{3,3}]),
{3,3}),
%% No scheme, hashsign is used
{sha256, rsa} = ssl_handshake:select_hashsign(
{HashSigns1, undefined},
Cert, ecdhe_rsa,
- tls_v1:default_signature_algs({3,3}),
+ tls_v1:default_signature_algs([{3,3}]),
{3,3}),
HashSigns2 = #hash_sign_algos{
hash_sign_algos = [{sha, dsa}]},
@@ -269,7 +269,7 @@ signature_algorithms(Config) ->
#alert{} = ssl_handshake:select_hashsign(
{HashSigns2, Schemes1},
Cert, ecdhe_rsa,
- tls_v1:default_signature_algs({3,3}),
+ tls_v1:default_signature_algs([{3,3}]),
{3,3}).
%%--------------------------------------------------------------------
diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl
index 17a04fb374..e4c23c22cf 100644
--- a/lib/ssl/test/ssl_test_lib.erl
+++ b/lib/ssl/test/ssl_test_lib.erl
@@ -35,6 +35,7 @@
end_per_group/2,
ct_log_supported_protocol_versions/1,
ssl_options/2,
+ ssl_options/3,
run_where/1,
run_where/2,
inet_port/1,
@@ -3277,6 +3278,10 @@ ubuntu_legacy_support() ->
true
end.
+ssl_options(Extra, Option, Config) ->
+ ExtraOpts = proplists:get_value(Extra, Config, []),
+ ExtraOpts ++ ssl_options(Option, Config).
+
ssl_options(Option, Config) when is_atom(Option) ->
ProtocolOpts = proplists:get_value(protocol_opts, Config, []),
Opts = proplists:get_value(Option, Config, []),
--
2.31.1