Skip to content

Commit fcf7c06

Browse files
committed
Merge branch 'maint'
2 parents e83bb78 + a89db25 commit fcf7c06

File tree

5 files changed

+416
-47
lines changed

5 files changed

+416
-47
lines changed

lib/diameter/test/diameter_config_SUITE.erl

Lines changed: 102 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -30,12 +30,18 @@
3030
run/1]).
3131

3232
%% common_test wrapping
33-
-export([suite/0,
33+
-export([
34+
%% Framework functions
35+
suite/0,
3436
all/0,
37+
init_per_suite/1,
38+
end_per_suite/1,
39+
40+
%% The test cases
3541
start_service/1,
3642
add_transport/1]).
3743

38-
-define(util, diameter_util).
44+
-include("diameter_util.hrl").
3945

4046
%% Lists of {Key, GoodConfigList, BadConfigList} with which to
4147
%% configure.
@@ -202,67 +208,127 @@
202208
[x,x]],
203209
[]}]).
204210

211+
212+
-define(CL(F), ?CL(F, [])).
213+
-define(CL(F, A), ?LOG("DCONF", F, A)).
214+
215+
205216
%% ===========================================================================
206217

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

210221
all() ->
211-
[start_service,
212-
add_transport].
222+
[
223+
start_service,
224+
add_transport
225+
].
226+
227+
228+
init_per_suite(Config) ->
229+
?DUTIL:init_per_suite(Config).
213230

214-
start_service(_Config) ->
215-
run([start_service]).
231+
end_per_suite(Config) ->
232+
?DUTIL:end_per_suite(Config).
216233

217-
add_transport(_Config) ->
218-
run([add_transport]).
234+
235+
start_service(Config) ->
236+
?CL("~w -> entry", [?FUNCTION_NAME]),
237+
put(dia_factor, dia_factor(Config)),
238+
Res = run([?FUNCTION_NAME]),
239+
?CL("~w -> done when"
240+
"~n Res: ~p", [?FUNCTION_NAME, Res]),
241+
Res.
242+
243+
add_transport(Config) ->
244+
?CL("~w -> entry", [?FUNCTION_NAME]),
245+
put(dia_factor, dia_factor(Config)),
246+
Res = run([?FUNCTION_NAME]),
247+
?CL("~w -> done when"
248+
"~n Res: ~p", [?FUNCTION_NAME, Res]),
249+
Res.
250+
251+
dia_factor(Config) ->
252+
{value, {?FUNCTION_NAME, DiaFactor}} =
253+
lists:keysearch(?FUNCTION_NAME, 1, Config),
254+
DiaFactor.
219255

220256
%% ===========================================================================
221257

258+
%% Factor: >= 1
259+
to(Base, Factor) when (Factor >= 0) ->
260+
round(Base * (((Factor-1) + 10) / 10)).
261+
222262
run() ->
223263
run(all()).
224264

225265
run(List)
226266
when is_list(List) ->
267+
BaseTo = 5000,
268+
To = case get(dia_factor) of
269+
undefined ->
270+
BaseTo;
271+
DF when is_integer(DF) ->
272+
to(BaseTo, DF)
273+
end,
274+
?CL("~w -> timeout calculated to ~w", [?FUNCTION_NAME, To]),
227275
try
228-
?util:run([[[fun run/1, {F, 5000}] || F <- List]])
276+
?RUN([[[fun run/1, {F, To}] || F <- List]])
229277
after
230278
dbg:stop(),
231279
diameter:stop()
232280
end;
233281

234282
run({F, Tmo}) ->
283+
?CL("~w -> entry - try start diameter", [?FUNCTION_NAME]),
235284
ok = diameter:start(),
236285
try
237-
?util:run([{[fun run/1, F], Tmo}])
286+
?CL("~w -> try - run ~p", [?FUNCTION_NAME, F]),
287+
?RUN([{[fun run/1, F], Tmo}])
238288
after
289+
?CL("~w -> after - try stop diameter", [?FUNCTION_NAME]),
239290
ok = diameter:stop()
240291
end;
241292

