Skip to content

Commit 9b7f21b

Browse files
committed
Quiet down ct_run startup logs
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.
1 parent a13c7f0 commit 9b7f21b

File tree

5 files changed

+86
-40
lines changed

5 files changed

+86
-40
lines changed

lib/common_test/src/Makefile

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ MODULES= \
4747
ct \
4848
ct_logs \
4949
ct_framework \
50+
ct_console \
5051
ct_ftp \
5152
ct_ssh \
5253
ct_snmp \

lib/common_test/src/ct_console.erl

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,31 @@
1+
% Deals with output formatting for the terminal.
2+
3+
-module(ct_console).
4+
-export([print_header/1]).
5+
6+
7+
print_header(Message) ->
8+
{ok, Columns} = terminal_width(user),
9+
MessageLength = length(Message),
10+
PaddingSize = trunc(Columns / 2) - trunc(MessageLength / 2) - 1,
11+
% shell_docs contains a lot of useful functions that we could maybe factor
12+
% out and use here.
13+
Start = "\033[;1m",
14+
Stop = "\033[0m",
15+
case PaddingSize of
16+
Amount when Amount < 0 ->
17+
% Not enough space to print the padding, proceed normally.
18+
io:format("~s~s~s~n", [Start, Message, Stop]);
19+
_Amount ->
20+
Padding = lists:duplicate(PaddingSize, "="),
21+
io:format("~s~s ~s ~s~s~n", [Start, Padding, Message, Padding, Stop])
22+
end.
23+
24+
-spec terminal_width(atom()) -> {ok, pos_integer()}.
25+
terminal_width(Driver) ->
26+
case io:columns(Driver) of
27+
{ok, _Columns} = Result ->
28+
Result;
29+
{error, enotsup} ->
30+
{ok, 80}
31+
end.

lib/common_test/src/ct_make.erl

Lines changed: 36 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,20 @@
3838
all() ->
3939
all([]).
4040

