Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
bmk committed Aug 9, 2024
2 parents eff93dd + 2b11534 commit 59f5e36
Show file tree
Hide file tree
Showing 4 changed files with 290 additions and 168 deletions.
9 changes: 8 additions & 1 deletion lib/snmp/test/snmp_agent_test_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1030,7 +1030,12 @@ await_stopped(Pid, Ref) ->
%% --- start subagent supervisor ---

start_sub_sup(Node, Dir) ->
rpc:call(Node, ?MODULE, start_sub_sup, [Dir]).
case rpc:call(Node, ?MODULE, start_sub_sup, [Dir]) of
{badrpc, _Reason} = BADRPC ->
?SKIP(BADRPC);
Result ->
Result
end.

start_sub_sup(Dir) ->
?DBG("start_sub -> entry",[]),
Expand All @@ -1056,6 +1061,8 @@ start_subagent(SaNode, RegTree, Mib) ->
Func = start_sub_agent,
Args = [MA, RegTree, [Mib1]],
case rpc:call(SaNode, Mod, Func, Args) of
{badrpc, _Reason} = BADRPC ->
?SKIP(BADRPC);
{ok, SA} ->
?DBG("start_subagent -> SA: ~p", [SA]),
{ok, SA};
Expand Down
15 changes: 9 additions & 6 deletions lib/snmp/test/snmp_manager_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1335,6 +1335,8 @@ do_notify_started02(Config) ->
?IPRINT("starting with Config: "
"~n ~p", [Config]),

Factor = ?config(snmp_factor, Config),

SCO = ?config(socket_create_opts, Config),
ConfDir = ?config(manager_conf_dir, Config),
DbDir = ?config(manager_db_dir, Config),
Expand All @@ -1359,7 +1361,7 @@ do_notify_started02(Config) ->
ApproxStartTime =
case ns02_client_await_approx_runtime(Pid1) of
{ok, T} ->
T;
?LIB:ftime(T, Factor);
{error, Reason} ->
%% Attempt cleanup just in case
exit(Pid1, kill),
Expand All @@ -1385,13 +1387,14 @@ do_notify_started02(Config) ->
?FAIL({client, Reason1});
{'EXIT', Pid1, Reason1} ->
?FAIL({client, Reason1})
after ApproxStartTime + 10000 ->
after ApproxStartTime + 15000 ->
exit(Pid1, kill),
exit(Pid2, kill),
?FAIL(timeout)
end,

?IPRINT("await snmpm starter process exit"),

Timeout2 = ?LIB:ftime(5000, Factor),
?IPRINT("await (~w msec) snmpm starter process exit", [Timeout2]),
receive
{'EXIT', Pid2, normal} ->
ok;
Expand All @@ -1400,7 +1403,7 @@ do_notify_started02(Config) ->
?SKIP(SkipReason2);
{'EXIT', Pid2, Reason2} ->
?FAIL({ctrl, Reason2})
after 5000 ->
after Timeout2 ->
exit(Pid2, kill),
?FAIL(timeout)
end,
Expand Down Expand Up @@ -1515,7 +1518,7 @@ ns02_ctrl_loop(Opts, N) ->
end,
?SLEEP(2000),
?IPRINT("stop manager"),
?SLEEP(100), % Give the verbosity to take effect...
?SLEEP(100), % Give the verbosity time to take effect...
TS3 = erlang:system_time(millisecond),
case snmpm:stop(5000) of
ok ->
Expand Down
34 changes: 31 additions & 3 deletions lib/snmp/test/snmp_manager_config_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -238,6 +238,10 @@ init_per_suite(Config0) when is_list(Config0) ->
%% We need one on this node also
snmp_test_sys_monitor:start(),

?IPRINT("init_per_suite -> try ensure snmpm_config not running"),

config_ensure_not_running(),

?IPRINT("init_per_suite -> end when"
"~n Config: ~p", [Config2]),

Expand Down Expand Up @@ -327,20 +331,44 @@ simple_start_and_stop(doc) ->
"Start the snmp manager config process with the \n"
"minimum setof options (config dir).";
simple_start_and_stop(Conf) when is_list(Conf) ->
put(tname, "SIME-START_AND_STOP"),
?IPRINT("start"),
put(tname, "SIMPLE_START_AND_STOP"),
process_flag(trap_exit, true),
Pre = fun() ->
%% Since this is the first test case in this
%% suite, we (possibly) need to do some cleanup...
?IPRINT("~w:pre -> ensure config not already running",
[?FUNCTION_NAME]),
config_ensure_not_running()
end,
TC = fun(_) ->
?IPRINT("~w:tc -> begin", [?FUNCTION_NAME]),
do_simple_start_and_stop(Conf)
end,
Post = fun(_) ->
?IPRINT("~w:post -> ensure config not still running",
[?FUNCTION_NAME]),
config_ensure_not_running()
end,
?TC_TRY(?FUNCTION_NAME, Pre, TC, Post).

do_simple_start_and_stop(Conf) when is_list(Conf) ->
ConfDir = ?config(manager_conf_dir, Conf),
DbDir = ?config(manager_db_dir, Conf),
DbDir = ?config(manager_db_dir, Conf),

?IPRINT("~w -> try write \"standard\" manager config to"
"~n ~p", [?FUNCTION_NAME, ConfDir]),
write_manager_conf(ConfDir),

Opts = [{versions, [v1]},
{config, [{verbosity, trace}, {dir, ConfDir}, {db_dir, DbDir}]}],

?IPRINT("~w -> try start with basic opts", [?FUNCTION_NAME]),
{ok, _Pid} = snmpm_config:start_link(Opts),

?IPRINT("~w -> try stop", [?FUNCTION_NAME]),
ok = snmpm_config:stop(),

?IPRINT("~w -> done", [?FUNCTION_NAME]),
ok.


Expand Down
Loading

0 comments on commit 59f5e36

Please sign in to comment.