File 1661-ssl-Handle-encryption-state-stepping-properly.patch of Package erlang

From d2512f28296e4fe536428575efcecf3979bf1347 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Wed, 26 Nov 2025 16:19:56 +0100
Subject: [PATCH 1/4] ssl: Handle encryption state stepping properly

---
 lib/ssl/src/tls_client_connection_1_3.erl |   9 +-
 lib/ssl/src/tls_handshake_1_3.erl         | 139 +++++++++++++---------
 lib/ssl/src/tls_server_connection_1_3.erl |  39 ++++--
 lib/ssl/test/ssl_session_ticket_SUITE.erl |   4 +-
 4 files changed, 120 insertions(+), 71 deletions(-)

diff --git a/lib/ssl/src/tls_client_connection_1_3.erl b/lib/ssl/src/tls_client_connection_1_3.erl
index 6522f1b533..7870b6b603 100644
--- a/lib/ssl/src/tls_client_connection_1_3.erl
+++ b/lib/ssl/src/tls_client_connection_1_3.erl
@@ -458,11 +458,12 @@ wait_finished(internal,
         State4 = Connection:queue_handshake(Finished, State3),
         %% Send first flight
         {State5, _} = Connection:send_handshake_flight(State4),
-        State6 = tls_handshake_1_3:handle_secrets(State5),
-        %% Configure traffic keys
-        State7 = ssl_record:step_encryption_state(State6),
+        State6 = tls_handshake_1_3:calculate_traffic_secrets(State5),
+        State7 = tls_handshake_1_3:maybe_calculate_resumption_master_secret(State6),
+        State8 = ssl_record:step_encryption_state(State7),
+        State9 = tls_handshake_1_3:prepare_connection(State8),
         {Record, State} =
-            ssl_gen_statem:prepare_connection(State7, tls_gen_connection),
+            ssl_gen_statem:prepare_connection(State9, tls_gen_connection),
         KeepSecrets = maps:get(keep_secrets, SSLOpts, false),
         tls_gen_connection_1_3:maybe_traffic_keylog_1_3(KeepSecrets, Role,
                                                         State#state.connection_states, 0),
diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl
index 44f795d92e..a7c4c6cf19 100644
--- a/lib/ssl/src/tls_handshake_1_3.erl
+++ b/lib/ssl/src/tls_handshake_1_3.erl
@@ -65,7 +65,7 @@
          replace_ch1_with_message_hash/1,
          select_common_groups/2,
          verify_signature_algorithm/2,
-         handle_secrets/1,
+         prepare_connection/1,
          set_client_random/2,
          handle_pre_shared_key/3,
          update_start_state/2,
@@ -83,6 +83,9 @@
          calculate_traffic_secrets/1,
          calculate_client_early_traffic_secret/5,
          calculate_client_early_traffic_secret/2,
+         calculate_read_traffic_secrets/1,
+         calculate_write_traffic_secrets/1,
+         maybe_calculate_resumption_master_secret/1,
          early_data_secret/1,
          hs_traffic_secrets/1,
          encode_early_data/2,
@@ -437,10 +440,9 @@ process_certificate(#certificate_1_3{
 process_certificate(#certificate_1_3{
                        certificate_request_context = <<>>,
                        certificate_list = []},
-                    #state{static_env = #static_env{role = server = Role},
+                    #state{static_env = #static_env{role = server},
                            ssl_options =
-                               #{fail_if_no_peer_cert := true}} = State0) ->
-    State = handle_alert_encryption_state(Role, State0),
+                               #{fail_if_no_peer_cert := true}} = State) ->
     {error, {?ALERT_REC(?FATAL, ?CERTIFICATE_REQUIRED, certificate_required), State}};
 process_certificate(#certificate_1_3{certificate_list = CertEntries},
                     #state{ssl_options = SslOptions,
@@ -458,8 +460,7 @@ process_certificate(#certificate_1_3{certificate_list = CertEntries},
            CertEntries, CertDbHandle, CertDbRef, SslOptions, CRLDbHandle, Role,
            Host, StaplingState) of
         #alert{} = Alert ->
-            State = handle_alert_encryption_state(Role, State0),
-            {error, {Alert, State}};
+            {error, {Alert, State0}};
         {PeerCert, PublicKeyInfo} ->
             State = store_peer_cert(State0, PeerCert, PublicKeyInfo),
             {ok, {State, wait_cv}}
@@ -470,7 +471,7 @@ verify_certificate_verify(#state{static_env = #static_env{role = Role},
                                  handshake_env =
                                      #handshake_env{
                                         public_key_info = PublicKeyInfo,
-                                        tls_handshake_history = HHistory}} = State0,
+                                        tls_handshake_history = HHistory}} = State,
                           #certificate_verify_1_3{
                              algorithm = SignatureScheme,
                              signature = Signature}) ->
