File 0781-megaco-examples-meas-Make-it-possible-to-specify-run.patch of Package erlang

From 83dd7aee6cdf8875097d5dfa7f5d32046a9753dd Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 10 Sep 2019 13:52:14 +0200
Subject: [PATCH 3/3] [megaco|examples|meas] Make it possible to specify run
 time for mstone1

The mstone1 script did not make it possible to specify run time,
it was fixed at 10 minutes. This has now been changed so that
its possible to specify time (with the '-t' option).
Default is still 10 minutes.

OTP-16061
---
 lib/megaco/examples/meas/megaco_codec_mstone1.erl | 130 +++++++++++++++-------
 lib/megaco/examples/meas/mstone1.sh.skel.src      |  16 ++-
 2 files changed, 104 insertions(+), 42 deletions(-)

diff --git a/lib/megaco/examples/meas/megaco_codec_mstone1.erl b/lib/megaco/examples/meas/megaco_codec_mstone1.erl
index 8439e167a2..542a8a7a1d 100644
--- a/lib/megaco/examples/meas/megaco_codec_mstone1.erl
+++ b/lib/megaco/examples/meas/megaco_codec_mstone1.erl
@@ -36,15 +36,14 @@
 	]).
 
 %% Internal exports
--export([mstone_runner_init/5]).
+-export([mstone_runner_init/6]).
 
 
 -define(LIB, megaco_codec_mstone_lib).
 
--ifndef(MSTONE_TIME).
--define(MSTONE_TIME, 10).
+-ifndef(MSTONE_RUN_TIME).
+-define(MSTONE_RUN_TIME, 10). % minutes
 -endif.
--define(MSTONE_RUN_TIME, timer:minutes(?MSTONE_TIME)).
 
 -ifndef(MSTONE_VERSION3).
 -define(MSTONE_VERSION3, v3).
@@ -74,63 +73,112 @@ start() ->
     start(?DEFAULT_FACTOR).
 
 start([Factor]) ->
-    start(?DEFAULT_MESSAGE_PACKAGE, Factor);
+    start(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor);
 start([MessagePackage, Factor]) ->
-    start(MessagePackage, Factor);
+    start(MessagePackage, ?MSTONE_RUN_TIME, Factor);
+start([MessagePackage, RunTime, Factor]) ->
+    start(MessagePackage, RunTime, Factor);
 start(Factor) ->
-    start(?DEFAULT_MESSAGE_PACKAGE, Factor).
+    start(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor).
 
 start(MessagePackage, Factor) ->
-    do_start(MessagePackage, Factor, ?DEFAULT_DRV_INCLUDE).
+    start(MessagePackage, ?MSTONE_RUN_TIME, Factor).
+
+start(MessagePackage, RunTime, Factor) ->
+    do_start(MessagePackage, RunTime, Factor, ?DEFAULT_DRV_INCLUDE).
 
 
 start_flex() ->
     start_flex(?DEFAULT_FACTOR).
 
 start_flex([Factor]) ->
-    start_flex(?DEFAULT_MESSAGE_PACKAGE, Factor);
+    start_flex(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor);
 start_flex([MessagePackage, Factor]) ->
-    start_flex(MessagePackage, Factor);
+    start_flex(MessagePackage, ?MSTONE_RUN_TIME, Factor);
+start_flex([MessagePackage, RunTime, Factor]) ->
+    start_flex(MessagePackage, RunTime, Factor);
 start_flex(Factor) ->
-    start_flex(?DEFAULT_MESSAGE_PACKAGE, Factor).
+    start_flex(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor).
 
 start_flex(MessagePackage, Factor) ->
-    do_start(MessagePackage, Factor, flex).
+    do_start(MessagePackage, ?MSTONE_RUN_TIME, Factor, flex).
+
+start_flex(MessagePackage, RunTime, Factor) ->
+    do_start(MessagePackage, RunTime, Factor, flex).
 
 
 start_only_drv() ->
     start_only_drv(?DEFAULT_FACTOR).
 
 start_only_drv([Factor]) ->
