Skip to content

Commit 63ea2c0

Browse files
committed
ssl: Correct TLS-1.3 refactor so prf function works properly
closes #7911
1 parent 7118194 commit 63ea2c0

8 files changed

+118
-47
lines changed

lib/ssl/src/tls_client_connection_1_3.erl

Lines changed: 13 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -463,9 +463,11 @@ wait_finished(internal,
463463
State8 = tls_handshake_1_3:forget_master_secret(State7),
464464
%% Configure traffic keys
465465
State9 = ssl_record:step_encryption_state(State8),
466-
{Record, State} = ssl_gen_statem:prepare_connection(State9,
467-
tls_gen_connection),
468-
tls_gen_connection:next_event(connection, Record, State,
466+
{Record, #state{protocol_specific = PS} = State} = ssl_gen_statem:prepare_connection(State9,
467+
tls_gen_connection),
468+
ExporterSecret = tls_handshake_1_3:calculate_exporter_secret(State),
469+
tls_gen_connection:next_event(connection, Record,
470+
State#state{protocol_specific = PS#{exporter_secret => ExporterSecret}},
469471
[{{timeout, handshake}, cancel}])
470472
catch
471473
{Ref, #alert{} = Alert} ->
@@ -505,6 +507,7 @@ handle_exlusive_1_3_hello_or_hello_retry_request(ServerHello, State0) ->
505507

506508
do_handle_exlusive_1_3_hello_or_hello_retry_request(
507509
#server_hello{cipher_suite = SelectedCipherSuite,
510+
random = Random,
508511
session_id = SessionId,
509512
extensions = Extensions},
510513
#state{static_env = #static_env{host = Host,
@@ -575,7 +578,8 @@ do_handle_exlusive_1_3_hello_or_hello_retry_request(
575578
#{cipher => SelectedCipherSuite,
576579
key_share => ClientKeyShare,
577580
session_id => SessionId,
578-
group => SelectedGroup}),
581+
group => SelectedGroup,
582+
random => Random}),
579583

580584
%% Replace ClientHello1 with a special synthetic handshake message
581585
State2 = tls_handshake_1_3:replace_ch1_with_message_hash(State1),
@@ -627,8 +631,9 @@ do_handle_exlusive_1_3_hello_or_hello_retry_request(
627631
end.
628632

629633
handle_server_hello(#server_hello{cipher_suite = SelectedCipherSuite,
630-
session_id = SessionId,
631-
extensions = Extensions} = ServerHello,
634+
random = Random,
635+
session_id = SessionId,
636+
extensions = Extensions} = ServerHello,
632637
#state{key_share = ClientKeyShare,
633638
ssl_options = #{ciphers := ClientCiphers,
634639
supported_groups := ClientGroups0,
@@ -664,7 +669,8 @@ handle_server_hello(#server_hello{cipher_suite = SelectedCipherSuite,
664669
key_share => ClientKeyShare,
665670
session_id => SessionId,
666671
group => SelectedGroup,
667-
peer_public_key => ServerPublicKey}),
672+
peer_public_key => ServerPublicKey,
673+
random => Random}),
668674

669675
#state{connection_states = ConnectionStates} = State2,
670676
#{security_parameters := SecParamsR} =

lib/ssl/src/tls_dtls_connection.erl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,8 @@
4848

4949
%% Help functions for tls|dtls_connection.erl
5050
-export([handle_session/7,
51-
handle_sni_extension/2]).
51+
handle_sni_extension/2,
52+
handle_call/4]).
5253

5354
%% General state handlingfor TLS-1.0 to TLS-1.2 and gen_handshake that wraps
5455
%% handling of common state handling for handshake messages for error handling

lib/ssl/src/tls_gen_connection_1_3.erl

