File 7952-OTP-19221-httpc-timeout-on-handle_answer.patch of Package erlang

From c47436b27b4a467f385b46671093da8ab280bbc5 Mon Sep 17 00:00:00 2001
From: Konrad Pietrzak <konrad@erlang.org>
Date: Fri, 6 Sep 2024 14:01:56 +0200
Subject: [PATCH 2/2] OTP-19221 httpc timeout on handle_answer

---
 lib/inets/src/http_client/httpc.erl          | 56 +++++++++++----
 lib/inets/src/http_client/httpc_handler.erl  | 15 ++--
 lib/inets/src/http_client/httpc_request.erl  | 50 +++++++-------
 lib/inets/src/http_client/httpc_response.erl |  2 +-
 lib/inets/test/httpc_SUITE.erl               | 72 ++++++++++++++------
 5 files changed, 127 insertions(+), 68 deletions(-)

diff --git a/lib/inets/doc/src/httpc.xml b/lib/inets/doc/src/httpc.xml
index 0ac74f14f3..ce9123d2e7 100644
--- a/lib/inets/doc/src/httpc.xml
+++ b/lib/inets/doc/src/httpc.xml
@@ -383,6 +383,11 @@
 		<c>{http, ReplyInfo}</c>.</p>
 	      </item>
 
+              <tag><c><![CDATA[alias/0]]></c></tag>
+              <item>
+                      <p>Messages are sent to this special reference in the format <c>{http, ReplyInfo}</c>.</p>
+              </item>
+
               <tag><c><![CDATA[function/1]]></c></tag>
               <item>
 	        <p>Information is delivered to the receiver through calls 
