File 2190-kernel-esock-test-Make-bench-runs-take-the-full-time.patch of Package erlang
From b28efa89a0ad65e14ceb713bd11d2947da185a26 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Thu, 10 Apr 2025 11:51:46 +0200
Subject: [PATCH 10/10] [kernel|esock|test] Make bench runs take the full time
Calculate the run time of the bench test cases depending on
if it is a 'standard' or 'bench' test run.
---
lib/kernel/test/kernel_bench.spec | 1 +
.../test/socket_test_ttest_tcp_server.erl | 20 +--
lib/kernel/test/socket_traffic_SUITE.erl | 165 ++++++++++++------
lib/kernel/test/socket_ttest_SUITE.erl | 94 ++++++----
4 files changed, 176 insertions(+), 104 deletions(-)
diff --git a/lib/kernel/test/kernel_bench.spec b/lib/kernel/test/kernel_bench.spec
index 514885199e..8a52804c0a 100644
--- a/lib/kernel/test/kernel_bench.spec
+++ b/lib/kernel/test/kernel_bench.spec
@@ -23,4 +23,5 @@
{groups,"../kernel_test",zlib_SUITE,[bench]}.
{groups,"../kernel_test",file_SUITE,[bench]}.
{groups,"../kernel_test",socket_traffic_SUITE,[bench]}.
+{groups,"../kernel_test",socket_ttest_SUITE,[bench]}.
{suites,"../kernel_test",[logger_stress_SUITE]}.
diff --git a/lib/kernel/test/socket_test_ttest_tcp_server.erl b/lib/kernel/test/socket_test_ttest_tcp_server.erl
index 1d471ebc63..07ec20714b 100644
--- a/lib/kernel/test/socket_test_ttest_tcp_server.erl
+++ b/lib/kernel/test/socket_test_ttest_tcp_server.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2018-2022. All Rights Reserved.
+%% Copyright Ericsson AB 2018-2025. 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.
@@ -51,7 +51,7 @@
-include_lib("kernel/include/inet.hrl").
-include("socket_test_ttest.hrl").
--define(ACC_TIMEOUT, 5000).
+-define(ACC_TIMEOUT, 1000).
-define(RECV_TIMEOUT, 5000).
-define(LIB, socket_test_ttest_lib).
@@ -206,18 +206,6 @@ server_accept(#{mod := Mod, lsock := LSock} = State, Timeout) ->
exit({accept, AReason})
end.
-%% server_accept(#{mod := Mod,
-%% lsock := LSock} = State) ->
-%% case Mod:accept(LSock, ?ACC_TIMEOUT) of
-%% {ok, Sock} ->
-%% server_handle_accepted(State, Sock);
-%% {error, timeout} ->
-%% State;
-%% {error, AReason} ->
-%% (catch Mod:close(LSock)),
-%% exit({accept, AReason})
-%% end.
-
server_handle_accepted(#{mod := Mod,
lsock := LSock,
active := Active,
@@ -426,6 +414,7 @@ handler_recv_message(#{mod := Mod,
bcnt => BCnt + MsgSz,
last_reply => ID};
{error, closed} ->
+ ?I("client done (socket close)"),
handler_done(State);
{error, timeout} ->
?I("timeout when: "
@@ -460,9 +449,10 @@ handler_recv_message(#{mod := Mod,
{error, closed} ->
if
(size(Acc) =:= 0) ->
+ ?I("client done (socket close)"),
handler_done(State);
true ->
- ?E("client done with partial message: "
+ ?E("client done (socket close) with partial message: "
"~n Last Reply Sent: ~w"
"~n Message Count: ~w"
"~n Byte Count: ~w"
diff --git a/lib/kernel/test/socket_traffic_SUITE.erl b/lib/kernel/test/socket_traffic_SUITE.erl
index 2a5c2eb6c6..f3a6722b0c 100644
--- a/lib/kernel/test/socket_traffic_SUITE.erl
+++ b/lib/kernel/test/socket_traffic_SUITE.erl
@@ -18,16 +18,6 @@
%% %CopyrightEnd%
%%
-%% There are some environment variables that can be used to "manipulate"
-%% the test suite:
-%%
-%% Variable that controls which 'groups' are to run (with default values)
-%%
-%% ESOCK_TEST_TRAFFIC_COUNTERS: include
-%% ESOCK_TEST_TRAFFIC_CHUNKS: include
-%% ESOCK_TEST_TRAFFIC_PING_PONG: include
-%% ESOCK_TEST_TRAFFIC_BENCH: exclude
-%%
%% Variable that controls "verbosity" of the test case(s):
%%
%% ESOCK_TEST_QUIET: true (default) | false
@@ -188,47 +178,71 @@ suite() ->
{timetrap, {minutes,1}}].
all() ->
- Groups = [
- {counters, "ESOCK_TEST_TRAFFIC_COUNTERS", include},
- {chunks, "ESOCK_TEST_TRAFFIC_CHUNKS", include},
- {ping_pong, "ESOCK_TEST_TRAFFIC_PING_PONG", include},
- %% {bench, "ESOCK_TEST_TRAFFIC_BENCH", exclude},
- {bench, "ESOCK_TEST_TRAFFIC_BENCH", include}
- ],
- [use_group(Group, Env, Default) || {Group, Env, Default} <- Groups].
-
-use_group(_Group, undefined, exclude) ->
- [];
-use_group(Group, undefined, _Default) ->
- [{group, Group}];
-use_group(Group, Env, Default) ->
- case os:getenv(Env) of
- false when (Default =:= include) ->
- [{group, Group}];
- false ->
- [];
- Val ->
- case list_to_atom(string:to_lower(Val)) of
- Use when (Use =:= include) orelse
- (Use =:= enable) orelse
- (Use =:= true) ->
- [{group, Group}];
- _ ->
- []
- end
- end.
+ %% Groups = [
+ %% {counters, "ESOCK_TEST_TRAFFIC_COUNTERS", include},
+ %% {chunks, "ESOCK_TEST_TRAFFIC_CHUNKS", include},
+ %% {ping_pong, "ESOCK_TEST_TRAFFIC_PING_PONG", include},
+ %% {tbench, "ESOCK_TEST_TRAFFIC_BENCH", include}
+ %% ],
+ %% [use_group(Group, Env, Default) || {Group, Env, Default} <- Groups].
+ [{group, standard}].
+
+%% use_group(_Group, undefined, exclude) ->
+%% [];
+%% use_group(Group, undefined, _Default) ->
+%% [{group, Group}];
+%% use_group(Group, Env, Default) ->
+%% case os:getenv(Env) of
+%% false when (Default =:= include) ->
+%% [{group, Group}];
+%% false ->
+%% [];
+%% Val ->
+%% case list_to_atom(string:to_lower(Val)) of
+%% Use when (Use =:= include) orelse
+%% (Use =:= enable) orelse
+%% (Use =:= true) ->
+%% [{group, Group}];
+%% _ ->
+%% []
+%% end
+%% end.
groups() ->
- [{counters, [], traffic_counters_cases()},
+ [
+ %% Top level "wrapper" groups
+ %% A normal (standard) test run will be running the 'suite'.
+ %% Which will run the 'standard' group, with all test cases but
+ %% the 'tbench' group of test cases will run with a short
+ %% run time.
+ %% A benchmark test run will run the 'bench' group directly,
+ %% with an "extended" run time.
+ %%
+ {standard, [], standard_cases()},
+ {bench, [], bench_cases()},
+
+ {counters, [], traffic_counters_cases()},
{chunks, [], traffic_chunks_cases()},
{ping_pong, [], traffic_ping_pong_cases()},
- {bench, [], traffic_bench_cases()},
+ {tbench, [], traffic_bench_cases()},
{pp_send_recv, [], traffic_pp_send_recv_cases()},
{pp_sendto_recvfrom, [], traffic_pp_sendto_recvfrom_cases()},
{pp_sendmsg_recvmsg, [], traffic_pp_sendmsg_recvmsg_cases()}
].
-
+
+standard_cases() ->
+ [
+ {group, counters},
+ {group, chunks},
+ {group, ping_pong},
+ {group, tbench}
+ ].
+
+bench_cases() ->
+ [
+ {group, tbench}
+ ].
traffic_counters_cases() ->
[
@@ -405,7 +419,31 @@ end_per_suite(Config0) ->
Config1.
+init_per_group(standard = GroupName, Config) ->
+ ?P("init_per_group -> entry with"
+ "~n GroupName: ~p"
+ "~n Config: ~p"
+ "~n when"
+ "~n Nodes: ~p", [GroupName, Config, erlang:nodes()]),
+ [{category, GroupName} | Config];
+init_per_group(bench = GroupName, Config) ->
+ ?P("init_per_group -> entry with"
+ "~n GroupName: ~p"
+ "~n Config: ~p"
+ "~n when"
+ "~n Nodes: ~p", [GroupName, Config, erlang:nodes()]),
+ case proplists:get_value(category, Config, undefined) of
+ undefined ->
+ [{category, GroupName} | Config];
+ _ ->
+ Config
+ end;
init_per_group(_GroupName, Config) ->
+ ?P("init_per_group -> entry with"
+ "~n GroupName: ~p"
+ "~n Config: ~p"
+ "~n when"
+ "~n Nodes: ~p", [_GroupName, Config, erlang:nodes()]),
Config.
end_per_group(_GroupName, Config) ->
@@ -7033,6 +7071,8 @@ tpp_udp_sock_close(Sock, Path) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% Benchmark test cases
+%% This test is (currently) very simple. Both parties of the test
+%% (server and client) runs in the same (this) node.
-define(TB_IOV_CHUNK(Sz,V), list_to_binary(lists:duplicate((Sz), (V)))).
tb_iov() ->
@@ -7069,8 +7109,19 @@ tb_iov() ->
TSz = iolist_size(IOV1),
[<<TSz:32/integer>> | IOV1].
+tb_runtime(Config) ->
+ ?SEV_IPRINT("~w -> entry with"
+ "~n Config: ~p", [?FUNCTION_NAME, Config]),
+ case proplists:get_value(category, Config, standard) of
+ bench ->
+ ?MINS(1);
+ standard ->
+ ?SECS(10)
+ end.
+
traffic_bench_sendv_and_recv_tcp4(Config) when is_list(Config) ->
- ?TT(?MINS(2)), %% Test *should* run for 60 secs
+ RunTime = tb_runtime(Config),
+ ?TT(RunTime + ?MINS(1)),
IOV = tb_iov(),
Send = fun(S, Data) when is_list(Data) ->
socket:sendv(S, Data)
@@ -7082,12 +7133,13 @@ traffic_bench_sendv_and_recv_tcp4(Config) when is_list(Config) ->
domain => inet,
send => Send,
iov => IOV,
- run_time => ?MINS(1)},
+ run_time => RunTime},
do_traffic_bench_send_and_recv(InitState)
end).
traffic_bench_send_and_recv_tcp4(Config) when is_list(Config) ->
- ?TT(?MINS(2)), %% Test *should* run for 60 secs
+ RunTime = tb_runtime(Config),
+ ?TT(RunTime + ?MINS(1)),
IOV = tb_iov(),
Send = fun(S, Data) when is_list(Data) ->
socket:send(S, iolist_to_binary(Data))
@@ -7099,12 +7151,13 @@ traffic_bench_send_and_recv_tcp4(Config) when is_list(Config) ->
domain => inet,
send => Send,
iov => IOV,
- run_time => ?MINS(1)},
+ run_time => RunTime},
do_traffic_bench_send_and_recv(InitState)
end).
traffic_bench_sendv_and_recv_tcp6(Config) when is_list(Config) ->
- ?TT(?MINS(2)), %% Test *should* run for 60 secs
+ RunTime = tb_runtime(Config),
+ ?TT(RunTime + ?MINS(1)),
IOV = tb_iov(),
Send = fun(S, Data) when is_list(Data) ->
socket:sendv(S, Data)
@@ -7116,12 +7169,13 @@ traffic_bench_sendv_and_recv_tcp6(Config) when is_list(Config) ->
domain => inet6,
send => Send,
iov => IOV,
- run_time => ?MINS(1)},
+ run_time => RunTime},
do_traffic_bench_send_and_recv(InitState)
end).
traffic_bench_send_and_recv_tcp6(Config) when is_list(Config) ->
- ?TT(?MINS(2)), %% Test *should* run for 60 secs
+ RunTime = tb_runtime(Config),
+ ?TT(RunTime + ?MINS(1)),
IOV = tb_iov(),
Send = fun(S, Data) when is_list(Data) ->
socket:send(S, iolist_to_binary(Data))
@@ -7133,12 +7187,13 @@ traffic_bench_send_and_recv_tcp6(Config) when is_list(Config) ->
domain => inet6,
send => Send,
iov => IOV,
- run_time => ?MINS(1)},
+ run_time => RunTime},
do_traffic_bench_send_and_recv(InitState)
end).
traffic_bench_sendv_and_recv_tcpL(Config) when is_list(Config) ->
- ?TT(?MINS(2)), %% Test *should* run for 60 secs
+ RunTime = tb_runtime(Config),
+ ?TT(RunTime + ?MINS(1)),
IOV = tb_iov(),
Send = fun(S, Data) when is_list(Data) ->
socket:sendv(S, Data)
@@ -7150,12 +7205,13 @@ traffic_bench_sendv_and_recv_tcpL(Config) when is_list(Config) ->
domain => local,
send => Send,
iov => IOV,
- run_time => ?MINS(1)},
+ run_time => RunTime},
do_traffic_bench_send_and_recv(InitState)
end).
traffic_bench_send_and_recv_tcpL(Config) when is_list(Config) ->
- ?TT(?MINS(2)), %% Test *should* run for 60 secs
+ RunTime = tb_runtime(Config),
+ ?TT(RunTime + ?MINS(1)),
IOV = tb_iov(),
Send = fun(S, Data) when is_list(Data) ->
socket:send(S, iolist_to_binary(Data))
@@ -7167,7 +7223,7 @@ traffic_bench_send_and_recv_tcpL(Config) when is_list(Config) ->
domain => local,
send => Send,
iov => IOV,
- run_time => ?MINS(1)},
+ run_time => RunTime},
do_traffic_bench_send_and_recv(InitState)
end).
@@ -7221,7 +7277,6 @@ tb_await_termination(BName,
{'DOWN', ClientMRef, process, ClientPid, {done, {Exchange, UnitStr}}} ->
?SEV_IPRINT("[ctrl] "
"received (expected) down from client with result"),
- ?SEV_IPRINT("[ctrl] send (ct) event"),
ct_event:notify( ?BENCH_EVENT(BName, Exchange) ),
?SEV_IPRINT("[ctrl] await server termination"),
NewComment = {comment, ?F("~p ~s", [Exchange, UnitStr])},
diff --git a/lib/kernel/test/socket_ttest_SUITE.erl b/lib/kernel/test/socket_ttest_SUITE.erl
index 2436e5823c..c655f7de78 100644
--- a/lib/kernel/test/socket_ttest_SUITE.erl
+++ b/lib/kernel/test/socket_ttest_SUITE.erl
@@ -439,7 +439,8 @@
-define(WINDOWS, {win32,nt}).
--define(TTEST_RUNTIME, ?SECS(1)).
+-define(TTEST_STANDARD_RUNTIME, ?SECS(1)).
+-define(TTEST_BENCH_RUNTIME, ?SECS(10)).
-define(TTEST_MIN_FACTOR, 3).
-define(TTEST_MIN_FACTOR_WIN, ?TTEST_MIN_FACTOR-1).
-define(TTEST_DEFAULT_SMALL_MAX_OUTSTANDING, 50).
@@ -465,33 +466,36 @@ suite() ->
{timetrap, {minutes,1}}].
all() ->
- Groups = [{ttest, "ESOCK_TEST_TTEST", include}],
- [use_group(Group, Env, Default) || {Group, Env, Default} <- Groups].
-
-use_group(_Group, undefined, exclude) ->
- [];
-use_group(Group, undefined, _Default) ->
- [{group, Group}];
-use_group(Group, Env, Default) ->
- case os:getenv(Env) of
- false when (Default =:= include) ->
- [{group, Group}];
- false ->
- [];
- Val ->
- case list_to_atom(string:to_lower(Val)) of
- Use when (Use =:= include) orelse
- (Use =:= enable) orelse
- (Use =:= true) ->
- [{group, Group}];
- _ ->
- []
- end
- end.
+ [{group, standard}].
+ %% Groups = [{ttest, "ESOCK_TEST_TTEST", include}],
+ %% [use_group(Group, Env, Default) || {Group, Env, Default} <- Groups].
+
+%% use_group(_Group, undefined, exclude) ->
+%% [];
+%% use_group(Group, undefined, _Default) ->
+%% [{group, Group}];
+%% use_group(Group, Env, Default) ->
+%% case os:getenv(Env) of
+%% false when (Default =:= include) ->
+%% [{group, Group}];
+%% false ->
+%% [];
+%% Val ->
+%% case list_to_atom(string:to_lower(Val)) of
+%% Use when (Use =:= include) orelse
+%% (Use =:= enable) orelse
+%% (Use =:= true) ->
+%% [{group, Group}];
+%% _ ->
+%% []
+%% end
+%% end.
groups() ->
- [{ttest, [], ttest_cases()},
+ [{standard, [], standard_cases()},
+ {bench, [], bench_cases()},
+ {ttest, [], ttest_cases()},
{ttest_sgenf, [], ttest_sgenf_cases()},
{ttest_sgenf_cgen, [], ttest_sgenf_cgen_cases()},
{ttest_sgenf_cgenf, [], ttest_sgenf_cgenf_cases()},
@@ -555,7 +559,7 @@ groups() ->
{ttest_simple_ssockt_csock, [], ttest_simple_ssockt_csock_cases()},
{ttest_simple_ssockt_csocko, [], ttest_simple_ssockt_csocko_cases()}
].
-
+
%% Condition for running the ttest cases.
%% No point in running these cases unless the machine is
@@ -632,6 +636,16 @@ ttest_max_outstanding(Config, EnvKey, Default) ->
end
end.
+standard_cases() ->
+ [
+ {group, ttest}
+ ].
+
+bench_cases() ->
+ [
+ {group, ttest}
+ ].
+
ttest_cases() ->
[
%% Server: transport = gen_tcp, active = false
@@ -1509,6 +1523,16 @@ end_per_suite(Config0) ->
Config1.
+init_per_group(standard = GroupName, Config) ->
+ io:format("init_per_group(~w) -> entry with"
+ "~n Config: ~p"
+ "~n", [GroupName, Config]),
+ [{category, GroupName} | Config];
+init_per_group(bench = GroupName, Config) ->
+ io:format("init_per_group(~w) -> entry with"
+ "~n Config: ~p"
+ "~n", [GroupName, Config]),
+ [{category, GroupName} | Config];
init_per_group(ttest = _GroupName, Config) ->
io:format("init_per_group(~w) -> entry with"
"~n Config: ~p"
@@ -6750,11 +6774,13 @@ ttest_simple_ssockt_csocko_small_tcpL(Config) when is_list(Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
which_ttest_runtime(Config) when is_list(Config) ->
- case lists:keysearch(esock_test_ttest_runtime, 1, Config) of
- {value, {esock_test_ttest_runtime, Runtime}} ->
- Runtime;
- false ->
- which_ttest_runtime_env()
+ case proplists:get_value(category, Config, standard) of
+ standard ->
+ proplists:get_value(esock_test_ttest_runtime,
+ Config, which_ttest_runtime_env());
+ bench ->
+ %% We always run a certain time for benchmark runs
+ ?TTEST_BENCH_RUNTIME
end.
which_ttest_runtime_env() ->
@@ -6763,7 +6789,7 @@ which_ttest_runtime_env() ->
which_ttest_runtime_env(TStr) when is_list(TStr) ->
which_ttest_runtime_env2(lists:reverse(TStr));
which_ttest_runtime_env(false) ->
- ?TTEST_RUNTIME.
+ ?TTEST_STANDARD_RUNTIME.
%% The format is: <int>[unit]
@@ -6785,7 +6811,7 @@ convert_time(TStrRev, Convert) ->
I -> Convert(I)
catch
_:_ ->
- ?TTEST_RUNTIME
+ ?TTEST_STANDARD_RUNTIME
end.
%% ttest_tcp(TC,
@@ -6794,7 +6820,7 @@ convert_time(TStrRev, Convert) ->
%% ClientMod, ClientActive,
%% MsgID, MaxOutstanding) ->
%% ttest_tcp(TC,
-%% ?TTEST_RUNTIME,
+%% ?TTEST_STANDARD_RUNTIME,
%% Domain,
%% ServerMod, ServerActive,
%% ClientMod, ClientActive,
--
2.43.0