Skip to content

Commit

Permalink
Quiet down ct_run startup logs
Browse files Browse the repository at this point in the history
The new output looks as follows:

    ============================= common test starting =============================
    cwd: /home/user/workspace/otp/_worktree/more-silent-tests/lib/inets/make_test_dir/inets_test
    make: 1 test module(s) compiled
    collected: 1 test(s), 451 case(s) in 11 suite(s)

    Testing make_test_dir.inets_test: Starting test, 451 test cases

The new module `ct_console` is introduced to serve as the main point for
new "fancy" terminal formatting.

Note that there is some duplication going on with respect to the color
formatting from `shell_docs`. We also don't really respect any "no
color" options the user might have (yet). This should later become part
of the `ct_console` module once we've figured out a clean way to do so.

The `Testing` output and below will be worked on in a following commit.
  • Loading branch information
jchristgit committed Jul 14, 2023
1 parent a13c7f0 commit 9b7f21b
Show file tree
Hide file tree
Showing 5 changed files with 86 additions and 40 deletions.
1 change: 1 addition & 0 deletions lib/common_test/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ MODULES= \
ct \
ct_logs \
ct_framework \
ct_console \
ct_ftp \
ct_ssh \
ct_snmp \
Expand Down
31 changes: 31 additions & 0 deletions lib/common_test/src/ct_console.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,31 @@
% Deals with output formatting for the terminal.

-module(ct_console).
-export([print_header/1]).


print_header(Message) ->
{ok, Columns} = terminal_width(user),
MessageLength = length(Message),
PaddingSize = trunc(Columns / 2) - trunc(MessageLength / 2) - 1,
% shell_docs contains a lot of useful functions that we could maybe factor
% out and use here.
Start = "\033[;1m",
Stop = "\033[0m",
case PaddingSize of
Amount when Amount < 0 ->
% Not enough space to print the padding, proceed normally.
io:format("~s~s~s~n", [Start, Message, Stop]);
_Amount ->
Padding = lists:duplicate(PaddingSize, "="),
io:format("~s~s ~s ~s~s~n", [Start, Padding, Message, Padding, Stop])
end.

-spec terminal_width(atom()) -> {ok, pos_integer()}.
terminal_width(Driver) ->
case io:columns(Driver) of
{ok, _Columns} = Result ->
Result;
{error, enotsup} ->
{ok, 80}
end.
63 changes: 36 additions & 27 deletions lib/common_test/src/ct_make.erl
Original file line number Diff line number Diff line change
Expand Up @@ -38,6 +38,20 @@
all() ->
all([]).

