File 4137-Improve-test-case-diagnostics.patch of Package erlang

From 67d5b481b9773e498a8e2d743c3fb6ec3668f904 Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Wed, 19 Oct 2022 15:11:18 +0200
Subject: [PATCH 17/27] Improve test case diagnostics

---
 lib/ssl/test/inet_crypto_dist.erl     | 16 ++++++++--
 lib/ssl/test/ssl_dist_bench_SUITE.erl | 42 ++++++++++++++++++++-------
 2 files changed, 45 insertions(+), 13 deletions(-)

diff --git a/lib/ssl/test/inet_crypto_dist.erl b/lib/ssl/test/inet_crypto_dist.erl
index 1994e6541e..908cf4bbd3 100644
--- a/lib/ssl/test/inet_crypto_dist.erl
+++ b/lib/ssl/test/inet_crypto_dist.erl
@@ -124,6 +124,7 @@ supported() ->
 
 start_key_pair_server() ->
     monitor_dist_proc(
+      key_pair_server,
       spawn_link(
         fun () ->
                 register(?MODULE, self()),
@@ -383,6 +384,7 @@ gen_accept(Listen, Driver) ->
     %% Spawn Acceptor process
     %%
     monitor_dist_proc(
+      acceptor,
       spawn_opt(
         fun () ->
                 start_key_pair_server(),
@@ -453,6 +455,7 @@ gen_accept_connection(
     %% Spawn Controller/handshaker/ticker process
     %%
     monitor_dist_proc(
+      accept_controller,
       spawn_opt(
         fun() ->
                 do_accept(
@@ -495,6 +498,7 @@ gen_setup(Node, Type, MyNode, LongOrShortNames, SetupTime, Driver) ->
     %% Spawn Controller/handshaker/ticker process
     %%
     monitor_dist_proc(
+      setup_controller,
       spawn_opt(
         setup_fun(
           Node, Type, MyNode, LongOrShortNames, SetupTime, Driver, NetKernel),
@@ -825,6 +829,7 @@ start_dist_ctrl(Socket, Timeout) ->
     Controller = self(),
     Server =
         monitor_dist_proc(
+          output_handler,
           spawn_opt(
             fun () ->
                     receive
@@ -1093,6 +1098,7 @@ handshake(
         {?MODULE, From, {handshake_complete, DistHandle}} ->
             InputHandler =
                 monitor_dist_proc(
+                  input_handler,
                   spawn_opt(
                     fun () ->
                             link(Controller),
@@ -1583,14 +1589,18 @@ death_row(Reason) -> receive after 5000 -> exit(Reason) end.
 trace(Term) -> Term.
 
 %% Keep an eye on this Pid (debug)
--ifndef(undefined).
-monitor_dist_proc(Pid) ->
+-ifdef(undefined).
+monitor_dist_proc(_Tag, Pid) ->
     Pid.
 -else.
-monitor_dist_proc(Pid) ->
+monitor_dist_proc(Tag, Pid) ->
     spawn(
       fun () ->
               MRef = erlang:monitor(process, Pid),
+              error_logger:info_report(
+                [monitor_dist_proc,
+                 {type, Tag},
+                 {pid, Pid}]),
               receive
                   {'DOWN', MRef, _, _, normal} ->
                       error_logger:error_report(
diff --git a/lib/ssl/test/ssl_dist_bench_SUITE.erl b/lib/ssl/test/ssl_dist_bench_SUITE.erl
index b5266a158f..40bdcdf367 100644
--- a/lib/ssl/test/ssl_dist_bench_SUITE.erl
+++ b/lib/ssl/test/ssl_dist_bench_SUITE.erl
@@ -416,8 +416,13 @@ sched_utilization(A, B, Prefix, Effort, HA, HB, Config) ->
     SSL = proplists:get_value(ssl_dist, Config),
     [] = ssl_apply(HA, erlang, nodes, []),
     [] = ssl_apply(HB, erlang, nodes, []),
-    ct:log("Starting scheduler utilization run on ~w and ~w", [A, B]),
-    {ClientMsacc, ServerMsacc, Msgs} =
+    PidA = ssl_apply(HA, os, getpid, []),
+    PidB = ssl_apply(HB, os, getpid, []),
+    ct:pal("Starting scheduler utilization run effort ~w:~n"
+           "    [~s] ~w~n"
+           "    [~s] ~w~n",
+           [Effort, PidA, A, PidB, B]),
+    {ClientMsacc, ServerMsacc, BusyDistPortMsgs} =
         ssl_apply(
           HA,
           fun () ->
@@ -427,7 +432,7 @@ sched_utilization(A, B, Prefix, Effort, HA, HB, Config) ->
                     "sched_utilization.Result", Result),
                   Result
           end),
-    ct:log("Got ~p busy_dist_port msgs",[length(Msgs)]),
+    ct:log("Got ~p busy_dist_port msgs",[tail(BusyDistPortMsgs)]),
     [B] = ssl_apply(HA, erlang, nodes, []),
     [A] = ssl_apply(HB, erlang, nodes, []),
     ct:log("Microstate accounting for node ~w:", [A]),
@@ -445,10 +450,13 @@ sched_utilization(A, B, Prefix, Effort, HA, HB, Config) ->
         round(10000 * msacc:stats(system_runtime,ServerMsacc) /
                   msacc:stats(system_realtime,ServerMsacc)),
     Verdict =
-        case Msgs of
-            [] ->
+        if
+            BusyDistPortMsgs =:= 0 ->
                 "";
-            _ ->
+            is_integer(BusyDistPortMsgs) ->
+                " ?";
+            true ->
+                ct:log("Stray Msgs: ~p", [BusyDistPortMsgs]),
                 " ???"
         end,
     {comment, ClientComment} =
@@ -523,7 +531,7 @@ sched_util_runner(A, B, Effort, Senders, Config) ->
         end,
     fs_log(Config, "sched_util_runner.ServerMsaccStats", ServerMsaccStats),
     %%
-    {ClientMsaccStats,ServerMsaccStats, flush()}.
+    {ClientMsaccStats,ServerMsaccStats, busy_dist_port_msgs()}.
 
 fs_log(Config, Name, Term) ->
     PrivDir = proplists:get_value(priv_dir, Config),
@@ -537,14 +545,28 @@ fs_log(Config, Name, Term) ->
              Term}])),
     ok.
 
-flush() ->
+busy_dist_port_msgs() ->
+    busy_dist_port_msgs(0).
+%%
+busy_dist_port_msgs(N) ->
     receive
         M ->
-            [M | flush()]
+            case M of
+                {monitor, P1, busy_dist_port, P2}
+                  when is_pid(P1), is_pid(P2) ->
+                    busy_dist_port_msgs(N + 1);
+                Stray ->
+                    [Stray | busy_dist_port_msgs(N)]
+            end
     after 0 ->
-            []
+            N
     end.
 
+tail([_|Tail]) ->
+    tail(Tail);
+tail(Tail) ->
+    Tail.
+
 throughput_server() ->
     receive _ -> ok end,
     receive _ -> ok end,
-- 
2.35.3

openSUSE Build Service is sponsored by