Skip to content

Commit

Permalink
Merge branch 'bmk/diameter/20241215/test_tweaking' into maint
Browse files Browse the repository at this point in the history
  • Loading branch information
bmk committed Jan 17, 2025
2 parents 8fd8649 + 153882f commit 95c94e0
Show file tree
Hide file tree
Showing 2 changed files with 84 additions and 21 deletions.
103 changes: 82 additions & 21 deletions lib/diameter/test/diameter_traffic_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -30,9 +30,18 @@
run/1]).

%% common_test wrapping
-export([suite/0,
-export([
%% Framework functions
suite/0,
all/0,
parallel/1]).
init_per_suite/1,
end_per_suite/1,
init_per_testcase/2,
end_per_testcase/2,

%% The test cases
parallel/1
]).

%% testcases
-export([send_ok/1,
Expand Down Expand Up @@ -110,18 +119,24 @@
-include("diameter.hrl").
-include("diameter_gen_base_rfc3588.hrl").
-include("diameter_gen_base_accounting.hrl").
-include("diameter_util.hrl").


%% The listening transports use RFC 3588 dictionaries, the client
%% transports use either 3588 or 6733. (So can't use the record
%% definitions in the latter case.)

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

-define(util, diameter_util).

-define(A, list_to_atom).
-define(L, atom_to_list).
-define(B, iolist_to_binary).

-define(TRL(F), ?TRL(F, [])).
-define(TRL(F, A), ?LOG("DTR", F, A)).

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

%% Don't use is_record/2 since dictionary hrl's aren't included.
%% (Since they define conflicting records with the same names.)
-define(is_record(Rec, Name), (Name == element(1, Rec))).
Expand All @@ -146,7 +161,7 @@
-define(RFCS, [rfc3588, rfc6733, rfc4005]).

%% Which transport protocol to use.
-define(TRANSPORTS, [sctp || ?util:have_sctp()] ++ [tcp]).
-define(TRANSPORTS, [sctp || ?HAVE_SCTP()] ++ [tcp]).

-record(group, {transport,
strings,
Expand Down Expand Up @@ -248,9 +263,44 @@ suite() ->
all() ->
[parallel].

init_per_suite(Config) ->
?TRL("init_per_suite -> entry with"
"~n Config: ~p", [Config]),
?DUTIL:init_per_suite(Config).

end_per_suite(Config) ->
?TRL("end_per_suite -> entry with"
"~n Config: ~p", [Config]),
?DUTIL:end_per_suite(Config).


%% This test case can take a *long* time, so if the machine is too slow, skip
init_per_testcase(parallel = Case, Config) when is_list(Config) ->
?TRL("init_per_testcase(~w) -> check factor", [Case]),
Key = dia_factor,
case lists:keysearch(Key, 1, Config) of
{value, {Key, Factor}} when (Factor > 10) ->
?TRL("init_per_testcase(~w) -> Too slow (~w) => SKIP",
[Case, Factor]),
{skip, {machine_too_slow, Factor}};
_ ->
?TRL("init_per_testcase(~w) -> run test", [Case]),
Config
end;
init_per_testcase(Case, Config) ->
?TRL("init_per_testcase(~w) -> entry", [Case]),
Config.


end_per_testcase(Case, Config) when is_list(Config) ->
?TRL("end_per_testcase(~w) -> entry", [Case]),
Config.


parallel(_Config) ->
run().


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

%% run/0
Expand All @@ -265,25 +315,26 @@ parallel(_Config) ->

run() ->
%% ok = logger:set_primary_config(level, debug),
Svc = ?util:unique_string(),
run(#group{transport = ?util:choose(?TRANSPORTS),
Svc = ?UNIQUE_STRING(),
run(#group{transport = ?CHOOSE(?TRANSPORTS),
strings = bool(),
encoding = ?util:choose(?ENCODINGS),
encoding = ?CHOOSE(?ENCODINGS),
client_service = [$C | Svc],
client_dict = appdict(?util:choose(?RFCS)),
client_dict = appdict(?CHOOSE(?RFCS)),
client_sender = bool(),
server_service = [$S | Svc],
server_decoding = ?util:choose(?DECODINGS),
server_decoding = ?CHOOSE(?DECODINGS),
server_sender = true, %% avoid deadlock
server_throttle = bool()}).

%% run/1

run(#group{} = Cfg) ->
_ = result_codes(Cfg),
io:format("config: ~p~n", [Cfg]),
?TRL("config:"
"~n ~p", [Cfg]),
try
?util:run([{[fun traffic/1, Cfg], 60000}])
?RUN([{[fun traffic/1, Cfg], 60000}])
after
code:delete(nas4005),
code:purge(nas4005),
Expand All @@ -293,14 +344,24 @@ run(#group{} = Cfg) ->
%% traffic/1

traffic(#group{} = Cfg) ->
?TRL("~w -> compile and load", [?FUNCTION_NAME]),
_ = compile_and_load(),
?TRL("~w -> start diameter", [?FUNCTION_NAME]),
ok = diameter:start(),
?TRL("~w -> start server", [?FUNCTION_NAME]),
LRef = server(Cfg),
?TRL("~w -> start client", [?FUNCTION_NAME]),
ok = client(Cfg, LRef),
?TRL("~w -> send", [?FUNCTION_NAME]),
[] = send(Cfg),
?TRL("~w -> print service(s) info", [?FUNCTION_NAME]),
print_services_info(),
?TRL("~w -> stop service(s)", [?FUNCTION_NAME]),
ok = stop_services(Cfg),
[] = ets:tab2list(diameter_request).
?TRL("~w -> verify (no remaining) requests", [?FUNCTION_NAME]),
[] = ets:tab2list(diameter_request),
?TRL("~w -> done", [?FUNCTION_NAME]),
ok.


print_services_info() ->
Expand Down Expand Up @@ -403,12 +464,12 @@ server(Config) ->
| ?SERVICE(SN, Grp)]),
Cfg = [{sender, SS},
{message_cb, ST andalso {?MODULE, message, [0]}}]
++ [{packet, ?util:choose([false, raw])} || T == sctp andalso CS]
++ [{packet, ?CHOOSE([false, raw])} || T == sctp andalso CS]
++ [{unordered, unordered()} || T == sctp],
Opts = [{capabilities_cb, fun capx/2},
{pool_size, 8}
| server_apps()],
_LRef = ?util:listen(SN, [T | Cfg], Opts).
_LRef = ?LISTEN(SN, [T | Cfg], Opts).

%% client/1

Expand All @@ -429,7 +490,7 @@ client(Config, LRef) ->
{strict_arities, decode},
{bins_info, bins_info()}
| ?SERVICE(CN, Grp)]),
_ = [?util:connect(CN, [T | C], LRef, O)
_ = [?CONNECT(CN, [T | C], LRef, O)
|| C <- [[{sender, CS} | client_opts(T)]],
D <- ?DECODINGS, %% for multiple candidate peers
R <- ?RFCS,
Expand All @@ -447,10 +508,10 @@ bins_info() ->
%% 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)]).
?CHOOSE([true, false, rand:uniform(42)]).

unordered() ->
?util:choose([true, false, 1, 2]).
?CHOOSE([true, false, 1, 2]).

client_opts(tcp) ->
[];
Expand Down Expand Up @@ -646,8 +707,8 @@ send_arbitrary(Config) ->
%% Send Proxy-Info in an ASR that the peer answers with 3xxx, and
%% ensure that the AVP is returned.
send_proxy_info(Config) ->
H0 = ?B(?util:unique_string()),
S0 = ?B(?util:unique_string()),
H0 = ?B(?UNIQUE_STRING()),
S0 = ?B(?UNIQUE_STRING()),
Req = ['ASR', {'Proxy-Info', #{'Proxy-Host' => H0,
'Proxy-State' => S0}}],
['answer-message' | #{'Result-Code' := 3999,
Expand Down Expand Up @@ -957,7 +1018,7 @@ send_destination_7(Config) ->
client_dict = Dict0}
= group(Config),
Name = proplists:get_value(testcase, Config),
Svc = ?util:unique_string(),
Svc = ?UNIQUE_STRING(),
SN = [$S | Svc],
Req =
#diameter_packet{msg = ['STR' |
Expand Down
2 changes: 2 additions & 0 deletions lib/diameter/test/diameter_util.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,8 @@
-define(INFO(), ?DUTIL:info()).
-define(SCRAMBLE(SS), ?DUTIL:scramble(SS)).

-define(CHOOSE(L), ?DUTIL:choose(L)).

-define(UNIQUE_STRING(), ?DUTIL:unique_string()).

-define(PCALL(F),
Expand Down

0 comments on commit 95c94e0

Please sign in to comment.