Skip to content

Commit

Permalink
ssl: Enhance client certificate selection
Browse files Browse the repository at this point in the history
In TLS-1.3, if chain certs are missing (so server auth domain adherence
can not be determined) send peer cert and hope the server is able to
recreate a chain in its auth domain.

Closes #6105
  • Loading branch information
IngelaAndin committed Aug 16, 2022
1 parent a9b0119 commit 27fdcf6
Show file tree
Hide file tree
Showing 3 changed files with 69 additions and 26 deletions.
38 changes: 29 additions & 9 deletions lib/ssl/src/tls_handshake_1_3.erl
Expand Up @@ -1446,7 +1446,7 @@ process_certificate_request(#certificate_request_1_3{
CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts, Version),
Session = select_client_cert_key_pair(Session0, CertKeyPairs,
ServerSignAlgs, ServerSignAlgsCert, ClientSignAlgs,
CertDbHandle, CertDbRef, CertAuths),
CertDbHandle, CertDbRef, CertAuths, undefined),
{ok, {State#state{client_certificate_status = requested, session = Session}, wait_cert}}.

process_certificate(#certificate_1_3{
Expand Down Expand Up @@ -3029,16 +3029,24 @@ default_or_fallback(Default, _) ->

select_client_cert_key_pair(Session0,
[#{private_key := NoKey, certs := [[]] = NoCerts}],
_,_,_,_,_,_) ->
_,_,_,_,_,_, _) ->
%% No certificate supplied : send empty certificate
Session0#session{own_certificates = NoCerts,
private_key = NoKey};
select_client_cert_key_pair(Session, [],_,_,_,_,_,_) ->
%% No certificate compliant with supported algorithms and extensison : send empty certificate in state 'wait_finished'
select_client_cert_key_pair(Session, [],_,_,_,_,_,_, undefined) ->
%% No certificate compliant with supported algorithms and
%% extensison : send empty certificate in state 'wait_finished'
Session#session{own_certificates = [[]],
private_key = #{}};
select_client_cert_key_pair(_,[],_,_,_,_,_,_, #session{} = Plausible) ->
%% If we do not find an alternative chain with a cert signed in auth_domain,
%% but have a single cert without chain certs it might be verifiable by
%% a server that has the means to recreate the chain
Plausible;
select_client_cert_key_pair(Session0, [#{private_key := Key, certs := [Cert| _] = Certs} | Rest],
ServerSignAlgs, ServerSignAlgsCert, ClientSignAlgs, CertDbHandle, CertDbRef, CertAuths) ->
ServerSignAlgs, ServerSignAlgsCert,
ClientSignAlgs, CertDbHandle, CertDbRef,
CertAuths, Plausible0) ->
{PublicKeyAlgo, SignAlgo, SignHash, MaybeRSAKeySize, Curve} = get_certificate_params(Cert),
case select_sign_algo(PublicKeyAlgo, MaybeRSAKeySize, ServerSignAlgs, ClientSignAlgs, Curve) of
{ok, SelectedSignAlg} ->
Expand All @@ -3051,15 +3059,27 @@ select_client_cert_key_pair(Session0, [#{private_key := Key, certs := [Cert| _]
own_certificates = EncodedChain,
private_key = Key
};
{error, _, not_in_auth_domain} ->
{error, EncodedChain, not_in_auth_domain} ->
Plausible = plausible_missing_chain(EncodedChain, Plausible0,
SelectedSignAlg, Key, Session0),
select_client_cert_key_pair(Session0, Rest, ServerSignAlgs, ServerSignAlgsCert,
ClientSignAlgs, CertDbHandle, CertDbRef, CertAuths)
ClientSignAlgs, CertDbHandle, CertDbRef, CertAuths,
Plausible)
end;
_ ->
select_client_cert_key_pair(Session0, Rest, ServerSignAlgs, ServerSignAlgsCert, ClientSignAlgs,
CertDbHandle, CertDbRef, CertAuths)
CertDbHandle, CertDbRef, CertAuths, Plausible0)
end;
{error, _} ->
select_client_cert_key_pair(Session0, Rest, ServerSignAlgsCert, ServerSignAlgsCert, ClientSignAlgs,
CertDbHandle, CertDbRef, CertAuths)
CertDbHandle, CertDbRef, CertAuths, Plausible0)
end.

plausible_missing_chain([_] = EncodedChain, undefined, SignAlg, Key, Session0) ->
Session0#session{sign_alg = SignAlg,
own_certificates = EncodedChain,
private_key = Key
};
plausible_missing_chain(_,Plausible,_,_,_) ->
Plausible.

