Skip to content

Commit d7434b1

Browse files
committed
Merge branch 'ingela/ssl/max-frag-len/OTP-19774' into maint
* ingela/ssl/max-frag-len/OTP-19774: ssl: Correct connection state handling in TLS sender
2 parents e38d617 + 0d8cf06 commit d7434b1

File tree

3 files changed

+29
-20
lines changed

3 files changed

+29
-20
lines changed

lib/ssl/src/tls_gen_connection.erl

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

206206
reinit(#state{protocol_specific = #{sender := Sender},
207207
connection_env = #connection_env{negotiated_version = Version},
208-
connection_states = #{current_write := Write}} = State0) ->
209-
tls_sender:update_connection_state(Sender, Write, Version),
208+
connection_states = #{current_write := Write} = ConnectionStates} = State0) ->
209+
MaxFragLength = maps:get(max_fragment_length, ConnectionStates, undefined),
210+
tls_sender:update_connection_state(Sender, Write, Version, MaxFragLength),
210211
State = reinit_handshake_data(State0),
211212
garbage_collect(),
212213
State.

lib/ssl/src/tls_record.erl

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

60-
-export_type([tls_version/0, tls_atom_version/0]).
60+
-export_type([tls_version/0, tls_atom_version/0, tls_max_frag_len/0]).
6161

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

lib/ssl/src/tls_sender.erl

Lines changed: 25 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@
4141
renegotiate/1,
4242
peer_renegotiate/1,
4343
downgrade/2,
44-
update_connection_state/3,
44+
update_connection_state/4,
4545
dist_handshake_complete/3]).
4646

4747
%% gen_statem callbacks
@@ -170,12 +170,14 @@ peer_renegotiate(Pid) ->
170170
gen_statem:call(Pid, renegotiate, ?DEFAULT_TIMEOUT).
171171

172172
%%--------------------------------------------------------------------
173-
-spec update_connection_state(pid(), WriteState::map(), tls_record:tls_version()) -> ok.
173+
-spec update_connection_state(pid(), WriteState::map(),
174+
tls_record:tls_version(),
175+
MaxFragLen :: tls_record:tls_max_frag_len()) -> ok.
174176
%% Description: So TLS connection process can synchronize the
175177
%% encryption state to be used when sending application data.
176178
%%--------------------------------------------------------------------
177-
update_connection_state(Pid, NewState, Version) ->
178-
gen_statem:cast(Pid, {new_write, NewState, Version}).
179+
update_connection_state(Pid, NewState, Version, MaxFragLen) ->
180+
gen_statem:cast(Pid, {new_write, NewState, Version, MaxFragLen}).
179181

180182
%%--------------------------------------------------------------------
181183
-spec downgrade(pid(), integer()) -> {ok, ssl_record:connection_state()}
@@ -339,13 +341,13 @@ connection(cast, #alert{} = Alert, #data{buff = Buff} = StateData0) ->
339341
Async ->
340342
{next_state, async_wait, StateData0#data{buff = Async#async{low = 0}}, [postpone]}
341343
end;
342-
connection(cast, {new_write, WritesState, Version},
343-
#data{connection_states = ConnectionStates, env = Env} = StateData) ->
344-
CW = maps:remove(aead_handle, WritesState),
344+
connection(cast, {new_write, WritesState, Version, MaxFragLen},
345+
#data{connection_states = ConnectionStates0, env = Env} = StateData) ->
346+
ConnectionStates = handle_new_write_state(ConnectionStates0, WritesState, MaxFragLen),
345347
hibernate_after(connection,
346-
StateData#data{connection_states = ConnectionStates#{current_write => CW},
347-
env = Env#env{negotiated_version = Version}}, []);
348-
%%
348+
StateData#data{connection_states = ConnectionStates,
349+
env = Env#env{negotiated_version = Version}},
350+
[]);
349351
connection(info, dist_data,
350352
#data{env = #env{dist_handle = DHandle}} = StateData) ->
351353
case dist_data(DHandle) of
@@ -409,15 +411,14 @@ handshake({call, _}, _, _) ->
409411
{keep_state_and_data, [postpone]};
410412
handshake(internal, {application_packets,_,_}, _) ->
411413
{keep_state_and_data, [postpone]};
412-
handshake(cast, {new_write, WriteState0, Version},
414+
handshake(cast, {new_write, WriteState, Version, MaxFragLen},
413415
#data{connection_states = ConnectionStates0,
414416
env = #env{key_update_at = KeyUpdateAt0,
415-
role = Role,
416-
num_key_updates = N,
417-
keylog_fun = Fun} = Env} = StateData) ->
418-
WriteState = maps:remove(aead_handle, WriteState0),
419-
ConnectionStates = ConnectionStates0#{current_write => WriteState},
417+
role = Role,
418+
num_key_updates = N,
419+
keylog_fun = Fun} = Env} = StateData) ->
420420
KeyUpdateAt = key_update_at(Version, WriteState, KeyUpdateAt0),
421+
ConnectionStates = handle_new_write_state(ConnectionStates0, WriteState, MaxFragLen),
421422
case Version of
422423
?TLS_1_3 ->
423424
maybe_traffic_keylog_1_3(Fun, Role, ConnectionStates, N);
@@ -427,7 +428,7 @@ handshake(cast, {new_write, WriteState0, Version},
427428
{next_state, connection,
428429
StateData#data{connection_states = ConnectionStates,
429430
env = Env#env{negotiated_version = Version,
430-
key_update_at = KeyUpdateAt}}};
431+
key_update_at = KeyUpdateAt}}};
431432
handshake(info, dist_data, _) ->
432433
{keep_state_and_data, [postpone]};
433434
handshake(info, tick, _) ->
@@ -489,6 +490,13 @@ code_change(_OldVsn, State, Data, _Extra) ->
489490
%%%===================================================================
490491
%%% Internal functions
491492
%%%===================================================================
493+
handle_new_write_state(ConnectionStates, WriteState0, undefined) ->
494+
WriteState = maps:remove(aead_handle, WriteState0),
495+
maps:without([max_fragment_length], ConnectionStates#{current_write => WriteState});
496+
handle_new_write_state(ConnectionStates, WriteState0, MaxFragLen) ->
497+
WriteState = maps:remove(aead_handle, WriteState0),
498+
ConnectionStates#{max_fragment_length => MaxFragLen, current_write => WriteState}.
499+
492500
handle_common(StateName, {call, From}, get_application_traffic_secret,
493501
#data{env = #env{num_key_updates = N}} = Data) ->
494502
CurrentWrite = maps:get(current_write, Data#data.connection_states),

0 commit comments

Comments
 (0)