Skip to content

Commit

Permalink
ct: Introduce replace mode to cth_log_redirect
Browse files Browse the repository at this point in the history
In addition to the existing way of logging to both the CT HTML logs and
console, allow users to completely replace the standard logging handler
with the log redirect hook, effectively silencing console logging
output during Common Test runs.

Mostly taken from #7375, with the caveat that "add" mode continues being
the default, and no changes outside of the hook take place.

Additionally, group cth_log_redirect test cases together to allow for
easier module verification.
  • Loading branch information
jchristgit committed Nov 22, 2023
1 parent 71841fe commit 7e6dc24
Show file tree
Hide file tree
Showing 3 changed files with 80 additions and 38 deletions.
19 changes: 19 additions & 0 deletions lib/common_test/doc/src/ct_hooks_chapter.xml
Original file line number Diff line number Diff line change
Expand Up @@ -511,6 +511,25 @@ results(State) ->
use another level either change the <c>default</c> handler level before
starting common_test, or use the <seemfa marker="kernel:logger#set_handler_config/3">
<c>logger:set_handler_config/3</c></seemfa> API.</p>
<p>This hook supports the following options:</p>
<taglist>
<tag><c>{mode, add}</c></tag>
<item>
<p>Add <c>cth_log_redirect</c> to the default logging handler:
Logs will be emitted to both standard output via the
default handler, and into the Common Test HTML logs.
This is the default behaviour.</p>
</item>
<tag><c>{mode, replace}</c></tag>
<item>
<p>Replace the <c>default</c> logging handler with <c>cth_log_redirect</c>
instead of logging to both the default handler and this handler.
This effectively silences any logger output which would normally be printed
to standard output during test runs. To enable this mode, you can pass
the following options to <c>ct_run</c>:</p>
<p><c>-enable_builtin_hooks false -ct_hooks cth_log_redirect [{mode,replace}]</c></p>
</item>
</taglist>
</item>
<tag><c>cth_surefire</c></tag>
<item>
Expand Down
21 changes: 14 additions & 7 deletions lib/common_test/src/cth_log_redirect.erl
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,8 @@

%%% Common Test Framework functions handling test specifications.
%%%
%%% This module redirects sasl and error logger info to common test log.
%%% This module redirects sasl, error logger, and standard logger messages to
%%% the common test log.

%% CTH Callbacks
-export([id/1, init/2,
Expand Down Expand Up @@ -56,9 +57,9 @@
id(_Opts) ->
?MODULE.

init(?MODULE, _Opts) ->
init(?MODULE, Opts) ->
ct_util:mark_process(),
ok = start_log_handler(),
ok = start_log_handler(Opts),
{ok, tc_log_async}.

pre_init_per_suite(Suite, Config, State) ->
Expand Down Expand Up @@ -115,7 +116,7 @@ post_end_per_group(_Suite, _Group, Config, Return, State) ->
set_curr_func({group,undefined}, Config),
{Return, State}.

start_log_handler() ->
start_log_handler(Options) ->
case whereis(?MODULE) of
undefined ->
ChildSpec =
Expand All @@ -137,9 +138,15 @@ start_log_handler() ->
_Else ->
{{?DEFAULT_FORMATTER,?DEFAULT_FORMAT_CONFIG},info}
end,
ok = logger:add_handler(?MODULE,?MODULE,
#{level=>DefaultLevel,
formatter=>DefaultFormatter}).
HandlerConfig = #{level => DefaultLevel, formatter => DefaultFormatter},
HandlerName = case proplists:get_value(mode, Options, add) of
add ->
?MODULE;
replace ->
ok = logger:remove_handler(default),
default
end,
ok = logger:add_handler(HandlerName, ?MODULE, HandlerConfig).

init([]) ->
{ok, #eh_state{log_func = tc_log_async}}.
Expand Down
78 changes: 47 additions & 31 deletions lib/common_test/test/ct_hooks_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -112,10 +112,16 @@ all(suite) ->
no_init_suite_config, no_init_config, no_end_config,
failed_sequence, repeat_force_stop, config_clash,
callbacks_on_skip, fallback, data_dir,
cth_log, cth_log_formatter, cth_log_unexpect
{group, cth_log_redirect}
]
).

