File 2653-snmp-test-Add-test-case-s-for-extra-socket-options.patch of Package erlang

From 4a4f59dd0512da1bbcd3d27e186570875eaf5260 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 24 Sep 2019 11:29:34 +0200
Subject: [PATCH 3/4] [snmp|test] Add test case(s) for extra socket options

Add new test cases for the new 'extra socket options' net-if
option. For both manager and agent.

OTP-16092
---
 lib/snmp/test/snmp_agent_test.erl   | 262 +++++++++++++++++++++++++++++++++---
 lib/snmp/test/snmp_manager_test.erl |  36 +++++
 2 files changed, 278 insertions(+), 20 deletions(-)

diff --git a/lib/snmp/test/snmp_agent_test.erl b/lib/snmp/test/snmp_agent_test.erl
index f6416ee2f9..1726a04513 100644
--- a/lib/snmp/test/snmp_agent_test.erl
+++ b/lib/snmp/test/snmp_agent_test.erl
@@ -294,7 +294,13 @@
 	 otp_4394/1, 
 
 	 %% all_tcs - tickets1 - otp7157
-	 otp_7157/1, 
+	 otp_7157/1,
+
+         %% all_tcs - tickets1 - otp16092
+         otp_16092_simple_start_and_stop1/1,
+         otp_16092_simple_start_and_stop2/1,
+         otp_16092_simple_start_and_stop3/1,
+         otp_16092_simple_start_and_stop4/1,
 
 	 %% tickets2
 	 otp8395/1, 
@@ -414,7 +420,7 @@
 	 mnesia_init/1, 
 	 mnesia_start/0, 
 	 mnesia_stop/0, 
-	 start_stdalone_agent/1, 
+	 start_standalone_agent/1, 
 	 do_info/1
 	]).
 
@@ -427,6 +433,7 @@
 -include_lib("snmp/include/snmp_types.hrl").
 -include_lib("snmp/src/agent/snmpa_atl.hrl").
 
+-define(ALIB, snmp_agent_test_lib).
 
 -define(klas1, [1,3,6,1,2,1,7]).
 -define(klas2, [1,3,6,1,2,1,9]).
@@ -538,7 +545,8 @@ groups() ->
      {tickets1,                      [], tickets1_cases()}, 
      {tickets2,                      [], tickets2_cases()}, 
      {otp4394,                       [], [otp_4394]},
-     {otp7157,                       [], [otp_7157]}
+     {otp7157,                       [], [otp_7157]},
+     {otp16092,                      [], otp16092_cases()}
     ].
 
 
@@ -795,6 +803,17 @@ init_per_testcase1(otp_7157 = _Case, Config) when is_list(Config) ->
 	 "~n   Config: ~p", [_Case, Config]),
     Dog = ?WD_START(?MINS(1)),
     [{watchdog, Dog} | Config ];
