Skip to content

Commit 349889b

Browse files
committed
Merge branch 'bmk/snmp/20250612/test_tweaking' into maint
2 parents 430b84c + 75a9d87 commit 349889b

File tree

5 files changed

+67
-16
lines changed

5 files changed

+67
-16
lines changed

lib/snmp/test/snmp_agent_SUITE.erl

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -753,7 +753,7 @@ init_per_group(GroupName, Config0) ->
753753
"~n Nodes: ~p",
754754
[?FUNCTION_NAME, GroupName, Config0, nodes()]),
755755

756-
case init_per_group2(GroupName, Config0) of
756+
try init_per_group2(GroupName, Config0) of
757757
Config1 when is_list(Config1) ->
758758

759759
?IPRINT("~w(~w) -> done when"
@@ -770,6 +770,15 @@ init_per_group(GroupName, Config0) ->
770770
"~n Nodes: ~p",
771771
[?FUNCTION_NAME, GroupName, SkipReason, nodes()]),
772772

773+
SKIP
774+
catch
775+
Class:{skip, SkipReason} = SKIP ->
776+
777+
?IPRINT("~w(~w) -> done when SKIP (~w)"
778+
"~n Skip Reason: ~p"
779+
"~n Nodes: ~p",
780+
[?FUNCTION_NAME, GroupName, Class, SkipReason, nodes()]),
781+
773782
SKIP
774783
end.
775784

lib/snmp/test/snmp_agent_test_lib.erl

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -130,15 +130,17 @@ init_all(Config) when is_list(Config) ->
130130
%% Start nodes
131131
%%
132132

133-
?IPRINT("init_all -> start sub-agent node"),
134-
Args = ["-s", "snmp_test_sys_monitor", "start", "-s", "global", "sync"],
133+
%% Since our nodes run through many test cases,
134+
%% we, *current* process, cannot be linked to it.
135+
%% Since we (current process) are dead once this
136+
%% initiation is done, which would get the 'Peer'
137+
%% process to terminate the node.
135138

