File 2942-ssl-Add-test-case-and-fix-for-the-happy-path.patch of Package erlang

From 20e9f871c8d04d90a58d42a616f9d6cc4a00278c Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 20 Nov 2020 15:05:43 +0100
Subject: [PATCH 2/2] ssl: Add test case and fix for the happy path

We do not want the test to be only implicit using
the old tls_closed_in_active_once now renamed.
---
 lib/ssl/src/ssl_connection.erl | 10 ++++-----
 lib/ssl/src/tls_connection.erl |  5 +----
 lib/ssl/test/tls_api_SUITE.erl | 41 ++++++++++++++++++++++++++++++++--
 3 files changed, 44 insertions(+), 12 deletions(-)

diff --git a/lib/ssl/src/ssl_connection.erl b/lib/ssl/src/ssl_connection.erl
index 0b600fe985..5618e1dbde 100644
--- a/lib/ssl/src/ssl_connection.erl
+++ b/lib/ssl/src/ssl_connection.erl
@@ -2897,13 +2897,11 @@ ssl_options_list([{Key, Value}|T], Acc) ->
 
 handle_active_option(false, connection = StateName, To, Reply, State) ->
     hibernate_after(StateName, State, [{reply, To, Reply}]);
-
 handle_active_option(_, connection = StateName, To, Reply, #state{static_env = #static_env{role = Role},
-                                                                   connection_env = #connection_env{terminated = true},
-                                                                   user_data_buffer = {_,0,_}} = State) ->
-    Alert = ?ALERT_REC(?FATAL, ?CLOSE_NOTIFY, all_data_deliverd),
-    handle_normal_shutdown(Alert#alert{role = Role}, StateName, 
-                           State#state{start_or_recv_from = To}),
+                                                                  connection_env = #connection_env{terminated = true},
+                                                                  user_data_buffer = {_,0,_}} = State) ->
+    Alert = ?ALERT_REC(?FATAL, ?CLOSE_NOTIFY, all_data_delivered),
+    handle_normal_shutdown(Alert#alert{role = Role}, StateName, State),
     {stop_and_reply,{shutdown, peer_close}, [{reply, To, Reply}]};
 handle_active_option(_, connection = StateName0, To, Reply, #state{static_env = #static_env{protocol_cb = Connection},
                                                                    user_data_buffer = {_,0,_}} = State0) ->
diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl
index 357bd46439..8887190f51 100644
--- a/lib/ssl/src/tls_connection.erl
+++ b/lib/ssl/src/tls_connection.erl
@@ -1346,10 +1346,7 @@ handle_alerts(_, {stop, _, _} = Stop) ->
 handle_alerts([#alert{level = ?WARNING, description = ?CLOSE_NOTIFY} | _Alerts], 
               {next_state, connection = StateName, #state{connection_env = CEnv, 
                                                           socket_options = #socket_options{active = false},
-                                                          user_data_buffer = {_,BufferSize,_},
-                                                          protocol_buffers = #protocol_buffers{tls_cipher_texts = CTs}} = 
-                   State}) when (BufferSize =/= 0) orelse
-                                (CTs =/= []) -> 
+                                                          start_or_recv_from = From} = State}) when From == undefined ->
     {next_state, StateName, State#state{connection_env = CEnv#connection_env{terminated = true}}};
 handle_alerts([Alert | Alerts], {next_state, StateName, State}) ->
      handle_alerts(Alerts, ssl_connection:handle_alert(Alert, StateName, State));
diff --git a/lib/ssl/test/tls_api_SUITE.erl b/lib/ssl/test/tls_api_SUITE.erl
index 4184713fd1..1c794eefa7 100644
--- a/lib/ssl/test/tls_api_SUITE.erl
+++ b/lib/ssl/test/tls_api_SUITE.erl
@@ -123,6 +125,7 @@ api_tests() ->
      tls_shutdown_error,
      tls_client_closes_socket,
      tls_closed_in_active_once,
+     tls_reset_in_active_once,
      tls_tcp_msg,
      tls_tcp_msg_big,
      tls_dont_crash_on_handshake_garbage,
@@ -367,10 +370,10 @@ tls_client_closes_socket(Config) when is_list(Config) ->
     ssl_test_lib:check_result(Server, {error,closed}).
 
 %%--------------------------------------------------------------------
-tls_closed_in_active_once() ->
+tls_reset_in_active_once() ->
     [{doc, "Test that ssl_closed is delivered in active once with non-empty buffer, check ERL-420."}].
 
-tls_closed_in_active_once(Config) when is_list(Config) ->
+tls_reset_in_active_once(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),
     {_ClientNode, _ServerNode, Hostname} = ssl_test_lib:run_where(Config),
@@ -396,6 +399,40 @@ tls_closed_in_active_once(Config) when is_list(Config) ->
 	ok -> ok;
 	_ -> ct:fail(Result)
     end.
+
+%%--------------------------------------------------------------------
+tls_closed_in_active_once() ->
+    [{doc, "Test that active once can be used to deliver not only all data"
+      " but even the close message, see ERL-1409, in normal operation." 
+      " This is also test, with slighly diffrent circumstances in"
+      " the old tls_closed_in_active_once test"
+      " renamed tls_reset_in_active_once"}].
+
+tls_closed_in_active_once(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),
+    {_ClientNode, _ServerNode, Hostname} = ssl_test_lib:run_where(Config),
+    TcpOpts = [binary, {reuseaddr, true}],
+    Port = ssl_test_lib:inet_port(node()),
+    Server = fun() ->
+		     {ok, Listen} = gen_tcp:listen(Port, TcpOpts),
+		     {ok, TcpServerSocket} = gen_tcp:accept(Listen),
+		     {ok, ServerSocket} = ssl:handshake(TcpServerSocket, ServerOpts),
+		     lists:foreach(
+		       fun(_) ->
+			       ssl:send(ServerSocket, "some random message\r\n")
+		       end, lists:seq(1, 20)),
+		     ssl:close(ServerSocket)
+	     end,
+    spawn_link(Server),
+    {ok, Socket} = ssl:connect(Hostname, Port, [{active, false} | ClientOpts]),
+    Result = tls_closed_in_active_once_loop(Socket),
+    ssl:close(Socket),
+    case Result of
+	ok -> ok;
+	_ -> ct:fail(Result)
+    end.
+
 %%--------------------------------------------------------------------
 tls_tcp_msg() ->
     [{doc,"Test what happens when a tcp tries to connect, i,e. a bad (ssl) packet is sent first"}].
-- 
2.26.2

openSUSE Build Service is sponsored by