+init_per_testcase1(Case, Config) 
+  when ((Case =:= otp_16092_simple_start_and_stop1)  orelse
+        (Case =:= otp_16092_simple_start_and_stop2)  orelse
+        (Case =:= otp_16092_simple_start_and_stop3)  orelse
+        (Case =:= otp_16092_simple_start_and_stop4)) andalso
+       is_list(Config) ->
+    ?DBG("init_per_testcase1 -> entry with"
+	 "~n   Case:   ~p"
+	 "~n   Config: ~p", [_Case, Config]),
+    Dog = ?WD_START(?MINS(1)),
+    init_per_testcase2(Case, [{watchdog, Dog} | Config]);
 init_per_testcase1(v2_inform_i = _Case, Config) when is_list(Config) ->
     ?DBG("init_per_testcase1 -> entry with"
 	 "~n   Case:   ~p"
@@ -6541,9 +6560,10 @@ otp_3725_test(MaNode) ->
 tickets1_cases() ->
     [
      {group, otp4394}, 
-     {group, otp7157}
+     {group, otp7157}, 
+     {group, otp16092}
     ].
-    
+
 
 otp_4394_init(Config) when is_list(Config) ->
     ?DBG("otp_4394_init -> entry with"
@@ -6633,8 +6653,6 @@ otp_4394_test() ->
 %% Slogan: Target mib tag list check invalid
 %%-----------------------------------------------------------------
 
-
-
 otp_7157_init(Config) when is_list(Config) ->
     %% <CONDITIONAL-SKIP>
     Skippable = [win32],
@@ -6697,6 +6715,190 @@ otp_7157_test(MA) ->
 
 
 
+%%-----------------------------------------------------------------
+%% Ticket: OTP-16092
+%% Slogan: Extra socket options
+%%         We perform simple start and stop tests with and without
+%%         this option.
+%%-----------------------------------------------------------------
+
+otp16092_cases() ->
+    [
+     otp_16092_simple_start_and_stop1, % default
+     otp_16092_simple_start_and_stop2, % []
+     otp_16092_simple_start_and_stop3, % bad => ignored
+     otp_16092_simple_start_and_stop4  % invalid content
+    ].
+
+otp_16092_simple_start_and_stop1(suite) -> [];
+otp_16092_simple_start_and_stop1(Config) ->
+    ?P(otp_16092_simple_start_and_stop1), 
+    ?DBG("otp_16092_simple_start_and_stop1 -> entry", []),
+
+    otp_16092_simple_start_and_stop(Config, default, success),
+
+    ?DBG("otp_16092_simple_start_and_stop1 -> done", []),
+    ok.
+
+
+otp_16092_simple_start_and_stop2(suite) -> [];
+otp_16092_simple_start_and_stop2(Config) ->
+    ?P(otp_16092_simple_start_and_stop2), 
+    ?DBG("otp_16092_simple_start_and_stop2 -> entry", []),
+
+    otp_16092_simple_start_and_stop(Config, [], success),
+
+    ?DBG("otp_16092_simple_start_and_stop2 -> done", []),
+    ok.
+
+
+otp_16092_simple_start_and_stop3(suite) -> [];
+otp_16092_simple_start_and_stop3(Config) ->
+    ?P(otp_16092_simple_start_and_stop3), 
+    ?DBG("otp_16092_simple_start_and_stop3 -> entry", []),
+
+    otp_16092_simple_start_and_stop(Config, 'this-should-be-ignored', success),
+
+    ?DBG("otp_16092_simple_start_and_stop3 -> done", []),
+    ok.
+
+
+otp_16092_simple_start_and_stop4(suite) -> [];
+otp_16092_simple_start_and_stop4(Config) ->
+    ?P(otp_16092_simple_start_and_stop4), 
+    ?DBG("otp_16092_simple_start_and_stop4 -> entry", []),
+
+    otp_16092_simple_start_and_stop(Config, ['this-should-fail'], failure),
+
+    ?DBG("otp_16092_simple_start_and_stop4 -> done", []),
+    ok.
+
+
+otp_16092_simple_start_and_stop(Config, ESO, Expected) ->
+    ?line ConfDir = ?config(agent_conf_dir, Config),
+    ?line DbDir   = ?config(agent_db_dir,   Config),
+
+    p("try start agent node~n"),
+    p(user, "try start agent node~n"),
+    Node = case ?ALIB:start_node(agent_16092) of
+               {ok, N} ->
+                   p("agent node ~p started~n", [N]),
+                   p(user, "agent node ~p started~n", [N]),
+                   N;
+               {error, Reason} ->
+                   e("Failed starting agent node: "
+                     "~n   ~p"
+                     "~n", [Reason]),
+                   ?SKIP({failed_starting_node, Reason})
+           end,
+
+    Vsns      = [v1],
+    IP        = tuple_to_list(?config(ip, Config)),
+    ManagerIP = IP,
+    TrapPort  = ?TRAP_UDP,
+    AgentIP   = IP,
+    AgentPort = 4000,
+    SysName   = "test",
+    ok = snmp_config:write_agent_snmp_files(
+           ConfDir, Vsns, ManagerIP, TrapPort, AgentIP, AgentPort, SysName),
+
+    ConfOpts = [{dir,        ConfDir},
+                {force_load, false}, 
+                {verbosity,  trace}],
+    NiOpts   =
+        case ESO of
+            default ->
+                [{verbosity, trace}];
+            _ -> 
+                [{verbosity, trace}, {options, [{extra_sock_opts, ESO}]}]
+        end,
+
+    Opts = [{agent_type, master},
+            {versions,   Vsns},
+            {db_dir,     DbDir},
+            {config,     ConfOpts},
+            {net_if,     NiOpts}],
+
+    
+    otp16092_try_start_and_stop_agent(Node, Opts, Expected),
+
+    p("try stop agent node ~p~n", [Node]),
+    p(user, "try stop agent node ~p~n", [Node]),
+    ?ALIB:stop_node(Node),
+
+    ?SLEEP(1000),
+
+    p("done~n"),
+    p(user, "done~n"),
+    ok.
+
+    
+otp16092_try_start_and_stop_agent(Node, Opts, Expected) ->
+    i("try start snmp (agent) supervisor (on ~p) - expect ~p~n", [Node, Expected]),
+    case start_standalone_agent(Node, Opts) of
+        Pid when is_pid(Pid) andalso (Expected =:= success) ->
+            i("Expected success starting snmp (agent) supervisor~n"),
+            ?SLEEP(1000),
+            stop_standalone_agent(Pid),
+            ok;
+        Pid when is_pid(Pid) andalso (Expected =:= failure) ->
+            e("Unexpected success starting snmp (agent) supervisor: (~p)~n", [Pid]),
+            ?SLEEP(1000),
+            stop_standalone_agent(Pid),
+            ?FAIL('unexpected-start-success');
+
+        {error,
+         shutdown,
+         {failed_to_start_child, snmpa_agent_sup,
+          {shutdown,
+           {failed_to_start_child, snmpa_agent,
+            {net_if_error, Reason}}}}} when (Expected =:= failure) ->
+            p("Expected (shutdown, net-if) error starting "
+              "snmp (agent) supervisor (on ~p):"
+              "~n   ~p", [Node, Reason]),
+            ok;
+        {error, {shutdown, Reason}} when (Expected =:= failure) ->
+            p("Expected (shutdown) error starting "
+              "snmp (agent) supervisor (on ~p):"
+              "~n   ~p", [Node, Reason]),
+            ok;
+        {error, Reason} when (Expected =:= failure) ->
+            p("Expected error starting snmp (agent) supervisor (on ~p):"
+              "~n   ~p", [Node, Reason]),
+            ok;
+
+        {badrpc, 
+         {'EXIT',
+          {shutdown,
+           {failed_to_start_child, snmpa_agent_sup,
+            {shutdown,
+             {failed_to_start_child, snmpa_agent,
+              {net_if_error, Reason}}}}}}} when (Expected =:= failure) ->
+            p("Expected (badrpc, shutdown, net-if) error starting "
+              "snmp (agent) supervisor (on ~p):"
+              "~n   ~p", [Node, Reason]),
+            ok;
+        {badrpc, {'EXIT', {shutdown, Reason}}} when (Expected =:= failure) ->
+            p("Expected (badrpc, shutdown) error starting "
+              "snmp (agent) supervisor (on ~p):"
+              "~n   ~p", [Node, Reason]),
+            ok;
+        {badrpc, {'EXIT', Reason}} when (Expected =:= failure) ->
+            p("Expected (badrpc) error starting snmp (agent) supervisor (on ~p):"
+              "~n   ~p", [Node, Reason]),
+            ok;
+
+        {badrpc, Reason} = BADRPC ->
+            e("Bad RPC to node ~p failed:"
+              "~n   ~p", [Node, Reason]),
+            ?SKIP({BADRPC, Node})
+
+    end,
+    ok.
+
+            
+
+
 %%-----------------------------------------------------------------
 %% Extra test cases
 %% These cases are started in the new way
@@ -6800,7 +7002,7 @@ otp8395({fin, Config}) when is_list(Config) ->
 
     AgentSup = ?config(agent_sup, Config),
     ?DBG("otp8395(fin) -> stop (stand-alone) agent: ~p", [AgentSup]),
-    stop_stdalone_agent(AgentSup), 
+    stop_standalone_agent(AgentSup), 
 
     %% - 
     %% Stop mnesia
@@ -6984,11 +7186,10 @@ start_agent(Config, Opts) ->
     
     %% Nodes
     AgentNode = ?config(agent_node, Config),
-    %% ManagerNode = ?config(manager_node, Config),
     
-    process_flag(trap_exit,true),
+    process_flag(trap_exit, true),
 
-    AgentTopSup = start_stdalone_agent(AgentNode, AgentConfig),
+    AgentTopSup = start_standalone_agent(AgentNode, AgentConfig),
 
     [{agent_sup, AgentTopSup} | Config].
     
@@ -7033,21 +7234,23 @@ process_options(Defaults, _Opts) ->
     Defaults.
 
 
-start_stdalone_agent(Node, Config)  ->
-    rpc:call(Node, ?MODULE, start_stdalone_agent, [Config]).
+start_standalone_agent(Node, Config)  ->
+    rpc:call(Node, ?MODULE, start_standalone_agent, [Config]).
 
-start_stdalone_agent(Config)  ->
+start_standalone_agent(Config)  ->
     case snmpa_supervisor:start_link(normal, Config) of
         {ok, AgentTopSup} ->
             unlink(AgentTopSup),
             AgentTopSup;
         {error, {already_started, AgentTopSup}} ->
-            AgentTopSup
+            AgentTopSup;
+        {error, _} = ERROR ->
+            ERROR
     end.
 
-stop_stdalone_agent(Pid) when (node(Pid) =/= node()) ->
+stop_standalone_agent(Pid) when (node(Pid) =/= node()) ->
     MRef = erlang:monitor(process, Pid),
-    rpc:call(node(Pid), ?MODULE, stop_stdalone_agent, [Pid]),
+    rpc:call(node(Pid), ?MODULE, stop_standalone_agent, [Pid]),
     receive
 	{'DOWN', MRef, process, Pid, _Info} ->
 	    ?DBG("received expected DOWN message "
@@ -7059,7 +7262,7 @@ stop_stdalone_agent(Pid) when (node(Pid) =/= node()) ->
 		 "regarding snmp agent supervisor within time", []),
 	    ok
     end;
-stop_stdalone_agent(Pid) ->
+stop_standalone_agent(Pid) ->
     ?DBG("attempting to terminate agent top-supervisor: ~p", [Pid]),
     nkill(Pid, kill).
 
@@ -7425,11 +7628,30 @@ rcall(Node, Mod, Func, Args) ->
 
 %% ------
 
+%% e(F) ->
+%%     e(F, []).
+
+e(F, A) ->
+    p(user,        "<ERROR> " ++ F, A),
+    p(standard_io, "<ERROR> " ++ F, A).
+
+i(F) ->
+    i(F, []).
+i(F, A) ->
+    p(user,        F, A),
+    p(standard_io, F, A).
+
 p(F) ->
     p(F, []).
 
+p(Dev, F) when is_atom(Dev) ->
+    p(Dev, F, []);
 p(F, A) ->
-    io:format("*** [~s] ***"
+    p(standard_io, F, A).
+
+p(Dev, F, A) ->
+    io:format(Dev,
+              "*** [~s] ***"
               "~n" ++ F ++ "~n", [formated_timestamp()|A]).
 
 formated_timestamp() ->
@@ -7520,7 +7742,7 @@ fin_v1_agent(Config) ->
     %% 
 
     AgentSup = ?config(agent_sup, Config),
-    stop_stdalone_agent(AgentSup), 
+    stop_standalone_agent(AgentSup), 
 
     %% - 
     %% Stop mnesia
diff --git a/lib/snmp/test/snmp_manager_test.erl b/lib/snmp/test/snmp_manager_test.erl
index e2356bd70a..0d171f8359 100644
--- a/lib/snmp/test/snmp_manager_test.erl
+++ b/lib/snmp/test/snmp_manager_test.erl
@@ -55,6 +55,7 @@
 	
 	 simple_start_and_stop1/1,
 	 simple_start_and_stop2/1,
+	 simple_start_and_stop3/1,
 	 simple_start_and_monitor_crash1/1,
 	 simple_start_and_monitor_crash2/1,
 	 notify_started01/1,
@@ -451,6 +452,7 @@ groups() ->
       [
        simple_start_and_stop1, 
        simple_start_and_stop2,
+       simple_start_and_stop3, 
        simple_start_and_monitor_crash1,
        simple_start_and_monitor_crash2, 
        notify_started01,
@@ -728,6 +730,40 @@ do_simple_start_and_stop2(Config) ->
     ok.
 
 
+%%======================================================================
+
+simple_start_and_stop3(suite) -> [];
+simple_start_and_stop3(Config) when is_list(Config) ->
+    ?TC_TRY(simple_start_and_stop3,
+            fun() -> do_simple_start_and_stop3(Config) end).
+
+do_simple_start_and_stop3(Config) ->
+    p("starting with Config: ~n~p", [Config]),
+    ConfDir = ?config(manager_conf_dir, Config),
+    DbDir   = ?config(manager_db_dir, Config),
+
+    write_manager_conf(ConfDir),
+
+    Opts = [{server,     [{verbosity, trace}]},
+	    {net_if,     [{verbosity, trace}, {options, [{extra_sock_opts, ['this-should-not-work']}]}]},
+	    {note_store, [{verbosity, trace}]},
+	    {config,     [{verbosity, trace}, {dir, ConfDir}, {db_dir, DbDir}]}],
+
+    p("try starting manager"),
+    try snmpm:start_link(Opts) of
+        ok ->
+            ?FAIL('unexpected-success')
+    catch
+        _:_ ->
+            p("expected start failure"),
+            ok
+    end,
+
+    ?SLEEP(1000),
+
+    ok.
+
+
 %%======================================================================
 
 simple_start_and_monitor_crash1(suite) -> [];
-- 
2.16.4

openSUSE Build Service is sponsored by