Skip to content

Commit

Permalink
Inets: formatting fixes
Browse files Browse the repository at this point in the history
  • Loading branch information
Whaileee committed Sep 25, 2024
1 parent 5411867 commit 6c07478
Show file tree
Hide file tree
Showing 6 changed files with 69 additions and 76 deletions.
6 changes: 0 additions & 6 deletions lib/inets/doc/src/httpc.xml
Original file line number Diff line number Diff line change
Expand Up @@ -379,12 +379,6 @@
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
70 changes: 35 additions & 35 deletions lib/inets/src/http_client/httpc.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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}};
Expand Down Expand Up @@ -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) ->
Expand Down Expand Up @@ -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,
Expand Down Expand Up @@ -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}]}})
Expand Down
4 changes: 2 additions & 2 deletions lib/inets/src/http_client/httpc_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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}}};
Expand Down
48 changes: 24 additions & 24 deletions lib/inets/src/http_client/httpc_request.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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),

Expand Down
3 changes: 1 addition & 2 deletions lib/inets/src/http_client/httpc_response.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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));
Expand Down
14 changes: 7 additions & 7 deletions lib/inets/test/httpc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down

0 comments on commit 6c07478

Please sign in to comment.