File 2414-snmp-agent-test-Each-test-case-is-run-in-its-own-new.patch of Package erlang
From 321bb09b1ec6d994b209c98977bb5624411c3092 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Fri, 17 Apr 2020 16:46:51 +0200
Subject: [PATCH 14/14] [snmp|agent|test] Each test case is run in its own
(new) node
There is some previously run test case that can leave
processes running (symbolic store and mib server).
This will then cause problems for most of the test
the testcases in this suite.
So, to avoid this, all test cases (in this suite) are now
run in their own temporary nodes.
---
lib/snmp/test/snmp_agent_mibs_SUITE.erl | 145 +++++++++++++++++++-------------
1 file changed, 86 insertions(+), 59 deletions(-)
diff --git a/lib/snmp/test/snmp_agent_mibs_SUITE.erl b/lib/snmp/test/snmp_agent_mibs_SUITE.erl
index 13734cbf79..39946ba7d1 100644
--- a/lib/snmp/test/snmp_agent_mibs_SUITE.erl
+++ b/lib/snmp/test/snmp_agent_mibs_SUITE.erl
@@ -219,6 +219,10 @@ end_per_testcase1(_Case, Config) when is_list(Config) ->
start_and_stop(suite) -> [];
start_and_stop(Config) when is_list(Config) ->
+ tc_try(start_and_start,
+ fun() -> do_start_and_stop(Config) end).
+
+do_start_and_stop(_Config) ->
Prio = normal,
Verbosity = trace,
@@ -237,6 +241,10 @@ start_and_stop(Config) when is_list(Config) ->
load_unload(suite) -> [];
load_unload(Config) when is_list(Config) ->
+ tc_try(load_unload,
+ fun() -> do_load_unload(Config) end).
+
+do_load_unload(Config) ->
?DBG("load_unload -> start", []),
Prio = normal,
@@ -364,62 +372,8 @@ do_size_check(Name, Config) ->
do_size_check(Name, Init, Config).
do_size_check(Name, Init, Config) ->
- io:format("do_size_check -> entry with"
- "~n Name: ~p"
- "~n Config: ~p"
- "~n", [Name, Config]),
- Pre = fun() ->
- {ok, Node} = ?ALIB:start_node(unique(Name)),
- ok = run_on(Node, Init),
- Node
- end,
- Case = fun(Node) ->
- monitor_node(Node, true),
- Pid = spawn_link(Node, fun() -> do_size_check(Config) end),
- receive
- {nodedown, Node} = N ->
- exit(N);
- {'EXIT', Pid, normal} ->
- monitor_node(Node, false),
- ok;
- {'EXIT', Pid, ok} ->
- monitor_node(Node, false),
- ok;
- {'EXIT', Pid, Reason} ->
- monitor_node(Node, false),
- exit(Reason)
- end
- end,
- Post = fun(Node) ->
- monitor_node(Node, true),
- ?NPRINT("try stop node ~p", [Node]),
- ?STOP_NODE(Node),
- receive
- {nodedown, Node} ->
- ?NPRINT("node ~p stopped", [Node]),
- ok
- end
- end,
- io:format("do_size_check -> do test"
- "~n", []),
- ?TC_TRY(Name, Pre, Case, Post).
+ tc_try(Name, Init, fun() -> do_size_check(Config) end).
-run_on(Node, F) when is_atom(Node) andalso is_function(F, 0) ->
- monitor_node(Node, true),
- Pid = spawn_link(Node, F),
- receive
- {nodedown, Node} = N ->
- exit(N);
- {'EXIT', Pid, normal} ->
- monitor_node(Node, false),
- ok;
- {'EXIT', Pid, Reason} ->
- monitor_node(Node, false),
- Reason
- end.
-
-unique(PreName) ->
- list_to_atom(?F("~w_~w", [PreName, erlang:system_time(millisecond)])).
do_size_check(Config) ->
?IPRINT("do_size_check -> start with"
@@ -477,6 +431,10 @@ do_size_check(Config) ->
me_lookup(suite) -> [];
me_lookup(Config) when is_list(Config) ->
+ tc_try(me_lookup,
+ fun() -> do_me_lookup(Config) end).
+
+do_me_lookup(Config) ->
Prio = normal,
Verbosity = trace,
MibDir = ?config(data_dir, Config),
@@ -530,6 +488,10 @@ me_lookup(Config) when is_list(Config) ->
which_mib(suite) -> [];
which_mib(Config) when is_list(Config) ->
+ tc_try(which_mib,
+ fun() -> do_which_mib(Config) end).
+
+do_which_mib(Config) ->
Prio = normal,
Verbosity = trace,
MibDir = ?config(data_dir, Config),
@@ -586,7 +548,11 @@ which_mib(Config) when is_list(Config) ->
cache_test(suite) -> [];
cache_test(Config) when is_list(Config) ->
- ?IPRINT("cache_test -> start"),
+ tc_try(cache_test,
+ fun() -> do_cache_test(Config) end).
+
+do_cache_test(Config) ->
+ ?IPRINT("cache_test -> start"),
Prio = normal,
%% Verbosity = trace,
Verbosity = info,
@@ -811,13 +777,13 @@ walk(MibsPid) ->
do_walk(MibsPid, Oid, MibView) ->
case snmpa_mib:next(MibsPid, Oid, MibView) of
{table, _, _, #me{oid = Oid}} ->
- ?IPRINT("do_walk -> table done"),
+ ?IPRINT("do_walk -> done for table (~p)", [Oid]),
ok;
{table, _, _, #me{oid = Next}} ->
?IPRINT("do_walk -> table next ~p", [Next]),
do_walk(MibsPid, Next, MibView);
{variable, #me{oid = Oid}, _} ->
- ?IPRINT("do_walk -> variable done"),
+ ?IPRINT("do_walk -> done for variable (~p)", [Oid]),
ok;
{variable, #me{oid = Next}, _} ->
?IPRINT("do_walk -> variable next ~p", [Next]),
@@ -1119,6 +1085,65 @@ mib_storage() ->
[{module, snmpa_mib_storage_ets}].
+%% --
+
+tc_try(Name, TC) ->
+ tc_try(Name, fun() -> ok end, TC).
+
+tc_try(Name, Init, TC)
+ when is_atom(Name) andalso is_function(Init, 0) andalso is_function(TC, 0) ->
+ Pre = fun() ->
+ {ok, Node} = ?ALIB:start_node(unique(Name)),
+ ok = run_on(Node, Init),
+ Node
+ end,
+ Case = fun(Node) ->
+ monitor_node(Node, true),
+ Pid = spawn_link(Node, TC),
+ receive
+ {nodedown, Node} = N ->
+ exit(N);
+ {'EXIT', Pid, normal} ->
+ monitor_node(Node, false),
+ ok;
+ {'EXIT', Pid, ok} ->
+ monitor_node(Node, false),
+ ok;
+ {'EXIT', Pid, Reason} ->
+ monitor_node(Node, false),
+ exit(Reason)
+ end
+ end,
+ Post = fun(Node) ->
+ monitor_node(Node, true),
+ ?NPRINT("try stop node ~p", [Node]),
+ ?STOP_NODE(Node),
+ receive
+ {nodedown, Node} ->
+ ?NPRINT("node ~p stopped", [Node]),
+ ok
+ end
+ end,
+ ?TC_TRY(Name, Pre, Case, Post).
+
+run_on(Node, F) when is_atom(Node) andalso is_function(F, 0) ->
+ monitor_node(Node, true),
+ Pid = spawn_link(Node, F),
+ receive
+ {nodedown, Node} = N ->
+ exit(N);
+ {'EXIT', Pid, normal} ->
+ monitor_node(Node, false),
+ ok;
+ {'EXIT', Pid, Reason} ->
+ monitor_node(Node, false),
+ Reason
+ end.
+
+unique(PreName) ->
+ list_to_atom(?F("~w_~w", [PreName, erlang:system_time(millisecond)])).
+
+
%% --
display_memory_usage(MibsPid) ->
--
2.16.4