242-
run(start_service) ->
243-
?util:run([[fun start/1, T]
293+
run(start_service = Case) ->
294+
?CL("~w(~w) -> entry", [?FUNCTION_NAME, Case]),
295+
?RUN([[fun start/1, T]
244296
|| T <- [lists:keyfind(capabilities, 1, ?TRANSPORT_CONFIG)
245297
| ?SERVICE_CONFIG]]);
246298

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

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

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

313+
256314
%% ===========================================================================
257315

258316
%% do/2
259317

260318
do(F, {Key, Good, Bad}) ->
319+
?CL("~w -> entry with"
320+
"~n Key: ~p"
321+
"~n Good: ~p"
322+
"~n Bad: ~p", [?FUNCTION_NAME, Key, Good, Bad]),
261323
F(Key, Good, Bad).
262324

263325
%% add/3
264326

265327
add(Key, Good, Bad) ->
328+
?CL("~w -> entry with"
329+
"~n Key: ~p"
330+
"~n Good: ~p"
331+
"~n Bad: ~p", [?FUNCTION_NAME, Key, Good, Bad]),
266332
{[],[]} = {[{Vs,T} || Vs <- Good,
267333
T <- [add(Key, Vs)],
268334
[T] /= [T || {ok,_} <- [T]]],
@@ -271,12 +337,19 @@ add(Key, Good, Bad) ->
271337
[T] /= [T || {error,_} <- [T]]]}.
272338

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

277346
%% start/3
278347

279348
start(Key, Good, Bad) ->
349+
?CL("~w -> entry with"
350+
"~n Key: ~p"
351+
"~n Good: ~p"
352+
"~n Bad: ~p", [?FUNCTION_NAME, Key, Good, Bad]),
280353
{[],[]} = {[{Vs,T} || Vs <- Good,
281354
T <- [start(Key, Vs)],
282355
T /= ok],
@@ -285,6 +358,9 @@ start(Key, Good, Bad) ->
285358
[T] /= [T || {error,_} <- [T]]]}.
286359

287360
start(capabilities = K, [Vs]) ->
361+
?CL("~w -> entry with"
362+
"~n K: ~p"
363+
"~n Vs: ~p", [?FUNCTION_NAME, K, Vs]),
288364
if is_list(Vs) ->
289365
start(make_ref(), Vs ++ apps(K));
290366
true ->
@@ -293,18 +369,26 @@ start(capabilities = K, [Vs]) ->
293369

294370
start(Key, Vs)
295371
when is_atom(Key) ->
372+
?CL("~w -> entry with"
373+
"~n Key: ~p"
374+
"~n Vs: ~p", [?FUNCTION_NAME, Key, Vs]),
296375
start(make_ref(), [list_to_tuple([Key | Vs]) | apps(Key)]);
297376

298377
start(SvcName, Opts) ->
299378
try
379+
?CL("~w -> [try] - start service: "
380+
"~n SvcName: ~p"
381+
"~n Opts: ~p", [?FUNCTION_NAME, SvcName, Opts]),
300382
Res1 = diameter:start_service(SvcName, Opts),
301-
%% io:format("[started] Is service ~p: ~p~n",
302-
%% [SvcName, diameter:is_service(SvcName)]),
383+
?CL("~w -> [try] - start service result: "
384+
"~n Res: ~p", [?FUNCTION_NAME, Res1]),
303385
Res1
304386
after
387+
?CL("~w -> [after] - try stop service: "
388+
"~n SvcName: ~p", [?FUNCTION_NAME, SvcName]),
305389
Res2 = diameter:stop_service(SvcName),
306-
%% io:format("[stopped] Is service ~p: ~p~n",
307-
%% [SvcName, diameter:is_service(SvcName)]),
390+
?CL("~w -> [after] - stop service result: "
391+
"~n Res: ~p", [?FUNCTION_NAME, Res2]),
308392
Res2
309393
end.
310394

