File 0221-erts-reduce-console-output-for-Common-Test.patch of Package erlang
From 3a55d118ace7f6ff63dbd8c610a56ab565e0a220 Mon Sep 17 00:00:00 2001
From: Maxim Fedorov <maximfca@gmail.com>
Date: Wed, 15 Dec 2021 15:52:08 -0800
Subject: [PATCH 1/2] [erts] reduce console output for Common Test
Some test cases produce 20+ Mb of debug output which does
not help to figure out a problem. This change suppresses
logs, leaving a chance to remove suppression for local runs.
---
erts/emulator/sys/common/erl_check_io.c | 7 ++++-
erts/emulator/test/busy_port_SUITE.erl | 10 +++----
erts/emulator/test/driver_SUITE.erl | 23 +++++++---------
erts/emulator/test/port_SUITE.erl | 4 +--
erts/emulator/test/process_SUITE.erl | 25 +++++++++--------
erts/emulator/test/trace_local_SUITE.erl | 34 ++++++++++++++++--------
6 files changed, 59 insertions(+), 44 deletions(-)
diff --git a/erts/emulator/sys/common/erl_check_io.c b/erts/emulator/sys/common/erl_check_io.c
index 5c1f755c45..e5aa36251d 100644
--- a/erts/emulator/sys/common/erl_check_io.c
+++ b/erts/emulator/sys/common/erl_check_io.c
@@ -2955,7 +2955,12 @@ erts_check_io_debug(ErtsCheckIoDebugInfo *ciodip)
erts_dsprintf(dsbufp, "internal fds=%d\n", counters.internal_fds);
#endif
erts_dsprintf(dsbufp, "---------------------------------------------------------\n");
- erts_send_error_to_logger_nogl(dsbufp);
+ if (counters.num_errors > 0)
+ erts_send_error_to_logger_nogl(dsbufp);
+ else {
+ erts_free(ERTS_ALC_T_LOGGER_DSBUF, (void *) dsbufp->str);
+ erts_free(ERTS_ALC_T_LOGGER_DSBUF, (void *) dsbufp);
+ }
#ifdef ERTS_SYS_CONTINOUS_FD_NUMBERS
erts_free(ERTS_ALC_T_TMP, (void *) counters.epep);
#endif
diff --git a/erts/emulator/test/busy_port_SUITE.erl b/erts/emulator/test/busy_port_SUITE.erl
index a90a2d13c7..c1f576276f 100644
--- a/erts/emulator/test/busy_port_SUITE.erl
+++ b/erts/emulator/test/busy_port_SUITE.erl
@@ -255,7 +255,7 @@ no_trap_exit(Config) when is_list(Config) ->
Pid = fun_spawn(fun no_trap_exit_process/3, [self(), linked, Config]),
receive
{Pid, port_created, Port} ->
- io:format("Process ~w created port ~w", [Pid, Port]),
+ ct:log("Process ~w created port ~w", [Pid, Port]),
exit(Port, die);
Other1 ->
ct:fail({unexpected_message, Other1})
@@ -278,7 +278,7 @@ no_trap_exit_unlinked(Config) when is_list(Config) ->
[self(), unlink, Config]),
receive
{Pid, port_created, Port} ->
- io:format("Process ~w created port ~w", [Pid, Port]),
+ ct:log("Process ~w created port ~w", [Pid, Port]),
exit(Port, die);
Other1 ->
ct:fail({unexpected_message, Other1})
@@ -320,7 +320,7 @@ trap_exit(Config) when is_list(Config) ->
Pid = fun_spawn(fun busy_port_exit_process/2, [self(), Config]),
receive
{Pid, port_created, Port} ->
- io:format("Process ~w created port ~w", [Pid, Port]),
+ ct:log("Process ~w created port ~w", [Pid, Port]),
unlink(Pid),
{status, suspended} = process_info(Pid, status),
exit(Port, die);
@@ -755,7 +755,7 @@ run_command(_M,spawn,{Args,Opts}) ->
run_command(M,spawn,Args) ->
run_command(M,spawn,{Args,[]});
run_command(Mod,Func,Args) ->
- erlang:display({{Mod,Func,Args}, erlang:system_time(microsecond)}),
+ %% erlang:display({{Mod,Func,Args}, erlang:system_time(microsecond)}),
apply(Mod,Func,Args).
validate_scenario(Data,[{print,Var}|T]) ->
@@ -869,7 +869,7 @@ chk_not_value(_, _) ->
wait_for([]) ->
ok;
wait_for(Pids) ->
- io:format("Waiting for ~p", [Pids]),
+ ct:log("Waiting for ~p", [Pids]),
receive
{'EXIT', Pid, normal} ->
wait_for(lists:delete(Pid, Pids));
diff --git a/erts/emulator/test/driver_SUITE.erl b/erts/emulator/test/driver_SUITE.erl
index 4e97b77db9..4fb177a116 100644
--- a/erts/emulator/test/driver_SUITE.erl
+++ b/erts/emulator/test/driver_SUITE.erl
@@ -211,12 +211,10 @@ init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->
end,
erts_debug:get_internal_state(check_io_debug)
end),
- erlang:display({init_per_testcase, Case}),
0 = element(1, CIOD),
[{testcase, Case}|Config].
-end_per_testcase(Case, Config) ->
- erlang:display({end_per_testcase, Case}),
+end_per_testcase(_Case, Config) ->
try rpc(Config, fun() ->
get_stable_check_io_info(),
erts_debug:get_internal_state(check_io_debug)
@@ -1016,12 +1014,11 @@ chkio_test({erts_poll_info, Before},
chk_chkio_port(Port),
Fun(),
During = get_check_io_total(erlang:system_info(check_io)),
- erlang:display(During),
[0 = element(1, erts_debug:get_internal_state(check_io_debug)) ||
%% The pollset is not stable when running the fallback testcase
Test /= ?CHKIO_USE_FALLBACK_POLLSET],
- io:format("During test: ~p~n", [During]),
+ ct:log("During test: ~p~n", [During]),
chk_chkio_port(Port),
case erlang:port_control(Port, ?CHKIO_STOP, "") of
Res when is_list(Res) ->
@@ -2085,12 +2082,12 @@ async_blast(Config) when is_list(Config) ->
end, Ps),
End = os:timestamp(),
MemAfter = driver_alloc_size(),
- io:format("MemBefore=~p, MemMid=~p, MemAfter=~p~n",
+ ct:log("MemBefore=~p, MemMid=~p, MemAfter=~p~n",
[MemBefore, MemMid, MemAfter]),
AsyncBlastTime = timer:now_diff(End,Start)/1000000,
- io:format("AsyncBlastTime=~p~n", [AsyncBlastTime]),
+ ct:log("AsyncBlastTime=~p~n", [AsyncBlastTime]),
MemBefore = MemAfter,
- erlang:display({async_blast_time, AsyncBlastTime}),
+ ct:log({async_blast_time, AsyncBlastTime}),
ok.
thr_msg_blast_receiver(_Port, N, N) ->
@@ -2141,13 +2138,12 @@ thr_msg_blast(Config) when is_list(Config) ->
ok
end,
MemAfter = driver_alloc_size(),
- io:format("MemBefore=~p, MemAfter=~p~n",
+ ct:log("MemBefore=~p, MemAfter=~p~n",
[MemBefore, MemAfter]),
ThrMsgBlastTime = timer:now_diff(End,Start)/1000000,
- io:format("ThrMsgBlastTime=~p~n", [ThrMsgBlastTime]),
+ ct:log("ThrMsgBlastTime=~p~n", [ThrMsgBlastTime]),
MemBefore = MemAfter,
Res = {thr_msg_blast_time, ThrMsgBlastTime},
- erlang:display(Res),
Res.
-define(IN_RANGE(LoW_, VaLuE_, HiGh_),
@@ -2408,8 +2404,7 @@ count_pp_sched_stop(Ps) ->
PNs = lists:map(fun (P) -> {P, 0} end, Ps),
receive {trace_delivered, all, Td} -> ok end,
Res = count_proc_sched(Ps, PNs),
- io:format("Scheduling counts: ~p~n", [Res]),
- erlang:display({scheduling_counts, Res}),
+ ct:log("Scheduling counts: ~p~n", [Res]),
Res.
do_inc_pn(_P, []) ->
diff --git a/erts/emulator/test/port_SUITE.erl b/erts/emulator/test/port_SUITE.erl
index a34e0147d4..8aae70494b 100644
--- a/erts/emulator/test/port_SUITE.erl
+++ b/erts/emulator/test/port_SUITE.erl
@@ -772,7 +772,7 @@ iter_max_ports_test(Config) ->
L = rpc:call(Node,?MODULE,do_iter_max_ports,[Iters, Command]),
test_server:stop_node(Node),
- io:format("Result: ~p",[L]),
+ ct:log("Result: ~p",[L]),
all_equal(L),
all_equal(L),
{comment, "Max ports: " ++ integer_to_list(hd(L))}.
@@ -2256,7 +2256,7 @@ port_expect(Config, Actions, HSize, CmdLine, Options0) ->
_ -> {packet, HSize}
end,
Options = [PortType|Options0],
- io:format("open_port({spawn, ~p}, ~p)", [Cmd, Options]),
+ ct:log("open_port({spawn, ~p}, ~p)", [Cmd, Options]),
Port = open_port({spawn, Cmd}, Options),
port_expect(Port, Actions, Options),
Port.
diff --git a/erts/emulator/test/process_SUITE.erl b/erts/emulator/test/process_SUITE.erl
index 1c3da584ef..354e4e054d 100644
--- a/erts/emulator/test/process_SUITE.erl
+++ b/erts/emulator/test/process_SUITE.erl
@@ -328,7 +328,19 @@ trap_exit_badarg(Config) when is_list(Config) ->
ct:timetrap({seconds, 10}),
start_spawner(),
process_flag(trap_exit, true),
- test_server:do_times(10, fun trap_exit_badarg/0),
+ try
+ %% suppress =ERROR REPORT=== emulator messages
+ ok = logger:add_primary_filter(suppress_log_spam, {
+ fun(#{meta := #{error_logger := #{emulator := true, tag := error}}}, _Report) ->
+ stop;
+ (_Meta, _Report) ->
+ ignore
+ end, ok}),
+ test_server:do_times(10, fun trap_exit_badarg/0),
+ ct:sleep(500) %% flush logging
+ after
+ ok = logger:remove_primary_filter(suppress_log_spam)
+ end,
stop_spawner(),
ok.
@@ -2847,15 +2847,12 @@ spawn_request_monitor_demonitor(Config)
spawn_request(Node, BlockFun, [{priority,max}, link]),
receive after 100 -> ok end,
- erlang:display(spawning),
erlang:yield(),
R = spawn_request(Node, timer, sleep, [10000], [monitor]),
%% Should not be possible to demonitor
%% before operation has succeeded...
- erlang:display(premature_demonitor),
{monitors, []} = process_info(self(), monitors),
false = erlang:demonitor(R, [info]), %% Should be ignored by VM...
- erlang:display(wait_success),
receive
{spawn_reply, R, ok, P} ->
erlang:display(demonitor),
@@ -2864,7 +2861,6 @@ spawn_request_monitor_demonitor(Config)
{monitors, []} = process_info(self(), monitors),
exit(P, kill)
end,
- erlang:display(done),
stop_node(Node),
ok.
@@ -3079,7 +3084,6 @@ spawn_request_abandon_bif(Config) when is_list(Config) ->
C = "Got " ++ integer_to_list(NoA1) ++ " and "
++ integer_to_list(NoA2) ++ " abandoneds of 2*"
++ integer_to_list(TotOps) ++ " ops!",
- erlang:display(C),
true = NoA1 /= 0,
true = NoA1 /= TotOps,
true = NoA2 /= 0,
diff --git a/erts/emulator/test/trace_local_SUITE.erl b/erts/emulator/test/trace_local_SUITE.erl
index 8cf8c81b7a..e64c15c4ef 100644
--- a/erts/emulator/test/trace_local_SUITE.erl
+++ b/erts/emulator/test/trace_local_SUITE.erl
@@ -744,15 +744,27 @@ exception_test(Opts) ->
shutdown();
true ->
Exceptions = exceptions(),
- lists:foreach(
- fun ({Func,Args}) ->
- exception_test_setup(
- [procs|ProcFlags],
- PatFlags),
- exception_test(Opts, Func, Args),
- shutdown()
- end,
- Exceptions)
+ try
+ %% suppress =ERROR REPORT=== emulator messages
+ ok = logger:add_primary_filter(suppress_log_spam, {
+ fun(#{meta := #{error_logger := #{emulator := true, tag := error}}}, _) ->
+ stop;
+ (_Meta, _Msg) ->
+ ignore
+ end, ok}),
+ lists:foreach(
+ fun ({Func,Args}) ->
+ exception_test_setup(
+ [procs|ProcFlags],
+ PatFlags),
+ exception_test(Opts, Func, Args),
+ shutdown()
+ end,
+ Exceptions)
+ after
+ %% remove the suppression for ERROR REPORTS
+ ok = logger:remove_primary_filter(suppress_log_spam)
+ end
end,
ok.
@@ -778,7 +790,7 @@ exceptions() ->
exception_test_setup(ProcFlags, PatFlags) ->
Pid = setup(ProcFlags),
- io:format("=== exception_test_setup(~p, ~p): ~p~n",
+ ct:log("=== exception_test_setup(~p, ~p): ~p~n",
[ProcFlags,PatFlags,Pid]),
Mprog = [{'_',[],[{exception_trace}]}],
erlang:trace_pattern({?MODULE,'_','_'}, Mprog, PatFlags),
@@ -792,7 +804,7 @@ exception_test_setup(ProcFlags, PatFlags) ->
-record(exc_opts, {nocatch=false, meta=false}).
exception_test(Opts, Func0, Args0) ->
- io:format("=== exception_test(~p, ~p, ~p)~n",
+ ct:log("=== exception_test(~p, ~p, ~p)~n",
[Opts,Func0,abbr(Args0)]),
Apply = proplists:get_bool(apply, Opts),
Function = proplists:get_bool(function, Opts),
--
2.31.1