Skip to content

Commit

Permalink
Merge branch 'bmk/diameter/20241126/test_tweaking' into maint
Browse files Browse the repository at this point in the history
  • Loading branch information
bmk committed Dec 3, 2024
2 parents 67712bc + e0ba268 commit a89db25
Show file tree
Hide file tree
Showing 5 changed files with 416 additions and 47 deletions.
120 changes: 102 additions & 18 deletions lib/diameter/test/diameter_config_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -30,12 +30,18 @@
run/1]).

%% common_test wrapping
-export([suite/0,
-export([
%% Framework functions
suite/0,
all/0,
init_per_suite/1,
end_per_suite/1,

%% The test cases
start_service/1,
add_transport/1]).

-define(util, diameter_util).
-include("diameter_util.hrl").

%% Lists of {Key, GoodConfigList, BadConfigList} with which to
%% configure.
Expand Down Expand Up @@ -202,67 +208,127 @@
[x,x]],
[]}]).


-define(CL(F), ?CL(F, [])).
-define(CL(F, A), ?LOG("DCONF", F, A)).


%% ===========================================================================

suite() ->
[{timetrap, {seconds, 15}}].

all() ->
[start_service,
add_transport].
[
start_service,
add_transport
].


init_per_suite(Config) ->
?DUTIL:init_per_suite(Config).

start_service(_Config) ->
run([start_service]).
end_per_suite(Config) ->
?DUTIL:end_per_suite(Config).

add_transport(_Config) ->
run([add_transport]).

start_service(Config) ->
?CL("~w -> entry", [?FUNCTION_NAME]),
put(dia_factor, dia_factor(Config)),
Res = run([?FUNCTION_NAME]),
?CL("~w -> done when"
"~n Res: ~p", [?FUNCTION_NAME, Res]),
Res.

add_transport(Config) ->
?CL("~w -> entry", [?FUNCTION_NAME]),
put(dia_factor, dia_factor(Config)),
Res = run([?FUNCTION_NAME]),
?CL("~w -> done when"
"~n Res: ~p", [?FUNCTION_NAME, Res]),
Res.

dia_factor(Config) ->
{value, {?FUNCTION_NAME, DiaFactor}} =
lists:keysearch(?FUNCTION_NAME, 1, Config),
DiaFactor.

%% ===========================================================================

%% Factor: >= 1
to(Base, Factor) when (Factor >= 0) ->
round(Base * (((Factor-1) + 10) / 10)).

run() ->
run(all()).

run(List)
when is_list(List) ->
BaseTo = 5000,
To = case get(dia_factor) of
undefined ->
BaseTo;
DF when is_integer(DF) ->
to(BaseTo, DF)
end,
?CL("~w -> timeout calculated to ~w", [?FUNCTION_NAME, To]),
try
?util:run([[[fun run/1, {F, 5000}] || F <- List]])
?RUN([[[fun run/1, {F, To}] || F <- List]])
after
dbg:stop(),
diameter:stop()
end;

run({F, Tmo}) ->
?CL("~w -> entry - try start diameter", [?FUNCTION_NAME]),
ok = diameter:start(),
try
?util:run([{[fun run/1, F], Tmo}])
?CL("~w -> try - run ~p", [?FUNCTION_NAME, F]),
?RUN([{[fun run/1, F], Tmo}])
after
?CL("~w -> after - try stop diameter", [?FUNCTION_NAME]),
ok = diameter:stop()
end;

run(start_service) ->
?util:run([[fun start/1, T]
run(start_service = Case) ->
?CL("~w(~w) -> entry", [?FUNCTION_NAME, Case]),
?RUN([[fun start/1, T]
|| T <- [lists:keyfind(capabilities, 1, ?TRANSPORT_CONFIG)
| ?SERVICE_CONFIG]]);

run(add_transport) ->
?util:run([[fun add/1, T] || T <- ?TRANSPORT_CONFIG]).
run(add_transport = Case) ->
?CL("~w(~w) -> entry", [?FUNCTION_NAME, Case]),
?RUN([[fun add/1, T] || T <- ?TRANSPORT_CONFIG]).

start(T) ->
?CL("~w -> entry with"
"~n T: ~p", [?FUNCTION_NAME, T]),
do(fun start/3, T).

add(T) ->
?CL("~w -> entry with"
"~n T: ~p", [?FUNCTION_NAME, T]),
do(fun add/3, T).


%% ===========================================================================

%% do/2

do(F, {Key, Good, Bad}) ->
?CL("~w -> entry with"
"~n Key: ~p"
"~n Good: ~p"
"~n Bad: ~p", [?FUNCTION_NAME, Key, Good, Bad]),
F(Key, Good, Bad).

%% add/3

add(Key, Good, Bad) ->
?CL("~w -> entry with"
"~n Key: ~p"
"~n Good: ~p"
"~n Bad: ~p", [?FUNCTION_NAME, Key, Good, Bad]),
{[],[]} = {[{Vs,T} || Vs <- Good,
T <- [add(Key, Vs)],
[T] /= [T || {ok,_} <- [T]]],
Expand All @@ -271,12 +337,19 @@ add(Key, Good, Bad) ->
[T] /= [T || {error,_} <- [T]]]}.

add(Key, Vs) ->
?CL("~w -> entry with"
"~n Key: ~p"
"~n Vs: ~p", [?FUNCTION_NAME, Key, Vs]),
T = list_to_tuple([Key | Vs]),
diameter:add_transport(make_ref(), {connect, [T]}).

%% start/3

start(Key, Good, Bad) ->
?CL("~w -> entry with"
"~n Key: ~p"
"~n Good: ~p"
"~n Bad: ~p", [?FUNCTION_NAME, Key, Good, Bad]),
{[],[]} = {[{Vs,T} || Vs <- Good,
T <- [start(Key, Vs)],
T /= ok],
Expand All @@ -285,6 +358,9 @@ start(Key, Good, Bad) ->
[T] /= [T || {error,_} <- [T]]]}.

