Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
7631-diameter-Add-new-servcie-option-bins_info....
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 7631-diameter-Add-new-servcie-option-bins_info.patch of Package erlang
From 47fe888b332f3ba7813e2f1a210587c74f60a750 Mon Sep 17 00:00:00 2001 From: Micael Karlberg <bmk@erlang.org> Date: Thu, 22 Feb 2024 15:16:01 +0100 Subject: [PATCH 1/5] [diameter] Add new servcie option bins_info --- lib/diameter/src/base/diameter.erl | 13 ++- lib/diameter/src/base/diameter_config.erl | 20 +++- lib/diameter/src/base/diameter_service.erl | 101 ++++++++++++++----- lib/diameter/test/diameter_traffic_SUITE.erl | 30 +++++- 4 files changed, 127 insertions(+), 37 deletions(-) diff --git a/lib/diameter/src/base/diameter.erl b/lib/diameter/src/base/diameter.erl index 557c6ffdf7..3231327c64 100644 --- a/lib/diameter/src/base/diameter.erl +++ b/lib/diameter/src/base/diameter.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2020. All Rights Reserved. +%% Copyright Ericsson AB 2010-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -87,6 +87,13 @@ -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])). + + %% --------------------------------------------------------------------------- %% start/0 %% --------------------------------------------------------------------------- @@ -98,6 +105,7 @@ start() -> application:start(?APPLICATION). + %% --------------------------------------------------------------------------- %% stop/0 %% --------------------------------------------------------------------------- @@ -109,6 +117,7 @@ start() -> stop() -> application:stop(?APPLICATION). + %% --------------------------------------------------------------------------- %% start_service/2 %% --------------------------------------------------------------------------- @@ -121,6 +130,7 @@ start_service(SvcName, Opts) when is_list(Opts) -> diameter_config:start_service(SvcName, Opts). + %% --------------------------------------------------------------------------- %% stop_service/1 %% --------------------------------------------------------------------------- @@ -382,6 +392,7 @@ call(SvcName, App, Message) -> | {string_decode, boolean()} | {traffic_counters, boolean()} | {use_shared_peers, remotes()} + | {bins_info, boolean() | non_neg_integer()} | common_opt(). -type application_opt() diff --git a/lib/diameter/src/base/diameter_config.erl b/lib/diameter/src/base/diameter_config.erl index 495e57e456..0d6610b866 100644 --- a/lib/diameter/src/base/diameter_config.erl +++ b/lib/diameter/src/base/diameter_config.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2020. All Rights Reserved. +%% Copyright Ericsson AB 2010-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -68,6 +68,7 @@ -include_lib("diameter/include/diameter.hrl"). -include("diameter_internal.hrl"). + %% Server state. -record(state, {id = diameter_lib:now(), role :: server | transport}). @@ -127,6 +128,7 @@ %%% The return values below assume the server diameter_config is started. %%% The functions will exit if it isn't. + %% -------------------------------------------------------------------------- %% # start_service/2 %% -------------------------------------------------------------------------- @@ -655,6 +657,9 @@ opt(service = S, {sequence = K, F}) -> {error, {E, R, Stack}} end; +opt(service, {bins_info, BI}) -> + is_boolean(BI) orelse (is_integer(BI) andalso (BI >= 0)); + opt(transport, {transport_module, M}) -> is_atom(M); @@ -792,6 +797,7 @@ stop_transport(SvcName, Refs) -> %% make_config/2 make_config(SvcName, Opts) -> + AppOpts = [T || {application, _} = T <- Opts], Apps = [init_app(T) || T <- AppOpts], @@ -809,10 +815,14 @@ make_config(SvcName, Opts) -> D = proplists:get_value(string_decode, SvcOpts, true), - #service{name = SvcName, - rec = #diameter_service{applications = Apps, - capabilities = binary_caps(Caps, D)}, - options = SvcOpts}. + Service = + #service{name = SvcName, + rec = #diameter_service{applications = Apps, + capabilities = binary_caps(Caps, D)}, + options = SvcOpts}, + + Service. + binary_caps(Caps, true) -> Caps; diff --git a/lib/diameter/src/base/diameter_service.erl b/lib/diameter/src/base/diameter_service.erl index 6ff9de3341..22fecf74a5 100644 --- a/lib/diameter/src/base/diameter_service.erl +++ b/lib/diameter/src/base/diameter_service.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2022. All Rights Reserved. +%% Copyright Ericsson AB 2010-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -68,6 +68,7 @@ -include_lib("diameter/include/diameter.hrl"). -include("diameter_internal.hrl"). + %% RFC 3539 watchdog states. -define(WD_INITIAL, initial). -define(WD_OKAY, okay). @@ -107,6 +108,7 @@ local :: {ets:tid(), ets:tid(), ets:tid()}, remote :: {ets:tid(), ets:tid(), ets:tid()}, monitor = false :: false | pid(), %% process to die with + bins_info = true :: boolean() | non_neg_integer(), options :: #{sequence := diameter:sequence(), %% sequence mask share_peers := diameter:remotes(),%% broadcast to use_shared_peers := diameter:remotes(),%% use from @@ -155,6 +157,7 @@ watchdog :: match(pid() %% key into watchdogT | undefined)}). %% undefined if remote + %% --------------------------------------------------------------------------- %% # start/1 %% --------------------------------------------------------------------------- @@ -690,9 +693,11 @@ cs(undefined, _) -> i(SvcName) -> %% Split the config into a server state and a list of transports. + Config = diameter_config:lookup(SvcName), + {#state{} = S, CL} = lists:foldl(fun cfg_acc/2, {false, []}, - diameter_config:lookup(SvcName)), + Config), %% Publish the state in order to be able to access it outside of %% the service process. Originally table identifiers were only @@ -711,17 +716,20 @@ i(SvcName) -> cfg_acc({SvcName, #diameter_service{applications = Apps} = Rec, Opts}, {false, Acc}) -> + lists:foreach(fun init_mod/1, Apps), #{monitor := M} = SvcOpts = service_opts(Opts), + S = #state{service_name = SvcName, service = Rec#diameter_service{pid = self()}, local = init_peers(), remote = init_peers(), monitor = mref(M), options = maps:remove(monitor, SvcOpts)}, - {S, Acc}; + BinsInfo = proplists:get_value(bins_info, Opts, S#state.bins_info), + {S#state{bins_info = BinsInfo}, Acc}; cfg_acc({_Ref, Type, _Opts} = T, {S, Acc}) when Type == connect; @@ -737,14 +745,17 @@ init_peers() -> %% Valid service options are all 2-tuples. service_opts(Opts) -> - remove([{strict_arities, true}, {avp_dictionaries, []}], - merge(lists:append([[{monitor, false}] | def_opts()]), Opts)). + remove([{bins_info, true}, {strict_arities, true}, {avp_dictionaries, []}], + merge(lists:append([[{monitor, false}] | def_opts()]), + lists:keydelete(bins_info, 1, Opts))). merge(List1, List2) -> maps:merge(maps:from_list(List1), maps:from_list(List2)). remove(List, Map) -> - maps:filter(fun(K,V) -> not lists:member({K,V}, List) end, + maps:filter(fun(K,V) -> + not lists:member({K,V}, List) + end, Map). def_opts() -> %% defaults on the options map @@ -2049,9 +2060,13 @@ keys(connect = T, Opts) -> keys(_, _) -> [{listen, accept}]. -peer_dict(#state{watchdogT = WatchdogT, local = {PeerT, _, _}}, Dict0) -> +peer_dict(#state{watchdogT = WatchdogT, + local = {PeerT, _, _}, + bins_info = BinsInfo}, Dict0) -> try ets:tab2list(WatchdogT) of - L -> lists:foldl(fun(T,A) -> peer_acc(PeerT, A, T) end, Dict0, L) + L -> lists:foldl(fun(T,A) -> + peer_acc(PeerT, A, T, BinsInfo) + end, Dict0, L) catch error: badarg -> Dict0 %% service has gone down end. @@ -2062,12 +2077,12 @@ peer_acc(PeerT, Acc, #watchdog{pid = Pid, options = Opts, state = WS, started = At, - peer = TPid}) -> + peer = TPid}, BinsInfo) -> Info = [{type, Type}, {options, Opts}, {watchdog, {Pid, At, WS}} | info_peer(PeerT, TPid, WS)], - dict:append(Ref, Info ++ [{info, info_process_info(Info)}], Acc). + dict:append(Ref, Info ++ [{info, info_process_info(Info, BinsInfo)}], Acc). info_peer(PeerT, TPid, WS) when is_pid(TPid), WS /= ?WD_DOWN -> @@ -2079,29 +2094,36 @@ info_peer(PeerT, TPid, WS) info_peer(_, _, _) -> []. -info_process_info(Info) -> - lists:flatmap(fun ipi/1, Info). +info_process_info(Info, BinsInfo) -> + lists:flatmap(fun(X) -> ipi(X, BinsInfo) end, Info). -ipi({watchdog, {Pid, _, _}}) -> - info_pid(Pid); +ipi({watchdog, {Pid, _, _}}, BinsInfo) -> + info_pid(Pid, BinsInfo); -ipi({peer, {Pid, _}}) -> - info_pid(Pid); +ipi({peer, {Pid, _}}, BinsInfo) -> + info_pid(Pid, BinsInfo); -ipi({port, [{owner, Pid} | _]}) -> - info_pid(Pid); +ipi({port, [{owner, Pid} | _]}, BinsInfo) -> + info_pid(Pid, BinsInfo); -ipi(_) -> +ipi(_, _) -> []. -info_pid(Pid) -> - case process_info(Pid, [message_queue_len, memory, binary]) of +info_pid(Pid, BinsInfo) -> + InfoItems = info_pid_items(BinsInfo), + case process_info(Pid, InfoItems) of undefined -> []; L -> - [{Pid, lists:map(fun({K,V}) -> {K, map_info(K,V)} end, L)}] + [{Pid, lists:map(fun({K,V}) -> {K, map_info(K,V,BinsInfo)} end, L)}] end. +info_pid_items(false) -> + [message_queue_len, memory]; +info_pid_items(_) -> + [message_queue_len, memory, binary]. + + %% The binary list consists of 3-tuples {Ptr, Size, Count}, where Ptr %% is a C pointer value, Size is the size of a referenced binary in %% bytes, and Count is a global reference count. The same Ptr can @@ -2113,15 +2135,38 @@ info_pid(Pid) -> %% The list can be quite large, and we aren't often interested in the %% pointers or counts, so whittle this down to the number of binaries %% referenced and their total byte count. -map_info(binary, L) -> - SzD = lists:foldl(fun({P,S,_}, D) -> dict:store(P,S,D) end, - dict:new(), - L), - {dict:size(SzD), dict:fold(fun(_,S,N) -> S + N end, 0, SzD)}; +map_info(binary, L, BinsInfo) -> + {RemainingL, SzD} = bins_sum(L, BinsInfo), + {dict:size(SzD), dict:fold(fun(_,S,N) -> S + N end, 0, SzD), RemainingL}; -map_info(_, T) -> + +map_info(_, T, _) -> T. +bins_sum(L, true = _BinsInfo) -> + {0, bins_sum2(L, dict:new())}; +bins_sum(L, BinsInfo) when is_integer(BinsInfo) -> + bins_sum3(L, BinsInfo, dict:new()); +bins_sum(_, _) -> + %% We should actually not get here, but just in case + %% we have a logic error somewhere... + dict:new(). + +bins_sum2([], D) -> + D; +bins_sum2([{P, S, _} | T], D) -> + bins_sum2(T, dict:store(P,S,D)). + +bins_sum3([], _, D) -> + {0, D}; +bins_sum3(L, N, D) when (N =< 0) -> + {length(L), D}; +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 %% containing entries that have a living watchdog. diff --git a/lib/diameter/test/diameter_traffic_SUITE.erl b/lib/diameter/test/diameter_traffic_SUITE.erl index 95ea6be020..37fc2d9446 100644 --- a/lib/diameter/test/diameter_traffic_SUITE.erl +++ b/lib/diameter/test/diameter_traffic_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2022. All Rights Reserved. +%% Copyright Ericsson AB 2010-2024. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -263,6 +263,7 @@ parallel(_Config) -> %% configuration results in sufficient coverage over time. run() -> + %% ok = logger:set_primary_config(level, debug), Svc = ?util:unique_string(), run(#group{transport = ?util:choose(?TRANSPORTS), strings = bool(), @@ -296,6 +297,12 @@ traffic(#group{} = Cfg) -> LRef = server(Cfg), ok = client(Cfg, LRef), [] = send(Cfg), + + io:format("Service(s) info: " + "~n ~p" + "~n", [[{SvcName, diameter:service_info(SvcName, all)} || + SvcName <- diameter:services()]]), + ok = stop_services(Cfg), [] = ets:tab2list(diameter_request). @@ -340,6 +347,10 @@ wait(MRef) -> %% server/1 server(Config) -> + + logger:debug("entry with" + "~n Config: ~p", [Config]), + #group{transport = T, client_sender = CS, server_service = SN, @@ -349,7 +360,8 @@ server(Config) -> = Grp = group(Config), ok = start_service(SN, [{traffic_counters, bool()}, - {decode_format, SD} + {decode_format, SD}, + {bins_info, bins_info()} | ?SERVICE(SN, Grp)]), Cfg = [{sender, SS}, {message_cb, ST andalso {?MODULE, message, [0]}}] @@ -363,6 +375,10 @@ server(Config) -> %% client/1 client(Config, LRef) -> + + logger:debug("entry with" + "~n Config: ~p", [Config]), + #group{transport = T, encoding = E, client_service = CN, @@ -372,7 +388,8 @@ client(Config, LRef) -> ok = start_service(CN, [{traffic_counters, bool()}, {sequence, ?CLIENT_MASK}, {decode_format, map}, - {strict_arities, decode} + {strict_arities, decode}, + {bins_info, bins_info()} | ?SERVICE(CN, Grp)]), _ = [?util:connect(CN, [T | C], LRef, O) || C <- [[{sender, CS} | client_opts(T)]], @@ -387,6 +404,13 @@ client(Config, LRef) -> bool() -> 0.5 =< rand:uniform(). +bins_info() -> + %% Three possibilities: true | false | non_neg_integer() + %% We choose a low range, 42, only because our test does not + %% actually stress the system, so no point in picking a large + %% number. + ?util:choose([true, false, rand:uniform(42)]). + unordered() -> ?util:choose([true, false, 1, 2]). -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor