Skip to content

Commit 45a34da

Browse files
committed
Merge branch 'bmk/snmp/20250605/manager_start_notification/OTP-19696' into maint
2 parents 4d75fb5 + 3b23ffa commit 45a34da

File tree

4 files changed

+189
-62
lines changed

4 files changed

+189
-62
lines changed

lib/snmp/src/manager/snmpm.erl

Lines changed: 89 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,8 @@ The module `snmpm` contains interface functions to the SNMP manager.
104104
-export([format_reason/1, format_reason/2]).
105105

106106
%% Application internal export
107-
-export([start_link/3, snmpm_start_verify/2, snmpm_start_verify/3]).
107+
-export([start_link/3]).
108+
-export([snmpm_start_verify/4, do_snmpm_start_verify/4]).
108109
-export([target_name/1, target_name/2]).
109110

110111
-export_type([
@@ -393,11 +394,39 @@ to this handler.
393394
This function is used in conjunction with the monitor function.
394395
""".
395396
-spec notify_started(Timeout) -> Pid when
396-
Timeout :: pos_integer(),
397-
Pid :: pid().
397+
Timeout :: non_neg_integer(),
398+
Pid :: pid();
399+
(Args) -> Pid when
400+
Args :: map(),
401+
Pid :: pid().
402+
403+
notify_started(Timeout)
404+
when is_integer(Timeout) andalso (Timeout > 0) ->
405+
notify_started(#{timeout => Timeout});
406+
notify_started(#{timeout := Timeout} = Args)
407+
when is_integer(Timeout) andalso (Timeout > 0) ->
408+
EOL = t() + Timeout,
409+
Self = self(),
410+
Verbose = ns_get_verbose(Args),
411+
TickTime = ns_get_tick_time(Args, Timeout),
412+
spawn_link(?MODULE, snmpm_start_verify, [Self, Verbose, TickTime, EOL]).
413+
414+
ns_get_verbose(Args) ->
415+
case maps:get(verbose, Args, false) of
416+
V when is_boolean(V) ->
417+
V
418+
end.
398419

399-
notify_started(To) when is_integer(To) andalso (To > 0) ->
400-
spawn_link(?MODULE, snmpm_start_verify, [self(), To]).
420+
ns_get_tick_time(Args, Timeout) ->
421+
case maps:get(tick_time, Args, ?NOTIFY_START_TICK_TIME) of
422+
%% Make sure Timeout and TickTime make sense
423+
TT when is_integer(TT) andalso (TT > 0) andalso (Timeout > TT) ->
424+
TT;
425+
426+
%% If TickTime > Timeout, use infinity instead
427+
_ ->
428+
infinity
429+
end.
401430

402431

403432
-doc """
@@ -411,42 +440,51 @@ cancel_notify_started(Pid) ->
411440
ok.
412441

413442
-doc false.
414-
snmpm_start_verify(Parent, To) ->
415-
?d("starting", []),
416-
snmpm_start_verify(Parent, monitor(), To).
443+
snmpm_start_verify(Parent, Verbose, TickTime, EOL) ->
444+
put(verbose, Verbose),
445+
maybe_inform("starting"),
446+
do_snmpm_start_verify(Parent, monitor(), TickTime, EOL).
417447

418448
-doc false.
419-
snmpm_start_verify(Parent, _Ref, To) when (To =< 0) ->
420-
?d("timeout", []),
421-
unlink(Parent),
422-
Parent ! {snmpm_start_timeout, self()};
423-
snmpm_start_verify(Parent, Ref, To) ->
424-
T0 = t(),
425-
receive
426-
{cancel, Parent} ->
427-
?d("cancel", []),
428-
demonitor(Ref),
429-
unlink(Parent),
430-
exit(normal);
431-
{'EXIT', Parent, _} ->
432-
exit(normal);
433-
{'DOWN', Ref, process, _Object, _Info} ->
434-
?d("down", []),
435-
sleep(?NOTIFY_START_TICK_TIME),
436-
?MODULE:snmpm_start_verify(Parent, monitor(), t(T0, To))
437-
after ?NOTIFY_START_TICK_TIME ->
438-
?d("down timeout", []),
439-
demonitor(Ref),
440-
case snmpm_server:is_started() of
441-
true ->
442-
unlink(Parent),
443-
Parent ! {snmpm_started, self()};
444-
_ ->
445-
?MODULE:snmpm_start_verify(Parent, monitor(), t(T0, To))
446-
end
449+
do_snmpm_start_verify(Parent, Ref, TickTime, EOL) ->
450+
case is_eol(EOL) of
451+
true ->
452+
maybe_inform("EOL - issue start-timeout"),
453+
Parent ! {snmpm_start_timeout, self()},
454+
unlink(Parent),
455+
exit(normal);
456+
false ->
457+
receive
458+
{cancel, Parent} ->
459+
maybe_inform("cancel"),
460+
demonitor(Ref),
461+
unlink(Parent),
462+
exit(normal);
463+
{'EXIT', Parent, _} ->
464+
maybe_inform("parent death"),
465+
exit(normal);
466+
{'DOWN', Ref, process, _Object, _Info} ->
467+
maybe_inform("down - not started"),
468+
sleep(TickTime),
469+
?MODULE:do_snmpm_start_verify(Parent, monitor(),
470+
TickTime, EOL)
471+
after TickTime ->
472+
maybe_inform("tick-timeout - check if started"),
473+
demonitor(Ref),
474+
case snmpm_server:is_started() of
475+
true ->
476+
maybe_inform("started"),
477+
unlink(Parent),
478+
Parent ! {snmpm_started, self()},
479+
exit(normal);
480+
_ ->
481+
?MODULE:do_snmpm_start_verify(Parent, monitor(),
482+
TickTime, EOL)
483+
end
484+
end
447485
end.
486+
448487

449-
t(T0, T) -> T - (t() - T0).
450488
t() -> snmp_misc:now(ms).
451489
sleep(To) -> snmp_misc:sleep(To).
452490

@@ -2409,8 +2447,22 @@ ensure_engine_id(Config) ->
24092447
[{engine_id, DefaultEngineId} | Config]
24102448
end.
24112449

2450+
is_eol(EOL) ->
2451+
TS = t(),
2452+
(TS > EOL).
24122453

2454+
maybe_inform(F) ->
2455+
maybe_inform(F, []).
24132456

2457+
maybe_inform(F, A) ->
2458+
maybe_inform(get(verbose), F, A).
2459+
2460+
maybe_inform(true, F, A) ->
2461+
error_logger:info_msg("[snmpm start notifyer ~p] " ++ F, [self()|A]);
2462+
maybe_inform(_, _, _) ->
2463+
ok.
2464+
2465+
24142466
%% p(F) ->
24152467
%% p(F, []).
24162468

lib/snmp/test/snmp_manager_SUITE.erl

Lines changed: 97 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -183,6 +183,7 @@ groups() ->
183183

184184
{all, [], all_cases()},
185185
{start_and_stop_tests, [], start_and_stop_tests_cases()},
186+
{notify, [], notify_cases()},
186187
{misc_tests, [], misc_tests_cases()},
187188
{usm_priv_aes_tests, [], usm_priv_aes_tests_cases()},
188189
{user_tests, [], user_tests_cases()},
@@ -238,6 +239,11 @@ start_and_stop_tests_cases() ->
238239
simple_start_and_stop3,
239240
simple_start_and_monitor_crash1,
240241
simple_start_and_monitor_crash2,
242+
{group, notify}
243+
].
244+
245+
notify_cases() ->
246+
[
241247
notify_started01,
242248
notify_started02
243249
].
@@ -1247,48 +1253,68 @@ do_notify_started01(Config) ->
12471253
{config, [{verbosity, log}, {dir, ConfDir}, {db_dir, DbDir}]}],
12481254

