Skip to content

Commit 7e7da59

Browse files
committed
ssl: Correct connection state handling in TLS sender
Optimization commit 28f7e80 broke max_fragment_length handling, that is the TLS sender lost its knowledge of the maximum fragment length. Make TLS sender process aware of it in the cases it is negotiated, for default maximum we do not need to store it in the connection state. Closes #10191
1 parent 940ec0f commit 7e7da59

File tree

3 files changed

+37
-27
lines changed

3 files changed

+37
-27
lines changed

lib/ssl/src/tls_gen_connection.erl

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -231,8 +231,9 @@ queue_change_cipher(Msg, #state{connection_env = #connection_env{negotiated_vers
231231

232232
reinit(#state{protocol_specific = #{sender := Sender},
233233
connection_env = #connection_env{negotiated_version = Version},
234-
connection_states = #{current_write := Write}} = State0) ->
235-
tls_sender:update_connection_state(Sender, Write, Version),
234+
connection_states = #{current_write := Write} = ConnectionStates} = State0) ->
235+
MaxFragLength = maps:get(max_fragment_length, ConnectionStates, undefined),
236+
tls_sender:update_connection_state(Sender, Write, Version, MaxFragLength),
236237
State = reinit_handshake_data(State0),
237238
garbage_collect(),
238239
State.

lib/ssl/src/tls_record.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@
5555
is_higher/2, supported_protocol_versions/0, sufficient_crypto_support/1,
5656
is_acceptable_version/1, is_acceptable_version/2, hello_version/1]).
5757

58-
-export_type([tls_version/0, tls_atom_version/0]).
58+
-export_type([tls_version/0, tls_atom_version/0, tls_max_frag_len/0]).
5959

6060
-type tls_version() :: ssl_record:ssl_version().
6161
-type tls_atom_version() :: sslv3 | tlsv1 | 'tlsv1.1' | 'tlsv1.2' | 'tlsv1.3'.

lib/ssl/src/tls_sender.erl

Lines changed: 33 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -42,8 +42,8 @@
4242
renegotiate/1,
4343
peer_renegotiate/1,
4444
downgrade/2,
45-
update_connection_state/3,
4645
dist_tls_socket/1,
46+
update_connection_state/4,
4747
dist_handshake_complete/3]).
4848

4949
%% gen_statem callbacks
@@ -166,12 +166,14 @@ peer_renegotiate(Pid) ->
166166
gen_statem:call(Pid, renegotiate, ?DEFAULT_TIMEOUT).
167167

168168
%%--------------------------------------------------------------------
169-
-spec update_connection_state(pid(), WriteState::map(), tls_record:tls_version()) -> ok.
169+
-spec update_connection_state(pid(), WriteState::map(),
170+
tls_record:tls_version(),
171+
MaxFragLen :: tls_record:tls_max_frag_len()) -> ok.
170172
%% Description: So TLS connection process can synchronize the
171173
%% encryption state to be used when sending application data.
172174
%%--------------------------------------------------------------------
173-
update_connection_state(Pid, NewState, Version) ->
174-
gen_statem:cast(Pid, {new_write, NewState, Version}).
175+
update_connection_state(Pid, NewState, Version, MaxFragLen) ->
176+
gen_statem:cast(Pid, {new_write, NewState, Version, MaxFragLen}).
175177

