Skip to content

Commit a0a3293

Browse files
committed
ssl: Add hybird MLKEM algorithms
1 parent da8fa24 commit a0a3293

11 files changed

+288
-78
lines changed

lib/ssl/src/ssl_cipher.erl

Lines changed: 1 addition & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -72,9 +72,7 @@
7272
bulk_cipher_algorithm/1]).
7373

7474
%% RFC 8446 TLS 1.3
75-
-export([generate_client_shares/1,
76-
generate_server_share/1,
77-
add_zero_padding/2,
75+
-export([add_zero_padding/2,
7876
encrypt_ticket/3,
7977
decrypt_ticket/3,
8078
encrypt_data/4,
@@ -1220,37 +1218,6 @@ filter_keyuse_suites(Use, KeyUse, CipherSuits, Suites) ->
12201218
CipherSuits -- Suites
12211219
end.
12221220

1223-
generate_server_share(Group) ->
1224-
Key = generate_key_exchange(Group),
1225-
#key_share_server_hello{
1226-
server_share = #key_share_entry{
1227-
group = Group,
1228-
key_exchange = Key
1229-
}}.
1230-
1231-
generate_client_shares(Groups) ->
1232-
KeyShareEntry = fun (Group) ->
1233-
#key_share_entry{group = Group, key_exchange = generate_key_exchange(Group)}
1234-
end,
1235-
ClientShares = lists:map(KeyShareEntry, Groups),
1236-
#key_share_client_hello{client_shares = ClientShares}.
1237-
1238-
generate_key_exchange(secp256r1) ->
1239-
public_key:generate_key({namedCurve, secp256r1});
1240-
generate_key_exchange(secp384r1) ->
1241-
public_key:generate_key({namedCurve, secp384r1});
1242-
generate_key_exchange(secp521r1) ->
1243-
public_key:generate_key({namedCurve, secp521r1});
1244-
generate_key_exchange(x25519) ->
1245-
crypto:generate_key(ecdh, x25519);
1246-
generate_key_exchange(x448) ->
1247-
crypto:generate_key(ecdh, x448);
1248-
generate_key_exchange(MLKem) when MLKem == mlkem512;
1249-
MLKem == mlkem768;
1250-
MLKem == mlkem1024 ->
1251-
crypto:generate_key(MLKem, []);
1252-
generate_key_exchange(FFDHE) ->
1253-
public_key:generate_key(ssl_dh_groups:dh_params(FFDHE)).
12541221

12551222

12561223
%% TODO: Move this functionality to crypto!

lib/ssl/src/ssl_handshake.erl

Lines changed: 73 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1474,21 +1474,35 @@ add_selected_version(Extensions) ->
14741474
Extensions#{server_hello_selected_version => SupportedVersions}.
14751475

14761476
kse_remove_private_key(#key_share_entry{
1477-
group = Group,
1478-
key_exchange =
1479-
#'ECPrivateKey'{publicKey = PublicKey}}) ->
1477+
group = Group,
1478+
key_exchange =
1479+
#'ECPrivateKey'{publicKey = PublicKey}}) ->
14801480
#key_share_entry{
14811481
group = Group,
14821482
key_exchange = PublicKey};
14831483
kse_remove_private_key(#key_share_entry{
1484-
group = Group,
1485-
key_exchange =
1486-
{PublicKey, _}}) ->
1484+
group = Group,
1485+
key_exchange =
1486+
{#'ECPrivateKey'{publicKey = PublicKey1},
1487+
{PublicKey2, _}}}) ->
1488+
#key_share_entry{
1489+
group = Group,
1490+
key_exchange = <<PublicKey1/binary, PublicKey2/binary>>};
1491+
kse_remove_private_key(#key_share_entry{
1492+
group = Group,
1493+
key_exchange =
1494+
{{PublicKey1, _}, {PublicKey2, _}}}) ->
1495+
#key_share_entry{
1496+
group = Group,
1497+
key_exchange = <<PublicKey1/binary, PublicKey2/binary>>};
1498+
kse_remove_private_key(#key_share_entry{
1499+
group = Group,
1500+
key_exchange =
1501+
{PublicKey, _}}) ->
14871502
#key_share_entry{
14881503
group = Group,
14891504
key_exchange = PublicKey}.
14901505