12491255
?IPRINT("[tc] request start notification (1)"),
1250-
Pid1 = snmpm:notify_started(10000),
1256+
NotifyPid1 = snmpm:notify_started(#{verbose => true,
1257+
tick_time => 1000,
1258+
timeout => 10000}),
12511259
receive
1252-
{snmpm_start_timeout, Pid1} ->
1253-
?IPRINT("[tc] received expected start timeout"),
1260+
{snmpm_start_timeout, NotifyPid1} ->
1261+
?IPRINT("[tc] received expected start timeout (~p)", [NotifyPid1]),
12541262
ok;
12551263
Any1 ->
1256-
?FAIL({unexpected_message, Any1})
1264+
?EPRINT("received unexpected message (1): "
1265+
"~n ~p"
1266+
"~n Notify Process (~p) Info: ~p",
1267+
[Any1,
1268+
NotifyPid1, (catch erlang:process_info(NotifyPid1))]),
1269+
?FAIL({unexpected_message, 1, Any1})
12571270
after 15000 ->
1258-
?FAIL({unexpected_timeout, Pid1})
1271+
?EPRINT("unexpected timeout: "
1272+
"~n Notify Process (~p) Info: ~p",
1273+
[NotifyPid1, (catch erlang:process_info(NotifyPid1))]),
1274+
?FAIL({unexpected_timeout, 1, NotifyPid1})
12591275
end,
12601276

