Skip to content

Commit

Permalink
ssl: Correct Option handling in TLS-1.3
Browse files Browse the repository at this point in the history
Options supplied based on SNI did not properly override
listen options for TLS-1.3 connections.
  • Loading branch information
IngelaAndin committed Jun 24, 2024
1 parent 928d03e commit 31987f6
Show file tree
Hide file tree
Showing 2 changed files with 83 additions and 18 deletions.
37 changes: 20 additions & 17 deletions lib/ssl/src/tls_server_connection_1_3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -390,17 +390,22 @@ handle_client_hello(ClientHello, State0) ->
do_handle_client_hello(#client_hello{cipher_suites = ClientCiphers,
random = Random,
session_id = SessionId,
extensions = Extensions} = Hello,
#state{ssl_options = #{ciphers := ServerCiphers,
signature_algs := ServerSignAlgs,
supported_groups := ServerGroups0,
alpn_preferred_protocols := ALPNPreferredProtocols,
honor_cipher_order := HonorCipherOrder,
early_data := EarlyDataEnabled} = Opts} = State0) ->
extensions = Extensions} = Hello, State0) ->
SNI = maps:get(sni, Extensions, undefined),
EarlyDataIndication = maps:get(early_data, Extensions, undefined),
{Ref,Maybe} = tls_gen_connection_1_3:do_maybe(),
try
#state{connection_states = ConnectionStates0,
session = Session0,
ssl_options = #{ciphers := ServerCiphers,
signature_algs := ServerSignAlgs,
supported_groups := ServerGroups0,
alpn_preferred_protocols := ALPNPreferredProtocols,
honor_cipher_order := HonorCipherOrder},
connection_env = #connection_env{cert_key_alts = CertKeyAlts}
} = State1 =
Maybe(ssl_gen_statem:handle_sni_extension(SNI, State0)),

ClientGroups0 = Maybe(tls_handshake_1_3:supported_groups_from_extensions(Extensions)),
ClientGroups = Maybe(tls_handshake_1_3:get_supported_groups(ClientGroups0)),
ServerGroups = Maybe(tls_handshake_1_3:get_supported_groups(ServerGroups0)),
Expand All @@ -415,15 +420,10 @@ do_handle_client_hello(#client_hello{cipher_suites = ClientCiphers,
maps:get(signature_algs, Extensions, undefined)),
ClientSignAlgsCert = tls_handshake_1_3:get_signature_scheme_list(
maps:get(signature_algs_cert, Extensions, undefined)),
CertAuths = tls_handshake_1_3:get_certificate_authorities(maps:get(certificate_authorities,
Extensions, undefined)),
CertAuths = tls_handshake_1_3:get_certificate_authorities(maps:get(certificate_authorities,
Extensions, undefined)),
Cookie = maps:get(cookie, Extensions, undefined),

#state{connection_states = ConnectionStates0,
session = Session0,
connection_env = #connection_env{cert_key_alts = CertKeyAlts}} = State1 =
Maybe(ssl_gen_statem:handle_sni_extension(SNI, State0)),

Maybe(validate_cookie(Cookie, State1)),