136-
{ok, SaPeer, SaNode} = ?CT_PEER(#{name => ?CT_PEER_NAME(snmp_sa), args => Args}),
137-
unlink(SaPeer), %% must unlink, otherwise peer will exit before test case
139+
?IPRINT("init_all -> start sub-agent node"),
140+
{SaPeer, SaNode} = ?START_NODE(?CT_PEER_NAME(snmp_sa), true),
138141

139142
?IPRINT("init_all -> start manager node"),
140-
{ok, MgrPeer, MgrNode} = ?CT_PEER(#{name => ?CT_PEER_NAME(snmp_mgr), args => Args}),
141-
unlink(MgrPeer), %% must unlink, otherwise peer will exit before test case
143+
{MgrPeer, MgrNode} = ?START_NODE(?CT_PEER_NAME(snmp_mgr), true),
142144

143145
global:sync(),
144146

lib/snmp/test/snmp_manager_SUITE.erl

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -6263,11 +6263,9 @@ agent_info(Node) ->
62636263
%% -- Misc node operation wrapper functions --
62646264

62656265
start_node(Case) ->
6266-
Args = ["-s", "snmp_test_sys_monitor", "start", "-s", "global", "sync"],
62676266
Name = peer:random_name(lists:concat([?MODULE, "-", Case])),
6268-
{ok, Peer, Node} = ?CT_PEER(#{name => Name, args => Args}),
6269-
global:sync(),
6270-
{Peer, Node}.
6267+
?START_NODE(Name, false).
6268+
62716269

62726270
%% -- Misc config wrapper functions --
62736271

lib/snmp/test/snmp_test_lib.erl

Lines changed: 42 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@
2323
-module(snmp_test_lib).
2424

2525
-include_lib("kernel/include/file.hrl").
26+
-include_lib("common_test/include/ct.hrl").
2627

2728

2829
-export([tc_try/2, tc_try/3,
@@ -42,7 +43,7 @@
4243
-export([fail/3, skip/3]).
4344
-export([hours/1, minutes/1, seconds/1, sleep/1]).
4445
-export([pi/2, flush_mqueue/0, mqueue/0, mqueue/1, trap_exit/0, trap_exit/1]).
45-
-export([ping/1, local_nodes/0, nodes_on/1]).
46+
-export([start_node/2, ping/1, local_nodes/0, nodes_on/1]).
4647
-export([is_app_running/1,
4748
is_crypto_running/0, is_mnesia_running/0, is_snmp_running/0,
4849
ensure_not_running/3]).
@@ -1042,7 +1043,10 @@ fail(Reason, Mod, Line) ->
10421043
skip(Reason, Module, Line) ->
10431044
String = lists:flatten(io_lib:format("Skipping ~p(~p): ~p~n",
10441045
[Module, Line, Reason])),
1045-
exit({skip, String}).
1046+
skip(String).
1047+
1048+
skip(Reason) ->
1049+
exit({skip, Reason}).
10461050

10471051

10481052
%% This function prints various host info, which might be useful
@@ -3163,6 +3167,42 @@ trap_exit(Flag) ->
31633167
%% Node utility functions
31643168
%%
31653169

3170+
%% This hinges on an updated peer verbose start
3171+
%% -define(VERBOSE_PEER_START, true).
3172+
3173+
-ifdef(VERBOSE_PEER_START).
3174+
-define(MAYBE_VERBOSE_START(SO), (SO)#{verbose => true}).
3175+
-define(START_OPTIONS(SO), (SO)#{connection => standard_io}).
3176+
-else.
3177+
-define(MAYBE_VERBOSE_START(SO), SO).
3178+
-define(START_OPTIONS(SO), SO).
3179+
-endif.
3180+
3181+
start_node(Name, Unlink) ->
3182+
Args = ["-s", "snmp_test_sys_monitor", "start", "-s", "global", "sync"],
3183+
%% Note that the 'verbose' option may not exist...
3184+
%% If it does not exist, this (verbose => true) "should" do nothing...
3185+
BaseStartOptions = #{name => Name,
3186+
args => Args},
3187+
StartOptions0 = ?MAYBE_VERBOSE_START(BaseStartOptions),
3188+
StartOptions = ?START_OPTIONS(StartOptions0),
3189+
case ?CT_PEER(StartOptions) of
3190+
{ok, Peer, Node} ->
3191+
%% Must unlink, otherwise peer will exit before test case
3192+
maybe_unlink(Unlink, Peer),
3193+
global:sync(),
3194+
{Peer, Node};
3195+
{error, Reason} ->
3196+
%%% throw({skip, {failed_starting_node, Name, Reason}})
3197+
skip({failed_starting_node, Name, Reason})
3198+
end.
3199+
3200+
maybe_unlink(true, Pid) ->
3201+
unlink(Pid);
3202+
maybe_unlink(false, _) ->
3203+
ok.
3204+
3205+
31663206
ping(N) ->
31673207
case net_adm:ping(N) of
31683208
pang ->

lib/snmp/test/snmp_test_lib.hrl

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@
5858
?LIB:non_pc_tc_maybe_skip(Config, Condition, ?MODULE, ?LINE)).
5959

6060
-define(SKIP(Reason), ?LIB:skip(Reason, ?MODULE, ?LINE)).
61+
-define(SKIPT(Reason), throw({skip, Reason})).
6162
-define(FAIL(Reason), ?LIB:fail(Reason, ?MODULE, ?LINE)).
6263
-define(HAS_SUPPORT_IPV6(), ?LIB:has_support_ipv6()).
6364

@@ -104,9 +105,10 @@
104105

105106
%% - Node utility macros -
106107

107-
-define(PING(N), ?LIB:ping(N)).
108-
-define(LNODES(), ?LIB:local_nodes()).
109-
-define(NODES(H), ?LIB:nodes_on(H)).
108+
-define(START_NODE(N, U), ?LIB:start_node((N), (U))).
109+
-define(PING(N), ?LIB:ping(N)).
110+
-define(LNODES(), ?LIB:local_nodes()).
111+
-define(NODES(H), ?LIB:nodes_on(H)).
110112

111113
%% - Application and Crypto utility macros -
112114

0 commit comments

Comments
 (0)