12611277
?IPRINT("[tc] request start notification (2)"),
1262-
Pid2 = snmpm:notify_started(10000),
1278+
NotifyPid2 = snmpm:notify_started(#{verbose => true,
1279+
tick_time => 1000,
1280+
timeout => ?NS_TIMEOUT}),
12631281

12641282
?IPRINT("[tc] start the snmpm starter"),
1265-
StarterPid = snmpm_starter(Opts, 5000),
1283+
{StarterPid, _StarterMRef} = snmpm_starter(Opts, 5000),
12661284

1267-
?IPRINT("[tc] await the start notification"),
1285+
?IPRINT("[tc] await the start notification: "
1286+
"~n Notify Process: ~p"
1287+
"~n Starter Process: ~p", [NotifyPid2, StarterPid]),
12681288
Ref =
12691289
receive
1270-
{snmpm_started, Pid2} ->
1290+
{snmpm_started, NotifyPid2} ->
12711291
?IPRINT("[tc] received start notification message -> "
12721292
"create the monitor"),
12731293
snmpm:monitor();
1274-
{snmpm_start_timeout, StarterPid} ->
1275-
?EPRINT("[tc] Start Timeout: "
1276-
"~n Starter Process (~p) Info: ~p",
1277-
[StarterPid, (catch erlang:process_info(StarterPid))]),
1294+
{snmpm_start_timeout, NotifyPid2} ->
1295+
?EPRINT("[tc] received unexpected start timeout when"
1296+
"~n Starter Process (~p) info: ~s",
1297+
[StarterPid,
1298+
format_process_info(StarterPid, " ")]),
1299+
exit(StarterPid, kill),
12781300
?FAIL(start_timeout);
12791301
Any2 ->
12801302
?EPRINT("[tc] Unexpected Message: "
1281-
"~n Notify Process Info: ~p"
1282-
"~n Starter Process info: ~p",
1283-
[(catch erlang:process_info(Pid2)),
1284-
(catch erlang:process_info(StarterPid))]),
1303+
"~n ~p"
1304+
"~n Notify Process (~p) Info: ~s"
1305+
"~n Starter Process (~p) info: ~s",
1306+
[Any2,
1307+
NotifyPid2,
1308+
format_process_info(NotifyPid2, " "),
1309+
StarterPid,
1310+
format_process_info(StarterPid, " ")]),
12851311
?FAIL({unexpected_message, Any2})
12861312
after 15000 ->
12871313
?EPRINT("[tc] Unexpected Start Timeout: "
1288-
"~n Notify Process Info: ~p"
1289-
"~n Starter Process info: ~p",
1290-
[(catch erlang:process_info(Pid2)),
1291-
(catch erlang:process_info(StarterPid))]),
1314+
"~n Notify Process (~p) Info: ~p"
1315+
"~n Starter Process (~p) info: ~p",
1316+
[NotifyPid2, (catch erlang:process_info(NotifyPid2)),
1317+
StarterPid, (catch erlang:process_info(StarterPid))]),
12921318
?FAIL(unexpected_start_timeout)
12931319
end,
12941320

@@ -1319,10 +1345,51 @@ do_notify_started01(Config) ->
13191345
?IPRINT("[tc] end"),
13201346
ok.
13211347