@@ -494,15 +495,11 @@ verify_certificate_verify(#state{static_env = #static_env{role = Role},
     %% scheme.
     case verify(THash, ContextString, HashAlgo, SignAlg, Signature, PublicKeyInfo) of
         {ok, true} ->
-            {ok, {State0, wait_finished}};
+            {ok, {State, wait_finished}};
         {ok, false} ->
-            State1 = calculate_traffic_secrets(State0),
-            State = ssl_record:step_encryption_state(State1),
             {error, {?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
                                 "Failed to verify CertificateVerify"), State}};
         {error, #alert{} = Alert} ->
-            State1 = calculate_traffic_secrets(State0),
-            State = ssl_record:step_encryption_state(State1),
             {error, {Alert, State}}
     end.
 
@@ -796,36 +793,6 @@ build_content(Context, THash) ->
     Prefix = binary:copy(<<32>>, 64),
     <<Prefix/binary,Context/binary,?BYTE(0),THash/binary>>.
 
-
-%% Sets correct encryption state when sending Alerts in shared states that use different secrets.
-%% - If server: use traffic secrets as by this time the client's state machine
-%%              already stepped into the 'connection' state.
-handle_alert_encryption_state(server, State0) ->
-    State1 = calculate_traffic_secrets(State0),
-    #state{ssl_options = Options,
-           connection_states = ConnectionStates,
-           protocol_specific = PS} = State = ssl_record:step_encryption_state(State1),
-    KeylogFun = maps:get(keep_secrets, Options, undefined),
-    maybe_keylog(KeylogFun, PS, ConnectionStates),
-    State;
-%% - If client: use handshake secrets.
-handle_alert_encryption_state(client, State) ->
-    State.
-
-maybe_keylog({Keylog, Fun}, ProtocolSpecific, ConnectionStates) when Keylog == keylog_hs;
-                                                                     Keylog == keylog ->
-    N = maps:get(num_key_updates, ProtocolSpecific, 0),
-    #{security_parameters := #security_parameters{client_random = ClientRandom,
-                                                  prf_algorithm = Prf,
-                                                  application_traffic_secret = TrafficSecret}}
-        = ssl_record:current_connection_state(ConnectionStates, write),
-    TrafficKeyLog = ssl_logger:keylog_traffic_1_3(server, ClientRandom,
-                                                  Prf, TrafficSecret, N),
-
-    ssl_logger:keylog(TrafficKeyLog, ClientRandom, Fun);
-maybe_keylog(_,_,_) ->
-    ok.
-
 validate_certificate_chain(CertEntries, CertDbHandle, CertDbRef,
                            SslOptions, CRLDbHandle, Role, Host, StaplingState) ->
     try split_cert_entries(CertEntries, StaplingState, [], #{}) of
@@ -906,12 +873,12 @@ message_hash(ClientHello1, HKDFAlgo) ->
      0,0,ssl_cipher:hash_size(HKDFAlgo),
      crypto:hash(HKDFAlgo, ClientHello1)].
 
