File 1781-megaco-test-Add-bench-test-group-in-the-load-suite.patch of Package erlang

From e25db6077354b3296f55556db9ceb6746dd354b7 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Thu, 18 Dec 2025 06:46:21 +0100
Subject: [PATCH 1/2] [megaco|test] Add bench test group in the load suite

Add bench(mark) related groups.
Cleanup of the load suite in prep for bench-ification.
Also fixed calculation for multi-user-load cases.
Add value checks to ensure usefull result
Add megaco_load_SUITE (bench) to the bench spec file
---
 lib/megaco/test/megaco_bench.spec     |   1 +
 lib/megaco/test/megaco_load_SUITE.erl | 338 +++++++++++++++++++-------
 2 files changed, 252 insertions(+), 87 deletions(-)

diff --git a/lib/megaco/test/megaco_bench.spec b/lib/megaco/test/megaco_bench.spec
index 5129b94f78..bf8da1a54d 100644
--- a/lib/megaco/test/megaco_bench.spec
+++ b/lib/megaco/test/megaco_bench.spec
@@ -21,3 +21,4 @@
 %%
 
 {groups,"../megaco_test",megaco_examples_SUITE,[bench]}.
+{groups,"../megaco_test",megaco_load_SUITE,[bench]}.
diff --git a/lib/megaco/test/megaco_load_SUITE.erl b/lib/megaco/test/megaco_load_SUITE.erl
index bbae47b364..c88a96c60d 100644
--- a/lib/megaco/test/megaco_load_SUITE.erl
+++ b/lib/megaco/test/megaco_load_SUITE.erl
@@ -71,6 +71,7 @@
 
 
 -include_lib("common_test/include/ct.hrl").
+-include_lib("common_test/include/ct_event.hrl").
 -include_lib("megaco/include/megaco.hrl").
 -include_lib("megaco/include/megaco_message_v1.hrl").
 -include("megaco_test_lib.hrl").
@@ -105,6 +106,8 @@
 -define(MG_SET_VERBOSITY(Pid, V), megaco_test_mg:verbosity(Pid, V)).
 
 
+-define(BENCH_SUITE, megaco_load).
+
 
 %%======================================================================
 %% Common Test interface functions
@@ -114,7 +117,7 @@ suite() ->
     [{ct_hooks, [ts_install_cth]}].
 
 all() -> 
-    %% This is a temporary messure to ensure that we can 
+    %% This is a "temporary" messure to ensure that we can 
     %% test the socket backend without effecting *all*
     %% applications on *all* machines.
     %% This flag is set only for *one* host.
@@ -137,21 +140,27 @@ groups() ->
      {inet_backend_inet,    [], inet_backend_inet_cases()},
      {inet_backend_socket,  [], inet_backend_socket_cases()},
 
-     {all,                  [], all_cases()},
+     {standard,             [], standard_cases()},
      {single,               [], single_cases()},
-     {multi,                [], multi_cases()}
+     {multi,                [], multi_cases()},
+
+     %% "special" group(s) - only run explicitly
+     {bench,                [], bench_cases()},
+     {bench_single,         [], bench_single_cases()},
+     {bench_multi,          [], bench_multi_cases()}
+     
     ].
 
 inet_backend_default_cases() ->
-    [{all, [], all_cases()}].
+    [{standard, [], standard_cases()}].
 
 inet_backend_inet_cases() ->
-    [{all, [], all_cases()}].
+    [{standard, [], standard_cases()}].
 
 inet_backend_socket_cases() ->
-    [{all, [], all_cases()}].
+    [{standard, [], standard_cases()}].
 
-all_cases() -> 
+standard_cases() ->
     [
      {group, single},
      {group, multi}
@@ -172,7 +181,27 @@ multi_cases() ->
      multi_user_heavy_load,
      multi_user_extreme_load
     ].
