File 3541-common_test-Allow-floats-to-multiply_timetraps-N.patch of Package erlang

From ce2c4ab42d0628c5be73a17972389a37053063b4 Mon Sep 17 00:00:00 2001
From: Tomas Abrahamsson <tomas.abrahamsson@gmail.com>
Date: Wed, 14 Apr 2021 22:14:50 +0200
Subject: [PATCH 1/2] common_test: Allow floats to -multiply_timetraps N

For the ct_run option -multiply_timetraps N, allow N to be a float
as well as previously an integer.  This makes it possible to scale down
timetraps. This applies also to the associated test spec option.
---
 lib/common_test/src/ct_run.erl                |   9 +-
 lib/common_test/src/ct_testspec.erl           |   2 +-
 lib/common_test/src/test_server_ctrl.erl      |   2 +-
 lib/common_test/test/ct_error_SUITE.erl       |  41 +++++-
 .../error/test/timetrap_9_SUITE.erl           | 122 ++++++++++++++++++
 5 files changed, 171 insertions(+), 5 deletions(-)
 create mode 100644 lib/common_test/test/ct_error_SUITE_data/error/test/timetrap_9_SUITE.erl

diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl
index 2704873276..a69267f5ea 100644
--- a/lib/common_test/src/ct_run.erl
+++ b/lib/common_test/src/ct_run.erl
@@ -237,7 +237,7 @@ script_start1(Parent, Args) ->
 			    [], Args),
     Verbosity = verbosity_args2opts(Args),
     MultTT = get_start_opt(multiply_timetraps,
-			   fun([MT]) -> list_to_integer(MT) end, Args),
+			   fun([MT]) -> list_to_number(MT) end, Args),
     ScaleTT = get_start_opt(scale_timetraps,
 			    fun([CT]) -> list_to_atom(CT);
 			       ([]) -> true
@@ -3148,6 +3148,8 @@ opts2args(EnvStartOpts) ->
 			  [{Opt,[atom_to_list(A)]}];
 		     ({Opt,I}) when is_integer(I) ->
 			  [{Opt,[integer_to_list(I)]}];
+		     ({Opt,I}) when is_float(I) ->
+			  [{Opt,[float_to_list(I)]}];
 		     ({Opt,S}) when is_list(S) ->
 			  [{Opt,[S]}];
 		     (Opt) ->
@@ -3263,6 +3265,11 @@ stop_trace(true) ->
 stop_trace(false) ->
     ok.
 
+list_to_number(S) ->
+    try list_to_integer(S)
+    catch error:badarg -> list_to_float(S)
+    end.
+
 ensure_atom(Atom) when is_atom(Atom) ->
     Atom;
 ensure_atom(String) when is_list(String), is_integer(hd(String)) ->
diff --git a/lib/common_test/src/ct_testspec.erl b/lib/common_test/src/ct_testspec.erl
index 2c18caf18f..a595aac569 100644
--- a/lib/common_test/src/ct_testspec.erl
+++ b/lib/common_test/src/ct_testspec.erl
@@ -1154,7 +1154,7 @@ handle_data(verbosity,Node,VLvls,_Spec) when is_list(VLvls) ->
     VLvls1 = lists:map(fun(VLvl = {_Cat,_Lvl}) -> VLvl;
 			  (Lvl) -> {'$unspecified',Lvl} end, VLvls),
     [{Node,VLvls1}];
-handle_data(multiply_timetraps,Node,Mult,_Spec) when is_integer(Mult) ->
+handle_data(multiply_timetraps,Node,Mult,_Spec) when is_number(Mult) ->
     [{Node,Mult}];
 handle_data(scale_timetraps,Node,Scale,_Spec) when Scale == true;
                                                    Scale == false ->
diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl
index dbd5537206..a84f444206 100644
--- a/lib/common_test/src/test_server_ctrl.erl
+++ b/lib/common_test/src/test_server_ctrl.erl
@@ -768,7 +768,7 @@ handle_call({reject_io_reqs,Bool}, _From, State) ->
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %% handle_call({multiply_timetraps,N}, _, State) -> ok
-%% N = integer() | infinity
+%% N = number() | infinity
 %%
 %% Multiplies all timetraps set by test cases with N
 
diff --git a/lib/common_test/test/ct_error_SUITE.erl b/lib/common_test/test/ct_error_SUITE.erl
index cd462938fe..3cd1fac8ed 100644
--- a/lib/common_test/test/ct_error_SUITE.erl
+++ b/lib/common_test/test/ct_error_SUITE.erl
@@ -66,8 +66,8 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
 all() -> 
     [cfg_error, lib_error, no_compile, timetrap_end_conf,
      timetrap_normal, timetrap_extended, timetrap_parallel,
-     timetrap_fun, timetrap_fun_group, misc_errors,
-     config_restored, config_func_errors].
+     timetrap_fun, timetrap_fun_group, timetrap_with_float_mult,
+     misc_errors, config_restored, config_func_errors].
 
 groups() -> 
     [].
