Skip to content

Commit 3b38c74

Browse files
committed
Merge branch 'ingela/ssl/mlkem-hybrid/OTP-19767' into maint
* ingela/ssl/mlkem-hybrid/OTP-19767: ssl: Add hybird MLKEM algorithms ssl: Make key share groups configurable
2 parents 44ee0cc + 763f6fa commit 3b38c74

14 files changed

+330
-88
lines changed

lib/ssl/src/ssl.erl

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1380,6 +1380,11 @@ certificate signatures.
13801380
The following options are specific to the client side, or have
13811381
different semantics for the client and server:
13821382

1383+
- **`{psk_groups, Groups}`** - key exchange groups that the client
1384+
will send pre share keys for, defaults to first group in
1385+
supported_groups. Must be a subset of supported_groups and will
1386+
be sent in the same order as they appear in supported_groups.
1387+
13831388
- **`{alpn_advertised_protocols, AppProtocols}`** - Application layer protocol
13841389

13851390
The list of protocols supported by the client to be sent to the server to be
@@ -1397,6 +1402,7 @@ different semantics for the client and server:
13971402

13981403
-type client_option() :: client_option_cert() |
13991404
common_option_cert() |
1405+
{psk_groups, [group()]} |
14001406
{alpn_advertised_protocols, AppProtocols::[AppProto::binary()]} |
14011407
{max_fragment_length, MaxLen:: undefined | 512 | 1024 | 2048 | 4096} |
14021408
client_option_tls13() |

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_config.erl