176178
%%--------------------------------------------------------------------
177179
-spec downgrade(pid(), integer()) -> {ok, ssl_record:connection_state()}
@@ -339,19 +341,19 @@ connection({call, From}, get_application_traffic_secret, #data{env = #env{num_ke
339341
[{reply, From, {ok, ApplicationTrafficSecret, N}}]);
340342
connection(internal, {application_packets, From, Data}, StateData) ->
341343
send_application_data(Data, From, connection, StateData);
344+
342345
connection(internal, {post_handshake_data, From, HSData}, StateData) ->
343346
send_post_handshake_data(HSData, From, connection, StateData);
344347
connection(cast, #alert{} = Alert, StateData0) ->
345348
StateData = send_tls_alert(Alert, StateData0),
346349
{next_state, connection, StateData};
347-
connection(cast, {new_write, WritesState, Version},
348-
#data{connection_states = ConnectionStates, env = Env} = StateData) ->
350+
connection(cast, {new_write, WritesState, Version, MaxFragLen},
351+
#data{connection_states = ConnectionStates0, env = Env} = StateData) ->
352+
ConnectionStates = handle_new_write_state(ConnectionStates0, WritesState, MaxFragLen),
349353
hibernate_after(connection,
350-
StateData#data{connection_states =
351-
ConnectionStates#{current_write => WritesState},
352-
env =
353-
Env#env{negotiated_version = Version}}, []);
354-
%%
354+
StateData#data{connection_states = ConnectionStates,
355+
env = Env#env{negotiated_version = Version}},
356+
[]);
355357
connection(info, dist_data,
356358
#data{env = #env{dist_handle = DHandle}} = StateData) ->
357359
case dist_data(DHandle) of
@@ -394,24 +396,24 @@ handshake({call, _}, _, _) ->
394396
{keep_state_and_data, [postpone]};
395397
handshake(internal, {application_packets,_,_}, _) ->
396398
{keep_state_and_data, [postpone]};
397-
handshake(cast, {new_write, WriteState, Version},
399+
handshake(cast, {new_write, WriteState, Version, MaxFragLen},
398400
#data{connection_states = ConnectionStates0,
399401
env = #env{key_update_at = KeyUpdateAt0,
400-
role = Role,
401-
num_key_updates = N,
402-
keylog_fun = Fun} = Env} = StateData) ->
403-
ConnectionStates = ConnectionStates0#{current_write => WriteState},
402+
role = Role,
403+
num_key_updates = N,
404+
keylog_fun = Fun} = Env} = StateData) ->
404405
KeyUpdateAt = key_update_at(Version, WriteState, KeyUpdateAt0),
405-
case Version of
406-
?TLS_1_3 ->
407-
maybe_traffic_keylog_1_3(Fun, Role, ConnectionStates, N);
408-
_ ->
409-
ok
410-
end,
411-
{next_state, connection,
406+
ConnectionStates = handle_new_write_state(ConnectionStates0, WriteState, MaxFragLen),
407+
case Version of
408+
?TLS_1_3 ->
409+
maybe_traffic_keylog_1_3(Fun, Role, ConnectionStates, N);
410+
_ ->
411+
ok
412+
end,
413+
{next_state, connection,
412414
StateData#data{connection_states = ConnectionStates,
413415
env = Env#env{negotiated_version = Version,
414-
key_update_at = KeyUpdateAt}}};
416+
key_update_at = KeyUpdateAt}}};
415417
handshake(info, dist_data, _) ->
416418
{keep_state_and_data, [postpone]};
417419
handshake(info, tick, _) ->
@@ -463,6 +465,13 @@ code_change(_OldVsn, State, Data, _Extra) ->
463465
%%%===================================================================
464466
%%% Internal functions
465467
%%%===================================================================
468+
handle_new_write_state(ConnectionStates, WriteState0, undefined) ->
469+
WriteState = maps:remove(aead_handle, WriteState0),
470+
maps:without([max_fragment_length], ConnectionStates#{current_write => WriteState});
471+
handle_new_write_state(ConnectionStates, WriteState0, MaxFragLen) ->
472+
WriteState = maps:remove(aead_handle, WriteState0),
473+
ConnectionStates#{max_fragment_length => MaxFragLen, current_write => WriteState}.
474+
466475
handle_set_opts(StateName, From, Opts,
467476
#data{env = #env{socket_options = SockOpts} = Env}
468477
= StateData) ->

0 commit comments

Comments
 (0)