Skip to content

Commit dbca62f

Browse files
author
Erlang/OTP
committed
Merge branch 'ingela/ssl/maint-27/key-update-unexpected-message/OTP-19806' into maint-27
* ingela/ssl/maint-27/key-update-unexpected-message/OTP-19806: ssl: Avoid sending internal message to client
2 parents 7057c0f + 5c69e0b commit dbca62f

File tree

3 files changed

+50
-25
lines changed

3 files changed

+50
-25
lines changed

lib/ssl/src/ssl_trace.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -489,7 +489,7 @@ trace_profiles() ->
489489
fun(M, F, A) -> dbg:ctpl(M, F, A) end,
490490
[{tls_gen_connection_1_3, [{handle_key_update, 2}]},
491491
{tls_sender, [{init, 3}, {time_to_rekey, 6},
492-
{send_post_handshake_data, 4}]},
492+
{send_post_handshake_data, 5}]},
493493
{tls_v1, [{update_traffic_secret, 2}]}]},
494494
{rle, %% role
495495
fun(M, F, A) -> dbg:tpl(M, F, A, x) end,

lib/ssl/src/tls_sender.erl

Lines changed: 23 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -291,7 +291,7 @@ connection({call, From}, {application_data, AppData},
291291
send_application_data(Data, From, connection, StateData)
292292
end;
293293
connection({call, From}, {post_handshake_data, HSData}, StateData) ->
294-
send_post_handshake_data(HSData, From, connection, StateData);
294+
send_post_handshake_data(HSData, From, connection, StateData, [{reply, From, ok}]);
295295
connection({call, From}, {ack_alert, #alert{} = Alert}, StateData0) ->
296296
StateData = send_tls_alert(Alert, StateData0),
297297
{next_state, connection, StateData,
@@ -343,7 +343,7 @@ connection(internal, {application_packets, From, Data}, StateData) ->
343343
send_application_data(Data, From, connection, StateData);
344344

345345
connection(internal, {post_handshake_data, From, HSData}, StateData) ->
346-
send_post_handshake_data(HSData, From, connection, StateData);
346+
send_post_handshake_data(HSData, From, connection, StateData, []);
347347
connection(cast, #alert{} = Alert, StateData0) ->
348348
StateData = send_tls_alert(Alert, StateData0),
349349
{next_state, connection, StateData};
@@ -441,6 +441,9 @@ death_row(_Type, _Msg, _StateData) ->
441441
keep_state_and_data.
442442

443443
%% State entry function that starts shutdown state_timeout
444+
%% distribution otherwise shuts down the sender
445+
death_row_shutdown(Reason, #data{env = #env{dist_handle = false}} = StateData) ->
446+
{stop, {shutdown, Reason}, StateData};
444447
death_row_shutdown(Reason, StateData) ->
445448
{next_state, death_row, StateData, [{state_timeout, 5000, Reason}]}.
446449

@@ -541,7 +544,7 @@ send_application_data(Data, From, StateName,
541544
case time_to_rekey(Version, DataSz, ConnectionStates0, RenegotiateAt, KeyUpdateAt, BytesSent) of
542545
key_update ->
543546
KeyUpdate = tls_handshake_1_3:key_update(update_requested),
544-
{keep_state_and_data, [{next_event, internal, {post_handshake_data, From, KeyUpdate}},
547+
{keep_state_and_data, [{next_event, internal, {post_handshake_data, undefined, KeyUpdate}},
545548
{next_event, internal, {application_packets, From, Data}}]};
546549
renegotiate ->
547550
tls_dtls_gen_connection:internal_renegotiation(Pid, ConnectionStates0),
@@ -551,8 +554,8 @@ send_application_data(Data, From, StateName,
551554
KeyUpdate = tls_handshake_1_3:key_update(update_requested),
552555
%% Prevent infinite loop of key updates
553556
{Chunk, Rest} = split_binary(iolist_to_binary(Data), KeyUpdateAt),
554-
{keep_state_and_data, [{next_event, internal, {post_handshake_data, From, KeyUpdate}},
555-
{next_event, internal, {application_packets, From, [Chunk]}},
557+
{keep_state_and_data, [{next_event, internal, {post_handshake_data, undefined, KeyUpdate}},
558+
{next_event, internal, {application_packets, undefined, [Chunk]}},
556559
{next_event, internal, {application_packets, From, [Rest]}}]};
557560
false ->
558561
{Msgs, ConnectionStates} = tls_record:encode_data(Data, Version, ConnectionStates0),
@@ -561,29 +564,29 @@ send_application_data(Data, From, StateName,
561564
ssl_logger:debug(LogLevel, outbound, 'record', Msgs),
562565
StateData1 = update_bytes_sent(Version, ConnectionStates, StateData0, DataSz),
563566
hibernate_after(StateName, StateData1, []);
564-
Reason when DistHandle =/= undefined ->
565-
StateData = StateData0#data{connection_states = ConnectionStates},
566-
death_row_shutdown(Reason, StateData);
567567
ok ->
568568
ssl_logger:debug(LogLevel, outbound, 'record', Msgs),
569569
StateData = update_bytes_sent(Version, ConnectionStates, StateData0, DataSz),
570-
gen_statem:reply(From, ok),
570+
send_reply(From, ok),
571571
hibernate_after(StateName, StateData, []);
572572
Result ->
573-
gen_statem:reply(From, Result),
573+
send_reply(From, Result),
574574
StateData = StateData0#data{connection_states = ConnectionStates},
575575
hibernate_after(StateName, StateData, [])
576576
end
577577
end.
578578

579+
send_reply(undefined, _Msg) -> ok;
580+
send_reply(From, Msg) -> gen_statem:reply(From, Msg).
581+
579582
%% TLS 1.3 Post Handshake Data
580-
send_post_handshake_data(Handshake, From, StateName,
583+
send_post_handshake_data(Handshake, _From, StateName,
581584
#data{env = #env{socket = Socket,
582-
dist_handle = DistHandle,
583-
negotiated_version = Version,
584-
transport_cb = Transport,
585-
log_level = LogLevel},
586-
connection_states = ConnectionStates0} = StateData0) ->
585+
dist_handle = DistHandle,
586+
negotiated_version = Version,
587+
transport_cb = Transport,
588+
log_level = LogLevel},
589+
connection_states = ConnectionStates0} = StateData0, AckAction) ->
587590
BinHandshake = tls_handshake:encode_handshake(Handshake, Version),
588591
{Encoded, ConnectionStates} =
589592
tls_record:encode_handshake(BinHandshake, Version, ConnectionStates0),
@@ -593,15 +596,13 @@ send_post_handshake_data(Handshake, From, StateName,
593596
ok when DistHandle =/= undefined ->
594597
ssl_logger:debug(LogLevel, outbound, 'record', Encoded),
595598
StateData = maybe_update_cipher_key(StateData1, Handshake),
596-
{next_state, StateName, StateData, []};
597-
Reason when DistHandle =/= undefined ->
598-
death_row_shutdown(Reason, StateData1);
599+
{next_state, StateName, StateData, AckAction};
599600
ok ->
600601
ssl_logger:debug(LogLevel, outbound, 'record', Encoded),
601602
StateData = maybe_update_cipher_key(StateData1, Handshake),
602-
{next_state, StateName, StateData, [{reply, From, ok}]};
603-
Result ->
604-
{next_state, StateName, StateData1, [{reply, From, Result}]}
603+
{next_state, StateName, StateData, AckAction};
604+
{error, Reason} ->
605+
death_row_shutdown(Reason, StateData1)
605606
end.
606607

607608
maybe_update_cipher_key(#data{connection_states = ConnectionStates0,

lib/ssl/test/ssl_key_update_SUITE.erl

Lines changed: 26 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,9 @@
4141
keylog_client_cb/0,
4242
keylog_client_cb/1,
4343
keylog_server_cb/0,
44-
keylog_server_cb/1
44+
keylog_server_cb/1,
45+
key_update_unexpected_msg/0,
46+
key_update_unexpected_msg/1
4547
]).
4648

4749
-include("ssl_test_lib.hrl").
@@ -59,7 +61,8 @@ tls_1_3_tests() ->
5961
key_update_at_server,
6062
explicit_key_update,
6163
keylog_client_cb,
62-
keylog_server_cb].
64+
keylog_server_cb,
65+
key_update_unexpected_msg].
6366

6467
init_per_suite(Config0) ->
6568
case application:ensure_started(crypto) of
@@ -198,6 +201,27 @@ keylog_server_cb(Config) ->
198201
end,
199202
ok = traffic_secret_1_and_2([{client,1}, {client, 2}, {server,1}, {server, 2}]).
200203

204+
key_update_unexpected_msg() ->
205+
[{doc,"Test that internla sync messages are not sent to socket user"}].
206+
key_update_unexpected_msg(Config) ->
207+
Data = "123456789012345", %% 15 bytes
208+
Server = ssl_test_lib:start_server(erlang,[], Config),
209+
Port = ssl_test_lib:inet_port(Server),
210+
211+
{ok, Socket} = ssl:connect(net_adm:localhost(), Port, [{verify, verify_none}, {key_update_at, 9}]),
212+
213+
ok = ssl:send(Socket, Data),
214+
215+
receive
216+
{_, ok} = Msg ->
217+
ct:fail({unexpected_message, Msg})
218+
after 500 ->
219+
ok
220+
end.
221+
222+
%%--------------------------------------------------------------------
223+
%% Internal functions -----------------------------------------------
224+
%%--------------------------------------------------------------------
201225
traffic_secret_1_and_2([]) ->
202226
ok;
203227
traffic_secret_1_and_2([_|_] = List) ->

0 commit comments

Comments
 (0)