-    
+
+
+bench_cases() ->
+    [
+     {group, bench_single},
+     {group, bench_multi}
+    ].
+
+bench_single_cases() ->
+    [
+     single_user_light_load,
+     single_user_medium_load
+    ].
+
+bench_multi_cases() ->
+    [
+     multi_user_light_load,
+     multi_user_medium_load
+    ].
+
+
 
 
 %%
@@ -228,6 +257,18 @@ end_per_suite(Config0) when is_list(Config0) ->
 %% -----
 %%
 
+init_per_group(bench = Group, Config) ->
+    ?ANNOUNCE_GROUP_INIT(Group),
+    [{category, Group}, {socket_create_opts, []} | Config];
+init_per_group(standard = Group, Config) ->
+    ?ANNOUNCE_GROUP_INIT(Group),
+    %% Just in case someone runs the group directly
+    case ?config(socket_create_opts, Config) of
+        undefined ->
+            [{category, Group}, {socket_create_opts, []} | Config];
+        _ ->
+            [{category, Group} | Config]
+    end;
 init_per_group(inet_backend_default = Group, Config) ->
     ?ANNOUNCE_GROUP_INIT(Group),
     [{socket_create_opts, []} | Config];
@@ -327,7 +368,7 @@ single_user_light_load(suite) ->
 single_user_light_load(doc) ->
     [];
 single_user_light_load(Config) when is_list(Config) ->
-    try_single_user_load(single_user_light_load, Config, 5).
+    try_single_user_load(?FUNCTION_NAME, single_user_light, Config, 5).
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -337,7 +378,7 @@ single_user_medium_load(suite) ->
 single_user_medium_load(doc) ->
     [];
 single_user_medium_load(Config) when is_list(Config) ->
-    try_single_user_load(single_user_medium_load, Config, 15).
+    try_single_user_load(?FUNCTION_NAME, single_user_medium, Config, 15).
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -347,7 +388,7 @@ single_user_heavy_load(suite) ->
 single_user_heavy_load(doc) ->
     [];
 single_user_heavy_load(Config) when is_list(Config) ->
-    try_single_user_load(single_user_heavy_load, Config, 25).
+    try_single_user_load(?FUNCTION_NAME, single_user_high, Config, 25).
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -357,7 +398,7 @@ single_user_extreme_load(suite) ->
 single_user_extreme_load(doc) ->
     [];
 single_user_extreme_load(Config) when is_list(Config) ->
-    try_single_user_load(single_user_extreme_load, Config, 100).
+    try_single_user_load(?FUNCTION_NAME, single_user_extreme, Config, 100).
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -367,7 +408,7 @@ multi_user_light_load(suite) ->
 multi_user_light_load(doc) ->
     [];
 multi_user_light_load(Config) when is_list(Config) ->
-    try_multi_user_load(multi_user_light_load, Config, 3, 1).
+    try_multi_user_load(?FUNCTION_NAME, multi_user_light, Config, 3, 2).
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -377,7 +418,7 @@ multi_user_medium_load(suite) ->
 multi_user_medium_load(doc) ->
     [];
 multi_user_medium_load(Config) when is_list(Config) ->
-    try_multi_user_load(multi_user_medium_load, Config, 3, 5).
+    try_multi_user_load(?FUNCTION_NAME, multi_user_medium, Config, 3, 5).
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -387,7 +428,7 @@ multi_user_heavy_load(suite) ->
 multi_user_heavy_load(doc) ->
     [];
 multi_user_heavy_load(Config) when is_list(Config) ->
-    try_multi_user_load(multi_user_heavy_load, Config, 3, 10).
+    try_multi_user_load(?FUNCTION_NAME, multi_user_high, Config, 3, 10).
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -397,7 +438,7 @@ multi_user_extreme_load(suite) ->
 multi_user_extreme_load(doc) ->
     [];
 multi_user_extreme_load(Config) when is_list(Config) ->
