File 1036-inets-Handle-that-inet-ssl-setopt-can-return-error.patch of Package erlang

From 6881c9c532c7d9d19f039e2aa80c1d740295d220 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Thu, 11 Jun 2020 09:53:30 +0200
Subject: [PATCH 3/3] inets: Handle that inet/ssl:setopt can return error

---
 lib/ftp/src/ftp.erl                           |  4 +-
 lib/inets/src/http_client/httpc_handler.erl   | 18 ++++----
 lib/inets/src/http_lib/http_transport.erl     |  6 +++
 .../src/http_server/httpd_request_handler.erl | 45 ++++++++++---------
 4 files changed, 41 insertions(+), 32 deletions(-)

diff --git a/lib/inets/src/ftp/ftp.erl b/lib/inets/src/ftp/ftp.erl
index dac316fe0b..b94c535467 100644
--- a/lib/inets/src/ftp/ftp.erl
+++ b/lib/inets/src/ftp/ftp.erl
@@ -2274,8 +2274,8 @@ activate_connection(Socket) ->
             activate_connection(ssl, ssl_closed, Socket)
     end.
 
-activate_connection(API, CloseTag, Socket) ->
-    Socket = unwrap_socket(Socket),
+activate_connection(API, CloseTag, Socket0) ->
+    Socket = unwrap_socket(Socket0),
     case API:setopts(Socket, [{active, once}]) of
         ok ->
             ok;
diff --git a/lib/inets/src/http_client/httpc_handler.erl b/lib/inets/src/http_client/httpc_handler.erl
index 3f91ae062c..1f8806d1d8 100644
--- a/lib/inets/src/http_client/httpc_handler.erl
+++ b/lib/inets/src/http_client/httpc_handler.erl
@@ -831,8 +831,7 @@ connect_and_send_first_request(Address, Request, #state{options = Options0} = St
                                            headers = undefined,
                                            body = undefined,
                                            status = new},
-                    http_transport:setopts(SocketType,
-                                           Socket, [{active, once}]),
+                    activate_once(Session),
                     NewState = activate_request_timeout(TmpState),
                     {ok, NewState};
                 {error, Reason} ->
