Skip to content

Commit

Permalink
ssl: Reject unsupported previous version with protocol alert
Browse files Browse the repository at this point in the history
Change implementation use gen_statem postpone for hello message when users
want to pause handshake instead of legacy "reimplementation" of postpone

Closes #5950
  • Loading branch information
IngelaAndin committed Jun 7, 2022
1 parent 0863bd3 commit 2705916
Show file tree
Hide file tree
Showing 8 changed files with 190 additions and 102 deletions.
21 changes: 7 additions & 14 deletions lib/ssl/src/dtls_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -324,14 +324,12 @@ hello(internal, #hello_verify_request{cookie = Cookie},
},
dtls_gen_connection:next_event(?FUNCTION_NAME, no_record, State, Actions);
hello(internal, #client_hello{extensions = Extensions} = Hello,
#state{ssl_options = #{handshake := hello},
handshake_env = HsEnv,
#state{handshake_env = #handshake_env{continue_status = pause},
start_or_recv_from = From} = State0) ->
try tls_dtls_connection:handle_sni_extension(State0, Hello) of
#state{} = State ->
{next_state, user_hello, State#state{start_or_recv_from = undefined,
handshake_env = HsEnv#handshake_env{hello = Hello}},
[{reply, From, {ok, Extensions}}]}
{next_state, user_hello, State#state{start_or_recv_from = undefined},
[{postpone, true}, {reply, From, {ok, Extensions}}]}
catch throw:#alert{} = Alert ->
alert_or_reset_connection(Alert, ?FUNCTION_NAME, State0)
end;
Expand All @@ -354,16 +352,11 @@ hello(internal, #client_hello{cookie = Cookie} = Hello, #state{static_env = #sta
hello(internal, Hello#client_hello{cookie = <<>>}, State)
end
end;
hello(internal, #server_hello{extensions = Extensions} = Hello,
#state{ssl_options = #{
handshake := hello},
handshake_env = HsEnv,
hello(internal, #server_hello{extensions = Extensions},
#state{handshake_env = #handshake_env{continue_status = pause},
start_or_recv_from = From} = State) ->
{next_state, user_hello, State#state{start_or_recv_from = undefined,
handshake_env = HsEnv#handshake_env{
hello = Hello}},
[{reply, From, {ok, Extensions}}]};

