File 0514-ssl-Correct-connection-state-handling-in-TLS-sender.patch of Package erlang
From 7e7da59b6f5a562d5f0e5c8745ec69ad7405af4a Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Tue, 16 Sep 2025 08:36:19 +0200
Subject: [PATCH] ssl: Correct connection state handling in TLS sender
Optimization commit 28f7e80233718f9f42fe8863370f7e99ee14d22c
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
---
lib/ssl/src/tls_gen_connection.erl | 5 +--
lib/ssl/src/tls_record.erl | 2 +-
lib/ssl/src/tls_sender.erl | 57 +++++++++++++++++-------------
3 files changed, 37 insertions(+), 27 deletions(-)
diff --git a/lib/ssl/src/tls_gen_connection.erl b/lib/ssl/src/tls_gen_connection.erl
index cb2b4ea6da..bf47983e07 100644
--- a/lib/ssl/src/tls_gen_connection.erl
+++ b/lib/ssl/src/tls_gen_connection.erl
@@ -231,8 +231,9 @@ queue_change_cipher(Msg, #state{connection_env = #connection_env{negotiated_vers
reinit(#state{protocol_specific = #{sender := Sender},
connection_env = #connection_env{negotiated_version = Version},
- connection_states = #{current_write := Write}} = State0) ->
- tls_sender:update_connection_state(Sender, Write, Version),
+ connection_states = #{current_write := Write} = ConnectionStates} = State0) ->
+ MaxFragLength = maps:get(max_fragment_length, ConnectionStates, undefined),
+ tls_sender:update_connection_state(Sender, Write, Version, MaxFragLength),
State = reinit_handshake_data(State0),
garbage_collect(),
State.
diff --git a/lib/ssl/src/tls_record.erl b/lib/ssl/src/tls_record.erl
index 7f50ccdec2..17bb765a3c 100644
--- a/lib/ssl/src/tls_record.erl
+++ b/lib/ssl/src/tls_record.erl
@@ -55,7 +55,7 @@
is_higher/2, supported_protocol_versions/0, sufficient_crypto_support/1,
is_acceptable_version/1, is_acceptable_version/2, hello_version/1]).
--export_type([tls_version/0, tls_atom_version/0]).
+-export_type([tls_version/0, tls_atom_version/0, tls_max_frag_len/0]).
-type tls_version() :: ssl_record:ssl_version().
-type tls_atom_version() :: sslv3 | tlsv1 | 'tlsv1.1' | 'tlsv1.2' | 'tlsv1.3'.
diff --git a/lib/ssl/src/tls_sender.erl b/lib/ssl/src/tls_sender.erl
index ce697d68fc..43ac87d415 100644
--- a/lib/ssl/src/tls_sender.erl
+++ b/lib/ssl/src/tls_sender.erl
@@ -42,8 +42,8 @@
renegotiate/1,
peer_renegotiate/1,
downgrade/2,
- update_connection_state/3,
dist_tls_socket/1,
+ update_connection_state/4,
dist_handshake_complete/3]).
%% gen_statem callbacks
@@ -166,12 +166,14 @@ peer_renegotiate(Pid) ->
gen_statem:call(Pid, renegotiate, ?DEFAULT_TIMEOUT).
%%--------------------------------------------------------------------
--spec update_connection_state(pid(), WriteState::map(), tls_record:tls_version()) -> ok.
+-spec update_connection_state(pid(), WriteState::map(),
+ tls_record:tls_version(),
+ MaxFragLen :: tls_record:tls_max_frag_len()) -> ok.
%% Description: So TLS connection process can synchronize the
%% encryption state to be used when sending application data.
%%--------------------------------------------------------------------
-update_connection_state(Pid, NewState, Version) ->
- gen_statem:cast(Pid, {new_write, NewState, Version}).
+update_connection_state(Pid, NewState, Version, MaxFragLen) ->
+ gen_statem:cast(Pid, {new_write, NewState, Version, MaxFragLen}).
%%--------------------------------------------------------------------
-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
[{reply, From, {ok, ApplicationTrafficSecret, N}}]);
connection(internal, {application_packets, From, Data}, StateData) ->
send_application_data(Data, From, connection, StateData);
+
connection(internal, {post_handshake_data, From, HSData}, StateData) ->
send_post_handshake_data(HSData, From, connection, StateData);
connection(cast, #alert{} = Alert, StateData0) ->
StateData = send_tls_alert(Alert, StateData0),
{next_state, connection, StateData};
-connection(cast, {new_write, WritesState, Version},
- #data{connection_states = ConnectionStates, env = Env} = StateData) ->
+connection(cast, {new_write, WritesState, Version, MaxFragLen},
+ #data{connection_states = ConnectionStates0, env = Env} = StateData) ->
+ ConnectionStates = handle_new_write_state(ConnectionStates0, WritesState, MaxFragLen),
hibernate_after(connection,
- StateData#data{connection_states =
- ConnectionStates#{current_write => WritesState},
- env =
- Env#env{negotiated_version = Version}}, []);
-%%
+ StateData#data{connection_states = ConnectionStates,
+ env = Env#env{negotiated_version = Version}},
+ []);
connection(info, dist_data,
#data{env = #env{dist_handle = DHandle}} = StateData) ->
case dist_data(DHandle) of
@@ -394,24 +396,24 @@ handshake({call, _}, _, _) ->
{keep_state_and_data, [postpone]};
handshake(internal, {application_packets,_,_}, _) ->
{keep_state_and_data, [postpone]};
-handshake(cast, {new_write, WriteState, Version},
+handshake(cast, {new_write, WriteState, Version, MaxFragLen},
#data{connection_states = ConnectionStates0,
env = #env{key_update_at = KeyUpdateAt0,
- role = Role,
- num_key_updates = N,
- keylog_fun = Fun} = Env} = StateData) ->
- ConnectionStates = ConnectionStates0#{current_write => WriteState},
+ role = Role,
+ num_key_updates = N,
+ keylog_fun = Fun} = Env} = StateData) ->
KeyUpdateAt = key_update_at(Version, WriteState, KeyUpdateAt0),
- case Version of
- ?TLS_1_3 ->
- maybe_traffic_keylog_1_3(Fun, Role, ConnectionStates, N);
- _ ->
- ok
- end,
- {next_state, connection,
+ ConnectionStates = handle_new_write_state(ConnectionStates0, WriteState, MaxFragLen),
+ case Version of
+ ?TLS_1_3 ->
+ maybe_traffic_keylog_1_3(Fun, Role, ConnectionStates, N);
+ _ ->
+ ok
+ end,
+ {next_state, connection,
StateData#data{connection_states = ConnectionStates,
env = Env#env{negotiated_version = Version,
- key_update_at = KeyUpdateAt}}};
+ key_update_at = KeyUpdateAt}}};
handshake(info, dist_data, _) ->
{keep_state_and_data, [postpone]};
handshake(info, tick, _) ->
@@ -463,6 +465,13 @@ code_change(_OldVsn, State, Data, _Extra) ->
%%%===================================================================
%%% Internal functions
%%%===================================================================
+handle_new_write_state(ConnectionStates, WriteState0, undefined) ->
+ WriteState = maps:remove(aead_handle, WriteState0),
+ maps:without([max_fragment_length], ConnectionStates#{current_write => WriteState});
+handle_new_write_state(ConnectionStates, WriteState0, MaxFragLen) ->
+ WriteState = maps:remove(aead_handle, WriteState0),
+ ConnectionStates#{max_fragment_length => MaxFragLen, current_write => WriteState}.
+
handle_set_opts(StateName, From, Opts,
#data{env = #env{socket_options = SockOpts} = Env}
= StateData) ->
--
2.51.0