From cb5c2808941bcc1c9a10955dceac3a96a2bce76d Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Wed, 7 Jun 2023 23:20:35 +0200 Subject: [PATCH 01/22] Allow running tests more silently When running tests at present via `make test`, the developer is met with lots of messages from both the testing script and logger messages emitted through libraries called by the testcases themselves. This clutters the output and makes it hard to distinguish actual test suite failures from regular progress and other logging messages. This commit introduces support for interpreting the `-s` / `--silent` / `--quiet` option from `make` and utilizing it to run tests in a more quiet manner. Specifically, this means that log output is fully captured by `cth_log_redirect` (instead of logging to both stdout and the CT log), and the banners and disclaimers from the testing script are reduced to a minimum (under the assumption that the person running the tests is familar with them). To accomplish this, the `cth_log_redirect` handler is augmented with the `mode` option, which instructs it how to work. The previous behaviour - logging to both stdout and the Common Test logs - is kept by default for now. As a small improvement that came up whilst implementing this change, `logger_std_h` is updated to skip logging filesync errors when instructeed to log to `/dev/null`. In `inets`, this reduces the output emitted by the tests from 2175 to 803 lines. --- HOWTO/DEVELOPMENT.md | 8 ++++++ Makefile.in | 6 ++++- lib/common_test/doc/src/ct_hooks_chapter.xml | 16 +++++++++++ lib/common_test/src/ct_run.erl | 6 +++++ lib/common_test/src/cth_log_redirect.erl | 28 +++++++++++++------- lib/kernel/src/logger_std_h.erl | 4 +++ make/app_targets.mk | 7 ++++- make/test_target_script.sh | 24 ++++++++++++----- 8 files changed, 81 insertions(+), 18 deletions(-) diff --git a/HOWTO/DEVELOPMENT.md b/HOWTO/DEVELOPMENT.md index b9be3026e17a..670db3918a45 100644 --- a/HOWTO/DEVELOPMENT.md +++ b/HOWTO/DEVELOPMENT.md @@ -213,6 +213,14 @@ for all process you would do this: ERL_ARGS="+hmqd off_heap" make emulator_test ``` +If you want logger messages to only be printed into the Common Test HTML logs +and keep test script information about starting and stopping the run to a +minimum, you can pass `-s` or `--silent`: + +```bash +make test -s +``` + ### Build and test a specific application You can also build the application from within itself. Like this: diff --git a/Makefile.in b/Makefile.in index 72ae67524aae..9e656dcb5296 100644 --- a/Makefile.in +++ b/Makefile.in @@ -1007,8 +1007,12 @@ bootstrap_clean: .PHONY: test dialyzer +ifeq ($(findstring s,${MAKEFLAGS}),s) + TEST_EXTRA_ARGS = --quiet +endif + test: all release release_tests - $(ERL_TOP)/make/test_target_script.sh $(ERL_TOP) + $(ERL_TOP)/make/test_target_script.sh $(TEST_EXTRA_ARGS) $(ERL_TOP) ifeq ($(TYPE),) dialyzer: all diff --git a/lib/common_test/doc/src/ct_hooks_chapter.xml b/lib/common_test/doc/src/ct_hooks_chapter.xml index ca8c0d2e0ef2..2ea87b493b96 100644 --- a/lib/common_test/doc/src/ct_hooks_chapter.xml +++ b/lib/common_test/doc/src/ct_hooks_chapter.xml @@ -511,6 +511,22 @@ results(State) -> use another level either change the default handler level before starting common_test, or use the logger:set_handler_config/3 API.

+

This hook supports the following options:

+ + {mode, replace} + +

Replace the default logging handler by the log redirect + instead of logging to both the default handler and the + cth_log_redirect handler. To use this mode, disable the builtin + hook and reconfigure it:

+

-enable_builtin_hooks false -ct_hooks cth_log_redirect [{mode,replace}]

+
+ {mode, add} + +

Add the logging handler instead of replacing the default logging + handler. This is the default behaviour.

+
+
cth_surefire diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index e16dc79c2780..107b3ddacd97 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -2825,6 +2825,12 @@ merge_arguments([CoverStop={cover_stop,_}|Args], Merged) -> merge_arguments([{'case',TC}|Args], Merged) -> merge_arguments(Args, handle_arg(merge, {testcase,TC}, Merged)); +merge_arguments([{ct_hooks,_}=Entry|Args], Merged) -> + % "stack" does not actually have any special handling - it + % just falls back into the default behaviour and allows each + % distinct `-ct_hooks` option to be stored separately. + merge_arguments(Args, handle_arg(stack, Entry, Merged)); + merge_arguments([Arg|Args], Merged) -> merge_arguments(Args, handle_arg(merge, Arg, Merged)); diff --git a/lib/common_test/src/cth_log_redirect.erl b/lib/common_test/src/cth_log_redirect.erl index 04e964f51a80..9553ff109446 100644 --- a/lib/common_test/src/cth_log_redirect.erl +++ b/lib/common_test/src/cth_log_redirect.erl @@ -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, @@ -55,10 +56,10 @@ id(_Opts) -> ?MODULE. -init(?MODULE, _Opts) -> +init(?MODULE, Opts) -> ct_util:mark_process(), - ok = start_log_handler(), - tc_log_async. + ok = start_log_handler(Opts), + {ok, tc_log_async}. pre_init_per_suite(Suite, Config, State) -> set_curr_func({Suite,init_per_suite}, Config), @@ -114,7 +115,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 = @@ -136,9 +137,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}}. @@ -169,10 +176,11 @@ log(#{msg:={report,Msg},meta:=#{domain:=[otp,sasl]}}=Log,Config) -> do_log(add_log_category(Log,sasl),Config) end end; +%% Prevent recursively logging messages we have seen +log(#{meta:=Meta}=_Log, _Config) when is_map_key(?MODULE, Meta) -> + ok; log(#{meta:=#{domain:=[otp]}}=Log,Config) -> do_log(add_log_category(Log,error_logger),Config); -log(#{meta:=#{domain:=_}},_) -> - ok; log(Log,Config) -> do_log(add_log_category(Log,error_logger),Config). diff --git a/lib/kernel/src/logger_std_h.erl b/lib/kernel/src/logger_std_h.erl index 1b2fabad72f3..602093bf223c 100644 --- a/lib/kernel/src/logger_std_h.erl +++ b/lib/kernel/src/logger_std_h.erl @@ -673,6 +673,10 @@ maybe_notify_error(Op, Result, #{write_res:=WR,sync_res:=SR}) (Op==filesync andalso Result==SR) -> %% don't report same error twice ok; +maybe_notify_error(filesync, {error, einval}, #{file_name:="/dev/null"}) -> + %% If logging to /dev/null, output should be discarded + %% Ignore any EINVAL errors for filesync operations + ok; maybe_notify_error(Op, Error, #{handler_name:=HandlerName,file_name:=FileName}) -> logger_h_common:error_notify({HandlerName,Op,FileName,Error}), ok. diff --git a/make/app_targets.mk b/make/app_targets.mk index cf7485e3f2e4..8cf5e4ac079b 100644 --- a/make/app_targets.mk +++ b/make/app_targets.mk @@ -23,8 +23,13 @@ APPLICATION ?= $(basename $(notdir $(PWD))) .PHONY: test info gclean dialyzer dialyzer_plt dclean ifndef NO_TEST_TARGET + +ifeq ($(findstring s,${MAKEFLAGS}),s) +TEST_ENV = SILENT=1 +endif + test: - TEST_NEEDS_RELEASE=$(TEST_NEEDS_RELEASE) TYPE=$(TYPE) \ + TEST_NEEDS_RELEASE=$(TEST_NEEDS_RELEASE) TYPE=$(TYPE) $(TEST_ENV) \ $(ERL_TOP)/make/test_target_script.sh $(ERL_TOP) endif diff --git a/make/test_target_script.sh b/make/test_target_script.sh index aae2c78b6c50..8945a2f2448f 100755 --- a/make/test_target_script.sh +++ b/make/test_target_script.sh @@ -27,15 +27,27 @@ LIGHT_CYAN='\033[1;36m' BOLD='\033[1m' NC='\033[0m' +SILENT="${SILENT:-0}" +if [ "$SILENT" -eq 1 ] && [ "${WSLcross}" != "true" ]; then + # cth_log_redirect is enabled by default, to configure it we need to remove and re-add it + ARGS="-enable_builtin_hooks false -ct_hooks cth_log_redirect [{mode,replace}] ${ARGS}" +fi + print_highlighted_msg_with_printer () { COLOR=$1 MSG_PRINTER=$2 - printf "\n${COLOR}======================================================================${NC}\n" - echo - $MSG_PRINTER - echo - printf "${COLOR}======================================================================${NC}\n" + IMPORTANT=${3:-0} + if [ "$SILENT" -ne 1 ]; then + printf "\n${COLOR}======================================================================${NC}\n" + echo + fi + if [ "$SILENT" -ne 1 ] || [ "$IMPORTANT" -eq 1 ]; then + $MSG_PRINTER + fi + if [ "$SILENT" -ne 1 ]; then + printf "${COLOR}======================================================================${NC}\n" + fi } print_highlighted_msg () { @@ -44,7 +56,7 @@ print_highlighted_msg () { print_msg () { echo "$MSG" } - print_highlighted_msg_with_printer $COLOR print_msg + print_highlighted_msg_with_printer $COLOR print_msg 1 } print_all_tests_takes_long_time_warning () { From d409f017789fec54aa8e8558b7eb69a1077bf190 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Wed, 12 Jul 2023 20:25:54 +0200 Subject: [PATCH 02/22] 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. --- lib/common_test/src/Makefile | 1 + lib/common_test/src/ct_console.erl | 39 +++++++++++++++ lib/common_test/src/ct_make.erl | 63 ++++++++++++++---------- lib/common_test/src/ct_run.erl | 25 +++++----- lib/common_test/src/cth_log_redirect.erl | 2 +- make/test_target_script.sh | 6 ++- 6 files changed, 95 insertions(+), 41 deletions(-) create mode 100644 lib/common_test/src/ct_console.erl diff --git a/lib/common_test/src/Makefile b/lib/common_test/src/Makefile index 00f13589f3c5..060b473af3a1 100644 --- a/lib/common_test/src/Makefile +++ b/lib/common_test/src/Makefile @@ -47,6 +47,7 @@ MODULES= \ ct \ ct_logs \ ct_framework \ + ct_console \ ct_ftp \ ct_ssh \ ct_snmp \ diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl new file mode 100644 index 000000000000..bd8d83711dff --- /dev/null +++ b/lib/common_test/src/ct_console.erl @@ -0,0 +1,39 @@ +% 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), + PaddingSizeLeft = trunc(Columns / 2) - trunc(MessageLength / 2) - 1, + PaddingSizeRight = header_right_padding(Columns, PaddingSizeLeft), + % shell_docs contains a lot of useful functions that we could maybe factor + % out and use here. + Start = "\033[;1m", + Stop = "\033[0m", + case PaddingSizeLeft of + Amount when Amount < 0 -> + % Not enough space to print the padding, proceed normally. + io:format("~s~s~s~n", [Start, Message, Stop]); + _Amount -> + PaddingLeft = lists:duplicate(PaddingSizeLeft, "="), + PaddingRight = lists:duplicate(PaddingSizeRight, "="), + io:format("~s~s ~s ~s~s~n", [Start, PaddingLeft, Message, PaddingRight, 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. + +-spec header_right_padding(pos_integer(), pos_integer()) -> pos_integer(). +header_right_padding(Columns, LeftPadding) when Columns rem 2 == 0 -> + LeftPadding; +header_right_padding(_Columns, LeftPadding) -> + LeftPadding + 1. diff --git a/lib/common_test/src/ct_make.erl b/lib/common_test/src/ct_make.erl index 220cb0473da9..dcef11e2c827 100644 --- a/lib/common_test/src/ct_make.erl +++ b/lib/common_test/src/ct_make.erl @@ -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 @@ -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 @@ -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. @@ -299,17 +309,16 @@ 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(), @@ -317,9 +326,9 @@ do_load(Dir, Mod, netload) -> 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) -> diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index 107b3ddacd97..9e69be135fc0 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -131,8 +131,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 @@ -706,7 +707,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. @@ -884,7 +884,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 -> @@ -1374,7 +1375,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), @@ -1753,7 +1755,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} = @@ -1766,6 +1769,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), @@ -1856,7 +1860,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 -> @@ -2210,15 +2213,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) " @@ -2702,7 +2703,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]), diff --git a/lib/common_test/src/cth_log_redirect.erl b/lib/common_test/src/cth_log_redirect.erl index 9553ff109446..29ba6ba25d50 100644 --- a/lib/common_test/src/cth_log_redirect.erl +++ b/lib/common_test/src/cth_log_redirect.erl @@ -138,7 +138,7 @@ start_log_handler(Options) -> {{?DEFAULT_FORMATTER,?DEFAULT_FORMAT_CONFIG},info} end, HandlerConfig = #{level => DefaultLevel, formatter => DefaultFormatter}, - HandlerName = case proplists:get_value(mode, Options, add) of + HandlerName = case proplists:get_value(mode, Options, replace) of add -> ?MODULE; replace -> diff --git a/make/test_target_script.sh b/make/test_target_script.sh index 8945a2f2448f..6e155f30a4b5 100755 --- a/make/test_target_script.sh +++ b/make/test_target_script.sh @@ -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" ] From d5964a078b79b22d398a894e45520fa3a79a23f5 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Thu, 20 Jul 2023 22:44:18 +0200 Subject: [PATCH 03/22] ct: Capture logger output by default in ct_run The new `-verbose` flag can be used to revert to the previous behavior. `ct:print` and `ct:pal` output is unaffected for now. --- lib/common_test/doc/src/ct_run_cmd.xml | 2 ++ lib/common_test/doc/src/run_test_chapter.xml | 5 ++++ lib/common_test/src/ct_run.erl | 24 ++++++++++++++++++-- lib/common_test/src/ct_util.hrl | 1 + lib/common_test/src/cth_log_redirect.erl | 2 +- 5 files changed, 31 insertions(+), 3 deletions(-) diff --git a/lib/common_test/doc/src/ct_run_cmd.xml b/lib/common_test/doc/src/ct_run_cmd.xml index 94c955a6ffa9..89fe8addba2f 100644 --- a/lib/common_test/doc/src/ct_run_cmd.xml +++ b/lib/common_test/doc/src/ct_run_cmd.xml @@ -107,6 +107,7 @@ [-logopts LogOpts] [-verbosity GenVLevel | [Category1 VLevel1 and Category2 VLevel2 and .. CategoryN VLevelN]] + [-verbose] [-silent_connections [ConnType1 ConnType2 .. ConnTypeN]] [-stylesheet CSSFile] [-cover CoverCfgFile] @@ -147,6 +148,7 @@ [-logopts LogOpts] [-verbosity GenVLevel | [Category1 VLevel1 and Category2 VLevel2 and .. CategoryN VLevelN]] + [-verbose] [-allow_user_terms] [-silent_connections [ConnType1 ConnType2 .. ConnTypeN]] [-stylesheet CSSFile] diff --git a/lib/common_test/doc/src/run_test_chapter.xml b/lib/common_test/doc/src/run_test_chapter.xml index 45a07ecc69d1..c0fd43993c0d 100644 --- a/lib/common_test/doc/src/run_test_chapter.xml +++ b/lib/common_test/doc/src/run_test_chapter.xml @@ -269,6 +269,11 @@

Sets verbosity levels for printouts.

+ +

Enables output of supervisor reports and other logging messages + directly to the terminal as the test is running. If not supplied, these + messages will be captured and only show up in the HTML report.

+

Disables automatic escaping of special HTML characters. See the Logging chapter.

diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index 9e69be135fc0..3d630563e5cf 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -56,6 +56,7 @@ basic_html, esc_chars = true, verbosity = [], + verbose = false, config = [], event_handlers = [], ct_hooks = [], @@ -238,6 +239,7 @@ script_start1(Parent, Args) -> fun(Os) -> [list_to_atom(O) || O <- Os] end, [], Args), Verbosity = verbosity_args2opts(Args), + Verbose = get_start_opt(verbose, fun ([]) -> true end, false, Args), MultTT = get_start_opt(multiply_timetraps, fun([MT]) -> list_to_number(MT) end, Args), ScaleTT = get_start_opt(scale_timetraps, @@ -249,15 +251,26 @@ script_start1(Parent, Args) -> ([]) -> auto_per_tc end, Args), EvHandlers = event_handler_args2opts(Args), - CTHooks = ct_hooks_args2opts(Args), + CTHooksRaw = ct_hooks_args2opts(Args), + CTHooks = case Verbose of + % "false" by default: replace the default logging handler and capture output + % otherwise, the handler will be configured with the default option telling + % it to add itself to the handlers list (backwards-compatible behaviour) + false -> [{cth_log_redirect, [{mode, replace}], ctfirst} | CTHooksRaw]; + _Other -> CTHooksRaw + end, CTHooksOrder = get_start_opt(ct_hooks_order, fun([CTHO]) -> list_to_atom(CTHO); ([]) -> undefined end, undefined, Args), - EnableBuiltinHooks = get_start_opt(enable_builtin_hooks, + EnableBuiltinHooksRaw = get_start_opt(enable_builtin_hooks, fun([CT]) -> list_to_atom(CT); ([]) -> undefined end, undefined, Args), + EnableBuiltinHooks = case {EnableBuiltinHooksRaw, Verbose} of + {undefined, false} -> false; + {Setting, _Verbose} -> Setting + end, %% check flags and set corresponding application env variables @@ -356,6 +369,7 @@ script_start1(Parent, Args) -> basic_html = BasicHtml, esc_chars = EscChars, verbosity = Verbosity, + verbose = Verbose, event_handlers = EvHandlers, ct_hooks = CTHooks, ct_hooks_order = CTHooksOrder, @@ -518,6 +532,7 @@ combine_test_opts(TS, Specs, Opts) -> AllVerbosity = merge_keyvals([Opts#opts.verbosity, TSOpts#opts.verbosity]), + Verbose = choose_val(Opts#opts.verbose, TSOpts#opts.verbose), AllSilentConns = merge_vals([Opts#opts.silent_connections, TSOpts#opts.silent_connections]), @@ -610,6 +625,7 @@ combine_test_opts(TS, Specs, Opts) -> basic_html = BasicHtml, esc_chars = EscChars, verbosity = AllVerbosity, + verbose = Verbose, silent_connections = AllSilentConns, config = TSOpts#opts.config, event_handlers = AllEvHs, @@ -760,6 +776,7 @@ script_usage() -> "\n\t [-logdir LogDir]" "\n\t [-logopts LogOpt1 LogOpt2 .. LogOptN]" "\n\t [-verbosity GenVLvl | [CategoryVLvl1 .. CategoryVLvlN]]" + "\n\t [-verbose]" "\n\t [-silent_connections [ConnType1 ConnType2 .. ConnTypeN]]" "\n\t [-stylesheet CSSFile]" "\n\t [-cover CoverCfgFile]" @@ -787,6 +804,7 @@ script_usage() -> "\n\t [-logdir LogDir]" "\n\t [-logopts LogOpt1 LogOpt2 .. LogOptN]" "\n\t [-verbosity GenVLvl | [CategoryVLvl1 .. CategoryVLvlN]]" + "\n\t [-verbose]" "\n\t [-allow_user_terms]" "\n\t [-join_specs]" "\n\t [-silent_connections [ConnType1 ConnType2 .. ConnTypeN]]" @@ -1434,6 +1452,7 @@ get_data_for_node(#testspec{label = Labels, esc_chars = EscChs, stylesheet = SSs, verbosity = VLvls, + verbose = Verbose, silent_connections = SilentConnsList, cover = CoverFs, cover_stop = CoverStops, @@ -1490,6 +1509,7 @@ get_data_for_node(#testspec{label = Labels, esc_chars = EscChars, stylesheet = Stylesheet, verbosity = Verbosity, + verbose = Verbose, silent_connections = SilentConns, cover = Cover, cover_stop = CoverStop, diff --git a/lib/common_test/src/ct_util.hrl b/lib/common_test/src/ct_util.hrl index e0145b05888c..678342db9708 100644 --- a/lib/common_test/src/ct_util.hrl +++ b/lib/common_test/src/ct_util.hrl @@ -39,6 +39,7 @@ logopts=[], basic_html=[], esc_chars=[], + verbose=false, verbosity=[], silent_connections=[], cover=[], diff --git a/lib/common_test/src/cth_log_redirect.erl b/lib/common_test/src/cth_log_redirect.erl index 29ba6ba25d50..9553ff109446 100644 --- a/lib/common_test/src/cth_log_redirect.erl +++ b/lib/common_test/src/cth_log_redirect.erl @@ -138,7 +138,7 @@ start_log_handler(Options) -> {{?DEFAULT_FORMATTER,?DEFAULT_FORMAT_CONFIG},info} end, HandlerConfig = #{level => DefaultLevel, formatter => DefaultFormatter}, - HandlerName = case proplists:get_value(mode, Options, replace) of + HandlerName = case proplists:get_value(mode, Options, add) of add -> ?MODULE; replace -> From 23beae9610d2145e093c1985eca6b8a6eadc9787 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Tue, 25 Jul 2023 12:36:57 +0200 Subject: [PATCH 04/22] ct: Print test progress via single characters --- lib/common_test/src/ct_console.erl | 29 ++++++--- lib/common_test/src/ct_run.erl | 23 +++---- lib/common_test/src/test_server_ctrl.erl | 78 ++++++++++++------------ make/test_target_script.sh | 4 -- 4 files changed, 72 insertions(+), 62 deletions(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index bd8d83711dff..f5d5b555806b 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -1,14 +1,19 @@ % Deals with output formatting for the terminal. -module(ct_console). --export([print_header/1]). +-export([print_header/1, pluralize/3]). +-spec print_header(string()) -> ok. print_header(Message) -> + io:fwrite(user, "~s", [format_header(Message)]). + +-spec format_header(string()) -> string(). +format_header(Message) -> {ok, Columns} = terminal_width(user), - MessageLength = length(Message), + MessageLength = iolist_size(Message), PaddingSizeLeft = trunc(Columns / 2) - trunc(MessageLength / 2) - 1, - PaddingSizeRight = header_right_padding(Columns, PaddingSizeLeft), + PaddingSizeRight = header_right_padding(Columns, PaddingSizeLeft, MessageLength), % shell_docs contains a lot of useful functions that we could maybe factor % out and use here. Start = "\033[;1m", @@ -16,13 +21,19 @@ print_header(Message) -> case PaddingSizeLeft of Amount when Amount < 0 -> % Not enough space to print the padding, proceed normally. - io:format("~s~s~s~n", [Start, Message, Stop]); + io_lib:format("~s~s~s~n", [Start, Message, Stop]); _Amount -> PaddingLeft = lists:duplicate(PaddingSizeLeft, "="), PaddingRight = lists:duplicate(PaddingSizeRight, "="), - io:format("~s~s ~s ~s~s~n", [Start, PaddingLeft, Message, PaddingRight, Stop]) + io_lib:format("~s~s ~s ~s~s~n", [Start, PaddingLeft, Message, PaddingRight, Stop]) end. + +-spec pluralize(non_neg_integer(), string(), string()) -> string(). +pluralize(1, Singular, _Plural) -> Singular; +pluralize(_, _Singular, Plural) -> Plural. + + -spec terminal_width(atom()) -> {ok, pos_integer()}. terminal_width(Driver) -> case io:columns(Driver) of @@ -32,8 +43,10 @@ terminal_width(Driver) -> {ok, 80} end. --spec header_right_padding(pos_integer(), pos_integer()) -> pos_integer(). -header_right_padding(Columns, LeftPadding) when Columns rem 2 == 0 -> +-spec header_right_padding(pos_integer(), pos_integer(), pos_integer()) -> pos_integer(). +header_right_padding(_Columns, LeftPadding, MessageLength) when MessageLength rem 2 == 1 -> + LeftPadding - 1; +header_right_padding(Columns, LeftPadding, _MessageLength) when Columns rem 2 == 0 -> LeftPadding; -header_right_padding(_Columns, LeftPadding) -> +header_right_padding(_Columns, LeftPadding, _MessageLength) -> LeftPadding + 1. diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index 3d630563e5cf..3aa8c31a0365 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -1789,7 +1789,8 @@ 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)]), + ModulesPrintout = ct_console:pluralize(length(TestSuites2), "module", "modules"), + io:format("~p test ~s compiled~n", [length(TestSuites2), ModulesPrintout]), SavedErrors = save_make_errors(SuiteMakeErrors), ct_repeat:log_loop_info(Args), @@ -2233,18 +2234,18 @@ do_run_test(Tests, Skip, Opts0) -> NoOfTests = length(Tests), NoOfSuites = length(Suites1), ct_util:warn_duplicates(Suites1), + TestsPrintout = ct_console:pluralize(NoOfTests, "test", "tests"), + SuitesPrintout = ct_console:pluralize(NoOfSuites, "suite", "suites"), if NoOfCases == unknown -> - 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]); + FormatArgs = [NoOfTests, TestsPrintout, NoOfSuites, SuitesPrintout], + io:format("collected: ~w ~s, ~w ~s~n~n", FormatArgs), + ct_logs:log("TEST INFO","~w ~s, ~w ~s", FormatArgs); true -> - 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) " - "in ~w suite(s)", - [NoOfTests,NoOfCases,NoOfSuites]) + 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), + 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 %% test_server to ignore stdout printouts to the test case log file diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index 23a6deb6dfa0..8f21b5d77e54 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -1482,9 +1482,6 @@ do_test_cases(TopCases, SkipCases, add_init_and_end_per_suite(TestSpec0, undefined, undefined, FwMod), TI = get_target_info(), - print(1, "Starting test~ts", - [print_if_known(N, {", ~w test cases",[N]}, - {" (with repeated test cases)",[]})]), Test = get(test_server_name), TestName = if is_list(Test) -> lists:flatten(io_lib:format("~ts", [Test])); @@ -2158,17 +2155,24 @@ run_test_cases(TestSpec, Config, TimetrapData) -> html_convert_modules(TestSpec, Config, FwMod) end, - run_test_cases_loop(TestSpec, [Config], TimetrapData, [], []), - - {AllSkippedN,UserSkipN,AutoSkipN,SkipStr} = - case get(test_server_skipped) of - {0,0} -> {0,0,0,""}; - {US,AS} -> {US+AS,US,AS,io_lib:format(", ~w skipped", [US+AS])} - end, - OkN = get(test_server_ok), - FailedN = get(test_server_failed), - print(1, "TEST COMPLETE, ~w ok, ~w failed~ts of ~w test cases\n", - [OkN,FailedN,SkipStr,OkN+FailedN+AllSkippedN]), + #{total := #{ + passed := OkN, + failed := FailedN, + user_skipped := UserSkipN, + auto_skipped := AutoSkipN + } + } = run_test_cases_loop(TestSpec, [Config], TimetrapData, [], []), + AllSkippedN = UserSkipN + AutoSkipN, + SkipStr = case AllSkippedN of + 0 -> ""; + Skips -> io_lib:format(", ~w skipped", [Skips]) + end, + + % We need to run through the user GL here to prevent having our output captured. + io:fwrite(user, "~n", []), + Trailer = io_lib:format("test finished: ~w ok, ~w failed~ts of ~w test cases", + [OkN, FailedN, SkipStr, OkN + FailedN + AllSkippedN]), + ct_console:print_header(Trailer), test_server_sup:framework_call(report, [tests_done, {OkN,FailedN,{UserSkipN,AutoSkipN}}]), print(major, "=finished ~s", [lists:flatten(timestamp_get(""))]), @@ -3019,8 +3023,16 @@ run_test_cases_loop([{Mod,Func,Args}=Case|Cases], Config, TimetrapData, Mode0, S end; %% TestSpec processing finished -run_test_cases_loop([], _Config, _TimetrapData, _, _) -> - ok. +run_test_cases_loop([], _Config, _TimetrapData, _, _Status) -> + {UserSkipped, AutoSkipped} = get(test_server_skipped), + #{ + total => #{ + passed => get(test_server_ok), + failed => get(test_server_failed), + user_skipped => UserSkipped, + auto_skipped => AutoSkipped + } + }. %%-------------------------------------------------------------------- %% various help functions @@ -4004,15 +4016,14 @@ num2str(N) -> integer_to_list(N). %% Note: Strings that are to be written to the minor log must %% be prefixed with "=== " here, or the indentation will be wrong. -progress(skip, CaseNum, Mod, Func, GrName, Loc, Reason, Time, +progress(skip, _CaseNum, Mod, Func, GrName, Loc, Reason, Time, Comment, {St0,St1}) -> {Reason1,{Color,Ret,ReportTag}} = if_auto_skip(Reason, fun() -> {?auto_skip_color,auto_skip,auto_skipped} end, fun() -> {?user_skip_color,skip,skipped} end), print(major, "=result ~w: ~tp", [ReportTag,Reason1]), - print(1, "*** SKIPPED ~ts ***", - [get_info_str(Mod,Func, CaseNum, get(test_server_cases))]), + io:fwrite(user, "s", []), test_server_sup:framework_call(report, [tc_done,{Mod,{Func,GrName}, {ReportTag,Reason1}}]), TimeStr = io_lib:format(if is_float(Time) -> "~.3fs"; @@ -4042,11 +4053,10 @@ progress(skip, CaseNum, Mod, Func, GrName, Loc, Reason, Time, print(minor, "=== Reason: ~ts", [ReasonStr1]), Ret; -progress(failed, CaseNum, Mod, Func, GrName, Loc, timetrap_timeout, T, +progress(failed, _CaseNum, Mod, Func, GrName, Loc, timetrap_timeout, T, Comment0, {St0,St1}) -> print(major, "=result failed: timeout, ~tp", [Loc]), - print(1, "*** FAILED ~ts ***", - [get_info_str(Mod,Func, CaseNum, get(test_server_cases))]), + io:fwrite(user, "F", []), test_server_sup:framework_call(report, [tc_done,{Mod,{Func,GrName}, {failed,timetrap_timeout}}]), @@ -4068,11 +4078,10 @@ progress(failed, CaseNum, Mod, Func, GrName, Loc, timetrap_timeout, T, print(minor, "=== Reason: timetrap timeout", []), failed; -progress(failed, CaseNum, Mod, Func, GrName, Loc, {testcase_aborted,Reason}, _T, +progress(failed, _CaseNum, Mod, Func, GrName, Loc, {testcase_aborted,Reason}, _T, Comment0, {St0,St1}) -> print(major, "=result failed: testcase_aborted, ~tp", [Loc]), - print(1, "*** FAILED ~ts ***", - [get_info_str(Mod,Func, CaseNum, get(test_server_cases))]), + io:fwrite(user, "F", []), test_server_sup:framework_call(report, [tc_done,{Mod,{Func,GrName}, {failed,testcase_aborted}}]), @@ -4097,11 +4106,10 @@ progress(failed, CaseNum, Mod, Func, GrName, Loc, {testcase_aborted,Reason}, _T, [Reason]))]), failed; -progress(failed, CaseNum, Mod, Func, GrName, unknown, Reason, Time, +progress(failed, _CaseNum, Mod, Func, GrName, unknown, Reason, Time, Comment0, {St0,St1}) -> print(major, "=result failed: ~tp, ~w", [Reason,unknown_location]), - print(1, "*** FAILED ~ts ***", - [get_info_str(Mod,Func, CaseNum, get(test_server_cases))]), + io:fwrite(user, "F", []), test_server_sup:framework_call(report, [tc_done,{Mod,{Func,GrName}, {failed,Reason}}]), TimeStr = io_lib:format(if is_float(Time) -> "~.3fs"; @@ -4136,7 +4144,7 @@ progress(failed, CaseNum, Mod, Func, GrName, unknown, Reason, Time, [escape_chars(io_lib:format("=== Reason: " ++ FStr, [FormattedReason]))]), failed; -progress(failed, CaseNum, Mod, Func, GrName, Loc, Reason, Time, +progress(failed, _CaseNum, Mod, Func, GrName, Loc, Reason, Time, Comment0, {St0,St1}) -> {LocMaj,LocMin} = if Func == error_in_suite -> case get_fw_mod(undefined) of @@ -4146,8 +4154,7 @@ progress(failed, CaseNum, Mod, Func, GrName, Loc, Reason, Time, true -> {Loc,Loc} end, print(major, "=result failed: ~tp, ~tp", [Reason,LocMaj]), - print(1, "*** FAILED ~ts ***", - [get_info_str(Mod,Func, CaseNum, get(test_server_cases))]), + io:fwrite(user, "F", []), test_server_sup:framework_call(report, [tc_done,{Mod,{Func,GrName}, {failed,Reason}}]), TimeStr = io_lib:format(if is_float(Time) -> "~.3fs"; @@ -4174,6 +4181,7 @@ progress(failed, CaseNum, Mod, Func, GrName, Loc, Reason, Time, progress(ok, _CaseNum, Mod, Func, GrName, _Loc, RetVal, Time, Comment0, {St0,St1}) -> + io:fwrite(user, ".", []), print(minor, "successfully completed test case", []), test_server_sup:framework_call(report, [tc_done,{Mod,{Func,GrName},ok}]), TimeStr = io_lib:format(if is_float(Time) -> "~.3fs"; @@ -4288,14 +4296,6 @@ update_skip_counters(Pat, {US,AS}) -> {_,Result} = if_auto_skip(Pat, fun() -> {US,AS+1} end, fun() -> {US+1,AS} end), Result. -get_info_str(Mod,Func, 0, _Cases) -> - io_lib:format("~tw", [{Mod,Func}]); -get_info_str(_Mod,_Func, CaseNum, unknown) -> - "test case " ++ integer_to_list(CaseNum); -get_info_str(_Mod,_Func, CaseNum, Cases) -> - "test case " ++ integer_to_list(CaseNum) ++ - " of " ++ integer_to_list(Cases). - print_if_known(Known, {SK,AK}, {SU,AU}) -> {S,A} = if Known == unknown -> {SU,AU}; true -> {SK,AK} diff --git a/make/test_target_script.sh b/make/test_target_script.sh index 6e155f30a4b5..a53ca2e15f0d 100755 --- a/make/test_target_script.sh +++ b/make/test_target_script.sh @@ -28,10 +28,6 @@ BOLD='\033[1m' NC='\033[0m' SILENT="${SILENT:-0}" -if [ "$SILENT" -eq 1 ] && [ "${WSLcross}" != "true" ]; then - # cth_log_redirect is enabled by default, to configure it we need to remove and re-add it - ARGS="-enable_builtin_hooks false -ct_hooks cth_log_redirect [{mode,replace}] ${ARGS}" -fi print_highlighted_msg_with_printer () { From 85a3b87445c8b834503e93ec311c330e1b73656a Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Tue, 25 Jul 2023 13:25:18 +0200 Subject: [PATCH 05/22] ct: Display result output based on # of failed tests --- HOWTO/DEVELOPMENT.md | 7 +- lib/common_test/doc/src/ct_hooks_chapter.xml | 10 ++- lib/common_test/src/ct_console.erl | 94 ++++++++++++++++---- lib/common_test/src/test_server_ctrl.erl | 18 ++-- 4 files changed, 90 insertions(+), 39 deletions(-) diff --git a/HOWTO/DEVELOPMENT.md b/HOWTO/DEVELOPMENT.md index 670db3918a45..ca64e317fbf0 100644 --- a/HOWTO/DEVELOPMENT.md +++ b/HOWTO/DEVELOPMENT.md @@ -213,14 +213,15 @@ for all process you would do this: ERL_ARGS="+hmqd off_heap" make emulator_test ``` -If you want logger messages to only be printed into the Common Test HTML logs -and keep test script information about starting and stopping the run to a -minimum, you can pass `-s` or `--silent`: +If you want to keep test script information about starting and stopping the run +to a minimum, you can pass `-s` or `--silent`: ```bash make test -s ``` +This will also quiet down other logs emitted by `make`. + ### Build and test a specific application You can also build the application from within itself. Like this: diff --git a/lib/common_test/doc/src/ct_hooks_chapter.xml b/lib/common_test/doc/src/ct_hooks_chapter.xml index 2ea87b493b96..019f86a1899a 100644 --- a/lib/common_test/doc/src/ct_hooks_chapter.xml +++ b/lib/common_test/doc/src/ct_hooks_chapter.xml @@ -517,14 +517,16 @@ results(State) ->