{next_state, user_hello, State#state{start_or_recv_from = undefined},
[{postpone, true},{reply, From, {ok, Extensions}}]};
hello(internal, #server_hello{} = Hello,
#state{
static_env = #static_env{role = client},
Expand Down
6 changes: 4 additions & 2 deletions lib/ssl/src/ssl_connection.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@


-record(handshake_env, {
client_hello_version :: ssl_record:ssl_version() | 'undefined',
client_hello_version :: ssl_record:ssl_version() | 'undefined', %% Legacy client hello
unprocessed_handshake_events = 0 :: integer(),
tls_handshake_history :: ssl_handshake:ssl_handshake_history() | secret_printout()
| 'undefined',
Expand All @@ -67,7 +67,9 @@
early_data_accepted = false :: boolean(), %% TLS 1.3
allow_renegotiate = true ::boolean(),
%% Ext handling
hello, %%:: #client_hello{} | #server_hello{}
%% continue_status reflects handling of the option handshake that is either full or
%% hello (will pause at hello message to allow user to act on hello extensions)
continue_status, %% full | pause | {pause, ClientVersionsExt} | continue
sni_hostname = undefined,
max_frag_enum :: undefined | {max_frag_enum, integer()},
expecting_next_protocol_negotiation = false ::boolean(),
Expand Down
13 changes: 12 additions & 1 deletion lib/ssl/src/ssl_gen_statem.erl
Original file line number Diff line number Diff line change
Expand Up @@ -149,6 +149,7 @@ init([_Role, _Host, _Port, _Socket, {TLSOpts, _, _}, _User, _CbInfo] = InitArgs
-spec ssl_config(ssl_options(), client | server, #state{}) -> #state{}.
%%--------------------------------------------------------------------
ssl_config(Opts, Role, #state{static_env = InitStatEnv0,
ssl_options = #{handshake := Handshake},
handshake_env = HsEnv,
connection_env = CEnv} = State0) ->
{ok, #{cert_db_ref := Ref,
Expand All @@ -162,6 +163,15 @@ ssl_config(Opts, Role, #state{static_env = InitStatEnv0,
TimeStamp = erlang:monotonic_time(),
Session = State0#state.session,

ContinueStatus = case Handshake of
hello ->
%% Will pause handshake after hello message to
%% enable user to react to hello extensions
pause;
full ->
Handshake
end,

State0#state{session = Session#session{time_stamp = TimeStamp},
static_env = InitStatEnv0#static_env{
file_ref_db = FileRefHandle,
Expand All @@ -170,7 +180,8 @@ ssl_config(Opts, Role, #state{static_env = InitStatEnv0,
crl_db = CRLDbHandle,
session_cache = CacheHandle
},
handshake_env = HsEnv#handshake_env{diffie_hellman_params = DHParams},
handshake_env = HsEnv#handshake_env{diffie_hellman_params = DHParams,
continue_status = ContinueStatus},
connection_env = CEnv#connection_env{cert_key_pairs = CertKeyPairs},
ssl_options = Opts}.

Expand Down
26 changes: 11 additions & 15 deletions lib/ssl/src/tls_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,8 @@
%% Setup
-export([init/1]).

-export([renegotiate/2]).
-export([renegotiate/2,
choose_tls_fsm/2]).

%% gen_statem state functions
-export([initial_hello/3,
Expand Down Expand Up @@ -207,23 +208,18 @@ config_error(Type, Event, State) ->
#state{}) ->
gen_statem:state_function_result().
%%--------------------------------------------------------------------
hello(internal, #client_hello{extensions = Extensions} = Hello,
#state{ssl_options = #{handshake := hello},
static_env = #static_env{role = server},
handshake_env = HsEnv,
hello(internal, #client_hello{extensions = Extensions},
#state{static_env = #static_env{role = server},
handshake_env = #handshake_env{continue_status = pause},
start_or_recv_from = From} = State) ->
{next_state, user_hello, State#state{start_or_recv_from = undefined,
handshake_env = HsEnv#handshake_env{hello = Hello}},
[{reply, From, {ok, Extensions}}]};
hello(internal, #server_hello{extensions = Extensions} = Hello,
#state{ssl_options = #{handshake := hello},
{next_state, user_hello, State#state{start_or_recv_from = undefined},
[{postpone, true}, {reply, From, {ok, Extensions}}]};
hello(internal, #server_hello{extensions = Extensions},
#state{handshake_env = #handshake_env{continue_status = pause},
static_env = #static_env{role = client},
handshake_env = HsEnv,
start_or_recv_from = From} = State) ->
start_or_recv_from = From} = State) ->
{next_state, user_hello,
State#state{start_or_recv_from = undefined,
handshake_env = HsEnv#handshake_env{
hello = Hello}}, [{reply, From, {ok, Extensions}}]};
State#state{start_or_recv_from = undefined}, [{postpone, true}, {reply, From, {ok, Extensions}}]};
hello(internal, #client_hello{client_version = ClientVersion} = Hello,
#state{static_env = #static_env{role = server}, connection_env = CEnv} = State0) ->
try
Expand Down
146 changes: 98 additions & 48 deletions lib/ssl/src/tls_connection_1_3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -237,61 +237,92 @@ user_hello({call, From}, cancel, State) ->
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?USER_CANCELED, user_canceled),
?FUNCTION_NAME, State);
user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
#state{static_env = #static_env{role = Role},
handshake_env = #handshake_env{hello = Hello},
#state{static_env = #static_env{role = client = Role},
handshake_env = HSEnv,
ssl_options = Options0} = State0) ->
Options = ssl:handle_options(NewOptions, Role, Options0#{handshake => full}),
Options = ssl:handle_options(NewOptions, Role, Options0),
State = ssl_gen_statem:ssl_config(Options, Role, State0),
Next = case Role of
client ->
wait_sh;
server ->
start
end,
{next_state, Next, State#state{start_or_recv_from = From},
[{next_event, internal, Hello}, {{timeout, handshake}, Timeout, close}]};
{next_state, wait_sh, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}},
[{{timeout, handshake}, Timeout, close}]};
user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
#state{static_env = #static_env{role = server = Role},
handshake_env = #handshake_env{continue_status = {pause, ClientVersions}} = HSEnv,
ssl_options = Options0} = State0) ->
Options = #{versions := Versions} = ssl:handle_options(NewOptions, Role, Options0),
State = ssl_gen_statem:ssl_config(Options, Role, State0),
case ssl_handshake:select_supported_version(ClientVersions, Versions) of
{3,4} ->
{next_state, start, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}},
[{{timeout, handshake}, Timeout, close}]};
undefined ->
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION), ?FUNCTION_NAME, State);
_Else ->
{next_state, hello, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}},
[{change_callback_module, tls_connection},
{{timeout, handshake}, Timeout, close}]}
end;
user_hello(info, {'DOWN', _, _, _, _} = Event, State) ->
ssl_gen_statem:handle_info(Event, ?FUNCTION_NAME, State);
user_hello(_, _, _) ->
{keep_state_and_data, [postpone]}.