1491-
14921506
signature_algs_ext(undefined) ->
14931507
undefined;
14941508
signature_algs_ext(SignatureSchemes0) ->
@@ -2665,7 +2679,6 @@ encode_versions(Versions) ->
26652679

26662680
encode_client_shares(ClientShares) ->
26672681
<< << (encode_key_share_entry(KeyShareEntry0))/binary >> || KeyShareEntry0 <- ClientShares >>.
2668-
26692682
encode_key_share_entry(#key_share_entry{group = Group,
26702683
key_exchange = KeyExchange}) ->
26712684
Len = byte_size(KeyExchange),
@@ -3057,13 +3070,15 @@ decode_extensions(<<?UINT16(?KEY_SHARE_EXT), ?UINT16(Len),
30573070
decode_extensions(<<?UINT16(?KEY_SHARE_EXT), ?UINT16(Len),
30583071
ExtData:Len/binary, Rest/binary>>,
30593072
Version, MessageType = server_hello, Acc) ->
3060-
<<?UINT16(Group),?UINT16(KeyLen),KeyExchange:KeyLen/binary>> = ExtData,
3073+
<<?UINT16(EnumGroup),?UINT16(KeyLen),KeyExchange0:KeyLen/binary>> = ExtData,
3074+
Group = tls_v1:enum_to_group(EnumGroup),
3075+
KeyExchange = maybe_dec_server_hybrid_share(Group, KeyExchange0),
30613076
decode_extensions(Rest, Version, MessageType,
30623077
Acc#{key_share =>
30633078
#key_share_server_hello{
30643079
server_share =
30653080
#key_share_entry{
3066-
group = tls_v1:enum_to_group(Group),
3081+
group = Group,
30673082
key_exchange = KeyExchange}}});
30683083

