File 3781-Allow-disabling-certificate_authorities-extension-on.patch of Package erlang
From 909d3a99fbaafbed71dc8f59da24b324631b2ae1 Mon Sep 17 00:00:00 2001
From: Jon Carstens <jjcarstens@me.com>
Date: Wed, 17 Aug 2022 16:13:11 -0600
Subject: [PATCH] Allow disabling `certificate_authorities` extension on server
with `verify_peer`
Fixes #6106
Based on the discussion from the issue (and #6204), it was decided that adding the
ability to disable the `certificate_authorities` extension on the server would be
the fitting resolution for situations where you do not want that extension forced
in TLS 1.3.
This adds that ability to specify as a server option and defaults to `true` to keep
with existing expected functionality.
---
lib/ssl/doc/src/ssl.xml | 16 +++++++++---
lib/ssl/src/ssl.erl | 16 +++++++-----
lib/ssl/src/tls_handshake_1_3.erl | 19 +++++++++-----
lib/ssl/test/ssl_cert_SUITE.erl | 43 +++++++++++++++++++++++++++++--
4 files changed, 75 insertions(+), 19 deletions(-)
diff --git a/lib/ssl/doc/src/ssl.xml b/lib/ssl/doc/src/ssl.xml
index 024fd4c1be..dc946d6564 100644
--- a/lib/ssl/doc/src/ssl.xml
+++ b/lib/ssl/doc/src/ssl.xml
@@ -1033,7 +1033,7 @@ fun(srp, Username :: binary(), UserState :: term()) ->
</datatype>
<datatype>
- <name name="certificate_authorities"/>
+ <name name="client_certificate_authorities"/>
<desc>
<p>If set to true, sends the certificate authorities extension in TLS-1.3 client hello.
The default is false. Note that setting it to true may result in a big overhead if you
@@ -1248,6 +1248,15 @@ fun(srp, Username :: binary(), UserState :: term()) ->
is supplied it overrides option <c>cacertfile</c>.</p>
</desc>
</datatype>
+
+ <datatype>
+ <name since="OTP 25.2" name="server_certificate_authorities"/>
+ <desc>
+ <p>When used with <c>{verify, verify_peer}</c> on the server with TLS-1.3, the certificate
+ authorities extension will be included or excluded from the certificate request. The Default
+ is true.</p>
+ </desc>
+ </datatype>
<datatype>
<name name="server_cafile"/>
@@ -1287,8 +1296,9 @@ fun(srp, Username :: binary(), UserState :: term()) ->
A server only does x509-certificate path validation in mode
<c>verify_peer</c>. By default the server is in <c>verify_none</c> mode
an hence will not send an certificate request to the client.
- When using <c>verify_peer</c> you may also want to specify the option
- <seetype marker="#fail_if_no_peer_cert">fail_if_no_peer_cert</seetype>.</p>
+ When using <c>verify_peer</c> you may also want to specify the options
+ <seetype marker="#fail_if_no_peer_cert">fail_if_no_peer_cert</seetype> and
+ <seetype marker="#server_certificate_authorities">certificate_authorities</seetype>.</p>
</desc>
</datatype>
diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl
index 53e58ceee9..acd79eae90 100644
--- a/lib/ssl/src/ssl.erl
+++ b/lib/ssl/src/ssl.erl
@@ -418,7 +418,7 @@
{customize_hostname_check, customize_hostname_check()} |
{fallback, fallback()} |
{middlebox_comp_mode, middlebox_comp_mode()} |
- {certificate_authorities, certificate_authorities()} |
+ {certificate_authorities, client_certificate_authorities()} |
{session_tickets, client_session_tickets()} |
{use_ticket, use_ticket()} |
{early_data, client_early_data()}.
@@ -429,7 +429,7 @@
-type client_verify_type() :: verify_type().
-type client_reuse_session() :: session_id() | {session_id(), SessionData::binary()}.
-type client_reuse_sessions() :: boolean() | save.
--type certificate_authorities() :: boolean().
+-type client_certificate_authorities() :: boolean().
-type client_cacerts() :: [public_key:der_encoded()].
-type client_cafile() :: file:filename().
-type app_level_protocol() :: binary().
@@ -458,6 +458,7 @@
{dhfile, dh_file()} |
{verify, server_verify_type()} |
{fail_if_no_peer_cert, fail_if_no_peer_cert()} |
+ {certificate_authorities, server_certificate_authorities()} |
{reuse_sessions, server_reuse_sessions()} |
{reuse_session, server_reuse_session()} |
{alpn_preferred_protocols, server_alpn()} |
@@ -490,6 +491,7 @@
-type client_renegotiation() :: boolean().
-type stateless_tickets_seed() :: binary().
-type cookie() :: boolean().
+-type server_certificate_authorities() :: boolean().
%% -------------------------------------------------------------------------------------------------------
-type prf_random() :: client_random | server_random. % exported
-type protocol_extensions() :: #{renegotiation_info => binary(),
@@ -1684,11 +1686,11 @@ handle_option(fallback = Option, Value0, OptionsMap, #{role := Role}) ->
assert_role(client_only, Role, Option, Value0),
Value = validate_option(Option, Value0),
OptionsMap#{Option => Value};
-handle_option(certificate_authorities = Option, unbound, OptionsMap, #{role := Role}) ->
- Value = default_option_role(client, false, Role),
- OptionsMap#{Option => Value};
-handle_option(certificate_authorities = Option, Value0, #{versions := Versions} = OptionsMap, #{role := Role}) ->
- assert_role(client_only, Role, Option, Value0),
+handle_option(certificate_authorities = Option, unbound, OptionsMap, #{role := server}) ->
+ OptionsMap#{Option => true};
+handle_option(certificate_authorities = Option, unbound, OptionsMap, #{role := client}) ->
+ OptionsMap#{Option => false};
+handle_option(certificate_authorities = Option, Value0, #{versions := Versions} = OptionsMap, _Env) ->
assert_option_dependency(Option, versions, Versions, ['tlsv1.3']),
Value = validate_option(Option, Value0),
OptionsMap#{Option => Value};
diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl
index e68b2f96f0..dedfb604b0 100644
--- a/lib/ssl/src/tls_handshake_1_3.erl
+++ b/lib/ssl/src/tls_handshake_1_3.erl
@@ -204,18 +204,23 @@ encrypted_extensions(#state{handshake_env = HandshakeEnv}) ->
}.
-certificate_request(SignAlgs0, SignAlgsCert0, CertDbHandle, CertDbRef) ->
+certificate_request(SignAlgs0, SignAlgsCert0, CertDbHandle, CertDbRef, CertAuthBool) ->
%% Input arguments contain TLS 1.2 algorithms due to backward compatibility
%% reasons. These {Hash, Algo} tuples must be filtered before creating the
%% the extensions.
SignAlgs = filter_tls13_algs(SignAlgs0),
SignAlgsCert = filter_tls13_algs(SignAlgsCert0),
Extensions0 = add_signature_algorithms(#{}, SignAlgs),
- Extensions = add_signature_algorithms_cert(Extensions0, SignAlgsCert),
- Auths = ssl_handshake:certificate_authorities(CertDbHandle, CertDbRef),
+ Extensions1 = add_signature_algorithms_cert(Extensions0, SignAlgsCert),
+ Extensions = if CertAuthBool =:= true ->
+ Auths = ssl_handshake:certificate_authorities(CertDbHandle, CertDbRef),
+ Extensions1#{certificate_authorities => #certificate_authorities{authorities = Auths}};
+ true ->
+ Extensions1
+ end,
#certificate_request_1_3{
certificate_request_context = <<>>,
- extensions = Extensions#{certificate_authorities => #certificate_authorities{authorities = Auths}}}.
+ extensions = Extensions}.
add_signature_algorithms(Extensions, SignAlgs) ->
@@ -1346,8 +1351,9 @@ maybe_send_certificate_request(#state{static_env = #static_env{protocol_cb = Con
cert_db_ref = CertDbRef}} = State,
#{verify := verify_peer,
signature_algs := SignAlgs,
- signature_algs_cert := SignAlgsCert}, _) ->
- CertificateRequest = certificate_request(SignAlgs, SignAlgsCert, CertDbHandle, CertDbRef),
+ signature_algs_cert := SignAlgsCert,
+ certificate_authorities := CertAuthBool}, _) ->
+ CertificateRequest = certificate_request(SignAlgs, SignAlgsCert, CertDbHandle, CertDbRef, CertAuthBool),
{Connection:queue_handshake(CertificateRequest, State), wait_cert}.
maybe_send_certificate(State, PSK) when PSK =/= undefined ->
@@ -3061,4 +3067,3 @@ select_client_cert_key_pair(Session0, [#{private_key := Key, certs := [Cert| _] = Certs} | Rest],
select_client_cert_key_pair(Session0, Rest, ServerSignAlgsCert, ServerSignAlgsCert, ClientSignAlgs,
CertDbHandle, CertDbRef, CertAuths)
end.
-
diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl
index d038cb64a2..1dcac41b19 100644
--- a/lib/ssl/test/ssl_cert_SUITE.erl
+++ b/lib/ssl/test/ssl_cert_SUITE.erl
@@ -123,7 +123,9 @@
signature_algorithms_bad_curve_secp384r1/0,
signature_algorithms_bad_curve_secp384r1/1,
signature_algorithms_bad_curve_secp521r1/0,
- signature_algorithms_bad_curve_secp521r1/1
+ signature_algorithms_bad_curve_secp521r1/1,
+ server_certificate_authorities_disabled/0,
+ server_certificate_authorities_disabled/1
]).
%%--------------------------------------------------------------------
@@ -191,7 +193,8 @@ tls_1_3_tests() ->
client_auth_no_suitable_chain,
hello_retry_client_auth,
hello_retry_client_auth_empty_cert_accepted,
- hello_retry_client_auth_empty_cert_rejected
+ hello_retry_client_auth_empty_cert_rejected,
+ server_certificate_authorities_disabled
].
pre_tls_1_3_rsa_tests() ->
@@ -1287,6 +1290,42 @@ basic_rsa_1024(Config) ->
{fail_if_no_peer_cert, true} | ServerOpts1],
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
+%%--------------------------------------------------------------------
+server_certificate_authorities_disabled() ->
+ [{doc,"TLS 1.3: Disabling certificate_authorities extension on the server when verify_peer is set to true"
+ " allows the client to send a chain that could be verifiable by the server but that would not adhere to"
+ " the certificate_authorities extension as it is not part of the regular trusted certificate set"}].
+
+server_certificate_authorities_disabled(Config) ->
+ ClientOpts0 = ssl_test_lib:ssl_options(client_cert_opts, Config),
+ ServerOpts0 = ssl_test_lib:ssl_options(server_cert_opts, Config),
+
+ % Strip out the ClientRoot to simulate cases where the they are manually managed and
+ % not expected to be included in certificate requests during mutual authentication.
+ {ok, CACerts0} = ssl_pkix_db:decode_pem_file(proplists:get_value(cacertfile, ServerOpts0)),
+ [_ClientRoot | ServerCACerts] = [CertDER || {_, CertDER, _} <- CACerts0],
+
+ FunAndState = {fun(_,{extension, _}, UserState) ->
+ {unknown, UserState};
+ (_, valid, UserState) ->
+ {valid, UserState};
+ % Because this is a manually managed setup, we also need to manually verify
+ % an unknown_ca (ClientCert) as expected. Typically you would have custom logic
+ % here to decide if you know the cert (like looking up pinned values in a DB)
+ % but for testing purposes, we'll allow everything
+ (_, {bad_cert, unknown_ca}, UserState) ->
+ {valid, UserState};
+ (_, valid_peer, UserState) ->
+ {valid, UserState}
+ end, [0]},
+
+ ClientOpts = [{versions, ['tlsv1.3']}, {verify, verify_peer} | ClientOpts0],
+ ServerOpts = [{versions, ['tlsv1.3']}, {verify, verify_peer},
+ {fail_if_no_peer_cert, true}, {cacerts, ServerCACerts},
+ {verify_fun, FunAndState} | ServerOpts0],
+ ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, certificate_required),
+ ssl_test_lib:basic_test(ClientOpts, [{certificate_authorities, false} | ServerOpts], Config).
+
%%--------------------------------------------------------------------
%% Internal functions -----------------------------------------------
%%--------------------------------------------------------------------
--
2.35.3