File 8231-stdlib-reduce-test-log-on-gh.patch of Package erlang
From 2f9a0cd01fb72cecc4b13ac0f6ea5a1a3d1bd8df Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Thu, 5 Dec 2024 09:40:49 +0100
Subject: [PATCH] stdlib: reduce test log on gh
- enable cte_track
- redirect logger events out of terminal output
- replace ct:pal with ct:log in stdlib test suites
---
lib/common_test/src/cte_track.erl | 7 +--
lib/stdlib/test/gen_event_SUITE.erl | 2 +-
lib/stdlib/test/gen_server_SUITE.erl | 14 +++---
.../format_status_server.erl | 4 +-
.../format_status_statem.erl | 4 +-
lib/stdlib/test/io_proto_SUITE.erl | 8 +---
lib/stdlib/test/peer_SUITE.erl | 4 +-
lib/stdlib/test/rand_SUITE.erl | 44 +++++++++----------
lib/stdlib/test/stdlib_gh.spec | 3 ++
9 files changed, 45 insertions(+), 45 deletions(-)
diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl
index aa21d941f0..c617895cbf 100644
--- a/lib/stdlib/test/gen_event_SUITE.erl
+++ b/lib/stdlib/test/gen_event_SUITE.erl
@@ -1169,7 +1169,7 @@ error_format_status(Module) when is_atom(Module) ->
FmtState, _]}} ->
ok;
Other ->
- ct:pal("Unexpected: ~p", [Other]),
+ ct:log("Unexpected: ~p", [Other]),
ct:fail(failed)
after 5000 ->
ct:fail({exit_gen_event,flush()})
diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index 95fafd66d8..6f4972beed 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -1723,13 +1723,13 @@ multicall_recv_opt_test(Type) ->
_Warmup = time_multicall(ExpRes, Nodes, Name, Req, Tmo, Loops div 10),
Empty = time_multicall(ExpRes, Nodes, Name, Req, Tmo, Loops),
- ct:pal("Time with empty message queue: ~p microsecond~n",
+ ct:log("Time with empty message queue: ~p microsecond~n",
[erlang:convert_time_unit(Empty, native, microsecond)]),
make_msgq(HugeMsgQ),
Huge = time_multicall(ExpRes, Nodes, Name, Req, Tmo, Loops),
- ct:pal("Time with huge message queue: ~p microsecond~n",
+ ct:log("Time with huge message queue: ~p microsecond~n",
[erlang:convert_time_unit(Huge, native, microsecond)]),
lists:foreach(fun ({_Node, {Ctrl, _Srv}}) -> unlink(Ctrl) end, SrvList),
@@ -2070,7 +2070,7 @@ error_format_status(Module) when is_atom(Module) ->
ClientPid, [_|_] = _ClientStack]}} ->
ok;
Other ->
- ct:pal("Unexpected: ~p", [Other]),
+ ct:log("Unexpected: ~p", [Other]),
ct:fail(failed)
end,
receive
@@ -2135,7 +2135,7 @@ crash_in_format_status(Module, Match) when is_atom(Module) ->
ClientPid, [_|_] = _ClientStack]}} ->
ok;
Other ->
- ct:pal("Unexpected: ~p", [Other]),
+ ct:log("Unexpected: ~p", [Other]),
ct:fail(failed)
after 5000 ->
io:format("Timeout: expected error logger msg", []),
@@ -2174,7 +2174,7 @@ throw_in_format_status(Module, Match) when is_atom(Module) ->
ClientPid, [_|_] = _ClientStack]}} ->
ok;
Other ->
- ct:pal("Unexpected: ~p", [Other]),
+ ct:log("Unexpected: ~p", [Other]),
ct:fail(failed)
after 5000 ->
io:format("Timeout: expected error logger msg", []),
@@ -2234,7 +2234,7 @@ format_all_status(Config) when is_list(Config) ->
ClientPid, [_|_] = _ClientStack]}} ->
ok;
Other ->
- ct:pal("Unexpected: ~p", [Other]),
+ ct:log("Unexpected: ~p", [Other]),
ct:fail(failed)
after 5000 ->
io:format("Timeout: expected error logger msg", []),
@@ -2255,7 +2255,7 @@ format_all_status(Config) when is_list(Config) ->
ClientPid, [_|_] = _ClientStack2]}} ->
ok;
Other2 ->
- ct:pal("Unexpected: ~p", [Other2]),
+ ct:log("Unexpected: ~p", [Other2]),
ct:fail(failed)
after 5000 ->
io:format("Timeout: expected error logger msg", []),
diff --git a/lib/stdlib/test/gen_server_SUITE_data/format_status_server.erl b/lib/stdlib/test/gen_server_SUITE_data/format_status_server.erl
index 96f1f74132..17b25b584b 100644
--- a/lib/stdlib/test/gen_server_SUITE_data/format_status_server.erl
+++ b/lib/stdlib/test/gen_server_SUITE_data/format_status_server.erl
@@ -48,8 +48,8 @@ format_status(#{ state := {_,_,Fun} } = S) when is_function(Fun) ->
format_status(#{ message := Msg } = S) when not is_map_key(state, S) ->
S#{message := {message,Msg}};
format_status(#{ reason := _, state := State } = Map) ->
- ct:pal("format_status(~p)",[Map]),
+ ct:log("format_status(~p)",[Map]),
Map#{ state => {formatted, State}};
format_status(Map) ->
- ct:pal("format_status(~p)",[Map]),
+ ct:log("format_status(~p)",[Map]),
Map#{ state => format_status_called }.
diff --git a/lib/stdlib/test/gen_statem_SUITE_data/format_status_statem.erl b/lib/stdlib/test/gen_statem_SUITE_data/format_status_statem.erl
index 7c0ee1f4d0..1657dd3b67 100644
--- a/lib/stdlib/test/gen_statem_SUITE_data/format_status_statem.erl
+++ b/lib/stdlib/test/gen_statem_SUITE_data/format_status_statem.erl
@@ -33,8 +33,8 @@ terminate(Reason, State, Data) ->
format_status(#{ data := Fun } = S) when is_function(Fun) ->
Fun(S);
format_status(#{ reason := _, state := State, data := Data } = Map) ->
- ct:pal("format_status(~p)",[Map]),
+ ct:log("format_status(~p)",[Map]),
Map#{ state := {formatted, State}, data := {formatted, Data}};
format_status(Map) ->
- ct:pal("format_status(~p)",[Map]),
+ ct:log("format_status(~p)",[Map]),
Map#{ data := format_data, state := format_status_called }.
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index a4ff29008e..4ded29b23b 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -922,9 +922,7 @@ unicode_options_gen(Config) when is_list(Config) ->
DoOneFile1 =
fun(Encoding, N, M) ->
?dbg({Encoding,M,N}),
- io:format("Read test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]),
- io:format(standard_error,
- "Read test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]),
+ ct:log("Read test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]),
Fname = filename:join(Dir,
"genfile_"++enc2str(Encoding)++
"_"++integer_to_list(N)),
@@ -977,9 +975,7 @@ unicode_options_gen(Config) when is_list(Config) ->
DoOneFile2 =
fun(Encoding,N,M) ->
?dbg({Encoding,M,N}),
- io:format("Write test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]),
- io:format(standard_error,
- "Write test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]),
+ ct:log("Write test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]),
Fname = filename:join(Dir,
"genfile_"++enc2str(Encoding)++
"_"++integer_to_list(N)),
diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl
index 11722fd060..2a64ed9b71 100644
--- a/lib/stdlib/test/rand_SUITE.erl
+++ b/lib/stdlib/test/rand_SUITE.erl
@@ -513,7 +513,7 @@ basic_stats_normal(Config) when is_list(Config) ->
lists:filter(
fun (R) -> R =/= [] end,
[begin
- ct:pal(
+ ct:log(
"Testing normal(~.2f, ~.2f)~n",
[float(IntendedMean), float(IntendedVariance)]),
lists:filter(
@@ -757,7 +757,7 @@ stats_standard_normal(Fun, S, Retries) ->
P0 = math:erf(1 / W),
Rounds = TargetHits * ceil(1.0 / P0),
Histogram = array:new({default, 0}),
- ct:pal(
+ ct:log(
"Running standard normal test against ~w std devs for ~w seconds...",
[StdDevs, Seconds]),
StopTime = erlang:monotonic_time(second) + Seconds,
@@ -770,7 +770,7 @@ stats_standard_normal(Fun, S, Retries) ->
TopPrecision = math:sqrt(TotalRounds * TopP) / StdDevs,
OutlierProbability = math:erfc(Outlier / Sqrt2) * TotalRounds,
InvOP = 1.0 / OutlierProbability,
- ct:pal(
+ ct:log(
"Total rounds: ~w, tolerance: 1/~.2f..1/~.2f, "
"outlier: ~.2f, probability 1/~.2f.",
[TotalRounds, Precision, TopPrecision, Outlier, InvOP]),
@@ -798,7 +798,7 @@ stats_standard_normal(Fun, S, Retries, Failure) ->
0 ->
ct:fail(Failure);
NewRetries ->
- ct:pal("Retry due to TC glitch: ~p", [Failure]),
+ ct:log("Retry due to TC glitch: ~p", [Failure]),
stats_standard_normal(Fun, S, NewRetries)
end.
%%
@@ -887,7 +887,7 @@ check_histogram(
uniform_real_conv(Config) when is_list(Config) ->
[begin
-%% ct:pal("~13.16.0bx~3.16.0b: ~p~n", [M,E,Gen]),
+%% ct:log("~13.16.0bx~3.16.0b: ~p~n", [M,E,Gen]),
uniform_real_conv_check(M, E, Gen)
end || {M, E, Gen} <- uniform_real_conv_data()],
uniform_real_scan(0),
@@ -982,14 +982,14 @@ uniform_real_conv_check(M, E, Gen) ->
try uniform_real_gen(Gen) of
F -> F;
FF ->
- ct:pal(
+ ct:log(
"~s =/= ~s: ~s~n",
[rand:float2str(FF), rand:float2str(F),
[["16#",integer_to_list(G,16),$\s]||G<-Gen]]),
ct:fail({neq, FF, F})
catch
Error:Reason:Stacktrace ->
- ct:pal(
+ ct:log(
"~w:~p ~s: ~s~n",
[Error, Reason, rand:float2str(F),
[["16#",integer_to_list(G,16),$\s]||G<-Gen]]),
@@ -1110,7 +1110,7 @@ do_measure(Iterations) ->
algs()
end,
%%
- ct:pal("~nRNG uniform integer range 10000 performance~n",[]),
+ ct:log("~nRNG uniform integer range 10000 performance~n",[]),
[TMarkUniformRange10000,OverheadUniformRange1000|_] =
measure_1(
fun (Mod, _State) ->
@@ -1271,7 +1271,7 @@ do_measure(Iterations) ->
system_time, Iterations,
TMarkUniformRange10000, OverheadUniformRange1000),
%%
- ct:pal("~nRNG uniform integer 32 bit performance~n",[]),
+ ct:log("~nRNG uniform integer 32 bit performance~n",[]),
[TMarkUniform32Bit,OverheadUniform32Bit|_] =
measure_1(
fun (Mod, _State) ->
@@ -1372,7 +1372,7 @@ do_measure(Iterations) ->
system_time, Iterations,
TMarkUniform32Bit, OverheadUniform32Bit),
%%
- ct:pal("~nRNG uniform integer half range performance~n",[]),
+ ct:log("~nRNG uniform integer half range performance~n",[]),
_ =
measure_1(
fun (Mod, State) ->
@@ -1385,7 +1385,7 @@ do_measure(Iterations) ->
end,
Algs, Iterations),
%%
- ct:pal("~nRNG uniform integer half range + 1 performance~n",[]),
+ ct:log("~nRNG uniform integer half range + 1 performance~n",[]),
_ =
measure_1(
fun (Mod, State) ->
@@ -1397,7 +1397,7 @@ do_measure(Iterations) ->
end
end, Algs, Iterations),
%%
- ct:pal("~nRNG uniform integer full range - 1 performance~n",[]),
+ ct:log("~nRNG uniform integer full range - 1 performance~n",[]),
_ =
measure_1(
fun (Mod, State) ->
@@ -1409,7 +1409,7 @@ do_measure(Iterations) ->
end
end, Algs, Iterations),
%%
- ct:pal("~nRNG uniform integer full range performance~n",[]),
+ ct:log("~nRNG uniform integer full range performance~n",[]),
[TMarkUniformFullRange,OverheadUniformFullRange|_] =
measure_1(
fun (Mod, State) ->
@@ -1538,7 +1538,7 @@ do_measure(Iterations) ->
{mwc59,procdict}, Iterations,
TMarkUniformFullRange, OverheadUniformFullRange),
%%
- ct:pal("~nRNG uniform integer full range + 1 performance~n",[]),
+ ct:log("~nRNG uniform integer full range + 1 performance~n",[]),
_ =
measure_1(
fun (Mod, State) ->
@@ -1550,7 +1550,7 @@ do_measure(Iterations) ->
end
end, Algs, Iterations),
%%
- ct:pal("~nRNG uniform integer double range performance~n",[]),
+ ct:log("~nRNG uniform integer double range performance~n",[]),
_ =
measure_1(
fun (Mod, State) ->
@@ -1562,7 +1562,7 @@ do_measure(Iterations) ->
end
end, Algs, Iterations),
%%
- ct:pal("~nRNG uniform integer double range + 1 performance~n",[]),
+ ct:log("~nRNG uniform integer double range + 1 performance~n",[]),
_ =
measure_1(
fun (Mod, State) ->
@@ -1574,7 +1574,7 @@ do_measure(Iterations) ->
end
end, Algs, Iterations),
%%
- ct:pal("~nRNG uniform integer 64 bit performance~n",[]),
+ ct:log("~nRNG uniform integer 64 bit performance~n",[]),
[TMarkUniform64Bit, OverheadUniform64Bit | _] =
measure_1(
fun (Mod, _State) ->
@@ -1601,7 +1601,7 @@ do_measure(Iterations) ->
TMarkUniform64Bit, OverheadUniform64Bit),
%%
ByteSize = 16, % At about 100 bytes crypto_bytes breaks even to exsss
- ct:pal("~nRNG ~w bytes performance~n",[ByteSize]),
+ ct:log("~nRNG ~w bytes performance~n",[ByteSize]),
[TMarkBytes1,OverheadBytes1|_] =
measure_1(
fun (Mod, _State) ->
@@ -1628,7 +1628,7 @@ do_measure(Iterations) ->
TMarkBytes1, OverheadBytes1),
%%
ByteSize2 = 1000, % At about 100 bytes crypto_bytes breaks even to exsss
- ct:pal("~nRNG ~w bytes performance~n",[ByteSize2]),
+ ct:log("~nRNG ~w bytes performance~n",[ByteSize2]),
[TMarkBytes2,OverheadBytes2|_] =
measure_1(
fun (Mod, _State) ->
@@ -1654,7 +1654,7 @@ do_measure(Iterations) ->
end, {mwc59,bytes}, Iterations div 50,
TMarkBytes2, OverheadBytes2),
%%
- ct:pal("~nRNG uniform float performance~n",[]),
+ ct:log("~nRNG uniform float performance~n",[]),
[TMarkUniformFloat,OverheadUniformFloat|_] =
measure_1(
fun (Mod, _State) ->
@@ -1691,7 +1691,7 @@ do_measure(Iterations) ->
{exsp,float}, Iterations,
TMarkUniformFloat, OverheadUniformFloat),
%%
- ct:pal("~nRNG uniform_real float performance~n",[]),
+ ct:log("~nRNG uniform_real float performance~n",[]),
_ =
measure_1(
fun (Mod, _State) ->
@@ -1702,7 +1702,7 @@ do_measure(Iterations) ->
end,
Algs, Iterations),
%%
- ct:pal("~nRNG normal float performance~n",[]),
+ ct:log("~nRNG normal float performance~n",[]),
[TMarkNormalFloat, OverheadNormalFloat|_] =
measure_1(
fun (Mod, _State) ->
--
2.43.0