Skip to content

Commit

Permalink
OTP-19221 httpc timeout on handle_answer
Browse files Browse the repository at this point in the history
  • Loading branch information
Whaileee committed Sep 24, 2024
1 parent 2cfff73 commit 523d0bb
Show file tree
Hide file tree
Showing 5 changed files with 64 additions and 25 deletions.
6 changes: 6 additions & 0 deletions lib/inets/doc/src/httpc.xml
Original file line number Diff line number Diff line change
Expand Up @@ -379,6 +379,12 @@
ReplyInfo}</c>.</p>
</item>

<tag><c>alias()</c></tag>
<item>
<p>Messages are sent to this special reference in the same format
as <c>pid()</c>.</p>
</item>

<tag><c>function/1</c></tag>
<item>
<p>Information is delivered to the receiver through calls to the
Expand Down
35 changes: 31 additions & 4 deletions lib/inets/src/http_client/httpc.erl
Original file line number Diff line number Diff line change
Expand Up @@ -806,7 +806,8 @@ handle_request(Method, Url,
request_options = Options},
case httpc_manager:request(Request, profile_name(Profile)) of
{ok, RequestId} ->
handle_answer(RequestId, Sync, Options);
handle_answer(RequestId, Receiver, Sync, Options,
element(#http_options.timeout, HTTPOptions));
{error, Reason} ->
{error, Reason}
end
Expand Down Expand Up @@ -862,20 +863,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}}} ->
unalias(ClientAlias),
{ok, saved_to_file};
{http, {RequestId, {error, Reason}}} ->
unalias(ClientAlias),
{error, Reason};
{http, {RequestId, {ok, {StatusLine,Headers,BinBody}}}} ->
unalias(ClientAlias),
Body = maybe_format_body(BinBody, Options),
{ok, {StatusLine, Headers, Body}};
{http, {RequestId, {ok, {StatusCode,BinBody}}}} ->
unalias(ClientAlias),
Body = maybe_format_body(BinBody, Options),
{ok, {StatusCode, Body}}
after Timeout ->
cancel_request(RequestId),
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) ->
Expand Down Expand Up @@ -1064,6 +1086,8 @@ request_options_defaults() ->
ok;
(Value) when is_function(Value, 1) ->
ok;
(Value) when is_reference(Value) ->
ok;
(_) ->
error
end,
Expand All @@ -1085,7 +1109,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}
].
Expand Down Expand Up @@ -1139,6 +1163,7 @@ request_options([{Key, DefaultVal, Verify} | Defaults], Options, Acc) ->
BodyFormat :: string() | binary() | atom(),
SocketOpt :: term(),
Receiver :: pid()
| reference()
| fun((term()) -> term())
| { ReceiverModule::atom()
, ReceiverFunction::atom()
Expand All @@ -1149,6 +1174,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}]}})
Expand Down
20 changes: 2 additions & 18 deletions lib/inets/src/http_client/httpc_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -519,7 +519,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);
Expand Down Expand Up @@ -1738,10 +1737,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 ->
Expand Down Expand Up @@ -1773,18 +1772,3 @@ do_format_answer({Ref, {StatusLine, _, BinBody}}, false, Sync) ->
end;
do_format_answer({Ref, {error, _Reason} = Error}, _, _) ->
{Ref, Error}.


clobber_and_retry(#state{session = #session{id = Id,
type = Type},
profile_name = ProfileName,
pipeline = Pipeline,
keep_alive = KeepAlive} = State) ->
%% Clobber session
(catch httpc_manager:delete_session(Id, ProfileName)),
case Type of
pipeline ->
maybe_retry_queue(Pipeline, State);
_ ->
maybe_retry_queue(KeepAlive, State)
end.
3 changes: 2 additions & 1 deletion lib/inets/src/http_client/httpc_response.erl
Original file line number Diff line number Diff line change
Expand Up @@ -150,7 +150,8 @@ 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)
orelse is_reference(Receiver) ->
Receiver ! {http, Msg};
send(Receiver, Msg) when is_function(Receiver) ->
(catch Receiver(Msg));
Expand Down
25 changes: 23 additions & 2 deletions lib/inets/test/httpc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -354,13 +354,19 @@ 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.

end_per_testcase(pipeline, _Config) ->
inets:stop(httpc, pipeline);
end_per_testcase(persistent_connection, _Config) ->
inets:stop(httpc, persistent);
end_per_testcase(async, Config) ->
Pid = proplists:get_value(httpc_pid, Config),
inets:stop(httpc, Pid);
end_per_testcase(Case, Config)
when Case == server_closing_connection_on_first_response;
Case == server_closing_connection_on_second_response ->
Expand Down Expand Up @@ -567,6 +573,7 @@ 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}]),
Expand All @@ -578,10 +585,11 @@ async(Config) when is_list(Config) ->
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)),
httpc:request(get, Request, [], [{sync, false},
{full_result, false}]),
Body2 =
receive
{http, {RequestId2, {200, BinBody2}}} ->
Expand All @@ -590,6 +598,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, [], [{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).
Expand Down

0 comments on commit 523d0bb

Please sign in to comment.