-    start_only_drv(?DEFAULT_MESSAGE_PACKAGE, Factor);
+    start_only_drv(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor);
 start_only_drv([MessagePackage, Factor]) ->
-    start_only_drv(MessagePackage, Factor);
+    start_only_drv(MessagePackage, ?MSTONE_RUN_TIME, Factor);
+start_only_drv([MessagePackage, RunTime, Factor]) ->
+    start_only_drv(MessagePackage, RunTime, Factor);
 start_only_drv(Factor) ->
-    start_only_drv(?DEFAULT_MESSAGE_PACKAGE, Factor).
+    start_only_drv(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor).
 
 start_only_drv(MessagePackage, Factor) ->
-    do_start(MessagePackage, Factor, only_drv).
+    do_start(MessagePackage, ?MSTONE_RUN_TIME, Factor, only_drv).
+
+start_only_drv(MessagePackage, RunTime, Factor) ->
+    do_start(MessagePackage, RunTime, Factor, only_drv).
 
 
 start_no_drv() ->
     start_no_drv(?DEFAULT_FACTOR).
 
 start_no_drv([Factor]) ->
-    start_no_drv(?DEFAULT_MESSAGE_PACKAGE, Factor);
+    start_no_drv(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor);
 start_no_drv([MessagePackage, Factor]) ->
-    start_no_drv(MessagePackage, Factor);
+    start_no_drv(MessagePackage, ?MSTONE_RUN_TIME, Factor);
+start_no_drv([MessagePackage, RunTime, Factor]) ->
+    start_no_drv(MessagePackage, RunTime, Factor);
 start_no_drv(Factor) ->
-    start_no_drv(?DEFAULT_MESSAGE_PACKAGE, Factor).
+    start_no_drv(?DEFAULT_MESSAGE_PACKAGE, ?MSTONE_RUN_TIME, Factor).
 
 start_no_drv(MessagePackage, Factor) ->
-    do_start(MessagePackage, Factor, no_drv).
+    do_start(MessagePackage, ?MSTONE_RUN_TIME, Factor, no_drv).
+
+start_no_drv(MessagePackage, RunTime, Factor) ->
+    do_start(MessagePackage, RunTime, Factor, no_drv).
 
     
-do_start(MessagePackageRaw, FactorRaw, DrvInclude) ->
+do_start(MessagePackageRaw, RunTimeRaw, FactorRaw, DrvInclude) ->
+    RunTime        = parse_runtime(RunTimeRaw),
     Factor         = parse_factor(FactorRaw),
     MessagePackage = parse_message_package(MessagePackageRaw),
-    mstone_init(MessagePackage, Factor, DrvInclude).
-	
+    mstone_init(MessagePackage, RunTime, Factor, DrvInclude).
+
+
+parse_runtime(RunTimeAtom) when is_atom(RunTimeAtom) ->
+    parse_runtime_str(atom_to_list(RunTimeAtom));
+parse_runtime(RunTimeStr) when is_list(RunTimeStr) ->
+    parse_runtime_str(RunTimeStr);
+parse_runtime(RunTime) when is_integer(RunTime) andalso (RunTime > 0) ->
+    timer:minutes(RunTime);
+parse_runtime(BadRunTime) ->
+    throw({error, {bad_runtime, BadRunTime}}).
+
+parse_runtime_str(RuneTimeStr) ->
+    try
+        begin
+            case lists:reverse(RuneTimeStr) of
+                [$s|Rest] ->
+                    timer:seconds(list_to_integer(lists:reverse(Rest)));
+                [$m|Rest] ->
+                    timer:minutes(list_to_integer(lists:reverse(Rest)));
+                [$h|Rest] ->
+                    timer:hours(list_to_integer(lists:reverse(Rest)));
+                _ ->
+                    timer:minutes(list_to_integer(RuneTimeStr))
+            end
+        end
+    catch
+        _:_ ->
+            throw({error, {bad_runtime, RuneTimeStr}})
+    end.
 
 
 parse_factor(FactorAtom) when is_atom(FactorAtom) ->