Lines changed: 27 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -160,6 +160,33 @@ connection({call, From}, negotiated_protocol,
160160
State) ->
161161
ssl_gen_statem:hibernate_after(?FUNCTION_NAME, State,
162162
[{reply, From, {ok, SelectedProtocol}}]);
163+
connection({call, From}, {prf, _, Label, Context0, WantedLength},
164+
#state{connection_states = ConnectionStates,
165+
protocol_specific = PS} = State) ->
166+
#{security_parameters := SecParams} =
167+
ssl_record:current_connection_state(ConnectionStates, read),
168+
#security_parameters{prf_algorithm = PRFAlgorithm,
169+
client_random = ClientRandom,
170+
server_random = ServerRandom} = SecParams,
171+
172+
Context0Size = erlang:iolist_size(Context0),
173+
Context = case Context0 of
174+
[client_random, server_random | Rest] ->
175+
erlang:iolist_to_binary([ClientRandom, SecParams, ?unit16(Context0), Context0]);
176+
_ ->
177+
erlang:iolist_to_binary([?unit16(Context0), Context0])
178+
end,
179+
180+
ExporterMasterSecret = maps:get(exporter_secret, PS),
181+
182+
%% TLS-Exporter(label, context_value, key_length) =
183+
%% HKDF-Expand-Label(Derive-Secret(ExporterSecret, label, ""),
184+
%% "exporter", Hash(context_value), key_length)
185+
ExporterSecret = tls_v1:derive_secret(ExporterMasterSecret, Label, <<>>, PRFAlgorithm),
186+
HashContext = tls_v1:transcript_hash(Context, PRFAlgorithm),
187+
Exporter = tls_v1:hkdf_expand_label(ExporterSecret, <<"exporter">>, HashContext,
188+
WantedLength, PRFAlgorithm),
189+
{next_state, ?FUNCTION_NAME, State, [{reply, From, {ok, Exporter}}]};
163190
connection(Type, Event, State) ->
164191
ssl_gen_statem:?FUNCTION_NAME(Type, Event, State).
165192

lib/ssl/src/tls_handshake_1_3.erl

Lines changed: 29 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@
5858
-export([process_certificate_request/2,
5959
process_certificate/2,
6060
calculate_handshake_secrets/5,
61+
calculate_exporter_secret/1,
6162
verify_certificate_verify/2,
6263
validate_finished/2,
6364
maybe_calculate_resumption_master_secret/1,
@@ -1089,9 +1090,6 @@ calculate_traffic_secrets(#state{
10891090
ReadKey, ReadIV, undefined,
10901091
WriteKey, WriteIV, undefined).
10911092

1092-
1093-
1094-
10951093
%% X25519, X448
10961094
calculate_shared_secret(OthersKey, MyKey, Group)
10971095
when is_binary(OthersKey) andalso is_binary(MyKey) andalso
@@ -1117,8 +1115,8 @@ maybe_calculate_resumption_master_secret(#state{
11171115
ssl_options = #{session_tickets := SessionTickets},
11181116
connection_states = ConnectionStates,
11191117
handshake_env =
1120-
#handshake_env{
1121-
tls_handshake_history = HHistory}} = State)
1118+
#handshake_env{
1119+
tls_handshake_history = HHistory}} = State)
11221120
when SessionTickets =/= disabled ->
11231121
#{security_parameters := SecParamsR} =
11241122
ssl_record:pending_connection_state(ConnectionStates, read),
@@ -1128,6 +1126,18 @@ maybe_calculate_resumption_master_secret(#state{
11281126
RMS = tls_v1:resumption_master_secret(HKDFAlgo, MasterSecret, lists:reverse(Messages0)),
11291127
update_resumption_master_secret(State, RMS).
11301128

1129+
calculate_exporter_secret(#state{
1130+
static_env = #static_env{role = Role},
1131+
connection_states = ConnectionStates,
1132+
handshake_env =
1133+
#handshake_env{
1134+
tls_handshake_history = HHistory}}) ->
1135+
#{security_parameters := SecParamsR} =
1136+
ssl_record:pending_connection_state(ConnectionStates, read),
1137+
#security_parameters{prf_algorithm = HKDFAlgo,
1138+
master_secret = MasterSecret} = SecParamsR,
1139+
Messages = get_handshake_context(Role, HHistory),
1140+
tls_v1:exporter_master_secret(HKDFAlgo, MasterSecret, lists:reverse(Messages)).
11311141

