File 1807-megaco-test-Move-proper-bench-tests-into-bench-group.patch of Package erlang

From 6087473eecc7ef1edd267e0be95f408457e2a5b8 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Thu, 10 Apr 2025 14:22:12 +0200
Subject: [PATCH 7/7] [megaco|test] Move (proper) bench tests into bench group

Move (proper) bench tests into bench group, which are only
run in its full coonfig during bench runs (and a reduced
variant during standard runs).
---
 .../examples/meas/megaco_codec_mstone2.erl    | 12 +++
 lib/megaco/test/megaco_examples_SUITE.erl     | 81 ++++++++++++-------
 2 files changed, 64 insertions(+), 29 deletions(-)

diff --git a/lib/megaco/examples/meas/megaco_codec_mstone2.erl b/lib/megaco/examples/meas/megaco_codec_mstone2.erl
index 478d042885..868b82b8d0 100644
--- a/lib/megaco/examples/meas/megaco_codec_mstone2.erl
+++ b/lib/megaco/examples/meas/megaco_codec_mstone2.erl
@@ -227,6 +227,18 @@ start(Opts, Factor, RunTime, Mode) when is_map(Opts) ->
           Factor, RunTime, Mode, ?DEFAULT_MESSAGE_PACKAGE).
 
 -doc false.
+start(#{bench := Bench},
+      Factor, RunTime, Mode, MessagePackage)
+  when is_boolean(Bench) andalso
+       is_integer(Factor) andalso
+       (Factor > 0) andalso
+       is_list(RunTime) andalso
+       ((Mode =:= standard) orelse
+        (Mode =:= flex) orelse
+        (Mode =:= no_drv) orelse
+        (Mode =:= only_drv)) ->
+    do_start(Bench,
+             Factor, ?LIB:parse_runtime(RunTime), Mode, MessagePackage);
 start(#{bench := Bench},
       Factor, RunTime, Mode, MessagePackage)
   when is_boolean(Bench) andalso
diff --git a/lib/megaco/test/megaco_examples_SUITE.erl b/lib/megaco/test/megaco_examples_SUITE.erl
index 148258a6d3..dfb0df282e 100644
--- a/lib/megaco/test/megaco_examples_SUITE.erl
+++ b/lib/megaco/test/megaco_examples_SUITE.erl
@@ -64,8 +64,7 @@ suite() ->
 all() -> 
     [
      simple,
-     {group, meas},
-     {group, bench}
+     {group, meas}
     ].
 
 groups() -> 
@@ -631,27 +630,47 @@ users(Proxy) ->
 meas(suite) ->
     [];
 meas(Config) when is_list(Config) ->
