File 1551-Fix-Cryptcookie-test-crypto-distribution-bugs.patch of Package erlang

From 4a78cc94924868c73fd88efb9cc7d595d229233f Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Thu, 17 Apr 2025 16:45:22 +0200
Subject: [PATCH 1/6] Fix Cryptcookie test crypto distribution bugs

---
 lib/ssl/test/cryptcookie.erl      | 33 ++++++++--------
 lib/ssl/test/dist_cryptcookie.erl | 63 ++++++++++++++++---------------
 2 files changed, 50 insertions(+), 46 deletions(-)

diff --git a/lib/ssl/test/cryptcookie.erl b/lib/ssl/test/cryptcookie.erl
index af18fd120c..d6d6110b93 100644
--- a/lib/ssl/test/cryptcookie.erl
+++ b/lib/ssl/test/cryptcookie.erl
@@ -462,9 +462,13 @@ encrypt_and_send_chunk(
    Chunk, Size) ->
     %%
     Timestamp = timestamp(),
+    Seq_1 = Seq + 1,
     if
-        RekeyCount =< Seq;
-        RekeyTimestamp + RekeyTime =< Timestamp ->
+        Seq_1 < RekeyCount,
+        Timestamp < RekeyTimestamp + RekeyTime ->
+            {encrypt_and_send_chunk(OutStream, Seq, Params, Chunk, Size),
+             [Seq_1 | Params]};
+        true ->
             {OutStream_1, Params_1} =
                 encrypt_and_send_rekey_chunk(
                   OutStream, Seq, Params, Timestamp),
@@ -475,15 +479,12 @@ encrypt_and_send_chunk(
                     {encrypt_and_send_chunk(
                        OutStream_1, 0, Params_1, Chunk, Size),
                      [1 | Params_1]}
-            end;
-        true ->
-            {encrypt_and_send_chunk(OutStream, Seq, Params, Chunk, Size),
-             [Seq + 1 | Params]}
+            end
     end.
 
 encrypt_and_send_chunk(OutStream, Seq, Params, Chunk, 0) -> % Tick
     <<>> = Chunk, % ASSERT
-    %% A ticks are sent as a somewhat random size block
+    %% A tick is sent as a somewhat random size block
     %% to make it less obvious to spot
     <<S:8>> = crypto:strong_rand_bytes(1),
     TickSize = 8 + (S band 63),
@@ -565,8 +566,8 @@ recv_and_decrypt_chunk(InStream, SeqParams = [Seq | Params]) ->
                     {[DataChunk | InStream_1], [Seq + 1 | Params]};
                 <<?TICK_CHUNK, _/binary>> ->
                     {[<<>> | InStream_1], [Seq + 1 | Params]};
-                <<?REKEY_CHUNK, RekeyChunk>> ->
-                    case decrypt_rekey(Params, RekeyChunk) of
+                <<?REKEY_CHUNK, RekeyChunk/binary>> ->
+                    case decrypt_rekey(Seq, Params, RekeyChunk) of
                         Params_1 = #params{} ->
                             recv_and_decrypt_chunk(
                               InStream_1, [0 | Params_1]);
@@ -644,24 +645,26 @@ decrypt_block(
     end.
 
 decrypt_rekey(
+  Seq,
   Params =
       #params{
-         iv = IV,
+         iv = {IVSalt, IVNo},
          key = Key,
          rekey_key = #keypair{public = PubKeyA} = KeyPair,
-         hmac_algorithm = HmacAlgorithm},
+         hmac_algorithm = HmacAlgo},
   RekeyChunk) ->
     %%
     PubKeyLen = byte_size(PubKeyA),
     case RekeyChunk of
         <<PubKeyB:PubKeyLen/binary>> ->
-            SharedSecret = compute_shared_secret(KeyPair, PubKeyB),
             KeyLen = byte_size(Key),