@@ -273,6 +273,28 @@ timetrap_fun_group(Config) when is_list(Config) ->
     TestEvents = events_to_check(timetrap_fun_group),
     ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
+%%%-----------------------------------------------------------------
+%%%
+timetrap_with_float_mult(Config) when is_list(Config) ->
+    DataDir = ?config(data_dir, Config),
+    Join = fun(D, S) -> filename:join(D, "error/test/"++S) end,
+    Suite = Join(DataDir, "timetrap_9_SUITE"),
+    {Opts,ERPid} = setup([{suite,Suite},
+			  {multiply_timetraps,0.5},
+			  {userconfig,{ct_userconfig_callback,
+				       "multiply 0.5"}}],
+			 Config),
+    ok = ct_test_support:run(Opts, Config),
+    Events = ct_test_support:get_events(ERPid, Config),
+
+    ct_test_support:log_events(timetrap_with_float_mult,
+			       reformat(Events, ?eh),
+			       ?config(priv_dir, Config),
+			       Opts),
+
+    TestEvents = events_to_check(timetrap_with_float_mult),
+    ok = ct_test_support:verify_events(TestEvents, Events, Config).
+
 %%%-----------------------------------------------------------------
 %%%
 misc_errors(Config) when is_list(Config) ->
@@ -1450,6 +1472,21 @@ test_events(timetrap_fun_group) ->
      {?eh,stop_logging,[]}
     ];
 
