File 1502-ssl-Add-hybird-MLKEM-algorithms.patch of Package erlang

From 763f6facaf06c8a3c14c2882c69af2caebf0cf8a Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Tue, 9 Sep 2025 11:51:10 +0200
Subject: [PATCH 2/2] ssl: Add hybird MLKEM algorithms

---
 lib/ssl/src/ssl_cipher.erl                 | 35 +--------
 lib/ssl/src/ssl_handshake.erl              | 86 ++++++++++++++++++----
 lib/ssl/src/tls_client_connection_1_3.erl  | 24 ++++--
 lib/ssl/src/tls_handshake_1_3.erl          | 64 +++++++++++++++-
 lib/ssl/src/tls_handshake_1_3.hrl          |  5 ++
 lib/ssl/src/tls_server_connection_1_3.erl  | 60 ++++++++++-----
 lib/ssl/src/tls_v1.erl                     | 28 ++++++-
 lib/ssl/test/openssl_client_cert_SUITE.erl |  9 +++
 lib/ssl/test/openssl_server_cert_SUITE.erl |  9 +++
 lib/ssl/test/ssl_cert_SUITE.erl            | 18 ++++-
 lib/ssl/test/ssl_cert_tests.erl            | 27 ++++++-
 11 files changed, 287 insertions(+), 78 deletions(-)

diff --git a/lib/ssl/src/ssl_cipher.erl b/lib/ssl/src/ssl_cipher.erl
index 419675cfa9..36f2ad638c 100644
--- a/lib/ssl/src/ssl_cipher.erl
+++ b/lib/ssl/src/ssl_cipher.erl
@@ -72,9 +72,7 @@
          bulk_cipher_algorithm/1]).
 
 %% RFC 8446 TLS 1.3
--export([generate_client_shares/1,
-         generate_server_share/1,
-         add_zero_padding/2,
+-export([add_zero_padding/2,
          encrypt_ticket/3,
          decrypt_ticket/3,
          encrypt_data/4,
@@ -1220,37 +1218,6 @@ filter_keyuse_suites(Use, KeyUse, CipherSuits, Suites) ->
 	    CipherSuits -- Suites
     end.
 
-generate_server_share(Group) ->
-    Key = generate_key_exchange(Group),
-    #key_share_server_hello{
-       server_share = #key_share_entry{
-                         group = Group,
-                         key_exchange = Key
-                        }}.
-
-generate_client_shares(Groups) ->
-    KeyShareEntry = fun (Group) ->
-                        #key_share_entry{group = Group, key_exchange = generate_key_exchange(Group)}
-                    end,
-    ClientShares = lists:map(KeyShareEntry, Groups),
-    #key_share_client_hello{client_shares = ClientShares}.
-
-generate_key_exchange(secp256r1) ->
-    public_key:generate_key({namedCurve, secp256r1});
-generate_key_exchange(secp384r1) ->
-    public_key:generate_key({namedCurve, secp384r1});
-generate_key_exchange(secp521r1) ->
-    public_key:generate_key({namedCurve, secp521r1});
-generate_key_exchange(x25519) ->
-    crypto:generate_key(ecdh, x25519);
-generate_key_exchange(x448) ->
-    crypto:generate_key(ecdh, x448);
-generate_key_exchange(MLKem) when MLKem == mlkem512;
-                                  MLKem == mlkem768;
-                                  MLKem == mlkem1024 ->
-    crypto:generate_key(MLKem, []);
-generate_key_exchange(FFDHE) ->
-    public_key:generate_key(ssl_dh_groups:dh_params(FFDHE)).
 
 
 %% TODO: Move this functionality to crypto!
diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl
index d88f47dad1..3cba63840b 100644
--- a/lib/ssl/src/ssl_handshake.erl
+++ b/lib/ssl/src/ssl_handshake.erl
@@ -1474,21 +1474,35 @@ add_selected_version(Extensions) ->
     Extensions#{server_hello_selected_version => SupportedVersions}.
 
 kse_remove_private_key(#key_share_entry{
-                      group = Group,
-                      key_exchange =
-                          #'ECPrivateKey'{publicKey = PublicKey}}) ->
+                          group = Group,
+                          key_exchange =
+                              #'ECPrivateKey'{publicKey = PublicKey}}) ->
     #key_share_entry{
        group = Group,
        key_exchange = PublicKey};
 kse_remove_private_key(#key_share_entry{
-                      group = Group,
-                      key_exchange =
-                          {PublicKey, _}}) ->
+                          group = Group,
+                          key_exchange =
+                              {#'ECPrivateKey'{publicKey = PublicKey1},
+                                {PublicKey2, _}}}) ->
+    #key_share_entry{
+       group = Group,
+       key_exchange = <<PublicKey1/binary, PublicKey2/binary>>};
+kse_remove_private_key(#key_share_entry{
+                          group = Group,
+                          key_exchange =
+                              {{PublicKey1, _}, {PublicKey2, _}}}) ->
+    #key_share_entry{
+       group = Group,
+       key_exchange = <<PublicKey1/binary, PublicKey2/binary>>};
+kse_remove_private_key(#key_share_entry{
+                          group = Group,
+                          key_exchange =
+                              {PublicKey, _}}) ->
     #key_share_entry{
        group = Group,
        key_exchange = PublicKey}.
 