-            IVLen = byte_size(IV),
-            IVSaltLen = IVLen - 6,
+            IVSaltLen = byte_size(IVSalt),
+            SharedSecret = compute_shared_secret(KeyPair, PubKeyB),
+            IV = <<(IVNo + Seq):48>>,
             {Key_1, <<IVSalt_1:IVSaltLen/binary, IVNo_1:48>>} =
                 hmac_key_iv(
-                  HmacAlgorithm, SharedSecret, [Key, IV], KeyLen, IVLen),
+                  HmacAlgo, SharedSecret, [Key, IVSalt, IV],
+                  KeyLen, IVSaltLen + 6),
             Params#params{
               iv = {IVSalt_1, IVNo_1},
               key = Key_1 };
diff --git a/lib/ssl/test/dist_cryptcookie.erl b/lib/ssl/test/dist_cryptcookie.erl
index 580ebb3ab3..cfdf3b0d98 100644
--- a/lib/ssl/test/dist_cryptcookie.erl
+++ b/lib/ssl/test/dist_cryptcookie.erl
@@ -293,33 +293,36 @@ output_handler_data(OutStream, EncryptState, CS_DH) ->
     erlang:dist_ctrl_get_data_notification(tl(CS_DH)),
     output_handler(OutStream_1, EncryptState_1, CS_DH).
 
-%% Get outbound data from VM; encrypt and send,
+%% Transfer outbound data from VM; encrypt and send,
 %% until the VM has no more
 %%
 %% Front,Size,Rear is an Okasaki queue of binaries with total byte Size
 %%
 output_handler_xfer(
-  OutStream, EncryptState, CS_DH, Front, Size, Rear)
-  when hd(CS_DH) =< Size ->
+  OutStream, EncryptState, [ChunkSize|_] = CS_DH, Front, Size, Rear)
+  when ChunkSize =< Size ->
+    %%
+    %% We have a full chunk or more -> collect chunks and send
     %%
-    %% We have a full chunk or more
-    %% -> collect one chunk or less and send
     output_handler_collect(
       OutStream, EncryptState, CS_DH, Front, Size, Rear);
 output_handler_xfer(
-  OutStream, EncryptState, CS_DH, Front, Size, Rear) ->
-    %% when Size < hd(CS_DH) ->
+  OutStream, EncryptState, [_|DistHandle] = CS_DH, Front, Size, Rear) ->
+    %% when Size < ChunkSize ->
     %%
     %% We do not have a full chunk -> try to fetch more from VM
-    case erlang:dist_ctrl_get_data(tl(CS_DH)) of
+    %%
+    case erlang:dist_ctrl_get_data(DistHandle) of
         none ->
             if
                 Size =:= 0 ->
                     %% No more data from VM, nothing buffered
                     %% -> done, for now
+                    %%
                     {OutStream, EncryptState};
                 true ->
                     %% The VM had no more -> send what we have
+                    %%
                     output_handler_collect(
                       OutStream, EncryptState, CS_DH, Front, Size, Rear)
             end;
@@ -330,8 +333,8 @@ output_handler_xfer(
               Iov)
     end.
 
-%% Enqueue VM data while splitting large binaries into
-%% chunk size; hd(CS_DH)
+%% Enqueue VM data while splitting large binaries into max
+%% ChunkSize = hd(CS_DH)
 %%
 output_handler_enq(
   OutStream, EncryptState, CS_DH, Front, Size, Rear, []) ->
@@ -339,40 +342,41 @@ output_handler_enq(
       OutStream, EncryptState, CS_DH, Front, Size, Rear);
 output_handler_enq(
   OutStream, EncryptState, CS_DH, Front, Size, Rear, [Bin|Iov]) ->
