File 7632-diameter-Add-various-utility-info-functions.patch of Package erlang
From 8c2ff23ea4cf2c29fd7d72339de408bbdaaf10b5 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 27 Feb 2024 12:56:31 +0100
Subject: [PATCH 2/5] [diameter] Add various utility/info functions
---
lib/diameter/src/base/diameter.erl | 91 ++++++++++-
lib/diameter/src/base/diameter_config.erl | 32 ++++
lib/diameter/src/base/diameter_service.erl | 162 ++++++++++++++++++-
lib/diameter/test/diameter_traffic_SUITE.erl | 47 +++++-
4 files changed, 323 insertions(+), 9 deletions(-)
diff --git a/lib/diameter/src/base/diameter.erl b/lib/diameter/src/base/diameter.erl
index 3231327c64..0d12dcc196 100644
--- a/lib/diameter/src/base/diameter.erl
+++ b/lib/diameter/src/base/diameter.erl
@@ -25,6 +25,9 @@
stop_service/1,
add_transport/2,
remove_transport/2,
+ which_transports/0, which_transports/1,
+ which_watchdogs/0, which_watchdogs/1,
+ which_connections/0, which_connections/1,
subscribe/1,
unsubscribe/1]).
@@ -142,6 +145,7 @@ start_service(SvcName, Opts)
stop_service(SvcName) ->
diameter_config:stop_service(SvcName).
+
%% ---------------------------------------------------------------------------
%% services/0
%% ---------------------------------------------------------------------------
@@ -152,6 +156,7 @@ stop_service(SvcName) ->
services() ->
[Name || {Name, _} <- diameter_service:services()].
+
%% ---------------------------------------------------------------------------
%% service_info/2
%% ---------------------------------------------------------------------------
@@ -164,7 +169,7 @@ service_info(SvcName, Option) ->
diameter_service:info(SvcName, Option).
%% ---------------------------------------------------------------------------
-%% peer_info/2
+%% peer_info/1
%% ---------------------------------------------------------------------------
-spec peer_info(peer_ref())
@@ -206,6 +211,90 @@ add_transport(SvcName, {T, Opts} = Cfg)
remove_transport(SvcName, Pred) ->
diameter_config:remove_transport(SvcName, Pred).
+
+%% ---------------------------------------------------------------------------
+%% which_transport/0, which_transport/1
+%% ---------------------------------------------------------------------------
+
+-spec which_transports() -> [#{ref := reference(),
+ type := atom(),
+ service := string()}].
+which_transports() ->
+ diameter_config:which_transports().
+
+
+-spec which_transports(SvcName) -> [#{ref := reference(),
+ type := atom()}] when
+ SvcName :: string().
+
+which_transports(SvcName) ->
+ diameter_config:which_transports(SvcName).
+
+
+%% ---------------------------------------------------------------------------
+%% which_watchdogs/0, which_watchdogs/1
+%% ---------------------------------------------------------------------------
+
+-spec which_watchdogs() -> [#{ref := reference(),
+ type := atom(),
+ pid := pid(),
+ state := diameter_service:wd_state(),
+ peer := boolean() | pid(),
+ uptime := {Hours, Mins, Secs, MicroSecs},
+ service := SvcName}] when
+ Hours :: non_neg_integer(),
+ Mins :: 0..59,
+ Secs :: 0..59,
+ MicroSecs :: 0..999999,
+ SvcName :: string().
+
+which_watchdogs() ->
+ diameter_service:which_watchdogs().
+
+
+-spec which_watchdogs(SvcName) ->
+ [#{ref := reference(),
+ type := atom(),
+ pid := pid(),
+ state := diameter_service:wd_state(),
+ peer := boolean() | pid(),
+ uptime := {Hours, Mins, Secs, MicroSecs}}] when
+ SvcName :: string(),
+ Hours :: non_neg_integer(),
+ Mins :: 0..59,
+ Secs :: 0..59,
+ MicroSecs :: 0..999999.
+
+which_watchdogs(SvcName) ->
+ diameter_service:which_watchdogs(SvcName).
+
+
+%% ---------------------------------------------------------------------------
+%% which_connections/0, which_connections/1
+%% ---------------------------------------------------------------------------
+
+-spec which_connections() ->
+ [{SvcName,
+ [#{peer := term(),
+ wd := term(),
+ peername := {inet:ip_address(), inet:port_number()},
+ sockname := {inet:ip_address(), inet:port_number()}}]}] when
+ SvcName :: string().
+
+which_connections() ->
+ diameter_service:which_connections().
+
+-spec which_connections(SvcName) ->
+ [#{peer := term(),
+ wd := term(),
+ peername := {inet:ip_address(), inet:port_number()},
+ sockname := {inet:ip_address(), inet:port_number()}}] when
+ SvcName :: string().
+
+which_connections(SvcName) ->
+ diameter_service:which_connections(SvcName).
+
+
%% ---------------------------------------------------------------------------
%% subscribe/1
%% ---------------------------------------------------------------------------
diff --git a/lib/diameter/src/base/diameter_config.erl b/lib/diameter/src/base/diameter_config.erl
index 0d6610b866..cf900186d3 100644
--- a/lib/diameter/src/base/diameter_config.erl
+++ b/lib/diameter/src/base/diameter_config.erl
@@ -46,6 +46,10 @@
lookup/1,
subscribe/2]).
+-export([
+ which_transports/0, which_transports/1
+ ]).
+
%% server start
-export([start_link/0,
start_link/1]).
@@ -234,6 +238,7 @@ pred(_) ->
subscribe(Ref, T) ->
diameter_reg:subscribe(?TRANSPORT_KEY(Ref), T).
+
%% --------------------------------------------------------------------------
%% # have_transport/2
%%
@@ -248,6 +253,32 @@ have_transport(SvcName, Ref) ->
{'=:=', '$2', {const, Ref}}}],
[true]}]).
+
+%% --------------------------------------------------------------------------
+%% # which_transports/0,1
+%% --------------------------------------------------------------------------
+
+which_transports() ->
+ MatchHead = #transport{service = '$1',
+ ref = '$2',
+ type = '$3',
+ _ = '_'},
+ Guard = [],
+ Return = [{{'$2', '$3', '$1'}}],
+ [#{ref => Ref, type => Type, service => Service} ||
+ {Ref, Type, Service} <- select([{MatchHead, Guard, Return}])].
+
+which_transports(SvcName) ->
+ MatchHead = #transport{service = '$1',
+ ref = '$2',
+ type = '$3',
+ _ = '_'},
+ Guard = [{'=:=', '$1', {const, SvcName}}],
+ Return = [{{'$2', '$3'}}],
+ [#{ref => Ref, type => Type} ||
+ {Ref, Type} <- select([{MatchHead, Guard, Return}])].
+
+
%% --------------------------------------------------------------------------
%% # lookup/1
%% --------------------------------------------------------------------------
@@ -263,6 +294,7 @@ lookup(SvcName) ->
[{'=:=', '$1', {const, SvcName}}],
[{{'$2', '$3', '$4'}}]}]).
+
%% ---------------------------------------------------------
%% EXPORTED INTERNAL FUNCTIONS
%% ---------------------------------------------------------
diff --git a/lib/diameter/src/base/diameter_service.erl b/lib/diameter/src/base/diameter_service.erl
index 22fecf74a5..a2a3771270 100644
--- a/lib/diameter/src/base/diameter_service.erl
+++ b/lib/diameter/src/base/diameter_service.erl
@@ -55,7 +55,9 @@
call_module/3,
whois/1,
state/1,
- uptime/1]).
+ uptime/1,
+ which_watchdogs/0, which_watchdogs/1,
+ which_connections/0, which_connections/1]).
%% gen_server callbacks
-export([init/1,
@@ -65,9 +67,16 @@
terminate/2,
code_change/3]).
+-export_type([wd_state/0]).
+
-include_lib("diameter/include/diameter.hrl").
-include("diameter_internal.hrl").
+%% Enable debug logging by set(ing) level to debug.
+%% For example: logger:set_primary_config(level, debug),
+%% -define(DBG(F,A),
+%% logger:debug("~w:~w(~w) -> " ++ F ++ "~n",
+%% [?MODULE, ?FUNCTION_NAME, ?LINE | A])).
%% RFC 3539 watchdog states.
-define(WD_INITIAL, initial).
@@ -205,6 +214,138 @@ stop_transport(_, []) ->
stop_transport(SvcName, [_|_] = Refs) ->
call_service_by_name(SvcName, {stop, Refs}).
+
+%% --------------------------------------------------------------------------
+%% # which_watchdogs/0, which_watchdogs/1
+%% --------------------------------------------------------------------------
+
+which_watchdogs() ->
+ which_watchdogs(services(), []).
+
+which_watchdogs([], Acc) ->
+ lists:flatten(lists:reverse(Acc));
+which_watchdogs([{SvcName, _} | Services], Acc) ->
+ case which_watchdogs(SvcName) of
+ WDs when is_list(WDs) ->
+ which_watchdogs(Services,
+ [[WD#{service => SvcName} || WD <- WDs] | Acc]);
+ undefined ->
+ which_watchdogs(Services, Acc)
+ end.
+
+which_watchdogs(SvcName) ->
+ case lookup_state(SvcName) of
+ [#state{watchdogT = WDT}] ->
+ [#{pid => Pid,
+ ref => Ref,
+ type => Type,
+ state => State,
+ uptime => diameter_lib:now_diff(Started),
+ peer => Peer} ||
+ #watchdog{pid = Pid,
+ type = Type,
+ ref = Ref,
+ state = State,
+ started = Started,
+ peer = Peer} <- ets:tab2list(WDT)];
+ [] ->
+ undefined
+ end.
+
+
+%% ---------------------------------------------------------------------------
+%% # which_connections/0, which_connections/1
+%% ---------------------------------------------------------------------------
+
+which_connections() ->
+ Services = [SvcName || {SvcName, _} <- services()],
+ which_connections1(Services).
+
+which_connections1(Services) ->
+ which_connections1(Services, []).
+
+which_connections1([], Acc) ->
+ lists:reverse(Acc);
+which_connections1([SvcName | Services], Acc) ->
+ case which_connections(SvcName) of
+ [] ->
+ which_connections1(Services, Acc);
+ Conns ->
+ which_connections1(Services, [{SvcName, Conns} | Acc])
+ end.
+
+which_connections(SvcName) ->
+ case lookup_state(SvcName) of
+ [#state{watchdogT = WDT,
+ local = {PT, _, _}}] ->
+ connections_info(WDT, PT);
+ [] ->
+ []
+ end.
+
+connections_info(WDT, PT) ->
+ try ets:tab2list(WDT) of
+ L ->
+ connections_info2(PT, L)
+ catch
+ error: badarg -> [] %% service has gone down
+ end.
+
+connections_info2(PT, L) ->
+ connections_info2(PT, L, []).
+
+connections_info2(_PT, [], Acc) ->
+ lists:reverse(Acc);
+connections_info2(PT, [WD | WDs], Acc) ->
+ ConnInfo = connection_info(PT, WD),
+ connections_info2(PT, WDs, [ConnInfo | Acc]).
+
+connection_info(PT, #watchdog{pid = Pid,
+ type = Type,
+ ref = Ref,
+ state = State,
+ started = Started,
+ peer = TPid}) ->
+ Info = #{wd => #{ref => Ref,
+ pid => Pid,
+ type => Type,
+ state => State,
+ uptime => diameter_lib:now_diff(Started)}
+ },
+ connection_info2(PT, TPid, State, Info).
+
+connection_info2(PT, TPid, State, Info)
+ when is_pid(TPid) andalso (State =/= ?WD_DOWN) ->
+ try ets:lookup(PT, TPid) of
+ [#peer{pid = PPid, started = Started}] ->
+ connection_info3(PPid, Started, Info);
+ [] ->
+ Info
+ catch
+ error: badarg -> [] %% service has gone down
+ end;
+connection_info2(_PT, _PPid, _State, Info) ->
+ Info.
+
+connection_info3(PPid, Started, Info) ->
+ Info2 = Info#{peer => #{pid => PPid,
+ uptime => diameter_lib:now_diff(Started)}},
+ {_, PD} = process_info(PPid, dictionary),
+ {_, T} = lists:keyfind({diameter_peer_fsm, start}, 1, PD),
+ {TPid, {_Type, TMod, _Cfg}} = T,
+ {_, TD} = process_info(TPid, dictionary),
+ {_, Data} = lists:keyfind({TMod, info}, 1, TD),
+ try TMod:info(Data) of
+ TInfo ->
+ Socket = proplists:get_value(socket, TInfo),
+ Peer = proplists:get_value(peer, TInfo),
+ Info2#{sockname => Socket,
+ peername => Peer}
+ catch
+ _:_ -> Info2
+ end.
+
+
%% ---------------------------------------------------------------------------
%% # info/2
%% ---------------------------------------------------------------------------
@@ -386,6 +527,10 @@ uptime(Svc) ->
call_module(Service, AppMod, Request) ->
call_service(Service, {call_module, AppMod, Request}).
+
+%% ===========================================================================
+%% ===========================================================================
+
%% ---------------------------------------------------------------------------
%% # init/1
%% ---------------------------------------------------------------------------
@@ -1974,7 +2119,8 @@ complete_info(Item, #state{service = Svc} = S) ->
#diameter_caps.firmware_revision;
capabilities -> service_info(?CAP_INFO, S);
applications -> info_apps(S);
- transport -> info_transport(S);
+ transport -> info_transport(S, false);
+ transport_simple -> info_transport(S, true);
options -> info_options(S);
keys -> ?ALL_INFO ++ ?CAP_INFO ++ ?OTHER_INFO;
all -> service_info(?ALL_INFO, S);
@@ -2016,7 +2162,16 @@ info_stats(#state{watchdogT = WatchdogT}) ->
%% the accumulated values for the ref and associated watchdog/peer
%% pids.
-info_transport(S) ->
+%% foo() ->
+%% #{ref :: reference(),
+%% type :: connect | listen,
+%% transport_module :: module(),
+%% wd :: {pid(), integer(), wd_state()},
+%% peer :: {pid(), Started :: integer()},
+%% local :: {inet:ip_address(), inet:port_number()},
+%% remote :: {inet:ip_address(), inet:port_number()}}.
+
+info_transport(S, _) ->
PeerD = peer_dict(S, config_dict(S)),
Stats = diameter_stats:sum(dict:fetch_keys(PeerD)),
dict:fold(fun(R, Ls, A) ->
@@ -2165,7 +2320,6 @@ bins_sum3([{P, S, _} | T], N, D) ->
bins_sum3(T, N-1, dict:store(P,S,D)).
-
%% The point of extracting the config here is so that 'transport' info
%% has one entry for each transport ref, the peer table only
diff --git a/lib/diameter/test/diameter_traffic_SUITE.erl b/lib/diameter/test/diameter_traffic_SUITE.erl
index 37fc2d9446..ac1d8c35fa 100644
--- a/lib/diameter/test/diameter_traffic_SUITE.erl
+++ b/lib/diameter/test/diameter_traffic_SUITE.erl
@@ -298,14 +298,53 @@ traffic(#group{} = Cfg) ->
ok = client(Cfg, LRef),
[] = send(Cfg),
- io:format("Service(s) info: "
- "~n ~p"
- "~n", [[{SvcName, diameter:service_info(SvcName, all)} ||
- SvcName <- diameter:services()]]),
+ print_services_info(),
ok = stop_services(Cfg),
[] = ets:tab2list(diameter_request).
+
+print_services_info() ->
+ print_services_info(diameter:services()).
+
+print_services_info([]) ->
+ io:format("~n", []);
+print_services_info([Service | Services]) ->
+ io:format("~n Service: ~s"
+ "~n Config:"
+ "~n ~p"
+ "~n Which Connections:"
+ "~n ~p"
+ "~n Which Connections/Service:"
+ "~n ~p"
+ "~n Which Watchdogs:"
+ "~n ~p"
+ "~n Which Watchdogs/Service:"
+ "~n ~p"
+ "~n Which Transports:"
+ "~n ~p"
+ "~n Which Transports/Service:"
+ "~n ~p"
+ "~n Peers Info:"
+ "~n ~p"
+ "~n Transport Info:"
+ "~n ~p"
+ "~n All info:"
+ "~n ~p",
+ [Service,
+ diameter_config:lookup(Service),
+ diameter:which_connections(),
+ diameter:which_connections(Service),
+ diameter:which_watchdogs(),
+ diameter:which_watchdogs(Service),
+ diameter:which_transports(),
+ diameter:which_transports(Service),
+ diameter:service_info(Service, peers),
+ diameter:service_info(Service, transport),
+ diameter:service_info(Service, all)]),
+ print_services_info(Services).
+
+
%% start_service/2
start_service(Svc, Opts) ->
--
2.35.3