-    try_multi_user_load(multi_user_extreme_load, Config, 3, 15).
+    try_multi_user_load(?FUNCTION_NAME, multi_user_extreme, Config, 3, 15).
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -416,41 +457,46 @@ load_controller(Config, Fun) when is_list(Config) and is_function(Fun) ->
     Env = get(),
     Loader = erlang:spawn_link(fun() -> Fun(Env) end),
     receive
+	{'EXIT', Loader, {comment, _} = Comment} ->
+	    d("~s -> "
+	      "loader [~p] terminated with comment", [?FUNCTION_NAME, Loader]),
+	    Comment;
 	{'EXIT', Loader, normal} ->
-	    d("load_controller -> "
-	      "loader [~p] terminated with normal", [Loader]),
+	    d("~s -> "
+	      "loader [~p] terminated with normal", [?FUNCTION_NAME, Loader]),
 	    ok;
 	{'EXIT', Loader, ok} ->
-	    d("load_controller -> "
-	      "loader [~p] terminated with ok~n", [Loader]),
+	    d("~s -> "
+	      "loader [~p] terminated with ok~n", [?FUNCTION_NAME, Loader]),
 	    ok;
 	{'EXIT', Loader, {skipped, {fatal, Reason, File, Line}}} ->
-	    i("load_controller -> "
+	    i("~s -> "
 	      "loader [~p] terminated with fatal skip"
 	      "~n   Reason: ~p"
-	      "~n   At:     ~p:~p", [Loader, Reason, File, Line]),
+	      "~n   At:     ~p:~p", [?FUNCTION_NAME, Loader, Reason, File, Line]),
 	    ?SKIP(Reason);
 	{'EXIT', Loader, {skipped, Reason}} ->
-	    i("load_controller -> "
+	    i("~s_controller -> "
 	      "loader [~p] terminated with skip"
-	      "~n   Reason: ~p", [Loader, Reason]),
+	      "~n   Reason: ~p", [?FUNCTION_NAME, Loader, Reason]),
 	    ?SKIP(Reason);
 	{'EXIT', Loader, Reason} ->
-	    i("load_controller -> "
+	    i("~s -> "
 	      "loader [~p] terminated with"
-	      "~n   ~p", [Loader, Reason]),
+	      "~n   ~p", [?FUNCTION_NAME, Loader, Reason]),
 	    erlang:error({unexpected_loader_result, Reason})
     after SkipTimeout ->
-	    i("load_controller -> "
-	      "loader [~p] timeout", [Loader]),
+	    i("~s -> "
+	      "loader [~p] timeout", [?FUNCTION_NAME, Loader]),
 	    exit(Loader, kill),
 	    ?SKIP({timeout, SkipTimeout, TcTimeout})
     end.
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-try_single_user_load(Name, Config, NumLoaders0) ->
+try_single_user_load(Name, BenchName, Config, NumLoaders0) ->
     Factor     = ?config(megaco_factor, Config),
+    Category   = ?config(category,      Config),
     NumLoaders =
 	if
 	    (Factor =:= 1) ->
@@ -468,10 +514,12 @@ try_single_user_load(Name, Config, NumLoaders0) ->
 		    "~n      MgNode:  ~p", [MgcNode, MgNode]),
 		  Nodes = [MgcNode, MgNode],
 		  ok = ?START_NODES(Nodes),
-		  Nodes
+		  #{bench_name => BenchName,
+                    category   => Category,
+                    nodes      => Nodes}
 	  end,
     Case = fun(State) -> single_user_load(State, Config, NumLoaders) end,
-    Post = fun(Nodes) ->
+    Post = fun(#{nodes := Nodes}) ->
                    d("stop nodes"),
                    ?STOP_NODES(lists:reverse(Nodes))
            end,
@@ -491,7 +539,10 @@ single_user_load(State, Config, NumLoaders) ->
     Res.
 
 do_single_user_load(SCO,
-                    [MgcNode, MgNode], NumLoaders) ->
+                    #{bench_name := BenchName,
+                      category   := Category,
+                      nodes      := [MgcNode, MgNode]},
+                    NumLoaders) ->
     %% Start the MGC and MGs
     i("[MGC] start"),
     MgcMid = {deviceName, "ctrl"},