-    output_handler_enq(
+    output_handler_split(
       OutStream, EncryptState, CS_DH, Front, Size, Rear, Iov, Bin).
-%%
-output_handler_enq(
-  OutStream, EncryptState, CS_DH, Front, Size, Rear, Iov, Bin) ->
-    BinSize = byte_size(Bin),
-    ChunkSize = hd(CS_DH),
+
+output_handler_split(
+  OutStream, EncryptState, [ChunkSize|_] = CS_DH,
+  Front, Size, Rear, Iov, Bin) ->
     if
-        BinSize =< ChunkSize ->
+        byte_size(Bin) =< ChunkSize ->
             output_handler_enq(
               OutStream, EncryptState, CS_DH, Front, Size, [Bin|Rear],
               Iov);
         true ->
             <<Bin1:ChunkSize/binary, Bin2/binary>> = Bin,
-            output_handler_enq(
+            output_handler_split(
               OutStream, EncryptState, CS_DH, Front, Size, [Bin1|Rear],
               Iov, Bin2)
     end.
 
 %% Collect small binaries into chunks of at most
-%% chunk size; hd(CS_DH)
+%% ChunkSize = hd(CS_DH); encrypt and send them
 %%
-output_handler_collect(OutStream, EncryptState, CS_DH, [], Zero, []) ->
+output_handler_collect(
+  OutStream, EncryptState, CS_DH, [], Zero, []) ->
     0 = Zero, % ASSERT
-    %% No more enqueued -> try to get more form VM
+    %% No more enqueued -> try to get more from VM
     output_handler_xfer(OutStream, EncryptState, CS_DH, [], Zero, []);
-output_handler_collect(OutStream, EncryptState, CS_DH, Front, Size, Rear) ->
+output_handler_collect(
+  OutStream, EncryptState, CS_DH, Front, Size, Rear) ->
     output_handler_collect(
       OutStream, EncryptState, CS_DH, Front, Size, Rear, [], 0).
 %%
 output_handler_collect(
   OutStream, EncryptState, CS_DH, [], Zero, [], Acc, DataSize) ->
     0 = Zero, % ASSERT
-    output_handler_chunk(
+    output_handler_encrypt_and_send_chunk(
       OutStream, EncryptState, CS_DH, [], Zero, [], Acc, DataSize);
 output_handler_collect(
   OutStream, EncryptState, CS_DH, [], Size, Rear, Acc, DataSize) ->
@@ -381,15 +385,14 @@ output_handler_collect(
       OutStream, EncryptState, CS_DH, lists:reverse(Rear), Size, [],
       Acc, DataSize);
 output_handler_collect(
-  OutStream, EncryptState, CS_DH, [Bin|Iov] = Front, Size, Rear,
-  Acc, DataSize) ->
-    ChunkSize = hd(CS_DH),
+  OutStream, EncryptState, [ChunkSize|_] = CS_DH,
+  [Bin|Iov] = Front, Size, Rear, Acc, DataSize) ->
     BinSize = byte_size(Bin),
     DataSize_1 = DataSize + BinSize,
     if
         ChunkSize < DataSize_1 ->
             %% Bin does not fit in chunk -> send Acc
-            output_handler_chunk(
+            output_handler_encrypt_and_send_chunk(
               OutStream, EncryptState, CS_DH, Front, Size, Rear,
               Acc, DataSize);
         DataSize_1 < ChunkSize ->
@@ -400,14 +403,12 @@ output_handler_collect(
         true -> % DataSize_1 == ChunkSize ->
             %% Optimize one iteration; Bin fits exactly
             %% -> accumulate and send
-            output_handler_chunk(
+            output_handler_encrypt_and_send_chunk(
               OutStream, EncryptState, CS_DH, Iov, Size - BinSize, Rear,
               [Bin|Acc], DataSize_1)
     end.
 
-%% Encrypt and send a chunk
-%%
-output_handler_chunk(
+output_handler_encrypt_and_send_chunk(
   OutStream, EncryptState, CS_DH, Front, Size, Rear, Acc, DataSize) ->
     Data = lists:reverse(Acc),
     {OutStream_1, EncryptState_1} =
-- 
2.51.0

openSUSE Build Service is sponsored by