diff --git a/lib/inets/src/http_client/httpc.erl b/lib/inets/src/http_client/httpc.erl
index 0ac74f14f3..ce9123d2e7 100644
--- a/lib/inets/src/http_client/httpc.erl
+++ b/lib/inets/src/http_client/httpc.erl
@@ -1205,14 +1208,15 @@ handle_request(Method, Url,
 			       started       = Started,
 			       unix_socket   = UnixSocket,
 			       ipv6_host_with_brackets = BracketedHost,
-			       request_options       = Options},
-	    case httpc_manager:request(Request, profile_name(Profile)) of
-		{ok, RequestId} ->
-		    handle_answer(RequestId, Sync, Options);
-		{error, Reason} ->
-		    {error, Reason}
-	    end
-	end
+			       request_options         = Options},
+            case httpc_manager:request(Request, profile_name(Profile)) of
+                {ok, RequestId} ->
+                    handle_answer(RequestId, Receiver, Sync, Options,
+                                  element(#http_options.timeout, HTTPOptions));
+                {error, Reason} ->
+                    {error, Reason}
+            end
+        end
     catch
 	error:{noproc, _} ->
 	    {error, {not_started, Profile}};
@@ -1264,20 +1268,41 @@ mk_chunkify_fun(ProcessBody) ->
     end.
 
 
-handle_answer(RequestId, false, _) ->
+handle_answer(RequestId, _, false, _, _) ->
     {ok, RequestId};
-handle_answer(RequestId, true, Options) ->
+handle_answer(RequestId, ClientAlias, true, Options, Timeout) ->
     receive
         {http, {RequestId, {ok, saved_to_file}}} ->
+            true = unalias(ClientAlias),
             {ok, saved_to_file};
         {http, {RequestId, {error, Reason}}} ->
+            true = unalias(ClientAlias),
             {error, Reason};
-        {http, {RequestId, {ok, {StatusLine,Headers,BinBody}}}} ->
+        {http, {RequestId, {ok, {StatusLine, Headers, BinBody}}}} ->
+            true = unalias(ClientAlias),
             Body = maybe_format_body(BinBody, Options),
             {ok, {StatusLine, Headers, Body}};
-        {http, {RequestId, {ok, {StatusCode,BinBody}}}} ->
+        {http, {RequestId, {ok, {StatusCode, BinBody}}}} ->
+            true = unalias(ClientAlias),
             Body = maybe_format_body(BinBody, Options),
             {ok, {StatusCode, Body}}
+    after Timeout ->
+            cancel_request(RequestId),
+            true = unalias(ClientAlias),
+            receive
+                {http, {RequestId, {ok, saved_to_file}}} ->
+                    {ok, saved_to_file};
+                {http, {RequestId, {error, Reason}}} ->
+                    {error, Reason};
+                {http, {RequestId, {ok, {StatusLine, Headers, BinBody}}}} ->
+                    Body = maybe_format_body(BinBody, Options),
+                    {ok, {StatusLine, Headers, Body}};
+                {http, {RequestId, {ok, {StatusCode, BinBody}}}} ->
+                    Body = maybe_format_body(BinBody, Options),
+                    {ok, {StatusCode, Body}}
+            after 0 ->
+                    {error, timeout}
+            end
     end.
 
 maybe_format_body(BinBody, Options) ->
@@ -1474,6 +1499,8 @@ request_options_defaults() ->
 		ok;
 	   (Value) when is_function(Value, 1) ->
 		ok;
+           (Value) when is_reference(Value) ->
+                ok;
 	   (_) ->
 		error
 	end,
@@ -1495,7 +1522,7 @@ request_options_defaults() ->
      {body_format,             string,    VerifyBodyFormat},
      {full_result,             true,      VerifyFullResult},
      {headers_as_is,           false,     VerifyHeaderAsIs},
-     {receiver,                self(),    VerifyReceiver},
+     {receiver,                alias(),    VerifyReceiver},
      {socket_opts,             undefined, VerifySocketOpts},
      {ipv6_host_with_brackets, false,     VerifyBrackets}
     ]. 
@@ -1559,6 +1587,8 @@ request_options_sanity_check(Opts) ->
 	    case proplists:get_value(receiver, Opts) of
 		Pid when is_pid(Pid) andalso (Pid =:= self()) ->
 		    ok;
+                Reference when is_reference(Reference) ->
+                    ok;
 		BadReceiver ->
 		    throw({error, {bad_options_combo, 
 				   [{sync, true}, {receiver, BadReceiver}]}})
diff --git a/lib/inets/src/http_client/httpc_handler.erl b/lib/inets/src/http_client/httpc_handler.erl
index ad8694c9f2..4a4fedc149 100644
--- a/lib/inets/src/http_client/httpc_handler.erl
+++ b/lib/inets/src/http_client/httpc_handler.erl
@@ -482,7 +482,6 @@ do_handle_info({Proto, _Socket, Data},
   when (Proto =:= tcp) orelse 
        (Proto =:= ssl) orelse 
        (Proto =:= httpc_handler) ->
-
     try Module:Function([Data | Args]) of
 	{ok, Result} ->
 	    handle_http_msg(Result, State); 
@@ -1320,9 +1319,9 @@ handle_server_closing(State = #state{headers = Headers}) ->
     end.
 
 answer_request(#request{id = RequestId, from = From, request_options = Options} = Request, Msg,
-	       #state{session      = Session, 
-		      timers       = Timers, 
-		      profile_name = ProfileName} = State) ->
+               #state{session      = Session,
+                      timers       = Timers,
+                  profile_name = ProfileName} = State) ->
     Answer = format_answer(Msg, Options),
     httpc_response:send(From, Answer),
     RequestTimers = Timers#timers.request_timers,