start(internal, #change_cipher_spec{}, State) ->
tls_gen_connection:next_event(?FUNCTION_NAME, no_record, State);
start(internal, #client_hello{extensions = Extensions} = Hello,
#state{ssl_options = #{handshake := hello},
start_or_recv_from = From,
handshake_env = HsEnv} = State) ->
start(internal, #client_hello{extensions = #{client_hello_versions :=
#client_hello_versions{versions = ClientVersions}
}} = Hello,
#state{ssl_options = #{handshake := full}} = State) ->
case tls_record:is_acceptable_version({3,4}, ClientVersions) of
true ->
do_server_start(Hello, State);
false ->
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION), ?FUNCTION_NAME, State)
end;
start(internal, #client_hello{extensions = #{client_hello_versions :=
#client_hello_versions{versions = ClientVersions}
}= Extensions},
#state{start_or_recv_from = From,
handshake_env = #handshake_env{continue_status = pause} = HSEnv} = State) ->
{next_state, user_hello,
State#state{start_or_recv_from = undefined,
handshake_env = HsEnv#handshake_env{
hello = Hello}}, [{reply, From, {ok, Extensions}}]};
start(internal, #client_hello{} = Hello, State0) ->
case tls_handshake_1_3:do_start(Hello, State0) of
#alert{} = Alert ->
ssl_gen_statem:handle_own_alert(Alert, start, State0);
{State, start} ->
{next_state, start, State, []};
{State, negotiated} ->
{next_state, negotiated, State, [{next_event, internal, {start_handshake, undefined}}]};
{State, negotiated, PSK} -> %% Session Resumption with PSK
{next_state, negotiated, State, [{next_event, internal, {start_handshake, PSK}}]}
State#state{start_or_recv_from = undefined, handshake_env = HSEnv#handshake_env{continue_status = {pause, ClientVersions}}},
[{postpone, true}, {reply, From, {ok, Extensions}}]};
start(internal, #client_hello{} = Hello,
#state{handshake_env = #handshake_env{continue_status = continue}} = State) ->
do_server_start(Hello, State);
start(internal, #client_hello{}, State0) -> %% Missing mandantory TLS-1.3 extensions, so it is a previous version hello.
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION), ?FUNCTION_NAME, State0);
start(internal, #server_hello{extensions = #{server_hello_selected_version :=
#server_hello_selected_version{selected_version = Version}}} = ServerHello,
#state{ssl_options = #{handshake := full,
versions := SupportedVersions}} = State) ->
case tls_record:is_acceptable_version(Version, SupportedVersions) of
true ->
do_client_start(ServerHello, State);
false ->
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION), ?FUNCTION_NAME, State)
end;
start(internal, #server_hello{extensions = Extensions} = ServerHello,
#state{ssl_options = #{handshake := hello},
handshake_env = HsEnv,
start_or_recv_from = From}
start(internal, #server_hello{extensions = #{server_hello_selected_version :=
#server_hello_selected_version{selected_version = Version}}
= Extensions},
#state{ssl_options = #{versions := SupportedVersions},
start_or_recv_from = From,
handshake_env = #handshake_env{continue_status = pause}}
= State) ->
{next_state, user_hello,
State#state{start_or_recv_from = undefined,
handshake_env = HsEnv#handshake_env{
hello = ServerHello}}, [{reply, From, {ok, Extensions}}]};
start(internal, #server_hello{} = ServerHello, State0) ->
case tls_handshake_1_3:do_start(ServerHello, State0) of
#alert{} = Alert ->
ssl_gen_statem:handle_own_alert(Alert, start, State0);
{State, NextState} ->
{next_state, NextState, State, []}
case tls_record:is_acceptable_version(Version, SupportedVersions) of
true ->
{next_state, user_hello,
State#state{start_or_recv_from = undefined}, [{postpone, true}, {reply, From, {ok, Extensions}}]};
false ->
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION), ?FUNCTION_NAME, State)
end;
start(internal, #server_hello{} = ServerHello,
#state{handshake_env = #handshake_env{continue_status = continue}} = State) ->
do_client_start(ServerHello, State);
start(internal, #server_hello{}, State0) -> %% Missing mandantory TLS-1.3 extensions, so it is a previous version hello.
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION), ?FUNCTION_NAME, State0);
start(info, Msg, State) ->
tls_gen_connection:handle_info(Msg, ?FUNCTION_NAME, State);
start(Type, Msg, State) ->
Expand Down Expand Up @@ -359,13 +390,11 @@ wait_finished(Type, Msg, State) ->