-    common_meas(?FUNCTION_NAME, #{}, Config).
+    common_meas(?FUNCTION_NAME, #{bench => false}, Config).
 
-common_meas(TC, Opts0, Config) when is_map(Opts0) ->
+meas_bench_adjust_time(true, Num) ->
+    Num;
+meas_bench_adjust_time(false, Num) when (Num >= 3) ->
+    Num div 3;
+meas_bench_adjust_time(false, Num) ->
+    Num.
+
+meas_bench_adjust_factor(true, Num) ->
+    Num;
+meas_bench_adjust_factor(false, Num) ->
+    Num * 3.
+
+
+common_meas(TC, #{bench := Bench} = Opts0, Config) ->
     Pre  = fun() ->
                    MFactor = ?config(megaco_factor, Config),
                    {Time, Factor} =
                        if
                            (MFactor =:= 1) ->
-                               {3,  100};
+                               {meas_bench_adjust_time(Bench, 3),
+                                meas_bench_adjust_factor(Bench, 100)};
                            (MFactor =:= 2) ->
-                               {4,  100};
+                               {meas_bench_adjust_time(Bench, 4),
+                                meas_bench_adjust_factor(Bench, 100)};
                            (MFactor =:= 3) ->
-                               {4,  200};
+                               {meas_bench_adjust_time(Bench, 4),
+                                meas_bench_adjust_factor(Bench, 200)};
                            (MFactor =:= 4) ->
-                               {5,  300};
+                               {meas_bench_adjust_time(Bench, 5),
+                                meas_bench_adjust_factor(Bench, 300)};
                            (MFactor =:= 5) ->
-                               {5,  400};
+                               {meas_bench_adjust_time(Bench, 5),
+                                meas_bench_adjust_factor(Bench, 400)};
                            (MFactor =:= 6) ->
-                               {6,  500};
+                               {meas_bench_adjust_time(Bench, 6),
+                                meas_bench_adjust_factor(Bench, 500)};
                            true ->
-                               {10, 600}
+                               {meas_bench_adjust_time(Bench, 10),
+                                meas_bench_adjust_factor(Bench, 600)}
                        end,
                    p("Run with: "
                      "~n      Timetrap: ~p mins"
@@ -750,27 +769,29 @@ publish_bench_results_multiple(Pre, [{Name, {_, Enc, Dec}} | Results], Acc) ->
 mstone1(suite) ->
     [];
 mstone1(Config) when is_list(Config) ->
-    common_mstone1(?FUNCTION_NAME, #{}, Config).
+    %% We give time in seconds, which is *not* the norm (minutes).
+    %% It will be converted into a run-time string in the form: "10s"
+    common_mstone1(?FUNCTION_NAME, #{run_time => 10, bench => false}, Config).
 
-common_mstone1(TC, Opts, Config) when is_list(Config) ->
+common_mstone1(TC, #{run_time := RunTime} = Opts, Config)
+  when is_list(Config) ->
     Pre  = fun() ->
                    %% The point of this is to make sure we
                    %% utilize as much of the host as possible...
-                   RunTime   = 1, % Minute
                    NumSched  =
                        try erlang:system_info(schedulers_online) of N -> N
                        catch _:_:_ -> 1
                        end,
                    Factor    = 1 + (NumSched div 12),
-                   ct:timetrap(?MINS(RunTime + 1)),
-                   {RunTime, Factor, ?config(worker_node, Config)}
+                   ct:timetrap(?SECS(10) + ?MINS(1)),
+                   {Factor, ?config(worker_node, Config)}
            end,
-    Case = fun({RunTime, Factor, WorkerNode}) ->
+    Case = fun({Factor, WorkerNode}) ->
                    Mod  = megaco_codec_mstone1,
                    Func = start,
-                   Args = [Opts, RunTime, Factor],
+                   Args = [Opts, ?F("~ws", [RunTime]), Factor],
                    p("Run with: "
-                     "~n      Run Time: ~p min(s)"
+                     "~n      Run Time: ~p sec(s)"
                      "~n      Factor:   ~p", [RunTime, Factor]),
                    do_meas(WorkerNode,
                            mstone1,
@@ -788,27 +809,27 @@ common_mstone1(TC, Opts, Config) when is_list(Config) ->
 mstone2(suite) ->
     [];
 mstone2(Config) when is_list(Config) ->
-    common_mstone2(?FUNCTION_NAME, #{}, Config).
+    common_mstone2(?FUNCTION_NAME, #{run_time => 10, bench => false}, Config).
 
-common_mstone2(TC, Opts, Config) when is_list(Config) ->
+common_mstone2(TC, #{run_time := RunTime} = Opts, Config)
+  when is_list(Config) ->
     Pre  = fun() ->
-                   RunTime  = 1, % Minutes
                    NumSched =
                        try erlang:system_info(schedulers_online) of N -> N
                        catch _:_:_ -> 1
                        end,
                    Factor   = 1 + (NumSched div 12),
-                   ct:timetrap(?MINS(RunTime + 1)),
-                   {Factor, RunTime, ?config(worker_node, Config)}
+                   ct:timetrap(?SECS(RunTime) + ?MINS(1)),
+                   {Factor, ?config(worker_node, Config)}
            end,
-    Case = fun({Factor, RunTime, WorkerNode}) ->
+    Case = fun({Factor, WorkerNode}) ->
                    Mode = standard,
                    Mod  = megaco_codec_mstone2,
                    Func = start,
-                   Args = [Opts, Factor, RunTime, Mode],
+                   Args = [Opts, Factor, ?F("~ws", [RunTime]), Mode],
                    p("Run with: "
                      "~n      Factor:   ~p"
-                     "~n      Run Time: ~p min(s)"
+                     "~n      Run Time: ~p sec(s)"
                      "~n      Mode:     ~p", [Factor, RunTime, Mode]),
                    do_meas(WorkerNode,
                            mstone2,
@@ -833,7 +854,9 @@ bench_meas(Config) when is_list(Config) ->
 bench_mstone1(suite) ->
     [];
 bench_mstone1(Config) when is_list(Config) ->
-    common_mstone1(?FUNCTION_NAME, #{bench => true}, Config).
+    %% We give time in seconds, which is *not* the norm (minutes).
+    %% It will be converted into a run-time string in the form: "60s"
+    common_mstone1(?FUNCTION_NAME, #{run_time => 60, bench => true}, Config).
 
 
 %% ------------------ bench:mstone2 ---------------------
@@ -841,7 +864,7 @@ bench_mstone1(Config) when is_list(Config) ->
 bench_mstone2(suite) ->
     [];
 bench_mstone2(Config) when is_list(Config) ->
-    common_mstone2(?FUNCTION_NAME, #{bench => true}, Config).
+    common_mstone2(?FUNCTION_NAME, #{run_time => 60, bench => true}, Config).
 
 
 
-- 
2.43.0

openSUSE Build Service is sponsored by