File 0679-ssl-Handle-DOWN-messages-from-user-process-in-all-st.patch of Package erlang
From 0598f76c34622db79700af432d1e2839d06dfb28 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Wed, 29 Sep 2021 13:22:48 +0200
Subject: [PATCH] ssl: Handle DOWN messages from user process in all states
If the user process unexpectedly dies the state callback needs to
handle "DOWN messages" to detect that and terminate.
Closes #5239
---
lib/ssl/src/ssl_gen_statem.erl | 4 ++
lib/ssl/src/tls_connection_1_3.erl | 2 +
lib/ssl/src/tls_dtls_connection.erl | 2 +
lib/ssl/test/tls_api_SUITE.erl | 78 ++++++++++++++++++++++++++++-
4 files changed, 85 insertions(+), 1 deletion(-)
diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl
index 165668289e..9121196b90 100644
--- a/lib/ssl/src/ssl_gen_statem.erl
+++ b/lib/ssl/src/ssl_gen_statem.erl
@@ -542,6 +542,8 @@ initial_hello({call, From}, {new_user, _} = Msg, State) ->
handle_call(Msg, From, ?FUNCTION_NAME, State);
initial_hello({call, From}, _Msg, _State) ->
{keep_state_and_data, [{reply, From, {error, notsup_on_transport_accept_socket}}]};
+initial_hello(info, {'DOWN', _, _, _, _} = Event, State) ->
+ handle_info(Event, ?FUNCTION_NAME, State);
initial_hello(_Type, _Event, _State) ->
{keep_state_and_data, [postpone]}.
@@ -558,6 +560,8 @@ config_error({call, From}, {close, _}, State) ->
{stop_and_reply, {shutdown, normal}, {reply, From, ok}, State};
config_error({call, From}, _Msg, State) ->
{next_state, ?FUNCTION_NAME, State, [{reply, From, {error, closed}}]};
+config_error(info, {'DOWN', _, _, _, _} = Event, State) ->
+ handle_info(Event, ?FUNCTION_NAME, State);
config_error(_Type, _Event, _State) ->
{keep_state_and_data, [postpone]}.
diff --git a/lib/ssl/src/tls_connection_1_3.erl b/lib/ssl/src/tls_connection_1_3.erl
index 5c7875b27c..2d123bab43 100644
--- a/lib/ssl/src/tls_connection_1_3.erl
+++ b/lib/ssl/src/tls_connection_1_3.erl
@@ -251,6 +251,8 @@ user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
end,
{next_state, Next, State#state{start_or_recv_from = From},
[{next_event, internal, Hello}, {{timeout, handshake}, Timeout, close}]};
+user_hello(info, {'DOWN', _, _, _, _} = Event, State) ->
+ ssl_gen_statem:handle_info(Event, ?FUNCTION_NAME, State);
user_hello(_, _, _) ->
{keep_state_and_data, [postpone]}.
diff --git a/lib/ssl/src/tls_dtls_connection.erl b/lib/ssl/src/tls_dtls_connection.erl
index 0174850758..bb138b035b 100644
--- a/lib/ssl/src/tls_dtls_connection.erl
+++ b/lib/ssl/src/tls_dtls_connection.erl
@@ -175,6 +175,8 @@ user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
State = ssl_gen_statem:ssl_config(Options, Role, State0),
{next_state, hello, State#state{start_or_recv_from = From},
[{next_event, internal, Hello}, {{timeout, handshake}, Timeout, close}]};
+user_hello(info, {'DOWN', _, _, _, _} = Event, State) ->
+ ssl_gen_statem:handle_info(Event, ?FUNCTION_NAME, State);
user_hello(_, _, _) ->
{keep_state_and_data, [postpone]}.
diff --git a/lib/ssl/test/tls_api_SUITE.erl b/lib/ssl/test/tls_api_SUITE.erl
index a3b642ab3f..897df14bab 100644
--- a/lib/ssl/test/tls_api_SUITE.erl
+++ b/lib/ssl/test/tls_api_SUITE.erl
@@ -32,6 +32,8 @@
groups/0,
init_per_suite/1,
init_per_group/2,
+ init_per_testcase/2,
+ end_per_testcase/2,
end_per_suite/1,
end_per_group/2
]).
@@ -77,6 +79,8 @@
tls_server_handshake_timeout/1,
transport_close/0,
transport_close/1,
+ transport_close_in_inital_hello/0,
+ transport_close_in_inital_hello/1,
emulated_options/0,
emulated_options/1,
accept_pool/0,
@@ -96,7 +100,6 @@
receive_msg/1
]).
--define(TIMEOUT, {seconds, 10}).
-define(SLEEP, 500).
%%--------------------------------------------------------------------
@@ -141,6 +144,7 @@ api_tests() ->
sockname,
tls_server_handshake_timeout,
transport_close,
+ transport_close_in_inital_hello,
emulated_options,
accept_pool,
reuseaddr
@@ -167,6 +171,13 @@ init_per_group(GroupName, Config) ->
end_per_group(GroupName, Config) ->
ssl_test_lib:end_per_group(GroupName, Config).
+init_per_testcase(Testcase, Config) when Testcase == tls_server_handshake_timeout;
+ Testcase == tls_upgrade_with_timeout ->
+ ct:timetrap({seconds, 10}),
+ Config;
+init_per_testcase(_, Config) ->
+ ct:timetrap({seconds, 5}),
+ Config.
end_per_testcase(_TestCase, Config) ->
Config.
@@ -754,6 +765,8 @@ tls_server_handshake_timeout(Config) ->
[] = supervisor:which_children(tls_connection_sup)
end
end.
+
+%%--------------------------------------------------------------------
transport_close() ->
[{doc, "Test what happens if socket is closed on TCP level after a while of normal operation"}].
transport_close(Config) when is_list(Config) ->
@@ -778,6 +791,69 @@ transport_close(Config) when is_list(Config) ->
gen_tcp:close(TcpS),
{error, _} = ssl:send(SslS, "Hello world").
+%%--------------------------------------------------------------------
+transport_close_in_inital_hello() ->
+ [{doc, "Test what happens if server dies after calling transport_accept but before initiating handshake."}].
+transport_close_in_inital_hello(Config) when is_list(Config) ->
+ ClientOpts = ssl_test_lib:ssl_options(client_rsa_opts, Config),
+ ServerOpts = ssl_test_lib:ssl_options(server_rsa_opts, Config),
+ {_, _, Hostname} = ssl_test_lib:run_where(Config),
+ process_flag(trap_exit, true),
+
+ Testcase = self(),
+
+ Acceptor = spawn_link(fun() ->
+ {ok, Listen} = ssl:listen(0, ServerOpts),
+ {ok, {_, Port}} = ssl:sockname(Listen),
+ Testcase ! {port, Port},
+ {ok, _Accept} = ssl:transport_accept(Listen),
+ receive
+ die -> ok
+ end
+ end),
+ Port = receive
+ {port, Port0} ->
+ Port0
+ end,
+
+ Connector = spawn_link(fun() ->
+ {ok, _} = ssl:connect(Hostname, Port,
+ [{verify, verify_none}],
+ infinity
+ )
+ end),
+
+
+ Sup = (whereis(tls_connection_sup)),
+
+ check_connection_workers(Sup, 2),
+
+ Acceptor ! die,
+
+ receive
+ {'EXIT', Acceptor, _} ->
+ ok
+ end,
+ receive
+ {'EXIT', Connector, _} ->
+ ok
+ end,
+ check_connection_workers(Sup, 0).
+
+check_connection_workers(Sup, N) ->
+ check_connection_workers(Sup, N, 5).
+
+check_connection_workers(Sup, N, 0) ->
+ N = proplists:get_value(workers, supervisor:count_children(Sup));
+check_connection_workers(Sup, N, M) ->
+ case proplists:get_value(workers, supervisor:count_children(Sup)) of
+ N ->
+ ok;
+ _ ->
+ ct:sleep(500),
+ check_connection_workers(Sup, N, M-1)
+ end.
+
%%--------------------------------------------------------------------
emulated_options() ->
[{doc,"Test API function getopts/2 and setopts/2"}].
--
2.31.1