File 0712-ssl-Backport-some-keylog-fixes.patch of Package erlang
From 3f61db32c579559f9644def7d52fc0b0a6c148c0 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Mon, 22 Dec 2025 09:27:02 +0100
Subject: [PATCH 2/5] ssl: Backport some keylog fixes
---
lib/ssl/src/ssl_gen_statem.erl | 82 ++++++++++++--------------
lib/ssl/src/tls_gen_connection.erl | 9 ++-
lib/ssl/src/tls_gen_connection_1_3.erl | 7 ++-
lib/ssl/src/tls_sender.erl | 51 +++++++++++++---
4 files changed, 92 insertions(+), 57 deletions(-)
diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl
index a0e4975f41..7eb9452a6f 100644
--- a/lib/ssl/src/ssl_gen_statem.erl
+++ b/lib/ssl/src/ssl_gen_statem.erl
@@ -2006,60 +2006,52 @@ connection_info(#state{handshake_env = #handshake_env{sni_hostname = SNIHostname
{sni_hostname, SNIHostname},
{srp_username, SrpUsername} | CurveInfo] ++ MFLInfo ++ ssl_options_list(Opts).
-security_info(#state{connection_states = ConnectionStates,
+security_info(#state{connection_states = #{current_read := Read,
+ current_write := Write},
static_env = #static_env{role = Role},
+ connection_env = #connection_env{negotiated_version = Version},
ssl_options = Opts,
protocol_specific = ProtocolSpecific}) ->
- ReadState = ssl_record:current_connection_state(ConnectionStates, read),
#{security_parameters :=
#security_parameters{client_random = ClientRand,
server_random = ServerRand,
- master_secret = MasterSecret,
- application_traffic_secret = AppTrafSecretRead,
- client_early_data_secret = ServerEarlyData
- }} = ReadState,
- BaseSecurityInfo = [{client_random, ClientRand}, {server_random, ServerRand}, {master_secret, MasterSecret}],
-
+ master_secret = MasterSecret}} = Read,
+ SecInfo = [{client_random, ClientRand},
+ {server_random, ServerRand}, {master_secret, MasterSecret}],
KeepSecrets = maps:get(keep_secrets, Opts, false),
- if KeepSecrets =/= true ->
- BaseSecurityInfo;
- true ->
- #{security_parameters :=
- #security_parameters{
- application_traffic_secret = AppTrafSecretWrite0,
- client_early_data_secret = ClientEarlyData}} =
- ssl_record:current_connection_state(ConnectionStates, write),
- Sender = maps:get(sender, ProtocolSpecific, undefined),
- AppTrafSecretWrite = {Sender, AppTrafSecretWrite0},
- if Role == server ->
- if ServerEarlyData =/= undefined ->
- [{server_traffic_secret_0, AppTrafSecretWrite},
- {client_traffic_secret_0, AppTrafSecretRead},
- {client_early_data_secret, ServerEarlyData}];
- true ->
- [{server_traffic_secret_0, AppTrafSecretWrite},
- {client_traffic_secret_0, AppTrafSecretRead}]
- end;
- true ->
- if ClientEarlyData =/= undefined ->
- [{client_traffic_secret_0, AppTrafSecretWrite},
- {server_traffic_secret_0, AppTrafSecretRead},
- {client_early_data_secret, ClientEarlyData}];
- true ->
- [{client_traffic_secret_0, AppTrafSecretWrite},
- {server_traffic_secret_0, AppTrafSecretRead}]
- end
- end ++
- case ReadState of
- #{client_handshake_traffic_secret := ClientHSTrafficSecret,
- server_handshake_traffic_secret := ServerHSTrafficSecret} ->
- [{client_handshake_traffic_secret, ClientHSTrafficSecret},
- {server_handshake_traffic_secret, ServerHSTrafficSecret}];
- _ ->
- []
- end ++ BaseSecurityInfo
+ case KeepSecrets of
+ false ->
+ %% Need to include {keep_secrets, false} for maybe_add_keylog
+ %% to be able to run in user process context
+ [{keep_secrets, false} | SecInfo];
+ _ -> %% true or keylog fun tuple
+ maybe_security_info_1_3(Version, Read, Write, ProtocolSpecific, Role)
+ ++ SecInfo
end.
+maybe_security_info_1_3(Version,
+ #{security_parameters :=
+ #security_parameters{application_traffic_secret = AppTrafSecretRead,
+ client_early_data_secret = EarlyData
+ }} = Read, Write,
+ ProtocolSpecific, Role) when ?TLS_GTE(Version, ?TLS_1_3)->
+ N = maps:get(num_key_updates, ProtocolSpecific, 0),
+ Sender = maps:get(sender, ProtocolSpecific, undefined),
+ case Role of
+ server ->
+ tls_handshake_1_3:early_data_secret(EarlyData) ++
+ tls_handshake_1_3:hs_traffic_secrets(Read, Write) ++
+ [{client_traffic_secret, AppTrafSecretRead, N},
+ {Role, Sender}];
+ client ->
+ tls_handshake_1_3:early_data_secret(EarlyData) ++
+ tls_handshake_1_3:hs_traffic_secrets(Read, Write) ++
+ [{server_traffic_secret, AppTrafSecretRead, N},
+ {Role, Sender}]
+ end;
+maybe_security_info_1_3(_,_,_,_,_) ->
+ [].
+
record_cb(tls) ->
tls_record;
record_cb(dtls) ->
diff --git a/lib/ssl/src/tls_gen_connection.erl b/lib/ssl/src/tls_gen_connection.erl
index 061a68a012..36da0f0ec2 100644
--- a/lib/ssl/src/tls_gen_connection.erl
+++ b/lib/ssl/src/tls_gen_connection.erl
@@ -162,6 +162,12 @@ initialize_tls_sender(#state{static_env = #static_env{
connection_states = #{current_write := ConnectionWriteState},
protocol_specific = #{sender := Sender}}) ->
HibernateAfter = maps:get(hibernate_after, SSLOpts, infinity),
+ KeyLogFun = case maps:get(keep_secrets, SSLOpts, false) of
+ {keylog, Fun} ->
+ Fun;
+ _ ->
+ undefined
+ end,
Init = #{current_write => ConnectionWriteState,
role => Role,
socket => Socket,
@@ -173,7 +179,8 @@ initialize_tls_sender(#state{static_env = #static_env{
renegotiate_at => RenegotiateAt,
key_update_at => KeyUpdateAt,
log_level => LogLevel,
- hibernate_after => HibernateAfter},
+ hibernate_after => HibernateAfter,
+ keylog_fun => KeyLogFun},
tls_sender:initialize(Sender, Init).
%%====================================================================
diff --git a/lib/ssl/src/tls_gen_connection_1_3.erl b/lib/ssl/src/tls_gen_connection_1_3.erl
index 7fa76401c1..5261d77a8a 100644
--- a/lib/ssl/src/tls_gen_connection_1_3.erl
+++ b/lib/ssl/src/tls_gen_connection_1_3.erl
@@ -293,9 +293,12 @@ send_key_update(Sender, Type) ->
KeyUpdate = tls_handshake_1_3:key_update(Type),
tls_sender:send_post_handshake(Sender, KeyUpdate).
-update_cipher_key(ConnStateName, #state{connection_states = CS0} = State0) ->
+update_cipher_key(ConnStateName, #state{connection_states = CS0,
+ protocol_specific = PS} = State0) ->
CS = update_cipher_key(ConnStateName, CS0),
- State0#state{connection_states = CS};
+ N = maps:get(num_key_updates, PS, 0),
+ State0#state{connection_states = CS,
+ protocol_specific = PS#{num_key_updates => N + 1}};
update_cipher_key(ConnStateName, CS0) ->
#{security_parameters := SecParams0,
cipher_state := CipherState0} = ConnState0 = maps:get(ConnStateName, CS0),
diff --git a/lib/ssl/src/tls_sender.erl b/lib/ssl/src/tls_sender.erl
index 25c4842071..31fbab3b9b 100644
--- a/lib/ssl/src/tls_sender.erl
+++ b/lib/ssl/src/tls_sender.erl
@@ -71,7 +71,9 @@
bytes_sent, %% TLS 1.3
dist_handle,
log_level,
- hibernate_after
+ hibernate_after,
+ keylog_fun,
+ num_key_updates = 0
}).
-record(data,
@@ -234,7 +236,8 @@ init({call, From}, {Pid, #{current_write := WriteState,
renegotiate_at := RenegotiateAt,
key_update_at := KeyUpdateAt,
log_level := LogLevel,
- hibernate_after := HibernateAfter}},
+ hibernate_after := HibernateAfter,
+ keylog_fun := KeyLogFun}},
#data{connection_states = ConnectionStates, static = Static0} = StateData0) ->
StateData =
StateData0#data{connection_states = ConnectionStates#{current_write => WriteState},
@@ -250,7 +253,9 @@ init({call, From}, {Pid, #{current_write := WriteState,
key_update_at = KeyUpdateAt,
bytes_sent = 0,
log_level = LogLevel,
- hibernate_after = HibernateAfter}},
+ hibernate_after = HibernateAfter,
+ keylog_fun = KeyLogFun
+ }},
{next_state, handshake, StateData, [{reply, From, ok}]};
init(info = Type, Msg, StateData) ->
handle_common(?FUNCTION_NAME, Type, Msg, StateData);
@@ -273,6 +278,14 @@ connection({call, From}, {application_packets, AppData},
Data ->
send_application_data(Data, From, ?FUNCTION_NAME, StateData)
end;
+connection({call, From}, get_application_traffic_secret,
+ #data{static = #static{num_key_updates = N}} = Data) ->
+ CurrentWrite = maps:get(current_write, Data#data.connection_states),
+ SecurityParams = maps:get(security_parameters, CurrentWrite),
+ ApplicationTrafficSecret =
+ SecurityParams#security_parameters.application_traffic_secret,
+ hibernate_after(connection, Data,
+ [{reply, From, {ok, ApplicationTrafficSecret, N}}]);
connection({call, From}, {post_handshake_data, HSData}, StateData) ->
send_post_handshake_data(HSData, From, ?FUNCTION_NAME, StateData, [{reply, From, ok}]);
connection({call, From}, {ack_alert, #alert{} = Alert}, StateData0) ->
@@ -380,13 +393,23 @@ handshake({call, _}, _, _) ->
handshake(internal, {application_packets,_,_}, _) ->
{keep_state_and_data, [postpone]};
handshake(cast, {new_write, WriteState, Version},
- #data{connection_states = ConnectionStates,
- static = #static{key_update_at = KeyUpdateAt0} = Static} = StateData) ->
+ #data{connection_states = ConnectionStates0,
+ static = #static{key_update_at = KeyUpdateAt0,
+ role = Role,
+ num_key_updates = N,
+ keylog_fun = Fun} = Env} = StateData) ->
+ ConnectionStates = ConnectionStates0#{current_write => WriteState},
KeyUpdateAt = key_update_at(Version, WriteState, KeyUpdateAt0),
- {next_state, connection,
- StateData#data{connection_states = ConnectionStates#{current_write => WriteState},
- static = Static#static{negotiated_version = Version,
- key_update_at = KeyUpdateAt}}};
+ 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,
+ static = Env#static{negotiated_version = Version,
+ key_update_at = KeyUpdateAt}}};
handshake(info, dist_data, _) ->
{keep_state_and_data, [postpone]};
handshake(info, tick, _) ->
@@ -579,6 +602,16 @@ maybe_update_cipher_key(#data{connection_states = ConnectionStates0,
maybe_update_cipher_key(StateData, _) ->
StateData.
+maybe_traffic_keylog_1_3(Fun, Role, ConnectionStates, N) when is_function(Fun) ->
+ #{security_parameters := #security_parameters{client_random = ClientRandom,
+ prf_algorithm = Prf,
+ application_traffic_secret = TrafficSecret}}
+ = ssl_record:current_connection_state(ConnectionStates, write),
+ KeyLog = ssl_logger:keylog_traffic_1_3(Role, ClientRandom, Prf, TrafficSecret, N),
+ ssl_logger:keylog(KeyLog, ClientRandom, Fun);
+maybe_traffic_keylog_1_3(_,_,_,_) ->
+ ok.
+
update_bytes_sent(Version, StateData, _) when ?TLS_LT(Version, ?TLS_1_3) ->
StateData;
%% Count bytes sent in TLS 1.3 for AES-GCM
--
2.51.0