Lines changed: 23 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -493,6 +493,7 @@ ssl_options() ->
493493
partial_chain,
494494
password,
495495
protocol,
496+
psk_groups,
496497
psk_identity,
497498
receiver_spawn_opts,
498499
renegotiate_at,
@@ -1371,7 +1372,7 @@ handle_user_lookup(UserOpts, #{versions := Versions} = Opts) ->
13711372
end.
13721373

13731374

1374-
opt_supported_groups(UserOpts, #{versions := TlsVsns} = Opts, _Env) ->
1375+
opt_supported_groups(UserOpts, #{versions := TlsVsns} = Opts, Env) ->
13751376
SG = case get_opt_list(supported_groups, undefined, UserOpts, Opts) of
13761377
{default, undefined} ->
13771378
try assert_version_dep(supported_groups, TlsVsns, ['tlsv1.3']) of
@@ -1404,7 +1405,27 @@ opt_supported_groups(UserOpts, #{versions := TlsVsns} = Opts, _Env) ->
14041405
throw:_ ->
14051406
[]
14061407
end,
1407-
Opts#{ciphers => CPHS, eccs => ECCS, supported_groups => SG}.
1408+
case opt_psk_groups(SG, UserOpts, Opts, Env) of
1409+
undefined ->
1410+
Opts#{ciphers => CPHS, eccs => ECCS, supported_groups => SG};
1411+
PSKGroups ->
1412+
Opts#{ciphers => CPHS, eccs => ECCS, supported_groups => SG, psk_groups => PSKGroups}
1413+
end.
1414+
1415+
opt_psk_groups(undefined, _, _, _) ->
1416+
undefined;
1417+
opt_psk_groups(#supported_groups{supported_groups = SupportedGroups}, UserOpts, Opts, _Env) ->
1418+
%% Version dependency already asserted when SupportedGroups is supported
1419+
%% so is psk_groups
1420+
First = hd(SupportedGroups),
1421+
case get_opt_list(psk_groups, [First], UserOpts, Opts) of
1422+
{default, Default} ->
1423+
Default;
1424+
{new, PSKGroups} ->
1425+
[Group || Group <- SupportedGroups, lists:member(Group, PSKGroups)];
1426+
{old, PSKGroups} ->
1427+
PSKGroups
1428+
end.
14081429

14091430
opt_crl(UserOpts, Opts, _Env) ->
14101431
{_, Check} = get_opt_of(crl_check, [best_effort, peer, true, false], false, UserOpts, Opts),

lib/ssl/src/ssl_handshake.erl

Lines changed: 73 additions & 13 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),
@@ -3075,14 +3088,15 @@ decode_extensions(<<?UINT16(?KEY_SHARE_EXT), ?UINT16(Len),
30753088
decode_extensions(<<?UINT16(?KEY_SHARE_EXT), ?UINT16(Len),
30763089
ExtData:Len/binary, Rest/binary>>,
30773090
Version, MessageType = server_hello, Acc) ->
3078-
<<?UINT16(Group),?UINT16(KeyLen),KeyExchange:KeyLen/binary>> = ExtData,
3079-
assert_unique_extension(key_share, Acc),
3091+
<<?UINT16(EnumGroup),?UINT16(KeyLen),KeyExchange0:KeyLen/binary>> = ExtData,
3092+
Group = tls_v1:enum_to_group(EnumGroup),
3093+
KeyExchange = maybe_dec_server_hybrid_share(Group, KeyExchange0),
30803094
decode_extensions(Rest, Version, MessageType,
30813095
Acc#{key_share =>
30823096
#key_share_server_hello{
30833097
server_share =
30843098
#key_share_entry{
3085-
group = tls_v1:enum_to_group(Group),
3099+
group = Group,
30863100
key_exchange = KeyExchange}}});
30873101

30883102
decode_extensions(<<?UINT16(?KEY_SHARE_EXT), ?UINT16(Len),
@@ -3239,8 +3253,53 @@ dec_hashsign(Value) ->
32393253
[HashSign] = decode_sign_alg(?TLS_1_2, Value),
32403254
HashSign.
32413255

3256+
maybe_dec_server_hybrid_share(x25519mlkem768, <<MLKem:1088/binary, X25519:32/binary>>) ->
3257+
%% Concatenation of an ML-KEM ciphertext returned from
3258+
%% encapsulation to the client's encapsulation key The size of the
3259+
%% server share is 1120 bytes (1088 bytes for the ML-KEM part and
3260+
%% 32 bytes for X25519).
3261+
%% Note exception algorithm should be in reveres order of name due to legacy reason
3262+
{MLKem, X25519};
3263+
maybe_dec_server_hybrid_share(secp256r1mlkem768, <<Secp256r1:65/binary, MLKem:1088/binary>>) ->
3264+
%% Concatenation of the server's ephemeral secp256r1 share encoded
3265+
%% in the same way as the client share and an ML-KEM The size of
3266+
%% the server share is 1153 bytes (1088 bytes for the ML-KEM part
3267+
%% and 65 bytes for secp256r1).
3268+
{Secp256r1, MLKem};
3269+
maybe_dec_server_hybrid_share(secp384r1mlkem1024, <<Secp384r1:97/binary, MLKem:1568/binary>>) ->
3270+
%% Concatenation of the server's ephemeral secp384r1 share encoded
3271+
%% in the same way as the client share and an ML-KEM ciphertext
3272+
%% returned from encapsulation to the client's encapsulation key
3273+
%% The size of the server share is 1665 bytes (1568 bytes for the
3274+
%% ML-KEM part and 97 bytes for secp384r1)
3275+
{Secp384r1, MLKem};
3276+
maybe_dec_server_hybrid_share(_, Share) ->
3277+
%% Not hybrid
3278+
Share.
3279+
3280+
maybe_dec_client_hybrid_share(x25519mlkem768, <<MLKem:1184/binary, X25519:32/binary>>) ->
3281+
%% Concatenation of the client's ML-KEM-768 encapsulation key and
3282+
%% the client's X25519 ephemeral share. The size of the client share
3283+
%% is 1216 bytes (1184 bytes for the ML-KEM part and 32 bytes for
3284+
%% X25519).
3285+
%% Note exception algorithm should be in reveres order of name due to legacy reason
3286+
{MLKem, X25519};
3287+
maybe_dec_client_hybrid_share(secp256r1mlkem768, <<Secp256r1:65/binary, MLKem:1184/binary>>) ->
3288+
%% Concatenation of the secp256r1 ephemeral share and ML-KEM-768
3289+
%% encapsulation key The size of the client share is 1249 bytes (65
3290+
%% bytes for the secp256r1 part and 1184 bytes for ML-KEM). Ignore
3291+
%% unknown names (only host_name is supported)
3292+
{Secp256r1, MLKem};
3293+
maybe_dec_client_hybrid_share(secp384r1mlkem1024, <<Secp384r1:97/binary, MLKem:1568/binary>>) ->
3294+
%% Concatenation of the secp384r1 ephemeral share and the
3295+
%% ML-KEM-1024 encapsulation key. The size of the client share
3296+
%% is 1665 bytes (97 bytes for the secp384r1 and the 1568 for the
3297+
%% ML-KEM).
3298+
{Secp384r1, MLKem};
3299+
maybe_dec_client_hybrid_share(_, Share) ->
3300+
%% Not hybrid
3301+
Share.
32423302

3243-
%% Ignore unknown names (only host_name is supported)
32443303
dec_sni(<<?BYTE(?SNI_NAMETYPE_HOST_NAME), ?UINT16(Len),
32453304
HostName:Len/binary, _/binary>>) ->
32463305
#sni{hostname = binary_to_list(HostName)};
@@ -3266,12 +3325,13 @@ decode_client_shares(ClientShares) ->
32663325
%%
32673326
decode_client_shares(<<>>, Acc) ->
32683327
lists:reverse(Acc);
3269-
decode_client_shares(<<?UINT16(Group0),?UINT16(Len),KeyExchange:Len/binary,Rest/binary>>, Acc) ->
3328+
decode_client_shares(<<?UINT16(Group0),?UINT16(Len),KeyExchange0:Len/binary,Rest/binary>>, Acc) ->
32703329
case tls_v1:enum_to_group(Group0) of
32713330
undefined ->
32723331
%% Ignore key_share with unknown group
32733332
decode_client_shares(Rest, Acc);
32743333
Group ->
3334+
KeyExchange = maybe_dec_client_hybrid_share(Group, KeyExchange0),
32753335
decode_client_shares(Rest, [#key_share_entry{
32763336
group = Group,
32773337
key_exchange= KeyExchange

lib/ssl/src/tls_client_connection_1_3.erl

Lines changed: 22 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -593,17 +593,25 @@ maybe_resumption(_) ->
593593
ok.
594594

595595
maybe_generate_client_shares(#{versions := [?TLS_1_3|_],
596-
supported_groups :=
597-
#supported_groups{
598-
supported_groups = [Group|_]}}) ->
599-
%% Generate only key_share entry for the most preferred group
600-
ssl_cipher:generate_client_shares([Group]);
596+
psk_groups := Groups}) ->
597+
%% Default will be the list of only the most preferred supported group
598+
generate_client_shares(Groups);
601599
maybe_generate_client_shares(_) ->
602600
undefined.
603601

604602
%%--------------------------------------------------------------------
605603
%% Internal functions
606604
%%--------------------------------------------------------------------
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+
607615
handle_exlusive_1_3_hello_or_hello_retry_request(ServerHello, State0) ->
608616
case do_handle_exlusive_1_3_hello_or_hello_retry_request(ServerHello,
609617
State0) of
@@ -667,7 +675,7 @@ do_handle_exlusive_1_3_hello_or_hello_retry_request(
667675
%% replace the original "key_share" extension with one containing only a
668676
%% new KeyShareEntry for the group indicated in the selected_group field
669677
%% of the triggering HelloRetryRequest.
670-
ClientKeyShare = ssl_cipher:generate_client_shares([SelectedGroup]),
678+
ClientKeyShare = generate_client_shares([SelectedGroup]),
671679
TicketData =
672680
tls_handshake_1_3:get_ticket_data(self(), SessionTickets, UseTicket),
673681
OcspNonce = maps:get(ocsp_nonce, StaplingState, undefined),
@@ -866,10 +874,14 @@ server_share(#key_share_hello_retry_request{selected_group = Share}) ->
866874
client_private_key(Group, ClientShares) ->
867875
case lists:keysearch(Group, 2, ClientShares) of
868876
{value, #key_share_entry{key_exchange =
869-
ClientPrivateKey = #'ECPrivateKey'{}}} ->
870-
ClientPrivateKey;
871-
{value, #key_share_entry{key_exchange = {_, ClientPrivateKey}}} ->
872-
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;
873885
false ->
874886
no_suitable_key
875887
end.

0 commit comments

Comments
 (0)