File 0237-ct-Optimize-surefire-cth-to-keep-state-in-seperate-p.patch of Package erlang

From 0d060f1ddc7b7090b48dff96ff68180290062085 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Fri, 7 Jan 2022 10:25:12 +0100
Subject: [PATCH 2/5] ct: Optimize surefire cth to keep state in seperate
 process

When running a suite with many processes the cth state
could become very large. Since the state is copied to the
testcase process each time a cth is called that because
very expensive. So instead we create a seperate process
that keeps the state of the surefire cth so that it does
not have to be copied.
---
 lib/common_test/src/cth_surefire.erl | 122 ++++++++++++++++++++-------
 1 file changed, 91 insertions(+), 31 deletions(-)

diff --git a/lib/common_test/src/cth_surefire.erl b/lib/common_test/src/cth_surefire.erl
index 780732fa1f..c556c90c91 100644
--- a/lib/common_test/src/cth_surefire.erl
+++ b/lib/common_test/src/cth_surefire.erl
@@ -46,11 +46,13 @@
 
 -export([terminate/1]).
 
+%% Gen server callbacks
+-export([init/1, handle_call/3]).
+
 -record(state, { filepath, axis, properties, package, hostname,
-		 curr_suite, curr_suite_file, curr_suite_ts, curr_group = [],
+		 curr_suite, curr_suite_file, curr_suite_ast, curr_suite_ts, curr_group = [],
 		 curr_log_dir, timer, tc_log, url_base,
-		 test_cases = [],
-		 test_suites = [] }).
+                 test_cases = [], test_suites = []}).
 
 -record(testcase, { log, url, group, file, line, classname, name, time, result, timestamp }).
 -record(testsuite, { errors, failures, skipped, hostname, name, tests,
@@ -66,22 +68,47 @@
 %% ct_run.<node>.<timestamp>/<test_name>/run.<timestamp>/<tc_log>.html
 -define(log_depth,3).
 
+%% The gen server proxy wrapper API
+%% The state of this hook can become very large for large test suites
+%%    for example diameter_traffic_SUITE
+%% so we keep the state in a separate process in order to not have to
+%% copy the full state to each testcase process. Doing it this way cuts
+%% the execution time of diameter_traffic_SUITE from 30 min to 5 min.
+init(Path, Opts) ->
+    {ok, Pid} = gen_server:start(?MODULE, [Path, Opts], []),
+    Pid.
+
+init([Path, Opts]) ->
+    ct_util:mark_process(),
+    {ok, Host} = inet:gethostname(),
+    {ok, #state{ filepath = Path,
+                 hostname = proplists:get_value(hostname,Opts,Host),
+                 package = proplists:get_value(package,Opts),
+                 axis = proplists:get_value(axis,Opts,[]),
+                 properties = proplists:get_value(properties,Opts,[]),
+                 url_base = proplists:get_value(url_base,Opts),
+                 timer = ?now }}.
+
+handle_call({terminate, Args}, _From, State) ->
+    Res = apply(?MODULE, terminate, Args ++ [State]),
+    {stop, normal, Res, State};
+handle_call({Function, Args}, _From, State)
+  when Function =:= on_tc_fail;
+       Function =:= on_tc_skip ->
+    NewState = apply(?MODULE, Function, Args ++ [State]),
+    {reply, ok, NewState};
+handle_call({Function, Args}, _From, State) ->
+    {Reply,NewState} = apply(?MODULE, Function, Args ++ [State]),
+    {reply,Reply,NewState}.
+
 id(Opts) ->
     case proplists:get_value(path, Opts) of
 	undefined -> ?default_report;
 	Path -> filename:absname(Path)
     end.
 
-init(Path, Opts) ->
-    {ok, Host} = inet:gethostname(),
-    #state{ filepath = Path,
-	    hostname = proplists:get_value(hostname,Opts,Host),
-	    package = proplists:get_value(package,Opts),
-	    axis = proplists:get_value(axis,Opts,[]),
-	    properties = proplists:get_value(properties,Opts,[]),
-	    url_base = proplists:get_value(url_base,Opts),
-	    timer = ?now }.
-
+pre_init_per_suite(Suite,SkipOrFail,Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite, SkipOrFail]}),Proxy};
 pre_init_per_suite(Suite,SkipOrFail,#state{ test_cases = [] } = State)
   when is_tuple(SkipOrFail) ->
     {SkipOrFail, init_tc(State#state{curr_suite = Suite,
@@ -98,9 +125,20 @@ pre_init_per_suite(Suite,Config,#state{ test_cases = [] } = State) ->
 	    P ->
 		P
 	end,
+    Ast =
+        case beam_lib:chunks(code:which(Suite),[debug_info]) of
+            {ok,{Suite,[{debug_info,
+                         {debug_info_v1,
+                          erl_abstract_code,
+                          {Abstr,_Opts}}}]}} ->
+                Abstr;
+            _ ->
+                undefined
+        end,
     {Config, init_tc(State#state{ filepath = Path,
 				  curr_suite = Suite,
                                   curr_suite_file = get_file(Suite),
+                                  curr_suite_ast = Ast,
 				  curr_suite_ts = ?now,
 				  curr_log_dir = CurrLogDir},
 		     Config) };
@@ -122,35 +160,56 @@ get_file(Suite) ->
             undefined
     end.
 
+post_init_per_suite(Suite,Config, Result, Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite, Config, Result]}),Proxy};
 post_init_per_suite(_Suite,Config, Result, State) ->
     {Result, end_tc(init_per_suite,Config,Result,State)}.
 
+pre_end_per_suite(Suite,Config,Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite, Config]}),Proxy};
 pre_end_per_suite(_Suite,Config,State) ->
     {Config, init_tc(State, Config)}.
 