start(capabilities = K, [Vs]) ->
?CL("~w -> entry with"
"~n K: ~p"
"~n Vs: ~p", [?FUNCTION_NAME, K, Vs]),
if is_list(Vs) ->
start(make_ref(), Vs ++ apps(K));
true ->
Expand All @@ -293,18 +369,26 @@ start(capabilities = K, [Vs]) ->

start(Key, Vs)
when is_atom(Key) ->
?CL("~w -> entry with"
"~n Key: ~p"
"~n Vs: ~p", [?FUNCTION_NAME, Key, Vs]),
start(make_ref(), [list_to_tuple([Key | Vs]) | apps(Key)]);

start(SvcName, Opts) ->
try
?CL("~w -> [try] - start service: "
"~n SvcName: ~p"
"~n Opts: ~p", [?FUNCTION_NAME, SvcName, Opts]),
Res1 = diameter:start_service(SvcName, Opts),
%% io:format("[started] Is service ~p: ~p~n",
%% [SvcName, diameter:is_service(SvcName)]),
?CL("~w -> [try] - start service result: "
"~n Res: ~p", [?FUNCTION_NAME, Res1]),
Res1
after
?CL("~w -> [after] - try stop service: "
"~n SvcName: ~p", [?FUNCTION_NAME, SvcName]),
Res2 = diameter:stop_service(SvcName),
%% io:format("[stopped] Is service ~p: ~p~n",
%% [SvcName, diameter:is_service(SvcName)]),
?CL("~w -> [after] - stop service result: "
"~n Res: ~p", [?FUNCTION_NAME, Res2]),
Res2
end.

Expand Down
49 changes: 39 additions & 10 deletions lib/diameter/test/diameter_dpr_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -220,38 +220,67 @@ send_dpr(Config) ->
"~n Config: ~p"
"~n => try listen", [?FUNCTION_NAME, Config]),
LRef = ?LISTEN(?SERVER, tcp),
?DL("~w -> try listen", [?FUNCTION_NAME]),
?DL("~w -> try connect", [?FUNCTION_NAME]),
Ref = ?CONNECT(?CLIENT, tcp, LRef, [{dpa_timeout, 10000}]),
?DL("~w -> get sender", [?FUNCTION_NAME]),
Svc = sender(group(Config)),
?DL("~w -> get connections for ~p", [?FUNCTION_NAME, Svc]),
Info = case diameter:service_info(Svc, connections) of
[I] ->
I;
[] ->
?DL("send_dpr -> no connections found: "
Info = case sdpr_await_connections(Svc) of
no_connections ->
?DL("~w -> no connections found: "
"~n Svc: ~p"
"~n Svc info: ~p"
"~n Services: ~p",
[Svc,
[?FUNCTION_NAME,
Svc,
diameter:service_info(Svc, all),
diameter:services()]),
ct:fail({no_connections, Svc})
ct:fail({no_connections, Svc});
I ->
I
end,
{_, {TPid, _}} = lists:keyfind(peer, 1, Info),
?DL("~w -> make a call (expect result 2001)", [?FUNCTION_NAME]),
#diameter_base_DPA{'Result-Code' = 2001}
= diameter:call(Svc,
common,
['DPR', {'Origin-Host', Svc ++ ".erlang.org"},
{'Origin-Realm', "erlang.org"},
{'Disconnect-Cause', 0}],
[{peer, TPid}]),
?DL("~w -> await down event", [?FUNCTION_NAME]),
ok = receive %% ensure the transport dies on DPA
#diameter_event{service = ?CLIENT, info = {down, Ref, _, _}} ->
?DL("~w -> received down event", [?FUNCTION_NAME]),
ok
after 5000 ->
erlang:process_info(self(), messages)
end.
MSGs = erlang:process_info(self(), messages),
?DL("~w -> (down) event timeout: "
"~n ~p", [?FUNCTION_NAME, MSGs]),
MSGs
end,
?DL("~w -> done", [?FUNCTION_NAME]),
ok.


-define(SDPR_AWAIT_CONN_N, 10).

sdpr_await_connections(Svc) ->
sdpr_await_connections(Svc, ?SDPR_AWAIT_CONN_N).

sdpr_await_connections(_Svc, 0) ->
no_connections;
sdpr_await_connections(Svc, N) ->
case diameter:service_info(Svc, connections) of
[I] when (N =:= ?SDPR_AWAIT_CONN_N) ->
I;
[I] when (N =/= ?SDPR_AWAIT_CONN_N) ->
?DL("sdpr_await_connections -> connections found at ~w", [N]),
I;
[] ->
timer:sleep(500),
sdpr_await_connections(Svc, N-1)
end.

%% sender/1

Expand Down
Loading

0 comments on commit a89db25

Please sign in to comment.