@@ -1718,10 +1717,10 @@ format_address({[$[|T], Port}) ->
 format_address(HostPort) ->
     HostPort.
 
-format_answer(Res0, Options) ->
+format_answer(Res, Options) ->
     FullResult = proplists:get_value(full_result, Options, true),
     Sync = proplists:get_value(sync, Options, true),
-    do_format_answer(Res0, FullResult, Sync).
+    do_format_answer(Res, FullResult, Sync).
 do_format_answer({Ref, StatusLine}, _, Sync) when is_atom(StatusLine) ->
     case Sync of
         true ->
@@ -1742,9 +1741,9 @@ do_format_answer({Ref, {StatusLine, Headers, BinBody}}, true, Sync) ->
             {Ref, {ok, {StatusLine, Headers, BinBody}}};
         _ ->
             {Ref, {StatusLine, Headers, BinBody}}
-        end;
+    end;
 do_format_answer({Ref, {StatusLine, _, BinBody}}, false, Sync) ->
-        {_, Status, _} = StatusLine,
+    {_, Status, _} = StatusLine,
     case Sync of
         true ->
             {Ref, {ok, {Status, BinBody}}};
diff --git a/lib/inets/src/http_client/httpc_request.erl b/lib/inets/src/http_client/httpc_request.erl
index 23c7156c02..364be6e856 100644
--- a/lib/inets/src/http_client/httpc_request.erl
+++ b/lib/inets/src/http_client/httpc_request.erl
@@ -56,32 +56,32 @@ send(SendAddr, #session{socket = Socket, socket_type = SocketType}, Request) ->
     send(SendAddr, Socket, SocketType, Request).
     
 send(SendAddr, Socket, SocketType,
-     #request{method        = Method,
-	      path              = Path,
-	      pquery            = Query,
-	      headers           = Headers,
-	      content           = Content,
-	      address           = Address,
-	      abs_uri           = AbsUri,
-	      headers_as_is     = HeadersAsIs,
-	      settings          = HttpOptions,
-	      userinfo          = UserInfo,
-	      request_options   = Options}) ->
-    
+     #request{method          = Method,
+              path            = Path,
+              pquery          = Query,
+              headers         = Headers,
+              content         = Content,
+              address         = Address,
+              abs_uri         = AbsUri,
+              headers_as_is   = HeadersAsIs,
+              settings        = HttpOptions,
+              userinfo        = UserInfo,
+              request_options = Options}) ->
+
     ?hcrt("send",
-	  [{send_addr,              SendAddr},
-	   {socket,                 Socket},
-	   {method,                 Method},
-	   {path,                   Path},
-	   {pquery,                 Query},
-	   {headers,                Headers},
-	   {content,                Content},
-	   {address,                Address},
-	   {abs_uri,                AbsUri},
-	   {headers_as_is,          HeadersAsIs},
-	   {settings,               HttpOptions},
-	   {userinfo,               UserInfo},
-	   {request_options,        Options}]),
+          [{send_addr,       SendAddr},
+           {socket,          Socket},
+           {method,          Method},
+           {path,            Path},
+           {pquery,          Query},
+           {headers,         Headers},
+           {content,         Content},
+           {address,         Address},
+           {abs_uri,         AbsUri},
+           {headers_as_is,   HeadersAsIs},
+           {settings,        HttpOptions},
+           {userinfo,        UserInfo},
+           {request_options, Options}]),
 
     TmpHdrs = handle_user_info(UserInfo, Headers),
 
diff --git a/lib/inets/src/http_client/httpc_response.erl b/lib/inets/src/http_client/httpc_response.erl
index 1dd0bdec66..9ebea9bdbc 100644
--- a/lib/inets/src/http_client/httpc_response.erl
+++ b/lib/inets/src/http_client/httpc_response.erl
@@ -151,7 +151,7 @@ result(Response = {{_,Code,_}, _, _}, Request) when (Code div 100) =:= 5 ->
 result(Response, Request) -> 
     transparent(Response, Request).
 
-send(Receiver, Msg) when is_pid(Receiver) ->
+send(Receiver, Msg) when is_pid(Receiver); is_reference(Receiver) ->
     Receiver ! {http, Msg};
 send(Receiver, Msg) when is_function(Receiver) ->
     (catch Receiver(Msg));
diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl
index a3149e7f26..bd62de9062 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -356,6 +356,9 @@ init_per_testcase(Case, Config) when Case == post;
 				     Case == post_stream ->
     ct:timetrap({seconds, 30}),
     Config;
+init_per_testcase(async, Config) ->
+    {ok,Pid} = inets:start(httpc, [{profile, async}], stand_alone),
+    [{httpc_pid, Pid} | Config];
 init_per_testcase(_Case, Config) ->
     Config.
 
@@ -381,6 +384,9 @@ end_per_testcase(Case, Config)
             ct:log("Not cleaning up because test case status was ~p", [Status]),
             ok
     end;