-handle_secrets(State0) ->
-    State1 = calculate_traffic_secrets(State0),
-    State2 = #state{protocol_specific = PS} = maybe_calculate_resumption_master_secret(State1),
-    ExporterSecret = calculate_exporter_master_secret(State2),
-    State3 =  State2#state{protocol_specific = PS#{exporter_master_secret => ExporterSecret}},
-    forget_master_secret(State3).
+prepare_connection(State0) ->
+    %% Handle different secrets on transition to the connection state
+    State1 = #state{protocol_specific = PS} = maybe_calculate_resumption_master_secret(State0),
+    ExporterSecret = calculate_exporter_master_secret(State1),
+    State =  State0#state{protocol_specific = PS#{exporter_master_secret => ExporterSecret}},
+    forget_master_secret(State).
 
 calculate_handshake_secrets(PublicKey, PrivateKey, SelectedGroup, PSK,
                               #state{connection_states = ConnectionStates,
@@ -1135,6 +1102,72 @@ calculate_traffic_secrets(#state{
                                      ReadKey, ReadIV, undefined,
                                      WriteKey, WriteIV, undefined).
 
+
+calculate_read_traffic_secrets(#state{
+                             static_env = #static_env{role = Role},
+                                  connection_states = #{pending_read := PendingRead0} =
+                                      ConnectionStates,
+                                  handshake_env =
+                                      #handshake_env{
+                                         tls_handshake_history = HHistory}} = State0) ->
+    #{security_parameters := SecParamsR,
+      cipher_state := #cipher_state{finished_key = FinishedKey}} =
+        ssl_record:pending_connection_state(ConnectionStates, read),
+    #security_parameters{prf_algorithm = HKDFAlgo,
+                         cipher_suite = CipherSuite,
+                         master_secret = HandshakeSecret} = SecParamsR,
+
+    MasterSecret =
+        tls_v1:key_schedule(master_secret, HKDFAlgo, HandshakeSecret),
+
+    %% Get the correct list messages for the handshake context.
+    Messages = get_handshake_context(Role, HHistory),
+
+    %% Calculate [sender]_application_traffic_secret_0
+    ClientAppTrafficSecret0 =
+        tls_v1:client_application_traffic_secret_0(HKDFAlgo, MasterSecret, lists:reverse(Messages)),
+
+    %% Calculate traffic keys
+    KeyLength = tls_v1:key_length(CipherSuite),
+    {ReadKey, ReadIV} = tls_v1:calculate_traffic_keys(HKDFAlgo, KeyLength, ClientAppTrafficSecret0),
+    PendingRead = update_connection_state(PendingRead0, MasterSecret, undefined,
+                                          ClientAppTrafficSecret0,
+                                          ReadKey, ReadIV, FinishedKey),
+    State0#state{connection_states = ConnectionStates#{pending_read => PendingRead}}.
+
+calculate_write_traffic_secrets(#state{
+                                   static_env = #static_env{role = Role},
+                                   connection_states = #{pending_write := PendingWrite0} =
+                                       ConnectionStates,
+                             handshake_env =
+                                 #handshake_env{
+                                    tls_handshake_history = HHistory}} = State0) ->
+    #{security_parameters := SecParamsR,
+      cipher_state := #cipher_state{finished_key = FinishedKey}} =
+        ssl_record:pending_connection_state(ConnectionStates, write),
+    #security_parameters{prf_algorithm = HKDFAlgo,
+                         cipher_suite = CipherSuite,
+                         master_secret = HandshakeSecret} = SecParamsR,
+
+    MasterSecret =
+        tls_v1:key_schedule(master_secret, HKDFAlgo, HandshakeSecret),
+
+    %% Get the correct list messages for the handshake context.
+    Messages = get_handshake_context(Role, HHistory),
+
+    %% Calculate [sender]_application_traffic_secret_0
+    ServerAppTrafficSecret0 =
+        tls_v1:server_application_traffic_secret_0(HKDFAlgo, MasterSecret, lists:reverse(Messages)),
+
+    %% Calculate traffic keys
+    KeyLength = tls_v1:key_length(CipherSuite),
+    {WriteKey, WriteIV} = tls_v1:calculate_traffic_keys(HKDFAlgo, KeyLength, ServerAppTrafficSecret0),
+    PendingWrite = update_connection_state(PendingWrite0, MasterSecret, undefined,
+                                          ServerAppTrafficSecret0,
+                                          WriteKey, WriteIV, FinishedKey),
+    State0#state{connection_states = ConnectionStates#{pending_write => PendingWrite}}.
+
+
 %% X25519, X448
 calculate_shared_secret(OthersKey, MyKey, Group)
   when is_binary(OthersKey) andalso is_binary(MyKey) andalso
@@ -1443,14 +1476,12 @@ get_handshake_context_client(L) ->
 %% CertificateRequest message.
 verify_signature_algorithm(#state{
                               static_env = #static_env{role = Role},
-                              ssl_options = #{signature_algs := LocalSignAlgs}} = State0,
+                              ssl_options = #{signature_algs := LocalSignAlgs}} = State,
                            #certificate_verify_1_3{algorithm = PeerSignAlg}) ->
     case lists:member(PeerSignAlg, filter_tls13_algs(LocalSignAlgs)) of
         true ->
-            {ok, maybe_update_selected_sign_alg(State0, PeerSignAlg, Role)};
+            {ok, maybe_update_selected_sign_alg(State, PeerSignAlg, Role)};
         false ->
-            State1 = calculate_traffic_secrets(State0),
-            State = ssl_record:step_encryption_state(State1),
             {error, {?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
                                 "CertificateVerify uses unsupported signature algorithm"), State}}
     end.
