Просмотр исходного кода

Metric counters for connection accepts and terminates

Maria-12648430 4 лет назад
Родитель
Сommit
03a8256e98

+ 2 - 2
Makefile

@@ -30,10 +30,10 @@ CONCUERROR_TESTS = ranch_concuerror:start_stop ranch_concuerror:info
 dep_ci.erlang.mk = git https://github.com/ninenines/ci.erlang.mk master
 DEP_EARLY_PLUGINS = ci.erlang.mk
 
-AUTO_CI_OTP ?= OTP-21+
+AUTO_CI_OTP ?= OTP-22+
 AUTO_CI_HIPE ?= OTP-LATEST
 # AUTO_CI_ERLLVM ?= OTP-LATEST
-AUTO_CI_WINDOWS ?= OTP-21+
+AUTO_CI_WINDOWS ?= OTP-22+
 
 # Standard targets.
 

+ 1 - 1
doc/src/guide/introduction.asciidoc

@@ -15,7 +15,7 @@ with socket programming and TCP protocols.
 
 Ranch is tested and supported on Linux, FreeBSD, macOS and Windows.
 
-Ranch is developed for Erlang/OTP 21+.
+Ranch is developed for Erlang/OTP 22+.
 
 Ranch may be compiled on earlier Erlang versions with small source code
 modifications but there is no guarantee that it will work as expected.

+ 9 - 0
doc/src/manual/ranch.info.asciidoc

@@ -38,9 +38,18 @@ transport:: Transport module.
 transport_options:: Transport options.
 protocol:: Protocol module.
 protocol_options:: Protocol options.
+metrics:: Listener metrics.
+
+== Metrics
+
+Listener metrics are provided as a map, with the following keys:
+
+{conns_sup, Index, accept}:: Number of accepted connections, per connection supervisor.
+{conns_sup, Index, terminate}:: Number of terminated connection processes, per connection supervisor.
 
 == Changelog
 
+* *2.1*: Added accept/terminate metrics to the output of `ranch:info/0,1`.
 * *2.0*: The listener info is now returned as a map.
 * *2.0*: The `num_acceptors` key has been removed.
 

+ 2 - 2
src/ranch.appup

@@ -16,15 +16,15 @@
 		{load_module, ranch_acceptor},
 		{update, ranch_acceptors_sup, supervisor},
 		{load_module, ranch_app},
+		{update, ranch_server, {advanced, []}},
+		{update, ranch_conns_sup_sup, supervisor},
 		%% See comments at the top of the file about ranch_conns_sup.
 		{update, ranch_conns_sup, {advanced, []}},
-		{update, ranch_conns_sup_sup, supervisor},
 		{load_module, ranch_crc32c},
 		{update, ranch_embedded_sup, supervisor},
 		{update, ranch_listener_sup, supervisor},
 		{load_module, ranch_protocol},
 		{load_module, ranch_proxy_header},
-		{update, ranch_server, {advanced, []}},
 		{update, ranch_server_proxy, {advanced, []}},
 		{load_module, ranch_ssl},
 		{update, ranch_sup, supervisor},

+ 19 - 1
src/ranch.erl

@@ -420,7 +420,8 @@ listener_info(Ref, Pid) ->
 		transport => Transport,
 		transport_options => TransOpts,
 		protocol => Protocol,
-		protocol_options => ProtoOpts
+		protocol_options => ProtoOpts,
+		metrics => metrics(Ref)
 	}.
 
 -spec procs(ref(), acceptors | connections) -> [pid()].
@@ -447,6 +448,23 @@ procs1(ListenerSup, connections) ->
 	),
 	lists:flatten(Conns).
 