-
 signature_algs_ext(undefined) ->
     undefined;
 signature_algs_ext(SignatureSchemes0) ->
@@ -2665,7 +2679,6 @@ encode_versions(Versions) ->
 
 encode_client_shares(ClientShares) ->
     << << (encode_key_share_entry(KeyShareEntry0))/binary >> || KeyShareEntry0 <- ClientShares >>.
-
 encode_key_share_entry(#key_share_entry{group = Group,
                                         key_exchange = KeyExchange}) ->
     Len = byte_size(KeyExchange),
@@ -3075,14 +3088,15 @@ decode_extensions(<<?UINT16(?KEY_SHARE_EXT), ?UINT16(Len),
 decode_extensions(<<?UINT16(?KEY_SHARE_EXT), ?UINT16(Len),
                     ExtData:Len/binary, Rest/binary>>,
                   Version, MessageType = server_hello, Acc) ->
-    <<?UINT16(Group),?UINT16(KeyLen),KeyExchange:KeyLen/binary>> = ExtData,
-    assert_unique_extension(key_share, Acc),
+    <<?UINT16(EnumGroup),?UINT16(KeyLen),KeyExchange0:KeyLen/binary>> = ExtData,
+    Group =  tls_v1:enum_to_group(EnumGroup),
+    KeyExchange = maybe_dec_server_hybrid_share(Group, KeyExchange0),
     decode_extensions(Rest, Version, MessageType,
                       Acc#{key_share =>
                                #key_share_server_hello{
                                   server_share =
                                       #key_share_entry{
-                                         group = tls_v1:enum_to_group(Group),
+                                         group = Group,
                                          key_exchange = KeyExchange}}});
 
 decode_extensions(<<?UINT16(?KEY_SHARE_EXT), ?UINT16(Len),
@@ -3239,8 +3253,53 @@ dec_hashsign(Value) ->
     [HashSign] = decode_sign_alg(?TLS_1_2, Value),
     HashSign.
 
+maybe_dec_server_hybrid_share(x25519mlkem768, <<MLKem:1088/binary, X25519:32/binary>>) ->
+    %% Concatenation of an ML-KEM ciphertext returned from
+    %% encapsulation to the client's encapsulation key The size of the
+    %% server share is 1120 bytes (1088 bytes for the ML-KEM part and
+    %% 32 bytes for X25519).
+    %% Note exception algorithm should be in reveres order of name due to legacy reason
+    {MLKem, X25519};
+maybe_dec_server_hybrid_share(secp256r1mlkem768, <<Secp256r1:65/binary, MLKem:1088/binary>>) ->
+    %% Concatenation of the server's ephemeral secp256r1 share encoded
+    %% in the same way as the client share and an ML-KEM The size of
+    %% the server share is 1153 bytes (1088 bytes for the ML-KEM part
+    %% and 65 bytes for secp256r1).
+    {Secp256r1, MLKem};
+maybe_dec_server_hybrid_share(secp384r1mlkem1024, <<Secp384r1:97/binary, MLKem:1568/binary>>) ->
+    %% Concatenation of the server's ephemeral secp384r1 share encoded
+    %% in the same way as the client share and an ML-KEM ciphertext
+    %% returned from encapsulation to the client's encapsulation key
+    %% The size of the server share is 1665 bytes (1568 bytes for the
+    %% ML-KEM part and 97 bytes for secp384r1)
+    {Secp384r1, MLKem};
+maybe_dec_server_hybrid_share(_, Share) ->
+    %% Not hybrid
+    Share.
+
+maybe_dec_client_hybrid_share(x25519mlkem768, <<MLKem:1184/binary, X25519:32/binary>>) ->
+    %% Concatenation of the client's ML-KEM-768 encapsulation key and
+    %% the client's X25519 ephemeral share.  The size of the client share
+    %% is 1216 bytes (1184 bytes for the ML-KEM part and 32 bytes for
+    %% X25519).
+    %% Note exception algorithm should be in reveres order of name due to legacy reason
+    {MLKem, X25519};
+maybe_dec_client_hybrid_share(secp256r1mlkem768, <<Secp256r1:65/binary, MLKem:1184/binary>>) ->
+    %% Concatenation of the secp256r1 ephemeral share and ML-KEM-768
+    %% encapsulation key The size of the client share is 1249 bytes (65
+    %% bytes for the secp256r1 part and 1184 bytes for ML-KEM).  Ignore
+    %% unknown names (only host_name is supported)
+    {Secp256r1, MLKem};
+maybe_dec_client_hybrid_share(secp384r1mlkem1024, <<Secp384r1:97/binary, MLKem:1568/binary>>) ->
+     %% Concatenation of the secp384r1 ephemeral share and the
+     %% ML-KEM-1024 encapsulation key.  The size of the client share
+     %% is 1665 bytes (97 bytes for the secp384r1 and the 1568 for the
+     %% ML-KEM).
+    {Secp384r1, MLKem};
+maybe_dec_client_hybrid_share(_, Share) ->
+    %% Not hybrid
+    Share.
 
-%% Ignore unknown names (only host_name is supported)
 dec_sni(<<?BYTE(?SNI_NAMETYPE_HOST_NAME), ?UINT16(Len),
                 HostName:Len/binary, _/binary>>) ->
     #sni{hostname = binary_to_list(HostName)};
@@ -3266,12 +3325,13 @@ decode_client_shares(ClientShares) ->
 %%
 decode_client_shares(<<>>, Acc) ->
     lists:reverse(Acc);
-decode_client_shares(<<?UINT16(Group0),?UINT16(Len),KeyExchange:Len/binary,Rest/binary>>, Acc) ->
+decode_client_shares(<<?UINT16(Group0),?UINT16(Len),KeyExchange0:Len/binary,Rest/binary>>, Acc) ->
     case tls_v1:enum_to_group(Group0) of
         undefined ->
             %% Ignore key_share with unknown group
             decode_client_shares(Rest, Acc);
         Group ->
+            KeyExchange = maybe_dec_client_hybrid_share(Group, KeyExchange0),
             decode_client_shares(Rest, [#key_share_entry{
                                            group = Group,
                                            key_exchange= KeyExchange
diff --git a/lib/ssl/src/tls_client_connection_1_3.erl b/lib/ssl/src/tls_client_connection_1_3.erl
index c6f0c54dca..635dfb9210 100644
--- a/lib/ssl/src/tls_client_connection_1_3.erl
+++ b/lib/ssl/src/tls_client_connection_1_3.erl
@@ -602,6 +602,16 @@ maybe_generate_client_shares(_) ->
 %%--------------------------------------------------------------------
 %% Internal functions
 %%--------------------------------------------------------------------
+generate_client_shares(Groups) ->
+    KeyShareEntry =
+        fun (Group) ->
+                #key_share_entry{group = Group,
+                                 key_exchange = tls_handshake_1_3:generate_kex_keys(Group)}
+        end,
+    ClientShares = lists:map(KeyShareEntry, Groups),
+    #key_share_client_hello{client_shares = ClientShares}.
+
+
 handle_exlusive_1_3_hello_or_hello_retry_request(ServerHello, State0) ->
     case do_handle_exlusive_1_3_hello_or_hello_retry_request(ServerHello,
                                                              State0) of
@@ -665,7 +675,7 @@ do_handle_exlusive_1_3_hello_or_hello_retry_request(
         %% replace the original "key_share" extension with one containing only a
         %% new KeyShareEntry for the group indicated in the selected_group field
         %% of the triggering HelloRetryRequest.
-        ClientKeyShare = ssl_cipher:generate_client_shares([SelectedGroup]),
+        ClientKeyShare = generate_client_shares([SelectedGroup]),
         TicketData =
             tls_handshake_1_3:get_ticket_data(self(), SessionTickets, UseTicket),
         OcspNonce = maps:get(ocsp_nonce, StaplingState, undefined),
@@ -864,10 +874,14 @@ server_share(#key_share_hello_retry_request{selected_group = Share}) ->
 client_private_key(Group, ClientShares) ->
     case lists:keysearch(Group, 2, ClientShares) of
         {value, #key_share_entry{key_exchange =
-                                     ClientPrivateKey = #'ECPrivateKey'{}}} ->
-            ClientPrivateKey;
-        {value, #key_share_entry{key_exchange = {_, ClientPrivateKey}}} ->
-                ClientPrivateKey;
+                                     PrivateKey = #'ECPrivateKey'{}}} ->
+            PrivateKey;
+        {value, #key_share_entry{key_exchange = {#'ECPrivateKey'{} = PrivateKey1, {_, PrivateKey2}}}} ->
+            {PrivateKey1, PrivateKey2};
+        {value, #key_share_entry{key_exchange = {{_, PrivateKey1}, {_, PrivateKey2}}}} ->
+            {PrivateKey1, PrivateKey2};
+        {value, #key_share_entry{key_exchange = {_, PrivateKey}}} ->
+            PrivateKey;
         false ->
             no_suitable_key
     end.
diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl
index dd1872d75e..685e5ca5a6 100644
--- a/lib/ssl/src/tls_handshake_1_3.erl
+++ b/lib/ssl/src/tls_handshake_1_3.erl
@@ -82,6 +82,8 @@
          get_pre_shared_key/4,
          get_pre_shared_key_early_data/2,
          get_supported_groups/1,
+         generate_kex_keys/1,
+         hybrid_algs/1,
          calculate_traffic_secrets/1,
          calculate_client_early_traffic_secret/5,
          calculate_client_early_traffic_secret/2,
@@ -1096,6 +1098,39 @@ get_supported_groups(undefined = Groups) ->
 get_supported_groups(#supported_groups{supported_groups = Groups}) ->
     {ok, Groups}.
 
+generate_kex_keys(secp256r1) ->
+    public_key:generate_key({namedCurve, secp256r1});
+generate_kex_keys(secp384r1) ->
+    public_key:generate_key({namedCurve, secp384r1});
+generate_kex_keys(secp521r1) ->
+    public_key:generate_key({namedCurve, secp521r1});
+generate_kex_keys(x25519) ->
+    crypto:generate_key(ecdh, x25519);
+generate_kex_keys(x448) ->
+    crypto:generate_key(ecdh, x448);
+generate_kex_keys(MLKem) when MLKem == mlkem512;
+                              MLKem == mlkem768;
+                              MLKem == mlkem1024 ->
+    crypto:generate_key(MLKem, []);
+generate_kex_keys(x25519mlkem768 = Group)->
+    %% Note exception algorithm should be in reveres order of name due to legacy reason
+    {Curve, MLKem} = hybrid_algs(Group),
+    {crypto:generate_key(MLKem, []), crypto:generate_key(ecdh, Curve)};
+generate_kex_keys(Group) when Group == secp256r1mlkem768;
+                              Group == secp384r1mlkem1024 ->
+    {Curve, MLKem} = hybrid_algs(Group),
+    {public_key:generate_key({namedCurve, Curve}), 
+     crypto:generate_key(MLKem, [])};
+generate_kex_keys(FFDHE) ->
+    public_key:generate_key(ssl_dh_groups:dh_params(FFDHE)).
+
+hybrid_algs(x25519mlkem768)->
+    {x25519, mlkem768};
+hybrid_algs(secp256r1mlkem768) ->
+    {secp256r1, mlkem768};
+hybrid_algs(secp384r1mlkem1024) ->
+    {secp384r1, mlkem1024}.
+
 choose_psk(undefined, _) ->
     undefined;
 choose_psk([], _) ->
@@ -1163,8 +1198,32 @@ calculate_shared_secret(OthersKey, MyKey = #'ECPrivateKey'{}, _Group)
     Point = #'ECPoint'{point = OthersKey},
     public_key:compute_key(Point, MyKey).
 
+mlkem_calculate_shared_secret(client, x25519mlkem768, 
+                              {CipherText, OthersKey}, {MLKemKey, EDKey}) ->
+    MLKem = crypto:decapsulate_key(mlkem768, MLKemKey, CipherText),
+    X25519 = calculate_shared_secret(OthersKey, EDKey, x25519),
+    <<MLKem/binary, X25519/binary>>;
+mlkem_calculate_shared_secret(client, secp256r1mlkem768,
+                              {OthersKey, CipherText}, {ECkey, MLKemKey}) ->
+    MLKem = crypto:decapsulate_key(mlkem768, MLKemKey, CipherText),
+    EC = calculate_shared_secret(OthersKey, ECkey, secp256r1),
+    <<EC/binary, MLKem/binary>>;
+mlkem_calculate_shared_secret(client, secp384r1mlkem1024,
+                              {OthersKey, CipherText}, {ECkey, MLKemKey}) ->
+    MLKem = crypto:decapsulate_key(mlkem1024, MLKemKey, CipherText),
+    EC = calculate_shared_secret(OthersKey, ECkey, secp384r1),
+    <<EC/binary, MLKem/binary>>;
 mlkem_calculate_shared_secret(client, Group, CipherText, PrivKey) ->
     crypto:decapsulate_key(Group, PrivKey, CipherText);
+mlkem_calculate_shared_secret(server, x25519mlkem768, {_, OthersKey}, {Secret, EdKey}) ->
+    EDSecret = calculate_shared_secret(OthersKey, EdKey, x25519),
+    <<Secret/binary, EDSecret/binary>>;
+mlkem_calculate_shared_secret(server, secp256r1mlkem768, {OthersKey, _}, {EcKey, Secret}) ->
+     ECSecret = calculate_shared_secret(OthersKey, EcKey, secp256r1),
+    <<ECSecret/binary, Secret/binary>>;
+mlkem_calculate_shared_secret(server, secp384r1mlkem1024, {OthersKey, _}, {EcKey, Secret}) ->
+     ECSecret = calculate_shared_secret(OthersKey, EcKey, secp384r1),
+    <<ECSecret/binary, Secret/binary>>;
 mlkem_calculate_shared_secret(server, _, _, Secret) ->
     Secret.
 
@@ -2047,7 +2106,10 @@ plausible_missing_chain(_,Plausible,_,_,_) ->
 
 is_mlkem(Group) when Group == mlkem512;
                      Group == mlkem768;
-                     Group == mlkem1024 ->
+                     Group == mlkem1024;
+                     Group == x25519mlkem768;
+                     Group == secp384r1mlkem1024;
+                     Group == secp256r1mlkem768 ->
     true;
 is_mlkem(_) ->
     false.
diff --git a/lib/ssl/src/tls_handshake_1_3.hrl b/lib/ssl/src/tls_handshake_1_3.hrl
index 2469b895e4..df942d24f4 100644
--- a/lib/ssl/src/tls_handshake_1_3.hrl
+++ b/lib/ssl/src/tls_handshake_1_3.hrl
@@ -185,6 +185,11 @@
 -define(MLKEM768, 16#0201).
 -define(MLKEM1024, 16#0202).
 
+%% ML-KEM hybrids
+-define(X25519MLKEM768, 16#11EC).
+-define(SECP256R1MLKEM768, 16#11EB).
+-define(SECP384R1MLKEM1024, 16#11ED).
+
 %% RFC 8446 Finite Field Groups (DHE)
 -define(FFDHE2048, 16#0100).
 -define(FFDHE3072, 16#0101).
diff --git a/lib/ssl/src/tls_server_connection_1_3.erl b/lib/ssl/src/tls_server_connection_1_3.erl
index bf63c94f3e..308afee67e 100644
--- a/lib/ssl/src/tls_server_connection_1_3.erl
+++ b/lib/ssl/src/tls_server_connection_1_3.erl
@@ -763,24 +763,39 @@ default_or_fallback({fallback, _}, #session{} = Default) ->
 default_or_fallback(Default, _) ->
     Default.
 
-is_mlkem(Group) when Group == mlkem512;
-                     Group == mlkem768;
-                     Group == mlkem1024 ->
-    true;
-is_mlkem(_) ->
-    false.
-
-generate_server_share(Group, OtherPubKey) ->
-    case is_mlkem(Group) of
-        true ->
-            {Secret, CipherText} = crypto:encapsulate_key(Group, OtherPubKey),
-            #key_share_server_hello{server_share = #key_share_entry{
-                                                      group = Group,
-                                                      key_exchange = {CipherText, Secret}
-                                                     }};
-        false ->
-            ssl_cipher:generate_server_share(Group)
-    end.
+generate_server_share(Group, OtherPubKey) when Group == mlkem512;
+                                               Group == mlkem768;
+                                               Group == mlkem1024 -> 
+    {Secret, CipherText} = crypto:encapsulate_key(Group, OtherPubKey),
+    #key_share_server_hello{server_share = #key_share_entry{
+                                              group = Group,
+                                              key_exchange = {CipherText, Secret}
+                                             }};
+generate_server_share(x25519mlkem768 = Group, {OtherPubKey, _}) ->
+    %% Note exception algorithm should be in reveres order of name due to legacy reason
+    {Curve, MlKem} = tls_handshake_1_3:hybrid_algs(Group),
+    {Secret, CipherText} = crypto:encapsulate_key(MlKem, OtherPubKey),
+    Keys = tls_handshake_1_3:generate_kex_keys(Curve),
+    #key_share_server_hello{server_share = #key_share_entry{
+                                              group = Group,
+                                              key_exchange = {{CipherText, Secret}, Keys}
+                                             }};
+generate_server_share(Group, {_, OtherPubKey}) when Group == secp256r1mlkem768;
+                                                    Group == secp384r1mlkem1024 ->
+    {Curve, MlKem} = tls_handshake_1_3:hybrid_algs(Group),
+    {Secret, CipherText} = crypto:encapsulate_key(MlKem, OtherPubKey),
+    Keys = tls_handshake_1_3:generate_kex_keys(Curve),
+    #key_share_server_hello{server_share = #key_share_entry{
+                                              group = Group,
+                                              key_exchange = {Keys, {CipherText, Secret}}
+                                             }};
+generate_server_share(Group, _) ->
+    Keys = tls_handshake_1_3:generate_kex_keys(Group),
+    #key_share_server_hello{
+       server_share = #key_share_entry{
+                         group = Group,
+                         key_exchange = Keys
+                        }}.
 
 select_server_private_key(#key_share_server_hello{server_share = ServerShare}) ->
     select_private_key(ServerShare).
@@ -788,6 +803,15 @@ select_server_private_key(#key_share_server_hello{server_share = ServerShare}) -
 select_private_key(#key_share_entry{
                    key_exchange = #'ECPrivateKey'{} = PrivateKey}) ->
     PrivateKey;
+select_private_key(#key_share_entry{
+                      key_exchange =
+                          {#'ECPrivateKey'{} = PrivateKey1, {_, PrivateKey2}}}) ->
+    {PrivateKey1, PrivateKey2};
+
+select_private_key(#key_share_entry{
+                      key_exchange =
+                          {{_, PrivateKey1}, {_, PrivateKey2}}}) ->
+    {PrivateKey1, PrivateKey2};
 select_private_key(#key_share_entry{
                       key_exchange =
                           {_, PrivateKey}}) ->
diff --git a/lib/ssl/src/tls_v1.erl b/lib/ssl/src/tls_v1.erl
index d1d32b40f2..34c483556e 100644
--- a/lib/ssl/src/tls_v1.erl
+++ b/lib/ssl/src/tls_v1.erl
@@ -1230,6 +1230,9 @@ groups(all) ->
      mlkem512,
      mlkem768,
      mlkem1024,
+     x25519mlkem768,
+     secp384r1mlkem1024,
+     secp256r1mlkem768,
      ffdhe2048,
      ffdhe3072,
      ffdhe4096,
@@ -1246,11 +1249,25 @@ groups(default) ->
      brainpoolP256r1tls13,
      mlkem512,
      mlkem768,
-     mlkem1024
+     mlkem1024,
+     x25519mlkem768,
+     secp384r1mlkem1024,
+     secp256r1mlkem768
     ];
 groups(TLSGroups) when is_list(TLSGroups) ->
     CryptoGroups = crypto_supported_groups(),
-    lists:filter(fun(Group) -> proplists:get_bool(maybe_group_to_curve(Group), CryptoGroups) end, TLSGroups).
+    lists:filter(fun(x25519mlkem768) ->
+                         proplists:get_bool(mlkem768, CryptoGroups)
+                             andalso proplists:get_bool(x25519, CryptoGroups);
+                     (secp256r1mlkem768) ->
+                         proplists:get_bool(mlkem768, CryptoGroups)
+                             andalso proplists:get_bool(secp256r1, CryptoGroups);
+                    (secp384r1mlkem1024) ->
+                         proplists:get_bool(mlkem1024, CryptoGroups)
+                             andalso proplists:get_bool(secp384r1, CryptoGroups);
+                    (Group) ->
+                         proplists:get_bool(maybe_group_to_curve(Group), CryptoGroups)
+                 end, TLSGroups).
 
 default_groups() ->
     TLSGroups = groups(default),
@@ -1271,6 +1288,9 @@ group_to_enum(brainpoolP512r1tls13) -> ?BRAINPOOLP512R1TLS13;
 group_to_enum(mlkem512)  -> ?MLKEM512;
 group_to_enum(mlkem768)  -> ?MLKEM768;
 group_to_enum(mlkem1024) -> ?MLKEM1024;
+group_to_enum(x25519mlkem768)  -> ?X25519MLKEM768;
+group_to_enum(secp256r1mlkem768) -> ?SECP256R1MLKEM768;
+group_to_enum(secp384r1mlkem1024)  -> ?SECP384R1MLKEM1024;
 group_to_enum(ffdhe2048) -> ?FFDHE2048;
 group_to_enum(ffdhe3072) -> ?FFDHE3072;
 group_to_enum(ffdhe4096) -> ?FFDHE4096;
@@ -1288,6 +1308,9 @@ enum_to_group(?BRAINPOOLP512R1TLS13) -> brainpoolP512r1tls13;
 enum_to_group(?MLKEM512)  -> mlkem512;
 enum_to_group(?MLKEM768)  -> mlkem768;
 enum_to_group(?MLKEM1024) -> mlkem1024;
+enum_to_group(?X25519MLKEM768)     -> x25519mlkem768;
+enum_to_group(?SECP256R1MLKEM768)  -> secp256r1mlkem768;
+enum_to_group(?SECP384R1MLKEM1024) -> secp384r1mlkem1024;
 enum_to_group(?FFDHE2048) -> ffdhe2048;
 enum_to_group(?FFDHE3072) -> ffdhe3072;
 enum_to_group(?FFDHE4096) -> ffdhe4096;
@@ -1295,7 +1318,6 @@ enum_to_group(?FFDHE6144) -> ffdhe6144;
 enum_to_group(?FFDHE8192) -> ffdhe8192;
 enum_to_group(_) -> undefined.
 
-
 %% 1-22 Deprecated in RFC 8422
 oid_to_enum(?sect163k1) -> 1;
 oid_to_enum(?sect163r1) -> 2;
diff --git a/lib/ssl/test/openssl_client_cert_SUITE.erl b/lib/ssl/test/openssl_client_cert_SUITE.erl
index 7fdd412b51..bbc7db7961 100644
--- a/lib/ssl/test/openssl_client_cert_SUITE.erl
+++ b/lib/ssl/test/openssl_client_cert_SUITE.erl
@@ -64,6 +64,8 @@
          custom_groups/1,
          mlkem_groups/0,
          mlkem_groups/1,
+         mlkem_hybrid_groups/0,
+         mlkem_hybrid_groups/1,
          hello_retry_client_auth/0,
          hello_retry_client_auth/1,
          hello_retry_client_auth_empty_cert_accepted/0,
@@ -145,6 +147,7 @@ tls_1_3_tests() ->
      hello_retry_request,
      custom_groups,
      mlkem_groups,
+     mlkem_hybrid_groups,
      hello_retry_client_auth,
      hello_retry_client_auth_empty_cert_accepted,
      hello_retry_client_auth_empty_cert_rejected
@@ -215,6 +218,8 @@ end_per_group(GroupName, Config) ->
 
 init_per_testcase(mlkem_groups, Config) ->
     ssl_cert_tests:support_kems(Config);
+init_per_testcase(mlkem_hybrid_groups, Config) ->
+   ssl_cert_tests:support_kems(Config);
 init_per_testcase(TestCase, Config) when
       TestCase == client_auth_empty_cert_accepted;
       TestCase == client_auth_empty_cert_rejected ->
@@ -383,6 +388,10 @@ mlkem_groups() ->
     ssl_cert_tests:mlkem_groups().
 mlkem_groups(Config) ->
     ssl_cert_tests:mlkem_groups(Config).
+mlkem_hybrid_groups() ->
+    ssl_cert_tests:mlkem_hybrid_groups().
+mlkem_hybrid_groups(Config) ->
+    ssl_cert_tests:mlkem_hybrid_groups(Config).
 unsupported_sign_algo_cert_client_auth() ->
  ssl_cert_tests:unsupported_sign_algo_cert_client_auth().
 unsupported_sign_algo_cert_client_auth(Config) ->
diff --git a/lib/ssl/test/openssl_server_cert_SUITE.erl b/lib/ssl/test/openssl_server_cert_SUITE.erl
index ea01a53776..29f66ae387 100644
--- a/lib/ssl/test/openssl_server_cert_SUITE.erl
+++ b/lib/ssl/test/openssl_server_cert_SUITE.erl
@@ -61,6 +61,8 @@
          custom_groups/1,
          mlkem_groups/0,
          mlkem_groups/1,
+         mlkem_hybrid_groups/0,
+         mlkem_hybrid_groups/1,
          hello_retry_client_auth/0,
          hello_retry_client_auth/1,
          hello_retry_client_auth_empty_cert_accepted/0,
@@ -138,6 +140,7 @@ tls_1_3_tests() ->
      hello_retry_request,
      custom_groups,
      mlkem_groups,
+     mlkem_hybrid_groups,
      hello_retry_client_auth,
      hello_retry_client_auth_empty_cert_accepted,
      hello_retry_client_auth_empty_cert_rejected
@@ -205,6 +208,8 @@ end_per_group(GroupName, Config) ->
 
 init_per_testcase(mlkem_groups, Config) ->
     ssl_cert_tests:support_kems(Config);
+init_per_testcase(mlkem_hybrid_groups, Config) ->
+    ssl_cert_tests:support_kems(Config);
 init_per_testcase(_TestCase, Config) ->
     ssl_test_lib:ct_log_supported_protocol_versions(Config),
     ct:timetrap({seconds, 30}),
@@ -266,6 +271,10 @@ mlkem_groups() ->
     ssl_cert_tests:mlkem_groups().
 mlkem_groups(Config) ->
     ssl_cert_tests:mlkem_groups(Config).
+mlkem_hybrid_groups() ->
+    ssl_cert_tests:mlkem_hybrid_groups().
+mlkem_hybrid_groups(Config) ->
+    ssl_cert_tests:mlkem_hybrid_groups(Config).
 unsupported_sign_algo_cert_client_auth() ->
     ssl_cert_tests:unsupported_sign_algo_cert_client_auth().
 unsupported_sign_algo_cert_client_auth(Config) ->
diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl
index a4be6e53f5..46a031f021 100644
--- a/lib/ssl/test/ssl_cert_SUITE.erl
+++ b/lib/ssl/test/ssl_cert_SUITE.erl
@@ -129,6 +129,8 @@
          custom_groups/1,
          mlkem_groups/0,
          mlkem_groups/1,
+         mlkem_hybrid_groups/0,
+         mlkem_hybrid_groups/1,
          hello_retry_client_auth/0,
          hello_retry_client_auth/1,
          hello_retry_client_auth_empty_cert_accepted/0,
@@ -216,6 +218,7 @@ tls_1_3_tests() ->
      hello_retry_request,
      custom_groups,
      mlkem_groups,
+     mlkem_hybrid_groups,
      client_auth_no_suitable_chain,
      cert_auth_in_first_ca,
      hello_retry_client_auth,
@@ -345,6 +348,8 @@ end_per_group(GroupName, Config) ->
 
 init_per_testcase(mlkem_groups, Config) ->
    ssl_cert_tests:support_kems(Config);
+init_per_testcase(mlkem_hybrid_groups, Config) ->
+   ssl_cert_tests:support_kems(Config);
 init_per_testcase(signature_algorithms_bad_curve_secp256r1, Config) ->
     init_ecdsa_opts(Config, secp256r1);
 init_per_testcase(signature_algorithms_bad_curve_secp384r1, Config) ->
@@ -1216,7 +1221,7 @@ custom_groups(Config) ->
 
 %%--------------------------------------------------------------------
 mlkem_groups() ->
-    [{doc,"Test that ssl server can select a common group for key-exchange"}].
+    [{doc,"Test that ssl server can select a common mlkem group for key-exchange"}].
 
 mlkem_groups(Config) ->
     ClientOpts0 = ssl_test_lib:ssl_options(client_cert_opts, Config),
@@ -1226,6 +1231,17 @@ mlkem_groups(Config) ->
     mlkem_kex(mlkem768, ClientOpts0, ServerOpts0, Config),
     mlkem_kex(mlkem1024, ClientOpts0, ServerOpts0, Config).
 
+mlkem_hybrid_groups() ->
+    [{doc,"Test that ssl server can select a common mlkem-hybrid group for key-exchange"}].
+
+mlkem_hybrid_groups(Config) ->
+    ClientOpts0 = ssl_test_lib:ssl_options(client_cert_opts, Config),
+    ServerOpts0 = ssl_test_lib:ssl_options(server_cert_opts, Config),
+
+    mlkem_kex(x25519mlkem768, ClientOpts0, ServerOpts0, Config),
+    mlkem_kex(secp256r1mlkem768, ClientOpts0, ServerOpts0, Config),
+    mlkem_kex(secp384r1mlkem1024, ClientOpts0, ServerOpts0, Config).
+
 mlkem_kex(MLKem, ClientOpts0, ServerOpts0, Config) ->
     %% Set versions
     ServerOpts = [{versions, ['tlsv1.3']},
diff --git a/lib/ssl/test/ssl_cert_tests.erl b/lib/ssl/test/ssl_cert_tests.erl
index 6d7857a591..54ee261e2d 100644
--- a/lib/ssl/test/ssl_cert_tests.erl
+++ b/lib/ssl/test/ssl_cert_tests.erl
@@ -75,6 +75,8 @@
          custom_groups/1,
          mlkem_groups/0,
          mlkem_groups/1,
+         mlkem_hybrid_groups/0,
+         mlkem_hybrid_groups/1,
          hello_retry_client_auth/0,
          hello_retry_client_auth/1,
          hello_retry_client_auth_empty_cert_accepted/0,
@@ -653,6 +655,14 @@ mlkem_groups(Config) ->
     test_mlkem(Config, mlkem768),
     test_mlkem(Config, mlkem1024).
 
+mlkem_hybrid_groups() ->
+    [{doc,"Test that ssl server can select a common mlkem hybrid group for key-exchange"}].
+
+mlkem_hybrid_groups(Config) ->
+    test_mlkem(Config, x25519mlkem768),
+    test_mlkem(Config, secp256r1mlkem768),
+    test_mlkem(Config, secp384r1mlkem1024).
+
 test_mlkem(Config, MLKemGroup) ->
     ClientOpts0 = ssl_test_lib:ssl_options(client_cert_opts, Config),
     ServerOpts0 = ssl_test_lib:ssl_options(server_cert_opts, Config),
@@ -831,9 +841,9 @@ group_config_mlkem(Config, ServerOpts, ClientOpts, Group) ->
         case proplists:get_value(client_type, Config) of
             erlang ->
                 {[{groups, openssl_mlkem(Group)} | ServerOpts],
-                 [{supported_groups, [Group]} | ClientOpts]};
+                 [{supported_groups, supported_groups(Group)} | ClientOpts]};
             openssl ->
-                {[{supported_groups, [Group]} | ServerOpts],
+                {[{supported_groups, supported_groups(Group)} | ServerOpts],
                  [{groups, openssl_mlkem(Group)} | ClientOpts]}
         end.
 
@@ -842,7 +852,18 @@ openssl_mlkem(mlkem512) ->
 openssl_mlkem(mlkem768) ->
     "MLKEM768";
 openssl_mlkem(mlkem1024) ->
-    "MLKEM1024".
+    "MLKEM1024";
+openssl_mlkem(x25519mlkem768) ->
+    "X25519MLKEM768";
+openssl_mlkem(secp256r1mlkem768) ->
+    "SecP256r1MLKEM768";
+openssl_mlkem(secp384r1mlkem1024) ->
+    "SecP384r1MLKEM1024".
+
+supported_groups(Group) ->
+    [Group].
+
+
 
 choose_custom_key(#'RSAPrivateKey'{} = Key, Version)
   when (Version == 'dtlsv1') or (Version == 'tlsv1') or (Version == 'tlsv1.1') ->
-- 
2.51.0

openSUSE Build Service is sponsored by