+test_events(timetrap_with_float_mult) ->
+    [
+     {?eh,start_logging,{'DEF','RUNDIR'}},
+     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
+     {?eh,start_info,{1,1,1}},
+     {?eh,tc_start,{timetrap_9_SUITE,init_per_suite}},
+     {?eh,tc_done,{timetrap_9_SUITE,init_per_suite,ok}},
+     {?eh,tc_start,{timetrap_9_SUITE,tc0}},
+     {?eh,tc_done,
+      {timetrap_9_SUITE,tc0,{failed,{timetrap_timeout,1500}}}},
+     {?eh,test_stats,{0,1,{0,0}}},
+     {?eh,test_done,{'DEF','STOP_TIME'}},
+     {?eh,stop_logging,[]}
+    ];
+
 test_events(misc_errors) ->
     [
      {?eh,start_logging,{'DEF','RUNDIR'}},
diff --git a/lib/common_test/test/ct_error_SUITE_data/error/test/timetrap_9_SUITE.erl b/lib/common_test/test/ct_error_SUITE_data/error/test/timetrap_9_SUITE.erl
new file mode 100644
index 0000000000..729d931ccd
--- /dev/null
+++ b/lib/common_test/test/ct_error_SUITE_data/error/test/timetrap_9_SUITE.erl
@@ -0,0 +1,122 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2021. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(timetrap_9_SUITE).
+
+-compile(export_all).
+
+-include_lib("common_test/include/ct.hrl").
+
+%%--------------------------------------------------------------------
+%% Function: suite() -> Info
+%% Info = [tuple()]
+%%--------------------------------------------------------------------
+suite() ->
+    [{timetrap,{seconds,3}},
+     {require,multiply}].
+
+%%--------------------------------------------------------------------
+%% Function: init_per_suite(Config0) ->
+%%               Config1 | {skip,Reason} | {skip_and_save,Reason,Config1}
+%% Config0 = Config1 = [tuple()]
+%% Reason = term()
+%%--------------------------------------------------------------------
+init_per_suite(Config) ->
+    Config.
+
+%%--------------------------------------------------------------------
+%% Function: end_per_suite(Config0) -> void() | {save_config,Config1}
+%% Config0 = Config1 = [tuple()]
+%%--------------------------------------------------------------------
+end_per_suite(_Config) ->
+    ok.
+
+%%--------------------------------------------------------------------
+%% Function: init_per_group(GroupName, Config0) ->
+%%               Config1 | {skip,Reason} | {skip_and_save,Reason,Config1}
+%% GroupName = atom()
+%% Config0 = Config1 = [tuple()]
+%% Reason = term()
+%%--------------------------------------------------------------------
+init_per_group(_GroupName, Config) ->
+    Config.
+
+%%--------------------------------------------------------------------
+%% Function: end_per_group(GroupName, Config0) ->
+%%               void() | {save_config,Config1}
+%% GroupName = atom()
+%% Config0 = Config1 = [tuple()]
+%%--------------------------------------------------------------------
+end_per_group(_GroupName, _Config) ->
+    ok.
+
+%%--------------------------------------------------------------------
+%% Function: init_per_testcase(TestCase, Config0) ->
+%%               Config1 | {skip,Reason} | {skip_and_save,Reason,Config1}
+%% TestCase = atom()
+%% Config0 = Config1 = [tuple()]
+%% Reason = term()
+%%--------------------------------------------------------------------
+init_per_testcase(_TestCase, Config) ->
+    Config.
+
+%%--------------------------------------------------------------------
+%% Function: end_per_testcase(TestCase, Config0) ->
+%%               void() | {save_config,Config1}
+%% TestCase = atom()
+%% Config0 = Config1 = [tuple()]
+%%--------------------------------------------------------------------
+end_per_testcase(_, _Config) ->
+    ok.
+
+%%--------------------------------------------------------------------
+%% Function: groups() -> [Group]
+%% Group = {GroupName,Properties,GroupsAndTestCases}
+%% GroupName = atom()
+%% Properties = [parallel | sequence | Shuffle | {RepeatType,N}]
+%% GroupsAndTestCases = [Group | {group,GroupName} | TestCase]
+%% TestCase = atom()
+%% Shuffle = shuffle | {shuffle,{integer(),integer(),integer()}}
+%% RepeatType = repeat | repeat_until_all_ok | repeat_until_all_fail |
+%%              repeat_until_any_ok | repeat_until_any_fail
+%% N = integer() | forever
+%%--------------------------------------------------------------------
+groups() ->
+    [].
+
+%%--------------------------------------------------------------------
+%% Function: all() -> GroupsAndTestCases | {skip,Reason}
+%% GroupsAndTestCases = [{group,GroupName} | TestCase]
+%% GroupName = atom()
+%% TestCase = atom()
+%% Reason = term()
+%%--------------------------------------------------------------------
+all() ->
+    [tc0].
+
+tc0(_) ->
+    N = list_to_number(ct:get_config(multiply)),
+    ct:comment(io_lib:format("TO after ~w sec", [3*N])),
+    ct:sleep({seconds,5}),
+    ok.
+
+list_to_number(S) ->
+    try list_to_integer(S)
+    catch error:badarg -> list_to_float(S)
+    end.
-- 
2.26.2

openSUSE Build Service is sponsored by