File 2941-ssl-Improve-active-emulation.patch of Package erlang

From daebbe4f30d82cf6667e9d4f09452bc1d5aace69 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Thu, 19 Nov 2020 13:19:03 +0100
Subject: [PATCH 1/2] ssl: Improve active emulation

If using active once sockets and the socket is closed and all data is already
delivered it is desirable that ssl:setopts(S, [{active, once}] shall succeed
and an active close message be sent instead of ssl:setopts returning {error, closed}
This how gen_tcp/inet behaves.

Example of client side:

> {ok, S} = ssl:connect("localhost", 9999, [{active, false}]).
{ok,{sslsocket,{gen_tcp,#Port<0.10>,tls_connection,
                        undefined},
               [<0.120.0>,<0.119.0>]}}
> ssl:setopts(S, [{active, once}]).
ok
> flush().
Shell got {ssl,{sslsocket,{gen_tcp,#Port<0.10>,tls_connection,undefined},
                          [<0.120.0>,<0.119.0>]},
               "foo"}
ok
> ssl:setopts(S, [{active, once}]).
ok
> flush().
Shell got {ssl_closed,
              {sslsocket,
                  {gen_tcp,#Port<0.10>,tls_connection,undefined},
                  [<0.120.0>,<0.119.0>]}}
ok
> ssl:setopts(S, [{active, once}]).
{error,closed}
> flush().
ok
---
 lib/ssl/src/ssl_connection.erl |  4 ++--
 lib/ssl/src/tls_connection.erl | 23 +++++++++++++++--------
 lib/ssl/test/tls_api_SUITE.erl |  4 +---
 3 files changed, 18 insertions(+), 13 deletions(-)

diff --git a/lib/ssl/src/ssl_connection.erl b/lib/ssl/src/ssl_connection.erl
index c50135881c..0b600fe985 100644
--- a/lib/ssl/src/ssl_connection.erl
+++ b/lib/ssl/src/ssl_connection.erl
@@ -2898,13 +2898,13 @@ 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},
+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}),
-    {stop,{shutdown, peer_close}, 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) ->
     case Connection:next_event(StateName0, no_record, State0) of
diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl
index b053a0258d..357bd46439 100644
--- a/lib/ssl/src/tls_connection.erl
+++ b/lib/ssl/src/tls_connection.erl
@@ -1294,9 +1294,8 @@ handle_info({CloseTag, Socket}, StateName,
                                    role = Role,
                                    socket = Socket,
                                    close_tag = CloseTag},
+                   start_or_recv_from = From,
                    socket_options = #socket_options{active = Active},
-                   protocol_buffers = #protocol_buffers{tls_cipher_texts = CTs},
-                   user_data_buffer = {_,BufferSize,_},
                    protocol_specific = PS} = State) ->
 
     %% Note that as of TLS 1.1,
@@ -1304,7 +1303,7 @@ handle_info({CloseTag, Socket}, StateName,
     %% session not be resumed.  This is a change from TLS 1.0 to conform
     %% with widespread implementation practice.
 
-    case (Active == false) andalso ((CTs =/= []) or (BufferSize =/= 0)) of
+    case (Active == false) andalso (From == undefined) of
         false ->
             %% As invalidate_sessions here causes performance issues,
             %% we will conform to the widespread implementation
@@ -1320,11 +1319,19 @@ handle_info({CloseTag, Socket}, StateName,
             ssl_connection:handle_normal_shutdown(Alert#alert{role = Role}, StateName, State),
             {stop, {shutdown, transport_closed}, State};
         true ->
-            %% 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. Set internal active_n to zero 
-            %% to ensure socket close message is sent if there is not enough data to deliver.
-            next_event(StateName, no_record, State#state{protocol_specific = PS#{active_n_toggle => true}})
+            %% Wait for next socket operation (most probably
+            %% ssl:setopts(S, [{active, true | once | N}]) or
+            %% ssl:recv(S, N, Timeout) before closing.  Possible
+            %% buffered data will be deliverd by the code handling
+            %% these options before closing. In the case of the
+            %% peer resetting the connection hard, that is
+            %% we do not receive any close ALERT, and an active once (or possible N)
+            %% strategy is used by the client we want to later trigger a new
+            %% "transport closed" message. This is achieved by setting the internal
+            %% active_n_toggle here which will cause
+            %% this to happen when tls_connection:activate_socket/1
+            %% is called after all data has been deliver.
+            {next_state, StateName, State#state{protocol_specific = PS#{active_n_toggle => true}}, []}
     end;
 handle_info({'EXIT', Sender, Reason}, _,
             #state{protocol_specific = #{sender := Sender}} = State) ->
diff --git a/lib/ssl/test/tls_api_SUITE.erl b/lib/ssl/test/tls_api_SUITE.erl
index 82b785faa4..4184713fd1 100644
--- a/lib/ssl/test/tls_api_SUITE.erl
+++ b/lib/ssl/test/tls_api_SUITE.erl
@@ -843,11 +843,9 @@ tls_closed_in_active_once_loop(Socket) ->
                     tls_closed_in_active_once_loop(Socket);
                 {ssl_closed, Socket} ->
                     ok
-            after 5000 ->
-                    no_ssl_closed_received
             end;
         {error, closed} ->
-            ok
+            {error, ssl_setopt_failed}
     end.
 
 drop_handshakes(Socket, Timeout) ->
-- 
2.26.2

openSUSE Build Service is sponsored by