+-spec metrics(ref()) -> #{}.
+metrics(Ref) ->
+	Counters = ranch_server:get_stats_counters(Ref),
+	CounterInfo = counters:info(Counters),
+	NumCounters = maps:get(size, CounterInfo),
+	NumConnsSups = NumCounters div 2,
+	lists:foldl(
+		fun (Id, Acc) ->
+			Acc#{
+				{conns_sup, Id, accept} => counters:get(Counters, 2*Id-1),
+				{conns_sup, Id, terminate} => counters:get(Counters, 2*Id)
+			}
+		end,
+		#{},
+		lists:seq(1, NumConnsSups)
+	).
+
 -spec wait_for_connections
 	(ref(), '>' | '>=' | '==' | '=<', non_neg_integer()) -> ok;
 	(ref(), '<', pos_integer()) -> ok.

+ 48 - 6
src/ranch_conns_sup.erl

@@ -34,6 +34,7 @@
 -record(state, {
 	parent = undefined :: pid(),
 	ref :: ranch:ref(),
+	id :: pos_integer(),
 	conn_type :: conn_type(),
 	shutdown :: shutdown(),
 	transport = undefined :: module(),
@@ -41,6 +42,7 @@
 	opts :: any(),
 	handshake_timeout :: timeout(),
 	max_conns = undefined :: ranch:max_conns(),
+	stats_counters_ref :: counters:counters_ref(),
 	logger = undefined :: module()
 }).
 
@@ -108,21 +110,25 @@ init(Parent, Ref, Id, Transport, TransOpts, Protocol, Logger) ->
 	Shutdown = maps:get(shutdown, TransOpts, 5000),
 	HandshakeTimeout = maps:get(handshake_timeout, TransOpts, 5000),
 	ProtoOpts = ranch_server:get_protocol_options(Ref),
+	StatsCounters = ranch_server:get_stats_counters(Ref),
 	ok = proc_lib:init_ack(Parent, {ok, self()}),
-	loop(#state{parent=Parent, ref=Ref, conn_type=ConnType,
+	loop(#state{parent=Parent, ref=Ref, id=Id, conn_type=ConnType,
 		shutdown=Shutdown, transport=Transport, protocol=Protocol,
-		opts=ProtoOpts, handshake_timeout=HandshakeTimeout,
+		opts=ProtoOpts, stats_counters_ref=StatsCounters,
+		handshake_timeout=HandshakeTimeout,
 		max_conns=MaxConns, logger=Logger}, 0, 0, []).
 
-loop(State=#state{parent=Parent, ref=Ref, conn_type=ConnType,
-		transport=Transport, protocol=Protocol, opts=Opts,
+loop(State=#state{parent=Parent, ref=Ref, id=Id, conn_type=ConnType,
+		transport=Transport, protocol=Protocol, opts=Opts, stats_counters_ref=StatsCounters,
 		max_conns=MaxConns, logger=Logger}, CurConns, NbChildren, Sleepers) ->
 	receive
 		{?MODULE, start_protocol, To, Socket} ->
 			try Protocol:start_link(Ref, Transport, Opts) of
 				{ok, Pid} ->
+					inc_accept(StatsCounters, Id, 1),
 					handshake(State, CurConns, NbChildren, Sleepers, To, Socket, Pid, Pid);
 				{ok, SupPid, ProtocolPid} when ConnType =:= supervisor ->
+					inc_accept(StatsCounters, Id, 1),
 					handshake(State, CurConns, NbChildren, Sleepers, To, Socket, SupPid, ProtocolPid);
 				Ret ->
 					To ! self(),
