File 0163-Fix-non-delivery-of-ssl_closed-message-in-active-onc.patch of Package erlang

From 8abe16c22d9a7d035ad8505b66d5d0611e35b543 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Johannes=20Wei=C3=9Fl?= <jargon@molb.org>
Date: Fri, 19 May 2017 00:47:06 +0200
Subject: [PATCH 1/2] Fix non-delivery of ssl_closed message in active once

The commit 8b10920 (OTP 19.3.1) fixed the non-delivery of final TLS
record in {active, once}, but this causes the ssl_closed message to be
lost when the TCP connection closes before ssl:close/1. The patch
restores the behavior of OTP 18.

This is the second part to fix https://bugs.erlang.org/browse/ERL-420
---
 lib/ssl/src/tls_connection.erl   |  1 +
 lib/ssl/test/ssl_basic_SUITE.erl | 44 ++++++++++++++++++++++++++++++++++++++++
 2 files changed, 45 insertions(+)

diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl
index 96c3ab86e..a7720e19b 100644
--- a/lib/ssl/src/tls_connection.erl
+++ b/lib/ssl/src/tls_connection.erl
@@ -429,6 +429,7 @@ handle_info({CloseTag, Socket}, StateName,
             %% Fixes non-delivery of final TLS record in {active, once}.
             %% Basically allows the application the opportunity to set {active, once} again
             %% and then receive the final message.
+            self() ! {CloseTag, Socket},
             next_event(StateName, no_record, State)
     end;
 handle_info(Msg, StateName, State) ->
diff --git a/lib/ssl/test/ssl_basic_SUITE.erl b/lib/ssl/test/ssl_basic_SUITE.erl
index 58870a341..d13b1b3f2 100644
--- a/lib/ssl/test/ssl_basic_SUITE.erl
+++ b/lib/ssl/test/ssl_basic_SUITE.erl
@@ -240,6 +240,7 @@ error_handling_tests()->
 error_handling_tests_tls()->
     [controller_dies,
      tls_client_closes_socket,
+     tls_closed_in_active_once,
      tls_tcp_error_propagation_in_active_mode,
      tls_tcp_connect,
      tls_tcp_connect_big,
@@ -430,6 +431,7 @@ init_per_testcase(prf, Config) ->
 
 init_per_testcase(TestCase, Config) when TestCase == tls_ssl_accept_timeout;
 					 TestCase == tls_client_closes_socket;
+					 TestCase == tls_closed_in_active_once;
 					 TestCase == tls_downgrade ->
     ssl_test_lib:ct_log_supported_protocol_versions(Config),
     ct:timetrap({seconds, 15}),
@@ -961,6 +963,48 @@ tls_client_closes_socket(Config) when is_list(Config) ->
     ssl_test_lib:check_result(Server, {error,closed}).
 
 %%--------------------------------------------------------------------
+tls_closed_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) ->
+    ClientOpts = ssl_test_lib:ssl_options(client_opts, Config),
+    ServerOpts = ssl_test_lib:ssl_options(server_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:ssl_accept(TcpServerSocket, ServerOpts),
+		     lists:foreach(
+		       fun(_) ->
+			       ssl:send(ServerSocket, "some random message\r\n")
+		       end, lists:seq(1, 20)),
+		     %% Close TCP instead of SSL socket to trigger the bug:
+		     gen_tcp:close(TcpServerSocket),
+		     gen_tcp:close(Listen)
+	     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_closed_in_active_once_loop(Socket) ->
+    ssl:setopts(Socket, [{active, once}]),
+    receive
+	{ssl, Socket, _} ->
+	    tls_closed_in_active_once_loop(Socket);
+	{ssl_closed, Socket} ->
+	    ok
+    after 5000 ->
+	      no_ssl_closed_received
+    end.
+
+%%--------------------------------------------------------------------
 connect_dist() ->
     [{doc,"Test a simple connect as is used by distribution"}].
 
-- 
2.13.0

openSUSE Build Service is sponsored by