File 1134-snmp-Tweaked-proxy-call.patch of Package erlang

From c2620db469e3b4e2c366382301fa1af75dcc8a95 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Mon, 14 Oct 2024 18:27:40 +0200
Subject: [PATCH] [snmp] Tweaked proxy-call

---
 lib/snmp/test/snmp_manager_SUITE.erl | 83 ++++++++++++++++++--------
 lib/snmp/test/snmp_test_lib.erl      | 87 ++++++++++++++++++++++++++--
 lib/snmp/test/snmp_test_lib.hrl      |  1 +
 3 files changed, 142 insertions(+), 29 deletions(-)

diff --git a/lib/snmp/test/snmp_manager_SUITE.erl b/lib/snmp/test/snmp_manager_SUITE.erl
index fba9b527d7..63a57ec49f 100644
--- a/lib/snmp/test/snmp_manager_SUITE.erl
+++ b/lib/snmp/test/snmp_manager_SUITE.erl
@@ -1218,11 +1218,19 @@ simulate_crash(NumKills, _) ->
 
 notify_started01(suite) -> [];
 notify_started01(Config) when is_list(Config) ->
-    ?TC_TRY(notify_started01,
-            fun() -> do_notify_started01(Config) end).
+    Cond = fun() -> ok end,
+    Pre  = fun() -> ok end,
+    TC   = fun(_) -> do_notify_started01(Config) end,
+    Post = fun(_) ->
+                   ?IPRINT("[post] ensure snmpm not running"),
+                   ?ENSURE_NOT_RUNNING(snmpm_supervisor,
+                                       fun() -> snmpm:stop() end,
+                                       1000)
+           end,
+    ?TC_TRY(?FUNCTION_NAME, Cond, Pre, TC, Post).
 
 do_notify_started01(Config) ->
-    ?IPRINT("starting with Config: "
+    ?IPRINT("[tc] starting with Config: "
             "~n      ~p", [Config]),
 
     SCO     = ?config(socket_create_opts, Config),
@@ -1236,11 +1244,11 @@ do_notify_started01(Config) ->
 	    {note_store, [{verbosity, silence}]},
 	    {config,     [{verbosity, log}, {dir, ConfDir}, {db_dir, DbDir}]}],
 
-    ?IPRINT("request start notification (1)"),
+    ?IPRINT("[tc] request start notification (1)"),
     Pid1 = snmpm:notify_started(10000),
     receive
 	{snmpm_start_timeout, Pid1} ->
-	    ?IPRINT("received expected start timeout"),
+	    ?IPRINT("[tc] received expected start timeout"),
 	    ok;
 	Any1 ->
 	    ?FAIL({unexpected_message, Any1})
@@ -1248,25 +1256,41 @@ do_notify_started01(Config) ->
 	    ?FAIL({unexpected_timeout, Pid1})
     end,
 
-    ?IPRINT("request start notification (2)"),
+    ?IPRINT("[tc] request start notification (2)"),
     Pid2 = snmpm:notify_started(10000),
 
-    ?IPRINT("start the snmpm starter"),
-    Pid = snmpm_starter(Opts, 5000),
+    ?IPRINT("[tc] start the snmpm starter"),
+    StarterPid = snmpm_starter(Opts, 5000),
 
-    ?IPRINT("await the start notification"),
+    ?IPRINT("[tc] await the start notification"),
     Ref = 
 	receive
 	    {snmpm_started, Pid2} ->
-		?IPRINT("received started message -> create the monitor"),
+		?IPRINT("[tc] received start notification message -> "
+                        "create the monitor"),
 		snmpm:monitor();
+            {snmpm_start_timeout, StarterPid} ->
+                ?EPRINT("[tc] Start Timeout: "
+                        "~n   Starter Process (~p) Info: ~p",
+                        [StarterPid, (catch erlang:process_info(StarterPid))]),
+                ?FAIL(start_timeout);
 	    Any2 ->
+                ?EPRINT("[tc] Unexpected Message: "
+                        "~n   Notify Process Info:  ~p"
+                        "~n   Starter Process info: ~p",
+                        [(catch erlang:process_info(Pid2)),
+                         (catch erlang:process_info(StarterPid))]),
 		?FAIL({unexpected_message, Any2})
 	after 15000 ->
-		?FAIL({unexpected_timeout, Pid2})
+                ?EPRINT("[tc] Unexpected Start Timeout: "
+                        "~n   Notify Process Info:  ~p"
+                        "~n   Starter Process info: ~p",
+                        [(catch erlang:process_info(Pid2)),
+                         (catch erlang:process_info(StarterPid))]),
+		?FAIL(unexpected_start_timeout)
 	end,
 
