File 5241-inets-update-function-heads-and-types.patch of Package erlang

From 8cf960cc2cc14a57c86fa6478f86e7f819da9b0b Mon Sep 17 00:00:00 2001
From: Kiko Fernandez-Reyes <kiko@erlang.org>
Date: Mon, 12 Dec 2022 15:03:28 +0100
Subject: [PATCH] inets: update function heads and types

Updates records, function headers, etc so that the `inets` app can be type
checked by type checkers such as eqWAlizer.
---
 lib/inets/src/http_client/httpc_handler.erl  | 27 ++++++++------------
 lib/inets/src/http_client/httpc_internal.hrl |  2 +-
 2 files changed, 12 insertions(+), 17 deletions(-)

diff --git a/lib/inets/src/http_client/httpc_handler.erl b/lib/inets/src/http_client/httpc_handler.erl
index 61e977777b..1868d9351a 100644
--- a/lib/inets/src/http_client/httpc_handler.erl
+++ b/lib/inets/src/http_client/httpc_handler.erl
@@ -44,8 +44,8 @@
 
 -record(timers, 
         {
-          request_timers = [] :: [reference()],
-          queue_timer         :: reference() | 'undefined'
+          request_timers = [] :: [reference() | {reference(), term()}],
+          queue_timer         :: reference() | undefined
          }).
 
 -record(state, 
@@ -622,13 +622,11 @@ do_handle_info({ssl_closed, _}, State = #state{request = undefined}) ->
     {stop, normal, State};
 
 %%% Error cases
-do_handle_info({tcp_closed, _}, #state{session = Session0} = State) ->
-    Socket  = Session0#session.socket,
+do_handle_info({tcp_closed, _}, #state{session = #session{socket = Socket}=Session0} = State) ->
     Session = Session0#session{socket = {remote_close, Socket}},
     %% {stop, session_remotly_closed, State};
     {stop, normal, State#state{session = Session}};
-do_handle_info({ssl_closed, _}, #state{session = Session0} = State) ->
-    Socket  = Session0#session.socket,
+do_handle_info({ssl_closed, _}, #state{session = #session{socket = Socket}=Session0} = State) ->
     Session = Session0#session{socket = {remote_close, Socket}},
     %% {stop, session_remotly_closed, State};
     {stop, normal, State#state{session = Session}};
@@ -878,7 +876,7 @@ connect_and_send_upgrade_request(Address, Request, #state{options = Options0} =
     end.
 
 handler_info(#state{request     = Request, 
-		    session     = Session, 
+		    session     = #session{socket = Socket}=Session,
 		    status_line = _StatusLine, 
 		    pipeline    = Pipeline, 
 		    keep_alive  = KeepAlive, 
@@ -906,8 +904,7 @@ handler_info(#state{request     = Request,
 			  queue:len(KeepAlive)
 		  end,
     Scheme     = Session#session.scheme, 
-    Socket     = Session#session.socket, 
-    SocketType = Session#session.socket_type, 
+    SocketType = Session#session.socket_type,
 
     SocketOpts  = http_transport:getopts(SocketType, Socket), 
     SocketStats = http_transport:getstat(SocketType, Socket), 
@@ -983,11 +980,10 @@ handle_http_body(Body, #state{headers = Headers,
 handle_http_body(_Body, #state{request = #request{method = head}} = State) ->
     handle_response(State#state{body = <<>>});
 
-handle_http_body(Body, #state{headers       = Headers, 
+handle_http_body(Body, #state{headers       = #http_response_h{'transfer-encoding' = TransferEnc}=Headers,
 			      max_body_size = MaxBodySize,
 			      status_line   = {_,Code, _},
 			      request       = Request} = State) ->
-    TransferEnc = Headers#http_response_h.'transfer-encoding',
     case case_insensitive_header(TransferEnc) of
         "chunked" ->
 	    try http_chunk:decode(Body, State#state.max_body_size, 
@@ -1064,7 +1060,7 @@ handle_response(#state{status = Status0} = State0) when Status0 =/= new ->
     RequestWithIpFamily = add_ipfamily_to_request(Request, Options#options.ipfamily),
     case httpc_response:result({StatusLine, Headers, Body}, RequestWithIpFamily) of
 	%% 100-continue
-	continue -> 
+	continue ->
 	    %% Send request body
 	    {_, RequestBody} = Request#request.content,
 	    send_raw(Session, RequestBody),
@@ -1080,7 +1076,7 @@ handle_response(#state{status = Status0} = State0) when Status0 =/= new ->
 
 	%% Ignore unexpected 100-continue response and receive the
 	%% actual response that the server will send right away. 
-	{ignore, Data} -> 
+	{ignore, Data} ->
 	    Relaxed = (Request#request.settings)#http_options.relaxed,
 	    MFA     = {httpc_response, parse,
 		       [State#state.max_header_size, Relaxed]}, 
@@ -1116,8 +1112,7 @@ handle_cookies(_,_, #options{cookies = disabled}, _) ->
 %% so the user will have to call a store command.
 handle_cookies(_,_, #options{cookies = verify}, _) ->
     ok;
-handle_cookies(Headers, Request, #options{cookies = enabled}, ProfileName) ->
-    {Host, _ } = Request#request.address,
+handle_cookies(Headers, #request{address = {Host, _}}=Request, #options{cookies = enabled}, ProfileName) ->
     Cookies = httpc_cookie:cookies(Headers#http_response_h.other, 
 				  Request#request.path, Host),
     httpc_manager:store_cookies(Cookies, Request#request.address,
@@ -1135,7 +1130,7 @@ handle_queue(#state{status = pipeline} = State, Data) ->
     handle_pipeline(State, Data).
 
 handle_pipeline(#state{status       = pipeline, 
-		       session      = Session,
+		       session      = #session{}=Session,
 		       profile_name = ProfileName,
 		       options      = #options{pipeline_timeout = TimeOut}} = State,
 		Data) ->
diff --git a/lib/inets/src/http_client/httpc_internal.hrl b/lib/inets/src/http_client/httpc_internal.hrl
index 709683ffb0..8e35bfef4f 100644
--- a/lib/inets/src/http_client/httpc_internal.hrl
+++ b/lib/inets/src/http_client/httpc_internal.hrl
@@ -127,7 +127,7 @@
 	  %% {{Host, Port}, HandlerPid}
 	  id, 
 
-	  client_close :: 'undefined' | boolean(),
+	  client_close = false :: boolean(),
 
 	  %% http (HTTP/TCP) | https (HTTP/SSL/TCP)
 	  scheme, 
-- 
2.35.3

openSUSE Build Service is sponsored by