11321142
forget_master_secret(#state{connection_states =
11331143
#{pending_read := PendingRead,
@@ -1232,22 +1242,28 @@ update_start_state(State, Map) ->
12321242
SelectedSignAlg = maps:get(sign_alg, Map, undefined),
12331243
PeerPublicKey = maps:get(peer_public_key, Map, undefined),
12341244
ALPNProtocol = maps:get(alpn, Map, undefined),
1245+
Random = maps:get(random, Map),
12351246
update_start_state(State, Cipher, KeyShare, SessionId,
12361247
Group, SelectedSignAlg, PeerPublicKey,
1237-
ALPNProtocol).
1248+
ALPNProtocol, Random).
12381249
%%
12391250
update_start_state(#state{connection_states = ConnectionStates0,
12401251
handshake_env = #handshake_env{} = HsEnv,
1252+
static_env = #static_env{role = Role},
12411253
connection_env = CEnv,
12421254
session = Session} = State,
12431255
Cipher, KeyShare, SessionId,
1244-
Group, SelectedSignAlg, PeerPublicKey, ALPNProtocol) ->
1256+
Group, SelectedSignAlg, PeerPublicKey, ALPNProtocol, Random) ->
12451257
#{security_parameters := SecParamsR0} = PendingRead =
12461258
maps:get(pending_read, ConnectionStates0),
12471259
#{security_parameters := SecParamsW0} = PendingWrite =
12481260
maps:get(pending_write, ConnectionStates0),
1249-
SecParamsR = ssl_cipher:security_parameters_1_3(SecParamsR0, Cipher),
1250-
SecParamsW = ssl_cipher:security_parameters_1_3(SecParamsW0, Cipher),
1261+
SecParamsR1 = ssl_cipher:security_parameters_1_3(SecParamsR0, Cipher),
1262+
SecParamsW1 = ssl_cipher:security_parameters_1_3(SecParamsW0, Cipher),
1263+
1264+
SecParamsR = update_random(Role, SecParamsR1, Random),
1265+
SecParamsW = update_random(Role, SecParamsW1, Random),
1266+
12511267
ConnectionStates =
12521268
ConnectionStates0#{pending_read => PendingRead#{security_parameters => SecParamsR},
12531269
pending_write => PendingWrite#{security_parameters => SecParamsW}},
@@ -1261,6 +1277,10 @@ update_start_state(#state{connection_states = ConnectionStates0,
12611277
cipher_suite = Cipher},
12621278
connection_env = CEnv#connection_env{negotiated_version = ?TLS_1_3}}.
12631279

1280+
update_random(server, SParams, Random) ->
1281+
SParams#security_parameters{client_random = Random};
1282+
update_random(client, SParams, Random) ->
1283+
SParams#security_parameters{server_random = Random}.
12641284

12651285
update_resumption_master_secret(#state{connection_states = ConnectionStates0} = State,
12661286
ResumptionMasterSecret) ->

lib/ssl/src/tls_server_connection_1_3.erl

Lines changed: 15 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -313,14 +313,15 @@ wait_finished(internal,
313313
State1 = tls_handshake_1_3:calculate_traffic_secrets(State0),
314314
State2 = tls_handshake_1_3:maybe_calculate_resumption_master_secret(State1),
315315
State3 = tls_handshake_1_3:forget_master_secret(State2),
316-
317316
%% Configure traffic keys
318317
State4 = ssl_record:step_encryption_state(State3),
319318

320319
State5 = maybe_send_session_ticket(State4),
321320

322-
{Record, State} = ssl_gen_statem:prepare_connection(State5, tls_gen_connection),
323-
tls_gen_connection:next_event(connection, Record, State,
321+
{Record, #state{protocol_specific = PS} = State} = ssl_gen_statem:prepare_connection(State5, tls_gen_connection),
322+
ExporterSecret = tls_handshake_1_3:calculate_exporter_secret(State),
323+
tls_gen_connection:next_event(connection, Record,
324+
State#state{protocol_specific = PS#{exporter_secret => ExporterSecret}},
324325
[{{timeout, handshake}, cancel}])
325326
catch
326327
{Ref, #alert{} = Alert} ->
@@ -387,14 +388,15 @@ handle_client_hello(ClientHello, State0) ->
387388
end.
388389

389390
do_handle_client_hello(#client_hello{cipher_suites = ClientCiphers,
390-
session_id = SessionId,
391-
extensions = Extensions} = Hello,
392-
#state{ssl_options = #{ciphers := ServerCiphers,
393-
signature_algs := ServerSignAlgs,
394-
supported_groups := ServerGroups0,
395-
alpn_preferred_protocols := ALPNPreferredProtocols,
396-
honor_cipher_order := HonorCipherOrder,
397-
early_data := EarlyDataEnabled} = Opts} = State0) ->
391+
random = Random,
392+
session_id = SessionId,
393+
extensions = Extensions} = Hello,
394+
#state{ssl_options = #{ciphers := ServerCiphers,
395+
signature_algs := ServerSignAlgs,
396+
supported_groups := ServerGroups0,
397+
alpn_preferred_protocols := ALPNPreferredProtocols,
398+
honor_cipher_order := HonorCipherOrder,
399+
early_data := EarlyDataEnabled} = Opts} = State0) ->
398400
SNI = maps:get(sni, Extensions, undefined),
399401
EarlyDataIndication = maps:get(early_data, Extensions, undefined),
400402
{Ref,Maybe} = tls_gen_connection_1_3:do_maybe(),
@@ -480,7 +482,8 @@ do_handle_client_hello(#client_hello{cipher_suites = ClientCiphers,
480482
group => Group,
481483
sign_alg => SelectedSignAlg,
482484
peer_public_key => ClientPubKey,
483-
alpn => ALPNProtocol}),
485+
alpn => ALPNProtocol,
486+
random => Random}),
484487

