Skip to content

Commit

Permalink
ssl: Make sure handshake messages are handled correctly during versio…
Browse files Browse the repository at this point in the history
…n negotiation

Handshake messages MAY be coalesced into a single TLSPlaintext record
or fragmented across several records. There are also stricter conditions
that must be met for TLS-1.3 "see RFC 8446 section 5.1.  Record Layer"

This means that when supporting both TLS-1.2 and TLS-1.3 as a client we need to
make sure that only the server hello message is handled initially so that
possible coalesced TLS-1.2 handshake messages will be handled by TLS-1.2 code
when the negotiated version has been established.

Closes #5961
  • Loading branch information
IngelaAndin committed Jun 1, 2022
1 parent a47d9ce commit 3192d81
Showing 1 changed file with 47 additions and 30 deletions.
77 changes: 47 additions & 30 deletions lib/ssl/src/tls_gen_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -389,27 +389,17 @@ handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA, fragment = Data}, Stat
next_event(StateName, Record, State)
end;
%%% TLS record protocol level handshake messages
handle_protocol_record(#ssl_tls{type = ?HANDSHAKE, fragment = Data},
StateName, #state{protocol_buffers =
#protocol_buffers{tls_handshake_buffer = Buf0} = Buffers,
connection_env = #connection_env{negotiated_version = Version},
static_env = #static_env{role = Role},
ssl_options = Options} = State0) ->
handle_protocol_record(#ssl_tls{type = ?HANDSHAKE, fragment = Data}, StateName,
#state{ssl_options = Options, protocol_buffers = Buffers} = State0) ->
try
%% Calculate the effective version that should be used when decoding an incoming handshake
%% message.
EffectiveVersion = effective_version(Version, Options, Role, StateName),
{Packets, Buf} = tls_handshake:get_tls_handshakes(EffectiveVersion,Data,Buf0, Options),

State = case EffectiveVersion =/= NegotiatedVersion of
State0#state{protocol_buffers =
Buffers#protocol_buffers{tls_handshake_buffer = Buf}},
case Packets of
{HSPackets, NewHSBuffer, RecordRest} = get_tls_handshakes(Data, StateName, State0),
State = State0#state{protocol_buffers = Buffers#protocol_buffers{tls_handshake_buffer = NewHSBuffer}},
case HSPackets of
[] ->
assert_buffer_sanity(Buf, Options),
assert_buffer_sanity(NewHSBuffer, Options),
next_event(StateName, no_record, State);
_ ->
Events = tls_handshake_events(Packets),
Events = tls_handshake_events(HSPackets, RecordRest),
case StateName of
connection ->
ssl_gen_statem:hibernate_after(StateName, State, Events);
Expand Down Expand Up @@ -529,10 +519,31 @@ protocol_name() ->
%%====================================================================
%% Internal functions
%%====================================================================
tls_handshake_events(Packets) ->
lists:map(fun(Packet) ->
{next_event, internal, {handshake, Packet}}
end, Packets).
get_tls_handshakes(Data, StateName, #state{protocol_buffers = #protocol_buffers{tls_handshake_buffer = HSBuffer},
connection_env = #connection_env{negotiated_version = Version},
static_env = #static_env{role = Role},
ssl_options = Options}) ->
case handle_unnegotiated_version(Version, Options, Data, HSBuffer, Role, StateName) of
{HSPackets, NewHSBuffer} ->
%% Common case
NoRecordRest = <<>>,
{HSPackets, NewHSBuffer, NoRecordRest};
{_Packets, _HSBuffer, _RecordRest} = Result ->
%% Possible coalesced TLS record data from pre TLS-1.3 server
Result
end.

tls_handshake_events(HSPackets, <<>>) ->
lists:map(fun(HSPacket) ->
{next_event, internal, {handshake, HSPacket}}
end, HSPackets);

tls_handshake_events(HSPackets, RecordRest) ->
%% Coalesced TLS record data to be handled after first handshake message has been handled
RestEvent = {next_event, internal, {protocol_record, #ssl_tls{type = ?HANDSHAKE, fragment = RecordRest}}},
FirstHS = tls_handshake_events(HSPackets, <<>>),
FirstHS ++ [RestEvent].


unprocessed_events(Events) ->
%% The first handshake event will be processed immediately
Expand Down Expand Up @@ -756,21 +767,27 @@ next_record_done(#state{protocol_buffers = Buffers} = State, CipherTexts, Connec
%% Pre TLS-1.3, on the client side, the connection state variable `negotiated_version` will initially be
%% the requested version. On the server side the same variable is initially undefined.
%% When the client can support TLS-1.3 and one or more prior versions and we are waiting
%% for the server hello (with or without a RetryRequest, that is in state hello or in state wait_sh),
%% the "initial requested version" kept in the connection state variable `negotiated_version`
%% for the server hello the "initial requested version" kept in the connection state variable `negotiated_version`
%% (before the versions is actually negotiated) will always be the value of TLS-1.2 (which is a legacy
%% field in TLS-1.3 client hello). The versions are instead negotiated with an hello extension. When
%% decoding the server_hello messages we want to go through TLS-1.3 decode functions to be able
%% to handle TLS-1.3 extensions if TLS-1.3 will be the negotiated version.
effective_version({3,3} , #{versions := [{3,4} = Version |_]}, client, StateName) when StateName == hello;
StateName == wait_sh ->
Version;
handle_unnegotiated_version({3,3} , #{versions := [{3,4} = Version |_]} = Options, Data, Buffer, client, hello) ->
%% The effective version for decoding the server hello message should be the TLS-1.3. Possible coalesced TLS-1.2
%% server handshake messages should be decoded with the negotiated version in later state.
<<_:8, ?UINT24(Length), _/binary>> = Data,
<<FirstPacket:(Length+4)/binary, RecordRest/binary>> = Data,
{HSPacket, <<>> = NewHsBuffer} = tls_handshake:get_tls_handshakes(Version, FirstPacket, Buffer, Options),
{HSPacket, NewHsBuffer, RecordRest};
%% TLS-1.3 RetryRequest
handle_unnegotiated_version({3,3} , #{versions := [{3,4} = Version |_]} = Options, Data, Buffer, client, wait_sh) ->
tls_handshake:get_tls_handshakes(Version, Data, Buffer, Options);
%% When the `negotiated_version` variable is not yet set use the highest supported version.
effective_version(undefined, #{versions := [Version|_]}, _, _) ->
Version;
handle_unnegotiated_version(undefined, #{versions := [Version|_]} = Options, Data, Buff, _, _) ->
tls_handshake:get_tls_handshakes(Version, Data, Buff, Options);
%% In all other cases use the version saved in the connection state variable `negotiated_version`
effective_version(Version, _, _, _) ->
Version.
handle_unnegotiated_version(Version, Options, Data, Buff, _, _) ->
tls_handshake:get_tls_handshakes(Version, Data, Buff, Options).

assert_buffer_sanity(<<?BYTE(_Type), ?UINT24(Length), Rest/binary>>,
#{max_handshake_size := Max}) when
Expand Down

0 comments on commit 3192d81

Please sign in to comment.