1348+
format_process_info(P, Indent) when is_pid(P) andalso is_list(Indent) ->
1349+
try
1350+
begin
1351+
CurrentFunction = pi(P, current_function),
1352+
CurrentStackTrace = pi(P, current_stacktrace),
1353+
Reductions = pi(P, reductions),
1354+
Memory = pi(P, memory),
1355+
HeapSize = pi(P, heap_size),
1356+
MaxHeapSize = pi(P, max_heap_size),
1357+
TotHeapSize = pi(P, total_heap_size),
1358+
Status = pi(P, status),
1359+
?F("~n"
1360+
"~sCurrent Function: ~p~n"
1361+
"~sCurrent StackTrace: ~p~n"
1362+
"~sReductions: ~p~n"
1363+
"~sMemory: ~p~n"
1364+
"~sHeapSize: ~p~n"
1365+
"~sMax Heap Size: ~p~n"
1366+
"~sTotal Heap Size: ~p~n"
1367+
"~sStatus: ~p~n",
1368+
[Indent, CurrentFunction,
1369+
Indent, CurrentStackTrace,
1370+
Indent, Reductions,
1371+
Indent, Memory,
1372+
Indent, HeapSize,
1373+
Indent, MaxHeapSize,
1374+
Indent, TotHeapSize,
1375+
Indent, Status])
1376+
end
1377+
catch
1378+
_:_:_ ->
1379+
"-"
1380+
end.
13221381

1382+
pi(Pid, Key) ->
1383+
case ?PI(Pid, Key) of
1384+
undefined ->
1385+
throw(no_process);
1386+
Value ->
1387+
Value
1388+
end.
1389+
13231390
snmpm_starter(Opts, To) ->
13241391
Parent = self(),
1325-
spawn(
1392+
spawn_monitor(
13261393
fun() ->
13271394
?IPRINT("[snmpm-starter] wait ~w msec", [To]),
13281395
?SLEEP(To),
@@ -1473,7 +1540,10 @@ ns02_client(Parent, N) when is_pid(Parent) ->
14731540
put(tname, ns02_client),
14741541
?IPRINT("starting"),
14751542
ns02_client_loop(Parent,
1476-
dummy, snmpm:notify_started(?NS_TIMEOUT),
1543+
dummy,
1544+
snmpm:notify_started(#{verbose => true,
1545+
tick_time => 1000,
1546+
timeout => ?NS_TIMEOUT}),
14771547
snmp_misc:now(ms), undefined,
14781548
N).
14791549

@@ -1514,7 +1584,10 @@ ns02_client_loop(Parent, Ref, Pid, Begin, End, N) ->
15141584
"~n Obj: ~p"
15151585
"~n Reason: ~p", [N, Obj, Reason]),
15161586
ns02_client_loop(Parent,
1517-
dummy, snmpm:notify_started(?NS_TIMEOUT),
1587+
dummy,
1588+
snmpm:notify_started(#{verbose => true,
1589+
tick_time => 1000,
1590+
timeout => ?NS_TIMEOUT}),
15181591
Begin, snmp_misc:now(ms),
15191592
N-1)
15201593
end.

lib/snmp/test/snmp_test_lib.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@
4141
replace_config/3, set_config/3, get_config/2, get_config/3]).
4242
-export([fail/3, skip/3]).
4343
-export([hours/1, minutes/1, seconds/1, sleep/1]).
44-
-export([flush_mqueue/0, mqueue/0, mqueue/1, trap_exit/0, trap_exit/1]).
44+
-export([pi/2, flush_mqueue/0, mqueue/0, mqueue/1, trap_exit/0, trap_exit/1]).
4545
-export([ping/1, local_nodes/0, nodes_on/1]).
4646
-export([is_app_running/1,
4747
is_crypto_running/0, is_mnesia_running/0, is_snmp_running/0,

lib/snmp/test/snmp_test_lib.hrl

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -98,6 +98,8 @@
9898
catch _:_:_ ->
9999
{not_running, __P__}
100100
end).
101+
-define(PI(K), ?PI(self(), K)).
102+
-define(PI(P, K), ?LIB:pi((P), (K))).
101103

102104

103105
%% - Node utility macros -

0 commit comments

Comments
 (0)