Replace the default logging handler by the log redirect instead of logging to both the default handler and the - cth_log_redirect handler. To use this mode, disable the builtin - hook and reconfigure it:

-

-enable_builtin_hooks false -ct_hooks cth_log_redirect [{mode,replace}]

+ cth_log_redirect handler. This is the default behaviour.

{mode, add}

Add the logging handler instead of replacing the default logging - handler. This is the default behaviour.

+ handler. To use this mode, pass the -verbose flag to ct_run. + -verbose is the short form of disabling the builtin + configuration of the hook and reconfiguring it:

+

+

-enable_builtin_hooks false -ct_hooks cth_log_redirect [{mode,replace}]

diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index f5d5b555806b..4936beb2714a 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -1,8 +1,45 @@ % Deals with output formatting for the terminal. -module(ct_console). --export([print_header/1, pluralize/3]). +-export([print_header/1, print_results/1, pluralize/3]). +%% Coloured output formatting charaters +% If adding a new format here, make sure to add it to `size_on_terminal/1`. +-define(TERM_BOLD, "\033[;1m"). +-define(TERM_BOLD_GREEN, "\033[;1;32m"). +-define(TERM_BLACK, "\033[;30m"). +-define(TERM_RED, "\033[;31m"). +-define(TERM_GREEN, "\033[;32m"). +-define(TERM_YELLOW, "\033[;33m"). +-define(TERM_CLEAR, "\033[0m"). + + +-spec print_results(map()) -> ok. +print_results(#{total := #{passed := OkN, failed := FailedN, + user_skipped := UserSkipN, auto_skipped := AutoSkipN}}) -> + AllSkippedN = UserSkipN + AutoSkipN, + PassedStr = format_if_nonzero(OkN, "~s~w passed~s", [?TERM_BOLD_GREEN, OkN, ?TERM_CLEAR]), + SkipStr = format_if_nonzero(AllSkippedN, "~s~w skipped~s", [?TERM_YELLOW, AllSkippedN, ?TERM_CLEAR]), + FailedStr = format_if_nonzero(FailedN, "~s~w failed~s", [?TERM_RED, FailedN, ?TERM_CLEAR]), + NonemptyStrs = lists:filter(fun(Item) -> Item =/= "" end, [PassedStr, SkipStr, FailedStr]), + ResultStr = lists:join(", ", NonemptyStrs), + PaddingColor = result_padding_color(OkN, FailedN), + ResultSize = size_on_terminal(ResultStr), + {PaddingSizeLeft, PaddingSizeRight} = centering_padding_size(ResultSize), + {PaddingLeft, PaddingRight} = padding_characters(PaddingSizeLeft, PaddingSizeRight), + io:fwrite( + user, + "~s~ts~s~ts~s~ts~s~n", + [PaddingColor, PaddingLeft, ?TERM_CLEAR, ResultStr, PaddingColor, PaddingRight, ?TERM_CLEAR] + ). + +-spec result_padding_color(non_neg_integer(), non_neg_integer()) -> string(). +result_padding_color(_Ok, 0) -> ?TERM_GREEN; +result_padding_color(_Ok, _Failed) -> ?TERM_RED. + +-spec format_if_nonzero(non_neg_integer(), io_lib:format(), [term()]) -> string(). +format_if_nonzero(0, _Format, _Data) -> ""; +format_if_nonzero(_, Format, Data) -> io_lib:format(Format, Data). -spec print_header(string()) -> ok. print_header(Message) -> @@ -10,23 +47,30 @@ print_header(Message) -> -spec format_header(string()) -> string(). format_header(Message) -> - {ok, Columns} = terminal_width(user), - MessageLength = iolist_size(Message), - PaddingSizeLeft = trunc(Columns / 2) - trunc(MessageLength / 2) - 1, - PaddingSizeRight = header_right_padding(Columns, PaddingSizeLeft, MessageLength), + {PaddingSizeLeft, PaddingSizeRight} = centering_padding_size(iolist_size(Message)), % shell_docs contains a lot of useful functions that we could maybe factor % out and use here. - Start = "\033[;1m", - Stop = "\033[0m", - case PaddingSizeLeft of - Amount when Amount < 0 -> - % Not enough space to print the padding, proceed normally. - io_lib:format("~s~s~s~n", [Start, Message, Stop]); - _Amount -> - PaddingLeft = lists:duplicate(PaddingSizeLeft, "="), - PaddingRight = lists:duplicate(PaddingSizeRight, "="), - io_lib:format("~s~s ~s ~s~s~n", [Start, PaddingLeft, Message, PaddingRight, Stop]) - end. + Start = ?TERM_BOLD, + Stop = ?TERM_CLEAR, + {PaddingLeft, PaddingRight} = padding_characters(PaddingSizeLeft, PaddingSizeRight), + io_lib:format("~s~ts~s~ts~s~n", [Start, PaddingLeft, Message, PaddingRight, Stop]). + + +-spec padding_characters(integer(), integer()) -> {string(), string()}. +padding_characters(SizeLeft, _SizeRight) when SizeLeft < 0 -> + % Not enough space to print the padding, proceed normally. + {"", ""}; +padding_characters(SizeLeft, SizeRight) -> + Left = lists:duplicate(SizeLeft, "="), + Right = lists:duplicate(SizeRight, "="), + {Left ++ " ", [" " | Right]}. + +-spec centering_padding_size(integer()) -> {integer(), integer()}. +centering_padding_size(MessageSize) -> + {ok, Columns} = terminal_width(user), + PaddingSizeLeft = trunc(Columns / 2) - trunc(MessageSize / 2) - 1, + PaddingSizeRight = header_right_padding(Columns, PaddingSizeLeft, MessageSize), + {PaddingSizeLeft, PaddingSizeRight}. -spec pluralize(non_neg_integer(), string(), string()) -> string(). @@ -44,9 +88,21 @@ terminal_width(Driver) -> end. -spec header_right_padding(pos_integer(), pos_integer(), pos_integer()) -> pos_integer(). -header_right_padding(_Columns, LeftPadding, MessageLength) when MessageLength rem 2 == 1 -> +header_right_padding(_Columns, LeftPadding, MessageSize) when MessageSize rem 2 == 1 -> LeftPadding - 1; -header_right_padding(Columns, LeftPadding, _MessageLength) when Columns rem 2 == 0 -> +header_right_padding(Columns, LeftPadding, _MessageSize) when Columns rem 2 == 0 -> LeftPadding; -header_right_padding(_Columns, LeftPadding, _MessageLength) -> +header_right_padding(_Columns, LeftPadding, _MessageSize) -> LeftPadding + 1. + +-spec size_on_terminal(iolist()) -> non_neg_integer(). +size_on_terminal(?TERM_BOLD ++ Rest) -> size_on_terminal(Rest); +size_on_terminal(?TERM_BOLD_GREEN ++ Rest) -> size_on_terminal(Rest); +size_on_terminal(?TERM_BLACK ++ Rest) -> size_on_terminal(Rest); +size_on_terminal(?TERM_RED ++ Rest) -> size_on_terminal(Rest); +size_on_terminal(?TERM_GREEN ++ Rest) -> size_on_terminal(Rest); +size_on_terminal(?TERM_YELLOW ++ Rest) -> size_on_terminal(Rest); +size_on_terminal(?TERM_CLEAR ++ Rest) -> size_on_terminal(Rest); +size_on_terminal([Items | Rest]) when is_list(Items) -> size_on_terminal(Items) + size_on_terminal(Rest); +size_on_terminal([Char | Rest]) when is_integer(Char) -> 1 + size_on_terminal(Rest); +size_on_terminal([]) -> 0. diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index 8f21b5d77e54..81221cb9eb93 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -2161,18 +2161,9 @@ run_test_cases(TestSpec, Config, TimetrapData) -> user_skipped := UserSkipN, auto_skipped := AutoSkipN } - } = run_test_cases_loop(TestSpec, [Config], TimetrapData, [], []), - AllSkippedN = UserSkipN + AutoSkipN, - SkipStr = case AllSkippedN of - 0 -> ""; - Skips -> io_lib:format(", ~w skipped", [Skips]) - end, - - % We need to run through the user GL here to prevent having our output captured. - io:fwrite(user, "~n", []), - Trailer = io_lib:format("test finished: ~w ok, ~w failed~ts of ~w test cases", - [OkN, FailedN, SkipStr, OkN + FailedN + AllSkippedN]), - ct_console:print_header(Trailer), + } = Results = run_test_cases_loop(TestSpec, [Config], TimetrapData, [], []), + io:fwrite(user, "~n~n", []), + ct_console:print_results(Results), test_server_sup:framework_call(report, [tests_done, {OkN,FailedN,{UserSkipN,AutoSkipN}}]), print(major, "=finished ~s", [lists:flatten(timestamp_get(""))]), @@ -2184,7 +2175,7 @@ run_test_cases(TestSpec, Config, TimetrapData) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%% run_test_cases_loop(TestCases, Config, TimetrapData, Mode, Status) -> ok +%% run_test_cases_loop(TestCases, Config, TimetrapData, Mode, Status) -> Results %% TestCases = [Test,...] %% Config = [[{Key,Val},...],...] %% TimetrapData = {MultiplyTimetrap,ScaleTimetrap} @@ -2201,6 +2192,7 @@ run_test_cases(TestSpec, Config, TimetrapData) -> %% repeat_until_all_fail | {repeat_until_all_fail,N} %% Status = [{Ref,{{Ok,Skipped,Failed},CopiedCases}}] %% Ok = Skipped = Failed = [Case,...] +%% Results = map() %% %% Execute the TestCases under configuration Config. Config is a list %% of lists, where hd(Config) holds the config tuples for the current From abcfa53a0a7cc48f101018bf9f17556a8691bf78 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Wed, 2 Aug 2023 16:03:12 +0200 Subject: [PATCH 06/22] ct: Output link to index.html at test run end --- lib/common_test/src/ct_logs.erl | 12 +----------- lib/common_test/src/ct_run.erl | 3 +-- make/test_target_script.sh | 11 ----------- 3 files changed, 2 insertions(+), 24 deletions(-) diff --git a/lib/common_test/src/ct_logs.erl b/lib/common_test/src/ct_logs.erl index 679d9109423b..31743b4f87b7 100644 --- a/lib/common_test/src/ct_logs.erl +++ b/lib/common_test/src/ct_logs.erl @@ -1933,10 +1933,6 @@ make_all_runs_index(When) -> put(basic_html, basic_html()), AbsName = ?abs(?all_runs_name), notify_and_lock_file(AbsName), - if When == start -> ok; - true -> io:put_chars("Updating " ++ AbsName ++ " ... ") - end, - %% check if log cache should be used, and if it exists UseCache = if When == refresh -> @@ -1994,9 +1990,6 @@ make_all_runs_index(When) -> all_runs_index_footer())) end, notify_and_unlock_file(AbsName), - if When == start -> ok; - true -> io:put_chars("done\n") - end, Result. make_all_runs_from_cache(AbsName, Dirs, LogCache) -> @@ -2694,9 +2687,6 @@ update_tests_in_cache(TempData,LogCache=#log_cache{tests=Tests}) -> %% make_all_suites_index1(When, AbsIndexName, AllTestLogDirs) -> IndexName = ?index_name, - if When == start -> ok; - true -> io:put_chars("Updating " ++ AbsIndexName ++ " ... ") - end, case catch make_all_suites_index2(IndexName, AllTestLogDirs) of {'EXIT', Reason} -> io:put_chars("CRASHED while updating " ++ AbsIndexName ++ "!\n"), @@ -2713,7 +2703,7 @@ make_all_suites_index1(When, AbsIndexName, AllTestLogDirs) -> TempData}}), TempData; _ -> - io:put_chars("done\n"), + io:put_chars("HTML logs can be found at file://" ++ AbsIndexName ++ "."), TempData end; Err -> diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index 3aa8c31a0365..43d3517e9e4c 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -3023,8 +3023,7 @@ rel_to_abs(CtArgs) -> _ = code:del_path(Dir) end, code:add_patha(Abs) - end || D <- PA], - io:format(user, "~n", []). + end || D <- PA]. rm_trailing_slash(Dir) -> filename:join(filename:split(Dir)). diff --git a/make/test_target_script.sh b/make/test_target_script.sh index a53ca2e15f0d..50ab5cc5f6cc 100755 --- a/make/test_target_script.sh +++ b/make/test_target_script.sh @@ -356,14 +356,3 @@ else -rsh ssh\ ${ERL_ARGS} fi - -CT_RUN_STATUS=$? -if [ $CT_RUN_STATUS = "0" ] -then - print_highlighted_msg $GREEN "The test(s) ran successfully (ct_run returned a success code)\nTest logs: file://$MAKE_TEST_CT_LOGS/index.html" - exit 0 -else - print_on_error_note - print_highlighted_msg $RED "ct_run returned the error code $CT_RUN_STATUS\nTest logs: file://$MAKE_TEST_CT_LOGS/index.html" - exit $CT_RUN_STATUS -fi From 06e4fc6ad0616e0abdc29d96378de1e18fbee3d7 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Fri, 11 Aug 2023 09:31:44 +0200 Subject: [PATCH 07/22] ct: Display failed test cases at the end --- lib/common_test/src/ct_console.erl | 47 +++++-- lib/common_test/src/ct_framework.erl | 3 - lib/common_test/src/ct_logs.erl | 2 +- lib/common_test/src/test_server_ctrl.erl | 149 ++++++++++++----------- 4 files changed, 119 insertions(+), 82 deletions(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index 4936beb2714a..fd48a7f69f1e 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -15,8 +15,15 @@ -spec print_results(map()) -> ok. +print_results(#{results := [_ | _]} = Results) -> + {FailedTestResults, ResultsWithoutFailures} = maps:take(results, Results), + print_header("failed tests follow", ?TERM_RED), + print_failed_test_results(FailedTestResults), + print_results(ResultsWithoutFailures); + print_results(#{total := #{passed := OkN, failed := FailedN, - user_skipped := UserSkipN, auto_skipped := AutoSkipN}}) -> + user_skipped := UserSkipN, auto_skipped := AutoSkipN}, + elapsed := _Elapsed}) -> AllSkippedN = UserSkipN + AutoSkipN, PassedStr = format_if_nonzero(OkN, "~s~w passed~s", [?TERM_BOLD_GREEN, OkN, ?TERM_CLEAR]), SkipStr = format_if_nonzero(AllSkippedN, "~s~w skipped~s", [?TERM_YELLOW, AllSkippedN, ?TERM_CLEAR]), @@ -33,6 +40,15 @@ print_results(#{total := #{passed := OkN, failed := FailedN, [PaddingColor, PaddingLeft, ?TERM_CLEAR, ResultStr, PaddingColor, PaddingRight, ?TERM_CLEAR] ). +print_failed_test_results([#{reason := Reason, module := Module, function := Function} | Rest]) -> + io:fwrite(user, "=> test case ~s:~s:~n", [Module, Function]), + {CrashReason, Traceback} = Reason, + io:fwrite(user, "~tp~n~tp~n~n", [CrashReason, elide_framework_code(Traceback)]), + print_failed_test_results(Rest); + +print_failed_test_results([]) -> + ok. + -spec result_padding_color(non_neg_integer(), non_neg_integer()) -> string(). result_padding_color(_Ok, 0) -> ?TERM_GREEN; result_padding_color(_Ok, _Failed) -> ?TERM_RED. @@ -43,23 +59,27 @@ format_if_nonzero(_, Format, Data) -> io_lib:format(Format, Data). -spec print_header(string()) -> ok. print_header(Message) -> - io:fwrite(user, "~s", [format_header(Message)]). + print_header(Message, ?TERM_BOLD). --spec format_header(string()) -> string(). -format_header(Message) -> +-spec print_header(string(), string()) -> ok. +print_header(Message, StartingColor) -> + io:fwrite(user, "~s", [format_header(Message, StartingColor)]). + +-spec format_header(string(), string()) -> string(). +format_header(Message, StartingColor) -> {PaddingSizeLeft, PaddingSizeRight} = centering_padding_size(iolist_size(Message)), % shell_docs contains a lot of useful functions that we could maybe factor % out and use here. - Start = ?TERM_BOLD, Stop = ?TERM_CLEAR, {PaddingLeft, PaddingRight} = padding_characters(PaddingSizeLeft, PaddingSizeRight), - io_lib:format("~s~ts~s~ts~s~n", [Start, PaddingLeft, Message, PaddingRight, Stop]). + io_lib:format("~s~ts~s~ts~s~n", [StartingColor, PaddingLeft, Message, PaddingRight, Stop]). -spec padding_characters(integer(), integer()) -> {string(), string()}. -padding_characters(SizeLeft, _SizeRight) when SizeLeft < 0 -> - % Not enough space to print the padding, proceed normally. - {"", ""}; +% Dialyzer said this can't happen +%padding_characters(SizeLeft, _SizeRight) when SizeLeft < 0 -> +% % Not enough space to print the padding, proceed normally. +% {"", ""}; padding_characters(SizeLeft, SizeRight) -> Left = lists:duplicate(SizeLeft, "="), Right = lists:duplicate(SizeRight, "="), @@ -106,3 +126,12 @@ size_on_terminal(?TERM_CLEAR ++ Rest) -> size_on_terminal(Rest); size_on_terminal([Items | Rest]) when is_list(Items) -> size_on_terminal(Items) + size_on_terminal(Rest); size_on_terminal([Char | Rest]) when is_integer(Char) -> 1 + size_on_terminal(Rest); size_on_terminal([]) -> 0. + +%% @doc Elide framework code from the given traceback. +-spec elide_framework_code(list()) -> list(). +elide_framework_code([{test_server, _Function, _Arguments, _Location} | Rest]) -> + elide_framework_code(Rest); +elide_framework_code([Frame | Rest]) -> + [Frame | elide_framework_code(Rest)]; +elide_framework_code([]) -> + []. diff --git a/lib/common_test/src/ct_framework.erl b/lib/common_test/src/ct_framework.erl index d81df7280b90..57ccb3423eeb 100644 --- a/lib/common_test/src/ct_framework.erl +++ b/lib/common_test/src/ct_framework.erl @@ -985,10 +985,7 @@ error_notification(Mod,Func,_Args,{Error,Loc}) -> end, PrintError = fun(ErrorFormat, ErrorArgs) -> - Div = "\n- - - - - - - - - - - - - - - - - - - " - "- - - - - - - - - - - - - - - - - - - - -\n", ErrorStr2 = io_lib:format(ErrorFormat, ErrorArgs), - io:format(?def_gl, "~ts~n", [lists:concat([Div,ErrorStr2,Div])]), Link = "\n\n" "Full error description and stacktrace" diff --git a/lib/common_test/src/ct_logs.erl b/lib/common_test/src/ct_logs.erl index 31743b4f87b7..b02b0c28fa74 100644 --- a/lib/common_test/src/ct_logs.erl +++ b/lib/common_test/src/ct_logs.erl @@ -2703,7 +2703,7 @@ make_all_suites_index1(When, AbsIndexName, AllTestLogDirs) -> TempData}}), TempData; _ -> - io:put_chars("HTML logs can be found at file://" ++ AbsIndexName ++ "."), + io:put_chars("HTML logs at file://" ++ AbsIndexName ++ "."), TempData end; Err -> diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index 81221cb9eb93..d5526d15cc77 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -2161,7 +2161,7 @@ run_test_cases(TestSpec, Config, TimetrapData) -> user_skipped := UserSkipN, auto_skipped := AutoSkipN } - } = Results = run_test_cases_loop(TestSpec, [Config], TimetrapData, [], []), + } = Results = run_test_cases_loop(TestSpec, [Config], TimetrapData, [], [], []), io:fwrite(user, "~n~n", []), ct_console:print_results(Results), test_server_sup:framework_call(report, [tests_done, @@ -2175,7 +2175,7 @@ run_test_cases(TestSpec, Config, TimetrapData) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%% run_test_cases_loop(TestCases, Config, TimetrapData, Mode, Status) -> Results +%% run_test_cases_loop(TestCases, Config, TimetrapData, Mode, Status, TestResults) -> SuiteResults %% TestCases = [Test,...] %% Config = [[{Key,Val},...],...] %% TimetrapData = {MultiplyTimetrap,ScaleTimetrap} @@ -2192,7 +2192,8 @@ run_test_cases(TestSpec, Config, TimetrapData) -> %% repeat_until_all_fail | {repeat_until_all_fail,N} %% Status = [{Ref,{{Ok,Skipped,Failed},CopiedCases}}] %% Ok = Skipped = Failed = [Case,...] -%% Results = map() +%% TestResults = list() +%% SuiteResults = map() %% %% Execute the TestCases under configuration Config. Config is a list %% of lists, where hd(Config) holds the config tuples for the current @@ -2318,14 +2319,14 @@ run_test_cases(TestSpec, Config, TimetrapData) -> %% run_test_cases_loop([{SkipTag,CaseData={Type,_Ref,_Case,_Comment}}|Cases], - Config, TimetrapData, Mode, Status) when + Config, TimetrapData, Mode, TestResults, Status) 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, Status); + Config, TimetrapData, Mode, TestResults, Status); run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases], - Config, TimetrapData, Mode, Status) when + Config, TimetrapData, Mode, TestResults, Status) 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))), @@ -2352,7 +2353,7 @@ run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases], test_server_sup:framework_call(report, [ReportTag,ConfData]), run_test_cases_loop(Cases, Config, TimetrapData, ParentMode, - delete_status(Ref, Status)); + delete_status(Ref, Status), TestResults); _ -> %% this is a skipped end conf for a parallel group nested %% under a parallel group (io buffering is active) @@ -2372,7 +2373,7 @@ run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases], end, run_test_cases_loop(Cases, Config, TimetrapData, ParentMode, - delete_status(Ref, Status)) + delete_status(Ref, Status), TestResults) end; {Ref,false} -> %% this is a skipped end conf for a non-parallel group that's not @@ -2407,7 +2408,7 @@ run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases], Cases end, run_test_cases_loop(Cases1, Config, TimetrapData, ParentMode, - delete_status(Ref, Status)); + delete_status(Ref, Status), TestResults); {Ref,_} -> %% this is a skipped end conf for a non-parallel group nested under %% a parallel group (io buffering is active) @@ -2425,7 +2426,7 @@ run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases], ok end, run_test_cases_loop(Cases, Config, TimetrapData, tl(Mode), - delete_status(Ref, Status)); + delete_status(Ref, Status), TestResults); {_,false} -> %% this is a skipped start conf for a group which is not nested %% under a parallel group @@ -2434,7 +2435,7 @@ run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases], ConfData = {Mod,{Func,get_name(SkipMode)},Comment}, test_server_sup:framework_call(report, [ReportTag,ConfData]), run_test_cases_loop(Cases, Config, TimetrapData, - [conf(Ref,[])|Mode], Status); + [conf(Ref,[])|Mode], Status, TestResults); {_,Ref0} when is_reference(Ref0) -> %% this is a skipped start conf for a group nested under a parallel %% group and if this is the first nested group, io buffering must @@ -2449,40 +2450,40 @@ run_test_cases_loop([{SkipTag,{Type,Ref,Case,Comment},SkipMode}|Cases], ConfData = {Mod,{Func,get_name(SkipMode)},Comment}, test_server_sup:framework_call(report, [ReportTag,ConfData]), run_test_cases_loop(Cases, Config, TimetrapData, - [conf(Ref,[])|Mode], Status) + [conf(Ref,[])|Mode], Status, TestResults) end; run_test_cases_loop([{auto_skip_case,{Case,Comment},SkipMode}|Cases], - Config, TimetrapData, Mode, Status) -> + Config, TimetrapData, Mode, Status, TestResults) -> {Mod,Func} = skip_case(auto, undefined, get(test_server_case_num)+1, Case, Comment, is_io_buffered(), SkipMode), test_server_sup:framework_call(report, [tc_auto_skip, {Mod,{Func,get_name(SkipMode)}, Comment}]), run_test_cases_loop(Cases, Config, TimetrapData, Mode, - update_status(skipped, Mod, Func, Status)); + update_status(skipped, Mod, Func, Status), TestResults); run_test_cases_loop([{skip_case,{{Mod,all}=Case,Comment},SkipMode}|Cases], - Config, TimetrapData, Mode, Status) -> + Config, TimetrapData, Mode, Status, TestResults) -> _ = skip_case(user, undefined, 0, Case, Comment, false, SkipMode), test_server_sup:framework_call(report, [tc_user_skip, {Mod,{all,get_name(SkipMode)}, Comment}]), - run_test_cases_loop(Cases, Config, TimetrapData, Mode, Status); + run_test_cases_loop(Cases, Config, TimetrapData, Mode, Status, TestResults); run_test_cases_loop([{skip_case,{Case,Comment},SkipMode}|Cases], - Config, TimetrapData, Mode, Status) -> + Config, TimetrapData, Mode, Status, TestResults) -> {Mod,Func} = skip_case(user, undefined, get(test_server_case_num)+1, Case, Comment, is_io_buffered(), SkipMode), test_server_sup:framework_call(report, [tc_user_skip, {Mod,{Func,get_name(SkipMode)}, Comment}]), run_test_cases_loop(Cases, Config, TimetrapData, Mode, - update_status(skipped, Mod, Func, Status)); + update_status(skipped, Mod, Func, Status), TestResults); %% 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) -> + Config, TimetrapData, Mode0, Status, TestResults) -> 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} = @@ -2717,7 +2718,7 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0, TimetrapData, CurrMode), case ConfCaseResult of - {_,NewCfg,_} when Func == init_per_suite, is_list(NewCfg) -> + {_,NewCfg,_,_} when Func == init_per_suite, is_list(NewCfg) -> %% check that init_per_suite returned data on correct format case lists:filter(fun({_,_}) -> false; (_) -> true end, NewCfg) of @@ -2725,7 +2726,7 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0, set_io_buffering(IOHandler), stop_minor_log_file(), run_test_cases_loop(Cases, [NewCfg|Config], - TimetrapData, Mode, Status2); + TimetrapData, Mode, Status2, TestResults); Bad -> print(minor, "~n*** ~tw returned bad elements in Config: ~tp.~n", @@ -2736,19 +2737,19 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0, set_io_buffering(IOHandler), stop_minor_log_file(), run_test_cases_loop(Cases2, Config, TimetrapData, Mode, - delete_status(Ref, Status2)) + delete_status(Ref, Status2), TestResults) end; - {_,NewCfg,_} when StartConf, is_list(NewCfg) -> + {_,NewCfg,_,_} when StartConf, is_list(NewCfg) -> print_conf_time(ConfTime), set_io_buffering(IOHandler), stop_minor_log_file(), - run_test_cases_loop(Cases, [NewCfg|Config], TimetrapData, Mode, Status2); - {_,{framework_error,{FwMod,FwFunc},Reason},_} -> + run_test_cases_loop(Cases, [NewCfg|Config], TimetrapData, Mode, Status2, TestResults); + {_,{framework_error,{FwMod,FwFunc},Reason},_,_} -> print(minor, "~n*** ~w failed in ~tw. Reason: ~tp~n", [FwMod,FwFunc,Reason]), print(1, "~w failed in ~tw. Reason: ~tp~n", [FwMod,FwFunc,Reason]), exit(framework_error); - {_,Fail,_} when element(1,Fail) == 'EXIT'; + {_,Fail,_,_} when element(1,Fail) == 'EXIT'; element(1,Fail) == timetrap_timeout; element(1,Fail) == user_timetrap_error; element(1,Fail) == failed -> @@ -2770,9 +2771,9 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0, end, set_io_buffering(IOHandler), stop_minor_log_file(), - run_test_cases_loop(Cases2, Config1, TimetrapData, Mode, Status3); + run_test_cases_loop(Cases2, Config1, TimetrapData, Mode, Status3, TestResults); - {_,{auto_skip,SkipReason},_} -> + {_,{auto_skip,SkipReason},_,_} -> %% this case can only happen if the framework (not the user) %% decides to skip execution of a conf function {Cases2,Config1,Status3} = @@ -2791,9 +2792,9 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0, end, set_io_buffering(IOHandler), stop_minor_log_file(), - run_test_cases_loop(Cases2, Config1, TimetrapData, Mode, Status3); + run_test_cases_loop(Cases2, Config1, TimetrapData, Mode, Status3, TestResults); - {_,{Skip,Reason},_} when StartConf and ((Skip==skip) or (Skip==skipped)) -> + {_,{Skip,Reason},_,_} when StartConf and ((Skip==skip) or (Skip==skipped)) -> ReportAbortRepeat(skipped), print(minor, "~n*** ~tw skipped.~n" " Skipping all cases.", [Func]), @@ -2802,8 +2803,8 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0, run_test_cases_loop(skip_cases_upto(Ref, Cases, Reason, conf, CurrMode, skip_case), Config, TimetrapData, Mode, - delete_status(Ref, Status2)); - {_,{skip_and_save,Reason,_SavedConfig},_} when StartConf -> + delete_status(Ref, Status2), TestResults); + {_,{skip_and_save,Reason,_SavedConfig},_,_} when StartConf -> ReportAbortRepeat(skipped), print(minor, "~n*** ~tw skipped.~n" " Skipping all cases.", [Func]), @@ -2812,8 +2813,8 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0, run_test_cases_loop(skip_cases_upto(Ref, Cases, Reason, conf, CurrMode, skip_case), [hd(Config)|Config], TimetrapData, Mode, - delete_status(Ref, Status2)); - {_,_Other,_} when Func == init_per_suite -> + delete_status(Ref, Status2), TestResults); + {_,_Other,_,_} when Func == init_per_suite -> print(minor, "~n*** init_per_suite failed to return a Config list.~n", []), Reason = {failed,{Mod,init_per_suite,bad_return}}, Cases2 = skip_cases_upto(Ref, Cases, Reason, conf, CurrMode, @@ -2821,15 +2822,15 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0, set_io_buffering(IOHandler), stop_minor_log_file(), run_test_cases_loop(Cases2, Config, TimetrapData, Mode, - delete_status(Ref, Status2)); - {_,_Other,_} when StartConf -> + delete_status(Ref, Status2), TestResults); + {_,_Other,_,_} when StartConf -> print_conf_time(ConfTime), set_io_buffering(IOHandler), ReportRepeatStop(), stop_minor_log_file(), run_test_cases_loop(Cases, [hd(Config)|Config], TimetrapData, - Mode, Status2); - {_,_EndConfRetVal,Opts} -> + Mode, Status2, TestResults); + {_,_EndConfRetVal,Opts,_} -> %% Check if return_group_result is set (ok, skipped or failed) and %% if so: %% 1) *If* the parent group is a sequence, skip all proceeding tests @@ -2863,31 +2864,31 @@ run_test_cases_loop([{conf,Ref,Props,{Mod,Func}}|_Cases]=Cs0, set_io_buffering(IOHandler), stop_minor_log_file(), run_test_cases_loop(Cases2, tl(Config), TimetrapData, - Mode, Status3) + Mode, Status3, TestResults) end; run_test_cases_loop([{make,Ref,{Mod,Func,Args}}|Cases0], Config, TimetrapData, - Mode, Status) -> + Mode, Status, TestResults) -> case run_test_case(Ref, 0, Mod, Func, Args, skip_init, TimetrapData) of - {_,Why={'EXIT',_},_} -> + {_,Why={'EXIT',_},_,_} -> print(minor, "~n*** ~tw failed.~n" " Skipping all cases.", [Func]), Reason = {failed,{Mod,Func,Why}}, Cases = skip_cases_upto(Ref, Cases0, Reason, conf, Mode, auto_skip_case), stop_minor_log_file(), - run_test_cases_loop(Cases, Config, TimetrapData, Mode, Status); - {_,_Whatever,_} -> + run_test_cases_loop(Cases, Config, TimetrapData, Mode, Status, TestResults); + {_,_Whatever,_,_} -> stop_minor_log_file(), - run_test_cases_loop(Cases0, Config, TimetrapData, Mode, Status) + run_test_cases_loop(Cases0, Config, TimetrapData, Mode, Status, TestResults) end; run_test_cases_loop([{conf,_Ref,_Props,_X}=Conf|_Cases0], - Config, _TimetrapData, _Mode, _Status) -> + Config, _TimetrapData, _Mode, _Status, _TestResults) -> erlang:error(badarg, [Conf,Config]); run_test_cases_loop([{repeat,Case,{RepeatType,N}}|Cases0], Config, - TimeTrapData, Mode, Status) -> + TimeTrapData, Mode, Status, TestResults) -> Ref = make_ref(), Parallel = check_prop(parallel, Mode) =/= false, Sequence = check_prop(sequence, Mode) =/= false, @@ -2906,10 +2907,10 @@ run_test_cases_loop([{repeat,Case,{RepeatType,N}}|Cases0], Config, true -> Mode1 = [{Ref,[{repeat,{RepeatType,1,N}}],?now}|Mode], run_test_cases_loop([Case | Cases0], Config, TimeTrapData, - Mode1, Status) + Mode1, Status, TestResults) end; -run_test_cases_loop([{Mod,Case}|Cases], Config, TimetrapData, Mode, Status) -> +run_test_cases_loop([{Mod,Case}|Cases], Config, TimetrapData, Mode, Status, TestResults) -> ActualCfg = case get(test_server_create_priv_dir) of auto_per_run -> @@ -2919,9 +2920,10 @@ run_test_cases_loop([{Mod,Case}|Cases], Config, TimetrapData, Mode, Status) -> update_config(hd(Config), [{data_dir,get_data_dir(Mod)}]) end, run_test_cases_loop([{Mod,Case,[ActualCfg]}|Cases], Config, - TimetrapData, Mode, Status); + TimetrapData, Mode, Status, TestResults); -run_test_cases_loop([{Mod,Func,Args}=Case|Cases], Config, TimetrapData, Mode0, Status) -> +run_test_cases_loop([{Mod,Func,Args}=Case|Cases], Config, TimetrapData, + Mode0, Status, TestResults) -> {Num,RunInit} = case FwMod = get_fw_mod(?MODULE) of Mod when Func == error_in_suite -> @@ -2954,14 +2956,14 @@ run_test_cases_loop([{Mod,Func,Args}=Case|Cases], Config, TimetrapData, Mode0, S case run_test_case(undefined, Num+1, Mod, Func, Args, RunInit, TimetrapData, Mode) of %% callback to framework module failed, exit immediately - {_,{framework_error,{FwMod,FwFunc},Reason},_} -> + {_,{framework_error,{FwMod,FwFunc},Reason},_,_} -> print(minor, "~n*** ~w failed in ~tw. Reason: ~tp~n", [FwMod,FwFunc,Reason]), print(1, "~w failed in ~tw. Reason: ~tp~n", [FwMod,FwFunc,Reason]), stop_minor_log_file(), exit(framework_error); %% sequential execution of test case finished - {Time,RetVal,_} -> + {Time,RetVal,_,Metadata} -> RetTag = if is_tuple(RetVal) -> element(1,RetVal); true -> undefined @@ -2977,12 +2979,13 @@ run_test_cases_loop([{Mod,Func,Args}=Case|Cases], Config, TimetrapData, Mode0, S _ -> {ok,false,update_status(ok, Mod, Func, Status)} end, + NewResults = update_test_results(TestResults, Failed, Metadata), case check_prop(sequence, Mode) of false -> {Cases1,Mode1} = check_repeat_testcase(Case,Result,Cases,Mode0), stop_minor_log_file(), - run_test_cases_loop(Cases1, Config, TimetrapData, Mode1, Status1); + run_test_cases_loop(Cases1, Config, TimetrapData, Mode1, Status1, NewResults); Ref -> %% the case is in a sequence; we must check the result and %% determine if the following cases should run or be skipped @@ -2990,7 +2993,7 @@ run_test_cases_loop([{Mod,Func,Args}=Case|Cases], Config, TimetrapData, Mode0, S {Cases1,Mode1} = check_repeat_testcase(Case,Result,Cases,Mode0), stop_minor_log_file(), - run_test_cases_loop(Cases1, Config, TimetrapData, Mode1, Status1); + run_test_cases_loop(Cases1, Config, TimetrapData, Mode1, Status1, NewResults); true -> % skip rest of cases in sequence print(minor, "~n*** ~tw failed.~n" " Skipping all other cases in sequence.", @@ -3001,7 +3004,7 @@ run_test_cases_loop([{Mod,Func,Args}=Case|Cases], Config, TimetrapData, Mode0, S Cases2 = skip_cases_upto(Ref, Cases1, Reason, tc, Mode, auto_skip_case), stop_minor_log_file(), - run_test_cases_loop(Cases2, Config, TimetrapData, Mode1, Status1) + run_test_cases_loop(Cases2, Config, TimetrapData, Mode1, Status1, NewResults) end end; %% the test case is being executed in parallel with the main process (and @@ -3011,11 +3014,11 @@ run_test_cases_loop([{Mod,Func,Args}=Case|Cases], Config, TimetrapData, Mode0, S %% handled later, so we have to save info about the case queue_test_case_io(undefined, Pid, Num+1, Mod, Func), {Cases1,Mode1} = check_repeat_testcase(Case,ok,Cases,Mode0), - run_test_cases_loop(Cases1, Config, TimetrapData, Mode1, Status) + run_test_cases_loop(Cases1, Config, TimetrapData, Mode1, Status, TestResults) end; %% TestSpec processing finished -run_test_cases_loop([], _Config, _TimetrapData, _, _Status) -> +run_test_cases_loop([], _Config, _TimetrapData, _, _Status, TestResults) -> {UserSkipped, AutoSkipped} = get(test_server_skipped), #{ total => #{ @@ -3023,12 +3026,18 @@ run_test_cases_loop([], _Config, _TimetrapData, _, _Status) -> failed => get(test_server_failed), user_skipped => UserSkipped, auto_skipped => AutoSkipped - } + }, + results => TestResults, + elapsed => get(test_server_total_time) }. %%-------------------------------------------------------------------- %% various help functions +-spec update_test_results(list(), boolean(), map()) -> list(). +update_test_results(Results, false, _Metadata) -> Results; +update_test_results(Results, true, Metadata) -> [Metadata | Results]. + new_status(Ref, Status) -> [{Ref,{{[],[],[]},[]}} | Status]. @@ -3499,7 +3508,7 @@ is_io_buffered() -> %% Save info about test case that gets its io buffered. This can %% be a parallel test case or it can be a test case (conf or normal) %% that belongs to a group nested under a parallel group. The queue -%% is processed after io buffering is disabled. See run_test_cases_loop/4 +%% is processed after io buffering is disabled. See run_test_cases_loop/5 %% and handle_test_case_io_and_status/0 for more info. queue_test_case_io(Ref, Pid, Num, Mod, Func) -> @@ -3593,7 +3602,7 @@ rm_cases_upto(Ref, [_|Ps]) -> %% by the main process (note that these cases do not generate 'EXIT' %% messages, only 'start' and 'finished' messages). %% -%% See the header comment for run_test_cases_loop/4 for more +%% See the header comment for run_test_cases_loop/5 for more %% info about IO handling. %% %% Note: It is important that the type of messages handled here @@ -3853,7 +3862,7 @@ run_test_case1(Ref, Num, Mod, Func, Args, RunInit, do_unless_parallel(Main, fun() -> file:set_cwd(filename:dirname(TSDir)) end), %% call the appropriate progress function clause to print the results to log - Status = + {Status, Metadata} = case {Time,RetVal} of {died,{timetrap_timeout,TimetrapTimeout}} -> progress(failed, Num, Mod, Func, GrName, Loc, @@ -3965,7 +3974,7 @@ run_test_case1(Ref, Num, Mod, Func, Args, RunInit, end, %% if the test case was executed sequentially, this updates the execution %% time count on the main process (adding execution time of parallel test - %% case groups is done in run_test_cases_loop/4) + %% case groups is done in run_test_cases_loop/5) if is_number(Time) -> put(test_server_total_time, get(test_server_total_time)+Time); true -> @@ -3984,7 +3993,9 @@ run_test_case1(Ref, Num, Mod, Func, Args, RunInit, ?mod_result(Status),{Time,RetVal,Opts}}, ok end, - {Time,RetVal,Opts}. + ExecutionMetadata = #{module => Mod, function => Func}, + FullMetadata = maps:merge(Metadata, ExecutionMetadata), + {Time,RetVal,Opts,FullMetadata}. %%-------------------------------------------------------------------- @@ -4043,7 +4054,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; + {Ret, #{reason => element(2, Reason1)}}; progress(failed, _CaseNum, Mod, Func, GrName, Loc, timetrap_timeout, T, Comment0, {St0,St1}) -> @@ -4068,7 +4079,7 @@ progress(failed, _CaseNum, Mod, Func, GrName, Loc, timetrap_timeout, T, FormatLoc = test_server_sup:format_loc(Loc), print(minor, "=== Location: ~ts", [FormatLoc]), print(minor, "=== Reason: timetrap timeout", []), - failed; + {failed, #{reason => timetrap_timeout}}; progress(failed, _CaseNum, Mod, Func, GrName, Loc, {testcase_aborted,Reason}, _T, Comment0, {St0,St1}) -> @@ -4096,7 +4107,7 @@ progress(failed, _CaseNum, Mod, Func, GrName, Loc, {testcase_aborted,Reason}, _T "~ts", [escape_chars(io_lib:format("=== Reason: {testcase_aborted,~tp}", [Reason]))]), - failed; + {failed, #{reason => {testcase_aborted, Reason}}}; progress(failed, _CaseNum, Mod, Func, GrName, unknown, Reason, Time, Comment0, {St0,St1}) -> @@ -4134,7 +4145,7 @@ progress(failed, _CaseNum, Mod, Func, GrName, unknown, Reason, Time, print(minor, "~ts", [escape_chars(io_lib:format("=== Reason: " ++ FStr, [FormattedReason]))]), - failed; + {failed, #{reason => unknown}}; progress(failed, _CaseNum, Mod, Func, GrName, Loc, Reason, Time, Comment0, {St0,St1}) -> @@ -4169,7 +4180,7 @@ progress(failed, _CaseNum, Mod, Func, GrName, Loc, Reason, Time, print(minor, "~ts", ["=== Reason: " ++ escape_chars(io_lib:format(FStr, [FormattedReason]))]), - failed; + {failed, #{reason => Reason}}; progress(ok, _CaseNum, Mod, Func, GrName, _Loc, RetVal, Time, Comment0, {St0,St1}) -> @@ -4204,7 +4215,7 @@ progress(ok, _CaseNum, Mod, Func, GrName, _Loc, RetVal, Time, print(minor, "~ts", [escape_chars(io_lib:format("=== Returned value: ~tp", [RetVal]))]), - ok. + {ok, #{}}. %%-------------------------------------------------------------------- %% various help functions From 1690c1badbce8ca85b4de08c2bab4ac9f4fd2b94 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Fri, 11 Aug 2023 10:37:20 +0200 Subject: [PATCH 08/22] ct: Display elapsed time at end of test run --- lib/common_test/src/ct_console.erl | 25 ++++++++++++++++++++++-- lib/common_test/src/test_server_ctrl.erl | 2 +- 2 files changed, 24 insertions(+), 3 deletions(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index fd48a7f69f1e..4d7fa8d354a8 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -23,14 +23,16 @@ print_results(#{results := [_ | _]} = Results) -> print_results(#{total := #{passed := OkN, failed := FailedN, user_skipped := UserSkipN, auto_skipped := AutoSkipN}, - elapsed := _Elapsed}) -> + elapsed := Elapsed}) -> AllSkippedN = UserSkipN + AutoSkipN, PassedStr = format_if_nonzero(OkN, "~s~w passed~s", [?TERM_BOLD_GREEN, OkN, ?TERM_CLEAR]), SkipStr = format_if_nonzero(AllSkippedN, "~s~w skipped~s", [?TERM_YELLOW, AllSkippedN, ?TERM_CLEAR]), FailedStr = format_if_nonzero(FailedN, "~s~w failed~s", [?TERM_RED, FailedN, ?TERM_CLEAR]), NonemptyStrs = lists:filter(fun(Item) -> Item =/= "" end, [PassedStr, SkipStr, FailedStr]), - ResultStr = lists:join(", ", NonemptyStrs), + TimeDescription = format_time(Elapsed), PaddingColor = result_padding_color(OkN, FailedN), + FormattedTimeDescription = io_lib:format("~s in ~s~s", [PaddingColor, TimeDescription, ?TERM_CLEAR]), + ResultStr = lists:join(", ", NonemptyStrs) ++ FormattedTimeDescription, ResultSize = size_on_terminal(ResultStr), {PaddingSizeLeft, PaddingSizeRight} = centering_padding_size(ResultSize), {PaddingLeft, PaddingRight} = padding_characters(PaddingSizeLeft, PaddingSizeRight), @@ -40,6 +42,7 @@ print_results(#{total := #{passed := OkN, failed := FailedN, [PaddingColor, PaddingLeft, ?TERM_CLEAR, ResultStr, PaddingColor, PaddingRight, ?TERM_CLEAR] ). + print_failed_test_results([#{reason := Reason, module := Module, function := Function} | Rest]) -> io:fwrite(user, "=> test case ~s:~s:~n", [Module, Function]), {CrashReason, Traceback} = Reason, @@ -93,6 +96,10 @@ centering_padding_size(MessageSize) -> {PaddingSizeLeft, PaddingSizeRight}. +-spec pluralize(non_neg_integer(), string()) -> string(). +pluralize(Amount, Singular) -> + pluralize(Amount, Singular, Singular ++ "s"). + -spec pluralize(non_neg_integer(), string(), string()) -> string(). pluralize(1, Singular, _Plural) -> Singular; pluralize(_, _Singular, Plural) -> Plural. @@ -135,3 +142,17 @@ elide_framework_code([Frame | Rest]) -> [Frame | elide_framework_code(Rest)]; elide_framework_code([]) -> []. + + +%% @doc Turn the given seconds into a human-readable string. +-spec format_time(non_neg_integer()) -> string(). +format_time(Seconds) -> + Minutes = trunc(Seconds / 60), + RemainingSeconds = Seconds rem 60, + case Minutes of + 0 -> + io_lib:format("~w ~s", [Seconds, pluralize(Seconds, "second")]); + _ -> + io_lib:format("~w ~s and ~w ~s", [Minutes, pluralize(Minutes, "minute"), + RemainingSeconds, pluralize(RemainingSeconds, "second")]) + end. diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index d5526d15cc77..eb8be6a79d9b 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -3028,7 +3028,7 @@ run_test_cases_loop([], _Config, _TimetrapData, _, _Status, TestResults) -> auto_skipped => AutoSkipped }, results => TestResults, - elapsed => get(test_server_total_time) + elapsed => trunc(get(test_server_total_time)) }. %%-------------------------------------------------------------------- From 113ab16dbd07f626bd0b6a938bd1d5a0cff93177 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Fri, 11 Aug 2023 10:53:49 +0200 Subject: [PATCH 09/22] ct: Print suite whose tests are being executed Co-authored-by: Jakub Witczak --- lib/common_test/src/ct_logs.erl | 2 +- lib/common_test/src/ct_run.erl | 4 ++-- lib/common_test/src/test_server_ctrl.erl | 13 +++++++++---- 3 files changed, 12 insertions(+), 7 deletions(-) diff --git a/lib/common_test/src/ct_logs.erl b/lib/common_test/src/ct_logs.erl index b02b0c28fa74..447ea8645f61 100644 --- a/lib/common_test/src/ct_logs.erl +++ b/lib/common_test/src/ct_logs.erl @@ -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 -> diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index 43d3517e9e4c..29f04f12a908 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -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 diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index eb8be6a79d9b..a547f15771b0 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -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))), @@ -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} = @@ -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}) -> From a6fdfb9238e3c8631bf8001e1ea1faf51d40e97f Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Fri, 11 Aug 2023 11:24:49 +0200 Subject: [PATCH 10/22] ct: Respect NO_COLOR variable too See https://no-color.org/ --- lib/common_test/src/ct_console.erl | 31 +++++++++++++++++++++--------- 1 file changed, 22 insertions(+), 9 deletions(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index 4d7fa8d354a8..23e9939a1af0 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -3,7 +3,7 @@ -module(ct_console). -export([print_header/1, print_results/1, pluralize/3]). -%% Coloured output formatting charaters +%% Colored output formatting charaters % If adding a new format here, make sure to add it to `size_on_terminal/1`. -define(TERM_BOLD, "\033[;1m"). -define(TERM_BOLD_GREEN, "\033[;1;32m"). @@ -13,11 +13,10 @@ -define(TERM_YELLOW, "\033[;33m"). -define(TERM_CLEAR, "\033[0m"). - -spec print_results(map()) -> ok. print_results(#{results := [_ | _]} = Results) -> {FailedTestResults, ResultsWithoutFailures} = maps:take(results, Results), - print_header("failed tests follow", ?TERM_RED), + print_header("failed tests follow", mc(?TERM_RED)), print_failed_test_results(FailedTestResults), print_results(ResultsWithoutFailures); @@ -25,9 +24,9 @@ print_results(#{total := #{passed := OkN, failed := FailedN, user_skipped := UserSkipN, auto_skipped := AutoSkipN}, elapsed := Elapsed}) -> AllSkippedN = UserSkipN + AutoSkipN, - PassedStr = format_if_nonzero(OkN, "~s~w passed~s", [?TERM_BOLD_GREEN, OkN, ?TERM_CLEAR]), - SkipStr = format_if_nonzero(AllSkippedN, "~s~w skipped~s", [?TERM_YELLOW, AllSkippedN, ?TERM_CLEAR]), - FailedStr = format_if_nonzero(FailedN, "~s~w failed~s", [?TERM_RED, FailedN, ?TERM_CLEAR]), + PassedStr = format_if_nonzero(OkN, "~s~w passed~s", [mc(?TERM_BOLD_GREEN), OkN, ?TERM_CLEAR]), + SkipStr = format_if_nonzero(AllSkippedN, "~s~w skipped~s", [mc(?TERM_YELLOW), AllSkippedN, ?TERM_CLEAR]), + FailedStr = format_if_nonzero(FailedN, "~s~w failed~s", [mc(?TERM_RED), FailedN, ?TERM_CLEAR]), NonemptyStrs = lists:filter(fun(Item) -> Item =/= "" end, [PassedStr, SkipStr, FailedStr]), TimeDescription = format_time(Elapsed), PaddingColor = result_padding_color(OkN, FailedN), @@ -53,8 +52,8 @@ print_failed_test_results([]) -> ok. -spec result_padding_color(non_neg_integer(), non_neg_integer()) -> string(). -result_padding_color(_Ok, 0) -> ?TERM_GREEN; -result_padding_color(_Ok, _Failed) -> ?TERM_RED. +result_padding_color(_Ok, 0) -> mc(?TERM_GREEN); +result_padding_color(_Ok, _Failed) -> mc(?TERM_RED). -spec format_if_nonzero(non_neg_integer(), io_lib:format(), [term()]) -> string(). format_if_nonzero(0, _Format, _Data) -> ""; @@ -62,7 +61,7 @@ format_if_nonzero(_, Format, Data) -> io_lib:format(Format, Data). -spec print_header(string()) -> ok. print_header(Message) -> - print_header(Message, ?TERM_BOLD). + print_header(Message, mc(?TERM_BOLD)). -spec print_header(string(), string()) -> ok. print_header(Message, StartingColor) -> @@ -156,3 +155,17 @@ format_time(Seconds) -> io_lib:format("~w ~s and ~w ~s", [Minutes, pluralize(Minutes, "minute"), RemainingSeconds, pluralize(RemainingSeconds, "second")]) end. + + +%% @doc +%% Return the given string if colorized output is wanted, else an empty string. +%% `mc' => "maybe color". +%% @end +-spec mc(string()) -> string(). +mc(Color) -> + case os:getenv("NO_COLOR") of + false -> + Color; + Value when Value =/= "" -> + "" + end. From a0bec42ae56176c9f369454901b8f0d8dcbed8d8 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Fri, 11 Aug 2023 19:45:01 +0200 Subject: [PATCH 11/22] ct: Do not output successful progress for config functions --- lib/common_test/src/test_server_ctrl.erl | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index a547f15771b0..b107e880f3b2 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -4189,7 +4189,10 @@ progress(failed, _CaseNum, Mod, Func, GrName, Loc, Reason, Time, progress(ok, _CaseNum, Mod, Func, GrName, _Loc, RetVal, Time, Comment0, {St0,St1}) -> - io:fwrite(user, ".", []), + IsConfigFunction = is_config_function(Func), + if IsConfigFunction -> ok; + true -> io:fwrite(user, ".", []) + end, print(minor, "successfully completed test case", []), test_server_sup:framework_call(report, [tc_done,{Mod,{Func,GrName},ok}]), TimeStr = io_lib:format(if is_float(Time) -> "~.3fs"; @@ -4297,6 +4300,14 @@ if_auto_skip({auto_skip,Reason}, True, _False) -> if_auto_skip(Reason, _True, False) -> {Reason,False()}. +is_config_function(Func) when Func == init_per_testcase; + Func == end_per_testcase; + Func == init_per_group; + Func == end_per_group; + Func == init_per_suite; + Func == end_per_suite -> true; +is_config_function(_) -> false. + update_skip_counters({_T,Pat,_Opts}, {US,AS}) -> {_,Result} = if_auto_skip(Pat, fun() -> {US,AS+1} end, fun() -> {US+1,AS} end), Result; From 3c74af59fba9d5f28c862e3be1141b3f644f3f4d Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Thu, 21 Sep 2023 11:30:10 +0200 Subject: [PATCH 12/22] ct: Report timetrap timeouts with their location --- lib/common_test/src/test_server_ctrl.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index b107e880f3b2..cd206c24fb4c 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -4084,7 +4084,7 @@ progress(failed, _CaseNum, Mod, Func, GrName, Loc, timetrap_timeout, T, FormatLoc = test_server_sup:format_loc(Loc), print(minor, "=== Location: ~ts", [FormatLoc]), print(minor, "=== Reason: timetrap timeout", []), - {failed, #{reason => timetrap_timeout}}; + {failed, #{reason => {timetrap_timeout, Loc}}}; progress(failed, _CaseNum, Mod, Func, GrName, Loc, {testcase_aborted,Reason}, _T, Comment0, {St0,St1}) -> From 9e463ef1bdd764f589d93335220e62c755a63b85 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Thu, 21 Sep 2023 11:30:34 +0200 Subject: [PATCH 13/22] ct: Annotate failure status argument --- lib/common_test/src/test_server_ctrl.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/common_test/src/test_server_ctrl.erl b/lib/common_test/src/test_server_ctrl.erl index cd206c24fb4c..3992737a91c2 100644 --- a/lib/common_test/src/test_server_ctrl.erl +++ b/lib/common_test/src/test_server_ctrl.erl @@ -3039,7 +3039,7 @@ run_test_cases_loop([], _Config, _TimetrapData, _, _Status, TestResults) -> %%-------------------------------------------------------------------- %% various help functions --spec update_test_results(list(), boolean(), map()) -> list(). +-spec update_test_results(list(), HasFailed :: boolean(), map()) -> list(). update_test_results(Results, false, _Metadata) -> Results; update_test_results(Results, true, Metadata) -> [Metadata | Results]. From 45946233561da5aebcb23fa1735c6c6311af6332 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Thu, 21 Sep 2023 11:30:55 +0200 Subject: [PATCH 14/22] ct: Handle process exits in console result format --- lib/common_test/src/ct_console.erl | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index 23e9939a1af0..46b80611ae39 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -44,13 +44,16 @@ print_results(#{total := #{passed := OkN, failed := FailedN, print_failed_test_results([#{reason := Reason, module := Module, function := Function} | Rest]) -> io:fwrite(user, "=> test case ~s:~s:~n", [Module, Function]), - {CrashReason, Traceback} = Reason, + {CrashReason, Traceback} = format_failure_reason(Reason), io:fwrite(user, "~tp~n~tp~n~n", [CrashReason, elide_framework_code(Traceback)]), print_failed_test_results(Rest); print_failed_test_results([]) -> ok. +format_failure_reason({'EXIT', Reason, Traceback}) -> {{'EXIT', Reason}, Traceback}; +format_failure_reason({_Reason, _Traceback} = Result) -> Result. + -spec result_padding_color(non_neg_integer(), non_neg_integer()) -> string(). result_padding_color(_Ok, 0) -> mc(?TERM_GREEN); result_padding_color(_Ok, _Failed) -> mc(?TERM_RED). From e6ff1198cd771f5f39d73f80f85b594682ac113d Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Thu, 21 Sep 2023 11:31:33 +0200 Subject: [PATCH 15/22] ct: Elide framework code properly --- lib/common_test/src/ct_console.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index 46b80611ae39..13e040825d7b 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -138,7 +138,7 @@ size_on_terminal([]) -> 0. %% @doc Elide framework code from the given traceback. -spec elide_framework_code(list()) -> list(). -elide_framework_code([{test_server, _Function, _Arguments, _Location} | Rest]) -> +elide_framework_code([{test_server, _Function, _Location} | Rest]) -> elide_framework_code(Rest); elide_framework_code([Frame | Rest]) -> [Frame | elide_framework_code(Rest)]; From 7e0b561e9b1068e84d5bc2d3488fe72eb63a1ff4 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Sat, 23 Sep 2023 08:10:04 +0200 Subject: [PATCH 16/22] ct: Fix discrepancies in hook documentation --- lib/common_test/doc/src/ct_hooks_chapter.xml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/lib/common_test/doc/src/ct_hooks_chapter.xml b/lib/common_test/doc/src/ct_hooks_chapter.xml index 019f86a1899a..af0aced731b2 100644 --- a/lib/common_test/doc/src/ct_hooks_chapter.xml +++ b/lib/common_test/doc/src/ct_hooks_chapter.xml @@ -525,8 +525,7 @@ results(State) -> handler. To use this mode, pass the -verbose flag to ct_run. -verbose is the short form of disabling the builtin configuration of the hook and reconfiguring it:

-

-

-enable_builtin_hooks false -ct_hooks cth_log_redirect [{mode,replace}]

+

-enable_builtin_hooks false -ct_hooks cth_log_redirect [{mode,add}]

From 2a0b32a0f3b66e3c189e938404b021278ba20dd9 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Sat, 23 Sep 2023 08:15:32 +0200 Subject: [PATCH 17/22] ct: Correct typo in ct_console.erl comment --- lib/common_test/src/ct_console.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index 13e040825d7b..c224dc86ee5d 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -3,7 +3,7 @@ -module(ct_console). -export([print_header/1, print_results/1, pluralize/3]). -%% Colored output formatting charaters +%% Colored output formatting characters % If adding a new format here, make sure to add it to `size_on_terminal/1`. -define(TERM_BOLD, "\033[;1m"). -define(TERM_BOLD_GREEN, "\033[;1;32m"). From 541388d027168674e02c0fe89ef60eb9947f74fc Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Sat, 23 Sep 2023 08:30:38 +0200 Subject: [PATCH 18/22] ct: Only use colored output if stdout is a tty --- lib/common_test/src/ct_console.erl | 51 ++++++++++++++++++++---------- 1 file changed, 35 insertions(+), 16 deletions(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index c224dc86ee5d..04592455dc7a 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -16,7 +16,8 @@ -spec print_results(map()) -> ok. print_results(#{results := [_ | _]} = Results) -> {FailedTestResults, ResultsWithoutFailures} = maps:take(results, Results), - print_header("failed tests follow", mc(?TERM_RED)), + ShouldColor = should_use_colored_output(), + print_header("failed tests follow", mc(?TERM_RED, ShouldColor)), print_failed_test_results(FailedTestResults), print_results(ResultsWithoutFailures); @@ -24,12 +25,16 @@ print_results(#{total := #{passed := OkN, failed := FailedN, user_skipped := UserSkipN, auto_skipped := AutoSkipN}, elapsed := Elapsed}) -> AllSkippedN = UserSkipN + AutoSkipN, - PassedStr = format_if_nonzero(OkN, "~s~w passed~s", [mc(?TERM_BOLD_GREEN), OkN, ?TERM_CLEAR]), - SkipStr = format_if_nonzero(AllSkippedN, "~s~w skipped~s", [mc(?TERM_YELLOW), AllSkippedN, ?TERM_CLEAR]), - FailedStr = format_if_nonzero(FailedN, "~s~w failed~s", [mc(?TERM_RED), FailedN, ?TERM_CLEAR]), + ShouldColor = should_use_colored_output(), + PassedStr = format_if_nonzero(OkN, "~s~w passed~s", + [mc(?TERM_BOLD_GREEN, ShouldColor), OkN, ?TERM_CLEAR]), + SkipStr = format_if_nonzero(AllSkippedN, "~s~w skipped~s", + [mc(?TERM_YELLOW, ShouldColor), AllSkippedN, ?TERM_CLEAR]), + FailedStr = format_if_nonzero(FailedN, "~s~w failed~s", + [mc(?TERM_RED, ShouldColor), FailedN, ?TERM_CLEAR]), NonemptyStrs = lists:filter(fun(Item) -> Item =/= "" end, [PassedStr, SkipStr, FailedStr]), TimeDescription = format_time(Elapsed), - PaddingColor = result_padding_color(OkN, FailedN), + PaddingColor = result_padding_color(OkN, FailedN, ShouldColor), FormattedTimeDescription = io_lib:format("~s in ~s~s", [PaddingColor, TimeDescription, ?TERM_CLEAR]), ResultStr = lists:join(", ", NonemptyStrs) ++ FormattedTimeDescription, ResultSize = size_on_terminal(ResultStr), @@ -54,9 +59,9 @@ print_failed_test_results([]) -> format_failure_reason({'EXIT', Reason, Traceback}) -> {{'EXIT', Reason}, Traceback}; format_failure_reason({_Reason, _Traceback} = Result) -> Result. --spec result_padding_color(non_neg_integer(), non_neg_integer()) -> string(). -result_padding_color(_Ok, 0) -> mc(?TERM_GREEN); -result_padding_color(_Ok, _Failed) -> mc(?TERM_RED). +-spec result_padding_color(non_neg_integer(), non_neg_integer(), boolean()) -> string(). +result_padding_color(_Ok, 0, ShouldColor) -> mc(?TERM_GREEN, ShouldColor); +result_padding_color(_Ok, _Failed, ShouldColor) -> mc(?TERM_RED, ShouldColor). -spec format_if_nonzero(non_neg_integer(), io_lib:format(), [term()]) -> string(). format_if_nonzero(0, _Format, _Data) -> ""; @@ -64,7 +69,8 @@ format_if_nonzero(_, Format, Data) -> io_lib:format(Format, Data). -spec print_header(string()) -> ok. print_header(Message) -> - print_header(Message, mc(?TERM_BOLD)). + ShouldColor = should_use_colored_output(), + print_header(Message, mc(?TERM_BOLD, ShouldColor)). -spec print_header(string(), string()) -> ok. print_header(Message, StartingColor) -> @@ -164,11 +170,24 @@ format_time(Seconds) -> %% Return the given string if colorized output is wanted, else an empty string. %% `mc' => "maybe color". %% @end --spec mc(string()) -> string(). -mc(Color) -> - case os:getenv("NO_COLOR") of - false -> - Color; - Value when Value =/= "" -> - "" +-spec mc(string(), ShouldColor :: boolean()) -> string(). +mc(Color, true) -> Color; +mc(_Color, false) -> "". + + +-spec should_use_colored_output() -> boolean(). +should_use_colored_output() -> + NoColor = os:getenv("NO_COLOR"), + StdoutIsATty = stdout_is_a_tty(), + NoColor == false andalso StdoutIsATty. + + +-spec stdout_is_a_tty() -> boolean(). +stdout_is_a_tty() -> + user_drv ! {self(), get_terminal_state}, + receive + {_Pid, get_terminal_state, IsATty} -> + IsATty + after 500 -> + false end. From 3c37db5db2199b7047c9f86c2a0e5b1f03617732 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Sat, 23 Sep 2023 08:34:41 +0200 Subject: [PATCH 19/22] ct: Uppercase "Common Test" in startup messages --- lib/common_test/src/ct_run.erl | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index 29f04f12a908..3b17c57997fe 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -132,7 +132,7 @@ script_start(Args) -> _ -> "" end end, - Header = io_lib:format("common test~s starting", [CTVsn]), + Header = io_lib:format("Common Test~s starting", [CTVsn]), ct_console:print_header(Header), io:format("cwd: ~ts~n", [Cwd]), Self = self(), @@ -902,7 +902,7 @@ run_test1(StartOpts) when is_list(StartOpts) -> undefined -> Tracing = start_trace(StartOpts), {ok,Cwd} = file:get_cwd(), - ct_console:print_header("common test starting"), + ct_console:print_header("Common Test starting"), io:format("cwd: ~ts~n", [Cwd]), Res = case ct_repeat:loop_test(func, StartOpts) of @@ -1393,7 +1393,7 @@ run_testspec1_fun(TestSpec) -> run_testspec1(TestSpec) -> {ok,Cwd} = file:get_cwd(), - ct_console:print_header("common test starting"), + ct_console:print_header("Common Test starting"), io:format("cwd: ~ts~n", [Cwd]), case catch run_testspec2(TestSpec) of {'EXIT',Reason} -> From 5b1b9c5ec51da01bb59feb511c8707b8cc00f99f Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Sat, 23 Sep 2023 14:45:54 +0200 Subject: [PATCH 20/22] ct: Correct unknown type in type specification --- lib/common_test/src/ct_console.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index 04592455dc7a..9eed0c9b3346 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -63,7 +63,7 @@ format_failure_reason({_Reason, _Traceback} = Result) -> Result. result_padding_color(_Ok, 0, ShouldColor) -> mc(?TERM_GREEN, ShouldColor); result_padding_color(_Ok, _Failed, ShouldColor) -> mc(?TERM_RED, ShouldColor). --spec format_if_nonzero(non_neg_integer(), io_lib:format(), [term()]) -> string(). +-spec format_if_nonzero(non_neg_integer(), io:format(), [term()]) -> string(). format_if_nonzero(0, _Format, _Data) -> ""; format_if_nonzero(_, Format, Data) -> io_lib:format(Format, Data). From 284bf84a011b454a8e6db25f5ca3b911ef904d9f Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Sat, 23 Sep 2023 15:14:44 +0200 Subject: [PATCH 21/22] ct: Fix failure reason formatting without traceback --- lib/common_test/src/ct_console.erl | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index 9eed0c9b3346..7c3d6e6cd4ea 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -56,7 +56,18 @@ print_failed_test_results([#{reason := Reason, module := Module, function := Fun print_failed_test_results([]) -> ok. +%% @doc +%% Format the reason why a test failed into the expected tuple format with the +%% following two elements: +%% +%% - The reason why the test failed, such as an explicit `test_case_failed' or +%% `badmatch' errors. +%% - The traceback of the test, as a list. Can be empty. When explicitly +%% failing a test, this will instead contain a string describing why the test +%% was failed. +%% @end format_failure_reason({'EXIT', Reason, Traceback}) -> {{'EXIT', Reason}, Traceback}; +format_failure_reason({Reason, undefined}) -> {Reason, []}; format_failure_reason({_Reason, _Traceback} = Result) -> Result. -spec result_padding_color(non_neg_integer(), non_neg_integer(), boolean()) -> string(). From 0bd7c5cf94e13953582bd96b790c5ec1cdd7f3c2 Mon Sep 17 00:00:00 2001 From: Johannes Christ Date: Mon, 25 Sep 2023 21:48:34 +0200 Subject: [PATCH 22/22] ct: Prevent crash on trying to elide non-traceback --- lib/common_test/src/ct_console.erl | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/lib/common_test/src/ct_console.erl b/lib/common_test/src/ct_console.erl index 7c3d6e6cd4ea..a5f2e6534ce5 100644 --- a/lib/common_test/src/ct_console.erl +++ b/lib/common_test/src/ct_console.erl @@ -49,8 +49,8 @@ print_results(#{total := #{passed := OkN, failed := FailedN, print_failed_test_results([#{reason := Reason, module := Module, function := Function} | Rest]) -> io:fwrite(user, "=> test case ~s:~s:~n", [Module, Function]), - {CrashReason, Traceback} = format_failure_reason(Reason), - io:fwrite(user, "~tp~n~tp~n~n", [CrashReason, elide_framework_code(Traceback)]), + {CrashReason, TracebackOrDetail} = format_failure_reason(Reason), + io:fwrite(user, "~tp~n~tp~n~n", [CrashReason, elide_framework_code(TracebackOrDetail)]), print_failed_test_results(Rest); print_failed_test_results([]) -> @@ -61,7 +61,7 @@ print_failed_test_results([]) -> %% following two elements: %% %% - The reason why the test failed, such as an explicit `test_case_failed' or -%% `badmatch' errors. +%% `badmatch' errors, or some other value returned by the test. %% - The traceback of the test, as a list. Can be empty. When explicitly %% failing a test, this will instead contain a string describing why the test %% was failed. @@ -153,14 +153,20 @@ size_on_terminal([Items | Rest]) when is_list(Items) -> size_on_terminal(Items) size_on_terminal([Char | Rest]) when is_integer(Char) -> 1 + size_on_terminal(Rest); size_on_terminal([]) -> 0. -%% @doc Elide framework code from the given traceback. +%% @doc +%% Elide framework code from the given traceback or exit reason. If the test +%% was failed explicitly due to some reason that did not generate a traceback, +%% such as an explicit fail, the given argument is passed through unchanged. +%% @end -spec elide_framework_code(list()) -> list(). elide_framework_code([{test_server, _Function, _Location} | Rest]) -> elide_framework_code(Rest); elide_framework_code([Frame | Rest]) -> [Frame | elide_framework_code(Rest)]; elide_framework_code([]) -> - []. + []; +elide_framework_code(Value) -> + Value. %% @doc Turn the given seconds into a human-readable string.