@@ -168,21 +216,23 @@ parse_message_package(BadMessagePackage) ->
 %%    pretty | compact | ber | per | erlang
 %%
 
-mstone_init(MessagePackage, Factor, DrvInclude) ->
+mstone_init(MessagePackage, RunTime, Factor, DrvInclude) ->
 %%     io:format("mstone_init -> entry with"
 %% 	      "~n   MessagePackage: ~p"
+%% 	      "~n   RunTime:        ~p"
 %% 	      "~n   Factor:         ~p"
 %% 	      "~n   DrvInclude:     ~p"
-%% 	      "~n", [MessagePackage, Factor, DrvInclude]),
+%% 	      "~n", [MessagePackage, RunTime, Factor, DrvInclude]),
     Codecs = ?MSTONE_CODECS, 
-    mstone_init(MessagePackage, Factor, Codecs, DrvInclude).
+    mstone_init(MessagePackage, RunTime, Factor, Codecs, DrvInclude).
 
-mstone_init(MessagePackage, Factor, Codecs, DrvInclude) ->
+mstone_init(MessagePackage, RunTime, Factor, Codecs, DrvInclude) ->
     Parent = self(), 
     Pid = spawn(
 	    fun() -> 
 		    process_flag(trap_exit, true),
-		    do_mstone(MessagePackage, Factor, Codecs, DrvInclude),  
+		    do_mstone(MessagePackage,
+                              RunTime, Factor, Codecs, DrvInclude),  
 		    Parent ! {done, self()}
 	    end),
     receive
@@ -190,7 +240,7 @@ mstone_init(MessagePackage, Factor, Codecs, DrvInclude) ->
 	    ok
     end.
 			 
-do_mstone(MessagePackage, Factor, Codecs, DrvInclude) ->
+do_mstone(MessagePackage, RunTime, Factor, Codecs, DrvInclude) ->
     io:format("~n", []),
     ?LIB:display_os_info(),
     ?LIB:display_system_info(),
@@ -201,7 +251,7 @@ do_mstone(MessagePackage, Factor, Codecs, DrvInclude) ->
     put(flex_scanner_conf, Conf),
     EMessages = ?LIB:expanded_messages(MessagePackage, Codecs, DrvInclude), 
     EMsgs  = duplicate(Factor, EMessages),
-    MStone = t1(EMsgs),
+    MStone = t1(RunTime, EMsgs),
     ?LIB:stop_flex_scanner(Pid),
     io:format("~n", []),
     io:format("MStone: ~p~n", [MStone]).
@@ -214,11 +264,11 @@ duplicate(_N, [], Acc) ->
 duplicate(N, [H|T], Acc) ->
     duplicate(N, T, [lists:duplicate(N, H)|Acc]).
 
-t1(EMsgs) ->
+t1(RunTime, EMsgs) ->
     io:format(" * starting runners [~w] ", [length(EMsgs)]),
-    t1(EMsgs, []).
+    t1(RunTime, EMsgs, []).
 
-t1([], Runners) ->
+t1(_RunTime, [], Runners) ->
     io:format(" done~n * await runners ready ", []),
     await_runners_ready(Runners),
     io:format(" done~n * now snooze", []),
@@ -226,10 +276,10 @@ t1([], Runners) ->
     io:format("~n * release them~n", []),
     lists:foreach(fun(P) -> P ! {go, self()} end, Runners),
     t2(1, [], Runners);
-t1([H|T], Runners) ->
-    Runner = init_runner(H),
+t1(RunTime, [H|T], Runners) ->
+    Runner = init_runner(RunTime, H),
     io:format(".", []),
-    t1(T, [Runner|Runners]).
+    t1(RunTime, T, [Runner|Runners]).
 
 await_runners_ready([]) ->
     ok;
