File 4562-ssh-MLKEM-kex-ssh.patch of Package erlang

From 95d0848c600302167d4cc3289247fadcfe6f7618 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Mon, 26 Jan 2026 09:05:05 +0100
Subject: [PATCH 2/4] ssh: MLKEM kex ssh

---
 lib/ssh/src/ssh.hrl                    |   1 +
 lib/ssh/src/ssh_connection_handler.erl |   2 +
 lib/ssh/src/ssh_fsm_kexinit.erl        |  25 +++-
 lib/ssh/src/ssh_message.erl            |  22 ++++
 lib/ssh/src/ssh_transport.erl          | 156 +++++++++++++++++++++----
 lib/ssh/src/ssh_transport.hrl          |  23 ++++
 lib/ssh/test/ssh_dbg_SUITE.erl         |   5 +
 lib/ssh/test/ssh_renegotiate_SUITE.erl |   2 +-
 8 files changed, 209 insertions(+), 27 deletions(-)

diff --git a/lib/ssh/src/ssh.hrl b/lib/ssh/src/ssh.hrl
index ad8b831985..48e73c065a 100644
--- a/lib/ssh/src/ssh.hrl
+++ b/lib/ssh/src/ssh.hrl
@@ -154,7 +154,8 @@
                             'curve448-sha512' |
                             'ecdh-sha2-nistp256' |
                             'ecdh-sha2-nistp384' |
-                            'ecdh-sha2-nistp521'
+                            'ecdh-sha2-nistp521' |
+                            'mlkem768x25519-sha256'
                             .
 
 -type pubkey_alg()       :: 'ecdsa-sha2-nistp256' |
diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index b0887fe525..9a36d7c8a9 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -1669,6 +1669,8 @@ set_kex_overload_prefix(Msg = <<?BYTE(Op),_/binary>>, #data{ssh_params=SshParams
 	    <<"dh_gex",Msg/binary>>;
 	"diffie-hellman-group" ++ _ ->
 	    <<"dh",Msg/binary>>;
+        "mlkem768x25519" ++ _ ->
+	    <<"mlkem",Msg/binary>>;
 	_ ->
 	    Msg
     end;
diff --git a/lib/ssh/src/ssh_fsm_kexinit.erl b/lib/ssh/src/ssh_fsm_kexinit.erl
index 319d9fd712..38d9cd1c2c 100644
--- a/lib/ssh/src/ssh_fsm_kexinit.erl
+++ b/lib/ssh/src/ssh_fsm_kexinit.erl
@@ -140,6 +140,25 @@ handle_event(internal, #ssh_msg_kex_ecdh_reply{} = Msg, {key_exchange,client,ReN
     ssh_connection_handler:send_bytes(ExtInfo, D),
     {next_state, {new_keys,client,ReNeg}, D#data{ssh_params=Ssh}};
 
+%%%---- PQ/T Hybrid Key Exchange Method
+handle_event(internal, #ssh_msg_kex_hybrid_init{} = Msg, {key_exchange,server,ReNeg}, D) ->
+    ok = check_kex_strict(Msg, D),
+    {ok, KexHybridReply, Ssh1} = ssh_transport:handle_kex_hybrid_init(Msg, D#data.ssh_params),
+    ssh_connection_handler:send_bytes(KexHybridReply, D),
+    {ok, NewKeys, Ssh2} = ssh_transport:new_keys_message(Ssh1),
+    ssh_connection_handler:send_bytes(NewKeys, D),
+    {ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh2),
+    ssh_connection_handler:send_bytes(ExtInfo, D),
+    {next_state, {new_keys,server,ReNeg}, D#data{ssh_params=Ssh}};
+
+handle_event(internal, #ssh_msg_kex_hybrid_reply{} = Msg, {key_exchange,client,ReNeg}, D) ->
+    ok = check_kex_strict(Msg, D),
+    {ok, NewKeys, Ssh1} = ssh_transport:handle_kex_hybrid_reply(Msg, D#data.ssh_params),
+    ssh_connection_handler:send_bytes(NewKeys, D),
+    {ok, ExtInfo, Ssh} = ssh_transport:ext_info_message(Ssh1),
+    ssh_connection_handler:send_bytes(ExtInfo, D),
+    {next_state, {new_keys,client,ReNeg}, D#data{ssh_params=Ssh}};
+
 %%% ######## handle KEX strict
 handle_event(internal, _Event, {key_exchange,_Role,init},
              #data{ssh_params = #ssh{algorithms = #alg{kex_strict_negotiated = true},
@@ -296,7 +315,9 @@ get_alg_group(Kex) when Kex == 'curve25519-sha256';
                         Kex == 'ecdh-sha2-nistp521';
                         Kex == 'ecdh-sha2-nistp384';
                         Kex == 'ecdh-sha2-nistp256' ->
-    ecdh_alg.
+    ecdh_alg;
+get_alg_group(Kex) when Kex == 'mlkem768x25519-sha256' ->
+    mlkem_alg.
 
 check_msg_group(_Msg, _AlgGroup, false) -> ok;
 check_msg_group(#ssh_msg_kexdh_init{},  dh_alg, true) -> ok;
@@ -308,6 +329,8 @@ check_msg_group(#ssh_msg_kex_dh_gex_init{},        dh_gex_alg, true) -> ok;
 check_msg_group(#ssh_msg_kex_dh_gex_reply{},       dh_gex_alg, true) -> ok;
 check_msg_group(#ssh_msg_kex_ecdh_init{},  ecdh_alg, true) -> ok;
 check_msg_group(#ssh_msg_kex_ecdh_reply{}, ecdh_alg, true) -> ok;
+check_msg_group(#ssh_msg_kex_hybrid_init{},  mlkem_alg, true) -> ok;
+check_msg_group(#ssh_msg_kex_hybrid_reply{}, mlkem_alg, true) -> ok;
 check_msg_group(_Msg, _AlgGroup, _) -> error.
 
 %%%################################################################
diff --git a/lib/ssh/src/ssh_message.erl b/lib/ssh/src/ssh_message.erl
index ef91cd6985..64422c973b 100644
--- a/lib/ssh/src/ssh_message.erl
+++ b/lib/ssh/src/ssh_message.erl
@@ -297,6 +297,15 @@ encode(#ssh_msg_kex_ecdh_reply{public_host_key = {Key,SigAlg}, q_s = Q_s, h_sig
     EncSign = encode_signature(Key, SigAlg, Sign),
     <<?Ebyte(?SSH_MSG_KEX_ECDH_REPLY), ?Ebinary(EncKey), ?Ebinary(Q_s), ?Ebinary(EncSign)>>;
 
+encode(#ssh_msg_kex_hybrid_init{c_init = {C_pk2, C_pk1}}) ->
+    <<?Ebyte(?SSH_MSG_KEX_HYBRID_INIT), ?Ebinary(<<C_pk2/binary, C_pk1/binary>>)>>;
+
+encode(#ssh_msg_kex_hybrid_reply{public_host_key = {Key,SigAlg}, s_reply = S_reply,
+                                 h_sig = Sign}) ->
+    EncKey = ssh2_pubkey_encode(Key),
+    EncSign = encode_signature(Key, SigAlg, Sign),
+    <<?Ebyte(?SSH_MSG_KEX_HYBRID_REPLY), ?Ebinary(EncKey), ?Ebinary(S_reply), ?Ebinary(EncSign)>>;
+
 encode(#ssh_msg_ignore{data = Data}) ->
     <<?Ebyte(?SSH_MSG_IGNORE), ?Estring_utf8(Data)>>;
 
@@ -530,6 +539,19 @@ decode(<<"ecdh",?BYTE(?SSH_MSG_KEX_ECDH_REPLY),
        h_sig = decode_signature(Sig)
       };
 
+decode(<<"mlkem",?BYTE(?SSH_MSG_KEX_HYBRID_INIT), ?DEC_BIN(C_init,__0)>>) ->
+    #ssh_msg_kex_hybrid_init{
+       c_init = C_init
+      };
+
+decode(<<"mlkem",?BYTE(?SSH_MSG_KEX_HYBRID_REPLY),
+	 ?DEC_BIN(Key,__1), ?DEC_BIN(S_reply,__2), ?DEC_BIN(Sig,__3)>>) ->
+    #ssh_msg_kex_hybrid_reply{
+       public_host_key = ssh2_pubkey_decode(Key),
+       s_reply = S_reply,
+       h_sig = decode_signature(Sig)
+      };
+
 decode(<<?SSH_MSG_SERVICE_REQUEST, ?DEC_BIN(Service,__0)>>) ->
     #ssh_msg_service_request{
        name = binary:bin_to_list(Service)
diff --git a/lib/ssh/src/ssh_transport.erl b/lib/ssh/src/ssh_transport.erl
index 4e6578d681..674d8db68c 100644
--- a/lib/ssh/src/ssh_transport.erl
+++ b/lib/ssh/src/ssh_transport.erl
@@ -47,9 +47,11 @@
 	 handle_kexinit_msg/4, handle_kexdh_init/2,
 	 handle_kex_dh_gex_group/2, handle_kex_dh_gex_init/2, handle_kex_dh_gex_reply/2,
 	 handle_new_keys/2, handle_kex_dh_gex_request/2,
-	 handle_kexdh_reply/2, 
+	 handle_kexdh_reply/2,
 	 handle_kex_ecdh_init/2,
 	 handle_kex_ecdh_reply/2,
+	 handle_kex_hybrid_init/2,
+	 handle_kex_hybrid_reply/2,
          parallell_gen_key/1,
 	 ssh_packet/2, pack/2,
          valid_key_sha_alg/3,
@@ -208,6 +210,7 @@ supported_algorithms() -> [{K,supported_algorithms(K)} || K <- algo_classes()].
 supported_algorithms(kex) ->
     select_crypto_supported(
       [
+       {'mlkem768x25519-sha256',                [{kems, mlkem768}, {public_keys,ecdh}, {curves,x25519}, {hashs,sha256}]},
        {'curve25519-sha256',                    [{public_keys,ecdh}, {curves,x25519}, {hashs,sha256}]},
        {'curve25519-sha256@libssh.org',         [{public_keys,ecdh}, {curves,x25519}, {hashs,sha256}]},
        {'curve448-sha512',                      [{public_keys,ecdh}, {curves,x448},   {hashs,sha512}]},
@@ -573,8 +576,17 @@ key_exchange_first_msg(Kex, Ssh0) when Kex == 'ecdh-sha2-nistp256' ;
     Curve = ecdh_curve(Kex),
     {Public, Private} = generate_key(ecdh, Curve),
     {SshPacket, Ssh1} = ssh_packet(#ssh_msg_kex_ecdh_init{q_c=Public},  Ssh0),
-    {ok, SshPacket, 
-     Ssh1#ssh{keyex_key = {{Public,Private},Curve}}}.
+    {ok, SshPacket,
+     Ssh1#ssh{keyex_key = {{Public,Private},Curve}}};
+key_exchange_first_msg(Kex, Ssh0) when Kex == 'mlkem768x25519-sha256' ->
+    Curve = ecdh_curve(Kex),
+    {C_publickey1, C_privkey1} = generate_key(ecdh, Curve),
+    {C_publickey2, C_privkey2} = generate_key(mlkem768, []),
+    {SshPacket, Ssh1} = ssh_packet(
+                          #ssh_msg_kex_hybrid_init{c_init = {C_publickey2, C_publickey1}},  Ssh0),
+    {ok, SshPacket,
+     Ssh1#ssh{keyex_key = {{mlkem768, {C_publickey2, C_privkey2}},
+                           {Curve, {C_publickey1, C_privkey1}}}}}.
 
 %%%----------------------------------------------------------------
 %%%
@@ -904,6 +916,91 @@ handle_kex_ecdh_reply(#ssh_msg_kex_ecdh_reply{public_host_key = PeerPubHostKey,
                                       [Class,Error], [{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
     end.
 
+%%%---- PQ/T Hybrid Key Exchange Method
+handle_kex_hybrid_init(#ssh_msg_kex_hybrid_init{c_init = C_init},
+                       Ssh0 = #ssh{algorithms = #alg{kex = Kex,
+                                                     hkey = SignAlg},
+                                   opts = Opts}) ->
+    %% at server
+    Curve = ecdh_curve(Kex),
+    {S_publickey1, S_privkey1} = generate_key(ecdh, Curve),
+    try
+        compute_key(hybrid_server, C_init, S_privkey1, Curve)
+    of
+        {S_ciphertext2, K_enc} ->
+            MyPrivHostKey = get_host_key(SignAlg, Opts),
+            MyPubHostKey = ssh_file:extract_public_key(MyPrivHostKey),
+            S_reply = <<S_ciphertext2/binary, S_publickey1/binary>>,
+            H = kex_hash(Ssh0, MyPubHostKey, sha(Curve),
+                         {mlkem, C_init, S_reply, K_enc}),
+            case sign(H, SignAlg, MyPrivHostKey, Ssh0) of
+                {ok, H_SIG} ->
+                    {SshPacket, Ssh1} =
+                        ssh_packet(#ssh_msg_kex_hybrid_reply{
+                                      public_host_key = {MyPubHostKey,SignAlg},
+                                      s_reply = S_reply,
+                                      h_sig = H_SIG
+                                     },
+                                   Ssh0),
+                    {ok, SshPacket, Ssh1#ssh{
+                                      shared_secret = K_enc,
+                                      exchanged_hash = H,
+                                      session_id = sid(Ssh1, H)}};
+                {error, unsupported_sign_alg} ->
+                    ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
+                                io_lib:format("Unsupported algorithm ~p", [SignAlg],
+                                             [{chars_limit, ssh_lib:max_log_len(Opts)}]))
+            end
+    catch
+        Class:Reason0:_Stacktrace ->
+            Reason = ssh_lib:trim_reason(Reason0),
+            MsgFun =
+                fun(debug) ->
+                        io_lib:format("Hybrid compute key failed in server: ~p:~p~n"
+                                      "Kex: ~p, Curve: ~p~n"
+                                      "C_init: ~p~n",
+                                      [Class, Reason, Kex, Curve, C_init],
+                                      [{chars_limit, ssh_lib:max_log_len(Ssh0)}]);
+                   (_) ->
+                        io_lib:format("Hybrid compute key failed in server: ~p:~p",
+                                      [Class,Reason],
+                                      [{chars_limit, ssh_lib:max_log_len(Ssh0)}])
+                end,
+            ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED, ?SELECT_MSG(MsgFun))
+    end.
+
+handle_kex_hybrid_reply(#ssh_msg_kex_hybrid_reply{public_host_key = PeerPubHostKey,
+                                                  s_reply = S_reply,
+                                                  h_sig = H_SIG},
+                        #ssh{keyex_key =
+                                 {{mlkem768, {C_publickey2, C_privkey2}},
+                                  {Curve, {C_publickey1, C_privkey1}}}
+                            } = Ssh0
+                       ) ->
+    %% at client
+    try
+        compute_key(hybrid_client, S_reply, {C_privkey2, C_privkey1}, Curve)
+    of
+	K_enc ->
+            H = kex_hash(Ssh0, PeerPubHostKey, sha(Curve),
+                         {mlkem, {C_publickey2, C_publickey1}, S_reply, K_enc}),
+	    case verify_host_key(Ssh0, PeerPubHostKey, H, H_SIG) of
+		ok ->
+		    {SshPacket, Ssh} = ssh_packet(#ssh_msg_newkeys{}, Ssh0),
+		    {ok, SshPacket, install_alg(snd, Ssh#ssh{shared_secret  = K_enc,
+                                                             exchanged_hash = H,
+                                                             session_id = sid(Ssh, H)})};
+		Error ->
+                    ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
+                                io_lib:format("Hybrid reply failed. Verify host key: ~p",[Error],
+                                              [{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
+	    end
+    catch
+        Class:Error:_Stacktrace ->
+            ?DISCONNECT(?SSH_DISCONNECT_KEY_EXCHANGE_FAILED,
+                        io_lib:format("Peer Hybrid public key seem invalid: ~p:~p",
+                                      [Class,Error], [{chars_limit, ssh_lib:max_log_len(Ssh0)}]))
+    end.
 
 %%%----------------------------------------------------------------
 handle_new_keys(#ssh_msg_newkeys{}, Ssh0) ->
@@ -1384,8 +1481,6 @@ pack(common, rfc4253, PlainText, DeltaLenTst,
     {Ssh1, CipherPkt} = encrypt(Ssh0, PlainPkt),
     MAC0 = mac(MacAlg, MacKey, SeqNum, PlainPkt),
     {<<CipherPkt/binary,MAC0/binary>>, Ssh1};
-
-
 pack(common, enc_then_mac, PlainText, DeltaLenTst,
      #ssh{send_sequence = SeqNum,
           send_mac = MacAlg,
@@ -1398,7 +1493,6 @@ pack(common, enc_then_mac, PlainText, DeltaLenTst,
     EncPacketPkt = <<?UINT32(PlainLen), CipherPkt/binary>>,
     MAC0 = mac(MacAlg, MacKey, SeqNum, EncPacketPkt),
     {<<?UINT32(PlainLen), CipherPkt/binary, MAC0/binary>>, Ssh1};
-
 pack(aead, _, PlainText, DeltaLenTst, Ssh0) ->
     PadLen = padding_length(1+byte_size(PlainText), Ssh0),
     Pad =  ssh_bits:random(PadLen),
@@ -1758,10 +1852,8 @@ encrypt_final(Ssh) ->
 		 encrypt_ctx = undefined
 		}}.
 
-
 encrypt(#ssh{encrypt = none} = Ssh, Data) ->
     {Ssh, Data};
-
 encrypt(#ssh{encrypt = 'chacha20-poly1305@openssh.com',
              encrypt_keys = {K1,K2},
              send_sequence = Seq} = Ssh,
@@ -1778,7 +1870,6 @@ encrypt(#ssh{encrypt = 'chacha20-poly1305@openssh.com',
     Ctag = crypto:mac(poly1305, PolyKey, EncBytes),
     %% Result
     {Ssh, {EncBytes,Ctag}};
-
 encrypt(#ssh{encrypt = SshCipher,
              encrypt_cipher = CryptoCipher,
              encrypt_keys = K,
@@ -1788,7 +1879,6 @@ encrypt(#ssh{encrypt = SshCipher,
     {Ctext,Ctag} = crypto:crypto_one_time_aead(CryptoCipher, K, IV0, PayloadData, LenData, true),
     IV = next_gcm_iv(IV0),
     {Ssh#ssh{encrypt_ctx = IV}, {<<LenData/binary,Ctext/binary>>,Ctag}};
-
 encrypt(#ssh{encrypt_ctx = Ctx0} = Ssh, Data) ->
     Enc = crypto:crypto_update(Ctx0, Data),
     {Ssh, Enc}.
@@ -1843,7 +1933,6 @@ decrypt_final(Ssh) ->
 
 decrypt(Ssh, <<>>) ->
     {Ssh, <<>>};
-
 decrypt(#ssh{decrypt = 'chacha20-poly1305@openssh.com',
              decrypt_keys = {K1,K2},
              recv_sequence = Seq} = Ssh, Data) ->
@@ -1866,10 +1955,8 @@ decrypt(#ssh{decrypt = 'chacha20-poly1305@openssh.com',
                     {Ssh,error}
             end
     end;
-
 decrypt(#ssh{decrypt = none} = Ssh, Data) ->
     {Ssh, Data};
-
 decrypt(#ssh{decrypt = SshCipher,
              decrypt_cipher = CryptoCipher,
 	     decrypt_keys = K,
@@ -2067,20 +2154,23 @@ kex_plaintext(SSH, Key, Args) ->
       ?Ebinary(EncodedKey),
       (kex_alg_dependent(Args))/binary>>.
 
-
+kex_alg_dependent({mlkem, {C_publickey2, C_publickey1}, S_reply, K_enc}) ->
+    %% mlkem client
+    C_init = <<C_publickey2/binary, C_publickey1/binary>>,
+    kex_alg_dependent({mlkem, C_init, S_reply, K_enc});
+kex_alg_dependent({mlkem, C_init, S_reply, K_enc}) ->
+    %% mlkem common
+    <<?Ebinary(C_init), ?Ebinary(S_reply), K_enc/binary>>;
 kex_alg_dependent({Q_c, Q_s, K}) when is_binary(Q_c), is_binary(Q_s) ->
     %% ecdh
     <<?Ebinary(Q_c), ?Ebinary(Q_s), ?Empint(K)>>;
-
 kex_alg_dependent({E, F, K}) ->
     %% diffie-hellman
     <<?Empint(E), ?Empint(F), ?Empint(K)>>;
-
 kex_alg_dependent({-1, NBits, -1, Prime, Gen, E, F, K}) ->
     %% ssh_msg_kex_dh_gex_request_old
     <<?Euint32(NBits),
       ?Empint(Prime), ?Empint(Gen), ?Empint(E), ?Empint(F), ?Empint(K)>>;
-
 kex_alg_dependent({Min, NBits, Max, Prime, Gen, E, F, K}) ->
     %% diffie-hellman group exchange
     <<?Euint32(Min), ?Euint32(NBits), ?Euint32(Max),
@@ -2156,10 +2246,10 @@ sha('curve25519-sha256' ) -> sha256;
 sha('curve25519-sha256@libssh.org' ) -> sha256;
 sha('curve448-sha512') -> sha512;
 sha(x25519) -> sha256;
+sha('mlkem768x25519-sha256') -> sha256;
 sha(x448) -> sha512;
 sha(Str) when is_list(Str), length(Str)<50 -> sha(list_to_existing_atom(Str)).
 
-
 mac_key_bytes('hmac-sha1')    -> 20;
 mac_key_bytes('hmac-sha1-etm@openssh.com') -> 20;
 mac_key_bytes('hmac-sha1-96') -> 20;
@@ -2193,7 +2283,6 @@ mac_digest_size(none) -> 0.
 %% Diffie-Hellman utils
 %%
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-
 dh_group('diffie-hellman-group1-sha1') ->  ?dh_group1;
 dh_group('diffie-hellman-group14-sha1') -> ?dh_group14;
 dh_group('diffie-hellman-group14-sha256') -> ?dh_group14;
@@ -2207,18 +2296,34 @@ parallell_gen_key(Ssh = #ssh{keyex_key = {x, {G, P}},
     {Public, Private} = generate_key(dh, [P,G,2*Sz]),
     Ssh#ssh{keyex_key = {{Private, Public}, {G, P}}}.
 
-
+generate_key(mlkem768, Args) ->
+    crypto:generate_key(mlkem768, Args);
 generate_key(ecdh, Args) ->
     crypto:generate_key(ecdh, Args);
 generate_key(dh, [P,G,Sz2]) ->
     {Public,Private} = crypto:generate_key(dh, [P, G, max(Sz2,?MIN_DH_KEY_SIZE)] ),
     {crypto:bytes_to_integer(Public), crypto:bytes_to_integer(Private)}.
 
-
-compute_key(Algorithm, OthersPublic, MyPrivate, Args) ->
-    Shared = crypto:compute_key(Algorithm, OthersPublic, MyPrivate, Args),
+compute_key(hybrid_server, C_init, S_privkey1, Curve) ->
+    <<C_publickey2:1184/binary, C_publickey1:32/binary>> = C_init,
+    {K_pq_secret, S_ciphertext2} = crypto:encapsulate_key(mlkem768, C_publickey2),
+    SharedSecret = hybrid_common(K_pq_secret, Curve, C_publickey1, S_privkey1),
+    {S_ciphertext2, <<?Ebinary(SharedSecret)>>};
+compute_key(hybrid_client, S_reply, {C_privkey2, C_privkey1}, Curve) ->
+    <<S_ciphertext2:1088/binary, S_publickey1:32/binary>> = S_reply,
+    K_pq_secret = crypto:decapsulate_key(mlkem768, C_privkey2, S_ciphertext2),
+    SharedSecret = hybrid_common(K_pq_secret, Curve, S_publickey1, C_privkey1),
+    <<?Ebinary(SharedSecret)>>;
+compute_key(Algorithm, PeerPublic, MyPrivate, Args) ->
+    Shared = crypto:compute_key(Algorithm, PeerPublic, MyPrivate, Args),
     crypto:bytes_to_integer(Shared).
 
+hybrid_common(K_pq_secret, Curve, PeerPublic, MyPrivate) ->
+    K_cl_secret = compute_key(ecdh, PeerPublic, MyPrivate, Curve),
+    K_cl_secret_mpint = <<?Empint(K_cl_secret)>>,
+    K_cl_secret_mpint_trim =
+        binary:part(K_cl_secret_mpint, byte_size(K_cl_secret_mpint), -32),
+    crypto:hash(sha(Curve), <<K_pq_secret/binary, K_cl_secret_mpint_trim/binary>>).
 
 dh_bits(#alg{encrypt = Encrypt,
              send_mac = SendMac}) ->
@@ -2233,8 +2338,9 @@ ecdh_curve('ecdh-sha2-nistp256') -> secp256r1;
 ecdh_curve('ecdh-sha2-nistp384') -> secp384r1;
 ecdh_curve('ecdh-sha2-nistp521') -> secp521r1;
 ecdh_curve('curve448-sha512'   ) -> x448;
-ecdh_curve('curve25519-sha256' ) -> x25519;
-ecdh_curve('curve25519-sha256@libssh.org' ) -> x25519.
+ecdh_curve('curve25519-sha256') -> x25519;
+ecdh_curve('mlkem768x25519-sha256') -> x25519;
+ecdh_curve('curve25519-sha256@libssh.org') -> x25519.
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %%
diff --git a/lib/ssh/src/ssh_transport.hrl b/lib/ssh/src/ssh_transport.hrl
index 3ab1ce319f..3b947ea5fe 100644
--- a/lib/ssh/src/ssh_transport.hrl
+++ b/lib/ssh/src/ssh_transport.hrl
@@ -215,6 +215,29 @@
 	  h_sig              % string (the signature on the exchange hash)
 	}).
 
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%%
+%% KEY ML-KEM messages
+%%
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+%% mlkem768x25519-sha256
+
+-define(SSH_MSG_KEX_HYBRID_INIT,                30).
+-define(SSH_MSG_KEX_HYBRID_REPLY,               31).
+
+-record(ssh_msg_kex_hybrid_init,
+	{
+         c_init    % string (concatenation of C_PK2 and C_PK1)
+	}).
+
+-record(ssh_msg_kex_hybrid_reply,
+	{
+         public_host_key,   % string (server's public host key) (k_s)
+         s_reply,           % string (concatenation of S_CT2 and S_PK1)
+         h_sig              % string (the signature on the exchange hash)
+	}).
+
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %%
diff --git a/lib/ssh/test/ssh_dbg_SUITE.erl b/lib/ssh/test/ssh_dbg_SUITE.erl
index b49b91d7da..a0e9a5797a 100644
--- a/lib/ssh/test/ssh_dbg_SUITE.erl
+++ b/lib/ssh/test/ssh_dbg_SUITE.erl
@@ -338,6 +338,11 @@ dbg_ssh_messages(Config) ->
     ?DBG_RECEIVE("Received SSH_MSG_KEXINIT:",      Ref, C, Pid),
 
     case atom_to_list( (ssh_connection_handler:alg(C))#alg.kex ) of
+        "mlkem"++_ ->
+            ?DBG_RECEIVE("Going to send SSH_MSG_KEX_HYBRID_INIT:",  Ref, C, Pid),
+            ?DBG_RECEIVE("Received SSH_MSG_KEX_HYBRID_INIT:",       Ref, D, Pid),
+            ?DBG_RECEIVE("Going to send SSH_MSG_KEX_HYBRID_REPLY:", Ref, D, Pid),
+            ?DBG_RECEIVE("Received SSH_MSG_KEX_HYBRID_REPLY:",      Ref, C, Pid);
         "curve"++_ ->
             ?DBG_RECEIVE("Going to send SSH_MSG_KEX_ECDH_INIT:",  Ref, C, Pid),
             ?DBG_RECEIVE("Received SSH_MSG_KEX_ECDH_INIT:",       Ref, D, Pid),
diff --git a/lib/ssh/test/ssh_renegotiate_SUITE.erl b/lib/ssh/test/ssh_renegotiate_SUITE.erl
index 662e6ae1c3..2302746a78 100644
--- a/lib/ssh/test/ssh_renegotiate_SUITE.erl
+++ b/lib/ssh/test/ssh_renegotiate_SUITE.erl
@@ -251,7 +251,7 @@ rekey_limit_daemon(Config) ->
 %% Check that datatransfer in the other direction does not trigger re-keying
 norekey_limit_client() -> [{timetrap,{seconds,500}}].
 norekey_limit_client(Config) ->
-    Limit = 6000,
+    Limit = 6500,
     UserDir = proplists:get_value(priv_dir, Config),
     DataFile = filename:join(UserDir, "rekey3.data"),
     file:write_file(DataFile, lists:duplicate(Limit+10,1)),
-- 
2.51.0

openSUSE Build Service is sponsored by