@@ -180,9 +186,11 @@ loop(State=#state{parent=Parent, ref=Ref, conn_type=ConnType,
 		{'EXIT', Pid, Reason} when Sleepers =:= [] ->
 			case erase(Pid) of
 				active ->
+					inc_terminate(StatsCounters, Id, 1),
 					report_error(Logger, Ref, Protocol, Pid, Reason),
 					loop(State, CurConns - 1, NbChildren - 1, Sleepers);
 				removed ->
+					inc_terminate(StatsCounters, Id, 1),
 					report_error(Logger, Ref, Protocol, Pid, Reason),
 					loop(State, CurConns, NbChildren - 1, Sleepers);
 				undefined ->
@@ -192,14 +200,17 @@ loop(State=#state{parent=Parent, ref=Ref, conn_type=ConnType,
 		{'EXIT', Pid, Reason} ->
 			case erase(Pid) of
 				active when CurConns > MaxConns ->
+					inc_terminate(StatsCounters, Id, 1),
 					report_error(Logger, Ref, Protocol, Pid, Reason),
 					loop(State, CurConns - 1, NbChildren - 1, Sleepers);
 				active ->
+					inc_terminate(StatsCounters, Id, 1),
 					report_error(Logger, Ref, Protocol, Pid, Reason),
 					[To|Sleepers2] = Sleepers,
 					To ! self(),
 					loop(State, CurConns - 1, NbChildren - 1, Sleepers2);
 				removed ->
+					inc_terminate(StatsCounters, Id, 1),
 					report_error(Logger, Ref, Protocol, Pid, Reason),
 					loop(State, CurConns, NbChildren - 1, Sleepers);
 				undefined ->
@@ -270,12 +281,15 @@ set_transport_options(State=#state{max_conns=MaxConns0}, CurConns, NbChildren, S
 		CurConns, NbChildren, Sleepers1).
 
 -spec terminate(#state{}, any(), non_neg_integer()) -> no_return().
-terminate(#state{shutdown=brutal_kill}, Reason, _) ->
+terminate(#state{shutdown=brutal_kill, id=Id,
+		stats_counters_ref=StatsCounters}, Reason, NbChildren) ->
 	kill_children(get_keys(active)),
 	kill_children(get_keys(removed)),
+	inc_terminate(StatsCounters, Id, NbChildren),
 	exit(Reason);
 %% Attempt to gracefully shutdown all children.
-terminate(#state{shutdown=Shutdown}, Reason, NbChildren) ->
+terminate(#state{shutdown=Shutdown, id=Id,
+		stats_counters_ref=StatsCounters}, Reason, NbChildren) ->
 	shutdown_children(get_keys(active)),
 	shutdown_children(get_keys(removed)),
 	_ = if
@@ -285,8 +299,17 @@ terminate(#state{shutdown=Shutdown}, Reason, NbChildren) ->
 			erlang:send_after(Shutdown, self(), kill)
 	end,
 	wait_children(NbChildren),
+	inc_terminate(StatsCounters, Id, NbChildren),
 	exit(Reason).
 
+inc_accept(StatsCounters, Id, N) ->
+	%% Accepts are counted in the odd indexes.
+	counters:add(StatsCounters, 2*Id-1, N).
+
+inc_terminate(StatsCounters, Id, N) ->
+	%% Terminates are counted in the even indexes.
+	counters:add(StatsCounters, 2*Id, N).
+
 %% Kill all children and then exit. We unlink first to avoid
 %% getting a message for each child getting killed.
 kill_children(Pids) ->
@@ -334,6 +357,25 @@ system_terminate(Reason, _, _, {State, _, NbChildren, _}) ->
 	terminate(State, Reason, NbChildren).
 
 -spec system_code_change(any(), _, _, _) -> {ok, any()}.
+system_code_change({#state{parent=Parent, ref=Ref, conn_type=ConnType,
+		shutdown=Shutdown, transport=Transport, protocol=Protocol,
+		opts=Opts, handshake_timeout=HandshakeTimeout,
+		max_conns=MaxConns, logger=Logger}, CurConns, NbChildren,
+		Sleepers}, _, {down, _}, _) ->
+	{ok, {{state, Parent, Ref, ConnType, Shutdown, Transport, Protocol,
+		Opts, HandshakeTimeout, MaxConns, Logger}, CurConns, NbChildren,
+		Sleepers}};
+system_code_change({{state, Parent, Ref, ConnType, Shutdown, Transport, Protocol,
+		Opts, HandshakeTimeout, MaxConns, Logger}, CurConns, NbChildren,
+		Sleepers}, _, _, _) ->
+	Self = self(),
+	[Id] = [Id || {Id, Pid} <- ranch_server:get_connections_sups(Ref), Pid=:=Self],
+	StatsCounters = ranch_server:get_stats_counters(Ref),
+	{ok, {#state{parent=Parent, ref=Ref, id=Id, conn_type=ConnType, shutdown=Shutdown,
+		transport=Transport, protocol=Protocol, opts=Opts,
+		handshake_timeout=HandshakeTimeout, max_conns=MaxConns,
+		stats_counters_ref=StatsCounters,
+		logger=Logger}, CurConns, NbChildren, Sleepers}};
 system_code_change(Misc, _, _, _) ->
 	{ok, Misc}.
 

+ 2 - 0
src/ranch_conns_sup_sup.erl

@@ -32,6 +32,8 @@ init({Ref, Transport, Protocol, Logger}) ->
 	TransOpts = ranch_server:get_transport_options(Ref),
 	NumAcceptors = maps:get(num_acceptors, TransOpts, 10),
 	NumConnsSups = maps:get(num_conns_sups, TransOpts, NumAcceptors),
+	StatsCounters = counters:new(2*NumConnsSups, []),
+	ok = ranch_server:set_stats_counters(Ref, StatsCounters),
 	ChildSpecs = [#{
 		id => {ranch_conns_sup, N},
 		start => {ranch_conns_sup, start_link, [Ref, N, Transport, TransOpts, Protocol, Logger]},

+ 18 - 0
src/ranch_server.erl

@@ -32,6 +32,8 @@
 -export([get_addr/1]).
 -export([set_max_connections/2]).
 -export([get_max_connections/1]).
+-export([set_stats_counters/2]).
+-export([get_stats_counters/1]).
 -export([set_transport_options/2]).
 -export([get_transport_options/1]).
 -export([set_protocol_options/2]).
@@ -79,6 +81,7 @@ cleanup_listener_opts(Ref) ->
 	%% expected a crash (because the listener was stopped).
 	%% Deleting it explictly here removes any possible confusion.
 	_ = ets:match_delete(?TAB, {{conns_sup, Ref, '_'}, '_'}),
+	_ = ets:delete(?TAB, {stats_counters, Ref}),
 	%% Ditto for the listener supervisor.
 	_ = ets:delete(?TAB, {listener_sup, Ref}),
 	ok.
@@ -86,6 +89,7 @@ cleanup_listener_opts(Ref) ->
 -spec cleanup_connections_sups(ranch:ref()) -> ok.
 cleanup_connections_sups(Ref) ->
 	_ = ets:match_delete(?TAB, {{conns_sup, Ref, '_'}, '_'}),
+	_ = ets:delete(?TAB, {stats_counters, Ref}),
 	ok.
 
 -spec set_connections_sup(ranch:ref(), non_neg_integer(), pid()) -> ok.
@@ -139,6 +143,14 @@ set_max_connections(Ref, MaxConnections) ->
 get_max_connections(Ref) ->
 	ets:lookup_element(?TAB, {max_conns, Ref}, 2).
 
+-spec set_stats_counters(ranch:ref(), counters:counters_ref()) -> ok.
+set_stats_counters(Ref, Counters) ->
+	gen_server:call(?MODULE, {set_stats_counters, Ref, Counters}).
+
+-spec get_stats_counters(ranch:ref()) -> counters:counters_ref().
+get_stats_counters(Ref) ->
+	ets:lookup_element(?TAB, {stats_counters, Ref}, 2).
+
 -spec set_transport_options(ranch:ref(), any()) -> ok.
 set_transport_options(Ref, TransOpts) ->
 	gen_server:call(?MODULE, {set_trans_opts, Ref, TransOpts}).
@@ -198,6 +210,9 @@ handle_call({set_max_conns, Ref, MaxConns}, _, State) ->
 	ets:insert(?TAB, {{max_conns, Ref}, MaxConns}),
 	_ = [ConnsSup ! {set_max_conns, MaxConns} || {_, ConnsSup} <- get_connections_sups(Ref)],
 	{reply, ok, State};
+handle_call({set_stats_counters, Ref, Counters}, _, State) ->
+	ets:insert(?TAB, {{stats_counters, Ref}, Counters}),
+	{reply, ok, State};
 handle_call({set_trans_opts, Ref, Opts}, _, State) ->
 	ets:insert(?TAB, {{trans_opts, Ref}, Opts}),
 	{reply, ok, State};
@@ -237,6 +252,9 @@ terminate(_Reason, _State) ->
 	ok.
 
 -spec code_change(term() | {down, term()}, #state{}, term()) -> {ok, term()}.
+code_change({down, _}, State, _Extra) ->
+	true = ets:match_delete(?TAB, {{stats_counters, '_'}, '_'}),
+	{ok, State};
 code_change(_OldVsn, State, _Extra) ->
 	{ok, State}.
 

+ 46 - 3
test/acceptor_SUITE.erl

@@ -75,6 +75,7 @@ groups() ->
 		misc_repeated_remove,
 		misc_info,
 		misc_info_embedded,
+		misc_metrics,
 		misc_opts_logger,
 		misc_set_transport_options,
 		misc_wait_for_connections,
@@ -281,6 +282,48 @@ misc_info_embedded(_) ->
 	embedded_sup:stop(SupPid),
 	ok.
 
+misc_metrics(_) ->
+	doc("Confirm accept/terminate metrics are correct."),
+	Name = name(),
+	{ok, _} = ranch:start_listener(Name, ranch_tcp, #{},
+		notify_and_wait_protocol, #{pid => self()}),
+	Port = ranch:get_port(Name),
+	%% Start 10 connections.
+	ok = connect_loop(Port, 10, 0),
+	{10, ConnPids1} = receive_loop(connected, 400),
+	#{metrics := Metrics1} = ranch:info(Name),
+	{10, 0} = do_accumulate_metrics(Metrics1),
+	%% Start 10 more connections.
+	ok = connect_loop(Port, 10, 0),
+	{10, ConnPids2} = receive_loop(connected, 400),
+	#{metrics := Metrics2} = ranch:info(Name),
+	{20, 0} = do_accumulate_metrics(Metrics2),
+	%% Terminate 10 connections.
+	ok = terminate_loop(stop, ConnPids2),
+	timer:sleep(100),
+	#{metrics := Metrics3} = ranch:info(Name),
+	{20, 10} = do_accumulate_metrics(Metrics3),
+	%% Terminate 10 more connections.
+	ok = terminate_loop(stop, ConnPids1),
+	timer:sleep(100),
+	#{metrics := Metrics4} = ranch:info(Name),
+	{20, 20} = do_accumulate_metrics(Metrics4),
+	ok = ranch:stop_listener(Name),
+	{'EXIT', _} = begin catch ranch:get_port(Name) end,
+	ok.
+
+do_accumulate_metrics(Metrics) ->
+	maps:fold(
+		fun
+			({conns_sup, _, accept}, N, {Accepts, Terminates}) ->
+				{Accepts+N, Terminates};
+			({conns_sup, _, terminate}, N, {Accepts, Terminates}) ->
+				{Accepts, Terminates+N}
+		end,
+		{0, 0},
+		Metrics
+	).
+
 misc_opts_logger(_) ->
 	doc("Confirm that messages are sent via the configured logger module."),
 	register(misc_opts_logger, self()),
@@ -322,9 +365,9 @@ misc_set_transport_options(_) ->
 	ConnsSups = [ConnsSup || {_, ConnsSup} <- ranch_server:get_connections_sups(Name)],
 	_ = [begin
 		{State, _, _, _} = sys:get_state(ConnsSup),
-		20 = element(10, State),
-		5001 = element(9, State),
-		1001 = element(5, State)
+		20 = element(11, State),
+		5001 = element(10, State),
+		1001 = element(6, State)
 	end || ConnsSup <- ConnsSups],
 	ok = ranch:suspend_listener(Name),
 	ok = ranch:resume_listener(Name),

+ 29 - 1
test/upgrade_SUITE.erl

@@ -192,13 +192,18 @@ upgrade_ranch_one_conn(_) ->
 
 do_upgrade_ranch_one_conn() ->
 	Example = tcp_echo,
+	ExampleStr = atom_to_list(Example),
 	Port = 5555,
+	{_, Rel, _} = do_get_paths(Example),
 	try
 		%% Copy the example.
 		do_copy(Example),
 		%% Build and start the example release using the previous Ranch version.
 		CommitOrTag = do_use_ranch_previous(Example),
 		do_compile_and_start(Example),
+		%% Ensure that the metrics key is not present in the ranch:info output.
+		"false\n" = do_exec_log(Rel ++ " eval "
+			"'maps:is_key(metrics, ranch:info(" ++ ExampleStr ++ "))'"),
 		%% Establish a connection and check that it works.
 		{ok, S} = gen_tcp:connect("localhost", Port, [{active, false}, binary]),
 		ok = gen_tcp:send(S, "Hello!"),
@@ -207,12 +212,35 @@ do_upgrade_ranch_one_conn() ->
 		do_build_relup(Example, CommitOrTag),
 		%% Perform the upgrade, then check that our connection is still up.
 		do_upgrade(Example),
+		%% Ensure that the mextrics key is present in the ranch:info output.
+		"true\n" = do_exec_log(Rel ++ " eval "
+			"'maps:is_key(metrics, ranch:info(" ++ ExampleStr ++ "))'"),
 		ok = gen_tcp:send(S, "Hello!"),
 		{ok, <<"Hello!">>} = gen_tcp:recv(S, 0, 1000),
+		%% Ensure that no accepts have been counted yet.
+		"0\n" = do_exec_log(Rel ++ " eval "
+			"'lists:sum([N || {{conns_sup, _, accept}, N} <- "
+			"maps:to_list(maps:get(metrics, ranch:info(" ++ ExampleStr ++ ")))])'"),
 		%% Check that new connections are still accepted.
-		{ok, _} = gen_tcp:connect("localhost", Port, [{active, false}, binary]),
+		{ok, S2} = gen_tcp:connect("localhost", Port, [{active, false}, binary]),
+		%% Ensure that the accept has been counted.
+		"1\n" = do_exec_log(Rel ++ " eval "
+			"'lists:sum([N || {{conns_sup, _, accept}, N} <- "
+			"maps:to_list(maps:get(metrics, ranch:info(" ++ ExampleStr ++ ")))])'"),
+		%% Ensure that no terminates have been counted yet.
+		"0\n" = do_exec_log(Rel ++ " eval "
+			"'lists:sum([N || {{conns_sup, _, terminate}, N} <- "
+			"maps:to_list(maps:get(metrics, ranch:info(" ++ ExampleStr ++ ")))])'"),
+		%% Close the socket, ensure that the termination has been counted.
+		ok = gen_tcp:close(S2),
+		"1\n" = do_exec_log(Rel ++ " eval "
+			"'lists:sum([N || {{conns_sup, _, terminate}, N} <- "
+			"maps:to_list(maps:get(metrics, ranch:info(" ++ ExampleStr ++ ")))])'"),
 		%% Perform the downgrade, then check that our connection is still up.
 		do_downgrade(Example),
+		%% Ensure that the mextrics key is not present any more.
+		"false\n" = do_exec_log(Rel ++ " eval "
+			"'maps:is_key(metrics, ranch:info(" ++ ExampleStr ++ "))'"),
 		ok = gen_tcp:send(S, "Hello!"),
 		{ok, <<"Hello!">>} = gen_tcp:recv(S, 0, 1000),
 		%% Check that new connections are still accepted.