41+
%% Run compilation via `Emakefile' in the current directory.
42+
%% Returns one of the following:
43+
%%
44+
%% - `Result' when the `noexec' option was passed as `true',
45+
%% - `{up_to_date, Result}' when all modules are up-to-date, or
46+
%% - `{error, Result}' when compilation failed for any module
47+
%%
48+
%% where `Result' contains tuples in the form:
49+
%%
50+
%% - `{File, out_of_date}' if the file needs recompilation but the `noexec'
51+
%% option was passed,
52+
%% - `{File, up_to_date}' if the file does not need any recompilation,
53+
%% - `{File, {error, Warnings, Errors}}}' on compilation failure, or
54+
%% - `{File, {ok, Warnings}}' on success.
4155
all(Options) ->
4256
{MakeOpts,CompileOpts} = sort_options(Options,[],[]),
4357
case read_emakefile('Emakefile',CompileOpts) of
@@ -200,12 +214,8 @@ load_opt(Opts) ->
200214
process([{[],_Opts}|Rest], NoExec, Load, Result) ->
201215
process(Rest, NoExec, Load, Result);
202216
process([{[H|T],Opts}|Rest], NoExec, Load, Result) ->
203-
case recompilep(coerce_2_list(H), NoExec, Load, Opts) of
204-
error ->
205-
process([{T,Opts}|Rest], NoExec, Load, [{H,error}|Result]);
206-
Info ->
207-
process([{T,Opts}|Rest], NoExec, Load, [{H,Info}|Result])
208-
end;
217+
CompileResult = recompilep(coerce_2_list(H), NoExec, Load, Opts),
218+
process([{T, Opts} | Rest], NoExec, Load, [{H, CompileResult} | Result]);
209219
process([], NoExec, _Load, Result) ->
210220
if not NoExec ->
211221
case lists:keysearch(error, 2, Result) of
@@ -272,25 +282,25 @@ include_opt([]) ->
272282
%% Actually recompile and load the file, depending on the flags.
273283
%% Where load can be netload | load | noload
274284

275-
recompile(File, NoExec, Load, Opts) ->
276-
case do_recompile(File, NoExec, Load, Opts) of
277-
{ok,_} -> ok;
278-
Other -> Other
279-
end.
280-
281-
do_recompile(_File, true, _Load, _Opts) ->
285+
recompile(_File, true, _Load, _Opts) ->
282286
out_of_date;
283-
do_recompile(File, false, Load, Opts) ->
284-
io:format("Recompile: ~ts\n",[File]),
285-
case compile:file(File, [report_errors, report_warnings |Opts]) of
286-
Ok when is_tuple(Ok), element(1,Ok)==ok ->
287-
maybe_load(element(2,Ok), Load, Opts);
288-
_Error ->
289-
error
287+
recompile(File, false, Load, Opts) ->
288+
case compile:file(File, [return_errors, return_warnings | Opts]) of
289+
{ok, Module, Warnings} ->
290+
{Loaded, ShouldLoad, Why} = maybe_load(Module, Load, Opts),
291+
case {Loaded, ShouldLoad, Why} of
292+
%% TODO: This needs checking whether the Reason is in a format we expect
293+
{false, true, Reason} when Reason =/= none ->
294+
{ok, [Reason | Warnings]};
295+
_ ->
296+
{ok, Warnings}
297+
end;
298+
{error, _Errors, _Warnings} = Result ->
299+
Result
290300
end.
291301

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

306315
do_load(Dir, Mod, load) ->
307316
code:purge(Mod),
308317
case code:load_abs(filename:join(Dir, Mod),Mod) of
309318
{module,Mod} ->
310-
{ok,Mod};
319+
{true, true, none};
311320
Other ->
312-
Other
321+
{false, true, Other}
313322
end;
314323
do_load(Dir, Mod, netload) ->
315324
Obj = atom_to_list(Mod) ++ code:objfile_extension(),
316325
Fname = filename:join(Dir, Obj),
317326
case file:read_file(Fname) of
318327
{ok,Bin} ->
319328
rpc:eval_everywhere(code,load_binary,[Mod,Fname,Bin]),
320-
{ok,Mod};
329+
{true, true};
321330
Other ->
322-
Other
331+
{false, true, Other}
323332
end.
324333

325334
exists(File) ->

lib/common_test/src/ct_run.erl

Lines changed: 13 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -130,8 +130,9 @@ script_start(Args) ->
130130
_ -> ""
131131
end
132132
end,
133-
io:format("~nCommon Test~s starting (cwd is ~ts)~n~n",
134-
[CTVsn,Cwd]),
133+
Header = io_lib:format("common test~s starting", [CTVsn]),
134+
ct_console:print_header(Header),
135+
io:format("cwd: ~ts~n", [Cwd]),
135136
Self = self(),
136137
Pid = spawn_link(fun() -> script_start1(Self, Args) end),
137138
receive
@@ -693,7 +694,6 @@ script_start3(Opts, Args) ->
693694
true ->
694695
%% no start options, use default "-dir ./"
695696
{ok,Dir} = file:get_cwd(),
696-
io:format("ct_run -dir ~ts~n~n", [Dir]),
697697
script_start4(Opts#opts{tests = tests([Dir])}, Args)
698698
end
699699
end.
@@ -870,7 +870,8 @@ run_test1(StartOpts) when is_list(StartOpts) ->
870870
undefined ->
871871
Tracing = start_trace(StartOpts),
872872
{ok,Cwd} = file:get_cwd(),
873-
io:format("~nCommon Test starting (cwd is ~ts)~n~n", [Cwd]),
873+
ct_console:print_header("common test starting"),
874+
io:format("cwd: ~ts~n", [Cwd]),
874875
Res =
875876
case ct_repeat:loop_test(func, StartOpts) of
876877
false ->
@@ -1352,7 +1353,8 @@ run_testspec1_fun(TestSpec) ->
13521353

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

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

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

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

18331837
%% attempt to compile the modules specified in TestSuites
18341838
auto_compile(TestSuites) ->
1835-
io:format("~nCommon Test: Running make in test directories...~n"),
18361839
UserInclude =
18371840
case application:get_env(common_test, include) of
18381841
{ok,UserInclDirs} when length(UserInclDirs) > 0 ->
@@ -2186,15 +2189,13 @@ do_run_test(Tests, Skip, Opts0) ->
21862189
NoOfTests = length(Tests),
21872190
NoOfSuites = length(Suites1),
21882191
ct_util:warn_duplicates(Suites1),
2189-
{ok,Cwd} = file:get_cwd(),
2190-
io:format("~nCWD set to: ~tp~n", [Cwd]),
21912192
if NoOfCases == unknown ->
2192-
io:format("~nTEST INFO: ~w test(s), ~w suite(s)~n~n",
2193+
io:format("collected: ~w test(s), ~w suite(s)~n~n",
21932194
[NoOfTests,NoOfSuites]),
21942195
ct_logs:log("TEST INFO","~w test(s), ~w suite(s)",
21952196
[NoOfTests,NoOfSuites]);
21962197
true ->
2197-
io:format("~nTEST INFO: ~w test(s), ~w case(s) "
2198+
io:format("collected: ~w test(s), ~w case(s) "
21982199
"in ~w suite(s)~n~n",
21992200
[NoOfTests,NoOfCases,NoOfSuites]),
22002201
ct_logs:log("TEST INFO","~w test(s), ~w case(s) "
@@ -2678,7 +2679,7 @@ run_make(Targets, TestDir0, Mod, UserInclude, COpts) ->
26782679
node=node(),
26792680
data=TestDir}),
26802681
case Result of
2681-
{up_to_date,_} ->
2682+
{up_to_date,_Out} ->
26822683
ok;
26832684
{'EXIT',Reason} ->
26842685
io:format("{error,{make_crashed,~tp}\n", [Reason]),

make/test_target_script.sh

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -237,7 +237,11 @@ EOF
237237
PATH="${RELEASE_ROOT}/bin/":${PATH}
238238
fi
239239

240-
echo "The tests in test directory for $APPLICATION will be executed with ${CT_RUN}"
240+
if [ "$SILENT" -ne 1 ]
241+
then
242+
echo "The tests in test directory for $APPLICATION will be executed with ${CT_RUN}"
243+
fi
244+
241245
if [ -z "${ARGS}" ]
242246
then
243247
if [ ! -d "$MAKE_TEST_DIR" ]

0 commit comments

Comments
 (0)