%% Handle ALPN extension if ALPN is configured
Expand Down Expand Up @@ -470,9 +470,12 @@ do_handle_client_hello(#client_hello{cipher_suites = ClientCiphers,
State1#state{session = Session}
end,

Opts = State2#state.ssl_options,
State3 = case maps:get(keep_secrets, Opts, false) of
true -> tls_handshake_1_3:set_client_random(State2, Hello#client_hello.random);
false -> State2
true ->
tls_handshake_1_3:set_client_random(State2, Hello#client_hello.random);
false ->
State2
end,

State4 = tls_handshake_1_3:update_start_state(State3,
Expand All @@ -494,7 +497,7 @@ do_handle_client_hello(#client_hello{cipher_suites = ClientCiphers,
case Maybe(send_hello_retry_request(State4, ClientPubKey, KeyShare, SessionId)) of
{_, start} = NextStateTuple ->
NextStateTuple;
{State5, negotiated} ->
{#state{ssl_options = #{early_data := EarlyDataEnabled}} = State5, negotiated} ->
%% Determine if early data is accepted
State = handle_early_data(State5, EarlyDataEnabled, EarlyDataIndication),
%% Exclude any incompatible PSKs.
Expand Down
64 changes: 63 additions & 1 deletion lib/ssl/test/ssl_api_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,8 @@
versions/1,
versions_option_based_on_sni/0,
versions_option_based_on_sni/1,
ciphers_option_based_on_sni/0,
ciphers_option_based_on_sni/1,
active_n/0,
active_n/1,
dh_params/0,
Expand Down Expand Up @@ -221,6 +223,7 @@
log/2,
get_connection_information/3,
protocol_version_check/2,
suite_check/2,
check_peercert/2,
%%TODO Keep?
run_error_server/1,
Expand Down Expand Up @@ -268,7 +271,8 @@ since_1_2() ->
[
conf_signature_algs,
no_common_signature_algs,
versions_option_based_on_sni
versions_option_based_on_sni,
ciphers_option_based_on_sni
].

pre_1_3() ->
Expand Down Expand Up @@ -1143,6 +1147,42 @@ versions_option_based_on_sni(Config) when is_list(Config) ->
ssl_test_lib:check_result(Server, ok),
ssl_test_lib:close(Server),
ssl_test_lib:close(Client).
%%--------------------------------------------------------------------

ciphers_option_based_on_sni() ->
[{doc,"Test that SNI versions option is selected over default ciphers option"}].

ciphers_option_based_on_sni(Config) when is_list(Config) ->
ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
ServerOpts = ssl_test_lib:ssl_options(server_rsa_opts, Config),
TestVersion = ssl_test_lib:protocol_version(Config),
Suites = rsa_cipher_suites_not_default(TestVersion),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),

SNI = net_adm:localhost(),
Fun = fun(ServerName) ->
case ServerName of
SNI ->
[{ciphers, Suites} | ServerOpts];
_ ->
ServerOpts
end
end,

Server = ssl_test_lib:start_server([{node, ServerNode}, {port, 0},
{from, self()},
{mfa, {?MODULE, suite_check, [TestVersion]}},
{options, [{sni_fun, Fun} | ServerOpts]}]),
Port = ssl_test_lib:inet_port(Server),
Client = ssl_test_lib:start_client([{node, ClientNode}, {port, Port},
{host, Hostname},
{from, self()},
{mfa, {ssl_test_lib, no_result, []}},
{options, [{server_name_indication, SNI} | ClientOpts]}]),

ssl_test_lib:check_result(Server, ok),
ssl_test_lib:close(Server),
ssl_test_lib:close(Client).

%%--------------------------------------------------------------------
%% Test case adapted from gen_tcp_misc_SUITE.
Expand Down Expand Up @@ -4449,3 +4489,25 @@ run_sha1_cert_conf(_, #{client_config := ClientOpts, server_config := ServerOpts
ssl_test_lib:basic_test([{verify, verify_peer} | ClientOpts] ++ SigOpts, ServerOpts, Config).


rsa_cipher_suites_not_default('tlsv1.3'= Version) ->
[_ | Suites] = ssl:cipher_suites(default, Version),
Suites;
rsa_cipher_suites_not_default(Version) ->
ssl_test_lib:test_ciphers(ecdhe_rsa, aes_128_gcm, Version).

suite_check(Socket, 'tlsv1.3'= Version) ->
[_, Suite| _] = ssl:cipher_suites(default, Version),
case ssl:connection_information(Socket, [selected_cipher_suite]) of
{ok, [{selected_cipher_suite, Suite}]} ->
ok;
Other ->
ct:fail({expected, Suite, got, Other})
end;
suite_check(Socket, Version) ->
[Suite |_] = rsa_cipher_suites_not_default(Version),
case ssl:connection_information(Socket, [selected_cipher_suite]) of
{ok, [{selected_cipher_suite, Suite}]} ->
ok;
Other ->
ct:fail({expected, Suite, got, Other})
end.

0 comments on commit 31987f6

Please sign in to comment.