30 changes: 30 additions & 0 deletions lib/ssl/test/ssl_cert_SUITE.erl
Expand Up @@ -72,6 +72,8 @@
verify_fun_always_run_server/1,
incomplete_chain_auth/0,
incomplete_chain_auth/1,
no_chain_client_auth/0,
no_chain_client_auth/1,
invalid_signature_client/0,
invalid_signature_client/1,
invalid_signature_server/0,
Expand Down Expand Up @@ -233,6 +235,7 @@ all_version_tests() ->
verify_fun_always_run_client,
verify_fun_always_run_server,
incomplete_chain_auth,
no_chain_client_auth,
invalid_signature_client,
invalid_signature_server,
critical_extension_auth,
Expand Down Expand Up @@ -573,6 +576,8 @@ missing_root_cert_auth_user_verify_fun_reject(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() ->
[{doc,"Test that we can verify an incompleat chain when we have the certs to rebuild it"}].
Expand All @@ -594,6 +599,31 @@ incomplete_chain_auth(Config) when is_list(Config) ->
proplists:delete(cacerts, ServerOpts0)], Config),
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).

%%--------------------------------------------------------------------
no_chain_client_auth() ->
[{doc,"In TLS-1.3 test that we allow sending only peer cert if chain CAs are missing and hence"
" we can not determine if client is in servers auth domain or not, so send and hope"
" that the cert chain is in the auth domain and that the server possess "
" intermediates to recreate the chain."}].
no_chain_client_auth(Config) when is_list(Config) ->
Prop = proplists:get_value(tc_group_properties, Config),
Group = proplists:get_value(name, Prop),
DefaultCertConf = ssl_test_lib:default_ecc_cert_chain_conf(Group),
#{client_config := ClientOpts0,
server_config := ServerOpts0} = ssl_test_lib:make_cert_chains_der(proplists:get_value(cert_key_alg, Config),
[{server_chain, DefaultCertConf},
{client_chain, DefaultCertConf}]),
ServerCas = proplists:get_value(cacerts, ServerOpts0),
[ClientRoot| _] = ClientCas = proplists:get_value(cacerts, ClientOpts0),
ClientOpts = ssl_test_lib:ssl_options(extra_client, [{verify, verify_peer},
{cacerts, [ClientRoot]} |
proplists:delete(cacerts, ClientOpts0)], Config),
ServerOpts = ssl_test_lib:ssl_options(extra_server, [{verify, verify_peer},
{fail_if_no_peer_cert, true},
{cacerts, ClientCas ++ ServerCas} |
proplists:delete(cacerts, ServerOpts0)], Config),
ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).

%%--------------------------------------------------------------------
verify_fun_always_run_client() ->
[{doc,"Verify that user verify_fun is always run (for valid and "
Expand Down
27 changes: 10 additions & 17 deletions lib/ssl/test/ssl_cert_tests.erl
Expand Up @@ -133,14 +133,17 @@ client_auth_no_suitable_chain() ->
[{doc, "Client sends an empty cert chain as no suitable chain is found."}].

client_auth_no_suitable_chain(Config) when is_list(Config) ->
CRoot = public_key:pkix_test_root_cert("OTP other client test ROOT", []),
#{client_config := ClientOpts0} = public_key:pkix_test_data(#{server_chain => #{root => [],
intermediates => [[]],
peer => []},
client_chain => #{root => CRoot,
intermediates => [[]],
peer => []}}),
ClientOpts = ssl_test_lib:ssl_options(extra_client, ClientOpts0, Config),
ServerOpts = [{verify, verify_peer}, {fail_if_no_peer_cert, true}
| 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]} |
proplists:delete(cacertfile, ClientOpts0)],
Version = proplists:get_value(version,Config),
Version = proplists:get_value(version, Config),

case Version of
'tlsv1.3' ->
Expand All @@ -149,7 +152,6 @@ client_auth_no_suitable_chain(Config) when is_list(Config) ->
ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, handshake_failure)
end.


%%--------------------------------------------------------------------
client_auth_use_partial_chain() ->
[{doc, "Client trusts intermediat CA and verifies the shorter chain."}].
Expand Down Expand Up @@ -308,16 +310,7 @@ invalid_signature_client(Config) when is_list(Config) ->
ssl_test_lib:der_to_pem(NewClientCertFile, [{'Certificate', NewClientDerCert, not_encrypted}]),
ClientOpts = [{certfile, NewClientCertFile} | proplists:delete(certfile, ClientOpts0)],
ServerOpts = [{verify, verify_peer}, {fail_if_no_peer_cert, true} | ServerOpts0],
Version = proplists:get_value(version,Config),

case Version of
'tlsv1.3' ->
%% Client will not be able to create chain to send that matches
%% certificate authorities
ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, certificate_required);
_ ->
ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, unknown_ca)
end.
ssl_test_lib:basic_alert(ClientOpts, ServerOpts, Config, unknown_ca).

%%--------------------------------------------------------------------
invalid_signature_server() ->
Expand Down

0 comments on commit 27fdcf6

Please sign in to comment.