Skip to content

Commit 523d0bb

Browse files
committed
OTP-19221 httpc timeout on handle_answer
1 parent 2cfff73 commit 523d0bb

File tree

5 files changed

+64
-25
lines changed

5 files changed

+64
-25
lines changed

lib/inets/doc/src/httpc.xml

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -379,6 +379,12 @@
379379
ReplyInfo}</c>.</p>
380380
</item>
381381

382+
<tag><c>alias()</c></tag>
383+
<item>
384+
<p>Messages are sent to this special reference in the same format
385+
as <c>pid()</c>.</p>
386+
</item>
387+
382388
<tag><c>function/1</c></tag>
383389
<item>
384390
<p>Information is delivered to the receiver through calls to the

lib/inets/src/http_client/httpc.erl

Lines changed: 31 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -806,7 +806,8 @@ handle_request(Method, Url,
806806
request_options = Options},
807807
case httpc_manager:request(Request, profile_name(Profile)) of
808808
{ok, RequestId} ->
809-
handle_answer(RequestId, Sync, Options);
809+
handle_answer(RequestId, Receiver, Sync, Options,
810+
element(#http_options.timeout, HTTPOptions));
810811
{error, Reason} ->
811812
{error, Reason}
812813
end
@@ -862,20 +863,41 @@ mk_chunkify_fun(ProcessBody) ->
862863
end.
863864

864865

865-
handle_answer(RequestId, false, _) ->
866+
handle_answer(RequestId, _, false, _, _) ->
866867
{ok, RequestId};
867-
handle_answer(RequestId, true, Options) ->
868+
handle_answer(RequestId, ClientAlias, true, Options, Timeout) ->
868869
receive
869870
{http, {RequestId, {ok, saved_to_file}}} ->
871+
unalias(ClientAlias),
870872
{ok, saved_to_file};
871873
{http, {RequestId, {error, Reason}}} ->
874+
unalias(ClientAlias),
872875
{error, Reason};
873876
{http, {RequestId, {ok, {StatusLine,Headers,BinBody}}}} ->
877+
unalias(ClientAlias),
874878
Body = maybe_format_body(BinBody, Options),
875879
{ok, {StatusLine, Headers, Body}};
876880
{http, {RequestId, {ok, {StatusCode,BinBody}}}} ->
881+
unalias(ClientAlias),
877882
Body = maybe_format_body(BinBody, Options),
878883
{ok, {StatusCode, Body}}
884+
after Timeout ->
885+
cancel_request(RequestId),
886+
unalias(ClientAlias),
887+
receive
888+
{http, {RequestId, {ok, saved_to_file}}} ->
889+
{ok, saved_to_file};
890+
{http, {RequestId, {error, Reason}}} ->
891+
{error, Reason};
892+
{http, {RequestId, {ok, {StatusLine,Headers,BinBody}}}} ->
893+
Body = maybe_format_body(BinBody, Options),
894+
{ok, {StatusLine, Headers, Body}};
895+
{http, {RequestId, {ok, {StatusCode,BinBody}}}} ->
896+
Body = maybe_format_body(BinBody, Options),
897+
{ok, {StatusCode, Body}}
898+
after 0 ->
899+
{error, timeout}
900+
end
879901
end.
880902

881903
maybe_format_body(BinBody, Options) ->
@@ -1064,6 +1086,8 @@ request_options_defaults() ->
10641086
ok;
10651087
(Value) when is_function(Value, 1) ->
10661088
ok;
1089+
(Value) when is_reference(Value) ->
1090+
ok;
10671091
(_) ->
10681092
error
10691093
end,
@@ -1085,7 +1109,7 @@ request_options_defaults() ->
10851109
{body_format, string, VerifyBodyFormat},
10861110
{full_result, true, VerifyFullResult},
10871111
{headers_as_is, false, VerifyHeaderAsIs},
1088-
{receiver, self(), VerifyReceiver},
1112+
{receiver, alias(), VerifyReceiver},
10891113
{socket_opts, undefined, VerifySocketOpts},
10901114
{ipv6_host_with_brackets, false, VerifyBrackets}
10911115
].
@@ -1139,6 +1163,7 @@ request_options([{Key, DefaultVal, Verify} | Defaults], Options, Acc) ->
11391163
BodyFormat :: string() | binary() | atom(),
11401164
SocketOpt :: term(),
11411165
Receiver :: pid()
1166+
| reference()
11421167
| fun((term()) -> term())
11431168
| { ReceiverModule::atom()
11441169
, ReceiverFunction::atom()
@@ -1149,6 +1174,8 @@ request_options_sanity_check(Opts) ->
11491174
case proplists:get_value(receiver, Opts) of
11501175
Pid when is_pid(Pid) andalso (Pid =:= self()) ->
11511176
ok;
1177+
Reference when is_reference(Reference) ->
1178+
ok;
11521179
BadReceiver ->
11531180
throw({error, {bad_options_combo,
11541181
[{sync, true}, {receiver, BadReceiver}]}})

lib/inets/src/http_client/httpc_handler.erl

Lines changed: 2 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -519,7 +519,6 @@ do_handle_info({Proto, _Socket, Data},
519519
when (Proto =:= tcp) orelse
520520
(Proto =:= ssl) orelse
521521
(Proto =:= httpc_handler) ->
522-
523522
try Module:Function([Data | Args]) of
524523
{ok, Result} ->
525524
handle_http_msg(Result, State);
@@ -1738,10 +1737,10 @@ format_address({[$[|T], Port}) ->
17381737
format_address(HostPort) ->
17391738
HostPort.
17401739

1741-
format_answer(Res0, Options) ->
1740+
format_answer(Res, Options) ->
17421741
FullResult = proplists:get_value(full_result, Options, true),
17431742
Sync = proplists:get_value(sync, Options, true),
1744-
do_format_answer(Res0, FullResult, Sync).
1743+
do_format_answer(Res, FullResult, Sync).
17451744
do_format_answer({Ref, StatusLine}, _, Sync) when is_atom(StatusLine) ->
17461745
case Sync of
17471746
true ->
@@ -1773,18 +1772,3 @@ do_format_answer({Ref, {StatusLine, _, BinBody}}, false, Sync) ->
17731772
end;
17741773
do_format_answer({Ref, {error, _Reason} = Error}, _, _) ->
17751774
{Ref, Error}.
1776-
1777-
1778-
clobber_and_retry(#state{session = #session{id = Id,
1779-
type = Type},
1780-
profile_name = ProfileName,
1781-
pipeline = Pipeline,
1782-
keep_alive = KeepAlive} = State) ->
1783-
%% Clobber session
1784-
(catch httpc_manager:delete_session(Id, ProfileName)),
1785-
case Type of
1786-
pipeline ->
1787-
maybe_retry_queue(Pipeline, State);
1788-
_ ->
1789-
maybe_retry_queue(KeepAlive, State)
1790-
end.

lib/inets/src/http_client/httpc_response.erl

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -150,7 +150,8 @@ result(Response = {{_,Code,_}, _, _}, Request) when (Code div 100) =:= 5 ->
150150
result(Response, Request) ->
151151
transparent(Response, Request).
152152

153-
send(Receiver, Msg) when is_pid(Receiver) ->
153+
send(Receiver, Msg) when is_pid(Receiver)
154+
orelse is_reference(Receiver) ->
154155
Receiver ! {http, Msg};
155156
send(Receiver, Msg) when is_function(Receiver) ->
156157
(catch Receiver(Msg));

lib/inets/test/httpc_SUITE.erl

Lines changed: 23 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -354,13 +354,19 @@ init_per_testcase(Case, Config) when Case == post;
354354
Case == post_stream ->
355355
ct:timetrap({seconds, 30}),
356356
Config;
357+
init_per_testcase(async, Config) ->
358+
{ok,Pid} = inets:start(httpc, [{profile, async}], stand_alone),
359+
[{httpc_pid, Pid} | Config];
357360
init_per_testcase(_Case, Config) ->
358361
Config.
359362

360363
end_per_testcase(pipeline, _Config) ->
361364
inets:stop(httpc, pipeline);
362365
end_per_testcase(persistent_connection, _Config) ->
363366
inets:stop(httpc, persistent);
367+
end_per_testcase(async, Config) ->
368+
Pid = proplists:get_value(httpc_pid, Config),
369+
inets:stop(httpc, Pid);
364370
end_per_testcase(Case, Config)
365371
when Case == server_closing_connection_on_first_response;
366372
Case == server_closing_connection_on_second_response ->
@@ -567,6 +573,7 @@ async() ->
567573
[{doc, "Test an asynchrony http request."}].
568574
async(Config) when is_list(Config) ->
569575
Request = {url(group_name(Config), "/dummy.html", Config), []},
576+
HttpcPid = proplists:get_value(httpc_pid, Config),
570577

571578
{ok, RequestId} =
572579
httpc:request(get, Request, [], [{sync, false}]),
@@ -578,10 +585,11 @@ async(Config) when is_list(Config) ->
578585
ct:fail(Msg)
579586
end,
580587
inets_test_lib:check_body(binary_to_list(Body)),
588+
581589
%% Check full result false option for async request
582590
{ok, RequestId2} =
583-
httpc:request(get, Request, [?SSL_NO_VERIFY], [{sync, false},
584-
{full_result, false}], ?profile(Config)),
591+
httpc:request(get, Request, [], [{sync, false},
592+
{full_result, false}]),
585593
Body2 =
586594
receive
587595
{http, {RequestId2, {200, BinBody2}}} ->
@@ -590,6 +598,19 @@ async(Config) when is_list(Config) ->
590598
ct:fail(Msg2)
591599
end,
592600
inets_test_lib:check_body(binary_to_list(Body2)),
601+
602+
%% Check receiver alias() option for async request with stand_alone httpc
603+
{ok, RequestId3} =
604+
httpc:request(get, Request, [], [{sync, false},
605+
{receiver, alias()}], HttpcPid),
606+
Body3 =
607+
receive
608+
{http, {RequestId3, {{_, 200, _}, _, BinBody3}}} ->
609+
BinBody3;
610+
{http, Msg3} ->
611+
ct:fail(Msg3)
612+
end,
613+
inets_test_lib:check_body(binary_to_list(Body3)),
593614
{ok, NewRequestId} =
594615
httpc:request(get, Request, [], [{sync, false}]),
595616
ok = httpc:cancel_request(NewRequestId).

0 commit comments

Comments
 (0)