File 0461-snmp-test-Add-utility-function-for-starting-nodes.patch of Package erlang

From 0c6cf22081d4cebb3370db5a272ee0b575a7c5f8 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Fri, 13 Jun 2025 07:40:24 +0200
Subject: [PATCH 1/7] [snmp|test] Add utility function for starting nodes

Add a utility function for starting nodes.
The node start sometimes fail (timeout) which causes a the
test case to fail. Instead, since this is not caused by
SNMP (or its test suite(s)), issue a skip.
---
 lib/snmp/test/snmp_agent_test_lib.erl | 14 ++++++++------
 lib/snmp/test/snmp_manager_SUITE.erl  |  6 ++----
 lib/snmp/test/snmp_test_lib.erl       | 21 ++++++++++++++++++++-
 lib/snmp/test/snmp_test_lib.hrl       |  7 ++++---
 4 files changed, 34 insertions(+), 14 deletions(-)

diff --git a/lib/snmp/test/snmp_agent_test_lib.erl b/lib/snmp/test/snmp_agent_test_lib.erl
index f0dae22149..393089c287 100644
--- a/lib/snmp/test/snmp_agent_test_lib.erl
+++ b/lib/snmp/test/snmp_agent_test_lib.erl
@@ -130,15 +130,17 @@ init_all(Config) when is_list(Config) ->
     %% Start nodes
     %%
 
-    ?IPRINT("init_all -> start sub-agent node"),
-    Args = ["-s", "snmp_test_sys_monitor", "start", "-s", "global", "sync"],
+    %% Since our nodes run through many test cases,
+    %% we, *current* process, cannot be linked to it.
+    %% Since we (current process) are dead once this
+    %% initiation is done, which would get the 'Peer'
+    %% process to terminate the node.
 
-    {ok, SaPeer, SaNode}  = ?CT_PEER(#{name => ?CT_PEER_NAME(snmp_sa), args => Args}),
-    unlink(SaPeer), %% must unlink, otherwise peer will exit before test case
+    ?IPRINT("init_all -> start sub-agent node"),
+    {SaPeer, SaNode} = ?START_NODE(?CT_PEER_NAME(snmp_sa), true),
 
     ?IPRINT("init_all -> start manager node"),
-    {ok, MgrPeer, MgrNode} = ?CT_PEER(#{name => ?CT_PEER_NAME(snmp_mgr), args => Args}),
-    unlink(MgrPeer), %% must unlink, otherwise peer will exit before test case
+    {MgrPeer, MgrNode} = ?START_NODE(?CT_PEER_NAME(snmp_mgr), true),
 
     global:sync(),
 
diff --git a/lib/snmp/test/snmp_manager_SUITE.erl b/lib/snmp/test/snmp_manager_SUITE.erl
index 1e398ed0d5..913274513c 100644
--- a/lib/snmp/test/snmp_manager_SUITE.erl
+++ b/lib/snmp/test/snmp_manager_SUITE.erl
@@ -6190,11 +6190,9 @@ agent_info(Node) ->
 %% -- Misc node operation wrapper functions --
 
 start_node(Case) ->
-    Args = ["-s", "snmp_test_sys_monitor", "start", "-s", "global", "sync"],
     Name = peer:random_name(lists:concat([?MODULE, "-", Case])),
-    {ok, Peer, Node}  = ?CT_PEER(#{name => Name, args => Args}),
-    global:sync(),
-    {Peer, Node}.
+    ?START_NODE(Name, false).
+
 
 %% -- Misc config wrapper functions --
 
diff --git a/lib/snmp/test/snmp_test_lib.erl b/lib/snmp/test/snmp_test_lib.erl
index e41da876b0..f3d7b2d2bb 100644
--- a/lib/snmp/test/snmp_test_lib.erl
+++ b/lib/snmp/test/snmp_test_lib.erl
@@ -23,6 +23,7 @@
 -module(snmp_test_lib).
 
 -include_lib("kernel/include/file.hrl").
+-include_lib("common_test/include/ct.hrl").
 
 
 -export([tc_try/2, tc_try/3,
@@ -42,7 +43,7 @@
 -export([fail/3, skip/3]).
 -export([hours/1, minutes/1, seconds/1, sleep/1]).
 -export([flush_mqueue/0, mqueue/0, mqueue/1, trap_exit/0, trap_exit/1]).
--export([ping/1, local_nodes/0, nodes_on/1]).
+-export([start_node/2, ping/1, local_nodes/0, nodes_on/1]).
 -export([is_app_running/1,
 	 is_crypto_running/0, is_mnesia_running/0, is_snmp_running/0,
          ensure_not_running/3]).
@@ -3163,6 +3164,24 @@ trap_exit(Flag) ->
 %% Node utility functions
 %% 
 
+start_node(Name, Unlink) ->
+    Args = ["-s", "snmp_test_sys_monitor", "start", "-s", "global", "sync"],
+    case ?CT_PEER(#{name => Name, args => Args}) of
+        {ok, Peer, Node}  ->
+            %% Must unlink, otherwise peer will exit before test case
+            maybe_unlink(Unlink, Peer),
+            global:sync(),
+            {Peer, Node};
+        {error, Reason} ->
+            ?SKIP({failed_starting_node, Name, Reason})
+    end.
+
+maybe_unlink(true, Pid) ->
+    unlink(Pid);
+maybe_unlink(false, _) ->
+    ok.
+
+    
 ping(N) ->
     case net_adm:ping(N) of
  	pang ->
diff --git a/lib/snmp/test/snmp_test_lib.hrl b/lib/snmp/test/snmp_test_lib.hrl
index 9a2addf97f..61e9b138d5 100644
--- a/lib/snmp/test/snmp_test_lib.hrl
+++ b/lib/snmp/test/snmp_test_lib.hrl
@@ -102,9 +102,10 @@
 
 %% - Node utility macros - 
 
--define(PING(N),            ?LIB:ping(N)).
--define(LNODES(),           ?LIB:local_nodes()).
--define(NODES(H),           ?LIB:nodes_on(H)).
+-define(START_NODE(N, U), ?LIB:start_node((N), (U))).
+-define(PING(N),          ?LIB:ping(N)).
+-define(LNODES(),         ?LIB:local_nodes()).
+-define(NODES(H),         ?LIB:nodes_on(H)).
 
 %% - Application and Crypto utility macros - 
 
-- 
2.43.0

openSUSE Build Service is sponsored by