Skip to content

Commit

Permalink
ct: Print suite whose tests are being executed
Browse files Browse the repository at this point in the history
Co-authored-by: Jakub Witczak <kuba@erlang.org>
  • Loading branch information
jchristgit and u3s committed Aug 11, 2023
1 parent acdbb00 commit 624f2d7
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 7 deletions.
2 changes: 1 addition & 1 deletion lib/common_test/src/ct_logs.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2703,7 +2703,7 @@ make_all_suites_index1(When, AbsIndexName, AllTestLogDirs) ->
TempData}}),
TempData;
_ ->
io:put_chars("HTML logs at file://" ++ AbsIndexName ++ "."),
io:put_chars("HTML logs at file://" ++ AbsIndexName ++ ".\n"),
TempData
end;
Err ->
Expand Down
4 changes: 2 additions & 2 deletions lib/common_test/src/ct_run.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2238,13 +2238,13 @@ do_run_test(Tests, Skip, Opts0) ->
SuitesPrintout = ct_console:pluralize(NoOfSuites, "suite", "suites"),
if NoOfCases == unknown ->
FormatArgs = [NoOfTests, TestsPrintout, NoOfSuites, SuitesPrintout],
io:format("collected: ~w ~s, ~w ~s~n~n", FormatArgs),
io:format("collected: ~w ~s, ~w ~s~n", FormatArgs),
ct_logs:log("TEST INFO","~w ~s, ~w ~s", FormatArgs);
true ->
CasesPrintout = ct_console:pluralize(NoOfCases, "case", "cases"),
FormatArgs = [NoOfTests, TestsPrintout, NoOfCases,
CasesPrintout, NoOfSuites, SuitesPrintout],
io:format("collected: ~w ~s, ~w ~s in ~w ~s~n~n", FormatArgs),
io:format("collected: ~w ~s, ~w ~s in ~w ~s~n", FormatArgs),
ct_logs:log("TEST INFO","~w ~s, ~w ~s in ~w ~s", FormatArgs)
end,
%% if the verbosity level is set lower than ?STD_IMPORTANCE, tell
Expand Down
13 changes: 9 additions & 4 deletions lib/common_test/src/test_server_ctrl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2319,14 +2319,14 @@ run_test_cases(TestSpec, Config, TimetrapData) ->
%%

run_test_cases_loop([{SkipTag,CaseData={Type,_Ref,_Case,_Comment}}|Cases],
Config, TimetrapData, Mode, TestResults, Status) when
Config, TimetrapData, Mode, Status, TestResults) when
((SkipTag==auto_skip_case) or (SkipTag==skip_case)) and
((Type==conf) or (Type==make)) ->
run_test_cases_loop([{SkipTag,CaseData,Mode}|Cases],
Config, TimetrapData, Mode, TestResults, Status);
Config, TimetrapData, Mode, Status, TestResults);

run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases],
Config, TimetrapData, Mode, TestResults, Status) when
Config, TimetrapData, Mode, Status, TestResults) when
((SkipTag==auto_skip_case) or (SkipTag==skip_case)) and
((Type==conf) or (Type==make)) ->
ok = file:set_cwd(filename:dirname(get(test_server_dir))),
Expand Down Expand Up @@ -2484,6 +2484,11 @@ run_test_cases_loop([{skip_case,{Case,Comment},SkipMode}|Cases],
%% a start *or* end conf case, wrapping test cases or other conf cases
run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0,
Config, TimetrapData, Mode0, Status, TestResults) ->
if Func == init_per_suite ->
io:fwrite(user, "~n~s ", [Mod]);
true ->
ok
end,
CurrIOHandler = get(test_server_common_io_handler),
%% check and update the mode for test case execution and io msg handling
{StartConf,Mode,IOHandler,ConfTime,Status1} =
Expand Down Expand Up @@ -4054,7 +4059,7 @@ progress(skip, _CaseNum, Mod, Func, GrName, Loc, Reason, Time,
FormatLoc = test_server_sup:format_loc(Loc),
print(minor, "=== Location: ~ts", [FormatLoc]),
print(minor, "=== Reason: ~ts", [ReasonStr1]),
{Ret, #{reason => element(2, Reason1)}};
{Ret, #{}};

progress(failed, _CaseNum, Mod, Func, GrName, Loc, timetrap_timeout, T,
Comment0, {St0,St1}) ->
Expand Down

0 comments on commit 624f2d7

Please sign in to comment.