@@ -515,20 +566,60 @@ do_single_user_load(SCO,
     d("MG conn info: ~p", [?MG_CONN_INFO(Mg, all)]),
 
     d("apply the load"),
-    Res = ?MG_MLOAD(Mg, NumLoaders, ?SINGLE_USER_LOAD_NUM_REQUESTS),
-    case Res of
-	{Time, {ok, Ok, Err}} ->
-	    Sec = Time / 1000000,
-	    io:format("~nmultiple loaders result: ~n"
-		      "   Number of successfull: ~w~n"
-		      "   Number of failure:     ~w~n"
-		      "   Time:                  ~w seconds~n"
-		      "   Calls / seconds        ~w~n~n", 
-		      [Ok, Err, Sec, (NumLoaders * ?SINGLE_USER_LOAD_NUM_REQUESTS)/Sec]);
-	{Time, Error} ->
-	    io:format("SUL: multiple loaders failed: ~p after ~w~n", 
-		      [Error, Time])
-    end,
+    LoadRes = ?MG_MLOAD(Mg, NumLoaders, ?SINGLE_USER_LOAD_NUM_REQUESTS),
+    {CResult, Result} =
+        case LoadRes of
+            {Time, {ok, Ok, Err}} ->
+                MSec = Time div 1000,
+                %% Just to be on the safe side we check that the
+                %% number of successsful calls is greater than or equal to
+                %% the (run) time in msec (otherwise the "performance" result
+                %% will be zero)
+                NumCalls = Ok * ?SINGLE_USER_LOAD_NUM_REQUESTS,
+                if
+                    (NumCalls > MSec) ->
+                        %% Each successful loader has performed
+                        %% ?SINGLE_USER_LOAD_NUM_REQUESTS calls
+                        %% Also, should we even count a loader that
+                        %% has registered fails? We do not know
+                        %% if a failed loader managed any requests...
+                        Perf = NumCalls div MSec,
+                        io:format("~nMultiple loaders result: ~n"
+                                  "   Number of successfull:     ~w~n"
+                                  "   Number of failure:         ~w~n"
+                                  "   Time:                      ~w msec~n"
+                                  "   (successful) Calls / msec: ~w~n~n", 
+                                  [Ok, Err, MSec, Perf]),
+                        {
+                         {comment, ?F("~w calls / msec", [Perf])},
+                         Perf
+                        };
+
+                    %% The resulting "performance" will be 0 (calls / msec),
+                    %% so either we are running on a really slow machine or
+                    %% something went wrong (lots of errors?).
+                    %% Either way, do not report this, will only skew the
+                    %% results.
+
+                    (Ok > 0) ->
+                        Sec  = Time div 10000000,
+                        Perf = NumCalls div Sec,
+                        io:format("~nMultiple loaders result: ~n"
+                                  "   Number of successfull:    ~w~n"
+                                  "   Number of failure:        ~w~n"
+                                  "   Time:                     ~w sec~n"
+                                  "   (successful) Calls / sec: ~w~n~n", 
+                                  [Ok, Err, Sec, Perf]),
+                        {
+                         {comment, ?F("~w calls / sec", [Perf])},
+                         undefined
+                        }
+                end;
+            {Time, Error} ->
+                io:format("SUL: multiple loaders failed: ~p after ~w~n", 
+                          [Error, Time]),
+                {Error, undefined}
+        end,
 
     i("flush the message queue: ~p", [megaco_test_lib:flush()]),
     
@@ -547,15 +638,25 @@ do_single_user_load(SCO,
     ?MGC_STOP(Mgc),
 
     i("flush the message queue: ~p", [megaco_test_lib:flush()]),
-    
-    ok.
+
+    maybe_publish_result(Category, BenchName, Result),
+    CResult.
 
 
+maybe_publish_result(bench = _Category,
+                     Name, Result) when (Result =/= undefined) ->
+    Event = ?BENCH_EVENT(Name, Result),
+    ct_event:notify(Event);
+maybe_publish_result(_, _, _) ->
+    ok.
+
+    
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
-try_multi_user_load(Name, Config, NumUsers, NumLoaders0) ->
+try_multi_user_load(Name, BenchName, Config, NumUsers, NumLoaders0) ->
     Factor     = ?config(megaco_factor, Config),
+    Category   = ?config(category,      Config),
     NumLoaders =
 	if
 	    (Factor =:= 1) ->
@@ -573,12 +674,14 @@ try_multi_user_load(Name, Config, NumUsers, NumLoaders0) ->
 		    "~n      MgNodes: ~p", [MgcNode, MgNodes]),
 		  Nodes = [MgcNode | MgNodes],
 		  ok = ?START_NODES(Nodes),
-		  Nodes
+		  #{bench_name => BenchName,
+                    category   => Category,
+                    nodes      => Nodes}
 	  end,
     Case = fun(State) ->
 		   multi_user_load(State, Config, NumUsers, NumLoaders)
 	   end,