@@ -312,11 +362,11 @@ t2(N, Acc, Runners) ->
 	    t2(N + 1, [MStone|Acc], lists:delete(Pid, Runners))
     end.
 
-init_runner({Codec, Mod, Conf, Msgs}) ->
+init_runner(RunTime, {Codec, Mod, Conf, Msgs}) ->
     Conf1 = runner_conf(Conf),
     Conf2 = [{version3,?VERSION3}|Conf1],
     Pid   = spawn_opt(?MODULE, mstone_runner_init, 
-		      [Codec, self(), Mod, Conf2, Msgs],
+		      [RunTime, Codec, self(), Mod, Conf2, Msgs],
 		      ?MSTONE_RUNNER_OPTS),
     Pid.
 
@@ -336,7 +386,7 @@ detect_versions(Codec, Conf, [{_Name, Bin}|Bins], Acc) ->
     detect_versions(Codec, Conf, Bins, [Data|Acc]).
 	    
 
-mstone_runner_init(_Codec, Parent, Mod, Conf, Msgs0) ->
+mstone_runner_init(RunTime, _Codec, Parent, Mod, Conf, Msgs0) ->
     Msgs = detect_versions(Mod, Conf, Msgs0, []),
     warmup(Mod, Conf, Msgs, []),
     Parent ! {ready, self()},
@@ -344,7 +394,7 @@ mstone_runner_init(_Codec, Parent, Mod, Conf, Msgs0) ->
         {go, Parent} ->
             ok
     end,
-    erlang:send_after(?MSTONE_RUN_TIME, self(), stop),
+    erlang:send_after(RunTime, self(), stop),
     mstone_runner_loop(Parent, Mod, Conf, 0, Msgs).
 
 mstone_runner_loop(Parent, Mod, Conf, N, Msgs1) ->
diff --git a/lib/megaco/examples/meas/mstone1.sh.skel.src b/lib/megaco/examples/meas/mstone1.sh.skel.src
index 24df0101e9..700da75454 100644
--- a/lib/megaco/examples/meas/mstone1.sh.skel.src
+++ b/lib/megaco/examples/meas/mstone1.sh.skel.src
@@ -39,6 +39,13 @@ Options:
                         default is time_test
  -h <num>               default process heap size
  -a <num>               async thread pool size (default is 0)
+ -t <run time>          The runtime of the test
+                        Format: <value>[unit], where unit can be:
+                           s: seconds
+                           m: minutes (default)
+                           h: hours
+                        If no unit is provided, minutes is assumed.
+                        defaults to 10 minutes
  -f <factor>            normally the test is run with 16 processes 
                         (factor 1), one for each codec config. The test 
                         can however be run with other factors, e.g. 
@@ -78,6 +85,7 @@ STARTF="start"
 FACTOR=""
 MSG_PACK=time_test
 SBT="+sbt tnnps"
+RT=10
 
 while test $# != 0; do
     # echo "DBG: Value = $1"
@@ -98,6 +106,10 @@ while test $# != 0; do
             ATP="+A $2";
             shift ; shift ;;
 
+        -t)
+            RT="$2";
+            shift ; shift ;;
+
         -d)
 	    case $2 in
 		std)
@@ -162,7 +174,7 @@ done
 
 if [ $TYPE = factor ]; then
 
-    MSTONE="-s $MODULE $STARTF $MSG_PACK $FACTOR"
+    MSTONE="-s $MODULE $STARTF $MSG_PACK $RT $FACTOR"
 
     # SCHEDS="01 02 04"
     # SCHEDS="01 02 04 08"
@@ -208,7 +220,7 @@ if [ $TYPE = factor ]; then
 
 elif [ $TYPE = sched ]; then
 
-    MSTONE="-s $MODULE $STARTF $MSG_PACK"
+    MSTONE="-s $MODULE $STARTF $MSG_PACK $RT"
 
     # FACTORS="01 02 03 04"
     # FACTORS="01 02 03 04 05 06 07 08 09 10"
-- 
2.16.4

openSUSE Build Service is sponsored by