@@ -1461,10 +1492,6 @@ maybe_update_selected_sign_alg(#state{session = Session} = State, SignAlg, clien
 maybe_update_selected_sign_alg(State, _, _) ->
     State.
 
-
-
-
-
 context_string(server) ->
     <<"TLS 1.3, server CertificateVerify">>;
 context_string(client) ->
diff --git a/lib/ssl/src/tls_server_connection_1_3.erl b/lib/ssl/src/tls_server_connection_1_3.erl
index 8f0e0864c0..79f0999263 100644
--- a/lib/ssl/src/tls_server_connection_1_3.erl
+++ b/lib/ssl/src/tls_server_connection_1_3.erl
@@ -308,14 +308,12 @@ wait_finished(internal,
     {Ref,Maybe} = tls_gen_connection_1_3:do_maybe(),
     try
         Maybe(tls_handshake_1_3:validate_finished(State0, VerifyData)),
-
-        State1 = tls_handshake_1_3:handle_secrets(State0),
-        %% Configure traffic keys
-        State2 = ssl_record:step_encryption_state(State1),
-
-        State3 = maybe_send_session_ticket(State2),
-
-        {Record, State} = ssl_gen_statem:prepare_connection(State3, tls_gen_connection),
+        State1 = tls_handshake_1_3:calculate_read_traffic_secrets(State0),
+        State2 = tls_handshake_1_3:maybe_calculate_resumption_master_secret(State1),
+        State3 = ssl_record:step_encryption_state_read(State2),
+        State4 = tls_handshake_1_3:prepare_connection(State3),
+        State5 = maybe_send_session_ticket(State4),
+        {Record, State} = ssl_gen_statem:prepare_connection(State5, tls_gen_connection),
         KeepSecrets = maps:get(keep_secrets, SSLOpts, false),
         tls_gen_connection_1_3:maybe_traffic_keylog_1_3(KeepSecrets, Role,
                                                         State#state.connection_states, 0),
@@ -583,8 +581,11 @@ send_hello_flight({start_handshake, PSK0},
         State9 = Connection:queue_handshake(Finished, State8),
 
         %% Send first flight
-        {State, _} = Connection:send_handshake_flight(State9),
+        {State10, _} = Connection:send_handshake_flight(State9),
 
+        State11 = tls_handshake_1_3:calculate_write_traffic_secrets(State10),
+        State = ssl_record:step_encryption_state_write(State11),
+        maybe_keylog(State),
         {State, NextState}
 
     catch
@@ -932,3 +933,23 @@ handle_alpn([ServerProtocol|T], ClientProtocols) ->
         false ->
             handle_alpn(T, ClientProtocols)
     end.
+
+maybe_keylog(#state{ssl_options = Options,
+                    connection_states = ConnectionStates,
+                    protocol_specific = PS})->
+    KeylogFun = maps:get(keep_secrets, Options, undefined),
+    maybe_keylog(KeylogFun, PS, ConnectionStates).
+
+maybe_keylog({Keylog, Fun}, ProtocolSpecific, ConnectionStates) when Keylog == keylog_hs;
+                                                                     Keylog == keylog ->
+    N = maps:get(num_key_updates, ProtocolSpecific, 0),
+    #{security_parameters := #security_parameters{client_random = ClientRandom,
+                                                  prf_algorithm = Prf,
+                                                  application_traffic_secret = TrafficSecret}}
+        = ssl_record:current_connection_state(ConnectionStates, write),
+    TrafficKeyLog = ssl_logger:keylog_traffic_1_3(server, ClientRandom,
+                                                  Prf, TrafficSecret, N),
+
+    ssl_logger:keylog(TrafficKeyLog, ClientRandom, Fun);
+maybe_keylog(_,_,_) ->
+    ok.
diff --git a/lib/ssl/test/ssl_session_ticket_SUITE.erl b/lib/ssl/test/ssl_session_ticket_SUITE.erl
index c721f3f010..1ce8d29e53 100644
--- a/lib/ssl/test/ssl_session_ticket_SUITE.erl
+++ b/lib/ssl/test/ssl_session_ticket_SUITE.erl
@@ -1222,7 +1222,7 @@ early_data_basic(Config) when is_list(Config) ->
                                                 verify_active_session_resumption,
                                                 [false]}},
                                          {from, self()}, {options, ClientOpts1}]),
-    skip_keylogs(3), %% HS and two traffic secrets
+    skip_keylogs(4), %% HS and two traffic secrets
 
     ssl_test_lib:check_result(Server0, ok, Client0, ok),
 
@@ -1247,7 +1247,7 @@ early_data_basic(Config) when is_list(Config) ->
         {keylog, #{items := EarlyKeylog}} ->
             ["CLIENT_EARLY_TRAFFIC_SECRET" ++ _| _] = EarlyKeylog
     end,
-    skip_keylogs(3), %% HS and two traffic secrets so they do not end up
+    skip_keylogs(4), %% HS and two traffic secrets so they do not end up
                      %% in check_result
 
     ssl_test_lib:check_result(Server0, ok, Client1, ok),
-- 
2.51.0

openSUSE Build Service is sponsored by