From be1bc8e40d986dd8ba407be7f454ff7b936cb9de Mon Sep 17 00:00:00 2001
From: Konrad Pietrzak
Messages are sent to this special reference in the same format
+ as
Information is delivered to the receiver through calls to the
diff --git a/lib/inets/src/http_client/httpc.erl b/lib/inets/src/http_client/httpc.erl
index ee4b8682c051..2087c7bf4227 100644
--- a/lib/inets/src/http_client/httpc.erl
+++ b/lib/inets/src/http_client/httpc.erl
@@ -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
@@ -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) ->
@@ -1064,6 +1086,8 @@ request_options_defaults() ->
ok;
(Value) when is_function(Value, 1) ->
ok;
+ (Value) when is_reference(Value) ->
+ ok;
(_) ->
error
end,
@@ -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}
].
@@ -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()
@@ -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}]}})
diff --git a/lib/inets/src/http_client/httpc_handler.erl b/lib/inets/src/http_client/httpc_handler.erl
index 14d9e58d1cba..a33b6f85674f 100644
--- a/lib/inets/src/http_client/httpc_handler.erl
+++ b/lib/inets/src/http_client/httpc_handler.erl
@@ -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);
@@ -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 ->
@@ -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.
diff --git a/lib/inets/src/http_client/httpc_response.erl b/lib/inets/src/http_client/httpc_response.erl
index 94693577e806..6872589fcce4 100644
--- a/lib/inets/src/http_client/httpc_response.erl
+++ b/lib/inets/src/http_client/httpc_response.erl
@@ -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));
diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl
index 1a7bc7116f10..3f7c5ead1f7b 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -354,6 +354,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.
@@ -361,6 +364,9 @@ 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 ->
@@ -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}]),
@@ -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}}} ->
@@ -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).
From 6c074782b72c17504c0413f99cf303f0deb185b3 Mon Sep 17 00:00:00 2001
From: Konrad Pietrzak
Messages are sent to this special reference in the same format
- as
Information is delivered to the receiver through calls to the
diff --git a/lib/inets/src/http_client/httpc.erl b/lib/inets/src/http_client/httpc.erl
index 2087c7bf4227..dd10481fab1c 100644
--- a/lib/inets/src/http_client/httpc.erl
+++ b/lib/inets/src/http_client/httpc.erl
@@ -803,15 +803,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, Receiver, Sync, Options,
- element(#http_options.timeout, HTTPOptions));
- {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}};
@@ -868,36 +868,36 @@ handle_answer(RequestId, _, false, _, _) ->
handle_answer(RequestId, ClientAlias, true, Options, Timeout) ->
receive
{http, {RequestId, {ok, saved_to_file}}} ->
- unalias(ClientAlias),
+ true = unalias(ClientAlias),
{ok, saved_to_file};
{http, {RequestId, {error, Reason}}} ->
- unalias(ClientAlias),
+ true = unalias(ClientAlias),
{error, Reason};
- {http, {RequestId, {ok, {StatusLine,Headers,BinBody}}}} ->
- unalias(ClientAlias),
+ {http, {RequestId, {ok, {StatusLine, Headers, BinBody}}}} ->
+ true = unalias(ClientAlias),
Body = maybe_format_body(BinBody, Options),
{ok, {StatusLine, Headers, Body}};
- {http, {RequestId, {ok, {StatusCode,BinBody}}}} ->
- unalias(ClientAlias),
+ {http, {RequestId, {ok, {StatusCode, BinBody}}}} ->
+ true = 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
+ 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) ->
@@ -1086,8 +1086,8 @@ request_options_defaults() ->
ok;
(Value) when is_function(Value, 1) ->
ok;
- (Value) when is_reference(Value) ->
- ok;
+ (Value) when is_reference(Value) ->
+ ok;
(_) ->
error
end,
@@ -1174,8 +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;
+ 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 a33b6f85674f..be32ebfbad30 100644
--- a/lib/inets/src/http_client/httpc_handler.erl
+++ b/lib/inets/src/http_client/httpc_handler.erl
@@ -1761,9 +1761,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 2ec6cf24de34..a9fcdc944959 100644
--- a/lib/inets/src/http_client/httpc_request.erl
+++ b/lib/inets/src/http_client/httpc_request.erl
@@ -55,32 +55,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 6872589fcce4..a3b81a6f7c2e 100644
--- a/lib/inets/src/http_client/httpc_response.erl
+++ b/lib/inets/src/http_client/httpc_response.erl
@@ -150,8 +150,7 @@ result(Response = {{_,Code,_}, _, _}, Request) when (Code div 100) =:= 5 ->
result(Response, Request) ->
transparent(Response, Request).
-send(Receiver, Msg) when is_pid(Receiver)
- orelse is_reference(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 3f7c5ead1f7b..275e150a6521 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -576,14 +576,14 @@ async(Config) when is_list(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
From fb19f1cbd4178f28d418bc26bf1aab3e856255f7 Mon Sep 17 00:00:00 2001
From: Konrad Pietrzak