-    Post = fun(Nodes) ->
+    Post = fun(#{nodes := Nodes}) ->
                    d("stop nodes"),
                    ?STOP_NODES(lists:reverse(Nodes))
            end,
@@ -598,7 +701,11 @@ multi_user_load(State, Config, NumUsers, NumLoaders) ->
     Res.
 
 
-do_multi_user_load(SCO, [MgcNode | MgNodes], NumUsers, NumLoaders) 
+do_multi_user_load(SCO,
+                   #{bench_name := BenchName,
+                     category   := Category,
+                     nodes      := [MgcNode | MgNodes]},
+                   NumUsers, NumLoaders) 
   when (is_integer(NumUsers) andalso (NumUsers > 1) andalso 
 	is_integer(NumLoaders) andalso (NumLoaders >= 1)) ->
     %% Start the MGC and MGs
@@ -614,7 +721,9 @@ do_multi_user_load(SCO, [MgcNode | MgNodes], NumUsers, NumLoaders)
     MgUsers = make_mids(MgNodes),
 
     d("start MGs, apply the load and stop MGs"),
-    ok = multi_load(MgUsers, SCO ++ DSI, NumLoaders, ?MULTI_USER_LOAD_NUM_REQUESTS),
+    {CResult, Result} =
+        multi_load(MgUsers, SCO ++ DSI, NumLoaders,
+                   ?MULTI_USER_LOAD_NUM_REQUESTS),
 
     i("flush the message queue: ~p", [megaco_test_lib:flush()]),
 
@@ -626,7 +735,8 @@ do_multi_user_load(SCO, [MgcNode | MgNodes], NumUsers, NumLoaders)
 
     i("flush the message queue: ~p", [megaco_test_lib:flush()]),
 
-    ok.
+    maybe_publish_result(Category, BenchName, Result),
+    CResult.
 
 
 multi_load(MGs, Conf, NumLoaders, NumReqs) ->
@@ -638,12 +748,15 @@ multi_load(MGs, Conf, NumLoaders, NumReqs) ->
     Pids = multi_load_collector_start(MGs, Conf, NumLoaders, NumReqs, []),
     case timer:tc(?MODULE, do_multi_load, [Pids, NumLoaders, NumReqs]) of
 	{Time, {ok, OKs, []}} ->
-	    Sec = Time / 1000000,
-	    multi_load_collector_calc(Sec, OKs);
+	    multi_load_collector_calc(Time, OKs);
 	{Time, Error} ->
-	    Sec = Time/1000000,
-	    io:format("~nmulti load failed after ~.1f:~n~p~n~n", [Sec,Error]),
-	    {error, Error}
+	    MSec = Time/1000,
+	    io:format("~nmulti load failed after ~.1f msec:~n~p~n~n",
+                      [MSec,Error]),
+	    {
+             {comment, ?F("~p", [Error])},
+             undefined
+            }
     end.
 
 do_multi_load(Pids, _NumLoaders, _NumReqs) ->