+post_end_per_suite(Suite,Config,Result,Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite, Config, Result]}),Proxy};
 post_end_per_suite(_Suite,Config,Result,State) ->
     {Result, end_tc(end_per_suite,Config,Result,State)}.
 
+pre_init_per_group(Suite,Group,Config,Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite, Group, Config]}),Proxy};
 pre_init_per_group(_Suite,Group,Config,State) ->
     {Config, init_tc(State#state{ curr_group = [Group|State#state.curr_group]},
 		     Config)}.
 
+post_init_per_group(Suite,Group,Config,Result,Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite, Group, Config, Result]}),Proxy};
 post_init_per_group(_Suite,_Group,Config,Result,State) ->
     {Result, end_tc(init_per_group,Config,Result,State)}.
 
+pre_end_per_group(Suite,Group,Config,Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite, Group, Config]}),Proxy};
 pre_end_per_group(_Suite,_Group,Config,State) ->
     {Config, init_tc(State, Config)}.
 
+post_end_per_group(Suite,Group,Config,Result,Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite,Group,Config,Result]}),Proxy};
 post_end_per_group(_Suite,_Group,Config,Result,State) ->
     NewState = end_tc(end_per_group, Config, Result, State),
     {Result, NewState#state{ curr_group = tl(NewState#state.curr_group)}}.
 
+pre_init_per_testcase(Suite,TC,Config,Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite,TC,Config]}),Proxy};
 pre_init_per_testcase(_Suite,_TC,Config,State) ->
     {Config, init_tc(State, Config)}.
 
+post_end_per_testcase(Suite,TC,Config,Result,Proxy) when is_pid(Proxy) ->
+    {gen_server:call(Proxy,{?FUNCTION_NAME, [Suite, TC, Config, Result]}),Proxy};
 post_end_per_testcase(_Suite,TC,Config,Result,State) ->
     {Result, end_tc(TC,Config, Result,State)}.
 
+on_tc_fail(Suite,TC,Result,Proxy) when is_pid(Proxy) ->
+    _ = gen_server:call(Proxy,{?FUNCTION_NAME, [Suite, TC, Result]}),
+    Proxy;
 on_tc_fail(_Suite,_TC, _Res, State = #state{test_cases = []}) ->
     State;
 on_tc_fail(Suite, _TC, Res, State) ->
@@ -179,6 +238,9 @@ get_line_from_result(Suite, {_Error, [{__M,__F,__A,__I}|_] = StackTrace}) ->
 get_line_from_result(_, _) ->
     undefined.
 
+on_tc_skip(Suite,TC,Result,Proxy) when is_pid(Proxy) ->
+    _ = gen_server:call(Proxy,{?FUNCTION_NAME, [Suite,TC,Result]}),
+    Proxy;
 on_tc_skip(Suite,{ConfigFunc,_GrName}, Res, State) ->
     on_tc_skip(Suite,ConfigFunc, Res, State);
 on_tc_skip(Suite,Tc, Res, State0) ->
@@ -234,7 +296,8 @@ end_tc(Name, _Config, _Res, State = #state{ curr_suite = Suite,
 					  name = Name,
 					  time = TimeTakes,
                                           file = State#state.curr_suite_file,
-                                          line = get_line_from_suite(Suite, Name),
+                                          line = get_line_from_suite(
+                                                   State#state.curr_suite_ast, Name),
 					  result = passed }|
 			       State#state.test_cases],
 		 tc_log = ""}. % so old tc_log is not set if next is on_tc_skip
@@ -267,6 +330,9 @@ close_suite(#state{ test_cases = TCs, url_base = UrlBase } = State) ->
                  test_cases = [],
 		 test_suites = [Suite | State#state.test_suites]}.
 
+terminate(Proxy) when is_pid(Proxy) ->
+    gen_server:call(Proxy,{?FUNCTION_NAME, []}),
+    ok;
 terminate(State = #state{ test_cases = [] }) ->
     {ok,D} = file:open(State#state.filepath,[write,{encoding,utf8}]),
     io:format(D, "<?xml version=\"1.0\" encoding= \"UTF-8\" ?>", []),
@@ -277,25 +343,19 @@ terminate(State) ->
     %% Have to close the last suite
     terminate(close_suite(State)).
 
-get_line_from_suite(Suite, TC) ->
-    case beam_lib:chunks(code:which(Suite),[debug_info]) of
-        {ok,{Suite,[{debug_info,
-                     {debug_info_v1,
-                      erl_abstract_code,
-                      {Abstr,_Opts}}}]}} ->
-            case [Anno || {function,Anno,Name,1,_} <- Abstr, TC =:= atom_to_list(Name)] of
-                [{Line,_Col}] ->
+get_line_from_suite(undefined, _TC) ->
+    undefined;
+get_line_from_suite(Abstr, TC) ->
+    case [Anno || {function,Anno,Name,1,_} <- Abstr, TC =:= atom_to_list(Name)] of
+        [{Line,_Col}] ->
+            Line;
+        _ ->
+            case [Anno || {function,Anno,Name,_,_} <- Abstr, TC =:= atom_to_list(Name)] of
+                [{Line,_}|_] ->
                     Line;
                 _ ->
-                    case [Anno || {function,Anno,Name,_,_} <- Abstr, TC =:= atom_to_list(Name)] of
-                        [{Line,_}|_] ->
-                            Line;
-                        _ ->
-                            undefined
-                    end
-            end;
-        _ ->
-            undefined
+                    undefined
+            end
     end.
 
 
-- 
2.31.1

openSUSE Build Service is sponsored by