Skip to content

Commit 465413d

Browse files
committed
add max_handlers_open option for httpc profile
1 parent a6c194f commit 465413d

File tree

4 files changed

+258
-59
lines changed

4 files changed

+258
-59
lines changed

lib/inets/src/http_client/httpc.erl

+42-6
Original file line numberDiff line numberDiff line change
@@ -235,6 +235,7 @@ request(Url, Profile) ->
235235
Result :: { StatusLine , [HttpHeader], HttpBodyResult}
236236
| { StatusCode, HttpBodyResult}
237237
| RequestId
238+
| {await, RequestId}
238239
| saved_to_file,
239240
StatusCode::non_neg_integer(),
240241
StatusLine :: { HttpVersion
@@ -254,8 +255,10 @@ request(Method, Request, HttpOptions, Options) ->
254255

255256
-doc """
256257
Sends an HTTP request. The function can be both synchronous and asynchronous. In
257-
the latter case, the function returns `{ok, RequestId}` and then the information
258-
is delivered to the `receiver` depending on that value.
258+
the latter case, the function returns `{ok, RequestId}` or {ok, {await, RequestId}}
259+
and then the information is delivered to the `receiver` depending on that value.
260+
The `{await, RequestId}` means that the request is not yet sent, and has been enqueued
261+
based on the [`MaxHandlersOpen`](`set_options/1`) option that set is for the profile in use.
259262
260263
When `Profile` is `stand_alone` only the pid can be used.
261264
@@ -327,6 +330,10 @@ Options details:
327330
the request is asynchronous, the message `{http, {RequestId, saved_to_file}}`
328331
is sent.
329332
333+
When a request happens to be enqueued based on the [`MaxHandlersOpen`](`set_options/1`)
334+
option, the first message sent to the receiver is `{started, RequestId}`. This is to ensure a
335+
proper behavior of timeout mechanisms.
336+
330337
Default is `none`.
331338
332339
- **`body_format`** - Defines if the body is to be delivered as a string or
@@ -547,6 +554,7 @@ cancel_request(RequestId, Profile)
547554
Option :: {proxy, {Proxy, NoProxy}}
548555
| {https_proxy, {Proxy, NoProxy}}
549556
| {max_sessions, MaxSessions}
557+
| {max_handlers_open, MaxHandlersOpen}
550558
| {max_keep_alive_length, MaxKeepAlive}
551559
| {keep_alive_timeout, KeepAliveTimeout}
552560
| {max_pipeline_length, MaxPipeline}
@@ -562,6 +570,7 @@ cancel_request(RequestId, Profile)
562570
Port :: non_neg_integer(),
563571
NoProxy :: [DomainDesc | HostName | IpAddressDesc],
564572
MaxSessions :: integer(),
573+
MaxHandlersOpen :: integer(),
565574
MaxKeepAlive :: integer(),
566575
KeepAliveTimeout :: integer(),
567576
MaxPipeline :: integer(),
@@ -594,6 +603,9 @@ Sets options to be used for subsequent requests.
594603
`{undefined, []}`, that is, no proxy is configured and `https_proxy` defaults
595604
to the value of `proxy`.
596605
606+
- **`MaxHandlersOpen`** - `MaxHandlersOpen` Maximum number of handlers that can be
607+
opened at the same time. Default is `-1` which means that it's not limited.
608+
597609
- **`MaxSessions`** - `MaxSessions` Maximum number of persistent connections to
598610
a host. Default is `2`.
599611
@@ -666,6 +678,7 @@ Sets options to be used for subsequent requests.
666678
Options :: [Option],
667679
Option :: {proxy, {Proxy, NoProxy}}
668680
| {https_proxy, {Proxy, NoProxy}}
681+
| {max_handlers_open, MaxHandlersOpen}
669682
| {max_sessions, MaxSessions}
670683
| {max_keep_alive_length, MaxKeepAlive}
671684
| {keep_alive_timeout, KeepAliveTimeout}
@@ -683,6 +696,7 @@ Sets options to be used for subsequent requests.
683696
Proxy :: {HostName, Port},
684697
Port :: non_neg_integer(),
685698
NoProxy :: [DomainDesc | HostName | IpAddressDesc],
699+
MaxHandlersOpen :: integer(),
686700
MaxSessions :: integer(),
687701
MaxKeepAlive :: integer(),
688702
KeepAliveTimeout :: integer(),
@@ -703,7 +717,9 @@ set_options(Options, Profile) when is_atom(Profile) orelse is_pid(Profile) ->
703717
true ->
704718
{ok, IpFamily} = get_option(ipfamily, Profile),
705719
{ok, UnixSock} = get_option(unix_socket, Profile),
706-
case validate_options(Options, IpFamily, UnixSock) of
720+
{ok, MaxSessions} = get_option(max_sessions, Profile),
721+
{ok, MaxHandlersOpen} = get_option(max_handlers_open, Profile),
722+
case validate_options(Options, IpFamily, UnixSock, MaxSessions, MaxHandlersOpen) of
707723
{ok, Opts} ->
708724
httpc_manager:set_options(Opts, profile_name(Profile));
709725
Error ->
@@ -735,7 +751,7 @@ get_options() ->
735751
-doc(#{since => <<"OTP R15B01">>}).
736752
-spec get_options(OptionItems) -> {ok, Values} | {error, Reason} when
737753
OptionItems :: all | [OptionItem],
738-
OptionItem :: proxy | https_proxy | max_sessions | keep_alive_timeout
754+
OptionItem :: proxy | https_proxy | max_sessions | max_handlers_open | keep_alive_timeout
739755
| max_keep_alive_length | pipeline_timeout | max_pipeline_length | cookies
740756
| ipfamily | ip | port | socket_opts | verbose | unix_socket,
741757
Values :: [{OptionItem, term()}],
@@ -750,7 +766,7 @@ get_options(Options) ->
750766
-doc(#{since => <<"OTP R15B01">>}).
751767
-spec get_options(OptionItems, Profile) -> {ok, Values} | {error, Reason} when
752768
OptionItems :: all | [OptionItem],
753-
OptionItem :: proxy | https_proxy | max_sessions | keep_alive_timeout
769+
OptionItem :: proxy | https_proxy | max_sessions | max_handlers_open | keep_alive_timeout
754770
| max_keep_alive_length | pipeline_timeout | max_pipeline_length | cookies
755771
| ipfamily | ip | port | socket_opts | verbose | unix_socket,
756772
Values :: [{OptionItem, term()}],
@@ -1274,6 +1290,10 @@ mk_chunkify_fun(ProcessBody) ->
12741290

12751291
handle_answer(RequestId, _, false, _, _) ->
12761292
{ok, RequestId};
1293+
handle_answer({await, RequestId}, ClientAlias, true, Options, Timeout) ->
1294+
receive {started, RequestId} ->
1295+
handle_answer(RequestId, ClientAlias, true, Options, Timeout)
1296+
end;
12771297
handle_answer(RequestId, ClientAlias, true, Options, Timeout) ->
12781298
receive
12791299
{http, {RequestId, {ok, saved_to_file}}} ->
@@ -1623,8 +1643,15 @@ validate_ipfamily_unix_socket(IpFamily, UnixSocket) ->
16231643
validate_ipfamily(IpFamily),
16241644
validate_unix_socket(UnixSocket).
16251645

1626-
validate_options(Options0, CurrIpFamily, CurrUnixSock) ->
1646+
validate_max_sessions_max_handlers_open(MaxSessions, MaxHandlersOpen)
1647+
when MaxSessions > MaxHandlersOpen andalso MaxHandlersOpen =/= -1 ->
1648+
throw({error, {max_sessions_over_max_handlers, MaxSessions, MaxHandlersOpen}});
1649+
validate_max_sessions_max_handlers_open(_, _) ->
1650+
ok.
1651+
1652+
validate_options(Options0, CurrIpFamily, CurrUnixSock, MaxSessions, MaxHandlersOpen) ->
16271653
try
1654+
validate_max_sessions_max_handlers_open(MaxSessions, MaxHandlersOpen),
16281655
validate_ipfamily_unix_socket(Options0, CurrIpFamily, CurrUnixSock),
16291656
validate_options(Options0, [])
16301657
catch
@@ -1647,6 +1674,10 @@ validate_options([{max_sessions, Value} = Opt| Tail], Acc) ->
16471674
validate_max_sessions(Value),
16481675
validate_options(Tail, [Opt | Acc]);
16491676

1677+
validate_options([{max_handlers_open, Value} = Opt| Tail], Acc) ->
1678+
validate_max_handlers_open(Value),
1679+
validate_options(Tail, [Opt | Acc]);
1680+
16501681
validate_options([{keep_alive_timeout, Value} = Opt| Tail], Acc) ->
16511682
validate_keep_alive_timeout(Value),
16521683
validate_options(Tail, [Opt | Acc]);
@@ -1722,6 +1753,11 @@ validate_max_sessions(Value) when is_integer(Value) andalso (Value >= 0) ->
17221753
validate_max_sessions(BadValue) ->
17231754
bad_option(max_sessions, BadValue).
17241755

1756+
validate_max_handlers_open(Value) when is_integer(Value) andalso (Value >= 0) ->
1757+
Value;
1758+
validate_max_handlers_open(BadValue) ->
1759+
bad_option(max_handlers_open, BadValue).
1760+
17251761
validate_keep_alive_timeout(Value) when is_integer(Value) andalso (Value >= 0) ->
17261762
Value;
17271763
validate_keep_alive_timeout(infinity = Value) ->

lib/inets/src/http_client/httpc_internal.hrl

+2-1
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,8 @@
8787
ip = default, % specify local interface
8888
port = default, % specify local port
8989
socket_opts = [], % other socket options
90-
unix_socket = undefined % Local unix socket
90+
unix_socket = undefined, % Local unix socket
91+
max_handlers_open = -1 % Maximum number of open handlers, -1 means no limit
9192
}
9293
).
9394
-type options() :: #options{}.

lib/inets/src/http_client/httpc_manager.erl

+67-28
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,8 @@
6060
cookie_db, % cookie_db()
6161
session_db, % ets() - Entry: #session{}
6262
profile_name, % atom()
63-
options = #options{}
63+
options = #options{},
64+
awaiting % queue() - Entry: #request{}
6465
}).
6566

6667
-define(DELAY, 500).
@@ -438,7 +439,8 @@ do_init(ProfileName, CookiesDir) ->
438439
State = #state{handler_db = HandlerDbName,
439440
cookie_db = CookieDb,
440441
session_db = SessionDbName,
441-
profile_name = ProfileName},
442+
profile_name = ProfileName,
443+
awaiting = queue:new()},
442444
{ok, State}.
443445

444446

@@ -555,7 +557,8 @@ handle_cast({set_options, Options}, State = #state{options = OldOptions}) ->
555557
port = get_port(Options, OldOptions),
556558
verbose = get_verbose(Options, OldOptions),
557559
socket_opts = get_socket_opts(Options, OldOptions),
558-
unix_socket = get_unix_socket_opts(Options, OldOptions)
560+
unix_socket = get_unix_socket_opts(Options, OldOptions),
561+
max_handlers_open = get_max_handlers_open(Options, OldOptions)
559562
},
560563
case {OldOptions#options.verbose, NewOptions#options.verbose} of
561564
{Same, Same} ->
@@ -579,7 +582,8 @@ handle_cast({store_cookies, _},
579582
handle_cast({store_cookies, {Cookies, _}}, State) ->
580583
ok = do_store_cookies(Cookies, State),
581584
{noreply, State};
582-
585+
handle_cast({await, Request}, #state{awaiting = Awaiting} = State) ->
586+
{noreply, State#state{awaiting = queue:in(Request, Awaiting)}};
583587
handle_cast(Msg, #state{profile_name = ProfileName} = State) ->
584588
error_report(ProfileName,
585589
"received unknown message"
@@ -592,11 +596,13 @@ handle_cast(Msg, #state{profile_name = ProfileName} = State) ->
592596
%% {stop, Reason, State} (terminate/2 is called)
593597
%% Description: Handling all non call/cast messages
594598
%%---------------------------------------------------------
599+
%%
595600
handle_info({'EXIT', _, _}, State) ->
596601
%% Handled in DOWN
597602
{noreply, State};
598-
handle_info({'DOWN', _, _, Pid, _}, State) ->
599-
ets:match_delete(State#state.handler_db, {'_', Pid, '_'}),
603+
handle_info({'DOWN', _, _, Pid, _}, State0) ->
604+
ets:match_delete(State0#state.handler_db, {'_', Pid, '_'}),
605+
State = start_enqueued_request(State0),
600606
{noreply, State};
601607
handle_info(Info, State) ->
602608
Report = io_lib:format("Unknown message in "
@@ -753,18 +759,19 @@ handle_request(Request0 = #request{socket_opts = SocketOpts},
753759
(Request#request.headers)#http_request_h{connection
754760
= "close"},
755761
%% Reset socket_opts to avoid setopts failure.
756-
start_handler(Request#request{headers = Headers, socket_opts = []}, State),
762+
Msg = start_handler(Request#request{headers = Headers, socket_opts = []}, State),
757763
%% Do not change the state
758-
{reply, {ok, Request#request.id}, State0};
764+
{reply, Msg, State0};
759765

760766
handle_request(Request, State = #state{options = Options}) ->
761767
NewRequest = handle_cookies(generate_request_id(Request), State),
762768
SessionType = session_type(Options),
763-
case select_session(Request#request.method,
769+
Message = case select_session(Request#request.method,
764770
Request#request.address,
765771
Request#request.scheme, SessionType, State) of
766772
{ok, HandlerPid} ->
767-
pipeline_or_keep_alive(NewRequest, HandlerPid, State);
773+
pipeline_or_keep_alive(NewRequest, HandlerPid, State),
774+
{ok, NewRequest#request.id};
768775
no_connection ->
769776
start_handler(NewRequest, State);
770777
{no_session, OpenSessions} when OpenSessions
@@ -778,7 +785,7 @@ handle_request(Request, State = #state{options = Options}) ->
778785
= "close"},
779786
start_handler(NewRequest#request{headers = NewHeaders}, State)
780787
end,
781-
{reply, {ok, NewRequest#request.id}, State}.
788+
{reply, Message, State}.
782789

783790

784791
%% Convert Request options to State options
@@ -790,26 +797,53 @@ convert_options([{ip, Value}|T], Options) ->
790797
convert_options(T, Options#options{ip = Value});
791798
convert_options([{port, Value}|T], Options) ->
792799
convert_options(T, Options#options{port = Value});
800+
convert_options([{max_handlers_open, Value}|T], Options) ->
801+
convert_options(T, Options#options{max_handlers_open = Value});
793802
convert_options([Option|T], Options = #options{socket_opts = SocketOpts}) ->
794803
convert_options(T, Options#options{socket_opts = SocketOpts ++ [Option]}).
795804

796-
start_handler(#request{id = Id,
797-
from = From} = Request,
798-
#state{profile_name = ProfileName,
799-
handler_db = HandlerDb,
800-
options = Options}) ->
801-
{ok, Pid} =
802-
case is_inets_manager() of
803-
true ->
804-
httpc_handler_sup:start_child([whereis(httpc_handler_sup),
805-
Request, Options, ProfileName]);
806-
false ->
807-
httpc_handler:start_link(self(), Request, Options, ProfileName)
808-
end,
809-
HandlerInfo = {Id, Pid, From},
810-
ets:insert(HandlerDb, HandlerInfo),
811-
erlang:monitor(process, Pid).
805+
start_handler(#request{} = Request,
806+
#state{handler_db = HandlerDb,
807+
options = Options} = State) ->
808+
MaxHandlersOpen = Options#options.max_handlers_open,
809+
case ets:info(HandlerDb, size) >= MaxHandlersOpen - 1
810+
andalso MaxHandlersOpen =/= -1 of
811+
true -> wait_for_handler_to_end_then_start(Request);
812+
false -> do_start_handler(Request, State)
813+
end.
812814

815+
do_start_handler(#request{id = Id,
816+
from = From} = Request,
817+
#state{profile_name = ProfileName,
818+
handler_db = HandlerDb,
819+
options = Options}) ->
820+
{ok, Pid} =
821+
case is_inets_manager() of
822+
true ->
823+
httpc_handler_sup:start_child([whereis(httpc_handler_sup),
824+
Request, Options, ProfileName]);
825+
false ->
826+
httpc_handler:start_link(self(), Request, Options, ProfileName)
827+
end,
828+
HandlerInfo = {Id, Pid, From},
829+
ets:insert(HandlerDb, HandlerInfo),
830+
erlang:monitor(process, Pid),
831+
{ok, Id}.
832+
833+
wait_for_handler_to_end_then_start(#request{id = Id} = Request) ->
834+
gen_server:cast(self(), {await, Request}),
835+
{ok, {await, Id}}.
836+
837+
start_enqueued_request(#state{awaiting = Awaiting} = State0)->
838+
case queue:out(Awaiting) of
839+
{{value, Request}, NewAwaiting} ->
840+
State = State0#state{awaiting = NewAwaiting},
841+
{ok, Id} = do_start_handler(Request, State#state{awaiting = NewAwaiting}),
842+
Request#request.from ! {started, Id},
843+
State;
844+
{empty, _} ->
845+
State0
846+
end.
813847

814848
select_session(Method, HostPort, Scheme, SessionType,
815849
#state{options = #options{max_pipeline_length = MaxPipe,
@@ -1001,7 +1035,9 @@ get_option(port, #options{port = Port}) ->
10011035
get_option(socket_opts, #options{socket_opts = SocketOpts}) ->
10021036
SocketOpts;
10031037
get_option(unix_socket, #options{unix_socket = UnixSocket}) ->
1004-
UnixSocket.
1038+
UnixSocket;
1039+
get_option(max_handlers_open, #options{max_handlers_open = MaxHandlersOpen}) ->
1040+
MaxHandlersOpen.
10051041

10061042

10071043
get_proxy(Opts, #options{proxy = Default}) ->
@@ -1046,6 +1082,9 @@ get_socket_opts(Opts, #options{socket_opts = Default}) ->
10461082
get_unix_socket_opts(Opts, #options{unix_socket = Default}) ->
10471083
proplists:get_value(unix_socket, Opts, Default).
10481084

1085+
get_max_handlers_open(Opts, #options{max_handlers_open = Default}) ->
1086+
proplists:get_value(max_handlers_open, Opts, Default).
1087+
10491088
handle_verbose(debug) ->
10501089
dbg:p(self(), [call]),
10511090
dbg:tp(?MODULE, [{'_', [], [{return_trace}]}]);

0 commit comments

Comments
 (0)