+end_per_testcase(async, Config) ->
+    Pid = proplists:get_value(httpc_pid, Config),
+    inets:stop(httpc, Pid);
 end_per_testcase(_Case, _Config) ->
     ok.
 
@@ -565,21 +571,21 @@ async() ->
     [{doc, "Test an asynchrony http request."}].
 async(Config) when is_list(Config) ->
     Request  = {url(group_name(Config), "/dummy.html", Config), []},
-
+    HttpcPid = proplists:get_value(httpc_pid, Config),
     {ok, RequestId} =
-	httpc:request(get, Request, [], [{sync, false}]),
+        httpc:request(get, Request, [], [{sync, false}]),
     Body =
-	receive
-	    {http, {RequestId, {{_, 200, _}, _, BinBody}}} ->
-		BinBody;
-	    {http, Msg} ->
-		ct:fail(Msg)
-	end,
+        receive
+            {http, {RequestId, {{_, 200, _}, _, BinBody}}} ->
+                BinBody;
+            {http, Msg} ->
+                ct:fail(Msg)
+        end,
     inets_test_lib:check_body(binary_to_list(Body)),
     %% Check full result false option for async request
     {ok, RequestId2} =
         httpc:request(get, Request, [?SSL_NO_VERIFY], [{sync, false},
-                                                       {full_result, false}], ?profile(Config)),
+                                         {full_result, false}]),
     Body2 =
         receive
             {http, {RequestId2, {200, BinBody2}}} ->
@@ -588,6 +594,19 @@ async(Config) when is_list(Config) ->
                 ct:fail(Msg2)
         end,
     inets_test_lib:check_body(binary_to_list(Body2)),
+
+    %% Check receiver alias() option for async request with stand_alone httpc
+    {ok, RequestId3} =
+        httpc:request(get, Request, [?SSL_NO_VERIFY], [{sync, false},
+                                         {receiver, alias()}], HttpcPid),
+    Body3 =
+        receive
+            {http, {RequestId3, {{_, 200, _}, _, BinBody3}}} ->
+                BinBody3;
+            {http, Msg3} ->
+                ct:fail(Msg3)
+        end,
+    inets_test_lib:check_body(binary_to_list(Body3)),
     {ok, NewRequestId} =
 	httpc:request(get, Request, [], [{sync, false}]),
     ok = httpc:cancel_request(NewRequestId).
@@ -1594,19 +1613,30 @@ timeout_memory_leak(Config) when is_list(Config) ->
     {_DummyServerPid, Port} = otp_8739_dummy_server(),
     {ok,Host} = inet:gethostname(),
     Request = {?URL_START ++ Host ++ ":" ++ integer_to_list(Port) ++ "/dummy.html", []},
+    WaitForCancelRequestToFinish =
+        fun F(Handlers = [_ | _]) when is_list(Handlers) -> ct:fail({unexpected_handlers, Handlers});
+            F(Handlers) when is_list(Handlers) -> ok;
+            F(N) when is_integer(N) ->
+                Info = httpc:info(),
+                ct:log("Info: ~p", [Info]),
+                {value, {handlers, Handlers}} =
+                    lists:keysearch(handlers, 1, Info),
+                case Handlers of
+                    [] ->
+                        ok;
+                    _ ->
+                        ct:sleep(1)
+                end,
+                case N of
+                    0 ->
+                        F(Handlers);
+                    _ ->
+                        F(N-1)
+                end
+        end,
     case httpc:request(get, Request, [{connect_timeout, 500}, {timeout, 1}], [{sync, true}]) of
 	{error, timeout} ->
-	    %% And now we check the size of the handler db
-	    Info = httpc:info(),
-	    ct:log("Info: ~p", [Info]),
-	    {value, {handlers, Handlers}} =
-		lists:keysearch(handlers, 1, Info),
-	    case Handlers of
-		[] ->
-		    ok;
-		_ ->
-		    ct:fail({unexpected_handlers, Handlers})
-	    end;
+       WaitForCancelRequestToFinish(5);
 	Unexpected ->
 	    ct:fail({unexpected, Unexpected})
     end.
-- 
2.43.0

openSUSE Build Service is sponsored by