Skip to content

Commit

Permalink
stdlib: reduce test log on gh
Browse files Browse the repository at this point in the history
- enable cte_track
- redirect logger events out of terminal output
- replace ct:pal with ct:log in stdlib test suites
  • Loading branch information
u3s committed Dec 5, 2024
1 parent 3b92c38 commit 7aec08e
Show file tree
Hide file tree
Showing 7 changed files with 39 additions and 36 deletions.
2 changes: 1 addition & 1 deletion lib/stdlib/test/gen_event_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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()})
Expand Down
14 changes: 7 additions & 7 deletions lib/stdlib/test/gen_server_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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),
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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", []),
Expand Down Expand Up @@ -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", []),
Expand Down Expand Up @@ -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", []),
Expand All @@ -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", []),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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 }.
Original file line number Diff line number Diff line change
Expand Up @@ -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 }.
4 changes: 2 additions & 2 deletions lib/stdlib/test/peer_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -440,7 +440,7 @@ shutdown_test(Config, TC, Shutdown, BlockTime, StopWhileBlocked, MaxWaitTime) ->
WaitTime = End - Start,
BlockTimeLeft = BlockTime + EnsureBlockedWait - (Start - BlockStart),
Connected = lists:member(Node, nodes(connected)),
ct:pal("Connected = ~p~nWaitTime = ~p~nBlockTimeLeft = ~p~n",
ct:log("Connected = ~p~nWaitTime = ~p~nBlockTimeLeft = ~p~n",
[Connected, WaitTime, BlockTimeLeft]),
true = WaitTime =< MaxWaitTime,
case StopWhileBlocked of
Expand Down Expand Up @@ -602,7 +602,7 @@ build_image(Dir) ->
"ENTRYPOINT [\"/opt/lambda/erts-" ++ erlang:system_info(version) ++ "/bin/dyn_erl\", \"-boot\", \"/opt/lambda/releases/1.0.0/start\"]\n",
ok = file:write_file(BuildScript, Dockerfile),
Output = os:cmd("docker build -t lambda " ++ Dir),
ct:pal("Build result: ~s~n", [Output]).
ct:log("Build result: ~s~n", [Output]).

docker(Config) when is_list(Config) ->
case os:find_executable("docker") of
Expand Down
44 changes: 22 additions & 22 deletions lib/stdlib/test/rand_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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(
Expand Down Expand Up @@ -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,
Expand All @@ -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]),
Expand Down Expand Up @@ -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.
%%
Expand Down Expand Up @@ -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),
Expand Down Expand Up @@ -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]]),
Expand Down Expand Up @@ -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) ->
Expand Down Expand Up @@ -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) ->
Expand Down Expand Up @@ -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) ->
Expand All @@ -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) ->
Expand All @@ -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) ->
Expand All @@ -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) ->
Expand Down Expand Up @@ -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) ->
Expand All @@ -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) ->
Expand All @@ -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) ->
Expand All @@ -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) ->
Expand All @@ -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) ->
Expand All @@ -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) ->
Expand All @@ -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) ->
Expand Down Expand Up @@ -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) ->
Expand All @@ -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) ->
Expand Down
3 changes: 3 additions & 0 deletions lib/stdlib/test/stdlib_gh.spec
Original file line number Diff line number Diff line change
Expand Up @@ -7,3 +7,6 @@
"Benchmark only"}.
{skip_cases, "../stdlib_test", gen_server_SUITE,
[multicall_remote_old1],"Broken in docker"}.
{event_handler, {cte_track, []}}.
{enable_builtin_hooks, false}.
{ct_hooks, [{cth_log_redirect, [{mode, replace}]}]}.

0 comments on commit 7aec08e

Please sign in to comment.