wait_sh(internal, #change_cipher_spec{}, State) ->
tls_gen_connection:next_event(?FUNCTION_NAME, no_record, State);
wait_sh(internal, #server_hello{extensions = Extensions} = Hello, #state{ssl_options = #{handshake := hello},
start_or_recv_from = From,
handshake_env = HsEnv} = State) ->
wait_sh(internal, #server_hello{extensions = Extensions},
#state{handshake_env = #handshake_env{continue_status = pause},
start_or_recv_from = From} = State) ->
{next_state, user_hello,
State#state{start_or_recv_from = undefined,
handshake_env = HsEnv#handshake_env{
hello = Hello}}, [{reply, From, {ok, Extensions}}]};
State#state{start_or_recv_from = undefined}, [{postpone, true},{reply, From, {ok, Extensions}}]};
wait_sh(internal, #server_hello{} = Hello, State0) ->
case tls_handshake_1_3:do_wait_sh(Hello, State0) of
#alert{} = Alert ->
Expand Down Expand Up @@ -464,6 +493,27 @@ downgrade(Type, Event, State) ->
%--------------------------------------------------------------------
%% internal functions
%%--------------------------------------------------------------------

do_server_start(ClientHello, State0) ->
case tls_handshake_1_3:do_start(ClientHello, State0) of
#alert{} = Alert ->
ssl_gen_statem:handle_own_alert(Alert, start, State0);
{State, start} ->
{next_state, start, State, []};
{State, negotiated} ->
{next_state, negotiated, State, [{next_event, internal, {start_handshake, undefined}}]};
{State, negotiated, PSK} -> %% Session Resumption with PSK
{next_state, negotiated, State, [{next_event, internal, {start_handshake, PSK}}]}
end.

do_client_start(ServerHello, State0) ->
case tls_handshake_1_3:do_start(ServerHello, State0) of
#alert{} = Alert ->
ssl_gen_statem:handle_own_alert(Alert, start, State0);
{State, NextState} ->
{next_state, NextState, State, []}
end.

initial_state(Role, Sender, Host, Port, Socket, {SSLOptions, SocketOptions, Trackers}, User,
{CbModule, DataTag, CloseTag, ErrorTag, PassiveTag}) ->
#{erl_dist := IsErlDist,
Expand Down
10 changes: 6 additions & 4 deletions lib/ssl/src/tls_dtls_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -168,12 +168,14 @@ user_hello({call, From}, cancel, _State) ->
throw(?ALERT_REC(?FATAL, ?USER_CANCELED, user_canceled));
user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
#state{static_env = #static_env{role = Role},
handshake_env = #handshake_env{hello = Hello},
handshake_env = HSEnv,
ssl_options = Options0} = State0) ->
Options = ssl:handle_options(NewOptions, Role, Options0#{handshake => full}),
Options = ssl:handle_options(NewOptions, Role, Options0),
State = ssl_gen_statem:ssl_config(Options, Role, State0),
{next_state, hello, State#state{start_or_recv_from = From},
[{next_event, internal, Hello}, {{timeout, handshake}, Timeout, close}]};
{next_state, hello, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}
},
[{{timeout, handshake}, Timeout, close}]};
user_hello(info, {'DOWN', _, _, _, _} = Event, State) ->
ssl_gen_statem:handle_info(Event, ?FUNCTION_NAME, State);
user_hello(_, _, _) ->
Expand Down
Loading

0 comments on commit 2705916

Please sign in to comment.