Skip to content

Commit

Permalink
common_test: abort_if_missing_suites defaults to true
Browse files Browse the repository at this point in the history
  • Loading branch information
u3s committed Nov 26, 2024
1 parent 171fb25 commit 5209c92
Show file tree
Hide file tree
Showing 5 changed files with 42 additions and 32 deletions.
23 changes: 13 additions & 10 deletions lib/common_test/doc/guides/run_test_chapter.md
Original file line number Diff line number Diff line change
Expand Up @@ -40,16 +40,19 @@ suites are compiled. If a particular test object directory is specified (meaning
all suites in this directory are to be part of the test), `Common Test` runs
function `make:all/1` in the directory to compile the suites.

If compilation fails for one or more suites, the compilation errors are printed
to tty and the operator is asked if the test run is to proceed without the
missing suites, or be aborted. If the operator chooses to proceed, the tests
having missing suites are noted in the HTML log. If `Common Test` is unable to
prompt the user after compilation failure (if `Common Test` does not control
`stdin`), the test run proceeds automatically without the missing suites. This
behavior can however be modified with the `ct_run` flag
`-abort_if_missing_suites`, or the `ct:run_test/1` option
`{abort_if_missing_suites,TrueOrFalse}`. If `abort_if_missing_suites` is set to
`true`, the test run stops immediately if some suites fail to compile.
If compilation fails for one or more suites, the test run stops
immediately if some suites fail to compile. This behavior can however
be modified with the `ct_run` flag `-abort_if_missing_suites`, or the
`ct:run_test/1` option `{abort_if_missing_suites,TrueOrFalse}`.Option
`abort_if_missing_suites` is set to `true` by default.

If `abort_if_missing_suites` is set to `false`, the compilation errors
are printed to tty and the operator is asked if the test run is to
proceed without the missing suites, or be aborted. If the operator
chooses to proceed, the tests having missing suites are noted in the
HTML log. If `Common Test` is unable to prompt the user after
compilation failure (if `Common Test` does not control `stdin`), the
test run proceeds automatically without the missing suites.