30693084
decode_extensions(<<?UINT16(?KEY_SHARE_EXT), ?UINT16(Len),
@@ -3204,8 +3219,53 @@ dec_hashsign(Value) ->
32043219
[HashSign] = decode_sign_alg(?TLS_1_2, Value),
32053220
HashSign.
32063221

3222+
maybe_dec_server_hybrid_share(x25519mlkem768, <<MLKem:1088/binary, X25519:32/binary>>) ->
3223+
%% Concatenation of an ML-KEM ciphertext returned from
3224+
%% encapsulation to the client's encapsulation key The size of the
3225+
%% server share is 1120 bytes (1088 bytes for the ML-KEM part and
3226+
%% 32 bytes for X25519).
3227+
%% Note exception algorithm should be in reveres order of name due to legacy reason
3228+
{MLKem, X25519};
3229+
maybe_dec_server_hybrid_share(secp256r1mlkem768, <<Secp256r1:65/binary, MLKem:1088/binary>>) ->
3230+
%% Concatenation of the server's ephemeral secp256r1 share encoded
3231+
%% in the same way as the client share and an ML-KEM The size of
3232+
%% the server share is 1153 bytes (1088 bytes for the ML-KEM part
3233+
%% and 65 bytes for secp256r1).
3234+
{Secp256r1, MLKem};
3235+
maybe_dec_server_hybrid_share(secp384r1mlkem1024, <<Secp384r1:97/binary, MLKem:1568/binary>>) ->
3236+
%% Concatenation of the server's ephemeral secp384r1 share encoded
3237+
%% in the same way as the client share and an ML-KEM ciphertext
3238+
%% returned from encapsulation to the client's encapsulation key
3239+
%% The size of the server share is 1665 bytes (1568 bytes for the
3240+
%% ML-KEM part and 97 bytes for secp384r1)
3241+
{Secp384r1, MLKem};
3242+
maybe_dec_server_hybrid_share(_, Share) ->
3243+
%% Not hybrid
3244+
Share.
3245+
3246+
maybe_dec_client_hybrid_share(x25519mlkem768, <<MLKem:1184/binary, X25519:32/binary>>) ->
3247+
%% Concatenation of the client's ML-KEM-768 encapsulation key and
3248+
%% the client's X25519 ephemeral share. The size of the client share
3249+
%% is 1216 bytes (1184 bytes for the ML-KEM part and 32 bytes for
3250+
%% X25519).
3251+
%% Note exception algorithm should be in reveres order of name due to legacy reason
3252+
{MLKem, X25519};
3253+
maybe_dec_client_hybrid_share(secp256r1mlkem768, <<Secp256r1:65/binary, MLKem:1184/binary>>) ->
3254+
%% Concatenation of the secp256r1 ephemeral share and ML-KEM-768
3255+
%% encapsulation key The size of the client share is 1249 bytes (65
3256+
%% bytes for the secp256r1 part and 1184 bytes for ML-KEM). Ignore
3257+
%% unknown names (only host_name is supported)
3258+
{Secp256r1, MLKem};
3259+
maybe_dec_client_hybrid_share(secp384r1mlkem1024, <<Secp384r1:97/binary, MLKem:1568/binary>>) ->
3260+
%% Concatenation of the secp384r1 ephemeral share and the
3261+
%% ML-KEM-1024 encapsulation key. The size of the client share
3262+
%% is 1665 bytes (97 bytes for the secp384r1 and the 1568 for the
3263+
%% ML-KEM).
3264+
{Secp384r1, MLKem};
3265+
maybe_dec_client_hybrid_share(_, Share) ->
3266+
%% Not hybrid
3267+
Share.
32073268

3208-
%% Ignore unknown names (only host_name is supported)
32093269
dec_sni(<<?BYTE(?SNI_NAMETYPE_HOST_NAME), ?UINT16(Len),
32103270
HostName:Len/binary, _/binary>>) ->
32113271
#sni{hostname = binary_to_list(HostName)};
@@ -3231,12 +3291,13 @@ decode_client_shares(ClientShares) ->
32313291
%%
32323292
decode_client_shares(<<>>, Acc) ->
32333293
lists:reverse(Acc);
3234-
decode_client_shares(<<?UINT16(Group0),?UINT16(Len),KeyExchange:Len/binary,Rest/binary>>, Acc) ->
3294+
decode_client_shares(<<?UINT16(Group0),?UINT16(Len),KeyExchange0:Len/binary,Rest/binary>>, Acc) ->
32353295
case tls_v1:enum_to_group(Group0) of
32363296
undefined ->
32373297
%% Ignore key_share with unknown group
32383298
decode_client_shares(Rest, Acc);
32393299
Group ->
3300+
KeyExchange = maybe_dec_client_hybrid_share(Group, KeyExchange0),
32403301
decode_client_shares(Rest, [#key_share_entry{
32413302
group = Group,
32423303
key_exchange= KeyExchange

lib/ssl/src/tls_client_connection_1_3.erl

Lines changed: 20 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -595,13 +595,23 @@ maybe_resumption(_) ->
595595
maybe_generate_client_shares(#{versions := [?TLS_1_3|_],
596596
psk_groups := Groups}) ->
597597
%% Default will be the list of only the most proffered supported group
598-
ssl_cipher:generate_client_shares(Groups);
598+
generate_client_shares(Groups);
599599
maybe_generate_client_shares(_) ->
600600
undefined.
601601

602602
%%--------------------------------------------------------------------
603603
%% Internal functions
604604
%%--------------------------------------------------------------------
605+
generate_client_shares(Groups) ->
606+
KeyShareEntry =
607+
fun (Group) ->
608+
#key_share_entry{group = Group,
609+
key_exchange = tls_handshake_1_3:generate_kex_keys(Group)}
610+
end,
611+
ClientShares = lists:map(KeyShareEntry, Groups),
612+
#key_share_client_hello{client_shares = ClientShares}.
613+
614+
605615
handle_exlusive_1_3_hello_or_hello_retry_request(ServerHello, State0) ->
606616
case do_handle_exlusive_1_3_hello_or_hello_retry_request(ServerHello,
607617
State0) of
@@ -665,7 +675,7 @@ do_handle_exlusive_1_3_hello_or_hello_retry_request(
665675
%% replace the original "key_share" extension with one containing only a
666676
%% new KeyShareEntry for the group indicated in the selected_group field
667677
%% of the triggering HelloRetryRequest.
668-
ClientKeyShare = ssl_cipher:generate_client_shares([SelectedGroup]),
678+
ClientKeyShare = generate_client_shares([SelectedGroup]),
669679
TicketData =
670680
tls_handshake_1_3:get_ticket_data(self(), SessionTickets, UseTicket),
671681
OcspNonce = maps:get(ocsp_nonce, StaplingState, undefined),
@@ -864,10 +874,14 @@ server_share(#key_share_hello_retry_request{selected_group = Share}) ->
864874
client_private_key(Group, ClientShares) ->
865875
case lists:keysearch(Group, 2, ClientShares) of
866876
{value, #key_share_entry{key_exchange =
867-
ClientPrivateKey = #'ECPrivateKey'{}}} ->
868-
ClientPrivateKey;
869-
{value, #key_share_entry{key_exchange = {_, ClientPrivateKey}}} ->
870-
ClientPrivateKey;
877+
PrivateKey = #'ECPrivateKey'{}}} ->
878+
PrivateKey;
879+
{value, #key_share_entry{key_exchange = {#'ECPrivateKey'{} = PrivateKey1, {_, PrivateKey2}}}} ->
880+
{PrivateKey1, PrivateKey2};
881+
{value, #key_share_entry{key_exchange = {{_, PrivateKey1}, {_, PrivateKey2}}}} ->
882+
{PrivateKey1, PrivateKey2};
883+
{value, #key_share_entry{key_exchange = {_, PrivateKey}}} ->
884+
PrivateKey;
871885
false ->
872886
no_suitable_key
873887
end.

lib/ssl/src/tls_handshake_1_3.erl

Lines changed: 63 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -82,6 +82,8 @@
8282
get_pre_shared_key/4,
8383
get_pre_shared_key_early_data/2,
8484
get_supported_groups/1,
85+
generate_kex_keys/1,
86+
hybrid_algs/1,
8587
calculate_traffic_secrets/1,
8688
calculate_client_early_traffic_secret/5,
8789
calculate_client_early_traffic_secret/2,
@@ -1096,6 +1098,39 @@ get_supported_groups(undefined = Groups) ->
10961098
get_supported_groups(#supported_groups{supported_groups = Groups}) ->
10971099
{ok, Groups}.
10981100

1101+
generate_kex_keys(secp256r1) ->
1102+
public_key:generate_key({namedCurve, secp256r1});
1103+
generate_kex_keys(secp384r1) ->
1104+
public_key:generate_key({namedCurve, secp384r1});
1105+
generate_kex_keys(secp521r1) ->
1106+
public_key:generate_key({namedCurve, secp521r1});
1107+
generate_kex_keys(x25519) ->
1108+
crypto:generate_key(ecdh, x25519);
1109+
generate_kex_keys(x448) ->
1110+
crypto:generate_key(ecdh, x448);
1111+
generate_kex_keys(MLKem) when MLKem == mlkem512;
1112+
MLKem == mlkem768;
1113+
MLKem == mlkem1024 ->
1114+
crypto:generate_key(MLKem, []);
1115+
generate_kex_keys(x25519mlkem768 = Group)->
1116+
%% Note exception algorithm should be in reveres order of name due to legacy reason
1117+
{Curve, MLKem} = hybrid_algs(Group),
1118+
{crypto:generate_key(MLKem, []), crypto:generate_key(ecdh, Curve)};
1119+
generate_kex_keys(Group) when Group == secp256r1mlkem768;
1120+
Group == secp384r1mlkem1024 ->
1121+
{Curve, MLKem} = hybrid_algs(Group),
1122+
{public_key:generate_key({namedCurve, Curve}),
1123+
crypto:generate_key(MLKem, [])};
1124+
generate_kex_keys(FFDHE) ->
1125+
public_key:generate_key(ssl_dh_groups:dh_params(FFDHE)).
1126+
1127+
hybrid_algs(x25519mlkem768)->
1128+
{x25519, mlkem768};
1129+
hybrid_algs(secp256r1mlkem768) ->
1130+
{secp256r1, mlkem768};
1131+
hybrid_algs(secp384r1mlkem1024) ->
1132+
{secp384r1, mlkem1024}.
1133+
10991134
choose_psk(undefined, _) ->
11001135
undefined;
11011136
choose_psk([], _) ->
@@ -1163,8 +1198,32 @@ calculate_shared_secret(OthersKey, MyKey = #'ECPrivateKey'{}, _Group)
11631198
Point = #'ECPoint'{point = OthersKey},
11641199
public_key:compute_key(Point, MyKey).
11651200

1201+
mlkem_calculate_shared_secret(client, x25519mlkem768,
1202+
{CipherText, OthersKey}, {MLKemKey, EDKey}) ->
1203+
MLKem = crypto:decapsulate_key(mlkem768, MLKemKey, CipherText),
1204+
X25519 = calculate_shared_secret(OthersKey, EDKey, x25519),
1205+
<<MLKem/binary, X25519/binary>>;
1206+
mlkem_calculate_shared_secret(client, secp256r1mlkem768,
1207+
{OthersKey, CipherText}, {ECkey, MLKemKey}) ->
1208+
MLKem = crypto:decapsulate_key(mlkem768, MLKemKey, CipherText),
1209+
EC = calculate_shared_secret(OthersKey, ECkey, secp256r1),
1210+
<<EC/binary, MLKem/binary>>;
1211+
mlkem_calculate_shared_secret(client, secp384r1mlkem1024,
1212+
{OthersKey, CipherText}, {ECkey, MLKemKey}) ->
1213+
MLKem = crypto:decapsulate_key(mlkem1024, MLKemKey, CipherText),
1214+
EC = calculate_shared_secret(OthersKey, ECkey, secp384r1),
1215+
<<EC/binary, MLKem/binary>>;
11661216
mlkem_calculate_shared_secret(client, Group, CipherText, PrivKey) ->
11671217
crypto:decapsulate_key(Group, PrivKey, CipherText);
1218+
mlkem_calculate_shared_secret(server, x25519mlkem768, {_, OthersKey}, {Secret, EdKey}) ->
1219+
EDSecret = calculate_shared_secret(OthersKey, EdKey, x25519),
1220+
<<Secret/binary, EDSecret/binary>>;
1221+
mlkem_calculate_shared_secret(server, secp256r1mlkem768, {OthersKey, _}, {EcKey, Secret}) ->
1222+
ECSecret = calculate_shared_secret(OthersKey, EcKey, secp256r1),
1223+
<<ECSecret/binary, Secret/binary>>;
1224+
mlkem_calculate_shared_secret(server, secp384r1mlkem1024, {OthersKey, _}, {EcKey, Secret}) ->
1225+
ECSecret = calculate_shared_secret(OthersKey, EcKey, secp384r1),
1226+
<<ECSecret/binary, Secret/binary>>;
11681227
mlkem_calculate_shared_secret(server, _, _, Secret) ->
11691228
Secret.
11701229

@@ -2047,7 +2106,10 @@ plausible_missing_chain(_,Plausible,_,_,_) ->
20472106

20482107
is_mlkem(Group) when Group == mlkem512;
20492108
Group == mlkem768;
2050-
Group == mlkem1024 ->
2109+
Group == mlkem1024;
2110+
Group == x25519mlkem768;
2111+
Group == secp384r1mlkem1024;
2112+
Group == secp256r1mlkem768 ->
20512113
true;
20522114
is_mlkem(_) ->
20532115
false.

lib/ssl/src/tls_handshake_1_3.hrl

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -185,6 +185,11 @@
185185
-define(MLKEM768, 16#0201).
186186
-define(MLKEM1024, 16#0202).
187187

188+
%% ML-KEM hybrids
189+
-define(X25519MLKEM768, 16#11EC).
190+
-define(SECP256R1MLKEM768, 16#11EB).
191+
-define(SECP384R1MLKEM1024, 16#11ED).
192+
188193
%% RFC 8446 Finite Field Groups (DHE)
189194
-define(FFDHE2048, 16#0100).
190195
-define(FFDHE3072, 16#0101).

0 commit comments

Comments
 (0)