485488
%% 4.1.4. Hello Retry Request
486489
%%

lib/ssl/src/tls_v1.erl

Lines changed: 13 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -67,12 +67,13 @@
6767

6868
-export([derive_secret/4,
6969
hkdf_expand_label/5,
70+
hkdf_expand_label/6,
7071
hkdf_extract/3,
7172
hkdf_expand/4,
7273
key_length/1,
7374
key_schedule/3,
7475
key_schedule/4,
75-
create_info/3,
76+
create_info/4,
7677
external_binder_key/2,
7778
resumption_binder_key/2,
7879
client_early_traffic_secret/3,
@@ -121,18 +122,26 @@ derive_secret(Secret, Label, Messages, Algo) ->
121122
Context::binary(), Length::integer(),
122123
Algo::ssl:hash()) -> KeyingMaterial::binary().
123124
hkdf_expand_label(Secret, Label0, Context, Length, Algo) ->
124-
HkdfLabel = create_info(Label0, Context, Length),
125+
HkdfLabel = create_info(Label0, Context, Length, <<"tls13 ">>),
125126
hkdf_expand(Secret, HkdfLabel, Length, Algo).
126127

128+
-spec hkdf_expand_label(Secret::binary(), Label0::binary(),
129+
Context::binary(), Length::integer(),
130+
Algo::ssl:hash(), Prefix::binary()) -> KeyingMaterial::binary().
131+
hkdf_expand_label(Secret, Label0, Context, Length, Algo , Prefix) ->
132+
HkdfLabel = create_info(Label0, Context, Length, Prefix),
133+
hkdf_expand(Secret, HkdfLabel, Length, Algo).
134+
135+
127136
%% Create info parameter for HKDF-Expand:
128137
%% HKDF-Expand(PRK, info, L) -> OKM
129-
create_info(Label0, Context0, Length) ->
138+
create_info(Label0, Context0, Length, Prefix) ->
130139
%% struct {
131140
%% uint16 length = Length;
132141
%% opaque label<7..255> = "tls13 " + Label;
133142
%% opaque context<0..255> = Context;
134143
%% } HkdfLabel;
135-
Label1 = << <<"tls13 ">>/binary, Label0/binary>>,
144+
Label1 = <<Prefix/binary, Label0/binary>>,
136145
LabelLen = byte_size(Label1),
137146
Label = <<?BYTE(LabelLen), Label1/binary>>,
138147
ContextLen = byte_size(Context0),

lib/ssl/test/ssl_api_SUITE.erl

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -3665,10 +3665,12 @@ check_srp_in_connection_information(Socket, Username, server) ->
36653665

36663666
%% In TLS 1.3 the master_secret field is used to store multiple secrets from the key schedule and it is a tuple.
36673667
%% client_random and server_random are not used in the TLS 1.3 key schedule.
3668-
check_connection_info('tlsv1.3', [{client_random, ClientRand}, {master_secret, {master_secret, MasterSecret}}]) ->
3669-
is_binary(ClientRand) andalso is_binary(MasterSecret);
3670-
check_connection_info('tlsv1.3', [{server_random, ServerRand}, {master_secret, {master_secret, MasterSecret}}]) ->
3671-
is_binary(ServerRand) andalso is_binary(MasterSecret);
3668+
check_connection_info('tlsv1.3', [{client_random, ClientRand}, {serer_random, ServerRand},
3669+
{master_secret, {master_secret, MasterSecret}}]) ->
3670+
is_binary(ClientRand) andalso is_binary(ServerRand) andalso is_binary(MasterSecret);
3671+
check_connection_info('tlsv1.3', [{client_random, ClientRand},{server_random, ServerRand},
3672+
{master_secret, {master_secret, MasterSecret}}]) ->
3673+
is_binary(ClientRand) andalso is_binary(ServerRand) andalso is_binary(MasterSecret);
36723674
check_connection_info(_, [{client_random, ClientRand}, {server_random, ServerRand}, {master_secret, MasterSecret}]) ->
36733675
is_binary(ClientRand) andalso is_binary(ServerRand) andalso is_binary(MasterSecret);
36743676
check_connection_info(_, _) ->

0 commit comments

Comments
 (0)