From fd5fcc04372b53f5e08232db5abcfdd1ceb111b7 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 3d62cb7ee84d..4518e96d50bb 100644 --- a/lib/inets/src/http_client/httpc_handler.erl +++ b/lib/inets/src/http_client/httpc_handler.erl @@ -1761,14 +1761,14 @@ 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}}}; _ -> {Ref, Status, BinBody} - end; + end; do_format_answer({Ref, {error, _Reason} = Error}, _, _) -> {Ref, Error}. 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 52d04a91f30b..100557960b3e 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