Any help module (that is, regular Erlang module with name not ending with
"\_SUITE") that resides in the same test object directory as a suite, which is
Expand Down
4 changes: 2 additions & 2 deletions lib/common_test/src/ct_run.erl
Original file line number Diff line number Diff line change
Expand Up @@ -307,7 +307,7 @@ script_start1(Parent, Args) ->
AbortIfMissing = get_start_opt(abort_if_missing_suites,
fun([]) -> true;
([Bool]) -> list_to_atom(Bool)
end, false, Args),
end, true, Args),
%% silent connections
SilentConns =
get_start_opt(silent_connections,
Expand Down Expand Up @@ -1036,7 +1036,7 @@ run_test2(StartOpts) ->
end,

%% abort test run if some suites can't be compiled
AbortIfMissing = get_start_opt(abort_if_missing_suites, value, false,
AbortIfMissing = get_start_opt(abort_if_missing_suites, value, true,
StartOpts),

%% decrypt config file
Expand Down
2 changes: 1 addition & 1 deletion lib/common_test/test/ct_error_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,7 @@ no_compile(Config) when is_list(Config) ->
Join = fun(D, S) -> filename:join(D, "error/test/"++S) end,
Suites = [Join(DataDir, "no_compile_SUITE")],
{Opts,ERPid} = setup([{suite,Suites}], Config),
ok = ct_test_support:run(Opts, Config),
{error, {make_failed, _}} = ct_test_support:run(Opts, Config),
Events = ct_test_support:get_events(ERPid, Config),

ct_test_support:log_events(no_compile,
Expand Down
41 changes: 24 additions & 17 deletions lib/common_test/test/ct_surefire_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -151,39 +151,39 @@ run_spec(Case,CTHs,Report,Config,Spec) ->
Test = [{spec,Spec},{ct_hooks,CTHs},{label,Case}],
do_run(Case, Report, Test, Config).

do_run(Case, Report, Test, Config) ->
{Opts,ERPid} = setup(Test, Config),
ok = execute(Case, Opts, ERPid, Config),
do_run(Case, Report, RunTestOpts0, Config) ->
{RunTestOpts,ERPid} = setup(RunTestOpts0, Config),
ok = execute(Case, RunTestOpts, ERPid, Config),
LogDir =
case lists:keyfind(logdir,1,Opts) of
case lists:keyfind(logdir,1,RunTestOpts) of
{logdir,LD} -> LD;
false -> ?config(priv_dir,Config)
end,
Re = filename:join([LogDir,"*",Report]),
check_xml(Case,Re).

setup(Test, Config) ->
setup(RunTestOpts0, Config) ->
Opts0 = ct_test_support:get_opts(Config),
Opts1 =
case lists:keymember(logdir,1,Test) of
case lists:keymember(logdir,1,RunTestOpts0) of
true -> lists:keydelete(logdir,1,Opts0);
false -> Opts0
end,
Level = ?config(trace_level, Config),
EvHArgs = [{cbm,ct_test_support},{trace_level,Level}],
Opts = Opts1 ++ [{event_handler,{?eh,EvHArgs}}|Test],
RunTestOpts = Opts1 ++ [{event_handler,{?eh,EvHArgs}}|RunTestOpts0],
ERPid = ct_test_support:start_event_receiver(Config),
{Opts,ERPid}.
{RunTestOpts,ERPid}.

execute(Name, Opts, ERPid, Config) ->
ok = ct_test_support:run(Opts, Config),
execute(Case, RunTestOpts, ERPid, Config) ->
ok = ct_test_support:run(RunTestOpts, Config),
Events = ct_test_support:get_events(ERPid, Config),
ct_test_support:log_events(Name,
ct_test_support:log_events(Case,
reformat(Events, ?eh),
?config(priv_dir, Config),
Opts),
RunTestOpts),

TestEvents = events_to_check(Name),
TestEvents = events_to_check(Case),
ct_test_support:verify_events(TestEvents, Events, Config).

reformat(Events, EH) ->
Expand Down Expand Up @@ -223,8 +223,8 @@ test_suite_events(pass_SUITE) ->
{?eh,test_stats,{1,0,{0,0}}},
{?eh,tc_start,{ct_framework,end_per_suite}},
{?eh,tc_done,{ct_framework,end_per_suite,ok}}];
test_suite_events(skip_all_surefire_SUITE) ->
[{?eh,tc_user_skip,{skip_all_surefire_SUITE,all,"skipped in spec"}},
test_suite_events(skip_suite_in_spec) ->
[{?eh,tc_user_skip,{surefire_SUITE,all,"skipped in spec"}},
{?eh,test_stats,{0,0,{1,0}}}];
test_suite_events(Test) ->
[{?eh,tc_start,{surefire_SUITE,init_per_suite}},
Expand Down Expand Up @@ -301,7 +301,7 @@ test_events(fail_pre_init_per_suite) ->
[{?eh,stop_logging,[]}];
test_events(skip_suite_in_spec) ->
[{?eh,start_logging,'_'},{?eh,start_info,{1,1,0}}] ++
test_suite_events(skip_all_surefire_SUITE) ++
test_suite_events(skip_suite_in_spec) ++
[{?eh,stop_logging,[]}];
test_events(Test) ->
[{?eh,start_logging,'_'}, {?eh,start_info,{1,1,11}}] ++
Expand Down Expand Up @@ -353,7 +353,14 @@ testsuites(Case,#xmlElement{name=testsuites,content=TS}) ->
testsuite(Case,TS).

testsuite(Case,[#xmlElement{name=testsuite,content=TC,attributes=A}|TS]) ->
TestSuiteEvents = test_suite_events(get_ts_name(A)),
TestSuiteEvents =
test_suite_events(
case Case of
skip_suite_in_spec ->
skip_suite_in_spec;
_ ->
get_ts_name(A)
end),
{ET,EF,ES} = events_to_numbers(lists:flatten(TestSuiteEvents)),
{T,E,F,S} = get_numbers_from_attrs(A,false,false,false,false),
ct:log("Expecting total:~p, error:~p, failure:~p, skipped:~p~n",[ET,0,EF,ES]),
Expand Down
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
{suites,".",[skip_all_surefire_SUITE]}.
{skip_suites,".",skip_all_surefire_SUITE,"skipped in spec"}.
{suites,".",[surefire_SUITE]}.
{skip_suites,".",surefire_SUITE,"skipped in spec"}.

0 comments on commit 5209c92

Please sign in to comment.