@@ -688,7 +801,7 @@ multi_load_collector(Parent, Node, Mid, Conf, NumLoaders, NumReqs, Env) ->
     end.
 
 multi_load_collector_loop(Parent, Pid, Mid, NumLoaders, NumReqs) ->
-    d("multi_load_collector_loop -> entry with"
+    d("~s -> entry with"
       "~n   Parent:     ~p"
       "~n   Pid:        ~p"
       "~n   Mid:        ~p"
@@ -697,10 +810,13 @@ multi_load_collector_loop(Parent, Pid, Mid, NumLoaders, NumReqs) ->
       "~nwhen"
       "~n   self():     ~p"
       "~n   node():     ~p", 
-      [Parent, Pid, Mid, NumLoaders, NumReqs, self(), node()]),
+      [?FUNCTION_NAME, Parent, Pid, Mid, NumLoaders, NumReqs, self(), node()]),
     receive
 	{apply_multi_load, Parent} ->
+            d("~s -> apply load (~w, ~w)",
+              [?FUNCTION_NAME, NumLoaders, NumReqs]),
 	    Res = ?MG_LOAD(Pid, NumLoaders, NumReqs),
+            d("~s -> load result: ~p", [?FUNCTION_NAME, Res]),
 	    Parent ! {load_complete, self(), Mid, Res},
 	    ?MG_SET_VERBOSITY(Pid, debug),
 	    ?MG_STOP(Pid),
@@ -714,31 +830,32 @@ await_multi_load_collectors([], Oks, Errs) ->
 await_multi_load_collectors(Pids, Oks, Errs) ->
     receive
 	{load_complete, Pid, Mg, {ok, Ok, Err}} ->
-	    i("await_multi_load_collectors -> "
-	      "received ok complete from "
-	      "~n   ~p [~p]", [Pid, Mg]),
+	    i("~s -> "
+	      "received ok complete: "
+	      "~n   From:   ~p [~p]"
+	      "~n   Result: ~p, ~p", [?FUNCTION_NAME, Pid, Mg, Ok, Errs]),
 	    Pids2 = lists:keydelete(Pid, 1, Pids),
 	    Oks2  = [{Mg, Ok, Err}|Oks],
 	    await_multi_load_collectors(Pids2, Oks2, Errs);
 	{load_complete, Pid, Mg, Error} ->
-	    i("await_multi_load_collectors -> "
-	      "received error complete from "
-	      "~n   ~p [~p]: "
-	      "~n   ~p", [Pid, Mg, Error]),
+	    i("~s -> "
+	      "received error complete: "
+	      "~n   From:  ~p [~p]: "
+	      "~n   Error: ~p", [?FUNCTION_NAME, Pid, Mg, Error]),
 	    Pids2 = lists:keydelete(Pid, 1, Pids),
 	    Errs2 = [{Mg, Error}|Errs],
 	    await_multi_load_collectors(Pids2, Oks, Errs2);
 
 	{'EXIT', Pid, normal} ->
 	    %% This is assumed to be one of the collectors
-	    i("await_multi_load_collectors -> "
-	      "received (normal) exit signal from ~p", [Pid]),
+	    i("~s -> "
+	      "received (normal) exit signal from ~p", [?FUNCTION_NAME, Pid]),
 	    await_multi_load_collectors(Pids, Oks, Errs);
 
 	{'EXIT', Pid, Reason} ->
-	    i("await_multi_load_collectors -> "
+	    i("~s -> "
 	      "received unexpected exit from ~p:"
-	      "~n   ~p", [Pid, Reason]),
+	      "~n   ~p", [?FUNCTION_NAME, Pid, Reason]),
 	    case lists:keydelete(Pid, 1, Pids) of
 		Pids ->
 		    %% Not one of my procs, or a proc I have already