-    ?IPRINT("[~p] make sure it has not already crashed...", [Ref]),
+    ?IPRINT("[tc] make sure it (~p) has not already crashed...", [Ref]),
     receive
 	{'DOWN', Ref, process, Obj1, Reason1} ->
 	    ?FAIL({unexpected_down, Obj1, Reason1})
@@ -1274,13 +1298,14 @@ do_notify_started01(Config) ->
 	    ok
     end,
 
-    ?IPRINT("stop the manager"),
-    Pid ! {stop, self()}, %ok = snmpm:stop(),
+    ?IPRINT("[tc] stop the manager (send stop to starter process ~p)",
+            [StarterPid]),
+    StarterPid ! {stop, self()}, %ok = snmpm:stop(),
 
-    ?IPRINT("await the down-message"),
+    ?IPRINT("[tc] await the down-message"),
     receive
 	{'DOWN', Ref, process, Obj2, Reason2} ->
-	    ?IPRINT("received expected down-message: "
+	    ?IPRINT("[tc] received expected down-message: "
                     "~n   Obj2:    ~p"
                     "~n   Reason2: ~p", 
                     [Obj2, Reason2]),
@@ -1264,7 +1264,7 @@ do_notify_started01(Config) ->
 	    ?FAIL(down_timeout)
     end,
 
-    ?IPRINT("end"),
+    ?IPRINT("[tc] end"),
     ok.
 
 
@@ -1272,12 +1272,20 @@ snmpm_starter(Opts, To) ->
     Parent = self(),
     spawn(
       fun() -> 
-	      ?SLEEP(To), 
-	      ok = snmpm:start(Opts),
+      fun() ->
+              ?IPRINT("[snmpm-starter] wait ~w msec", [To]),
+	      ?SLEEP(To),
+              ?IPRINT("[snmpm-starter] try start snmpm"),
+	      ok = ?PCALL(fun() -> snmpm:start(Opts) end,
+                          To, 1000, {error, timeout}),
+              ?IPRINT("[snmpm-starter] snmpm started - await stop command"),
 	      receive
 		  {stop, Parent} ->
+                      ?IPRINT("[snmpm-starter] received stop command"),
 		      snmpm:stop()
-	      end
+	      end,
+              ?IPRINT("[snmpm-starter] done"),
+              ok
       end).
 
 
@@ -1285,7 +1293,7 @@ snmpm_starter(Opts, To) ->
 
 notify_started02(suite) -> [];
 notify_started02(Config) when is_list(Config) ->
-    ?TC_TRY(notify_started02,
+    ?TC_TRY(?FUNCTION_NAME,
             fun() -> notify_started02_cond(Config) end,
             fun() -> do_notify_started02(Config) end).
 
@@ -1344,9 +1376,12 @@ do_notify_started02(Config) ->
     write_manager_conf(ConfDir),
 
     Opts = [{server,     [{verbosity, log}]},
-	    {net_if,     [{verbosity, silence}, {options, SCO}]},
+	    {net_if,     [{verbosity, silence},
+                          {options,   SCO}]},
 	    {note_store, [{verbosity, silence}]},
-	    {config,     [{verbosity, debug}, {dir, ConfDir}, {db_dir, DbDir}]}],
+	    {config,     [{verbosity, debug},
+                          {dir,       ConfDir},
+                          {db_dir,    DbDir}]}],
 
     ?IPRINT("start snmpm client process"),
     NumIterations = 5,
diff --git a/lib/snmp/test/snmp_test_lib.erl b/lib/snmp/test/snmp_test_lib.erl
index 49df6db0ee..6e354d5510 100644
--- a/lib/snmp/test/snmp_test_lib.erl
+++ b/lib/snmp/test/snmp_test_lib.erl
@@ -25,7 +25,7 @@
 
 -export([tc_try/2, tc_try/3,
          tc_try/4, tc_try/5]).
--export([proxy_call/3]).
+-export([proxy_call/3, proxy_call/4]).
 -export([hostname/0, hostname/1, localhost/0, localhost/1, sz/1,
 	 display_suite_info/1]).
 -export([non_pc_tc_maybe_skip/4,
@@ -294,18 +294,89 @@ test_inet_backends() ->
 
 
 
-proxy_call(F, Timeout, Default)
-  when is_function(F, 0) andalso is_integer(Timeout) andalso (Timeout > 0) ->
-    {P, M} = erlang:spawn_monitor(fun() -> exit(F()) end),
+proxy_call(F, Timeout, Default) ->
+    proxy_call(F, Timeout, infinity, Default).
+
+proxy_call(F, Timeout, PollTimeout, Default)
+  when is_function(F, 0) andalso
+       is_integer(Timeout) andalso (Timeout > 0) andalso
+       ((PollTimeout =:= infinity) orelse
+        (is_integer(PollTimeout) andalso (PollTimeout > 0))) ->
+    PollTimer = poll_timer_start(Timeout, PollTimeout),
+    iprint("[proxy-init] create proxy", []),
+    {P, M}    = erlang:spawn_monitor(fun() -> exit(F()) end),
+    pc_loop(P, M, Timeout, PollTimer, Default).
+
+pc_loop(P, M, Timeout, PollTimer, Default) ->
+    T0 = t(),
     receive
         {'DOWN', M, process, P, Reply} ->
-            Reply
+            iprint("[proxy-loop] received result: "
+                   "~n   ~p", [Reply]),
+            Reply;
+        {?MODULE, poll, PollTimeout} ->
+            iprint("[proxy-loop] Poll proxy: "
+                   "~n   Current Function:   ~p"
+                   "~n   Current Stacktrace: ~p"
+                   "~n   Reductions:         ~p"
+                   "~n   Memory:             ~p"
+                   "~n   Heap Size:          ~p"
+                   "~n   Max Heap Size:      ~p"
+                   "~n   Total Heap Size:    ~p"
+                   "~n   Status:             ~p",
+                   [pi(P, current_function),
+                    pi(P, current_stacktrace),
+                    pi(P, reductions),
+                    pi(P, memory),
+                    pi(P, heap_size),
+                    pi(P, max_heap_size),
+                    pi(P, total_heap_size),
+                    pi(P, status)]),
+            Timeout2   = t(T0, Timeout),
+            PollTimer2 = poll_timer_start(Timeout2, PollTimeout),
+            pc_loop(P, M, Timeout2, PollTimer2, Default)
+
     after Timeout ->
+            wprint("[proxy-loop] timeout: "
+                   "~n   Current Function:   ~p"
+                   "~n   Current Stacktrace: ~p"
+                   "~n   Reductions:         ~p"
+                   "~n   Memory:             ~p"
+                   "~n   Heap Size:          ~p"
+                   "~n   Max Heap Size:      ~p"
+                   "~n   Total Heap Size:    ~p"
+                   "~n   Status:             ~p",
+                   [pi(P, current_function),
+                    pi(P, current_stacktrace),
+                    pi(P, reductions),
+                    pi(P, memory),
+                    pi(P, heap_size),
+                    pi(P, max_heap_size),
+                    pi(P, total_heap_size),
+                    pi(P, status)]),
+            poll_timer_stop(PollTimer),
             erlang:demonitor(M, [flush]),
             exit(P, kill),
             Default
     end.
 
+poll_timer_start(_Timeout, PollTimeout)
+  when (PollTimeout =:= infinity) ->
+    undefined;
+poll_timer_start(Timeout, PollTimeout)
+  when (Timeout > PollTimeout) ->
+    erlang:send_after(PollTimeout, self(), {?MODULE, poll, PollTimeout});
+poll_timer_start(_, _) ->
+    undefined.
+
+poll_timer_stop(TRef) when is_reference(TRef) ->
+    erlang:cancel_timer(TRef);
+poll_timer_stop(_) ->
+    ok.
+
+t(T0, T)  -> T - (t() - T0).
+t()       -> snmp_misc:now(ms).
+
 
 hostname() ->
     hostname(node()).
@@ -3345,6 +3416,12 @@ del_file_or_dir(FileOrDir) ->
     end.
 	    
 
+%% ----------------------------------------------------------------------
+
+pi(P, Key) ->
+    {Key, Value} = erlang:process_info(P, Key),
+    Value.
+
 %% ----------------------------------------------------------------------
 %% (debug) Print functions
 %%
diff --git a/lib/snmp/test/snmp_test_lib.hrl b/lib/snmp/test/snmp_test_lib.hrl
index f57f2b0e35..4e85b5e28a 100644
--- a/lib/snmp/test/snmp_test_lib.hrl
+++ b/lib/snmp/test/snmp_test_lib.hrl
@@ -61,6 +61,7 @@
 -define(HAS_SUPPORT_IPV6(),  ?LIB:has_support_ipv6()).
 
 -define(PCALL(F, T, D),      ?LIB:proxy_call(F, T, D)).
+-define(PCALL(F, T, PT, D),  ?LIB:proxy_call(F, T, PT, D)).
 
 
 %% - Time macros -
-- 
2.43.0

openSUSE Build Service is sponsored by