%% Run compilation via `Emakefile' in the current directory.
%% Returns one of the following:
%%
%% - `Result' when the `noexec' option was passed as `true',
%% - `{up_to_date, Result}' when all modules are up-to-date, or
%% - `{error, Result}' when compilation failed for any module
%%
%% where `Result' contains tuples in the form:
%%
%% - `{File, out_of_date}' if the file needs recompilation but the `noexec'
%% option was passed,
%% - `{File, up_to_date}' if the file does not need any recompilation,
%% - `{File, {error, Warnings, Errors}}}' on compilation failure, or
%% - `{File, {ok, Warnings}}' on success.
all(Options) ->
{MakeOpts,CompileOpts} = sort_options(Options,[],[]),
case read_emakefile('Emakefile',CompileOpts) of
Expand Down Expand Up @@ -200,12 +214,8 @@ load_opt(Opts) ->
process([{[],_Opts}|Rest], NoExec, Load, Result) ->
process(Rest, NoExec, Load, Result);
process([{[H|T],Opts}|Rest], NoExec, Load, Result) ->
case recompilep(coerce_2_list(H), NoExec, Load, Opts) of
error ->
process([{T,Opts}|Rest], NoExec, Load, [{H,error}|Result]);
Info ->
process([{T,Opts}|Rest], NoExec, Load, [{H,Info}|Result])
end;
CompileResult = recompilep(coerce_2_list(H), NoExec, Load, Opts),
process([{T, Opts} | Rest], NoExec, Load, [{H, CompileResult} | Result]);
process([], NoExec, _Load, Result) ->
if not NoExec ->
case lists:keysearch(error, 2, Result) of
Expand Down Expand Up @@ -272,25 +282,25 @@ include_opt([]) ->
%% Actually recompile and load the file, depending on the flags.
%% Where load can be netload | load | noload

recompile(File, NoExec, Load, Opts) ->
case do_recompile(File, NoExec, Load, Opts) of
{ok,_} -> ok;
Other -> Other
end.

do_recompile(_File, true, _Load, _Opts) ->
recompile(_File, true, _Load, _Opts) ->
out_of_date;
do_recompile(File, false, Load, Opts) ->
io:format("Recompile: ~ts\n",[File]),
case compile:file(File, [report_errors, report_warnings |Opts]) of
Ok when is_tuple(Ok), element(1,Ok)==ok ->
maybe_load(element(2,Ok), Load, Opts);
_Error ->
error
recompile(File, false, Load, Opts) ->
case compile:file(File, [return_errors, return_warnings | Opts]) of
{ok, Module, Warnings} ->
{Loaded, ShouldLoad, Why} = maybe_load(Module, Load, Opts),
case {Loaded, ShouldLoad, Why} of
%% TODO: This needs checking whether the Reason is in a format we expect
{false, true, Reason} when Reason =/= none ->
{ok, [Reason | Warnings]};
_ ->
{ok, Warnings}
end;
{error, _Errors, _Warnings} = Result ->
Result
end.

maybe_load(_Mod, noload, _Opts) ->
ok;
{false, false, none};
maybe_load(Mod, Load, Opts) ->
%% We have compiled File with options Opts. Find out where the
%% output file went to, and load it.
Expand All @@ -299,27 +309,26 @@ maybe_load(Mod, Load, Opts) ->
Dir = proplists:get_value(outdir,Opts,"."),
do_load(Dir, Mod, Load);
false ->
io:format("** Warning: No object file created - nothing loaded **~n"),
ok
{false, true}
end.

do_load(Dir, Mod, load) ->
code:purge(Mod),
case code:load_abs(filename:join(Dir, Mod),Mod) of
{module,Mod} ->
{ok,Mod};
{true, true, none};
Other ->
Other
{false, true, Other}
end;
do_load(Dir, Mod, netload) ->
Obj = atom_to_list(Mod) ++ code:objfile_extension(),
Fname = filename:join(Dir, Obj),
case file:read_file(Fname) of
{ok,Bin} ->
rpc:eval_everywhere(code,load_binary,[Mod,Fname,Bin]),
{ok,Mod};
{true, true};
Other ->
Other
{false, true, Other}
end.

exists(File) ->
Expand Down
25 changes: 13 additions & 12 deletions lib/common_test/src/ct_run.erl
Original file line number Diff line number Diff line change
Expand Up @@ -130,8 +130,9 @@ script_start(Args) ->
_ -> ""
end
end,
io:format("~nCommon Test~s starting (cwd is ~ts)~n~n",
[CTVsn,Cwd]),
Header = io_lib:format("common test~s starting", [CTVsn]),
ct_console:print_header(Header),
io:format("cwd: ~ts~n", [Cwd]),
Self = self(),
Pid = spawn_link(fun() -> script_start1(Self, Args) end),
receive
Expand Down Expand Up @@ -693,7 +694,6 @@ script_start3(Opts, Args) ->
true ->
%% no start options, use default "-dir ./"
{ok,Dir} = file:get_cwd(),
io:format("ct_run -dir ~ts~n~n", [Dir]),
script_start4(Opts#opts{tests = tests([Dir])}, Args)
end
end.
Expand Down Expand Up @@ -870,7 +870,8 @@ run_test1(StartOpts) when is_list(StartOpts) ->
undefined ->
Tracing = start_trace(StartOpts),
{ok,Cwd} = file:get_cwd(),
io:format("~nCommon Test starting (cwd is ~ts)~n~n", [Cwd]),
ct_console:print_header("common test starting"),
io:format("cwd: ~ts~n", [Cwd]),
Res =
case ct_repeat:loop_test(func, StartOpts) of
false ->
Expand Down Expand Up @@ -1352,7 +1353,8 @@ run_testspec1_fun(TestSpec) ->

run_testspec1(TestSpec) ->
{ok,Cwd} = file:get_cwd(),
io:format("~nCommon Test starting (cwd is ~ts)~n~n", [Cwd]),
ct_console:print_header("common test starting"),
io:format("cwd: ~ts~n", [Cwd]),
case catch run_testspec2(TestSpec) of
{'EXIT',Reason} ->
ok = file:set_cwd(Cwd),
Expand Down Expand Up @@ -1729,7 +1731,8 @@ compile_and_run(Tests, Skip, Opts, Args) ->
log_ts_names(Opts#opts.testspec_files),
TestSuites = suite_tuples(Tests),

{_TestSuites1,SuiteMakeErrors,AllMakeErrors} =
io:format("make: "),
{TestSuites2,SuiteMakeErrors,AllMakeErrors} =
case application:get_env(common_test, auto_compile) of
{ok,false} ->
{TestSuites1,SuitesNotFound} =
Expand All @@ -1742,6 +1745,7 @@ compile_and_run(Tests, Skip, Opts, Args) ->

case continue(AllMakeErrors, Opts#opts.abort_if_missing_suites) of
true ->
io:format("~p test module(s) compiled~n", [length(TestSuites2)]),
SavedErrors = save_make_errors(SuiteMakeErrors),
ct_repeat:log_loop_info(Args),

Expand Down Expand Up @@ -1832,7 +1836,6 @@ possibly_spawn(true, Tests, Skip, Opts) ->

%% attempt to compile the modules specified in TestSuites
auto_compile(TestSuites) ->
io:format("~nCommon Test: Running make in test directories...~n"),
UserInclude =
case application:get_env(common_test, include) of
{ok,UserInclDirs} when length(UserInclDirs) > 0 ->
Expand Down Expand Up @@ -2186,15 +2189,13 @@ do_run_test(Tests, Skip, Opts0) ->
NoOfTests = length(Tests),
NoOfSuites = length(Suites1),
ct_util:warn_duplicates(Suites1),
{ok,Cwd} = file:get_cwd(),
io:format("~nCWD set to: ~tp~n", [Cwd]),
if NoOfCases == unknown ->
io:format("~nTEST INFO: ~w test(s), ~w suite(s)~n~n",
io:format("collected: ~w test(s), ~w suite(s)~n~n",
[NoOfTests,NoOfSuites]),
ct_logs:log("TEST INFO","~w test(s), ~w suite(s)",
[NoOfTests,NoOfSuites]);
true ->
io:format("~nTEST INFO: ~w test(s), ~w case(s) "
io:format("collected: ~w test(s), ~w case(s) "
"in ~w suite(s)~n~n",
[NoOfTests,NoOfCases,NoOfSuites]),
ct_logs:log("TEST INFO","~w test(s), ~w case(s) "
Expand Down Expand Up @@ -2678,7 +2679,7 @@ run_make(Targets, TestDir0, Mod, UserInclude, COpts) ->
node=node(),
data=TestDir}),
case Result of
{up_to_date,_} ->
{up_to_date,_Out} ->
ok;
{'EXIT',Reason} ->
io:format("{error,{make_crashed,~tp}\n", [Reason]),
Expand Down
6 changes: 5 additions & 1 deletion make/test_target_script.sh
Original file line number Diff line number Diff line change
Expand Up @@ -237,7 +237,11 @@ EOF
PATH="${RELEASE_ROOT}/bin/":${PATH}
fi

echo "The tests in test directory for $APPLICATION will be executed with ${CT_RUN}"
if [ "$SILENT" -ne 1 ]
then
echo "The tests in test directory for $APPLICATION will be executed with ${CT_RUN}"
fi

if [ -z "${ARGS}" ]
then
if [ ! -d "$MAKE_TEST_DIR" ]
Expand Down

0 comments on commit 9b7f21b

Please sign in to comment.