@@ -751,29 +868,76 @@ await_multi_load_collectors(Pids, Oks, Errs) ->
 	    end;
 
 	Else ->
-	    i("await_multi_load_collectors -> received unexpected message:"
-	      "~n~p", [Else]),
+	    i("~s -> received unexpected message:"
+	      "~n~p", [?FUNCTION_NAME, Else]),
 	    await_multi_load_collectors(Pids, Oks, Errs)
     after 
 	5000 ->
-	    i("await_multi_load_collectors -> still awaiting reply from:"
-	      "~n~p", [Pids]),
+	    i("~s -> still awaiting reply from:"
+	      "~n~p", [?FUNCTION_NAME, Pids]),
 	    await_multi_load_collectors(Pids, Oks, Errs)
     end.
 	    
 		
 %% Note that this is an approximation...we run all the
-%% MGs in parrallel, so it should be "accurate"...
-multi_load_collector_calc(Sec, Oks) ->
-    Succs = lists:sum([Ok   || {_, Ok,   _} <- Oks]),
-    Fails = lists:sum([Err  || {_,  _, Err} <- Oks]),
-    io:format("~ntotal multiple loaders result: ~n"
-	      "   Number of successfull: ~w~n"
-	      "   Number of failure:     ~w~n"
-	      "   Total Calls / seconds: ~.2f~n~n", 
-	      [Succs, Fails, Sec]),
-    ok.
-    
+%% MGs in parallel, so it should be "accurate"...
+multi_load_collector_calc(Time, Oks) ->
+    io:format("~s -> entry with"
+              "~n   Time: ~p (usec)"
+              "~n   Oks:  ~p"
+              "~n", [?FUNCTION_NAME, Time, Oks]),
+    Succs    = lists:sum([Ok   || {_, Ok,   _} <- Oks]),
+    Fails    = lists:sum([Err  || {_,  _, Err} <- Oks]),
+    MSec     = Time div 1000,
+    NumCalls = Succs * ?MULTI_USER_LOAD_NUM_REQUESTS,
+    if
+        (NumCalls > MSec) ->
+            %% The resulting "performance" will be a value greater 
+            %% or equal to one (1).
+            Perf  = NumCalls div MSec,
+            io:format("~nTotal multiple loaders result: ~n"
+                      "   Number of successfull: ~w~n"
+                      "   Number of failure:     ~w~n"
+                      "   Time:                  ~w msec~n"
+                      "   Total (successful) Calls / msec: ~w~n~n", 
+                      [Succs, Fails, MSec, Perf]),
+            {
+             {comment, ?F("~w calls / msec", [Perf])},
+             Perf
+            };
+
+        %% The resulting "performance" will be 0 (calls / msec),
+        %% so either we are running on a really slow machine or
+        %% something went wrong (lots of errors?).
+        %% Either way, do not report this, will only skew the
+        %% results.
+
+        (Succs > 0) ->
+            Sec   = Time div 10000000,
+            Perf  = NumCalls div Sec,
+            io:format("~nTotal multiple loaders result: ~n"
+                      "   Number of successfull: ~w~n"
+                      "   Number of failure:     ~w~n"
+                      "   Time:                  ~w sec~n"
+                      "   Total (successful) Calls / sec: ~w~n~n", 
+                      [Succs, Fails, Sec, Perf]),
+            {
+             {comment, ?F("~w calls / sec", [Perf])},
+             undefined
+            };
+        true ->
+            io:format("~nTotal multiple loaders result: ~n"
+                      "   Number of successfull: ~w~n"
+                      "   Number of failure:     ~w~n"
+                      "   Time:                  ~w usec~n~n", 
+                      [Succs, Fails, Time]),
+            {
+             {comment, "No successful calls"},
+             undefined
+            }
+    end.
+
+
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 make_node_names(Name, Num) ->
-- 
2.51.0

openSUSE Build Service is sponsored by