@@ -1238,7 +1237,12 @@ case_insensitive_header(Str) ->
     Str.
 
 activate_once(#session{socket = Socket, socket_type = SocketType}) ->
-    http_transport:setopts(SocketType, Socket, [{active, once}]).
+    case http_transport:setopts(SocketType, Socket, [{active, once}]) of
+        ok ->
+            ok;
+        {error, _} -> %% inet can return einval instead of closed
+            self() ! {http_transport:close_tag(SocketType), Socket}
+    end.
 
 close_socket(#session{socket = {remote_close,_}}) ->
     ok;
@@ -1581,8 +1585,7 @@ send_raw(SocketType, Socket, ProcessBody, Acc) ->
             end
     end.
 
-tls_tunnel(Address, Request, #state{session = #session{socket = Socket, 
-						       socket_type = SocketType} = Session} = State, 
+tls_tunnel(Address, Request, #state{session = #session{} = Session} = State, 
 	   ErrorHandler) ->
     UpgradeRequest = tls_tunnel_request(Request), 
     case httpc_request:send(Address, Session, UpgradeRequest) of
@@ -1594,8 +1597,7 @@ tls_tunnel(Address, Request, #state{session = #session{socket = Socket,
 				       init_status_line(UpgradeRequest),
 				   headers = undefined,
 				   body = undefined},
-	    http_transport:setopts(SocketType,
-				   Socket, [{active, once}]),
+	    activate_once(Session),
 	    NewState = activate_request_timeout(TmpState),
 	    {ok, NewState#state{status = {ssl_tunnel, Request}}};
 	{error, Reason} ->
@@ -1661,7 +1663,7 @@ tls_upgrade(#state{status =
 			type = SessionType,
 			client_close = ClientClose},
 	    httpc_request:send(Address, Session, Request), 
-	    http_transport:setopts(SocketType, TLSSocket, [{active, once}]),
+            activate_once(Session),
 	    NewState = State#state{session = Session,
 				   request = Request,
 				   mfa = init_mfa(Request, State),
diff --git a/lib/inets/src/http_lib/http_transport.erl b/lib/inets/src/http_lib/http_transport.erl
index d5e1d71336..d2148a3a8a 100644
--- a/lib/inets/src/http_lib/http_transport.erl
+++ b/lib/inets/src/http_lib/http_transport.erl
@@ -27,6 +27,7 @@
 	 listen/4, listen/5,
 	 accept/2, accept/3, 
 	 close/2,
+         close_tag/1,
 	 send/3, 
 	 controlling_process/3, 
 	 setopts/3, getopts/2, getopts/3, 
@@ -459,6 +460,11 @@ ipv6_name({A, B, C, D, E, F, G, H}) ->
 	http_util:integer_to_hexlist(H).
 
 
+close_tag(ip_comm) ->
+    tcp_closed;
+close_tag(_) ->
+    ssl_closed.
+
 %%%========================================================================
 %%% Internal functions
 %%%========================================================================
diff --git a/lib/inets/src/http_server/httpd_request_handler.erl b/lib/inets/src/http_server/httpd_request_handler.erl
index e82b1c46e9..65ca1181e8 100644
--- a/lib/inets/src/http_server/httpd_request_handler.erl
+++ b/lib/inets/src/http_server/httpd_request_handler.erl
@@ -162,8 +162,9 @@ continue_init(Manager, ConfigDB, SocketType, Socket, Peername, Sockname,
 		   mfa                    = MFA,
                    chunk                   = chunk_start(MaxChunk)},
     
-    http_transport:setopts(SocketType, Socket, 
-			   [binary, {packet, 0}, {active, once}]),
+    ok = http_transport:setopts(SocketType, Socket, 
+                                [binary, {packet, 0}]),
+    activate_once(Socket, SocketType),
     NewState =  data_receive_counter(activate_request_timeout(State), httpd_util:lookup(ConfigDB, minimum_bytes_per_second, false)),
      gen_server:enter_loop(?MODULE, [], NewState).
 
@@ -242,7 +243,7 @@ handle_info({Proto, Socket, Data},
             NewState = handle_chunk(Module, Function, Args, State),
             {noreply, NewState};
 	NewMFA ->
-	    http_transport:setopts(SockType, Socket, [{active, once}]),
+	    activate_once(Socket, SockType),
 	    case NewDataSize of
 		undefined ->
 		    {noreply, State#state{mfa = NewMFA}};
@@ -363,9 +364,7 @@ handle_msg({{continue, Chunk}, Module, Function, Args}, #state{chunk = {_, CbSta
     handle_internal_chunk(State#state{chunk = {continue, CbState},
                                       body = Chunk}, Module, Function, Args);
 handle_msg({continue, Module, Function, Args}, 	#state{mod = ModData} = State) ->
-    http_transport:setopts(ModData#mod.socket_type, 
-                           ModData#mod.socket, 
-                           [{active, once}]),
+    activate_once(ModData#mod.socket, ModData#mod.socket_type),
     {noreply, State#state{mfa = {Module, Function, Args}}};
 handle_msg({last, Body}, #state{headers = Headers, chunk = {_, CbState}} = State) -> 
     NewHeaders = Headers#http_request_h{'content-length' = integer_to_list(size(Body))},
@@ -471,9 +470,7 @@ handle_body(#state{headers = Headers, body = Body,
 	"chunked" ->
 	    try http_chunk:decode(Body, MaxBodySize, MaxHeaderSize) of
                 {Module, Function, Args} ->
-		    http_transport:setopts(ModData#mod.socket_type, 
-					   ModData#mod.socket, 
-					   [{active, once}]),
+                    activate_once(ModData#mod.socket, ModData#mod.socket_type),
 		    {noreply, State#state{mfa = 
                                               {Module, Function, Args},
                                           chunk = chunk_start(MaxChunk)}};
@@ -502,17 +499,13 @@ handle_body(#state{headers = Headers, body = Body,
                         %% This is the case that the we need more data to complete
                         %% the body but chunking to the mod_esi user is not enabled.
                         {Module, add_chunk = Function,  Args} ->  
-                            http_transport:setopts(ModData#mod.socket_type, 
-						   ModData#mod.socket, 
-						   [{active, once}]),
+                            activate_once(ModData#mod.socket, ModData#mod.socket_type),
 			    {noreply, State#state{mfa = 
 						      {Module, Function, Args}}};
                         %% Chunking to mod_esi user is enabled
                         {ok, {continue, Module, Function, Args}} ->
-                                http_transport:setopts(ModData#mod.socket_type, 
-						   ModData#mod.socket, 
-						   [{active, once}]),
-			    {noreply, State#state{mfa = 
+                            activate_once(ModData#mod.socket, ModData#mod.socket_type),
+                            {noreply, State#state{mfa = 
 						      {Module, Function, Args}}};
                         {ok, {{continue, Chunk}, Module, Function, Args}} ->
                             handle_internal_chunk(State#state{chunk =  chunk_start(MaxChunk), 
@@ -588,7 +581,7 @@ handle_chunk(http_chunk = Module, decode_data = Function,
                                socket = Socket} = ModData} = State) ->
     {continue, NewCbState} = httpd_response:handle_continuation(ModData#mod{entity_body = 
                                                                                 {continue, BodySoFar, CbState}}),
-    http_transport:setopts(SockType, Socket, [{active, once}]),
+    activate_once(Socket, SockType),                         
     State#state{chunk = {continue, NewCbState}, mfa = {Module, Function, [ChunkSize, TotalChunk, {MaxBodySize, <<>>, 0, MaxHeaderSize}]}};
 
 handle_chunk(http_chunk = Module, decode_size = Function, 
@@ -597,11 +590,11 @@ handle_chunk(http_chunk = Module, decode_size = Function,
                     mod = #mod{socket_type = SockType,
                                socket = Socket} = ModData} = State) ->
     {continue, NewCbState} = httpd_response:handle_continuation(ModData#mod{entity_body = {continue, BodySoFar, CbState}}),
-    http_transport:setopts(SockType, Socket, [{active, once}]),
+    activate_once(Socket, SockType),                         
     State#state{chunk = {continue, NewCbState}, mfa = {Module, Function, [Data, HexList, 0, {MaxBodySize, <<>>, 0, MaxHeaderSize}]}};
 handle_chunk(Module, Function, Args, #state{mod = #mod{socket_type = SockType,
                                                                       socket = Socket}} = State) ->
-    http_transport:setopts(SockType, Socket, [{active, once}]),
+    activate_once(Socket, SockType),
     State#state{mfa = {Module, Function, Args}}.
 
 handle_internal_chunk(#state{chunk = {ChunkState, CbState}, body = Chunk, 
@@ -611,7 +604,7 @@ handle_internal_chunk(#state{chunk = {ChunkState, CbState}, body = Chunk,
     {continue, NewCbState} = httpd_response:handle_continuation(ModData#mod{entity_body = Bodychunk}),
     case Args of
         [<<>> | _] ->
-            http_transport:setopts(SockType, Socket, [{active, once}]),
+            activate_once(Socket, SockType),
             {noreply, State#state{chunk = {continue, NewCbState}, mfa = {Module, Function, Args}}};
         _ ->
             handle_info({dummy, Socket, <<>>}, State#state{chunk = {continue, NewCbState}, 
@@ -675,8 +668,7 @@ handle_next_request(#state{mod = #mod{connection = true} = ModData,
 
     case Data of
 	<<>> ->
-	    http_transport:setopts(ModData#mod.socket_type,
-				   ModData#mod.socket, [{active, once}]),
+            activate_once(ModData#mod.socket, ModData#mod.socket_type),
 	    {noreply, NewState};
 	_ ->
 	    handle_info({dummy, ModData#mod.socket, Data}, NewState)
@@ -751,3 +743,12 @@ body_chunk(first, _, Chunk) ->
     {first, Chunk};
 body_chunk(ChunkState, CbState, Chunk) ->
     {ChunkState, Chunk, CbState}.
+
+activate_once(Socket, SocketType) ->
+    case http_transport:setopts(SocketType, Socket, [{active, once}]) of
+        ok ->
+            ok;
+        {error, _} -> %% inet can return einval instead of closed
+            self() ! {http_transport:close_tag(SocketType), Socket}
+    end.
+
-- 
2.26.2

openSUSE Build Service is sponsored by