groups() ->
[
{cth_log_redirect, [], [cth_log_unexpect, cth_log_formatter,
cth_log, cth_log_mode_replace]}
].


%%--------------------------------------------------------------------
%% TEST CASES
Expand Down Expand Up @@ -300,36 +306,7 @@ data_dir(Config) when is_list(Config) ->
cth_log(Config) when is_list(Config) ->
%% test that cth_log_redirect writes properly to
%% html I/O log
ct:timetrap({minutes,10}),
StartOpts = do_test(cth_log, "cth_log_SUITE.erl", [], Config),
Logdir = proplists:get_value(logdir, StartOpts),
TCLogs =
filelib:wildcard(
filename:join(Logdir,
"ct_run*/cth.tests*/run*/cth_log_suite.tc*.html")),
lists:foreach(
fun(TCLog) ->
{ok,Bin} = file:read_file(TCLog),
Ts = string:lexemes(binary_to_list(Bin),[$\n]),
Matches = lists:foldl(fun("=ERROR"++_, {E,I,N,L}) ->
{E+1,I,N,L};
("=INFO"++_, {E,I,N,L}) ->
{E,I+1,N,L};
("=NOTICE"++_, {E,I,N,L}) ->
{E,I,N+1,L};
("Logger"++_, {E,I,N,L}) ->
{E,I,N,L+1};
(_, N) -> N
end, {0,0,0,0}, Ts),
ct:pal("~p ({Error,Info,Notice,Log}) matches in ~tp",
[Matches,TCLog]),
MatchList = tuple_to_list(Matches),
case [N || N <- MatchList, N<1] of
[] -> ok;
_ -> exit({missing_io,TCLog})
end
end, TCLogs),
ok.
verify_cth_log_output(Config, [], []).

cth_log_formatter(Config) when is_list(Config) ->
%% test that cth_log_redirect writes properly to
Expand Down Expand Up @@ -398,6 +375,12 @@ cth_log_unexpect(Config) when is_list(Config) ->
end, UnexpIoLogs),
ok.

cth_log_mode_replace(Config) when is_list(Config) ->
%% test that cth_log_redirect writes properly to
%% html I/O log when replace mode is used
verify_cth_log_output(Config, [{cth_log_redirect, [{mode, replace}]}],
[{enable_builtin_hooks, false}]).

%% OTP-10599 adds the Suite argument as first argument to all hook
%% callbacks that did not have a Suite argument from before. This test
%% checks that ct_hooks will fall back to old versions of callbacks if
Expand Down Expand Up @@ -542,6 +525,39 @@ gen_config(Name,KeyVals,Config) ->
|| {Key,Value} <- KeyVals]),
File.

verify_cth_log_output(Config, CTHooks, ExtraOpts) ->
ct:timetrap({minutes,10}),
StartOpts = do_test(cth_log, "cth_log_SUITE.erl", CTHooks, Config, ok, 2, ExtraOpts),
Logdir = proplists:get_value(logdir, StartOpts),
TCLogs =
filelib:wildcard(
filename:join(Logdir,
"ct_run*/cth.tests*/run*/cth_log_suite.tc*.html")),
lists:foreach(
fun(TCLog) ->
{ok,Bin} = file:read_file(TCLog),
Ts = string:lexemes(binary_to_list(Bin),[$\n]),
Matches = lists:foldl(fun("=ERROR"++_, {E,I,N,L}) ->
{E+1,I,N,L};
("=INFO"++_, {E,I,N,L}) ->
{E,I+1,N,L};
("=NOTICE"++_, {E,I,N,L}) ->
{E,I,N+1,L};
("Logger"++_, {E,I,N,L}) ->
{E,I,N,L+1};
(_, N) -> N
end, {0,0,0,0}, Ts),
ct:pal("~p ({Error,Info,Notice,Log}) matches in ~tp",
[Matches,TCLog]),
MatchList = tuple_to_list(Matches),
case [N || N <- MatchList, N<1] of
[] -> ok;
_ -> exit({missing_io,TCLog})
end
end, TCLogs),
ok.


%%%-----------------------------------------------------------------
%%% TEST EVENTS
%%%-----------------------------------------------------------------
Expand Down

0 comments on commit 7e6dc24

Please sign in to comment.