From 633640c0dcc275a00bb3669a03e8a887f0751dcd Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Thu, 2 May 2024 13:27:28 +0200 Subject: [PATCH 01/38] [diameter|test] Improve debugging Improve test case analuyzis by adding various printouts... --- lib/diameter/test/Makefile | 4 +- .../test/diameter_distribution_SUITE.erl | 90 +++++++--- lib/diameter/test/diameter_examples_SUITE.erl | 65 +++++-- .../test/diameter_transport_SUITE.erl | 160 ++++++++++++++---- lib/diameter/test/diameter_util.erl | 35 ++-- lib/diameter/test/diameter_util.hrl | 38 +++++ 6 files changed, 312 insertions(+), 80 deletions(-) create mode 100644 lib/diameter/test/diameter_util.hrl diff --git a/lib/diameter/test/Makefile b/lib/diameter/test/Makefile index 36cc2ec17e85..8a0d1c9e53fa 100644 --- a/lib/diameter/test/Makefile +++ b/lib/diameter/test/Makefile @@ -40,6 +40,7 @@ RELSYSDIR = $(RELEASE_PATH)/diameter_test include modules.mk +HRL_FILES = diameter_util.hrl ERL_FILES = $(MODULES:%=%.erl) TARGET_FILES = $(MODULES:%=%.$(EMULATOR)) @@ -183,7 +184,8 @@ release_spec release_docs_spec: release_tests_spec: $(INSTALL_DIR) "$(RELSYSDIR)" - $(INSTALL_DATA) $(TEST_SPEC_FILE) \ + $(INSTALL_DATA) $(HRL_FILES) \ + $(TEST_SPEC_FILE) \ $(COVER_SPEC_FILE) \ "$(RELSYSDIR)" $(MAKE) $(DATA_DIRS:%/=release_data_%) diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index 013c42496e47..6ffd7031ec1f 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2013-2022. All Rights Reserved. +%% Copyright Ericsson AB 2013-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. @@ -29,13 +29,19 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - traffic/1]). + + %% The test cases + traffic/1 + ]). %% rpc calls -export([ping/1, start/1, + stop/1, connect/1, call/1]). @@ -52,9 +58,13 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc6733.hrl"). +-include("diameter_util.hrl"). + + %% =========================================================================== --define(util, diameter_util). +-define(DL(F), ?DL(F, [])). +-define(DL(F, A), ?LOG("DDISTS", F, A)). -define(CLIENT, 'CLIENT'). -define(SERVER, 'SERVER'). @@ -92,11 +102,12 @@ %% The order here is significant and causes the server to listen %% before the clients connect. --define(NODES, [{server, ?SERVER}, +-define(NODES, [{server, ?SERVER}, {client0, ?CLIENT}, {client1, ?CLIENT}, {client2, ?CLIENT}]). + %% =========================================================================== suite() -> @@ -106,28 +117,43 @@ all() -> [traffic]. traffic(_Config) -> - traffic(). + ?DL("traffic -> entry"), + Res = traffic(), + ?DL("traffic -> done when" + "~n Res: ~p", [Res]), + Res. %% =========================================================================== run() -> - [] = ?util:run([{fun traffic/0, 60000}]). + [] = ?DUTIL:run([{fun traffic/0, 60000}]). %% process for linked peers to die with %% traffic/0 traffic() -> + ?DL("traffic -> make sure we have distro"), true = is_alive(), %% need distribution for peer nodes + ?DL("traffic -> get nodes"), Nodes = enslave(), + ?DL("traffic -> ping nodes"), [] = ping(Nodes), %% drop client node + ?DL("traffic -> start nodes"), [] = start(Nodes), + ?DL("traffic -> connect nodes"), [_] = connect(Nodes), - [] = send(Nodes). + ?DL("traffic -> send (to) nodes"), + [] = send(Nodes), + ?DL("traffic -> stop nodes"), + [] = stop(Nodes), + ?DL("traffic -> done"), + ok. %% enslave/0 %% -%% Start four slave nodes, one to implement a Diameter server, -%% three to implement a client. +%% Start four nodes; +%% - one to implement a Diameter server, +%% - three to implement a client. enslave() -> Here = filename:dirname(code:which(?MODULE)), @@ -136,7 +162,7 @@ enslave() -> [{N,S} || {M,S} <- ?NODES, N <- [start(M, Args)]]. start(Name, Args) -> - {ok, _, Node} = ?util:peer(#{name => Name, args => Args}), + {ok, _, Node} = ?DUTIL:peer(#{name => Name, args => Args}), Node. %% ping/1 @@ -171,6 +197,20 @@ start(Nodes) -> RC <- [rpc:call(N, ?MODULE, start, [S])], RC /= ok]. +%% stop/1 +%% +%% Stop diameter services. + +stop(SvcName) + when is_atom(SvcName) -> + ok = diameter:stop_service(SvcName), + ok = diameter:stop(); + +stop(Nodes) -> + [{N,RC} || {N,S} <- Nodes, + RC <- [rpc:call(N, ?MODULE, stop, [S])], + RC /= ok]. + sequence() -> sequence(sname()). @@ -203,10 +243,10 @@ peers(client2) -> nodes(). %% nodes. connect({?SERVER, _, []}) -> - [_LRef = ?util:listen(?SERVER, tcp)]; + [_LRef = ?DUTIL:listen(?SERVER, tcp)]; connect({?CLIENT, [{Node, _} | _], [LRef] = Acc}) -> - ?util:connect(?CLIENT, tcp, {Node, LRef}), + ?DUTIL:connect(?CLIENT, tcp, {Node, LRef}), Acc; connect(Nodes) -> @@ -221,31 +261,43 @@ connect(Nodes) -> %% send/1 send(Nodes) -> - ?util:run([[fun send/2, Nodes, T] - || T <- [local, remote, timeout, failover]]). + ?RUN([[fun send/2, Nodes, T] + || T <- [local, remote, timeout, failover]]). %% send/2 %% Send a request from the first client node, using a the local %% transport. send(Nodes, local) -> + ?DL("send(local) -> entry - expect success (~p)", [?SUCCESS]), #diameter_base_STA{'Result-Code' = ?SUCCESS} - = send(Nodes, 0, str(?LOGOUT)); + = send(Nodes, 0, str(?LOGOUT)), + ?DL("send(local) -> success (=success)"), + ok; %% Send a request from the first client node, using a transport on the %% another node. send(Nodes, remote) -> + ?DL("send(remote) -> entry - expect success (~p)", [?SUCCESS]), #diameter_base_STA{'Result-Code' = ?SUCCESS} - = send(Nodes, 1, str(?LOGOUT)); + = send(Nodes, 1, str(?LOGOUT)), + ?DL("send(remote) -> success (=success)"), + ok; %% Send a request that the server discards. send(Nodes, timeout) -> - {error, timeout} = send(Nodes, 1, str(?TIMEOUT)); + ?DL("send(timeout) -> entry - expect timeout"), + {error, timeout} = send(Nodes, 1, str(?TIMEOUT)), + ?DL("send(timeout) -> success (=timeout)"), + ok; %% Send a request that causes the server to take the transport down. send(Nodes, failover) -> + ?DL("send(failover) -> entry - expect busy (~p)", [?BUSY]), #'diameter_base_answer-message'{'Result-Code' = ?BUSY} - = send(Nodes, 2, str(?MOVED)). + = send(Nodes, 2, str(?MOVED)), + ?DL("send(failover) -> success (=busy)"), + ok. %% =========================================================================== diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl index 7bb39cace31b..0429a473cd04 100644 --- a/lib/diameter/test/diameter_examples_SUITE.erl +++ b/lib/diameter/test/diameter_examples_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2013-2022. All Rights Reserved. +%% Copyright Ericsson AB 2013-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. @@ -29,10 +29,15 @@ run/1]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, + + %% The test cases dict/1, - code/1]). + code/1 + ]). %% rpc calls -export([install/1, @@ -41,9 +46,13 @@ -include("diameter.hrl"). -%% =========================================================================== +-include("diameter_util.hrl"). + + +-define(EL(F, A), ?LOG("DEXS", F, A)). --define(util, diameter_util). + +%% =========================================================================== %% The order here is significant and causes the server to listen %% before the clients connect. @@ -60,11 +69,12 @@ -define(DICT0, [rfc3588_base, rfc6733_base]). %% Transport protocols over which the example Diameter nodes are run. --define(PROTS, [sctp || ?util:have_sctp()] ++ [tcp]). +-define(PROTS, [sctp || ?HAVE_SCTP()] ++ [tcp]). -define(L, atom_to_list). -define(A, list_to_atom). + %% =========================================================================== %% common_test wrapping @@ -74,11 +84,24 @@ suite() -> all() -> [dict, code]. + dict(Config) -> - run(dict, Config). + ?EL("dict -> entry with" + "~n Config: ~p", [Config]), + Res = run(dict, Config), + ?EL("dict -> done when" + "~n Res: ~p", [Res]), + Res. + code(Config) -> - run(code, Config). + ?EL("code -> entry with" + "~n Config: ~p", [Config]), + Res = run(code, Config), + ?EL("code -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== @@ -90,16 +113,27 @@ run() -> %% run/1 run({dict, Dir}) -> - compile_dicts(Dir); + ?EL("run(dict) -> entry with" + "~n Dir: ~p", [Dir]), + Res = compile_dicts(Dir), + ?EL("run(dict) -> done when" + "~n Res: ~p", [Res]), + Res; + %% The example code doesn't use the example dictionaries, so a %% separate testcase. run({code, Dir}) -> - run_code(Dir); + ?EL("run(code) -> entry with" + "~n Dir: ~p", [Dir]), + Res = run_code(Dir), + ?EL("run(code) -> done when" + "~n Res: ~p", [Res]), + Res; run(List) when is_list(List) -> - Tmp = ?util:mktemp("diameter_examples"), + Tmp = ?MKTEMP("diameter_examples"), try run(List, Tmp) after @@ -111,11 +145,12 @@ run(List) %% Eg. erl -noinput -s diameter_examples_SUITE run code -s init stop ... run(List, Dir) when is_list(List) -> - ?util:run([{[fun run/1, {F, Dir}], 60000} || F <- List]); + ?RUN([{[fun run/1, {F, Dir}], 60000} || F <- List]); run(F, Config) -> run([F], proplists:get_value(priv_dir, Config)). + %% =========================================================================== %% compile_dicts/1 %% @@ -301,7 +336,7 @@ enslave(Prefix) -> slave(Name, Dir) -> Args = ["-pa", Dir, filename:join([Dir, "..", "ebin"])], - {ok, _Pid, _Node} = ?util:peer(#{name => Name, args => Args}). + {ok, _Pid, _Node} = ?PEER(#{name => Name, args => Args}). here() -> filename:dirname(code:which(?MODULE)). @@ -320,7 +355,7 @@ start({server, Prot, Ebin}) -> ok = diameter:start(), ok = server:start(), {ok, Ref} = server:listen({Prot, any, 3868}), - [_] = ?util:lport(Prot, Ref), + [_] = ?LPORT(Prot, Ref), ok; start({client = Svc, Prot, Ebin}) -> @@ -365,7 +400,7 @@ traffic({Prot, Ebin}) -> run_code(Dir) -> true = is_alive(), %% need distribution for peer nodes {ok, Ebin} = compile_code(mkdir(Dir, "code")), - ?util:run([[fun traffic/1, {T, Ebin}] || T <- ?PROTS]). + ?RUN([[fun traffic/1, {T, Ebin}] || T <- ?PROTS]). %% call/1 diff --git a/lib/diameter/test/diameter_transport_SUITE.erl b/lib/diameter/test/diameter_transport_SUITE.erl index 9b763141ffe2..6b0f538ba357 100644 --- a/lib/diameter/test/diameter_transport_SUITE.erl +++ b/lib/diameter/test/diameter_transport_SUITE.erl @@ -29,9 +29,14 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - parallel/1]). + + %% The test cases + parallel/1 + ]). -export([accept/1, connect/1, @@ -41,7 +46,7 @@ -include_lib("kernel/include/inet_sctp.hrl"). -include("diameter.hrl"). --define(util, diameter_util). +-include("diameter_util.hrl"). %% Corresponding to diameter_* transport modules. -define(TRANSPORTS, [tcp, sctp]). @@ -77,6 +82,11 @@ %% Messages from gen_sctp. -define(SCTP(Sock, Data), {sctp, Sock, _, _, Data}). + +-define(TL(F), ?TL(F, [])). +-define(TL(F, A), ?LOG("DTRANSPS", F, A)). + + %% =========================================================================== %% common_test wrapping @@ -87,7 +97,12 @@ all() -> [parallel]. parallel(_) -> - run(). + ?TL("parallel -> entry"), + Res = run(), + ?TL("parallel -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== @@ -96,9 +111,9 @@ parallel(_) -> run() -> ok = diameter:start(), try - ?util:run([[fun run/1, {P,F}] - || P <- [sctp || ?util:have_sctp()] ++ [tcp], - F <- [connect, accept, reconnect]]) + ?RUN([[fun run/1, {P,F}] + || P <- [sctp || ?HAVE_SCTP()] ++ [tcp], + F <- [connect, accept, reconnect]]) after diameter:stop() end. @@ -106,13 +121,29 @@ run() -> %% run/1 run({Prot, reconnect}) -> - reconnect(Prot); + ?TL("run(reconnect) -> entry with" + "~n Prot: ~p", [Prot]), + Res = reconnect(Prot), + ?TL("run(reconnect) -> done when" + "~n Res: ~p", [Res]), + Res; run({Prot, accept}) -> - accept(Prot); + ?TL("run(accept) -> entry with" + "~n Prot: ~p", [Prot]), + Res = accept(Prot), + ?TL("run(accept) -> done when" + "~n Res: ~p", [Res]), + Res; run({Prot, connect}) -> - connect(Prot). + ?TL("run(connect) -> entry with" + "~n Prot: ~p", [Prot]), + Res = connect(Prot), + ?TL("run(connect) -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== %% accept/1 @@ -120,11 +151,19 @@ run({Prot, connect}) -> %% diameter transport accepting, test code connecting. accept(Prot) -> + ?TL("accept -> entry with" + "~n Prot: ~p", [Prot]), + Ref = make_ref(), true = diameter_reg:add_new({diameter_config, transport, Ref}), %% fake it T = {Prot, Ref}, - ?util:run([{{?MODULE, [init, X, T]}, 15000} - || X <- [accept, gen_connect]]). + Res = ?RUN([{{?MODULE, [init, X, T]}, 15000} + || X <- [accept, gen_connect]]), + + ?TL("accept -> done when" + "~n Res: ~p", [Res]), + ok. + %% =========================================================================== %% connect/1 @@ -132,9 +171,17 @@ accept(Prot) -> %% Test code accepting, diameter transport connecting. connect(Prot) -> + ?TL("connect -> entry with" + "~n Prot: ~p", [Prot]), + T = {Prot, make_ref()}, - ?util:run([{{?MODULE, [init, X, T]}, 15000} - || X <- [gen_accept, connect]]). + Res = ?RUN([{{?MODULE, [init, X, T]}, 15000} + || X <- [gen_accept, connect]]), + + ?TL("connect -> done when" + "~n Res: ~p", [Res]), + ok. + %% =========================================================================== %% reconnect/1 @@ -144,9 +191,11 @@ connect(Prot) -> %% broken. reconnect({listen, Ref}) -> + ?TL("reconnect(listen) -> entry with" + "~n Ref: ~p", [Ref]), SvcName = make_ref(), ok = start_service(SvcName), - LRef = ?util:listen(SvcName, tcp, [{watchdog_timer, 6000}]), + LRef = ?LISTEN(SvcName, tcp, [{watchdog_timer, 6000}]), [_] = diameter_reg:wait({diameter_tcp, listener, {LRef, '_'}}), true = diameter_reg:add_new({?MODULE, Ref, LRef}), @@ -157,15 +206,22 @@ reconnect({listen, Ref}) -> exit(TPid, kill), %% Wait for the partner again. - abort(SvcName, LRef, Ref); + Res = abort(SvcName, LRef, Ref), + + ?TL("reconnect(listen) -> done when" + "~n Res: ~p", [Res]), + ok; reconnect({connect, Ref}) -> + ?TL("reconnect(connect) -> entry with" + "~n Ref: ~p", [Ref]), + SvcName = make_ref(), true = diameter:subscribe(SvcName), ok = start_service(SvcName), [{{_, _, LRef}, Pid}] = diameter_reg:wait({?MODULE, Ref, '_'}), - CRef = ?util:connect(SvcName, tcp, LRef, [{connect_timer, 2000}, - {watchdog_timer, 6000}]), + CRef = ?CONNECT(SvcName, tcp, LRef, [{connect_timer, 2000}, + {watchdog_timer, 6000}]), %% Tell partner to kill transport after seeing that there are no %% reconnection attempts. @@ -181,13 +237,23 @@ reconnect({connect, Ref}) -> %% Wait for partner to die. MRef = erlang:monitor(process, Pid), - ?RECV({'DOWN', MRef, process, _, _}); + Res = ?RECV({'DOWN', MRef, process, _, _}), + + ?TL("reconnect(connect) -> done when" + "~n Res: ~p", [Res]), + ok; reconnect(Prot) -> + ?TL("reconnect -> entry with" + "~n Prot: ~p", [Prot]), Ref = make_ref(), - ?util:run([{{?MODULE, [reconnect, {T, Ref}]}, 240000} - || Prot == tcp, %% ignore sctp - T <- [listen, connect]]). + Res = ?RUN([{{?MODULE, [reconnect, {T, Ref}]}, 240000} + || Prot == tcp, %% ignore sctp + T <- [listen, connect]]), + + ?TL("reconnect -> done when" + "~n Res: ~p", [Res]), + ok. start_service(SvcName) -> OH = diameter_util:unique_string(), @@ -225,6 +291,10 @@ abort(SvcName, LRef, Ref) %% init/2 init(accept, {Prot, Ref}) -> + ?TL("init(accept) -> entry with" + "~n Prot: ~p" + "~n Ref: ~p", [Prot, Ref]), + %% Start an accepting transport and receive notification of a %% connection. TPid = start_accept(Prot, Ref), @@ -238,19 +308,34 @@ init(accept, {Prot, Ref}) -> %% Expect the transport process to die as a result of the peer %% closing the connection. MRef = erlang:monitor(process, TPid), - ?RECV({'DOWN', MRef, process, _, _}); + Res = ?RECV({'DOWN', MRef, process, _, _}), + + ?TL("init(accept) -> done when" + "~n Res: ~p", [Res]), + ok; init(gen_connect, {Prot, Ref}) -> + ?TL("init(gen_connect) -> entry with" + "~n Prot: ~p" + "~n Ref: ~p", [Prot, Ref]), + %% Lookup the peer's listening socket. - [PortNr] = ?util:lport(Prot, Ref), + [PortNr] = ?LPORT(Prot, Ref), %% Connect, send a message and receive it back. {ok, Sock} = gen_connect(Prot, PortNr), Bin = make_msg(), ok = gen_send(Prot, Sock, Bin), - Bin = gen_recv(Prot, Sock); + Bin = gen_recv(Prot, Sock), + + ?TL("init(gen_connect) -> done"), + ok; init(gen_accept, {Prot, Ref}) -> + ?TL("init(gen_accept) -> entry with" + "~n Prot: ~p" + "~n Ref: ~p", [Prot, Ref]), + %% Open a listening socket and publish the port number. {ok, LSock} = gen_listen(Prot), {ok, PortNr} = inet:port(LSock), @@ -261,14 +346,22 @@ init(gen_accept, {Prot, Ref}) -> {ok, Sock} = gen_accept(Prot, LSock), Bin = gen_recv(Prot, Sock), ok = gen_send(Prot, Sock, Bin), - receive - {tcp_closed, Sock} = T -> - T; - ?SCTP(Sock, {_, #sctp_assoc_change{}}) = T -> - T - end; + Res = receive + {tcp_closed, Sock} = T -> + T; + ?SCTP(Sock, {_, #sctp_assoc_change{}}) = T -> + T + end, + + ?TL("init(gen_accept) -> done when" + "~n T: ~p", [T]), + ok; init(connect, {Prot, Ref}) -> + ?TL("init(connect) -> entry with" + "~n Prot: ~p" + "~n Ref: ~p", [Prot, Ref]), + %% Lookup the peer's listening socket. [{?TEST_LISTENER(_, PortNr), _}] = diameter_reg:wait(?TEST_LISTENER(Ref, '_')), @@ -280,7 +373,10 @@ init(connect, {Prot, Ref}) -> %% Send a message and receive it back. Bin = make_msg(), TPid ! ?TMSG({send, Bin}), - Bin = bin(Prot, ?RECV(?TMSG({recv, P}), P)). + Bin = bin(Prot, ?RECV(?TMSG({recv, P}), P)), + + ?TL("init(connect) -> done"), + ok. bin(sctp, #diameter_packet{bin = Bin}) -> Bin; diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index a8c2555e08a6..075fc59c6001 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -37,7 +37,8 @@ peer/1, unique_string/0, have_sctp/0, - eprof/1]). + eprof/1, + log/4]). %% diameter-specific -export([lport/2, @@ -46,9 +47,12 @@ disconnect/4, info/0]). +-include("diameter_util.hrl"). + + -define(L, atom_to_list). --define(LOG(F, A), log(?LINE, F, A)). +-define(DL(F, A), ?LOG("DUTIL", F, A)). %% --------------------------------------------------------------------------- @@ -129,23 +133,23 @@ down(Parent, Worker) %% Die with the worker, kill the worker if the parent dies. down(ParentMRef, WorkerPid) -> - ?LOG("down -> await worker (~p) termination", [WorkerPid]), + ?DL("down -> await worker (~p) termination", [WorkerPid]), receive {'EXIT', TCPid, {timetrap_timeout = R, TCTimeout, TCStack}} -> - ?LOG("down -> test case timetrap timeout when" - "~n (test case) Pid: ~p" - "~n (test case) Timeout: ~p" - "~n (test case) Stack: ~p", [TCPid, TCTimeout, TCStack]), + ?DL("down -> test case timetrap timeout when" + "~n (test case) Pid: ~p" + "~n (test case) Timeout: ~p" + "~n (test case) Stack: ~p", [TCPid, TCTimeout, TCStack]), exit(WorkerPid, kill), %% So many wrapper levels, make sure we go with a bang exit({TCPid, R, TCStack}); {'DOWN', ParentMRef, process, PPid, PReason} -> - ?LOG("down -> parent process (~p) died: " - "~n Reason: ~p", [PPid, PReason]), + ?DL("down -> parent process (~p) died: " + "~n Reason: ~p", [PPid, PReason]), exit(WorkerPid, kill); {'DOWN', _, process, WorkerPid, WReason} -> - ?LOG("down -> worker process (~p) died: " - "~n Reason: ~p", [WorkerPid, WReason]), + ?DL("down -> worker process (~p) died: " + "~n Reason: ~p", [WorkerPid, WReason]), ok end. @@ -470,5 +474,10 @@ info(S) -> info(Key, SvcName) -> [{Key, _}] = diameter:service_info(SvcName, [Key]). -log(LINE, F, A) -> - ct:log("[DUTIL:~w,~p] " ++ F ++ "~n", [LINE,self()|A]). + +log(ModStr, LINE, F, A) + when is_list(ModStr) andalso + is_integer(LINE) andalso + is_list(F) andalso + is_list(A) -> + ct:log("[~s:~w,~p] " ++ F ++ "~n", [ModStr, LINE, self()|A]). diff --git a/lib/diameter/test/diameter_util.hrl b/lib/diameter/test/diameter_util.hrl new file mode 100644 index 000000000000..2bb67802cb1c --- /dev/null +++ b/lib/diameter/test/diameter_util.hrl @@ -0,0 +1,38 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2024-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. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% + +-ifndef(diameter_util__). +-define(diameter_util__, true). + +-define(DUTIL, diameter_util). + +-define(LOG(F, A), ?LOG(atom_to_list(?MODULE), F, A)). +-define(LOG(MS, F, A), ?DUTIL:log(MS, ?LINE, F, A)). + +-define(HAVE_SCTP(), ?DUTIL:have_sctp()). +-define(MKTEMP(S), ?DUTIL:mktemp(S)). +-define(RUN(A), ?DUTIL:run(A)). +-define(PEER(P), ?DUTIL:peer(P)). +-define(LPORT(P, R), ?DUTIL:lport(P, R)). + +-define(LISTEN(SN, Proto, Opts), ?DUTIL:listen(SN, Proto, Opts)). +-define(CONNECT(SN, Proto, LR, Opts), ?DUTIL:connect(SN, Proto, LR, Opts)). + +-endif. From b0549b8cc7f89ed6615691830dd68649b0dd90ef Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 3 May 2024 10:32:01 +0200 Subject: [PATCH 02/38] [diameter|test] More test tweaking --- .../test/diameter_transport_SUITE.erl | 32 ++++++++++++------- 1 file changed, 21 insertions(+), 11 deletions(-) diff --git a/lib/diameter/test/diameter_transport_SUITE.erl b/lib/diameter/test/diameter_transport_SUITE.erl index 6b0f538ba357..e86270d7fbbd 100644 --- a/lib/diameter/test/diameter_transport_SUITE.erl +++ b/lib/diameter/test/diameter_transport_SUITE.erl @@ -346,15 +346,15 @@ init(gen_accept, {Prot, Ref}) -> {ok, Sock} = gen_accept(Prot, LSock), Bin = gen_recv(Prot, Sock), ok = gen_send(Prot, Sock, Bin), - Res = receive - {tcp_closed, Sock} = T -> - T; - ?SCTP(Sock, {_, #sctp_assoc_change{}}) = T -> - T - end, + _Res = receive + {tcp_closed, Sock} = T -> + T; + ?SCTP(Sock, {_, #sctp_assoc_change{}}) = T -> + T + end, ?TL("init(gen_accept) -> done when" - "~n T: ~p", [T]), + "~n Res: ~p", [_Res]), ok; init(connect, {Prot, Ref}) -> @@ -486,12 +486,22 @@ gen_send(tcp, Sock, Bin) -> %% gen_recv/2 gen_recv(sctp, Sock) -> - {_OS, _IS, Id} = getr(assoc), + {OS, IS, Id} = getr(assoc), receive - ?SCTP(Sock, {[#sctp_sndrcvinfo{assoc_id = I}], Bin}) + ?SCTP(Sock, {[#sctp_sndrcvinfo{assoc_id = I} = INFO], Bin}) when is_binary(Bin) -> - {Id, _} = {I, Id}, %% assert - Bin + case {I, Id} of + {Id, _} -> % assert + Bin; + _ -> + ?TL("unexpected assoc id in received info msg:" + "~n Expected Assoc ID: ~p" + "~n OS: ~p" + "~n IS: ~p" + "~n Received Assoc ID: ~p" + "~n Info: ~p", [Id, OS, IS, I, INFO]), + ct:fail({unexpected_assoc_id, I, Id}) + end end; gen_recv(tcp, Sock) -> tcp_recv(Sock, <<>>). From 6fd4015ff74bc31521de8db0783d244b45b5aa96 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 3 May 2024 12:40:08 +0200 Subject: [PATCH 03/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_relay_SUITE.erl | 67 +++++++++++++++------- lib/diameter/test/diameter_util.hrl | 5 ++ 2 files changed, 50 insertions(+), 22 deletions(-) diff --git a/lib/diameter/test/diameter_relay_SUITE.erl b/lib/diameter/test/diameter_relay_SUITE.erl index 2502820e0f0e..c641d29b4fe9 100644 --- a/lib/diameter/test/diameter_relay_SUITE.erl +++ b/lib/diameter/test/diameter_relay_SUITE.erl @@ -38,9 +38,14 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - parallel/1]). + + %% The test cases + parallel/1 + ]). %% diameter callbacks -export([pick_peer/4, @@ -52,9 +57,10 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc3588.hrl"). -%% =========================================================================== +-include("diameter_util.hrl"). + --define(util, diameter_util). +%% =========================================================================== -define(ADDR, {127,0,0,1}). @@ -99,6 +105,10 @@ -define(LOGOUT, ?'DIAMETER_BASE_TERMINATION-CAUSE_LOGOUT'). -define(AUTHORIZE_ONLY, ?'DIAMETER_BASE_RE-AUTH-REQUEST-TYPE_AUTHORIZE_ONLY'). +-define(RL(F), ?RL(F, [])). +-define(RL(F, A), ?LOG("DRELAYS", F, A)). + + %% =========================================================================== suite() -> @@ -108,7 +118,12 @@ all() -> [parallel]. parallel(_Config) -> - run(). + ?RL("parallel -> entry"), + Res = run(), + ?RL("parallel -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== @@ -117,7 +132,7 @@ parallel(_Config) -> run() -> ok = diameter:start(), try - ?util:run([{fun traffic/0, 20000}]) + ?RUN([{fun traffic/0, 20000}]) after ok = diameter:stop() end. @@ -125,12 +140,20 @@ run() -> %% traffic/0 traffic() -> + ?RL("traffic -> start services"), Servers = start_services(), + ?RL("traffic -> connect"), Conns = connect(Servers), + ?RL("traffic -> send"), [] = send(), + ?RL("traffic -> check counters"), [] = counters(), + ?RL("traffic -> disconnect"), [] = disconnect(Conns), - [] = stop_services(). + ?RL("traffic -> stop services"), + [] = stop_services(), + ?RL("traffic -> done"), + ok. start_services() -> [S1,S2,S3,S4] = [server(N, ?DICT_COMMON) || N <- [?SERVER1, @@ -159,30 +182,30 @@ stop_services() -> %% Traffic cases run when services are started and connections %% established. send() -> - ?util:run([[fun traffic/1, T] || T <- [send1, - send2, - send3, - send4, - send_loop, - send_timeout_1, - send_timeout_2, - info]]). + ?RUN([[fun traffic/1, T] || T <- [send1, + send2, + send3, + send4, + send_loop, + send_timeout_1, + send_timeout_2, + info]]). %% ---------------------------------------- break({{CN,CR},{SN,SR}}) -> try - ?util:disconnect(CN,CR,SN,SR) + ?DISCONNECT(CN,CR,SN,SR) after diameter:remove_transport(SN, SR) end. server(Name, Dict) -> ok = diameter:start_service(Name, ?SERVICE(Name, Dict)), - {Name, ?util:listen(Name, tcp)}. + {Name, ?LISTEN(Name, tcp)}. connect(Name, Refs) -> - [{{Name, ?util:connect(Name, tcp, LRef)}, T} || {_, LRef} = T <- Refs]. + [{{Name, ?CONNECT(Name, tcp, LRef)}, T} || {_, LRef} = T <- Refs]. %% =========================================================================== %% traffic testcases @@ -226,12 +249,12 @@ traffic(info) -> %% Wait for RELAY1 to have answered all requests, so that the %% suite doesn't end before all answers are sent and counted. receive after 6000 -> ok end, - [] = ?util:info(). + [] = ?INFO(). counters() -> - ?util:run([[fun counters/2, K, S] - || K <- [statistics, transport, connections], - S <- ?SERVICES]). + ?RUN([[fun counters/2, K, S] + || K <- [statistics, transport, connections], + S <- ?SERVICES]). counters(Key, Svc) -> counters(Key, Svc, [_|_] = diameter:service_info(Svc, Key)). diff --git a/lib/diameter/test/diameter_util.hrl b/lib/diameter/test/diameter_util.hrl index 2bb67802cb1c..d8680a3b69dc 100644 --- a/lib/diameter/test/diameter_util.hrl +++ b/lib/diameter/test/diameter_util.hrl @@ -32,7 +32,12 @@ -define(PEER(P), ?DUTIL:peer(P)). -define(LPORT(P, R), ?DUTIL:lport(P, R)). +-define(LISTEN(SN, Proto), ?DUTIL:listen(SN, Proto)). -define(LISTEN(SN, Proto, Opts), ?DUTIL:listen(SN, Proto, Opts)). +-define(CONNECT(SN, Proto, LR), ?DUTIL:connect(SN, Proto, LR)). -define(CONNECT(SN, Proto, LR, Opts), ?DUTIL:connect(SN, Proto, LR, Opts)). +-define(DISCONNECT(CN, CR, SN, SR), ?DUTIL:disconnect(CN, CR, SN, SR)). + +-define(INFO(), ?DUTIL:info()). -endif. From 06ada887041853ed4ebadbc0c7d43d3b00fae5f9 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 3 May 2024 13:02:49 +0200 Subject: [PATCH 04/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_tls_SUITE.erl | 73 +++++++++++++++++------- lib/diameter/test/diameter_util.hrl | 1 + 2 files changed, 53 insertions(+), 21 deletions(-) diff --git a/lib/diameter/test/diameter_tls_SUITE.erl b/lib/diameter/test/diameter_tls_SUITE.erl index 2033b60355c5..efdf282da685 100644 --- a/lib/diameter/test/diameter_tls_SUITE.erl +++ b/lib/diameter/test/diameter_tls_SUITE.erl @@ -38,11 +38,16 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, init_per_suite/1, end_per_suite/1, - parallel/1]). + + %% The test cases + parallel/1 + ]). %% diameter callbacks -export([prepare_request/3, @@ -53,9 +58,10 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc3588.hrl"). -%% =========================================================================== +-include("diameter_util.hrl"). + --define(util, diameter_util). +%% =========================================================================== -define(ADDR, {127,0,0,1}). @@ -97,7 +103,7 @@ %% Config for diameter:add_transport/2. In the listening case, listen %% on a free port that we then lookup using the implementation detail %% that diameter_tcp registers the port with diameter_reg. --define(CONNECT(PortNr, Caps, Opts), +-define(TCONNECT(PortNr, Caps, Opts), {connect, [{transport_module, diameter_tcp}, {transport_config, [{raddr, ?ADDR}, {rport, PortNr}, @@ -105,7 +111,7 @@ {port, 0} | Opts]}, {capabilities, Caps}]}). --define(LISTEN(Caps, Opts), +-define(TLISTEN(Caps, Opts), {listen, [{transport_module, diameter_tcp}, {transport_config, [{ip, ?ADDR}, {port, 0} | Opts]}, {capabilities, Caps}]}). @@ -113,6 +119,10 @@ -define(SUCCESS, 2001). -define(LOGOUT, ?'DIAMETER_BASE_TERMINATION-CAUSE_LOGOUT'). +-define(TL(F), ?TL(F, [])). +-define(TL(F, A), ?LOG("DTLSS", F, A)). + + %% =========================================================================== %% common_test wrapping @@ -141,7 +151,11 @@ end_per_suite(_Config) -> crypto:stop(). parallel(Config) -> - run(dir(Config), false). + ?TL("parallel -> entry"), + Res = run(dir(Config), false), + ?TL("parallel -> done when" + "~n Res: ~p", [Res]), + Res. dir(Config) -> proplists:get_value(priv_dir, Config). @@ -149,7 +163,7 @@ dir(Config) -> %% =========================================================================== run() -> - Tmp = ?util:mktemp("diameter_tls"), + Tmp = ?MKTEMP("diameter_tls"), try run(Tmp, true) after @@ -157,34 +171,51 @@ run() -> end. run(Dir, B) -> + ?TL("run -> start crypto"), crypto:start(), + ?TL("run -> start ssl"), ssl:start(), try - ?util:run([{[fun traffic/2, Dir, B], 60000}]) + ?TL("run -> try run traffic"), + ?RUN([{[fun traffic/2, Dir, B], 60000}]) after + ?TL("run(after) -> stop diameter"), diameter:stop(), + ?TL("run(after) -> stop ssl"), ssl:stop(), - crypto:stop() + ?TL("run(after) -> stop crypto"), + crypto:stop(), + ?TL("run(after) -> done"), + ok end. traffic(Dir, true) -> + ?TL("traffic(true) -> make certs"), [] = make_certs(Dir), traffic(Dir, false); traffic(Dir, false) -> + ?TL("traffic(false) -> start diameter"), ok = diameter:start(), + ?TL("traffic(false) -> start (diameter) services"), Servers = start_services(Dir), + ?TL("traffic(false) -> add transports"), Connections = add_transports(Dir, Servers), - [] = ?util:run([[fun call/1, S] || S <- ?util:scramble(?SERVERS)]), + ?TL("traffic(false) -> calls"), + [] = ?RUN([[fun call/1, S] || S <- ?SCRAMBLE(?SERVERS)]), + ?TL("traffic(false) -> remove transports"), [] = remove_transports(Connections), - [] = stop_services(). + ?TL("traffic(false) -> stop (diameter) services"), + [] = stop_services(), + ?TL("traffic(false) -> done"), + ok. make_certs(Dir) -> - ?util:run([[fun make_cert/2, Dir, B] || B <- ["server1", - "server2", - "server4", - "server5", - "client"]]). + ?RUN([[fun make_cert/2, Dir, B] || B <- ["server1", + "server2", + "server4", + "server5", + "client"]]). start_services(Dir) -> Servers = [{S, {_,_} = server(S, sopts(S, Dir))} || S <- ?SERVERS], @@ -200,7 +231,7 @@ add_transports(Dir, Servers) -> %% transport to go down. remove_transports(Connections) -> [] = [T || S <- ?SERVERS, T <- [diameter:subscribe(S)], T /= true], - [] = ?util:run([[fun disconnect/1, T] || T <- Connections]), + [] = ?RUN([[fun disconnect/1, T] || T <- Connections]), [S || S <- ?SERVERS, I <- [receive #diameter_event{service = S, info = I} -> I end], down /= catch element(1, I)]. @@ -308,8 +339,8 @@ join(Strs) -> server(Host, {Caps, Opts}) -> ok = diameter:start_service(Host, ?SERVICE(Host, ?DICT_COMMON)), - {ok, LRef} = diameter:add_transport(Host, ?LISTEN(Caps, Opts)), - {LRef, hd([_] = ?util:lport(tcp, LRef))}. + {ok, LRef} = diameter:add_transport(Host, ?TLISTEN(Caps, Opts)), + {LRef, hd([_] = ?LPORT(tcp, LRef))}. sopts(?SERVER1, Dir) -> {inband_security([?TLS]), @@ -330,7 +361,7 @@ ssl([{ssl_options = T, Opts}]) -> %% connect/3 connect(Host, {_LRef, PortNr}, {Caps, Opts}) -> - {ok, Ref} = diameter:add_transport(Host, ?CONNECT(PortNr, Caps, Opts)), + {ok, Ref} = diameter:add_transport(Host, ?TCONNECT(PortNr, Caps, Opts)), {up, Ref, _, _, #diameter_packet{}} = receive #diameter_event{service = Host, info = Info} diff --git a/lib/diameter/test/diameter_util.hrl b/lib/diameter/test/diameter_util.hrl index d8680a3b69dc..859a5b8c299c 100644 --- a/lib/diameter/test/diameter_util.hrl +++ b/lib/diameter/test/diameter_util.hrl @@ -39,5 +39,6 @@ -define(DISCONNECT(CN, CR, SN, SR), ?DUTIL:disconnect(CN, CR, SN, SR)). -define(INFO(), ?DUTIL:info()). +-define(SCRAMBLE(SS), ?DUTIL:scramble(SS)). -endif. From e541c753d212c77de107a5471d5d96016d86cba7 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Sat, 4 May 2024 10:24:53 +0200 Subject: [PATCH 05/38] [diameter|test] More test tweaking --- lib/diameter/test/diameter_util.erl | 20 +++++++++++++++++++- 1 file changed, 19 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index 075fc59c6001..0bb49be33412 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -364,9 +364,27 @@ connect(Client, Prot, LRef) -> connect(Client, Prot, LRef, []). connect(Client, ProtOpts, LRef, Opts) -> + ?DL("connect -> entry with" + "~n Client: ~p" + "~n ProtOpts: ~p" + "~n LRef: ~p" + "~n Opts: ~p", [Client, ProtOpts, LRef, Opts]), Prot = head(ProtOpts), [PortNr] = lport(Prot, LRef), - Client = diameter:service_info(Client, name), %% assert + case diameter:service_info(Client, name) of + Client -> % assert + ok; + undefined -> + ?DL("no name: " + "~n Service Info: ~p", [diameter:service_info(Client)]), + ct:fail({undefined_name, Client}); + WrongName -> % This should not be possible but... + ?DL("Wrong Name: " + "~n ~p" + "~n Service Info: ~p", + [WrongName, diameter:service_info(Client)]), + ct:fail({undefined_name, Client, WrongName}) + end, true = diameter:subscribe(Client), Ref = add_transport(Client, {connect, opts(ProtOpts, PortNr) ++ Opts}), true = transport(Client, Ref), %% assert From d62f46223e9a834112158e95c7052526e0f9dd35 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Sun, 5 May 2024 10:19:11 +0200 Subject: [PATCH 06/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 21 +++++++++++++++------ 1 file changed, 15 insertions(+), 6 deletions(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index 0bb49be33412..a29450a6dc26 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -376,14 +376,23 @@ connect(Client, ProtOpts, LRef, Opts) -> ok; undefined -> ?DL("no name: " - "~n Service Info: ~p", [diameter:service_info(Client)]), + "~n 'all' Service Info: ~p" + "~n 'info' Service Info: ~p" + "~n 'stats' Service Info: ~p", + [diameter:service_info(Client, all), + diameter:service_info(Client, info), + diameter:service_info(Client, statistics)]), ct:fail({undefined_name, Client}); WrongName -> % This should not be possible but... - ?DL("Wrong Name: " - "~n ~p" - "~n Service Info: ~p", - [WrongName, diameter:service_info(Client)]), - ct:fail({undefined_name, Client, WrongName}) + ?DL("Wrong Name: ~p" + "~n 'all' Service Info: ~p" + "~n 'info' Service Info: ~p" + "~n 'stats' Service Info: ~p", + [WrongName, + diameter:service_info(Client, all), + diameter:service_info(Client, info), + diameter:service_info(Client, statistics)]), + ct:fail({wrong_name, Client, WrongName}) end, true = diameter:subscribe(Client), Ref = add_transport(Client, {connect, opts(ProtOpts, PortNr) ++ Opts}), From e7471e92b38cacf3571988a5a3b02dbb4fc88ff3 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Sun, 5 May 2024 16:44:16 +0200 Subject: [PATCH 07/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index a29450a6dc26..cc2ff3507df7 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -376,19 +376,27 @@ connect(Client, ProtOpts, LRef, Opts) -> ok; undefined -> ?DL("no name: " + "~n Services: ~p" + "~n Service: ~p" "~n 'all' Service Info: ~p" "~n 'info' Service Info: ~p" "~n 'stats' Service Info: ~p", - [diameter:service_info(Client, all), + [diameter:services(), + Client, + diameter:service_info(Client, all), diameter:service_info(Client, info), diameter:service_info(Client, statistics)]), ct:fail({undefined_name, Client}); WrongName -> % This should not be possible but... ?DL("Wrong Name: ~p" + "~n Services: ~p" + "~n Service: ~p" "~n 'all' Service Info: ~p" "~n 'info' Service Info: ~p" "~n 'stats' Service Info: ~p", [WrongName, + diameter:services(), + Client, diameter:service_info(Client, all), diameter:service_info(Client, info), diameter:service_info(Client, statistics)]), From eec76598f73ad3dea442cad6549c10281d6ca29d Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 6 May 2024 09:29:23 +0200 Subject: [PATCH 08/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 34 ++++++++++++++++++++++------- 1 file changed, 26 insertions(+), 8 deletions(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index cc2ff3507df7..86de1be63fe7 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -52,7 +52,8 @@ -define(L, atom_to_list). --define(DL(F, A), ?LOG("DUTIL", F, A)). +-define(UL(F), ?UL(F, [])). +-define(UL(F, A), ?LOG("DUTIL", F, A)). %% --------------------------------------------------------------------------- @@ -133,10 +134,10 @@ down(Parent, Worker) %% Die with the worker, kill the worker if the parent dies. down(ParentMRef, WorkerPid) -> - ?DL("down -> await worker (~p) termination", [WorkerPid]), + ?UL("down -> await worker (~p) termination", [WorkerPid]), receive {'EXIT', TCPid, {timetrap_timeout = R, TCTimeout, TCStack}} -> - ?DL("down -> test case timetrap timeout when" + ?UL("down -> test case timetrap timeout when" "~n (test case) Pid: ~p" "~n (test case) Timeout: ~p" "~n (test case) Stack: ~p", [TCPid, TCTimeout, TCStack]), @@ -144,11 +145,11 @@ down(ParentMRef, WorkerPid) -> %% So many wrapper levels, make sure we go with a bang exit({TCPid, R, TCStack}); {'DOWN', ParentMRef, process, PPid, PReason} -> - ?DL("down -> parent process (~p) died: " + ?UL("down -> parent process (~p) died: " "~n Reason: ~p", [PPid, PReason]), exit(WorkerPid, kill); {'DOWN', _, process, WorkerPid, WReason} -> - ?DL("down -> worker process (~p) died: " + ?UL("down -> worker process (~p) died: " "~n Reason: ~p", [WorkerPid, WReason]), ok end. @@ -303,31 +304,48 @@ have_sctp(_) -> %% Evaluate a function in one of a number of forms. eval({F, infinity}) -> + ?UL("eval(infinity) -> entry"), eval(F); eval({F, Tmo}) when is_integer(Tmo) -> + ?UL("eval(~p) -> entry", [Tmo]), {ok, _} = timer:exit_after(Tmo, timeout), eval(F); eval({M,[F|A]}) when is_atom(F) -> + ?UL("eval -> entry with" + "~n M: ~p" + "~n F: ~p" + "~n A: ~p", [M, F, A]), apply(M,F,A); eval({M,F,A}) -> + ?UL("eval -> entry with" + "~n M: ~p" + "~n F: ~p" + "~n A: ~p", [M, F, A]), apply(M,F,A); eval([F|A]) when is_function(F) -> + ?UL("eval -> entry with" + "~n F: ~p" + "~n A: ~p", [F, A]), apply(F,A); eval(L) when is_list(L) -> + ?UL("eval -> entry with" + "~n length(L): ~p", [length(L)]), [eval(F) || F <- L]; eval(F) when is_function(F,0) -> + ?UL("eval -> entry"), F(). + %% --------------------------------------------------------------------------- %% lport/2 %% @@ -364,7 +382,7 @@ connect(Client, Prot, LRef) -> connect(Client, Prot, LRef, []). connect(Client, ProtOpts, LRef, Opts) -> - ?DL("connect -> entry with" + ?UL("connect -> entry with" "~n Client: ~p" "~n ProtOpts: ~p" "~n LRef: ~p" @@ -375,7 +393,7 @@ connect(Client, ProtOpts, LRef, Opts) -> Client -> % assert ok; undefined -> - ?DL("no name: " + ?UL("no name: " "~n Services: ~p" "~n Service: ~p" "~n 'all' Service Info: ~p" @@ -388,7 +406,7 @@ connect(Client, ProtOpts, LRef, Opts) -> diameter:service_info(Client, statistics)]), ct:fail({undefined_name, Client}); WrongName -> % This should not be possible but... - ?DL("Wrong Name: ~p" + ?UL("Wrong Name: ~p" "~n Services: ~p" "~n Service: ~p" "~n 'all' Service Info: ~p" From 2b1aa8ed0b8e46987c33328a3675d874d648bb4b Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 6 May 2024 09:45:26 +0200 Subject: [PATCH 09/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_examples_SUITE.erl | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl index 0429a473cd04..1e238ab1264b 100644 --- a/lib/diameter/test/diameter_examples_SUITE.erl +++ b/lib/diameter/test/diameter_examples_SUITE.erl @@ -49,6 +49,7 @@ -include("diameter_util.hrl"). +-define(EL(F), ?EL(F, [])). -define(EL(F, A), ?LOG("DEXS", F, A)). @@ -157,7 +158,9 @@ run(F, Config) -> %% Compile example dictionaries in examples/dict. compile_dicts(Dir) -> + ?EL("compile_dicts -> entry"), Out = mkdir(Dir, "dict"), + ?EL("compile_dicts -> create paths"), Dirs = [filename:join(H ++ ["examples", "dict"]) || H <- [[code:lib_dir(diameter)], [here(), ".."]]], [] = [{F,D,RC} || {_,F} <- sort(find_files(Dirs, ".*\\.dia$")), @@ -198,18 +201,26 @@ make(Path, Dict0, Out) make(Path, atom_to_list(Dict0), Out); make(Path, Dict0, Out) -> + ?EL("make -> entry with" + "~n Path: ~p" + "~n Dict0: ~p" + "~n Out: ~p", [Path, Dict0, Out]), Dict = filename:rootname(filename:basename(Path)), {Mod, Pre} = make_name(Dict), {"diameter_gen_base" ++ Suf = Mod0, _} = make_name(Dict0), Name = Mod ++ Suf, try + ?EL("make -> try make codec: to erl"), ok = to_erl(Path, [{name, Name}, {prefix, Pre}, {outdir, Out}, {inherits, "common/" ++ Mod0} | [{inherits, D ++ "/" ++ M ++ Suf} || {D,M} <- dep(Dict)]]), - ok = to_beam(filename:join(Out, Name)) + ?EL("make -> try make codec: to beam"), + ok = to_beam(filename:join(Out, Name)), + ?EL("make -> done"), + ok catch throw: {_,_} = E -> E From ff16a721536844f8122e685eacd5041125f840f9 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 6 May 2024 16:57:27 +0200 Subject: [PATCH 10/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index 86de1be63fe7..dbb7d2d9ef37 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -309,7 +309,9 @@ eval({F, infinity}) -> eval({F, Tmo}) when is_integer(Tmo) -> ?UL("eval(~p) -> entry", [Tmo]), - {ok, _} = timer:exit_after(Tmo, timeout), + %% Since this function is used for all kinds of functions, + %% a timeout is not very informative, so include the "function". + {ok, _} = timer:exit_after(Tmo, {timeout, F}), eval(F); eval({M,[F|A]}) From 55c2a1849a895e9cb5dec8e7dc3a19188a8f0def Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 6 May 2024 17:27:29 +0200 Subject: [PATCH 11/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_app_SUITE.erl | 48 ++++++++++++++---------- lib/diameter/test/diameter_util.hrl | 1 + 2 files changed, 30 insertions(+), 19 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index e96133908f63..488f68ba7ee8 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -43,7 +43,11 @@ -include_lib("kernel/include/file.hrl"). --define(util, diameter_util). +-include("diameter_util.hrl"). + + +%% =========================================================================== + -define(A, list_to_atom). %% Modules not in the app and that should not have dependencies on it @@ -58,6 +62,10 @@ -define(INFO_MODULES, [diameter_dbg, diameter_info]). +-define(AL(F), ?AL(F, [])). +-define(AL(F, A), ?LOG("DAPPS", F, A)). + + %% =========================================================================== suite() -> @@ -78,7 +86,7 @@ run() -> run(all()). run(List) -> - Tmp = ?util:mktemp("diameter_app"), + Tmp = ?MKTEMP("diameter_app"), try run([{priv_dir, Tmp}], List) after @@ -86,8 +94,9 @@ run(List) -> end. run(Config, List) -> - [{application, diameter, App}] = ?util:consult(diameter, app), - ?util:run([{{?MODULE, F, [{App, Config}]}, 10000} || F <- List]). + [{application, diameter, App}] = ?CONSULT(diameter, app), + ?RUN([{{?MODULE, F, [{App, Config}]}, 10000} || F <- List]). + %% =========================================================================== %% # keys/1 @@ -178,7 +187,7 @@ release(Config) -> %% in the case of relup/1. appvsn(Name) -> - [{application, Name, App}] = ?util:consult(Name, app), + [{application, Name, App}] = ?CONSULT(Name, app), fetch(vsn, App). %% =========================================================================== @@ -196,10 +205,10 @@ xref({App, _Config}) -> Mods = fetch(modules, App), %% modules listed in the app file %% List of application names extracted from runtime_dependencies. - i("xref -> get deps"), + ?AL("xref -> get deps"), Deps = lists:map(fun unversion/1, fetch(runtime_dependencies, App)), - i("xref -> start xref"), + ?AL("xref -> start xref"), {ok, XRef} = xref:start(make_name(xref_test_name)), ok = xref:set_default(XRef, [{verbose, false}, {warnings, false}]), @@ -209,30 +218,30 @@ xref({App, _Config}) -> %% was previously in kernel. Erts isn't an application however, in %% the sense that there's no .app file, and isn't listed in %% applications. - i("xref -> add own and dep apps"), + ?AL("xref -> add own and dep apps"), ok = lists:foreach(fun(A) -> add_application(XRef, A) end, [diameter, erts | fetch(applications, App)]), - i("xref -> analyze undefined_function_calls"), + ?AL("xref -> analyze undefined_function_calls"), {ok, Undefs} = xref:analyze(XRef, undefined_function_calls), - i("xref -> analyze module use: " - "~n For mods: ~p", [Mods]), + ?AL("xref -> analyze module use: " + "~n For mods: ~p", [Mods]), {ok, RTmods} = xref:analyze(XRef, {module_use, Mods}), - i("xref -> analyze (compiler) module use: " - "~n For mods: ~p", [?COMPILER_MODULES]), + ?AL("xref -> analyze (compiler) module use: " + "~n For mods: ~p", [?COMPILER_MODULES]), {ok, CTmods} = xref:analyze(XRef, {module_use, ?COMPILER_MODULES}), - i("xref -> analyze module call: " - "~n For mods: ~p", [Mods]), + ?AL("xref -> analyze module call: " + "~n For mods: ~p", [Mods]), {ok, RTdeps} = xref:analyze(XRef, {module_call, Mods}), - i("xref -> stop xref"), + ?AL("xref -> stop xref"), xref:stop(XRef), - i("xref -> get OTP release"), + ?AL("xref -> get OTP release"), Rel = release(), %% otp_release-ish %% Only care about calls from our own application. - i("xref -> Only care about calls from our own application"), + ?AL("xref -> Only care about calls from our own application"), [] = lists:filter(fun({{F,_,_} = From, {_,_,_} = To}) -> lists:member(F, Mods) andalso not ignored(From, To, Rel) @@ -331,6 +340,7 @@ add_application(XRef, App) -> make_name(Suf) -> list_to_atom("diameter_" ++ atom_to_list(Suf)). + %% =========================================================================== %% # relup/1 %% @@ -342,7 +352,7 @@ relup({App, Config}) -> "~n App: ~p" "~n Config: ~p", [App, Config]), - [{Vsn, Up, Down}] = ?util:consult(diameter, appup), + [{Vsn, Up, Down}] = ?CONSULT(diameter, appup), true = is_vsn(Vsn), i("relup -> " diff --git a/lib/diameter/test/diameter_util.hrl b/lib/diameter/test/diameter_util.hrl index 859a5b8c299c..86ab23fccaf9 100644 --- a/lib/diameter/test/diameter_util.hrl +++ b/lib/diameter/test/diameter_util.hrl @@ -31,6 +31,7 @@ -define(RUN(A), ?DUTIL:run(A)). -define(PEER(P), ?DUTIL:peer(P)). -define(LPORT(P, R), ?DUTIL:lport(P, R)). +-define(CONSULT(N, S), ?DUTIL:consult(N, S)). -define(LISTEN(SN, Proto), ?DUTIL:listen(SN, Proto)). -define(LISTEN(SN, Proto, Opts), ?DUTIL:listen(SN, Proto, Opts)). From 83ecd758cc99a96d7e220d3adad4fe052793590d Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 7 May 2024 09:53:53 +0200 Subject: [PATCH 12/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_tls_SUITE.erl | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/lib/diameter/test/diameter_tls_SUITE.erl b/lib/diameter/test/diameter_tls_SUITE.erl index efdf282da685..e0531a276b13 100644 --- a/lib/diameter/test/diameter_tls_SUITE.erl +++ b/lib/diameter/test/diameter_tls_SUITE.erl @@ -288,14 +288,19 @@ handle_request(#diameter_packet{msg = #diameter_base_STR{'Session-Id' = SId}}, %% Send an STR intended for a specific server and expect success. call(Server) -> + ?TL("call -> entry with" + "~n Server: ~p", [Server]), Realm = realm(Server), Req = ['STR', {'Destination-Realm', Realm}, {'Termination-Cause', ?LOGOUT}, {'Auth-Application-Id', ?APP_ID}], - #diameter_base_STA{'Result-Code' = ?SUCCESS, - 'Origin-Host' = Server, + ?TL("call -> make (STR) call (with filter and realm) - expect STA"), + #diameter_base_STA{'Result-Code' = ?SUCCESS, + 'Origin-Host' = Server, 'Origin-Realm' = Realm} - = call(Req, [{filter, realm}]). + = call(Req, [{filter, realm}]), + ?TL("call -> done"), + ok. call(Req, Opts) -> diameter:call(?CLIENT, ?APP_ALIAS, Req, Opts). From 4a09fa89d7d8b9dffe139c0396219daa202219b1 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 7 May 2024 10:11:38 +0200 Subject: [PATCH 13/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_distribution_SUITE.erl | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index 6ffd7031ec1f..d211d4740f86 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -309,11 +309,15 @@ str(Cause) -> %% send/3 send([_, {Node, _} | _], Where, Req) -> + ?DL("send -> make rpc call to node ~p", [Node]), rpc:call(Node, ?MODULE, call, [{Where, Req}]). %% call/1 call({Where, Req}) -> + ?DL("call -> entry with" + "~n Where: ~p" + "~n Req: ~p", [Where, Req]), diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}]). %% sname/0 From 95add66750154fbf043dad818fb00a707ff92352 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 7 May 2024 17:47:41 +0200 Subject: [PATCH 14/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index dbb7d2d9ef37..af2a38d2a942 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -174,7 +174,9 @@ fold(_, Acc, Map) fold(Fun, Acc, #{} = Map) -> receive - {'DOWN', MRef, process, _, Info} when is_map_key(MRef, Map) -> + {'DOWN', MRef, process, Pid, Info} when is_map_key(MRef, Map) -> + ?UL("fold -> process ~p terminated:" + "~n ~p", [Pid, Info]), fold(Fun, Fun(Info, Acc), maps:remove(MRef, Map)) end. From 98e37c2cc1fc37d1f44626efcfd71b00a8d9ceb7 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 7 May 2024 19:03:58 +0200 Subject: [PATCH 15/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_util.erl | 38 ++++++++++++++++++++++++++--- 1 file changed, 35 insertions(+), 3 deletions(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index af2a38d2a942..a55934aa99d1 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -135,25 +135,57 @@ down(Parent, Worker) %% Die with the worker, kill the worker if the parent dies. down(ParentMRef, WorkerPid) -> ?UL("down -> await worker (~p) termination", [WorkerPid]), + timer:send_after(1000, self(), check_worker_status), + await_down(ParentMRef, WorkerPid). + +await_down(ParentMRef, WorkerPid) -> receive + check_worker_status -> + ?UL("await_down -> check worker process (~p) status: " + "~n Current Function: ~p" + "~n Message Queue Length: ~p" + "~n Reductions: ~p" + "~n Status: ~p", + [WorkerPid, + pi(WorkerPid, current_function), + pi(WorkerPid, message_queue_len), + pi(WorkerPid, reductions), + pi(WorkerPid, status)]), + timer:send_after(1000, self(), check_worker_status), + await_down(ParentMRef, WorkerPid); + {'EXIT', TCPid, {timetrap_timeout = R, TCTimeout, TCStack}} -> - ?UL("down -> test case timetrap timeout when" + ?UL("await_down -> test case timetrap timeout when" "~n (test case) Pid: ~p" "~n (test case) Timeout: ~p" "~n (test case) Stack: ~p", [TCPid, TCTimeout, TCStack]), exit(WorkerPid, kill), %% So many wrapper levels, make sure we go with a bang exit({TCPid, R, TCStack}); + {'DOWN', ParentMRef, process, PPid, PReason} -> - ?UL("down -> parent process (~p) died: " + ?UL("await_down -> parent process (~p) died: " "~n Reason: ~p", [PPid, PReason]), exit(WorkerPid, kill); {'DOWN', _, process, WorkerPid, WReason} -> - ?UL("down -> worker process (~p) died: " + ?UL("await_down -> worker process (~p) died: " "~n Reason: ~p", [WorkerPid, WReason]), ok end. + +pi(Pid, Key) -> + try + begin + {Key, Value} = process_info(Pid, Key), + Value + end + catch + _:_:_ -> + undefined + end. + + %% --------------------------------------------------------------------------- %% fold/3 %% From 563d15848076a00a985a9e1c86c59710eea3708b Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 8 May 2024 10:16:26 +0200 Subject: [PATCH 16/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_app_SUITE.erl | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 488f68ba7ee8..6d2a55f32cff 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -218,9 +218,10 @@ xref({App, _Config}) -> %% was previously in kernel. Erts isn't an application however, in %% the sense that there's no .app file, and isn't listed in %% applications. - ?AL("xref -> add own and dep apps"), - ok = lists:foreach(fun(A) -> add_application(XRef, A) end, - [diameter, erts | fetch(applications, App)]), + Apps = [diameter, erts | fetch(applications, App)], + ?AL("xref -> add own and dep apps: " + "~n ~p", [Apps]), + ok = lists:foreach(fun(A) -> add_application(XRef, A) end, Apps), ?AL("xref -> analyze undefined_function_calls"), {ok, Undefs} = xref:analyze(XRef, undefined_function_calls), @@ -335,6 +336,8 @@ app(Mod) -> end. add_application(XRef, App) -> + ?AL("add_application -> entry with" + "~n App: ~p", [App]), {ok, App} = xref:add_application(XRef, code:lib_dir(App), []). make_name(Suf) -> From 1235bfe5ed1f002f3f4ec93ceae96636f343a0e1 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 8 May 2024 10:41:54 +0200 Subject: [PATCH 17/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_app_SUITE.erl | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 6d2a55f32cff..077f509480e6 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -336,9 +336,11 @@ app(Mod) -> end. add_application(XRef, App) -> - ?AL("add_application -> entry with" - "~n App: ~p", [App]), - {ok, App} = xref:add_application(XRef, code:lib_dir(App), []). + ?AL("add_application -> get lib dir for app ~p", [App]), + LibDir = code:lib_dir(App), + ?AL("add_application -> [xref] add lib dir:" + "~n ~p", [LibDir]), + {ok, App} = xref:add_application(XRef, LibDir, []). make_name(Suf) -> list_to_atom("diameter_" ++ atom_to_list(Suf)). From 07c5265ec05b62e3a63b95eb51a1d8436521c59b Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 8 May 2024 10:57:55 +0200 Subject: [PATCH 18/38] [diameter|test] More test case tweaking We should really analyze the host before we set the timeouts, bit will have to do for now. --- lib/diameter/test/diameter_examples_SUITE.erl | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl index 1e238ab1264b..d258207cdb36 100644 --- a/lib/diameter/test/diameter_examples_SUITE.erl +++ b/lib/diameter/test/diameter_examples_SUITE.erl @@ -80,7 +80,7 @@ %% common_test wrapping suite() -> - [{timetrap, {seconds, 75}}]. + [{timetrap, {seconds, 120}}]. all() -> [dict, code]. @@ -146,7 +146,7 @@ run(List) %% Eg. erl -noinput -s diameter_examples_SUITE run code -s init stop ... run(List, Dir) when is_list(List) -> - ?RUN([{[fun run/1, {F, Dir}], 60000} || F <- List]); + ?RUN([{[fun run/1, {F, Dir}], 90000} || F <- List]); run(F, Config) -> run([F], proplists:get_value(priv_dir, Config)). From bed84a9b15488f19972b86cfc9999cee1febddb7 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 13 May 2024 09:56:20 +0200 Subject: [PATCH 19/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_app_SUITE.erl | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 077f509480e6..027b816edc54 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -198,9 +198,9 @@ appvsn(Name) -> %% =========================================================================== xref({App, _Config}) -> - i("xref -> entry with" - "~n App: ~p" - "~n Config: ~p", [App, _Config]), + ?AL("xref -> entry with" + "~n App: ~p" + "~n Config: ~p", [App, _Config]), Mods = fetch(modules, App), %% modules listed in the app file @@ -254,30 +254,30 @@ xref({App, _Config}) -> %% depend on other diameter modules but it's a simple source of %% build errors if not properly encoded in the makefile so guard %% against it. - i("xref -> ensure only runtime and info mod"), + ?AL("xref -> ensure only runtime and info mod"), [] = (RTmods -- Mods) -- ?INFO_MODULES, %% Ensure that runtime modules don't call compiler modules. - i("xref -> ensure runtime mods don't call compiler mods"), + ?AL("xref -> ensure runtime mods don't call compiler mods"), CTmods = CTmods -- Mods, %% Ensure that runtime modules only call other runtime modules, or %% applications declared in runtime_dependencies in the app file. %% The declared application versions are ignored since we only %% know what we see now. - i("xref -> ensure runtime mods only call runtime mods"), + ?AL("xref -> ensure runtime mods only call runtime mods"), [] = lists:filter(fun(M) -> not lists:member(app(M), Deps) end, RTdeps -- Mods), - i("xref -> done"), + ?AL("xref -> done"), ok; xref(Config) -> - i("xref -> entry with" - "~n Config: ~p", [Config]), + ?AL("xref -> entry with" + "~n Config: ~p", [Config]), Res = run(Config, [xref]), - i("xref -> done when" - "~n Res: ~p", [Res]), + ?AL("xref -> done when" + "~n Res: ~p", [Res]), Res. ignored({FromMod,_,_}, {ToMod,_,_} = To, Rel)-> From 586cee87fff7c496fc341a61303281d6ff53c0d4 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 13 May 2024 09:57:47 +0200 Subject: [PATCH 20/38] [diameter|test] More test case tweaking --- lib/diameter/test/diameter_dpr_SUITE.erl | 51 ++++++++++++++++++++---- 1 file changed, 43 insertions(+), 8 deletions(-) diff --git a/lib/diameter/test/diameter_dpr_SUITE.erl b/lib/diameter/test/diameter_dpr_SUITE.erl index 45f4ec9b5a3f..e4b8788ed64e 100644 --- a/lib/diameter/test/diameter_dpr_SUITE.erl +++ b/lib/diameter/test/diameter_dpr_SUITE.erl @@ -51,6 +51,9 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc6733.hrl"). +-include("diameter_util.hrl"). + + %% =========================================================================== -define(util, diameter_util). @@ -85,6 +88,11 @@ []] ++ [[{dpr, [{timeout, 5000}, {cause, T}]}] || T <- ?CAUSES]). + +-define(DL(F), ?DL(F, [])). +-define(DL(F, A), ?LOG("DDPRS", F, A)). + + %% =========================================================================== suite() -> @@ -93,7 +101,7 @@ suite() -> all() -> [client, server, uncommon, transport, service, application]. --define(tc(Name), Name(_) -> run([Name])). +-define(tc(Name), Name(_) -> ?DL("~w -> entry", [Name]), run([Name])). ?tc(client). ?tc(server). @@ -102,6 +110,7 @@ all() -> ?tc(service). ?tc(application). + %% =========================================================================== %% run/0 @@ -113,20 +122,34 @@ run() -> run(List) when is_list(List) -> + ?DL("run -> entry with" + "~n List: ~p", [List]), try - ?util:run([[{[fun run/1, T], 15000} || T <- List]]) + ?RUN([[{[fun run/1, T], 15000} || T <- List]]) after + ?DL("run(after) -> stop diameter"), diameter:stop() end; run(Grp) -> + ?DL("run(~w) -> start (diameter) app", [Grp]), ok = diameter:start(), + ?DL("run(~w) -> start (diameter) service 'server'", [Grp]), ok = diameter:start_service(?SERVER, service(?SERVER, Grp)), + ?DL("run(~w) -> start (diameter) service 'client'", [Grp]), ok = diameter:start_service(?CLIENT, service(?CLIENT, Grp)), - _ = lists:foldl(fun(F,A) -> apply(?MODULE, F, [A]) end, + _ = lists:foldl(fun(F,A) -> + ?DL("run(~w) -> apply" + "~n F: ~p" + "~n A: ~p", [F, A]), + apply(?MODULE, F, [A]) + end, [{group, Grp}], tc(Grp)), - ok = diameter:stop(). + ?DL("run(~w) -> stop (diameter) app", [Grp]), + ok = diameter:stop(), + ?DL("run(~w) -> done", [Grp]), + ok. tc(T) when T == client; @@ -178,10 +201,22 @@ service(?CLIENT = Svc, _) -> %% send_dpr/1 send_dpr(Config) -> - LRef = ?util:listen(?SERVER, tcp), - Ref = ?util:connect(?CLIENT, tcp, LRef, [{dpa_timeout, 10000}]), - Svc = sender(group(Config)), - [Info] = diameter:service_info(Svc, connections), + LRef = ?LISTEN(?SERVER, tcp), + Ref = ?CONNECT(?CLIENT, tcp, LRef, [{dpa_timeout, 10000}]), + Svc = sender(group(Config)), + Info = case diameter:service_info(Svc, connections) of + [I] -> + I; + [] -> + ?DL("send_dpr -> no connections: " + "~n Svc: ~p" + "~n Svc info: ~p" + "~n Services: ~p", + [Svc, + diameter:service_info(Svc, all), + diameter:services()]), + ct:fail({no_connections, Svc}) + end, {_, {TPid, _}} = lists:keyfind(peer, 1, Info), #diameter_base_DPA{'Result-Code' = 2001} = diameter:call(Svc, From 4c2941079b223ec36279984e1acc12e50bc67a85 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 14 May 2024 12:21:47 +0200 Subject: [PATCH 21/38] [diameter|test|3xxx] More tweaking --- lib/diameter/test/diameter_3xxx_SUITE.erl | 67 ++++++++++++++++++++--- 1 file changed, 59 insertions(+), 8 deletions(-) diff --git a/lib/diameter/test/diameter_3xxx_SUITE.erl b/lib/diameter/test/diameter_3xxx_SUITE.erl index 63de2467a32c..2af853ea2723 100644 --- a/lib/diameter/test/diameter_3xxx_SUITE.erl +++ b/lib/diameter/test/diameter_3xxx_SUITE.erl @@ -60,9 +60,11 @@ -include("diameter_gen_base_rfc6733.hrl"). %% Use the fact that STR/STA is identical in RFC's 3588 and 6733. +-include("diameter_util.hrl"). + + %% =========================================================================== --define(util, diameter_util). -define(testcase(), get(?MODULE)). -define(L, atom_to_list). @@ -95,6 +97,10 @@ -define(LOGOUT, ?'DIAMETER_BASE_TERMINATION-CAUSE_LOGOUT'). +-define(XL(F), ?XL(F, [])). +-define(XL(F, A), ?LOG("D3XS", F, A)). + + %% =========================================================================== suite() -> @@ -104,6 +110,7 @@ all() -> [traffic]. traffic(_Config) -> + ?XL("traffic -> entry"), run(). %% =========================================================================== @@ -123,44 +130,68 @@ tc() -> %% run/0 run() -> - ?util:run([[{{?MODULE, run, [{E,D}]}, 60000} || E <- ?ERRORS, - D <- ?RFCS]]). + ?XL("run -> entry"), + ?RUN([[{{?MODULE, run, [{E,D}]}, 60000} || E <- ?ERRORS, + D <- ?RFCS]]). %% run/1 run({F, [_,_] = G}) -> + ?XL("run -> entry with" + "~n F: ~p" + "~n G: ~p", [F, G]), put(?MODULE, F), apply(?MODULE, F, [G]); run({E,D}) -> + ?XL("run -> entry with" + "~n E: ~p" + "~n D: ~p", [E, D]), try run([E,D]) after + ?XL("run(after) -> stop diameter app"), ok = diameter:stop() end; run([Errors, RFC] = G) -> + ?XL("run -> entry with" + "~n Errors: ~p" + "~n RFC: ~p", [Errors, RFC]), Name = ?L(Errors) ++ "," ++ ?L(RFC), + ?XL("run -> start diameter app"), ok = diameter:start(), + ?XL("run -> start service 'server' (~p)", [Name]), ok = diameter:start_service(?SERVER, ?SERVICE(Name, Errors, RFC)), + ?XL("run -> start service 'client'"), ok = diameter:start_service(?CLIENT, ?SERVICE(?CLIENT, callback, rfc6733)), - LRef = ?util:listen(?SERVER, tcp), - ?util:connect(?CLIENT, tcp, LRef), - ?util:run([{?MODULE, run, [{F,G}]} || F <- tc()]), + ?XL("run -> (server) listen"), + LRef = ?LISTEN(?SERVER, tcp), + ?XL("run -> (client) connect"), + ?CONNECT(?CLIENT, tcp, LRef), + ?XL("run -> run"), + ?RUN([{?MODULE, run, [{F,G}]} || F <- tc()]), + ?XL("run -> \"check\" counters"), _ = counters(G), + ?XL("run -> remove 'client' transport"), ok = diameter:remove_transport(?CLIENT, true), + ?XL("run -> remove 'server' transport"), ok = diameter:remove_transport(?SERVER, true), + ?XL("run -> stop service 'server'"), ok = diameter:stop_service(?SERVER), - ok = diameter:stop_service(?CLIENT). + ?XL("run -> stop service 'client'"), + ok = diameter:stop_service(?CLIENT), + ?XL("run -> done"), + ok. %% counters/1 %% %% Check that counters are as expected. counters([_Errors, _RFC] = G) -> - [] = ?util:run([[fun counters/3, K, S, G] + [] = ?RUN([[fun counters/3, K, S, G] || K <- [statistics, transport, connections], S <- [?CLIENT, ?SERVER]]). @@ -357,6 +388,7 @@ stats(?SERVER, callback, rfc6733, L) -> %% diameter answers. send_unknown_application([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3007, %% UNSUPPORTED_APPLICATION 'Failed-AVP' = [], @@ -369,10 +401,12 @@ send_unknown_application([_,_]) -> %% handle_request discards the request. send_unknown_command([callback, _]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), {error, timeout} = call(); %% diameter answers. send_unknown_command([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3001, %% UNSUPPORTED_COMMAND 'Failed-AVP' = [], @@ -385,6 +419,7 @@ send_unknown_command([_,_]) -> %% Callback answers. send_ok([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 5002, %% UNKNOWN_SESSION_ID 'Failed-AVP' = [], 'AVP' = []} @@ -396,6 +431,7 @@ send_ok([_,_]) -> %% Callback answers. send_invalid_hdr_bits([callback, _]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 2001, %% SUCCESS 'Failed-AVP' = [], 'AVP' = []} @@ -403,6 +439,7 @@ send_invalid_hdr_bits([callback, _]) -> %% diameter answers. send_invalid_hdr_bits([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3008, %% INVALID_HDR_BITS 'Failed-AVP' = [], 'AVP' = []} @@ -414,6 +451,7 @@ send_invalid_hdr_bits([_,_]) -> %% diameter answers. send_missing_avp([answer, rfc6733]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -421,6 +459,7 @@ send_missing_avp([answer, rfc6733]) -> %% Callback answers. send_missing_avp([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -432,6 +471,7 @@ send_missing_avp([_,_]) -> %% diameter answers. send_ignore_missing_avp([answer, rfc6733]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -439,6 +479,7 @@ send_ignore_missing_avp([answer, rfc6733]) -> %% Callback answers, ignores the error send_ignore_missing_avp([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 2001, %% SUCCESS 'Failed-AVP' = [], 'AVP' = []} @@ -451,6 +492,7 @@ send_ignore_missing_avp([_,_]) -> %% RFC 6733 allows 5xxx in an answer-message. send_5xxx_missing_avp([_, rfc6733]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -458,10 +500,12 @@ send_5xxx_missing_avp([_, rfc6733]) -> %% RFC 3588 doesn't: sending answer fails. send_5xxx_missing_avp([_, rfc3588]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), {error, timeout} = call(); %% Callback answers, ignores the error send_5xxx_missing_avp([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 2001, %% SUCCESS 'Failed-AVP' = [], 'AVP' = []} @@ -473,6 +517,7 @@ send_5xxx_missing_avp([_,_]) -> %% Callback answers with STA. send_double_error([callback, _]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #diameter_base_STA{'Result-Code' = 5005, %% MISSING_AVP 'Failed-AVP' = [_], 'AVP' = []} @@ -480,6 +525,7 @@ send_double_error([callback, _]) -> %% diameter answers with answer-message. send_double_error([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3008, %% INVALID_HDR_BITS 'Failed-AVP' = [], 'AVP' = []} @@ -491,6 +537,7 @@ send_double_error([_,_]) -> %% Callback answers. send_3xxx([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 3999, 'Failed-AVP' = [], 'AVP' = []} @@ -503,10 +550,12 @@ send_3xxx([_,_]) -> %% Callback answers but fails since 5xxx isn't allowed in an RFC 3588 %% answer-message. send_5xxx([_, rfc3588]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), {error, timeout} = call(); %% Callback answers. send_5xxx([_,_]) -> + ?XL("~w -> entry", [?FUNCTION_NAME]), #'diameter_base_answer-message'{'Result-Code' = 5999, 'Failed-AVP' = [], 'AVP' = []} @@ -516,6 +565,7 @@ send_5xxx([_,_]) -> call() -> Name = ?testcase(), + ?XL("call -> make diameter call with Name: ~p", [Name]), diameter:call(?CLIENT, ?DICT, #diameter_base_STR @@ -524,6 +574,7 @@ call() -> 'Class' = [?L(Name)]}, [{extra, [Name]}]). + %% =========================================================================== %% diameter callbacks From a8dfa61d0190ba9f380bc6f2829d7c12553d7629 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 14 May 2024 17:03:57 +0200 Subject: [PATCH 22/38] [diameter|test] Add host and os analyzis function(s) --- lib/diameter/test/diameter_util.erl | 2296 ++++++++++++++++++++++++++- 1 file changed, 2292 insertions(+), 4 deletions(-) diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index a55934aa99d1..d247f0510e22 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -24,8 +24,15 @@ %% Utility functions. %% +%% Framework +-export([ + init_per_suite/1, + end_per_suite/1 + ]). + %% generic --export([name/1, +-export([ + name/1, consult/2, run/1, fold/3, @@ -38,14 +45,20 @@ unique_string/0, have_sctp/0, eprof/1, - log/4]). + log/4, + proxy_call/3 + ]). %% diameter-specific --export([lport/2, +-export([ + lport/2, listen/2, listen/3, connect/3, connect/4, disconnect/4, - info/0]). + info/0 + ]). + +-export([analyze_and_print_host_info/0]). -include("diameter_util.hrl"). @@ -56,6 +69,41 @@ -define(UL(F, A), ?LOG("DUTIL", F, A)). +%% --------------------------------------------------------------------------- + +init_per_suite(Config) -> + try analyze_and_print_host_info() of + {Factor, HostInfo} when is_integer(Factor) -> + try maybe_skip(HostInfo) of + true -> + {skip, "Unstable host and/or os (or combo thererof)"}; + false -> + case lists:keysearch(label, 1, HostInfo) of + {value, Label} -> + [{dia_factor, Factor}, Label | Config]; + false -> + [{dia_factor, Factor} | Config] + end + catch + throw:{skip, _} = SKIP -> + SKIP; + _:_:_ -> + [{dia_factor, Factor} | Config] + end; + _ -> + [{dia_factor, 1} | Config] + catch + throw:{skip, _} = SKIP -> + SKIP; + _:_:_ -> + [{dia_factor, 1} | Config] + end. + + +end_per_suite(_Config) -> + ok. + + %% --------------------------------------------------------------------------- eprof(start) -> @@ -549,6 +597,7 @@ cfg(listen) -> cfg(PortNr) -> [{raddr, ?ADDR}, {rport, PortNr}]. + %% --------------------------------------------------------------------------- %% info/0 @@ -570,3 +619,2242 @@ log(ModStr, LINE, F, A) is_list(F) andalso is_list(A) -> ct:log("[~s:~w,~p] " ++ F ++ "~n", [ModStr, LINE, self()|A]). + + +%% --------------------------------------------------------------------------- + +analyze_and_print_host_info() -> + {OsFam, OsName} = os:type(), + Version = + case os:version() of + {Maj, Min, Rel} -> + f("~w.~w.~w", [Maj, Min, Rel]); + VStr -> + VStr + end, + case {OsFam, OsName} of + {unix, linux} -> + analyze_and_print_linux_host_info(Version); + {unix, openbsd} -> + analyze_and_print_openbsd_host_info(Version); + {unix, freebsd} -> + analyze_and_print_freebsd_host_info(Version); + {unix, netbsd} -> + analyze_and_print_netbsd_host_info(Version); + {unix, darwin} -> + analyze_and_print_darwin_host_info(Version); + {unix, sunos} -> + analyze_and_print_solaris_host_info(Version); + {win32, nt} -> + analyze_and_print_win_host_info(Version); + _ -> + io:format("OS Family: ~p" + "~n OS Type: ~p" + "~n Version: ~p" + "~n Num Online Schedulers: ~s" + "~n", [OsFam, OsName, Version, str_num_schedulers()]), + {num_schedulers_to_factor(), []} + end. + + +%% -- Unix:Linux -- + +analyze_and_print_linux_host_info(Version) -> + {Distro, Label} = + case file:read_file_info("/etc/issue") of + {ok, _} -> + linux_which_distro(Version); + _ -> + L = ts_extra_platform_label(), + io:format("Linux: ~s" + "~n TS Extra Platform Label: ~s" + "~n", [Version, L]), + {other, simplify_label(L)} + end, + %% 'VirtFactor' will be 0 unless virtual + VirtFactor = linux_virt_factor(), + Factor = + case (catch linux_which_cpuinfo(Distro)) of + {ok, {CPU, BogoMIPS}} -> + io:format("CPU: " + "~n Model: ~s" + "~n BogoMIPS: ~w" + "~n Num Online Schedulers: ~s" + "~n", [CPU, BogoMIPS, str_num_schedulers()]), + if + (BogoMIPS > 50000) -> + 1; + (BogoMIPS > 40000) -> + 2; + (BogoMIPS > 30000) -> + 3; + (BogoMIPS > 20000) -> + 4; + (BogoMIPS > 10000) -> + 5; + (BogoMIPS > 5000) -> + 8; + (BogoMIPS > 3000) -> + 12; + true -> + 10 + end; + {ok, "POWER9" ++ _ = CPU} -> + %% For some reason this host is really slow + %% Consider the CPU, it really should not be... + %% But, to not fail a bunch of test cases, we add 5 + case linux_cpuinfo_clock() of + Clock when is_integer(Clock) andalso (Clock > 0) -> + io:format("CPU: " + "~n Model: ~s" + "~n CPU Speed: ~w" + "~n Num Online Schedulers: ~s" + "~n", [CPU, Clock, str_num_schedulers()]), + if + (Clock > 2000) -> + 5 + num_schedulers_to_factor(); + true -> + 10 + num_schedulers_to_factor() + end; + _ -> + num_schedulers_to_factor() + end; + {ok, CPU} -> + io:format("CPU: " + "~n Model: ~s" + "~n Num Online Schedulers: ~s" + "~n", [CPU, str_num_schedulers()]), + num_schedulers_to_factor(); + _ -> + 5 + end, + AddLabelFactor = label2factor(Label), + %% Check if we need to adjust the factor because of the memory + AddMemFactor = try linux_which_meminfo() + catch _:_:_ -> 0 + end, + TSScaleFactor = case timetrap_scale_factor() of + N when is_integer(N) andalso (N > 0) -> + N - 1; + _ -> + 0 + end, + io:format("Factor calc:" + "~n Base Factor: ~w" + "~n Label Factor: ~w" + "~n Mem Factor: ~w" + "~n Virtual Factor: ~w" + "~n TS Scale Factor: ~w" + "~n", [Factor, AddLabelFactor, AddMemFactor, VirtFactor, + TSScaleFactor]), + {Factor + AddLabelFactor + AddMemFactor + VirtFactor + TSScaleFactor, + [{label, Label}]}. + + +linux_which_distro(Version) -> + try do_linux_which_distro(Version) + catch + throw:{distro, DistroAndLabel} -> + DistroAndLabel + end. + +do_linux_which_distro(Version) -> + Label = ts_extra_platform_label(), + + %% Many (linux) distro's use the /etc/issue file, so try that first. + %% Then we just keep going until we are "done". + DistroStr = do_linux_which_distro_issue(Version, Label), + + %% Still not sure; try fedora + _ = do_linux_which_distro_fedora(Version, Label), + + %% Still not sure; try suse + _ = do_linux_which_distro_suse(Version, Label), + + %% Still not sure; try os-release + _ = do_linux_which_distro_os_release(Version, Label), + + %% And the fallback + io:format("Linux: ~s" + "~n Distro: ~s" + "~n Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + {other, simplify_label(Label)}. + +do_linux_which_distro_issue(Version, Label) -> + case file:read_file_info("/etc/issue") of + {ok, _} -> + case [string:trim(S) || + S <- string:tokens(os:cmd("cat /etc/issue"), [$\n])] of + [DistroStr | _] -> + case DistroStr of + "Wind River Linux" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {wind_river, simplify_label(Label)}}); + "MontaVista" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {montavista, simplify_label(Label)}}); + "Yellow Dog" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {yellow_dog, simplify_label(Label)}}); + "Ubuntu" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {ubuntu, simplify_label(Label)}}); + "Linux Mint" ++ _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {linux_mint, simplify_label(Label)}}); + _ -> + DistroStr + end; + X -> + X + end; + _ -> + "Unknown" + end. + +do_linux_which_distro_fedora(Version, Label) -> + %% Check if fedora + case file:read_file_info("/etc/fedora-release") of + {ok, _} -> + case [string:trim(S) || + S <- string:tokens(os:cmd("cat /etc/fedora-release"), + [$\n])] of + [DistroStr | _] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]); + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, "Fedora", Label, + linux_product_name()]) + end, + throw({distro, {fedora, simplify_label(Label)}}); + _ -> + ignore + end. + +do_linux_which_distro_suse(Version, Label) -> + %% Check if its a SuSE + case file:read_file_info("/etc/SUSE-brand") of + {ok, _} -> + case file:read_file_info("/etc/SuSE-release") of + {ok, _} -> + case [string:trim(S) || + S <- string:tokens(os:cmd("cat /etc/SuSE-release"), + [$\n])] of + ["SUSE Linux Enterprise Server" ++ _ = DistroStr | _] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, {sles, simplify_label(Label)}}); + [DistroStr | _] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, {suse, simplify_label(Label)}}); + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, "SuSE", Label, + linux_product_name()]), + throw({distro, {suse, simplify_label(Label)}}) + end; + _ -> + case string:tokens(os:cmd("cat /etc/SUSE-brand"), [$\n]) of + ["SLE" = DistroStr, VERSION | _] -> + case [string:strip(S) || + S <- string:tokens(VERSION, [$=])] of + ["VERSION", VersionNo] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n Distro Version: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, + DistroStr, VersionNo, + Label, + linux_product_name()]), + throw({distro, + {sles, simplify_label(Label)}}); + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {sles, simplify_label(Label)}}) + end; + ["openSUSE" = DistroStr, VERSION | _] -> + case [string:strip(S) || + S <- string:tokens(VERSION, [$=])] of + ["VERSION", VersionNo] -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n Distro Version: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, + DistroStr, VersionNo, + Label, + linux_product_name()]), + throw({distro, + {suse, simplify_label(Label)}}); + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, Label, + linux_product_name()]), + throw({distro, + {suse, simplify_label(Label)}}) + end; + _ -> + io:format("Linux: ~s" + "~n Distro: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, "Unknown SUSE", Label, + linux_product_name()]), + throw({distro, {suse, simplify_label(Label)}}) + end + end; + _ -> + ignore + end. + +do_linux_which_distro_os_release(Version, Label) -> + case file:read_file_info("/etc/os-release") of + {ok, _} -> + %% We want to 'catch' if our processing is wrong, + %% that's why we catch and re-throw the distro. + %% Actual errors will be returned as 'ignore'. + try + begin + Info = linux_process_os_release(), + {value, {_, DistroStr}} = lists:keysearch(name, 1, Info), + {value, {_, VersionNo}} = lists:keysearch(version, 1, Info), + io:format("Linux: ~s" + "~n Distro: ~s" + "~n Distro Version: ~s" + "~n TS Extra Platform Label: ~s" + "~n Product Name: ~s" + "~n", + [Version, DistroStr, VersionNo, Label, + linux_product_name()]), + throw({distro, + {linux_distro_str_to_distro_id(DistroStr), + simplify_label(Label)}}) + end + catch + throw:{distro, _} = DISTRO -> + throw(DISTRO); + _:_ -> + ignore + end; + _ -> + ignore + end. + +linux_process_os_release() -> + %% Read the "raw" file + Raw = os:cmd("cat /etc/os-release"), + %% Split it into lines + Lines1 = string:tokens(Raw, [$\n]), + %% Just in case, skip any lines starting with '#'. + Lines2 = linux_process_os_release1(Lines1), + %% Each (remaining) line *should* be: = + %% Both sides will be strings, the value side will be a quoted string... + %% Convert those into a 2-tuple list: [{Tag, Value}] + linux_process_os_release2(Lines2). + +linux_process_os_release1(Lines) -> + linux_process_os_release1(Lines, []). + +linux_process_os_release1([], Acc) -> + lists:reverse(Acc); +linux_process_os_release1([H|T], Acc) -> + case H of + "#" ++ _ -> + linux_process_os_release1(T, Acc); + _ -> + linux_process_os_release1(T, [H|Acc]) + end. + +linux_process_os_release2(Lines) -> + linux_process_os_release2(Lines, []). + +linux_process_os_release2([], Acc) -> + lists:reverse(Acc); +linux_process_os_release2([H|T], Acc) -> + case linux_process_os_release3(H) of + {value, Value} -> + linux_process_os_release2(T, [Value|Acc]); + false -> + linux_process_os_release2(T, Acc) + end. + +linux_process_os_release3(H) -> + case [string:strip(S) || S <- string:tokens(H, [$=])] of + [Tag, Value] -> + Tag2 = list_to_atom(string:to_lower(Tag)), + Value2 = string:strip(Value, both, $"), + linux_process_os_release4(Tag2, Value2); + _ -> + false + end. + +linux_process_os_release4(name = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(version = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(version_id = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(id = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(pretty_name = Tag, Value) -> + {value, {Tag, Value}}; +linux_process_os_release4(_Tag, _Value) -> + false. + +linux_distro_str_to_distro_id("Debian" ++ _) -> + debian; +linux_distro_str_to_distro_id("Fedora" ++ _) -> + fedora; +linux_distro_str_to_distro_id("Linux Mint" ++ _) -> + linux_mint; +linux_distro_str_to_distro_id("MontaVista" ++ _) -> + montavista; +linux_distro_str_to_distro_id("openSUSE" ++ _) -> + suse; +linux_distro_str_to_distro_id("SLES" ++ _) -> + sles; +linux_distro_str_to_distro_id("Ubuntu" ++ _) -> + ubuntu; +linux_distro_str_to_distro_id("Wind River Linux" ++ _) -> + wind_river; +linux_distro_str_to_distro_id("Yellow Dog" ++ _) -> + yellow_dog; +linux_distro_str_to_distro_id(X) -> + X. + + +linux_virt_factor() -> + linux_virt_factor(linux_product_name()). + +linux_virt_factor("VMware" ++ _) -> + 2; +linux_virt_factor("VirtualBox" ++ _) -> + 4; +linux_virt_factor(_) -> + 0. + + +linux_product_name() -> + ProductNameFile = "/sys/devices/virtual/dmi/id/product_name", + case file:read_file_info(ProductNameFile) of + {ok, _} -> + case os:cmd("cat " ++ ProductNameFile) of + false -> + "-"; + Info -> + string:trim(Info) + end; + _ -> + "-" + end. + + +linux_info_lookup(Key, File) -> + LKey = string:to_lower(Key), + try [string:trim(S) || S <- string:tokens(os:cmd("grep -i " ++ "\"" ++ LKey ++ "\"" ++ " " ++ File), [$:,$\n])] of + Info -> + linux_info_lookup_collect(LKey, Info, []) + catch + _:_:_ -> + "-" + end. + +linux_info_lookup_collect(_Key, [], Values) -> + lists:reverse(Values); +linux_info_lookup_collect(Key, [Key, Value|Rest], Values) -> + linux_info_lookup_collect(Key, Rest, [Value|Values]); +linux_info_lookup_collect(Key1, [Key2, Value|Rest], Values) -> + case string:to_lower(Key2) of + Key1 -> + linux_info_lookup_collect(Key1, Rest, [Value|Values]); + _ -> + lists:reverse(Values) + end; +linux_info_lookup_collect(_, _, Values) -> + lists:reverse(Values). + + +linux_cpuinfo_lookup(Key) when is_list(Key) -> + linux_info_lookup(Key, "/proc/cpuinfo"). + +linux_cpuinfo_cpu() -> + case linux_cpuinfo_lookup("cpu") of + [Model] -> + Model; + ["POWER9" ++ _ = CPU|_] -> + CPU; + _ -> + "-" + end. + +linux_cpuinfo_motherboard() -> + case linux_cpuinfo_lookup("motherboard") of + [MB] -> + MB; + _ -> + "-" + end. + +linux_cpuinfo_bogomips() -> + case linux_cpuinfo_lookup("bogomips") of + [] -> + "-"; + BMips when is_list(BMips) -> + BMScale = 1.0, + try round(BMScale * lists:sum([bogomips_to_int(BM) || BM <- BMips])) + catch + _:_:_ -> + "-" + end; + _X -> + "-" + end. + +linux_cpuinfo_total_bogomips() -> + case linux_cpuinfo_lookup("total bogomips") of + [TBM] -> + try bogomips_to_int(TBM) + catch + _:_:_ -> + "-" + end; + _ -> + "-" + end. + +bogomips_to_int(BM) -> + try list_to_float(BM) of + F -> + floor(F) + catch + _:_:_ -> + try list_to_integer(BM) of + I -> + I + catch + _:_:_ -> + throw(noinfo) + end + end. + +linux_cpuinfo_model() -> + case linux_cpuinfo_lookup("model") of + [M] -> + M; + _X -> + "-" + end. + +linux_cpuinfo_platform() -> + case linux_cpuinfo_lookup("platform") of + [P] -> + P; + _ -> + "-" + end. + +linux_cpuinfo_model_name() -> + case linux_cpuinfo_lookup("model name") of + [P|_] -> + P; + _ -> + "-" + end. + +linux_cpuinfo_processor() -> + case linux_cpuinfo_lookup("Processor") of + [P] -> + P; + _ -> + "-" + end. + +linux_cpuinfo_machine() -> + case linux_cpuinfo_lookup("machine") of + [M] -> + M; + _ -> + "-" + end. + +linux_which_cpuinfo(montavista) -> + CPU = + case linux_cpuinfo_cpu() of + "-" -> + throw(noinfo); + Model -> + case linux_cpuinfo_motherboard() of + "-" -> + Model; + MB -> + Model ++ " (" ++ MB ++ ")" + end + end, + case linux_cpuinfo_bogomips() of + "-" -> + {ok, CPU}; + BMips -> + {ok, {CPU, BMips}} + end; + +linux_which_cpuinfo(yellow_dog) -> + CPU = + case linux_cpuinfo_cpu() of + "-" -> + throw(noinfo); + Model -> + case linux_cpuinfo_motherboard() of + "-" -> + Model; + MB -> + Model ++ " (" ++ MB ++ ")" + end + end, + {ok, CPU}; + +linux_which_cpuinfo(wind_river) -> + CPU = + case linux_cpuinfo_model() of + "-" -> + throw(noinfo); + Model -> + case linux_cpuinfo_platform() of + "-" -> + Model; + Platform -> + Model ++ " (" ++ Platform ++ ")" + end + end, + case linux_cpuinfo_total_bogomips() of + "-" -> + {ok, CPU}; + BMips -> + {ok, {CPU, BMips}} + end; + +%% Check for x86 (Intel or AMD) +linux_which_cpuinfo(Other) when (Other =:= debian) orelse + (Other =:= fedora) orelse + (Other =:= ubuntu) orelse + (Other =:= linux_mint) orelse + (Other =:= sles) orelse + (Other =:= suse) orelse + (Other =:= other) -> + CPU = + case linux_cpuinfo_model_name() of + "-" -> + %% This is for POWER9 + case linux_cpuinfo_cpu() of + "POWER9" ++ _ = PowerCPU -> + Machine = + case linux_cpuinfo_machine() of + "-" -> + ""; + M -> + " (" ++ M ++ ")" + end, + PowerCPU ++ Machine; + _X -> + %% ARM (at least some distros...) + case linux_cpuinfo_processor() of + "-" -> + case linux_cpuinfo_model() of + "-" -> + %% Ok, we give up + throw(noinfo); + Model -> + Model + end; + Proc -> + Proc + end + end; + ModelName -> + ModelName + end, + case linux_cpuinfo_bogomips() of + "-" -> + {ok, CPU}; + BMips -> + {ok, {CPU, BMips}} + end. + +linux_meminfo_lookup(Key) when is_list(Key) -> + linux_info_lookup(Key, "/proc/meminfo"). + +linux_meminfo_memtotal() -> + case linux_meminfo_lookup("MemTotal") of + [X] -> + X; + _ -> + "-" + end. + +%% We *add* the value this return to the Factor. +linux_which_meminfo() -> + case linux_meminfo_memtotal() of + "-" -> + 0; + MemTotal -> + io:format("Memory:" + "~n ~s" + "~n", [MemTotal]), + case string:tokens(MemTotal, [$ ]) of + [MemSzStr, MemUnit] -> + MemSz2 = list_to_integer(MemSzStr), + MemSz3 = + case string:to_lower(MemUnit) of + "kb" -> + MemSz2; + "mb" -> + MemSz2*1024; + "gb" -> + MemSz2*1024*1024; + _ -> + throw(noinfo) + end, + if + (MemSz3 >= 8388608) -> + 0; + (MemSz3 >= 4194304) -> + 1; + (MemSz3 >= 2097152) -> + 3; + true -> + 5 + end; + _X -> + 0 + end + end. + + +linux_cpuinfo_clock() -> + %% This is written as: "3783.000000MHz" + %% So, check unit MHz (handle nothing else). + %% Also, check for both float and integer + %% Also, the freq is per core, and can vary... + case linux_cpuinfo_lookup("clock") of + [C|_] when is_list(C) -> + case lists:reverse(string:to_lower(C)) of + "zhm" ++ CRev -> + try trunc(list_to_float(lists:reverse(CRev))) of + I -> + I + catch + _:_:_ -> + try list_to_integer(lists:reverse(CRev)) of + I -> + I + catch + _:_:_ -> + 0 + end + end; + _ -> + 0 + end; + _ -> + 0 + end. + + +%% -- Unix:OpenBSD -- + +%% Just to be clear: This is ***not*** scientific... +analyze_and_print_openbsd_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + io:format("OpenBSD:" + "~n Version: ~s" + "~n", [Version]), + Extract = + fun(Key) -> + string:tokens(string:trim(os:cmd("sysctl " ++ Key)), [$=]) + end, + try + begin + CPU = + case Extract("hw.model") of + ["hw.model", Model] -> + string:trim(Model); + _ -> + "-" + end, + CPUSpeed = + case Extract("hw.cpuspeed") of + ["hw.cpuspeed", Speed] -> + list_to_integer(Speed); + _ -> + -1 + end, + NCPU = + case Extract("hw.ncpufound") of + ["hw.ncpufound", N] -> + list_to_integer(N); + _ -> + -1 + end, + Memory = + case Extract("hw.physmem") of + ["hw.physmem", PhysMem] -> + list_to_integer(PhysMem) div 1024; + _ -> + -1 + end, + io:format("CPU:" + "~n Model: ~s" + "~n Speed: ~w" + "~n N: ~w" + "~nMemory:" + "~n ~w KB" + "~n", [CPU, CPUSpeed, NCPU, Memory]), + CPUFactor = + if + (CPUSpeed >= 3000) -> + if + (NCPU >= 8) -> + 1; + (NCPU >= 6) -> + 2; + (NCPU >= 4) -> + 3; + (NCPU >= 2) -> + 4; + true -> + 10 + end; + (CPUSpeed >= 2000) -> + if + (NCPU >= 8) -> + 2; + (NCPU >= 6) -> + 3; + (NCPU >= 4) -> + 4; + (NCPU >= 2) -> + 5; + true -> + 12 + end; + (CPUSpeed >= 1000) -> + if + (NCPU >= 8) -> + 3; + (NCPU >= 6) -> + 4; + (NCPU >= 4) -> + 5; + (NCPU >= 2) -> + 6; + true -> + 14 + end; + true -> + if + (NCPU >= 8) -> + 4; + (NCPU >= 6) -> + 6; + (NCPU >= 4) -> + 8; + (NCPU >= 2) -> + 10; + true -> + 20 + end + end, + MemAddFactor = + if + (Memory >= 16777216) -> + 0; + (Memory >= 8388608) -> + 1; + (Memory >= 4194304) -> + 3; + (Memory >= 2097152) -> + 5; + true -> + 10 + end, + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + {CPUFactor + MemAddFactor + AddLabelFactor, []} + end + catch + _:_:_ -> + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + {2 + AddLabelFactor, []} + end. + + +%% -- Unix:FreeBSD -- + +analyze_and_print_freebsd_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + FreeBSDVersion = which_freebsd_version(), + case FreeBSDVersion of + undefined -> + io:format("FreeBSD:" + "~n Version: ~s" + "~n", [Version]), + ""; + _ -> + io:format("FreeBSD:" + "~n Version: ~s (~s)" + "~n", [Version, FreeBSDVersion]) + end, + %% This test require that the program 'sysctl' is in the path. + %% First test with 'which sysctl', if that does not work + %% try with 'which /sbin/sysctl'. If that does not work either, + %% we skip the test... + try + begin + SysCtl = + case string:trim(os:cmd("which sysctl")) of + [] -> + case string:trim(os:cmd("which /sbin/sysctl")) of + [] -> + throw(sysctl); + SC2 -> + SC2 + end; + SC1 -> + SC1 + end, + Extract = + fun(Key) -> + string:tokens(string:trim(os:cmd(SysCtl ++ " " ++ Key)), + [$:]) + end, + CPU = analyze_freebsd_cpu(Extract), + CPUSpeed = analyze_freebsd_cpu_speed(Extract), + NCPU = analyze_freebsd_ncpu(Extract), + Memory = analyze_freebsd_memory(Extract), + io:format("CPU:" + "~n Model: ~s" + "~n Speed: ~w" + "~n N: ~w" + "~n Num Online Schedulers: ~s" + "~nMemory:" + "~n ~w KB" + "~n", + [CPU, CPUSpeed, NCPU, str_num_schedulers(), Memory]), + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + CPUFactor = + if + (CPUSpeed =:= -1) -> + 1; + (CPUSpeed >= 3000) -> + if + (NCPU >= 8) -> + 1; + (NCPU >= 6) -> + 2; + (NCPU >= 4) -> + 3; + (NCPU >= 2) -> + 4; + true -> + 5 + end; + (CPUSpeed >= 2000) -> + if + (NCPU >= 12) -> + 1; + (NCPU >= 8) -> + 2; + (NCPU >= 6) -> + 4; + (NCPU >= 4) -> + 6; + (NCPU >= 2) -> + 8; + true -> + 10 + end; + true -> + if + (NCPU =:= -1) -> + 2; + (NCPU >= 12) -> + 2; + (NCPU >= 8) -> + 3; + (NCPU >= 6) -> + 5; + (NCPU >= 4) -> + 7; + (NCPU >= 2) -> + 9; + true -> + 12 + end + end, + MemAddFactor = + if + (Memory =:= -1) -> + 0; + (Memory >= 8388608) -> + 0; + (Memory >= 4194304) -> + 1; + (Memory >= 2097152) -> + 2; + true -> + 3 + end, + {CPUFactor + MemAddFactor, []} + end + catch + _:_:_ -> + io:format("CPU:" + "~n Num Online Schedulers: ~s" + "~n", [str_num_schedulers()]), + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + {num_schedulers_to_factor() ++ AddLabelFactor, []} + end. + + +which_freebsd_version() -> + case string:trim(os:cmd("which freebsd-version")) of + [] -> + "-"; + FreeBSDVersion -> + case string:trim(os:cmd(FreeBSDVersion)) of + [] -> + undefined; + V -> + V + end + end. + + +analyze_freebsd_cpu(Extract) -> + analyze_freebsd_item(Extract, "hw.model", fun(X) -> X end, "-"). + +analyze_freebsd_cpu_speed(Extract) -> + analyze_freebsd_item(Extract, + "hw.clockrate", + fun(X) -> list_to_integer(X) end, + -1). + +analyze_freebsd_ncpu(Extract) -> + analyze_freebsd_item(Extract, + "hw.ncpu", + fun(X) -> list_to_integer(X) end, + -1). + +analyze_freebsd_memory(Extract) -> + analyze_freebsd_item(Extract, + "hw.physmem", + fun(X) -> list_to_integer(X) div 1024 end, + -1). + +analyze_freebsd_item(Extract, Key, Process, Default) -> + try + begin + case Extract(Key) of + [Key, Model] -> + Process(string:trim(Model)); + _ -> + Default + end + end + catch + _:_:_ -> + Default + end. + + +%% -- Unix:NetBSD -- + +analyze_and_print_netbsd_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + io:format("NetBSD:" + "~n Version: ~s" + "~n", [Version]), + %% This test require that the program 'sysctl' is in the path. + %% First test with 'which sysctl', if that does not work + %% try with 'which /sbin/sysctl'. If that does not work either, + %% we skip the test... + try + begin + SysCtl = + case string:trim(os:cmd("which sysctl")) of + [] -> + case string:trim(os:cmd("which /sbin/sysctl")) of + [] -> + throw(sysctl); + SC2 -> + SC2 + end; + SC1 -> + SC1 + end, + Extract = + fun(Key) -> + [string:trim(S) || + S <- + string:tokens(string:trim(os:cmd(SysCtl ++ " " ++ Key)), + [$=])] + end, + CPU = analyze_netbsd_cpu(Extract), + Machine = analyze_netbsd_machine(Extract), + Arch = analyze_netbsd_machine_arch(Extract), + CPUSpeed = analyze_netbsd_cpu_speed(Extract), + NCPU = analyze_netbsd_ncpu(Extract), + Memory = analyze_netbsd_memory(Extract), + io:format("CPU:" + "~n Model: ~s (~s, ~s)" + "~n Speed: ~w MHz" + "~n N: ~w" + "~n Num Schedulers: ~w" + "~nMemory:" + "~n ~w KB" + "~n", + [CPU, Machine, Arch, CPUSpeed, NCPU, + erlang:system_info(schedulers), Memory]), + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + CPUFactor = + if + (CPUSpeed =:= -1) -> + 1; + (CPUSpeed >= 2000) -> + if + (NCPU >= 4) -> + 1; + (NCPU >= 2) -> + 2; + true -> + 3 + end; + true -> + if + (NCPU =:= -1) -> + 1; + (NCPU >= 4) -> + 2; + (NCPU >= 2) -> + 3; + true -> + 4 + end + end, + MemAddFactor = + if + (Memory =:= -1) -> + 0; + (Memory >= 8388608) -> + 0; + (Memory >= 4194304) -> + 1; + (Memory >= 2097152) -> + 2; + true -> + 3 + end, + {CPUFactor + MemAddFactor + AddLabelFactor, []} + end + catch + _:_:_ -> + io:format("CPU:" + "~n Num Schedulers: ~w" + "~n", [erlang:system_info(schedulers)]), + io:format("TS Scale Factor: ~w~n" + "TS Extra Platform Label: ~s~n", + [timetrap_scale_factor(), Label]), + Factor = num_schedulers_to_factor(), + {Factor + AddLabelFactor, []} + end. + + +analyze_netbsd_cpu(Extract) -> + analyze_netbsd_item(Extract, "hw.model", fun(X) -> X end, "-"). + +analyze_netbsd_machine(Extract) -> + analyze_netbsd_item(Extract, "hw.machine", fun(X) -> X end, "-"). + +analyze_netbsd_machine_arch(Extract) -> + analyze_netbsd_item(Extract, "hw.machine_arch", fun(X) -> X end, "-"). + +analyze_netbsd_cpu_speed(Extract) -> + analyze_netbsd_item(Extract, "machdep.dmi.processor-frequency", + fun(X) -> case string:tokens(X, [$\ ]) of + [MHz, "MHz"] -> + list_to_integer(MHz); + _ -> + -1 + end + end, "-"). + +analyze_netbsd_ncpu(Extract) -> + analyze_netbsd_item(Extract, + "hw.ncpu", + fun(X) -> list_to_integer(X) end, + -1). + +analyze_netbsd_memory(Extract) -> + analyze_netbsd_item(Extract, + "hw.physmem64", + fun(X) -> list_to_integer(X) div 1024 end, + -1). + +analyze_netbsd_item(Extract, Key, Process, Default) -> + analyze_freebsd_item(Extract, Key, Process, Default). + + +%% -- Unix:Darwin -- + +%% Model Identifier: Macmini7,1 +%% Processor Name: Intel Core i5 +%% Processor Speed: 2,6 GHz +%% Number of Processors: 1 +%% Total Number of Cores: 2 +%% L2 Cache (per Core): 256 KB +%% L3 Cache: 3 MB +%% Hyper-Threading Technology: Enabled +%% Memory: 16 GB + +%% Hardware: +%% +%% Hardware Overview: +%% +%% Model Name: MacBook Pro +%% Model Identifier: MacBookPro18,1 +%% Chip: Apple M1 Pro +%% Total Number of Cores: 10 (8 performance and 2 efficiency) +%% Memory: 32 GB +%% System Firmware Version: 7459.101.2 +%% OS Loader Version: 7459.101.2 +%% Serial Number (system): THF4W05C97 +%% Hardware UUID: 7C9AB2E1-73B1-5AD6-9BC8-7229DE7A748C +%% Provisioning UDID: 00006000-000259042662801E +%% Activation Lock Status: Enabled + + +analyze_and_print_darwin_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + %% This stuff is for macOS. + %% If we ever tested on a pure darwin machine, + %% we need to find some other way to find some info... + %% Also, I suppose its possible that we for some other + %% reason *fail* to get the info... + Label = ts_extra_platform_label(), + {BaseFactor, MemFactor} = + case analyze_darwin_software_info() of + [] -> + io:format("Darwin:" + "~n Version: ~s" + "~n Num Online Schedulers: ~s" + "~n TS Extra Platform Label: ~s" + "~n", [Version, str_num_schedulers(), Label]), + {num_schedulers_to_factor(), 1}; + SwInfo when is_list(SwInfo) -> + SystemVersion = analyze_darwin_sw_system_version(SwInfo), + KernelVersion = analyze_darwin_sw_kernel_version(SwInfo), + HwInfo = analyze_darwin_hardware_info(), + ModelName = analyze_darwin_hw_model_name(HwInfo), + ModelId = analyze_darwin_hw_model_identifier(HwInfo), + {Processor, CPUFactor} = analyze_darwin_hw_processor(HwInfo), + Memory = analyze_darwin_hw_memory(HwInfo), + Memory = analyze_darwin_hw_memory(HwInfo), + io:format("Darwin:" + "~n System Version: ~s" + "~n Kernel Version: ~s" + "~n Model: ~s (~s)" + "~n Processor: ~s" + "~n Memory: ~s" + "~n Num Online Schedulers: ~s" + "~n TS Extra Platform Label: ~s" + "~n~n", + [SystemVersion, KernelVersion, + ModelName, ModelId, + Processor, + Memory, + str_num_schedulers(), Label]), + {CPUFactor, analyze_darwin_memory_to_factor(Memory)} + end, + AddLabelFactor = label2factor(simplify_label(Label)), + AddMemFactor = if + (MemFactor > 0) -> + MemFactor - 1; + true -> + 0 + end, + TSScaleFactor = ts_scale_factor(), + io:format("Factor calc:" + "~n Base Factor: ~w" + "~n Label Factor: ~w" + "~n Mem Factor: ~w" + "~n TS Scale Factor: ~w" + "~n~n", + [BaseFactor, AddLabelFactor, AddMemFactor, TSScaleFactor]), + {BaseFactor + AddLabelFactor + AddMemFactor + TSScaleFactor, + [{label, Label}]}. + + +analyze_darwin_software_info() -> + analyze_darwin_system_profiler("SPSoftwareDataType"). + +analyze_darwin_hardware_info() -> + analyze_darwin_system_profiler("SPHardwareDataType"). + +analyze_darwin_system_profiler(DataType) -> + %% First, make sure the program actually exist (with the current PATH): + Prog0 = "system_profiler", + case os:cmd("which " ++ Prog0) of + [] -> + %% Ok, as a last resource, check if is /usr/sbin/system_profiler? + Prog1 = "/usr/sbin/system_profiler", + case os:cmd("which " ++ Prog1) of + [] -> + []; + _ -> + analyze_darwin_system_profiler(Prog1, DataType) + end; + _ -> + analyze_darwin_system_profiler(Prog0, DataType) + end. + +analyze_darwin_system_profiler(Prog, DataType) -> + D0 = os:cmd(Prog ++ " " ++ DataType), + D1 = string:tokens(D0, [$\n]), + D2 = [string:trim(S1) || S1 <- D1], + D3 = [string:tokens(S2, [$:]) || S2 <- D2], + analyze_darwin_system_profiler2(D3). + +analyze_darwin_system_profiler2(L) -> + analyze_darwin_system_profiler2(L, []). + +analyze_darwin_system_profiler2([], Acc) -> + [{string:to_lower(K), V} || {K, V} <- lists:reverse(Acc)]; +analyze_darwin_system_profiler2([[_]|T], Acc) -> + analyze_darwin_system_profiler2(T, Acc); +analyze_darwin_system_profiler2([[H1,H2]|T], Acc) -> + analyze_darwin_system_profiler2(T, [{H1, string:trim(H2)}|Acc]); +analyze_darwin_system_profiler2([[H|TH0]|T], Acc) -> + %% Some value parts has ':' in them, so put them together + TH1 = colonize(TH0), + analyze_darwin_system_profiler2(T, [{H, string:trim(TH1)}|Acc]). + + +analyze_darwin_sw_system_version(SwInfo) -> + proplists:get_value("system version", SwInfo, "-"). + +analyze_darwin_sw_kernel_version(SwInfo) -> + proplists:get_value("kernel version", SwInfo, "-"). + + +analyze_darwin_hw_chip(HwInfo) -> + proplists:get_value("chip", HwInfo, "-"). + +analyze_darwin_hw_model_name(HwInfo) -> + proplists:get_value("model name", HwInfo, "-"). + +analyze_darwin_hw_model_identifier(HwInfo) -> + proplists:get_value("model identifier", HwInfo, "-"). + +analyze_darwin_hw_processor(HwInfo) -> + case analyze_darwin_hw_processor_name(HwInfo) of + "-" -> % Maybe Apple Chip + case analyze_darwin_hw_chip(HwInfo) of + "-" -> + "-"; + Chip -> + NumCores = analyze_darwin_hw_total_number_of_cores(HwInfo), + CPUFactor = analyze_darwin_cpu_to_factor(Chip, NumCores), + {f("~s [~s]", [Chip, NumCores]), CPUFactor} + end; + ProcName -> + ProcSpeed = analyze_darwin_hw_processor_speed(HwInfo), + NumProc = analyze_darwin_hw_number_of_processors(HwInfo), + NumCores = analyze_darwin_hw_total_number_of_cores(HwInfo), + CPUFactor = analyze_darwin_cpu_to_factor(ProcName, + ProcSpeed, + NumProc, + NumCores), + {f("~s [~s, ~s, ~s]", + [ProcName, ProcSpeed, NumProc, NumCores]), CPUFactor} + end. + +analyze_darwin_hw_processor_name(HwInfo) -> + proplists:get_value("processor name", HwInfo, "-"). + +analyze_darwin_hw_processor_speed(HwInfo) -> + proplists:get_value("processor speed", HwInfo, "-"). + +analyze_darwin_hw_number_of_processors(HwInfo) -> + proplists:get_value("number of processors", HwInfo, "-"). + +analyze_darwin_hw_total_number_of_cores(HwInfo) -> + proplists:get_value("total number of cores", HwInfo, "-"). + +analyze_darwin_hw_memory(HwInfo) -> + proplists:get_value("memory", HwInfo, "-"). + + +%% The memory looks like this " ". Example: "2 GB" +analyze_darwin_memory_to_factor(Mem) -> + case [string:to_lower(S) || S <- string:tokens(Mem, [$\ ])] of + [_SzStr, "tb"] -> + 1; + [SzStr, "gb"] -> + try list_to_integer(SzStr) of + Sz when Sz < 2 -> + 20; + Sz when Sz < 4 -> + 10; + Sz when Sz < 8 -> + 5; + Sz when Sz < 16 -> + 2; + _ -> + 1 + catch + _:_:_ -> + 20 + end; + [_SzStr, "mb"] -> + 20; + _ -> + 20 + end. + +%% This is for the M1 family of chips +%% We don't actually know *how* fast it is, only that its fast. +%% the speed may be a float, which we transforms into an integer of MHz. +%% To calculate a factor based on processor "class" and number of cores +%% is ... not an exact ... science ... +analyze_darwin_cpu_to_factor("Apple M" ++ _ = _Chip, _NumCoresStr) -> + %% We know that pretty much every M processor is *fast*, + %% so there is no real need to "calculate" anything... + 1. + +analyze_darwin_cpu_to_factor(_ProcName, + ProcSpeedStr, NumProcStr, NumCoresStr) -> + Speed = + case [string:to_lower(S) || S <- string:tokens(ProcSpeedStr, [$\ ])] of + [SpeedStr, "mhz"] -> + try list_to_integer(SpeedStr) of + SpeedI -> + SpeedI + catch + _:_:_ -> + try list_to_float(SpeedStr) of + SpeedF -> + trunc(SpeedF) + catch + _:_:_ -> + -1 + end + end; + [SpeedStr, "ghz"] -> + try list_to_float(SpeedStr) of + SpeedF -> + trunc(1000*SpeedF) + catch + _:_:_ -> + try list_to_integer(SpeedStr) of + SpeedI -> + 1000*SpeedI + catch + _:_:_ -> + -1 + end + end; + _ -> + -1 + end, + NumProc = try list_to_integer(NumProcStr) of + NumProcI -> + NumProcI + catch + _:_:_ -> + 1 + end, + NumCores = try list_to_integer(NumCoresStr) of + NumCoresI -> + NumCoresI + catch + _:_:_ -> + 1 + end, + if + (Speed > 3000) -> + if + (NumProc =:= 1) -> + if + (NumCores < 2) -> + 5; + (NumCores < 4) -> + 3; + (NumCores < 6) -> + 2; + true -> + 1 + end; + true -> + if + (NumCores < 4) -> + 2; + true -> + 1 + end + end; + (Speed > 2000) -> + if + (NumProc =:= 1) -> + if + (NumCores < 2) -> + 8; + (NumCores < 4) -> + 5; + (NumCores < 6) -> + 3; + true -> + 1 + end; + true -> + if + (NumCores < 4) -> + 5; + (NumCores < 8) -> + 2; + true -> + 1 + end + end; + true -> + if + (NumProc =:= 1) -> + if + (NumCores < 2) -> + 10; + (NumCores < 4) -> + 7; + (NumCores < 6) -> + 5; + (NumCores < 8) -> + 3; + true -> + 1 + end; + true -> + if + (NumCores < 4) -> + 8; + (NumCores < 8) -> + 4; + true -> + 1 + end + end + end. + + +%% -- Unix:SunOS (Solaris) -- + +analyze_and_print_solaris_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + + Release = + case file:read_file_info("/etc/release") of + {ok, _} -> + case [string:trim(S) || S <- string:tokens(os:cmd("cat /etc/release"), [$\n])] of + [Rel | _] -> + Rel; + _ -> + "-" + end; + _ -> + "-" + end, + %% Display the firmware device tree root properties (prtconf -b) + Props = [list_to_tuple([string:trim(PS) || PS <- Prop]) || + Prop <- [string:tokens(S, [$:]) || + S <- string:tokens(os:cmd("prtconf -b"), [$\n])]], + BannerName = case lists:keysearch("banner-name", 1, Props) of + {value, {_, BN}} -> + string:trim(BN); + _ -> + "-" + end, + InstructionSet = + case string:trim(os:cmd("isainfo -k")) of + "Pseudo-terminal will not" ++ _ -> + "-"; + IS -> + IS + end, + PtrConf = [list_to_tuple([string:trim(S) || S <- Items]) || Items <- [string:tokens(S, [$:]) || S <- string:tokens(os:cmd("prtconf"), [$\n])], length(Items) > 1], + SysConf = + case lists:keysearch("System Configuration", 1, PtrConf) of + {value, {_, SC}} -> + SC; + _ -> + "-" + end, + %% Because we count the lines of the output (which may contain + %% any number of extra crap lines) we need to ensure we only + %% count the "proper" stdout. So send it to a tmp file first + %% and then count its number of lines... + NumPhysCPU = + try + begin + File1 = f("/tmp/psrinfo_p.~s.~w", [os:getpid(), os:system_time()]), + os:cmd("psrinfo -p > " ++ File1), + string:trim(os:cmd("cat " ++ File1)) + end + catch + _:_:_ -> + "-" + end, + %% Because we count the lines of the output (which may contain + %% any number of extra crap lines) we need to ensure we only + %% count the "proper" stdout. So send it to a tmp file first + %% and then count its number of lines... + NumVCPU = + try + begin + File2 = f("/tmp/psrinfo.~s.~w", [os:getpid(), os:system_time()]), + os:cmd("psrinfo > " ++ File2), + [NumVCPUStr | _] = string:tokens(os:cmd("wc -l " ++ File2), [$\ ]), + NumVCPUStr + end + catch + _:_:_ -> + "-" + end, + MemSz = + case lists:keysearch("Memory size", 1, PtrConf) of + {value, {_, MS}} -> + MS; + _ -> + "-" + end, + io:format("Solaris: ~s" + "~n Release: ~s" + "~n Banner Name: ~s" + "~n Instruction Set: ~s" + "~n CPUs: ~s (~s)" + "~n System Config: ~s" + "~n Memory Size: ~s" + "~n Num Online Schedulers: ~s" + "~n~n", [Version, Release, BannerName, InstructionSet, + NumPhysCPU, NumVCPU, + SysConf, MemSz, + str_num_schedulers()]), + AddMemFactor = + try string:tokens(MemSz, [$ ]) of + [SzStr, "Mega" ++ _] -> + try list_to_integer(SzStr) of + Sz when Sz > 16384 -> + 0; + Sz when Sz > 8192 -> + 1; + Sz when Sz > 4096 -> + 4; + Sz when Sz > 2048 -> + 8; + _ -> + 12 + catch + _:_:_ -> + 10 + end; + [SzStr, "Giga" ++ _] -> + try list_to_integer(SzStr) of + Sz when Sz > 16 -> + 0; + Sz when Sz > 8 -> + 1; + Sz when Sz > 4 -> + 4; + Sz when Sz > 2 -> + 8; + _ -> + 12 + catch + _:_:_ -> + 10 + end; + _ -> + 10 + catch + _:_:_ -> + 10 + end, + %% We don't really have enough info about the CPU to calculate the + %% base factor based on that, so we just use the number of schedulers. + BaseFactor = + try erlang:system_info(schedulers) of + 1 -> + 12; + 2 -> + 8; + N when (N =:= 3) orelse (N =:= 4) -> + 4; + N when (N =< 6) -> + 3; + _ -> + 2 + catch + _:_:_ -> + 12 + end, + TSScaleFactor = ts_scale_factor(), + io:format("Factor calc:" + "~n Base Factor: ~w" + "~n Label Factor: ~w" + "~n Mem Factor: ~w" + "~n TS Scale Factor: ~w" + "~n TS Extra Platform Label: ~s" + "~n~n", + [BaseFactor, AddLabelFactor, AddMemFactor, + TSScaleFactor, Label]), + {BaseFactor + AddMemFactor + AddLabelFactor + TSScaleFactor, + [{label, Label}]}. + + +%% -- Win32:NT -- + +analyze_and_print_win_host_info(Version) -> + Label = ts_extra_platform_label(), + AddLabelFactor = label2factor(simplify_label(Label)), + + SysInfo = which_win_system_info(), + OsName = win_sys_info_lookup(os_name, SysInfo), + OsVersion = win_sys_info_lookup(os_version, SysInfo), + SysMan = win_sys_info_lookup(system_manufacturer, SysInfo), + SysMod = win_sys_info_lookup(system_model, SysInfo), + SysType = win_sys_info_lookup(system_type, SysInfo), + NumProcs = win_sys_info_lookup(num_processors, SysInfo), + TotPhysMem = win_sys_info_lookup(total_phys_memory, SysInfo), + io:format("Windows: ~s" + "~n OS Version: ~s (~p)" + "~n System Manufacturer: ~s" + "~n System Model: ~s" + "~n System Type: ~s" + "~n Number of Processor(s): ~s" + "~n Total Physical Memory: ~s" + "~n (Erlang) WordSize: ~w" + "~n Num Online Schedulers: ~s" + "~n~n", [OsName, OsVersion, Version, + SysMan, SysMod, SysType, + NumProcs, TotPhysMem, + erlang:system_info(wordsize), + str_num_schedulers()]), + io:format("TS: " + "~n TimeTrap Factor: ~w" + "~n Extra Platform Label: ~s" + "~n~n", + [timetrap_scale_factor(), Label]), + %% 'VirtFactor' will be 0 unless virtual + VirtFactor = win_virt_factor(SysMod), + + %% On some machines this is a badly formated string + %% (contains a char of 255), so we need to do some nasty stuff... + MemFactor = + try + begin + %% "Normally" this looks like this: "16,123 MB" + %% But sometimes the "," is replaced by a + %% 255 or 160 char, which I assume must be some + %% unicode screwup... + %% Anyway, filter out both of them! + TotPhysMem1 = lists:delete($,, TotPhysMem), + TotPhysMem2 = lists:delete(255, TotPhysMem1), + TotPhysMem3 = lists:delete(160, TotPhysMem2), + [MStr, MUnit|_] = string:tokens(TotPhysMem3, [$\ ]), + case string:to_lower(MUnit) of + "gb" -> + try list_to_integer(MStr) of + M when M >= 16 -> + 0; + M when M >= 8 -> + 1; + M when M >= 4 -> + 3; + M when M >= 2 -> + 6; + _ -> + 10 + catch + _:_:_ -> + %% For some reason the string contains + %% "unusual" characters... + %% ...so print the string as a list... + io:format("Bad memory string: " + "~n [gb] ~w" + "~n", [MStr]), + 10 + end; + "mb" -> + try list_to_integer(MStr) of + M when M >= 16384 -> + 0; + M when M >= 8192 -> + 1; + M when M >= 4096 -> + 3; + M when M >= 2048 -> + 6; + _ -> + 10 + catch + _:_:_ -> + %% For some reason the string contains + %% "unusual" characters... + %% ...so print the string as a list... + io:format("Bad memory string: " + "~n [mb] ~w" + "~n", [MStr]), + 10 + end; + _ -> + io:format("Bad memory string: " + "~n ~w" + "~n", [MStr]), + 10 + end + end + catch + _:_:_ -> + %% For some reason the string contains + %% "unusual" characters... + %% ...so print the string as a list... + io:format("Bad memory string: " + "~n (y) ~w" + "~n", [TotPhysMem]), + 10 + end, + CPUFactor = + case erlang:system_info(schedulers) of + 1 -> + 10; + 2 -> + 5; + _ -> + 2 + end, + io:format("Factor calc:" + "~n CPU Factor: ~w" + "~n Mem Factor: ~w" + "~n Label Factor: ~w" + "~n Virtual Factor: ~w" + "~n~n", + [CPUFactor, MemFactor, AddLabelFactor, VirtFactor]), + {CPUFactor + MemFactor + AddLabelFactor + VirtFactor, SysInfo}. + + +%% This function only extracts the prop we actually care about! +which_win_system_info() -> + F = fun() -> + try + begin + SysInfo = os:cmd("systeminfo"), + process_win_system_info( + string:tokens(SysInfo, [$\r, $\n]), []) + end + catch + C:E:S -> + io:format("Failed get or process System info: " + " Error Class: ~p" + " Error: ~p" + " Stack: ~p" + "~n", [C, E, S]), + [] + end + end, + proxy_call(F, timer:minutes(1), []). + + +win_sys_info_lookup(Key, SysInfo) -> + win_sys_info_lookup(Key, SysInfo, "-"). + +win_sys_info_lookup(Key, SysInfo, Def) -> + case lists:keysearch(Key, 1, SysInfo) of + {value, {Key, Value}} -> + Value; + false -> + Def + end. + + +win_virt_factor("VMware" ++ _) -> + 2; +win_virt_factor(_) -> + 0. + + +process_win_system_info([], Acc) -> + Acc; +process_win_system_info([H|T], Acc) -> + case string:tokens(H, [$:]) of + [Key, Value] -> + case string:to_lower(Key) of + "os name" -> + process_win_system_info(T, + [{os_name, string:trim(Value)}|Acc]); + "os version" -> + process_win_system_info(T, + [{os_version, string:trim(Value)}|Acc]); + "system manufacturer" -> + process_win_system_info(T, + [{system_manufacturer, string:trim(Value)}|Acc]); + "system model" -> + process_win_system_info(T, + [{system_model, string:trim(Value)}|Acc]); + "system type" -> + process_win_system_info(T, + [{system_type, string:trim(Value)}|Acc]); + "processor(s)" -> + [NumProcStr|_] = string:tokens(Value, [$\ ]), + T2 = lists:nthtail(list_to_integer(NumProcStr), T), + process_win_system_info(T2, + [{num_processors, NumProcStr}|Acc]); + "total physical memory" -> + process_win_system_info(T, + [{total_phys_memory, string:trim(Value)}|Acc]); + _ -> + process_win_system_info(T, Acc) + end; + _ -> + process_win_system_info(T, Acc) + end. + + +%% --------------------------------------------------------------------------- + +str_num_schedulers() -> + try erlang:system_info(schedulers_online) of + N -> f("~w", [N]) + catch + _:_:_ -> "-" + end. + +num_schedulers_to_factor() -> + try erlang:system_info(schedulers_online) of + 1 -> + 10; + 2 -> + 8; + 3 -> + 6; + 4 -> + 4; + N when (N =< 5) -> + 2; + _ -> + 1 + catch + _:_:_ -> + 10 + end. + + +ts_extra_platform_label() -> + case os:getenv("TS_EXTRA_PLATFORM_LABEL") of + false -> "-"; + Val -> Val + end. + +ts_scale_factor() -> + case timetrap_scale_factor() of + N when is_integer(N) andalso (N > 0) -> + N - 1; + _ -> + 0 + end. + + +timetrap_scale_factor() -> + case (catch test_server:timetrap_scale_factor()) of + {'EXIT', _} -> + 1; + N -> + N + end. + + +simplify_label("Systemtap" ++ _) -> + {host, systemtap}; +simplify_label("Meamax" ++ _) -> + {host, meamax}; +simplify_label("Cover" ++ _) -> + {host, cover}; +simplify_label(Label) -> + case string:find(string:to_lower(Label), "docker") of + "docker" ++ _ -> + docker; + _ -> + {host, undefined} + end. + +label2factor(docker) -> + 4; +label2factor({host, meamax}) -> + 2; +label2factor({host, cover}) -> + 6; +label2factor({host, _}) -> + 0. + + + +%% --------------------------------------------------------------------------- + +maybe_skip(_HostInfo) -> + + %% We have some crap machines that causes random test case failures + %% for no obvious reason. So, attempt to identify those without actually + %% checking for the host name... + + LinuxVersionVerify = + fun(V) when (V > {3,6,11}) -> + false; % OK - No skip + (V) when (V =:= {3,6,11}) -> + case string:trim(os:cmd("cat /etc/issue")) of + "Fedora release 16 " ++ _ -> % Stone age Fedora => Skip + true; + _ -> + false + end; + (V) when (V =:= {3,4,20}) -> + case string:trim(os:cmd("cat /etc/issue")) of + "Wind River Linux 5.0.1.0" ++ _ -> % *Old* Wind River => skip + true; + _ -> + false + end; + (V) when (V =:= {2,6,32}) -> + case string:trim(os:cmd("cat /etc/issue")) of + "Debian GNU/Linux 6.0 " ++ _ -> % Stone age Debian => Skip + true; + _ -> + false + end; + (V) when (V > {2,6,24}) -> + false; % OK - No skip + (V) when (V =:= {2,6,10}) -> + case string:trim(os:cmd("cat /etc/issue")) of + "MontaVista" ++ _ -> % Stone age MontaVista => Skip + %% The real problem is that the machine is *very* slow + true; + _ -> + false + end; + (_) -> + %% We are specifically checking for + %% a *really* old gento... + case string:find(string:strip(os:cmd("uname -a")), "gentoo") of + nomatch -> + false; + _ -> % Stone age gentoo => Skip + true + end + end, + DarwinVersionVerify = + fun(V) when (V > {9, 8, 0}) -> + %% This version is OK: No Skip + false; + (_V) -> + %% This version is *not* ok: Skip + true + end, + SkipWindowsOnVirtual = + %% fun() -> + %% SysMan = win_sys_info_lookup(system_manufacturer, HostInfo), + %% case string:to_lower(SysMan) of + %% "vmware" ++ _ -> + %% true; + %% _ -> + %% false + %% end + %% end, + fun() -> + %% The host has been replaced and the VM has been reinstalled + %% so for now we give it a chance... + false + end, + COND = [{unix, [{linux, LinuxVersionVerify}, + {darwin, DarwinVersionVerify}]}, + {win32, SkipWindowsOnVirtual}], + os_cond_skip(COND). + +os_cond_skip(any) -> + true; +os_cond_skip(Skippable) when is_list(Skippable) -> + os_cond_skip(Skippable, os:type()); +os_cond_skip(_Crap) -> + false. + +os_cond_skip(Skippable, {OsFam, OsName}) -> + os_cond_skip(Skippable, OsFam, OsName); +os_cond_skip(Skippable, OsFam) -> + os_cond_skip(Skippable, OsFam, undefined). + +os_cond_skip(Skippable, OsFam, OsName) -> + %% Check if the entire family is to be skipped + %% Example: [win32, unix] + case lists:member(OsFam, Skippable) of + true -> + true; + false -> + %% Example: [{unix, freebsd}] | [{unix, [freebsd, darwin]}] + case lists:keysearch(OsFam, 1, Skippable) of + {value, {OsFam, OsName}} -> + true; + {value, {OsFam, OsNames}} when is_list(OsNames) -> + %% OsNames is a list of: + %% [atom()|{atom(), function/0 | function/1}] + case lists:member(OsName, OsNames) of + true -> + true; + false -> + os_cond_skip_check(OsName, OsNames) + end; + {value, {OsFam, Check}} when is_function(Check, 0) -> + Check(); + {value, {OsFam, Check}} when is_function(Check, 1) -> + Check(os:version()); + _ -> + false + end + end. + +%% Performs a check via a provided fun with arity 0 or 1. +%% The argument is the result of os:version(). +os_cond_skip_check(OsName, OsNames) -> + case lists:keysearch(OsName, 1, OsNames) of + {value, {OsName, Check}} when is_function(Check, 0) -> + Check(); + {value, {OsName, Check}} when is_function(Check, 1) -> + Check(os:version()); + _ -> + false + end. + + + +%% --------------------------------------------------------------------------- + +proxy_call(F, Timeout, Default) + when is_function(F, 0) andalso is_integer(Timeout) andalso (Timeout > 0) -> + {P, M} = erlang:spawn_monitor(fun() -> exit(F()) end), + receive + {'DOWN', M, process, P, Reply} -> + Reply + after Timeout -> + erlang:demonitor(M, [flush]), + exit(P, kill), + Default + end. + + +%% --------------------------------------------------------------------------- + +f(F, A) -> + lists:flatten(io_lib:format(F, A)). + +%% This is only called if the length is at least 2 +colonize([L1, L2]) -> + L1 ++ ":" ++ L2; +colonize([H|T]) -> + H ++ ":" ++ colonize(T). + From 5e9b3804a4407f6fe50c2feaf5ff4925f2d97c09 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 14 May 2024 17:04:37 +0200 Subject: [PATCH 23/38] [diameter|test|app] Add [init|end]_per_suite --- lib/diameter/test/diameter_app_SUITE.erl | 18 ++++++++++++++++-- 1 file changed, 16 insertions(+), 2 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 027b816edc54..896dca711947 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -29,8 +29,13 @@ run/1]). %% common_test wrapping --export([suite/0, - all/0]). +-export([ + %% Framework functions + suite/0, + all/0, + init_per_suite/1, + end_per_suite/1 + ]). %% testcases -export([keys/1, @@ -80,6 +85,15 @@ all() -> xref, relup]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + %% =========================================================================== run() -> From 81fdc21c378eb2aa356e06223297818e09a8dda2 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 14 May 2024 17:51:10 +0200 Subject: [PATCH 24/38] [diameter|test] Misc cleanup --- lib/diameter/test/diameter_3xxx_SUITE.erl | 22 +++++++++++++++--- .../test/diameter_distribution_SUITE.erl | 11 +++++++++ lib/diameter/test/diameter_dpr_SUITE.erl | 23 +++++++++++++++---- lib/diameter/test/diameter_examples_SUITE.erl | 9 ++++++++ lib/diameter/test/diameter_relay_SUITE.erl | 12 +++++++++- lib/diameter/test/diameter_tls_SUITE.erl | 13 +++++++---- .../test/diameter_transport_SUITE.erl | 12 +++++++++- 7 files changed, 88 insertions(+), 14 deletions(-) diff --git a/lib/diameter/test/diameter_3xxx_SUITE.erl b/lib/diameter/test/diameter_3xxx_SUITE.erl index 2af853ea2723..d19f79c9c2e3 100644 --- a/lib/diameter/test/diameter_3xxx_SUITE.erl +++ b/lib/diameter/test/diameter_3xxx_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2013-2022. All Rights Reserved. +%% Copyright Ericsson AB 2013-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. @@ -31,9 +31,16 @@ run/1]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - traffic/1]). + init_per_suite/1, + end_per_suite/1, + + %% The test cases + traffic/1 + ]). %% internal -export([send_unknown_application/1, @@ -109,10 +116,19 @@ suite() -> all() -> [traffic]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + traffic(_Config) -> ?XL("traffic -> entry"), run(). + %% =========================================================================== tc() -> diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index d211d4740f86..22d3a0ee5b49 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -33,6 +33,8 @@ %% Framework functions suite/0, all/0, + init_per_suite/1, + end_per_suite/1, %% The test cases traffic/1 @@ -116,6 +118,14 @@ suite() -> all() -> [traffic]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + traffic(_Config) -> ?DL("traffic -> entry"), Res = traffic(), @@ -123,6 +133,7 @@ traffic(_Config) -> "~n Res: ~p", [Res]), Res. + %% =========================================================================== run() -> diff --git a/lib/diameter/test/diameter_dpr_SUITE.erl b/lib/diameter/test/diameter_dpr_SUITE.erl index e4b8788ed64e..5670dd9775c1 100644 --- a/lib/diameter/test/diameter_dpr_SUITE.erl +++ b/lib/diameter/test/diameter_dpr_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2012-2022. All Rights Reserved. +%% Copyright Ericsson AB 2012-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. @@ -29,14 +29,21 @@ 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 client/1, server/1, uncommon/1, transport/1, service/1, - application/1]). + application/1 + ]). %% internal -export([connect/1, @@ -101,6 +108,14 @@ suite() -> all() -> [client, server, uncommon, transport, service, application]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + -define(tc(Name), Name(_) -> ?DL("~w -> entry", [Name]), run([Name])). ?tc(client). @@ -141,7 +156,7 @@ run(Grp) -> _ = lists:foldl(fun(F,A) -> ?DL("run(~w) -> apply" "~n F: ~p" - "~n A: ~p", [F, A]), + "~n A: ~p", [Grp, F, A]), apply(?MODULE, F, [A]) end, [{group, Grp}], diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl index d258207cdb36..9ff45b35297c 100644 --- a/lib/diameter/test/diameter_examples_SUITE.erl +++ b/lib/diameter/test/diameter_examples_SUITE.erl @@ -33,6 +33,8 @@ %% Framework functions suite/0, all/0, + init_per_suite/1, + end_per_suite/1, %% The test cases dict/1, @@ -86,6 +88,13 @@ all() -> [dict, code]. +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + dict(Config) -> ?EL("dict -> entry with" "~n Config: ~p", [Config]), diff --git a/lib/diameter/test/diameter_relay_SUITE.erl b/lib/diameter/test/diameter_relay_SUITE.erl index c641d29b4fe9..701552d91409 100644 --- a/lib/diameter/test/diameter_relay_SUITE.erl +++ b/lib/diameter/test/diameter_relay_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. @@ -42,6 +42,8 @@ %% Framework functions suite/0, all/0, + init_per_suite/1, + end_per_suite/1, %% The test cases parallel/1 @@ -117,6 +119,14 @@ suite() -> all() -> [parallel]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + parallel(_Config) -> ?RL("parallel -> entry"), Res = run(), diff --git a/lib/diameter/test/diameter_tls_SUITE.erl b/lib/diameter/test/diameter_tls_SUITE.erl index e0531a276b13..6f21ceafce28 100644 --- a/lib/diameter/test/diameter_tls_SUITE.erl +++ b/lib/diameter/test/diameter_tls_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2010-2023. 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. @@ -135,20 +135,22 @@ all() -> %% Shouldn't really have to know about crypto here but 'ok' from %% ssl:start() isn't enough to guarantee that TLS is available. init_per_suite(Config) -> + Config2 = ?DUTIL:init_per_suite(Config), try - [] == (catch make_certs(dir(Config))) + [] == (catch make_certs(dir(Config2))) orelse throw({?MODULE, no_certs}), ok == crypto:start() orelse throw({?MODULE, no_crypto}), ok == ssl:start() orelse throw({?MODULE, no_ssl}), - Config + Config2 catch {?MODULE, E} -> {skip, E} end. -end_per_suite(_Config) -> +end_per_suite(Config) -> ssl:stop(), - crypto:stop(). + crypto:stop(), + ?DUTIL:end_per_suite(Config). parallel(Config) -> ?TL("parallel -> entry"), @@ -160,6 +162,7 @@ parallel(Config) -> dir(Config) -> proplists:get_value(priv_dir, Config). + %% =========================================================================== run() -> diff --git a/lib/diameter/test/diameter_transport_SUITE.erl b/lib/diameter/test/diameter_transport_SUITE.erl index e86270d7fbbd..578871e95377 100644 --- a/lib/diameter/test/diameter_transport_SUITE.erl +++ b/lib/diameter/test/diameter_transport_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. @@ -33,6 +33,8 @@ %% Framework functions suite/0, all/0, + init_per_suite/1, + end_per_suite/1, %% The test cases parallel/1 @@ -96,6 +98,14 @@ suite() -> all() -> [parallel]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + parallel(_) -> ?TL("parallel -> entry"), Res = run(), From ba6b466d819b324835950507219e970c1772ece8 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 17 May 2024 12:03:46 +0200 Subject: [PATCH 25/38] [diameter|test|distribution] Tweaked test case Attempt to calculate the diameter call timeout depending on the "factor" (instead of just use the default timeout of 5 secs). --- .../test/diameter_distribution_SUITE.erl | 98 ++++++++++++------- 1 file changed, 62 insertions(+), 36 deletions(-) diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index 22d3a0ee5b49..d28cda4cb73a 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -66,7 +66,7 @@ %% =========================================================================== -define(DL(F), ?DL(F, [])). --define(DL(F, A), ?LOG("DDISTS", F, A)). +-define(DL(F, A), ?LOG("DDISTRS", F, A)). -define(CLIENT, 'CLIENT'). -define(SERVER, 'SERVER'). @@ -126,9 +126,10 @@ end_per_suite(Config) -> ?DUTIL:end_per_suite(Config). -traffic(_Config) -> +traffic(Config) -> ?DL("traffic -> entry"), - Res = traffic(), + Factor = dia_factor(Config), + Res = do_traffic(Factor), ?DL("traffic -> done when" "~n Res: ~p", [Res]), Res. @@ -137,27 +138,27 @@ traffic(_Config) -> %% =========================================================================== run() -> - [] = ?DUTIL:run([{fun traffic/0, 60000}]). + [] = ?RUN([{fun() -> do_traffic(1) end, 60000}]). %% process for linked peers to die with %% traffic/0 -traffic() -> - ?DL("traffic -> make sure we have distro"), +do_traffic(Factor) -> + ?DL("do_traffic -> make sure we have distro"), true = is_alive(), %% need distribution for peer nodes - ?DL("traffic -> get nodes"), + ?DL("do_traffic -> get nodes"), Nodes = enslave(), - ?DL("traffic -> ping nodes"), + ?DL("do_traffic -> ping nodes"), [] = ping(Nodes), %% drop client node - ?DL("traffic -> start nodes"), + ?DL("do_traffic -> start nodes"), [] = start(Nodes), - ?DL("traffic -> connect nodes"), + ?DL("do_traffic -> connect nodes"), [_] = connect(Nodes), - ?DL("traffic -> send (to) nodes"), - [] = send(Nodes), - ?DL("traffic -> stop nodes"), + ?DL("do_traffic -> send (to) nodes"), + [] = send(Nodes, Factor), + ?DL("do_traffic -> stop nodes"), [] = stop(Nodes), - ?DL("traffic -> done"), + ?DL("do_traffic -> done"), ok. %% enslave/0 @@ -254,10 +255,10 @@ peers(client2) -> nodes(). %% nodes. connect({?SERVER, _, []}) -> - [_LRef = ?DUTIL:listen(?SERVER, tcp)]; + [_LRef = ?LISTEN(?SERVER, tcp)]; connect({?CLIENT, [{Node, _} | _], [LRef] = Acc}) -> - ?DUTIL:connect(?CLIENT, tcp, {Node, LRef}), + ?CONNECT(?CLIENT, tcp, {Node, LRef}), Acc; connect(Nodes) -> @@ -269,47 +270,48 @@ connect(Nodes) -> %% =========================================================================== -%% send/1 +%% send/2 -send(Nodes) -> - ?RUN([[fun send/2, Nodes, T] +send(Nodes, Factor) -> + ?RUN([[fun send/3, Nodes, T, Factor] || T <- [local, remote, timeout, failover]]). -%% send/2 +%% send/3 %% Send a request from the first client node, using a the local %% transport. -send(Nodes, local) -> +send(Nodes, local, Factor) -> ?DL("send(local) -> entry - expect success (~p)", [?SUCCESS]), #diameter_base_STA{'Result-Code' = ?SUCCESS} - = send(Nodes, 0, str(?LOGOUT)), + = send(Nodes, 0, str(?LOGOUT), Factor), ?DL("send(local) -> success (=success)"), ok; %% Send a request from the first client node, using a transport on the %% another node. -send(Nodes, remote) -> +send(Nodes, remote, Factor) -> ?DL("send(remote) -> entry - expect success (~p)", [?SUCCESS]), #diameter_base_STA{'Result-Code' = ?SUCCESS} - = send(Nodes, 1, str(?LOGOUT)), + = send(Nodes, 1, str(?LOGOUT), Factor), ?DL("send(remote) -> success (=success)"), ok; %% Send a request that the server discards. -send(Nodes, timeout) -> +send(Nodes, timeout, Factor) -> ?DL("send(timeout) -> entry - expect timeout"), - {error, timeout} = send(Nodes, 1, str(?TIMEOUT)), + {error, timeout} = send(Nodes, 1, str(?TIMEOUT), Factor), ?DL("send(timeout) -> success (=timeout)"), ok; %% Send a request that causes the server to take the transport down. -send(Nodes, failover) -> +send(Nodes, failover, Factor) -> ?DL("send(failover) -> entry - expect busy (~p)", [?BUSY]), #'diameter_base_answer-message'{'Result-Code' = ?BUSY} - = send(Nodes, 2, str(?MOVED)), + = send(Nodes, 2, str(?MOVED), Factor), ?DL("send(failover) -> success (=busy)"), ok. + %% =========================================================================== str(Cause) -> @@ -317,25 +319,30 @@ str(Cause) -> 'Auth-Application-Id' = ?DICT:id(), 'Termination-Cause' = Cause}. -%% send/3 +%% send/4 -send([_, {Node, _} | _], Where, Req) -> +send([_, {Node, _} | _], Where, Req, Factor) -> ?DL("send -> make rpc call to node ~p", [Node]), - rpc:call(Node, ?MODULE, call, [{Where, Req}]). + rpc:call(Node, ?MODULE, call, [{Where, Req, Factor}]). %% call/1 -call({Where, Req}) -> - ?DL("call -> entry with" - "~n Where: ~p" - "~n Req: ~p", [Where, Req]), - diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}]). +call({Where, Req, Factor}) -> + Timeout = timeout(Factor), + ?DL("call -> make diameter call with" + "~n Where: ~p" + "~n Req: ~p" + "~nwhen" + "~n Timeout: ~w (~w)", [Where, Req, Timeout, Factor]), + diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}, + {timeout, Timeout}]). %% sname/0 sname() -> ?A(hd(string:tokens(?L(node()), "@"))). + %% =========================================================================== %% diameter callbacks @@ -428,3 +435,22 @@ fail(0, _) -> %% sent from the originating node ... fail(_, TPid) -> %% ... or through a remote node: force failover exit(TPid, kill), discard. + + +%% =========================================================================== + +-define(CALL_TO_DEFAULT, 5000). +timeout(Factor) when (Factor > 0) andalso (Factor =< 20) -> + (Factor - 1) * 500 + ?CALL_TO_DEFAULT; +timeout(Factor) when (Factor > 0) -> + 3*?CALL_TO_DEFAULT. % Max at 15 seconds + + +%% =========================================================================== + +dia_factor(Config) -> + config_lookup(?FUNCTION_NAME, Config). + +config_lookup(Key, Config) -> + {value, {Key, Value}} = lists:keysearch(Key, 1, Config), + Value. From d42b814e1a419f4a1cfd0408250bd234d76f250e Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 17 May 2024 17:11:38 +0200 Subject: [PATCH 26/38] [diameter|test|dist] Tweaked test case(s) Add diameter call timeout (other then default). --- lib/diameter/test/diameter_dist_SUITE.erl | 117 +++++++++++++++++----- 1 file changed, 93 insertions(+), 24 deletions(-) diff --git a/lib/diameter/test/diameter_dist_SUITE.erl b/lib/diameter/test/diameter_dist_SUITE.erl index 81d2dfbf3647..fa72c683d890 100644 --- a/lib/diameter/test/diameter_dist_SUITE.erl +++ b/lib/diameter/test/diameter_dist_SUITE.erl @@ -29,9 +29,16 @@ -export([run/0]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, - traffic/1]). + init_per_suite/1, + end_per_suite/1, + + %% The test cases + traffic/1 + ]). %% diameter callbacks -export([peer_up/3, @@ -52,9 +59,13 @@ -include("diameter.hrl"). -include("diameter_gen_base_rfc6733.hrl"). +-include("diameter_util.hrl"). + + %% =========================================================================== --define(util, diameter_util). +-define(DL(F), ?DL(F, [])). +-define(DL(F, A), ?LOG("DDISTS", F, A)). -define(CLIENT, 'CLIENT'). -define(SERVER, 'SERVER'). @@ -105,26 +116,47 @@ suite() -> all() -> [traffic]. -traffic(_Config) -> - run(). +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(Config) -> + ?DUTIL:end_per_suite(Config). + + +traffic(Config) -> + ?DL("traffic -> entry"), + Factor = dia_factor(Config), + Res = do_traffic(Factor), + ?DL("traffic -> done when" + "~n Res: ~p", [Res]), + Res. + %% =========================================================================== %% run/0 run() -> - [] = ?util:run([{fun traffic/0, 60000}]). + [] = ?RUN([{fun() -> do_traffic(1) end, 60000}]). %% process for linked peers to die with %% traffic/0 -traffic() -> +do_traffic(Factor) -> + ?DL("do_traffic -> check we have distribution"), true = is_alive(), %% need distribution for peer nodes + ?DL("do_traffic -> get nodes"), Nodes = enslave(), + ?DL("do_traffic -> ping nodes (except client node)"), [] = ping(lists:droplast(Nodes)), %% drop client node + ?DL("do_traffic -> start nodes"), [] = start(Nodes), + ?DL("do_traffic -> connect nodes"), ok = connect(Nodes), - ok = send(Nodes). + ?DL("do_traffic -> send (to) nodes"), + ok = send(Nodes, Factor), + ?DL("do_traffic -> done"), + ok. %% enslave/1 %% @@ -138,8 +170,15 @@ enslave() -> [{N,S} || {M,S} <- ?NODES, N <- [start(M, Args)]]. start(Name, Args) -> - {ok, _, Node} = ?util:peer(#{name => Name, args => Args}), - Node. + case ?PEER(#{name => Name, args => Args}) of + {ok, _, Node} -> + Node; + {error, Reason} -> + ?DL("Failed starting node ~p" + "~n Reason: ~p", [Name, Reason]), + exit({skip, {failed_starting_node, Name, Reason}}) + end. + %% ping/1 %% @@ -211,14 +250,14 @@ origin(Server) -> connect({?SERVER, [{Node, _} | _], []}) when Node == node() -> %% server0 - [_LRef = ?util:listen(?SERVER, tcp)]; + [_LRef = ?LISTEN(?SERVER, tcp)]; connect({?SERVER, _, [_] = Acc}) -> %% server[12]: register to receive requests ok = diameter_dist:attach([?SERVER]), Acc; connect({?CLIENT, [{Node, _} | _], [LRef]}) -> - ?util:connect(?CLIENT, tcp, {Node, LRef}), + ?CONNECT(?CLIENT, tcp, {Node, LRef}), ok; connect(Nodes) -> @@ -231,17 +270,18 @@ connect(Nodes) -> %% =========================================================================== %% traffic testcases -%% send/1 +%% send/2 %% %% Send 100 requests and ensure the node name sent as User-Name isn't %% the node terminating transport. -send(Nodes) -> - send(Nodes, 100, dict:new()). +send(Nodes, Factor) -> + send(Nodes, 100, dict:new(), Factor). %% send/2 -send(Nodes, 0, Dict) -> +send(Nodes, 0, Dict, _Factor) -> + ?DL("send(0) -> entry - verify stats"), [{Server0, _} | _] = Nodes, Node = atom_to_binary(Server0, utf8), {false, _} = {dict:is_key(Node, Dict), dict:to_list(Dict)}, @@ -256,14 +296,17 @@ send(Nodes, 0, Dict) -> {[{send, 0, 100, 2001}], _} = {[{D,R,N,C} || {{{0,275,R}, D, {'Result-Code', C}}, N} <- Stats], Stats}, + ?DL("send(0) -> done"), ok; -send(Nodes, N, Dict) -> +send(Nodes, N, Dict, Factor) -> + ?DL("send(~w) -> entry", [N]), #diameter_base_STA{'Result-Code' = ?SUCCESS, 'User-Name' = [ServerNode]} - = send(Nodes, str(?LOGOUT)), + = send(Nodes, str(?LOGOUT), Factor), true = is_binary(ServerNode), - send(Nodes, N-1, dict:update_counter(ServerNode, 1, Dict)). + send(Nodes, N-1, dict:update_counter(ServerNode, 1, Dict), Factor). + %% =========================================================================== @@ -272,22 +315,29 @@ str(Cause) -> 'Auth-Application-Id' = ?DICT:id(), 'Termination-Cause' = Cause}. -%% send/2 +%% send/3 -send(Nodes, Req) -> +send(Nodes, Req, Factor) -> {Node, _} = lists:last(Nodes), - rpc:call(Node, ?MODULE, call, [Req]). + ?DL("send -> make rpc call (to call) to node ~p", [Node]), + rpc:call(Node, ?MODULE, call, [{Req, Factor}]). %% call/1 -call(Req) -> - diameter:call(?CLIENT, ?DICT, Req, []). +call({Req, Factor}) -> + Timeout = timeout(Factor), + ?DL("call -> make diameter call with" + "~n Req: ~p" + "~nwhen" + "~n Timeout: ~w (~w)", [Req, Timeout, Factor]), + diameter:call(?CLIENT, ?DICT, Req, [{timeout, Timeout}]). %% sname/0 sname() -> ?A(hd(string:tokens(?L(node()), "@"))). + %% =========================================================================== %% diameter callbacks @@ -347,3 +397,22 @@ handle_request(Pkt, ?SERVER, {_, Caps}) -> 'Origin-Host' = OH, 'Origin-Realm' = OR, 'User-Name' = [atom_to_binary(node(), utf8)]}}. + + +%% =========================================================================== + +-define(CALL_TO_DEFAULT, 5000). +timeout(Factor) when (Factor > 0) andalso (Factor =< 20) -> + (Factor - 1) * 500 + ?CALL_TO_DEFAULT; +timeout(Factor) when (Factor > 0) -> + 3*?CALL_TO_DEFAULT. % Max at 15 seconds + + +%% =========================================================================== + +dia_factor(Config) -> + config_lookup(?FUNCTION_NAME, Config). + +config_lookup(Key, Config) -> + {value, {Key, Value}} = lists:keysearch(Key, 1, Config), + Value. From de9001f940b341825d06f38eea653f620b6d7b8f Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 22 May 2024 08:26:05 +0200 Subject: [PATCH 27/38] [diameter|test|transport] More test case tweaking --- lib/diameter/test/diameter_transport_SUITE.erl | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/lib/diameter/test/diameter_transport_SUITE.erl b/lib/diameter/test/diameter_transport_SUITE.erl index 578871e95377..1d9561c8929b 100644 --- a/lib/diameter/test/diameter_transport_SUITE.erl +++ b/lib/diameter/test/diameter_transport_SUITE.erl @@ -204,18 +204,25 @@ reconnect({listen, Ref}) -> ?TL("reconnect(listen) -> entry with" "~n Ref: ~p", [Ref]), SvcName = make_ref(), + ?TL("reconnect(listen) -> start service (~p)", [SvcName]), ok = start_service(SvcName), + ?TL("reconnect(listen) -> connect"), LRef = ?LISTEN(SvcName, tcp, [{watchdog_timer, 6000}]), + ?TL("reconnect(listen) -> wait"), [_] = diameter_reg:wait({diameter_tcp, listener, {LRef, '_'}}), + ?TL("reconnect(listen) -> register new transport"), true = diameter_reg:add_new({?MODULE, Ref, LRef}), %% Wait for partner to request transport death. + ?TL("reconnect(listen) -> abort: await (request for) transport death"), TPid = abort(SvcName, LRef, Ref), %% Kill transport to force the peer to reconnect. + ?TL("reconnect(listen) -> kill transport"), exit(TPid, kill), %% Wait for the partner again. + ?TL("reconnect(listen) -> abort: wait for partner again"), Res = abort(SvcName, LRef, Ref), ?TL("reconnect(listen) -> done when" @@ -227,25 +234,35 @@ reconnect({connect, Ref}) -> "~n Ref: ~p", [Ref]), SvcName = make_ref(), + ?TL("reconnect(connect) -> subscribe"), true = diameter:subscribe(SvcName), + ?TL("reconnect(connect) -> start service (~p)", [SvcName]), ok = start_service(SvcName), + ?TL("reconnect(connect) -> wait"), [{{_, _, LRef}, Pid}] = diameter_reg:wait({?MODULE, Ref, '_'}), + ?TL("reconnect(connect) -> connect"), CRef = ?CONNECT(SvcName, tcp, LRef, [{connect_timer, 2000}, {watchdog_timer, 6000}]), %% Tell partner to kill transport after seeing that there are no %% reconnection attempts. + ?TL("reconnect(connect) -> abort (kill transport)"), abort(SvcName, Pid, Ref), %% Transport goes down and is reestablished. + ?TL("reconnect(connect) -> await transport down"), ?RECV(#diameter_event{service = SvcName, info = {down, CRef, _, _}}), + ?TL("reconnect(connect) -> await transport reconnect"), ?RECV(#diameter_event{service = SvcName, info = {reconnect, CRef, _}}), + ?TL("reconnect(connect) -> await transport up"), ?RECV(#diameter_event{service = SvcName, info = {up, CRef, _, _, _}}), %% Kill again. + ?TL("reconnect(connect) -> abort (kill transport again)"), abort(SvcName, Pid, Ref), %% Wait for partner to die. + ?TL("reconnect(connect) -> await partner death"), MRef = erlang:monitor(process, Pid), Res = ?RECV({'DOWN', MRef, process, _, _}), From 5de1dc369f30c7a52b3963aa52967d137aae2d4d Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Fri, 24 May 2024 10:46:15 +0200 Subject: [PATCH 28/38] [diameter|test|app] Calculating timeouts --- lib/diameter/test/diameter_app_SUITE.erl | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 896dca711947..0cdf42ebf62c 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -74,7 +74,7 @@ %% =========================================================================== suite() -> - [{timetrap, {seconds, 20}}]. + [{timetrap, {seconds, 120}}]. all() -> [keys, @@ -108,10 +108,21 @@ run(List) -> end. run(Config, List) -> + Timeout = factor2timeout(Config, 10000), [{application, diameter, App}] = ?CONSULT(diameter, app), - ?RUN([{{?MODULE, F, [{App, Config}]}, 10000} || F <- List]). + ?RUN([{{?MODULE, F, [{App, Config}]}, Timeout} || F <- List]). +factor2timeout(Config, BaseTime) -> + Key = dia_factor, + case lists:keysearch(Key, 1, Config) of + {value, {Key, Factor}} when (Factor > 0) -> + BaseTime + (((Factor-1)*BaseTime) div 10); + _ -> + BaseTime + end. + + %% =========================================================================== %% # keys/1 %% From ae44d0a24cb36c03d68e398226aea3ae1457e254 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 27 May 2024 10:29:14 +0200 Subject: [PATCH 29/38] [diameter|test] Skip xref test case if factor too large --- lib/diameter/test/diameter_app_SUITE.erl | 28 +++++++++++++++++++++++- 1 file changed, 27 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_app_SUITE.erl b/lib/diameter/test/diameter_app_SUITE.erl index 0cdf42ebf62c..0d7bae2ede92 100644 --- a/lib/diameter/test/diameter_app_SUITE.erl +++ b/lib/diameter/test/diameter_app_SUITE.erl @@ -34,7 +34,9 @@ suite/0, all/0, init_per_suite/1, - end_per_suite/1 + end_per_suite/1, + init_per_testcase/2, + end_per_testcase/2 ]). %% testcases @@ -94,6 +96,29 @@ end_per_suite(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(xref = Case, Config) when is_list(Config) -> + ?AL("init_per_testcase(~w) -> check factor", [Case]), + Key = dia_factor, + case lists:keysearch(Key, 1, Config) of + {value, {Key, Factor}} when (Factor > 10) -> + ?AL("init_per_testcase(~w) -> Too slow (~w) => SKIP", + [Case, Factor]), + {skip, {machine_too_slow, Factor}}; + _ -> + ?AL("init_per_testcase(~w) -> run test", [Case]), + Config + end; +init_per_testcase(Case, Config) -> + ?AL("init_per_testcase(~w) -> entry", [Case]), + Config. + + +end_per_testcase(Case, Config) when is_list(Config) -> + ?AL("end_per_testcase(~w) -> entry", [Case]), + Config. + + %% =========================================================================== run() -> @@ -109,6 +134,7 @@ run(List) -> run(Config, List) -> Timeout = factor2timeout(Config, 10000), + ?AL("run -> use Timeout: ~w", [Timeout]), [{application, diameter, App}] = ?CONSULT(diameter, app), ?RUN([{{?MODULE, F, [{App, Config}]}, Timeout} || F <- List]). From fca2d3946b7fee7f7c69e88c488e80c8d115a1c8 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 28 May 2024 09:31:22 +0200 Subject: [PATCH 30/38] [diameter|test] Tweaked test case(s) Try to measure (diameter) call time. We seem to have timeouts even though timeout time is long enough (timeout after a couple of msec when timeout is several secs). --- .../test/diameter_distribution_SUITE.erl | 29 +++++++++++++++---- 1 file changed, 23 insertions(+), 6 deletions(-) diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index d28cda4cb73a..d93f9ef9d0f1 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -321,21 +321,38 @@ str(Cause) -> %% send/4 +%% erlang:system_time(millisecond) + send([_, {Node, _} | _], Where, Req, Factor) -> ?DL("send -> make rpc call to node ~p", [Node]), - rpc:call(Node, ?MODULE, call, [{Where, Req, Factor}]). + case rpc:call(Node, ?MODULE, call, [{Where, Req, Factor}]) of + {Result, T1, T2, Timeout} when is_integer(T1) andalso is_integer(T2) -> + ?DL("request completed:" + "~n Time: ~w msec" + "~n Timeout: ~w msec" + "~n Result: ~p", [T2-T1, Timeout, Result]), + Result; + {badrpc, Reason} -> + ?DL("rpc failed:" + "~n Reason: ~p", [Reason]), + ct:fail({rpc_call_failed, Node, Where, Req, Reason}) + end. %% call/1 call({Where, Req, Factor}) -> Timeout = timeout(Factor), ?DL("call -> make diameter call with" - "~n Where: ~p" - "~n Req: ~p" + "~n (own) Node: ~p" + "~n Where: ~p" + "~n Req: ~p" "~nwhen" - "~n Timeout: ~w (~w)", [Where, Req, Timeout, Factor]), - diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}, - {timeout, Timeout}]). + "~n Timeout: ~w (~w)", [node(), Where, Req, Timeout, Factor]), + T1 = erlang:system_time(millisecond), + Result = diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}, + {timeout, Timeout}]), + T2 = erlang:system_time(millisecond), + {Result, T1, T2, Timeout}. %% sname/0 From 61e1e0853117961ca625446bc195d19526971dd4 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 3 Jun 2024 11:31:49 +0200 Subject: [PATCH 31/38] [diameter|test] Tweaked the dpr suite --- lib/diameter/test/diameter_dpr_SUITE.erl | 8 +++++++- lib/diameter/test/diameter_util.erl | 24 ++++++++++++++++++++---- 2 files changed, 27 insertions(+), 5 deletions(-) diff --git a/lib/diameter/test/diameter_dpr_SUITE.erl b/lib/diameter/test/diameter_dpr_SUITE.erl index 5670dd9775c1..bf1e4904872e 100644 --- a/lib/diameter/test/diameter_dpr_SUITE.erl +++ b/lib/diameter/test/diameter_dpr_SUITE.erl @@ -216,14 +216,20 @@ service(?CLIENT = Svc, _) -> %% send_dpr/1 send_dpr(Config) -> + ?DL("~w -> entry with" + "~n Config: ~p" + "~n => try listen", [?FUNCTION_NAME, Config]), LRef = ?LISTEN(?SERVER, tcp), + ?DL("~w -> try listen", [?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: " + ?DL("send_dpr -> no connections found: " "~n Svc: ~p" "~n Svc info: ~p" "~n Services: ~p", diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index d247f0510e22..15921d56ac15 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -451,9 +451,17 @@ listen(SvcName, Prot) -> listen(SvcName, Prot, []). listen(SvcName, Prot, Opts) -> + ?UL("~w -> entry with" + "~n SvcName: ~p" + "~n Prot: ~p" + "~n Opts: ~p" + "~n => verisfy service name", [?FUNCTION_NAME, SvcName, Prot, Opts]), SvcName = diameter:service_info(SvcName, name), %% assert + ?UL("~w -> add transport", [?FUNCTION_NAME]), Ref = add_transport(SvcName, {listen, opts(Prot, listen) ++ Opts}), + ?UL("~w -> verify transport (~p)", [?FUNCTION_NAME, Ref]), true = transport(SvcName, Ref), %% assert + ?UL("~w -> done", [?FUNCTION_NAME]), Ref. %% --------------------------------------------------------------------------- @@ -466,13 +474,14 @@ connect(Client, Prot, LRef) -> connect(Client, Prot, LRef, []). connect(Client, ProtOpts, LRef, Opts) -> - ?UL("connect -> entry with" + ?UL("~w -> entry with" "~n Client: ~p" "~n ProtOpts: ~p" "~n LRef: ~p" - "~n Opts: ~p", [Client, ProtOpts, LRef, Opts]), + "~n Opts: ~p", [?FUNCTION_NAME, Client, ProtOpts, LRef, Opts]), Prot = head(ProtOpts), [PortNr] = lport(Prot, LRef), + ?UL("~w -> verify service name", [?FUNCTION_NAME]), case diameter:service_info(Client, name) of Client -> % assert ok; @@ -504,12 +513,16 @@ connect(Client, ProtOpts, LRef, Opts) -> diameter:service_info(Client, statistics)]), ct:fail({wrong_name, Client, WrongName}) end, + ?UL("~w -> subscribe", [?FUNCTION_NAME]), true = diameter:subscribe(Client), + ?UL("~w -> add transport", [?FUNCTION_NAME]), Ref = add_transport(Client, {connect, opts(ProtOpts, PortNr) ++ Opts}), + ?UL("~w -> verify transport (~p)", [?FUNCTION_NAME, Ref]), true = transport(Client, Ref), %% assert - + ?UL("~w -> await up", [?FUNCTION_NAME]), diameter_lib:for_n(fun(_) -> ok = up(Client, Ref, Prot, PortNr) end, proplists:get_value(pool_size, Opts, 1)), + ?UL("~w -> done", [?FUNCTION_NAME]), Ref. head([T|_]) -> @@ -519,7 +532,10 @@ head(T) -> up(Client, Ref, Prot, PortNr) -> receive - {diameter_event, Client, {up, Ref, _, _, _}} -> ok + {diameter_event, Client, {up, Ref, _, _, _}} -> + ?UL("~w -> received 'up' event regarding ~p for service ~p", + [?FUNCTION_NAME, Ref, Client]), + ok after 10000 -> {Client, Prot, PortNr, process_info(self(), messages)} end. From a2b7c68b6433d25653a037a24ce6419a94aea121 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 3 Jun 2024 11:42:51 +0200 Subject: [PATCH 32/38] [diameter|test] Add factor check for dict test case of examples suite --- lib/diameter/test/diameter_examples_SUITE.erl | 27 +++++++++++++++++++ 1 file changed, 27 insertions(+) diff --git a/lib/diameter/test/diameter_examples_SUITE.erl b/lib/diameter/test/diameter_examples_SUITE.erl index 9ff45b35297c..99297e051709 100644 --- a/lib/diameter/test/diameter_examples_SUITE.erl +++ b/lib/diameter/test/diameter_examples_SUITE.erl @@ -35,6 +35,8 @@ all/0, init_per_suite/1, end_per_suite/1, + init_per_testcase/2, + end_per_testcase/2, %% The test cases dict/1, @@ -95,6 +97,31 @@ end_per_suite(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(dict = Case, Config) when is_list(Config) -> + ?EL("init_per_testcase(~w) -> check factor", [Case]), + Key = dia_factor, + case lists:keysearch(Key, 1, Config) of + {value, {Key, Factor}} when (Factor > 10) -> + ?EL("init_per_testcase(~w) -> Too slow (~w) => SKIP", + [Case, Factor]), + {skip, {machine_too_slow, Factor}}; + _ -> + ?EL("init_per_testcase(~w) -> run test", [Case]), + Config + end; +init_per_testcase(Case, Config) -> + ?EL("init_per_testcase(~w) -> entry", [Case]), + Config. + + +end_per_testcase(Case, Config) when is_list(Config) -> + ?EL("end_per_testcase(~w) -> entry", [Case]), + Config. + + +%% =========================================================================== + dict(Config) -> ?EL("dict -> entry with" "~n Config: ~p", [Config]), From 40d068db79a4eae300d5487b7853b7797ab4fbe9 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 4 Jun 2024 11:12:00 +0200 Subject: [PATCH 33/38] [diameter|test] Tweak distro (suite) test case(s) --- lib/diameter/test/diameter_distribution_SUITE.erl | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index d93f9ef9d0f1..342a4a0e6084 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -352,6 +352,10 @@ call({Where, Req, Factor}) -> Result = diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}, {timeout, Timeout}]), T2 = erlang:system_time(millisecond), + ?DL("call -> diameter call ended with" + "~n Result: ~p" + "~nwhen" + "~n T2-T1: ~w (~w - ~w)", [Result, T2 - T1, T2, T1]), {Result, T1, T2, Timeout}. %% sname/0 @@ -419,7 +423,9 @@ handle_answer(Pkt, _Req, ?CLIENT, _Peer, {_, client0}) -> %% handle_error/5 -handle_error(Reason, _Req, ?CLIENT, _Peer, {_, client0}) -> +handle_error(Reason, _Req, ?CLIENT = Svc, _Peer, {_, client0}) -> + ?DL("~w(~p) -> entry with" + "~n Reason: ~p", [?FUNCTION_NAME, Svc, Reason]), {error, Reason}. %% handle_request/3 From 1ecba538d5aa4e8bddc1802205283526fdea10a3 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 4 Jun 2024 11:13:04 +0200 Subject: [PATCH 34/38] [diameter|test] Tweak 3xxx (suite) test case(s) --- lib/diameter/test/diameter_3xxx_SUITE.erl | 66 ++++++++++++++++------- 1 file changed, 48 insertions(+), 18 deletions(-) diff --git a/lib/diameter/test/diameter_3xxx_SUITE.erl b/lib/diameter/test/diameter_3xxx_SUITE.erl index d19f79c9c2e3..a6f985e6b762 100644 --- a/lib/diameter/test/diameter_3xxx_SUITE.erl +++ b/lib/diameter/test/diameter_3xxx_SUITE.erl @@ -240,26 +240,56 @@ stats(?CLIENT, E, rfc3588, L) {{{0,275,0},recv,{'Result-Code',5005}},1}] = L; -stats(?SERVER, E, rfc3588, L) +stats(?SERVER = Svc, E, rfc3588 = RFC, L) when E == answer; E == answer_3xxx -> - [{{{unknown,0},send},2}, - {{{unknown,1},recv},1}, - {{{0,257,0},send},1}, - {{{0,257,1},recv},1}, - {{{0,275,0},send},6}, - {{{0,275,1},recv},8}, - {{{unknown,0},send,{'Result-Code',3001}},1}, - {{{unknown,0},send,{'Result-Code',3007}},1}, - {{{unknown,1},recv,error},1}, - {{{0,257,0},send,{'Result-Code',2001}},1}, - {{{0,275,0},send,{'Result-Code',2001}},1}, - {{{0,275,0},send,{'Result-Code',3008}},2}, - {{{0,275,0},send,{'Result-Code',3999}},1}, - {{{0,275,0},send,{'Result-Code',5002}},1}, - {{{0,275,0},send,{'Result-Code',5005}},1}, - {{{0,275,1},recv,error},5}] - = L; + %% [{{{unknown,0},send},2}, + %% {{{unknown,1},recv},1}, + %% {{{0,257,0},send},1}, + %% {{{0,257,1},recv},1}, + %% {{{0,275,0},send},6}, + %% {{{0,275,1},recv},8}, + %% {{{unknown,0},send,{'Result-Code',3001}},1}, + %% {{{unknown,0},send,{'Result-Code',3007}},1}, + %% {{{unknown,1},recv,error},1}, + %% {{{0,257,0},send,{'Result-Code',2001}},1}, + %% {{{0,275,0},send,{'Result-Code',2001}},1}, + %% {{{0,275,0},send,{'Result-Code',3008}},2}, + %% {{{0,275,0},send,{'Result-Code',3999}},1}, + %% {{{0,275,0},send,{'Result-Code',5002}},1}, + %% {{{0,275,0},send,{'Result-Code',5005}},1}, + %% {{{0,275,1},recv,error},5}] + %% = L; + ?XL("~w(~p, ~w) -> (attempt to) verify answer: " + "~n E: ~p" + "~n L: ~p", [?FUNCTION_NAME, Svc, RFC, E, L]), + Expected = [{{{unknown,0},send},2}, + {{{unknown,1},recv},1}, + {{{0,257,0},send},1}, + {{{0,257,1},recv},1}, + {{{0,275,0},send},6}, + {{{0,275,1},recv},8}, + {{{unknown,0},send,{'Result-Code',3001}},1}, + {{{unknown,0},send,{'Result-Code',3007}},1}, + {{{unknown,1},recv,error},1}, + {{{0,257,0},send,{'Result-Code',2001}},1}, + {{{0,275,0},send,{'Result-Code',2001}},1}, + {{{0,275,0},send,{'Result-Code',3008}},2}, + {{{0,275,0},send,{'Result-Code',3999}},1}, + {{{0,275,0},send,{'Result-Code',5002}},1}, + {{{0,275,0},send,{'Result-Code',5005}},1}, + {{{0,275,1},recv,error},5}], + case L of + Expected -> + ?XL("~w(~w) -> ok", [?FUNCTION_NAME, RFC]), + L; + _ -> + ?XL("~w(~w, ~w) -> wrong: " + "~n L -- Expected: ~p" + "~n Expected -- L: ~p", + [?FUNCTION_NAME, Svc, RFC, L -- Expected, Expected -- L]), + exit({wrong_answer, Svc, E, RFC}) + end; stats(?CLIENT, answer, rfc6733, L) -> [{{{unknown,0},recv},2}, From bf6caeaf03a9d3b9a68cb5f3b7d63586ea197d28 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Mon, 10 Jun 2024 15:00:51 +0200 Subject: [PATCH 35/38] [diameter|test] Tweaked codec suite --- lib/diameter/test/diameter_codec_SUITE.erl | 109 ++++++++++++++++++--- 1 file changed, 95 insertions(+), 14 deletions(-) diff --git a/lib/diameter/test/diameter_codec_SUITE.erl b/lib/diameter/test/diameter_codec_SUITE.erl index f92b360dabc4..8b37e40c6083 100644 --- a/lib/diameter/test/diameter_codec_SUITE.erl +++ b/lib/diameter/test/diameter_codec_SUITE.erl @@ -33,18 +33,32 @@ run/1]). %% common_test wrapping --export([suite/0, +-export([ + %% Framework functions + suite/0, all/0, + init_per_suite/1, + end_per_suite/1, + init_per_testcase/2, + end_per_testcase/2, + + %% The test cases base/1, gen/1, lib/1, unknown/1, - recode/1]). + recode/1 + ]). -include("diameter.hrl"). --define(util, diameter_util). --define(L, atom_to_list). +-include("diameter_util.hrl"). + + +-define(CL(F), ?CL(F, [])). +-define(CL(F, A), ?LOG("DCS", F, A)). +-define(L, atom_to_list). + %% =========================================================================== @@ -54,22 +68,76 @@ suite() -> all() -> [base, gen, lib, unknown, recode]. + +init_per_suite(Config) -> + ?DUTIL:init_per_suite(Config). + +end_per_suite(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(Case, Config) when is_list(Config) -> + ?CL("init_per_testcase(~w) -> check factor", [Case]), + Key = dia_factor, + case lists:keysearch(Key, 1, Config) of + {value, {Key, Factor}} when (Factor > 10) -> + ?CL("init_per_testcase(~w) -> Too slow (~w) => SKIP", + [Case, Factor]), + {skip, {machine_too_slow, Factor}}; + _ -> + ?CL("init_per_testcase(~w) -> run test", [Case]), + Config + end; +init_per_testcase(Case, Config) -> + ?CL("init_per_testcase(~w) -> entry", [Case]), + Config. + + +end_per_testcase(Case, Config) when is_list(Config) -> + ?CL("end_per_testcase(~w) -> entry", [Case]), + Config. + + +%% =========================================================================== + base(_Config) -> - run(base). + ?CL("~w -> entry", [?FUNCTION_NAME]), + Res = run(base), + ?CL("~w -> done when" + "~n Res: ~p", [?FUNCTION_NAME, Res]), + Res. gen(_Config) -> - run(gen). + ?CL("~w -> entry", [?FUNCTION_NAME]), + Res = run(gen), + ?CL("~w -> done when" + "~n Res: ~p", [?FUNCTION_NAME, Res]), + Res. lib(_Config) -> - run(lib). + ?CL("~w -> entry", [?FUNCTION_NAME]), + Res = run(lib), + ?CL("~w -> done when" + "~n Res: ~p", [?FUNCTION_NAME, Res]), + Res. unknown(Config) -> + ?CL("~w -> entry", [?FUNCTION_NAME]), Priv = proplists:get_value(priv_dir, Config), Data = proplists:get_value(data_dir, Config), - unknown(Priv, Data). + Res = unknown(Priv, Data), + ?CL("~w -> done when" + "~n Res: ~p", [?FUNCTION_NAME, Res]), + Res. recode(_Config) -> - run(recode). + ?CL("~w -> entry", [?FUNCTION_NAME]), + Res = run(recode), + ?CL("~w -> done when" + "~n Res: ~p", [?FUNCTION_NAME, Res]), + Res. + %% =========================================================================== @@ -97,7 +165,7 @@ run(lib) -> %% Have a separate AVP dictionary just to exercise more code. run(unknown) -> - PD = ?util:mktemp("diameter_codec"), + PD = ?MKTEMP("diameter_codec"), DD = filename:join([code:lib_dir(diameter), "test", "diameter_codec_SUITE_data"]), @@ -119,19 +187,24 @@ run(failed_error) -> run(recode) -> ok = diameter:start(), try - ?util:run([{?MODULE, run, [F]} || F <- [success, - grouped_error, - failed_error]]) + ?RUN([{?MODULE, run, [F]} || F <- [success, + grouped_error, + failed_error]]) after ok = diameter:stop() end; run(List) -> - ?util:run([{{?MODULE, run, [F]}, 10000} || F <- List]). + ?RUN([{{?MODULE, run, [F]}, 10000} || F <- List]). + %% =========================================================================== unknown(Priv, Data) -> + ?CL("~w -> entry with" + "~n Priv dir: ~p" + "~n Data dir: ~p" + "~n", [?FUNCTION_NAME, Priv, Data]), ok = make(Data, "recv.dia", Priv), ok = make(Data, "avps.dia", Priv), {ok, _, _} = compile(Priv, "diameter_test_avps.erl"), @@ -144,14 +217,22 @@ unknown(Priv, Data) -> diameter_test_unknown:run(). make(Dir, File, Out) -> + ?CL("~w -> entry with" + "~n File: ~p" + "~n", [?FUNCTION_NAME, File]), diameter_make:codec(filename:join(Dir, File), [{outdir, Out}]). compile(Dir, File) -> compile(Dir, File, []). compile(Dir, File, Opts) -> + ?CL("~w -> entry with" + "~n File: ~p" + "~n Opts: ~p" + "~n", [?FUNCTION_NAME, File, Opts]), compile:file(filename:join(Dir, File), [return | Opts]). + %% =========================================================================== %% Ensure a Grouped AVP is represented by a list in the avps field. From b90bf6c421425dcfa658ad909feddba6bc6b6588 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 12 Jun 2024 12:03:02 +0200 Subject: [PATCH 36/38] [diameter|test] Attempted ugly workaround for timeout issue Attempted ugly workaround, in the 3xxx test suite, for the timeout issue (a call returns with {error, timeout} even though only a fraction of the timeout has expired). --- lib/diameter/test/diameter_3xxx_SUITE.erl | 37 ++++++++++++++++++----- lib/diameter/test/diameter_util.hrl | 2 ++ 2 files changed, 32 insertions(+), 7 deletions(-) diff --git a/lib/diameter/test/diameter_3xxx_SUITE.erl b/lib/diameter/test/diameter_3xxx_SUITE.erl index a6f985e6b762..07cc775f8301 100644 --- a/lib/diameter/test/diameter_3xxx_SUITE.erl +++ b/lib/diameter/test/diameter_3xxx_SUITE.erl @@ -612,13 +612,36 @@ send_5xxx([_,_]) -> call() -> Name = ?testcase(), ?XL("call -> make diameter call with Name: ~p", [Name]), - diameter:call(?CLIENT, - ?DICT, - #diameter_base_STR - {'Termination-Cause' = ?LOGOUT, - 'Auth-Application-Id' = ?COMMON, - 'Class' = [?L(Name)]}, - [{extra, [Name]}]). + %% There is a "bug" in diameter, which can cause this function to return + %% {error, timeout} even though only a fraction on the time has expired. + %% This is because the timer has in fact *not* expired. Instead what + %% has happened is the transport process has died and the selection + %% of a new transport fails (I think its a race causing the pick_peer + %% to return the same tranport process), at that error is converted to + %% a timeout error. + %% So, if this call returns {error, timeout} but only a fraction of the + %% time has passed we skip instead! + Timeout = 5000, + T1 = ?TS(), + case diameter:call(?CLIENT, + ?DICT, + #diameter_base_STR + {'Termination-Cause' = ?LOGOUT, + 'Auth-Application-Id' = ?COMMON, + 'Class' = [?L(Name)]}, + [{extra, [Name]}, {timeout, Timeout}]) of + {error, timeout} = ERROR -> + T2 = ?TS(), + TDiff = T2 - T1, + if + TDiff < 100 -> + exit({skip, {invalid_timeout, TDiff, Timeout}}); + true -> + ERROR + end; + R -> + R + end. %% =========================================================================== diff --git a/lib/diameter/test/diameter_util.hrl b/lib/diameter/test/diameter_util.hrl index 86ab23fccaf9..29860f95489a 100644 --- a/lib/diameter/test/diameter_util.hrl +++ b/lib/diameter/test/diameter_util.hrl @@ -42,4 +42,6 @@ -define(INFO(), ?DUTIL:info()). -define(SCRAMBLE(SS), ?DUTIL:scramble(SS)). +-define(TS(), erlang:system_time(millisecond)). + -endif. From a02442712d7953165f1f05fcf41d79e6a3674864 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Wed, 12 Jun 2024 14:58:16 +0200 Subject: [PATCH 37/38] [diameter|test] Add more (timeout) skip --- .../test/diameter_distribution_SUITE.erl | 28 ++++++++++++++++--- lib/diameter/test/diameter_util.erl | 19 +++++++++++-- 2 files changed, 40 insertions(+), 7 deletions(-) diff --git a/lib/diameter/test/diameter_distribution_SUITE.erl b/lib/diameter/test/diameter_distribution_SUITE.erl index 342a4a0e6084..20e97e5aa8ae 100644 --- a/lib/diameter/test/diameter_distribution_SUITE.erl +++ b/lib/diameter/test/diameter_distribution_SUITE.erl @@ -321,11 +321,31 @@ str(Cause) -> %% send/4 -%% erlang:system_time(millisecond) - +%% There is a "bug" in diameter, which can cause this function to return +%% {error, timeout} even though only a fraction on the time has expired. +%% This is because the timer has in fact *not* expired. Instead what +%% has happened is the transport process has died and the selection +%% of a new transport fails (I think its a race causing the pick_peer +%% to return the same tranport process), at that error is converted to +%% a timeout error. +%% So, if this call returns {error, timeout} but only a fraction of the +%% time has passed we skip instead! send([_, {Node, _} | _], Where, Req, Factor) -> ?DL("send -> make rpc call to node ~p", [Node]), case rpc:call(Node, ?MODULE, call, [{Where, Req, Factor}]) of + {{error, timeout} = Result, T1, T2, Timeout} + when is_integer(T1) andalso is_integer(T2) -> + TDiff = T2 - T1, + ?DL("request completed:" + "~n Time: ~w msec" + "~n Timeout: ~w msec" + "~n Result: ~p", [TDiff, Timeout, Result]), + if + (TDiff < 100) -> + exit({skip, {invalid_timeout, TDiff, Timeout}}); + true -> + Result + end; {Result, T1, T2, Timeout} when is_integer(T1) andalso is_integer(T2) -> ?DL("request completed:" "~n Time: ~w msec" @@ -348,10 +368,10 @@ call({Where, Req, Factor}) -> "~n Req: ~p" "~nwhen" "~n Timeout: ~w (~w)", [node(), Where, Req, Timeout, Factor]), - T1 = erlang:system_time(millisecond), + T1 = ?TS(), Result = diameter:call(?CLIENT, ?DICT, Req, [{extra, [{Where, sname()}]}, {timeout, Timeout}]), - T2 = erlang:system_time(millisecond), + T2 = ?TS(), ?DL("call -> diameter call ended with" "~n Result: ~p" "~nwhen" diff --git a/lib/diameter/test/diameter_util.erl b/lib/diameter/test/diameter_util.erl index 15921d56ac15..de6c766d7e90 100644 --- a/lib/diameter/test/diameter_util.erl +++ b/lib/diameter/test/diameter_util.erl @@ -162,7 +162,14 @@ consult(Path) -> run(L) -> Ref = make_ref(), - AccF = fun(I, [F|T]) -> + AccF = fun({skip, _SkipReason} = SKIP, _) -> + %% ?UL("run:AccF(skip) -> entry with" + %% "~n Skip Reason: ~p", [_SkipReason]), + exit(SKIP); + (I, [F|T]) -> + %% ?UL("run:AccF -> entry with" + %% "~n I: ~p" + %% "~n F: ~p", [I, F]), Ref == (catch element(1, I)) orelse error(#{failed => F, reason => I}), T @@ -212,11 +219,17 @@ await_down(ParentMRef, WorkerPid) -> exit({TCPid, R, TCStack}); {'DOWN', ParentMRef, process, PPid, PReason} -> - ?UL("await_down -> parent process (~p) died: " + ?UL("await_down -> parent process [~p] died: " "~n Reason: ~p", [PPid, PReason]), exit(WorkerPid, kill); + + {'DOWN', _, process, WorkerPid, {skip, WSkipReason} = SKIP} -> + ?UL("await_down -> worker process [~p] died with skip: " + "~n Skip Reason: ~p", [WorkerPid, WSkipReason]), + exit(SKIP); + {'DOWN', _, process, WorkerPid, WReason} -> - ?UL("await_down -> worker process (~p) died: " + ?UL("await_down -> worker process [~p] died: " "~n Reason: ~p", [WorkerPid, WReason]), ok end. From 5ea28b985249c9b9cef9bca3821d14731c2e5657 Mon Sep 17 00:00:00 2001 From: Micael Karlberg Date: Tue, 25 Jun 2024 07:39:36 +0200 Subject: [PATCH 38/38] [diameter|test] Tweaked the relay suite --- lib/diameter/test/diameter_relay_SUITE.erl | 31 ++++++++++++++++++++++ 1 file changed, 31 insertions(+) diff --git a/lib/diameter/test/diameter_relay_SUITE.erl b/lib/diameter/test/diameter_relay_SUITE.erl index 701552d91409..056fc2a8370b 100644 --- a/lib/diameter/test/diameter_relay_SUITE.erl +++ b/lib/diameter/test/diameter_relay_SUITE.erl @@ -44,6 +44,8 @@ all/0, init_per_suite/1, end_per_suite/1, + init_per_testcase/2, + end_per_testcase/2, %% The test cases parallel/1 @@ -121,12 +123,41 @@ all() -> init_per_suite(Config) -> + ?RL("init_per_suite -> entry with" + "~n Config: ~p", [Config]), ?DUTIL:init_per_suite(Config). end_per_suite(Config) -> + ?RL("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) -> + ?RL("init_per_testcase(~w) -> check factor", [Case]), + Key = dia_factor, + case lists:keysearch(Key, 1, Config) of + {value, {Key, Factor}} when (Factor > 10) -> + ?RL("init_per_testcase(~w) -> Too slow (~w) => SKIP", + [Case, Factor]), + {skip, {machine_too_slow, Factor}}; + _ -> + ?RL("init_per_testcase(~w) -> run test", [Case]), + Config + end; +init_per_testcase(Case, Config) -> + ?RL("init_per_testcase(~w) -> entry", [Case]), + Config. + + +end_per_testcase(Case, Config) when is_list(Config) -> + ?RL("end_per_testcase(~w) -> entry", [Case]), + Config. + + +%% =========================================================================== + parallel(_Config) -> ?RL("parallel -> entry"), Res = run(),