Skip to content

Commit

Permalink
common_test: cth surefire skip group fix
Browse files Browse the repository at this point in the history
  • Loading branch information
u3s committed Nov 26, 2024
1 parent 0418c10 commit 48bfbf9
Show file tree
Hide file tree
Showing 2 changed files with 97 additions and 3 deletions.
12 changes: 10 additions & 2 deletions lib/common_test/src/cth_surefire.erl
Original file line number Diff line number Diff line change
Expand Up @@ -249,14 +249,22 @@ on_tc_skip(Suite,{ConfigFunc,_GrName}, Res, State) ->
on_tc_skip(Suite,ConfigFunc, Res, State);
on_tc_skip(Suite,Tc, Res, State0) ->
TcStr = atom_to_list(Tc),
State =
State1 =
case State0#state.test_cases of
[#testcase{name=TcStr}|TCs] ->
State0#state{test_cases=TCs};
_ ->
State0
end,
do_tc_skip(Res, end_tc(Tc,[],Res,init_tc(set_suite(Suite,State),[]))).
State2 = end_tc(Tc,[],Res,init_tc(set_suite(Suite,State1),[])),
State =
case Tc of
end_per_group ->
State2#state{curr_group = tl(State2#state.curr_group)};
_ ->
State2
end,
do_tc_skip(Res, State).

do_tc_skip(Res, State) ->
TCs = State#state.test_cases,
Expand Down
88 changes: 87 additions & 1 deletion lib/common_test/test/ct_surefire_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@
%%%-------------------------------------------------------------------
-module(ct_surefire_SUITE).

-compile(export_all).
-compile([export_all, nowarn_export_all]).

-include_lib("common_test/include/ct.hrl").
-include_lib("common_test/include/ct_event.hrl").
Expand Down Expand Up @@ -75,6 +75,7 @@ all() ->
url,
logdir,
fail_pre_init_per_suite,
skip_init_per_group,
skip_case_in_spec,
skip_suite_in_spec
].
Expand Down Expand Up @@ -122,6 +123,12 @@ fail_pre_init_per_suite(Config) when is_list(Config) ->
run(fail_pre_init_per_suite,[fail_pre_init_per_suite,
{cth_surefire,[{path,Path}]}],Path,Config,[],Suites).

skip_init_per_group(Config) when is_list(Config) ->
DataDir = ?config(data_dir,Config),
Suites = [filename:join(DataDir,"skip_init_per_group_SUITE")],
Path = "skip_group.xml",
run(skip_init_per_group,[{cth_surefire,[{path,Path}]}],Path,Config,[],Suites).

skip_case_in_spec(Config) ->
DataDir = ?config(data_dir,Config),
Spec = filename:join(DataDir,"skip_one_case.spec"),
Expand All @@ -139,10 +146,12 @@ skip_suite_in_spec(Config) ->
%%%-----------------------------------------------------------------
run(Case,CTHs,Report,Config) ->
run(Case,CTHs,Report,Config,[]).

run(Case,CTHs,Report,Config,ExtraOpts) ->
DataDir = ?config(data_dir, Config),
Suite = filename:join(DataDir, "surefire_SUITE"),
run(Case,CTHs,Report,Config,ExtraOpts,Suite).