lib/diameter/test/diameter_dpr_SUITE.erl

Lines changed: 39 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -220,38 +220,67 @@ send_dpr(Config) ->
220220
"~n Config: ~p"
221221
"~n => try listen", [?FUNCTION_NAME, Config]),
222222
LRef = ?LISTEN(?SERVER, tcp),
223-
?DL("~w -> try listen", [?FUNCTION_NAME]),
223+
?DL("~w -> try connect", [?FUNCTION_NAME]),
224224
Ref = ?CONNECT(?CLIENT, tcp, LRef, [{dpa_timeout, 10000}]),
225225
?DL("~w -> get sender", [?FUNCTION_NAME]),
226226
Svc = sender(group(Config)),
227227
?DL("~w -> get connections for ~p", [?FUNCTION_NAME, Svc]),
228-
Info = case diameter:service_info(Svc, connections) of
229-
[I] ->
230-
I;
231-
[] ->
232-
?DL("send_dpr -> no connections found: "
228+
Info = case sdpr_await_connections(Svc) of
229+
no_connections ->
230+
?DL("~w -> no connections found: "
233231
"~n Svc: ~p"
234232
"~n Svc info: ~p"
235233
"~n Services: ~p",
236-
[Svc,
234+
[?FUNCTION_NAME,
235+
Svc,
237236
diameter:service_info(Svc, all),
238237
diameter:services()]),
239-
ct:fail({no_connections, Svc})
238+
ct:fail({no_connections, Svc});
239+
I ->
240+
I
240241
end,
241242
{_, {TPid, _}} = lists:keyfind(peer, 1, Info),
243+
?DL("~w -> make a call (expect result 2001)", [?FUNCTION_NAME]),
242244
#diameter_base_DPA{'Result-Code' = 2001}
243245
= diameter:call(Svc,
244246
common,
245247
['DPR', {'Origin-Host', Svc ++ ".erlang.org"},
246248
{'Origin-Realm', "erlang.org"},
247249
{'Disconnect-Cause', 0}],
248250
[{peer, TPid}]),
251+
?DL("~w -> await down event", [?FUNCTION_NAME]),
249252
ok = receive %% ensure the transport dies on DPA
250253
#diameter_event{service = ?CLIENT, info = {down, Ref, _, _}} ->
254+
?DL("~w -> received down event", [?FUNCTION_NAME]),
251255
ok
252256
after 5000 ->
253-
erlang:process_info(self(), messages)
254-
end.
257+
MSGs = erlang:process_info(self(), messages),
258+
?DL("~w -> (down) event timeout: "
259+
"~n ~p", [?FUNCTION_NAME, MSGs]),
260+
MSGs
261+
end,
262+
?DL("~w -> done", [?FUNCTION_NAME]),
263+
ok.
264+
265+
266+
-define(SDPR_AWAIT_CONN_N, 10).
267+
268+
sdpr_await_connections(Svc) ->
269+
sdpr_await_connections(Svc, ?SDPR_AWAIT_CONN_N).
270+
271+
sdpr_await_connections(_Svc, 0) ->
272+
no_connections;
273+
sdpr_await_connections(Svc, N) ->
274+
case diameter:service_info(Svc, connections) of
275+
[I] when (N =:= ?SDPR_AWAIT_CONN_N) ->
276+
I;
277+
[I] when (N =/= ?SDPR_AWAIT_CONN_N) ->
278+
?DL("sdpr_await_connections -> connections found at ~w", [N]),
279+
I;
280+
[] ->
281+
timer:sleep(500),
282+
sdpr_await_connections(Svc, N-1)
283+
end.
255284

256285
%% sender/1
257286

0 commit comments

Comments
 (0)