Skip to content

Commit

Permalink
OTP-19158 httpc enable options for async request
Browse files Browse the repository at this point in the history
  • Loading branch information
Whaileee committed Aug 28, 2024
1 parent 00c3a73 commit 469c2c1
Show file tree
Hide file tree
Showing 5 changed files with 107 additions and 46 deletions.
29 changes: 12 additions & 17 deletions lib/inets/src/http_client/httpc.erl
Original file line number Diff line number Diff line change
Expand Up @@ -802,7 +802,8 @@ handle_request(Method, Url,
socket_opts = SocketOpts,
started = Started,
unix_socket = UnixSocket,
ipv6_host_with_brackets = BracketedHost},
ipv6_host_with_brackets = BracketedHost,
request_options = Options},
case httpc_manager:request(Request, profile_name(Profile)) of
{ok, RequestId} ->
handle_answer(RequestId, Sync, Options);
Expand Down Expand Up @@ -865,22 +866,16 @@ handle_answer(RequestId, false, _) ->
{ok, RequestId};
handle_answer(RequestId, true, Options) ->
receive
{http, {RequestId, saved_to_file}} ->
{ok, saved_to_file};
{http, {RequestId, {_,_,_} = Result}} ->
return_answer(Options, Result);
{http, {RequestId, {error, Reason}}} ->
{error, Reason}
end.

return_answer(Options, {StatusLine, Headers, BinBody}) ->
Body = maybe_format_body(BinBody, Options),
case proplists:get_value(full_result, Options, true) of
true ->
{ok, {StatusLine, Headers, Body}};
false ->
{_, Status, _} = StatusLine,
{ok, {Status, Body}}
{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}}
end.

maybe_format_body(BinBody, Options) ->
Expand Down
58 changes: 55 additions & 3 deletions lib/inets/src/http_client/httpc_handler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1339,11 +1339,12 @@ handle_server_closing(State = #state{headers = Headers}) ->
false -> State
end.

answer_request(#request{id = RequestId, from = From} = Request, Msg,
answer_request(#request{id = RequestId, from = From, request_options = Options} = Request, Msg,
#state{session = Session,
timers = Timers,
profile_name = ProfileName} = State) ->
httpc_response:send(From, Msg),
profile_name = ProfileName} = State) ->
Answer = format_answer(Msg, Options),
httpc_response:send(From, Answer),
RequestTimers = Timers#timers.request_timers,
TimerRef =
proplists:get_value(RequestId, RequestTimers, undefined),
Expand Down Expand Up @@ -1736,3 +1737,54 @@ format_address({[$[|T], Port}) ->
{Address, Port};
format_address(HostPort) ->
HostPort.

format_answer(Res0, 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({Ref, StatusLine}, _, Sync) when is_atom(StatusLine) ->
case Sync of
true ->
{Ref, {ok, StatusLine}};
_ ->
{Ref, StatusLine}
end;
do_format_answer({Ref, StatusLine, Headers}, _, Sync) when is_atom(StatusLine) ->
case Sync of
true ->
{Ref, {ok, {StatusLine, Headers}}};
_ ->
{Ref, StatusLine, Headers}
end;
do_format_answer({Ref, {StatusLine, Headers, BinBody}}, true, Sync) ->
case Sync of
true ->
{Ref, {ok, {StatusLine, Headers, BinBody}}};
_ ->
{Ref, {StatusLine, Headers, BinBody}}
end;
do_format_answer({Ref, {StatusLine, _, BinBody}}, false, Sync) ->
{_, Status, _} = StatusLine,
case Sync of
true ->
{Ref, {ok, {Status, BinBody}}};
_ ->
{Ref, Status, BinBody}
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_internal.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,8 @@
timer :: undefined | reference(),
socket_opts, % undefined | [socket_option()]
unix_socket, % undefined | string()
ipv6_host_with_brackets % boolean()
ipv6_host_with_brackets, % boolean()
request_options :: undefined | proplists:proplist()
}
).
-type request() :: #request{}.
Expand Down
50 changes: 26 additions & 24 deletions lib/inets/src/http_client/httpc_request.erl
Original file line number Diff line number Diff line change
Expand Up @@ -54,31 +54,33 @@ send(SendAddr, #session{socket = Socket, socket_type = SocketType},
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}) ->
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}) ->

?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}]),
?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}]),

TmpHdrs = handle_user_info(UserInfo, Headers),

Expand Down
13 changes: 12 additions & 1 deletion lib/inets/test/httpc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -578,7 +578,18 @@ 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)),
Body2 =
receive
{http, {RequestId2, 200, BinBody2}} ->
BinBody2;
{http, Msg2} ->
ct:fail(Msg2)
end,
inets_test_lib:check_body(binary_to_list(Body2)),
{ok, NewRequestId} =
httpc:request(get, Request, [], [{sync, false}]),
ok = httpc:cancel_request(NewRequestId).
Expand Down

0 comments on commit 469c2c1

Please sign in to comment.