run(Case,CTHs,Report,Config,ExtraOpts,Suite) ->
Test = [{suite,Suite},{ct_hooks,CTHs},{label,Case}|ExtraOpts],
do_run(Case, Report, Test, Config).
Expand Down Expand Up @@ -226,6 +235,44 @@ test_suite_events(pass_SUITE) ->
test_suite_events(skip_all_surefire_SUITE) ->
[{?eh,tc_user_skip,{skip_all_surefire_SUITE,all,"skipped in spec"}},
{?eh,test_stats,{0,0,{1,0}}}];
test_suite_events(skip_init_per_group_SUITE) ->
[{ct_test_support_eh,tc_start,{ct_framework,init_per_suite}},
{ct_test_support_eh,tc_done,{ct_framework,init_per_suite,ok}},

[{ct_test_support_eh,tc_start,
{skip_init_per_group_SUITE,{init_per_group,root,[]}}},
{ct_test_support_eh,tc_done,
{skip_init_per_group_SUITE,{init_per_group,root,[]},ok}},
[{ct_test_support_eh,tc_start,
{skip_init_per_group_SUITE,{init_per_group,left,[]}}},
{ct_test_support_eh,tc_done,
{skip_init_per_group_SUITE,
{init_per_group,left,[]},
{skipped,skip_on_purpose}}},
{ct_test_support_eh,tc_user_skip,
{skip_init_per_group_SUITE,{test_case,left},skip_on_purpose}},
{ct_test_support_eh,test_stats,{0,0,{1,0}}},
{ct_test_support_eh,tc_user_skip,
{skip_init_per_group_SUITE,{end_per_group,left},skip_on_purpose}}],

[{ct_test_support_eh,tc_start,
{skip_init_per_group_SUITE,{init_per_group,right,[]}}},
{ct_test_support_eh,tc_done,
{skip_init_per_group_SUITE,{init_per_group,right,[]},ok}},
{ct_test_support_eh,tc_start,{skip_init_per_group_SUITE,test_case}},
{ct_test_support_eh,tc_done,{skip_init_per_group_SUITE,test_case,ok}},
{ct_test_support_eh,test_stats,{1,0,{1,0}}},
{ct_test_support_eh,tc_start,
{skip_init_per_group_SUITE,{end_per_group,right,[]}}},
{ct_test_support_eh,tc_done,
{skip_init_per_group_SUITE,{end_per_group,right,[]},ok}}],
{ct_test_support_eh,tc_start,
{skip_init_per_group_SUITE,{end_per_group,root,[]}}},
{ct_test_support_eh,tc_done,
{skip_init_per_group_SUITE,{end_per_group,root,[]},ok}}],

{ct_test_support_eh,tc_start,{ct_framework,end_per_suite}},
{ct_test_support_eh,tc_done,{ct_framework,end_per_suite,ok}}];
test_suite_events(Test) ->
[{?eh,tc_start,{surefire_SUITE,init_per_suite}},
{?eh,tc_done,{surefire_SUITE,init_per_suite,ok}},
Expand Down Expand Up @@ -303,6 +350,10 @@ test_events(skip_suite_in_spec) ->
[{?eh,start_logging,'_'},{?eh,start_info,{1,1,0}}] ++
test_suite_events(skip_all_surefire_SUITE) ++
[{?eh,stop_logging,[]}];
test_events(skip_init_per_group) ->
[{?eh,start_logging,'_'},{?eh,start_info,{1,1,2}}] ++
test_suite_events(skip_init_per_group_SUITE) ++
[{?eh,stop_logging,[]}];
test_events(Test) ->
[{?eh,start_logging,'_'}, {?eh,start_info,{1,1,11}}] ++
test_suite_events(Test) ++
Expand Down Expand Up @@ -404,6 +455,41 @@ failed_or_skipped([#xmlElement{name=skipped}|E]) ->
failed_or_skipped([]) ->
[].

assert_lines(skip_init_per_group, A) ->
Name = lists:keyfind(name,#xmlAttribute.name,A),
Group = lists:keyfind(group,#xmlAttribute.name,A),
VerifyFun =
fun ("init_per_group", [{testcase,2}, {testsuite,1}, {testsuites,1}], "root") ->
ok;
("init_per_group", [{testcase,3}, {testsuite,1}, {testsuites,1}], "root.left") ->
ok;
("test_case", [{testcase,4}, {testsuite,1}, {testsuites,1}], "root.left") ->
ok;
("end_per_group", [{testcase,5}, {testsuite,1}, {testsuites,1}], "root.left") ->
ok;
("init_per_group", [{testcase,6}, {testsuite,1}, {testsuites,1}], "root.right") ->
ok;
("test_case", [{testcase,7}, {testsuite,1}, {testsuites,1}], "root.right") ->
ok;
("end_per_group", [{testcase,8}, {testsuite,1}, {testsuites,1}], "root.right") ->
ok;
("end_per_group", [{testcase,9}, {testsuite,1}, {testsuites,1}], "root") ->
ok;
(Tc, TcParents, TcGroupPath) ->
exit({wrong_grouppath, [{tc, Tc},
{tc_parents, TcParents},
{tc_group_path, TcGroupPath}]})
end,
case is_record(Group, xmlAttribute) of
true ->
Tc = Name#xmlAttribute.value,
TcParents = Group#xmlAttribute.parents,
TcGroupPath = Group#xmlAttribute.value,
VerifyFun(Tc, TcParents, TcGroupPath),
ok;
_ ->
ok
end;
assert_lines(Case, A) when Case =/= fail_pre_init_per_suite,
Case =/= skip_case_in_spec,
Case =/= skip_suite_in_spec ->
Expand Down

0 comments on commit 48bfbf9

Please sign in to comment.