File 4886-ct-apply-review-comments.patch of Package erlang
From abde78fc4f7b57915ce491b42053f51c601dd06b Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Tue, 18 Jul 2023 11:33:08 +0200
Subject: [PATCH 6/6] ct: apply review comments
- support ct_hooks_order only in cmd line, spec and suite/0
---
lib/common_test/doc/src/ct_hooks_chapter.xml | 28 +++---
lib/common_test/doc/src/ct_suite.xml | 6 +-
lib/common_test/internal_doc/ct_notes.md | 9 +-
lib/common_test/src/ct_hooks.erl | 50 +++--------
lib/common_test/test/ct_hooks_SUITE.erl | 87 +++----------------
.../cth/tests/ct_hooks_order_a_cth.erl | 13 +--
.../cth/tests/ct_hooks_order_b_cth.erl | 11 ++-
.../ct_hooks_order_config_group_SUITE.erl | 71 ---------------
.../tests/ct_hooks_order_config_ipg_SUITE.erl | 71 ---------------
.../cth/tests/ct_hooks_order_test_SUITE.erl | 7 ++
10 files changed, 74 insertions(+), 279 deletions(-)
delete mode 100644 lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_group_SUITE.erl
delete mode 100644 lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_ipg_SUITE.erl
diff --git a/lib/common_test/doc/src/ct_hooks_chapter.xml b/lib/common_test/doc/src/ct_hooks_chapter.xml
index 78678c0ebe..ca8c0d2e0e 100644
--- a/lib/common_test/doc/src/ct_hooks_chapter.xml
+++ b/lib/common_test/doc/src/ct_hooks_chapter.xml
@@ -118,28 +118,32 @@
<section>
<marker id="cth_execution_order"/>
<title>CTH Execution Order</title>
- <p>By default, each CTH installed is executed in the order that
+ <p>By default, each installed CTH is executed in the order in which
they are installed for init calls, and then reversed for end
- calls. This order can be referred as test centric, as order is
- reversed after testcase is executed and corresponds to default
- value <c>test</c> of <c>ct_hooks_order</c> option.</p>
- <p>Installation based order is not always
+ calls. This order can be referred to as test-centric, as the order is
+ reversed after a testcase is executed and corresponds to the default
+ value (<c>test</c>) of <c>ct_hooks_order</c> option.</p>
+ <p>The installation-based order is not always
desired, so <c>Common Test</c> allows the user to specify a
- priority for each hook. The priority can either be specified in
+ priority for each hook. The priority can be specified in
the CTH function <seemfa
marker="ct_hooks#Module:init/2">init/2</seemfa> or when
installing the hook. The priority specified at installation
overrides the priority returned by the CTH.</p>
- <p>In some cases, reversed order for all end calls is not
- desired and instead user might prefer reversed order for post
- hook calls. Such behavior can be enabled with
- <c>ct_hooks_order</c> option with <c>config</c> value. When
- option is enabled, execution order is configuration centric, as
+ <p>In some cases, the reversed order for all end calls is not
+ desired, and instead, the user might prefer the reversed order
+ for post hook calls. Such behavior can be enabled with
+ <c>ct_hooks_order</c> option with <c>config</c> value. When this
+ option is enabled, the execution order is configuration-centric, as
the reversed order happens after each configuration function and
not in relation to testcase.</p>
- <p>Note that <c>ct_hooks_order</c> option is considered as a
+ <p>Note that the <c>ct_hooks_order</c> option is considered as a
global framework setting. In case when option is configured
multiple times framework with process only the first value.</p>
+ <p>The <c>ct_hooks_order</c> option can be set as: <c>ct_run</c>
+ argument, in test specification or <seemfa
+ marker="ct_suite#Module:suite/0">suite/0</seemfa> return
+ value.</p>
</section>
</section>
diff --git a/lib/common_test/doc/src/ct_suite.xml b/lib/common_test/doc/src/ct_suite.xml
index 4c99181e2c..3713d78f7a 100644
--- a/lib/common_test/doc/src/ct_suite.xml
+++ b/lib/common_test/doc/src/ct_suite.xml
@@ -293,7 +293,7 @@
subgroups).</fsummary>
<type>
<v>GroupName = <seetype marker="#ct_groupname">ct_groupname()</seetype></v>
- <v><seetype marker="#ct_info">ct_info()</seetype> = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} | {ct_hooks_order, CTHOrder}</v>
+ <v><seetype marker="#ct_info">ct_info()</seetype> = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs}</v>
<v>Time = TimeVal | TimeFunc</v>
<v>TimeVal = MilliSec | {seconds, integer()} | {minutes, integer()} | {hours, integer()}</v>
<v>TimeFunc = {Mod, Func, Args} | Fun</v>
@@ -316,7 +316,6 @@
<v>CTHModule = atom()</v>
<v>CTHInitArgs = term()</v>
<v>CTHPriority = integer()</v>
- <v>CTHOrder = test | config</v>
</type>
<desc>
@@ -499,7 +498,7 @@
<name since="OTP R14B">Module:Testcase() -> [ct_info()] </name>
<fsummary>Test case information function.</fsummary>
<type>
- <v><seetype marker="#ct_info">ct_info()</seetype> = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} | {ct_hooks_order, CTHOrder}</v>
+ <v><seetype marker="#ct_info">ct_info()</seetype> = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs}</v>
<v>Time = TimeVal | TimeFunc</v>
<v>TimeVal = MilliSec | {seconds, integer()} | {minutes, integer()} | {hours, integer()}</v>
<v>TimeFunc = {Mod, Func, Args} | Fun</v>
@@ -522,7 +521,6 @@
<v>CTHModule = atom()</v>
<v>CTHInitArgs = term()</v>
<v>CTHPriority = integer()</v>
- <v>CTHOrder = test | config</v>
</type>
<desc>
diff --git a/lib/common_test/internal_doc/ct_notes.md b/lib/common_test/internal_doc/ct_notes.md
index a72c396663..061e4d2cdb 100644
--- a/lib/common_test/internal_doc/ct_notes.md
+++ b/lib/common_test/internal_doc/ct_notes.md
@@ -40,22 +40,25 @@ flowchart TD
pre_ipt_B["(B) pre_init_per_testcase"] --Config--> ipt[/"init_per_testcase"/]
end
ipt --Config,Return--> post_ipt_A
+ ipt --Config--> post_ipt_B
subgraph hooks
- post_ipt_A["(A) post_init_per_testcase"] --Config,Return--> post_ipt_B
+ post_ipt_A["(A) post_init_per_testcase"] --Return--> post_ipt_B
end
subgraph suite
post_ipt_B["(B) post_init_per_testcase"] --Config--> testcase
testcase((("Testcase")))
end
subgraph hooks
- testcase --Config,Return--> pre_ept_B
- pre_ept_B["(B) pre_end_per_testcase"] --Config,Return--> pre_ept_A
+ testcase --tc_status--> pre_ept_B
+ pre_ept_B["(B) pre_end_per_testcase"] --Config--> pre_ept_A
end
subgraph suite
pre_ept_A["(A) pre_end_per_testcase"] --Config--> end_per_test_case
end
subgraph hooks
end_per_test_case[/"end_per_testcase"/] --Config,Return--> post_ept_B
+ post_ept_B[/"(B) post_end_per_testcase"/] --Return--> post_ept_A[/"(A) post_end_per_testcase"/]
+ end_per_test_case --Config--> post_ept_A
end
```
#### Configuration centric (option candidate)
diff --git a/lib/common_test/src/ct_hooks.erl b/lib/common_test/src/ct_hooks.erl
index 6144b2458c..d182e08efc 100644
--- a/lib/common_test/src/ct_hooks.erl
+++ b/lib/common_test/src/ct_hooks.erl
@@ -160,15 +160,13 @@ init_tc(Mod, TC = error_in_suite, Config) ->
{fail, Reason :: term()} |
ok | '$ct_no_change'.
-end_tc(Mod, CFunc = init_per_suite, Config, _Result, Return) ->
- process_hooks_order(CFunc, Return),
+end_tc(Mod, init_per_suite, Config, _Result, Return) ->
call(fun call_generic/3, Return, [post_init_per_suite, Mod, Config],
'$ct_no_change');
end_tc(Mod, end_per_suite, Config, Result, _Return) ->
call(fun call_generic/3, Result, [post_end_per_suite, Mod, Config],
'$ct_no_change');
-end_tc(Mod, {CFunc = init_per_group, GroupName, _}, Config, _Result, Return) ->
- process_hooks_order(CFunc, Return),
+end_tc(Mod, {init_per_group, GroupName, _}, Config, _Result, Return) ->
call(fun call_generic_fallback/3, Return,
[post_init_per_group, Mod, GroupName, Config], '$ct_no_change');
end_tc(Mod, {end_per_group, GroupName, Properties}, Config, Result, _Return) ->
@@ -291,7 +289,7 @@ call([{Hook, call_id, NextFun} | Rest], Config, Meta, Hooks) ->
{Hooks ++ [NewHook],
Rest ++ [{NewId, call_init}, {NewId,NextFun}]}
end,
- {_, Order} = get_hooks_order(),
+ Order = get_hooks_order(),
call(resort(NewRest, NewHooks, Meta, Order), Config, Meta,
NewHooks)
catch Error:Reason:Trace ->
@@ -308,9 +306,7 @@ call([{HookId, Fun} | Rest], Config, Meta, Hooks) ->
{NewConf, NewHook} = Fun(Hook, Config, Meta),
NewCalls = get_new_hooks(NewConf, Fun),
NewHooks = lists:keyreplace(HookId, #ct_hook_config.id, Hooks, NewHook),
- %% FIXME - not needed, but maybe logical?
- %% process_hooks_order(NewConf),
- {_, Order} = get_hooks_order(),
+ Order = get_hooks_order(),
call(resort(NewCalls ++ Rest, NewHooks,
Meta, Order), %% Resort if call_init changed prio
remove([?hooks_name, ?hooks_order_name], NewConf), Meta,
@@ -321,7 +317,6 @@ call([{HookId, Fun} | Rest], Config, Meta, Hooks) ->
end;
call([], Config, _Meta, Hooks) ->
save_suite_data_async(Hooks),
- %% process_hooks_order([{?hooks_order_name, HooksOrder}]),
Config.
remove([], List) when is_list(List) ->
@@ -536,44 +531,25 @@ catch_apply(M,F,A) ->
[M,F,length(A)]))})
end.
-process_hooks_order(Stage = init, Return) when is_list(Return) ->
- maybe_save_hooks_order(Stage, Return);
-process_hooks_order(Stage, Return) when is_list(Return) ->
- {StoredStage, StoredOrder0} = get_hooks_order(),
- DeleteConditions =
- [{pre_end_per_suite, init_per_group},
- {pre_end_per_suite, pre_init_per_group},
- {pre_end_per_group, pre_init_per_testcase}],
- StoredOrder =
- case lists:member({Stage, StoredStage}, DeleteConditions) of
- true->
- ct_util:delete_suite_data(?hooks_order_name),
- undefined;
- _ ->
- StoredOrder0
- end,
- case StoredOrder of
+process_hooks_order(init, Return) when is_list(Return) ->
+ maybe_save_hooks_order(Return);
+process_hooks_order(_Stage, Return) when is_list(Return) ->
+ case get_hooks_order() of
undefined ->
- maybe_save_hooks_order(Stage, Return);
- _ ->
+ maybe_save_hooks_order(Return);
+ StoredOrder ->
StoredOrder
end;
process_hooks_order(_Stage, _) ->
nothing_to_save.
get_hooks_order() ->
- Value = ct_util:read_suite_data(?hooks_order_name),
- case Value of
- undefined ->
- {undefined, undefined};
- {_, _} ->
- Value
- end.
+ ct_util:read_suite_data(?hooks_order_name).
-maybe_save_hooks_order(Stage, Return) ->
+maybe_save_hooks_order(Return) ->
case proplists:get_value(?hooks_order_name, Return) of
Order when Order == config ->
- ct_util:save_suite_data_async(?hooks_order_name, {Stage, Order}),
+ ct_util:save_suite_data_async(?hooks_order_name, Order),
Order;
_ ->
test
diff --git a/lib/common_test/test/ct_hooks_SUITE.erl b/lib/common_test/test/ct_hooks_SUITE.erl
index 0e77f37eb9..a59bc3bd5a 100644
--- a/lib/common_test/test/ct_hooks_SUITE.erl
+++ b/lib/common_test/test/ct_hooks_SUITE.erl
@@ -106,8 +106,7 @@ all(suite) ->
skip_post_suite_cth, recover_post_suite_cth, update_config_cth,
update_config_cth2,
ct_hooks_order_test_cth, ct_hooks_order_config_suite_cth,
- ct_hooks_order_config_group_cth,
- ct_hooks_order_config_ips_cth, ct_hooks_order_config_ipg_cth,
+ ct_hooks_order_config_ips_cth,
state_update_cth, update_result_cth, options_cth, same_id_cth,
fail_n_skip_with_minimal_cth, prio_cth, no_config,
no_init_suite_config, no_init_config, no_end_config,
@@ -251,18 +250,10 @@ ct_hooks_order_config_suite_cth(Config) when is_list(Config) ->
do_test(ct_hooks_order_config_suite_cth, "ct_hooks_order_config_suite_SUITE.erl",
[ct_hooks_order_a_cth, ct_hooks_order_b_cth],Config).
-ct_hooks_order_config_group_cth(Config) when is_list(Config) ->
- do_test(ct_hooks_order_config_group_cth, "ct_hooks_order_config_group_SUITE.erl",
- [ct_hooks_order_a_cth, ct_hooks_order_b_cth],Config).
-
ct_hooks_order_config_ips_cth(Config) when is_list(Config) ->
do_test(ct_hooks_order_config_ips_cth, "ct_hooks_order_config_ips_SUITE.erl",
[ct_hooks_order_a_cth, ct_hooks_order_b_cth],Config).
-ct_hooks_order_config_ipg_cth(Config) when is_list(Config) ->
- do_test(ct_hooks_order_config_ipg_cth, "ct_hooks_order_config_ipg_SUITE.erl",
- [ct_hooks_order_a_cth, ct_hooks_order_b_cth],Config).
-
state_update_cth(Config) when is_list(Config) ->
do_test(state_update_cth, "ct_cth_fail_one_skip_one_SUITE.erl",
[state_update_cth,state_update_cth],Config).
@@ -1372,11 +1363,10 @@ test_events(ct_hooks_order_test_cth) ->
{pre_ipt_2, [pre_ipt_a], pre_ipt_1},
{post_ipt_1, [ipt, pre_ipt_b], pre_ipt_2},
{post_ipt_2, [post_ipt_a], post_ipt_1},
+
%% "Test centric" (default mode) end functions
%% Pivot point (testcase) after which hook order is reversed (B hook executed as 1st)
- {pre_ept_1, [post_ipt_b], post_ipt_1},
- %% FIXME-1 line below should work instead of line above, maybe bug?
- %% {pre_ept_1, [post_ipt_b], post_ipt_2},
+ {pre_ept_1, [post_ipt_b], post_ipt_2},
{pre_ept_2, [pre_ept_b], pre_ept_1},
{post_ept_1, [pre_ept_a], pre_ept_2},
{post_ept_2, [post_ept_b], post_ept_1},
@@ -1387,9 +1377,7 @@ test_events(ct_hooks_order_test_cth) ->
{pre_eps_1, [], post_ips_2},
{pre_eps_2, [pre_eps_b], pre_eps_1},
{post_eps_1, [pre_eps_a], pre_eps_2},
- {post_eps_2, [post_eps_b], post_eps_1},
- {term_1, [post_eps_a], post_eps_1},
- {term_2, [post_eps_b], post_eps_1}
+ {post_eps_2, [post_eps_b], post_eps_1}
],
hooks_order_events_helper(Suite, Recipe);
test_events(TC) when TC == ct_hooks_order_config_suite_cth;
@@ -1403,74 +1391,34 @@ test_events(TC) when TC == ct_hooks_order_config_suite_cth;
Recipe =
[{pre_ips_1, [], []},
{pre_ips_2, [pre_ips_a], []},
- {post_ips_1, [ips, pre_ips_b], pre_ips_2},
%% "Config centric" post functions have reversed execution order (B hook executed 1st)
+ {post_ips_1, [ips, pre_ips_b], pre_ips_2},
{post_ips_2, [post_ips_b], post_ips_1},
+
{pre_ipg_1, [post_ips_a], post_ips_2},
{pre_ipg_2, [pre_ipg_a], pre_ipg_1},
{post_ipg_1, [ipg, pre_ipg_b], pre_ipg_2},
{post_ipg_2, [post_ipg_b], post_ipg_1},
+
{pre_ipt_1, [post_ipg_a], post_ipg_2},
{pre_ipt_2, [pre_ipt_a], pre_ipt_1},
{post_ipt_1, [ipt, pre_ipt_b], pre_ipt_2},
{post_ipt_2, [post_ipt_b], post_ipt_1},
- {pre_ept_1, [post_ipt_a], post_ipt_1},
- %% FIXME-1 line below should work instead of line above, maybe bug?
- %% {pre_ept_1, [post_ipt_b], post_ipt_2},
+
+ {pre_ept_1, [post_ipt_a], post_ipt_2},
{pre_ept_2, [pre_ept_a], pre_ept_1},
{post_ept_1, [pre_ept_b], pre_ept_2},
{post_ept_2, [post_ept_b], post_ept_1},
+
{pre_epg_1, [], pre_ipt_1},
{pre_epg_2, [pre_epg_a], pre_epg_1},
{post_epg_1, [pre_epg_b], pre_epg_2},
{post_epg_2, [post_epg_b], post_epg_1},
+
{pre_eps_1, [], post_ips_2},
{pre_eps_2, [pre_eps_a], pre_eps_1},
{post_eps_1, [pre_eps_b], pre_eps_2},
- {post_eps_2, [post_eps_b], post_eps_1},
- {term_1, [post_eps_a], post_eps_1},
- {term_2, [post_eps_b], post_eps_1}
- ],
- hooks_order_events_helper(Suite, Recipe);
-test_events(TC) when TC == ct_hooks_order_config_ipg_cth;
- TC == ct_hooks_order_config_group_cth ->
- Suite = case TC of
- ct_hooks_order_config_group_cth ->
- ct_hooks_order_config_group_SUITE;
- _ ->
- ct_hooks_order_config_ipg_SUITE
- end,
- Recipe =
- [{pre_ips_1, [], []},
- {pre_ips_2, [pre_ips_a], []},
- {post_ips_1, [ips, pre_ips_b], pre_ips_2},
- {post_ips_2, [post_ips_a], post_ips_1},
- {pre_ipg_1, [post_ips_b], post_ips_2},
- {pre_ipg_2, [pre_ipg_a], pre_ipg_1},
- %% "Config centric" post functions have reversed execution order (B hook executed 1st)
- %% order option in init_per_group
- {post_ipg_1, [ipg, pre_ipg_b], pre_ipg_2},
- {post_ipg_2, [post_ipg_b], post_ipg_1},
- {pre_ipt_1, [post_ipg_a], post_ipg_2},
- {pre_ipt_2, [pre_ipt_a], pre_ipt_1},
- {post_ipt_1, [ipt, pre_ipt_b], pre_ipt_2},
- {post_ipt_2, [post_ipt_b], post_ipt_1},
- {pre_ept_1, [post_ipt_a], post_ipt_1},
- %% FIXME-1 line below should work instead of line above, maybe bug?
- %% {pre_ept_1, [post_ipt_b], post_ipt_2},
- {pre_ept_2, [pre_ept_a], pre_ept_1},
- {post_ept_1, [pre_ept_b], pre_ept_2},
- {post_ept_2, [post_ept_b], post_ept_1},
- {pre_epg_1, [], pre_ipt_1},
- {pre_epg_2, [pre_epg_a], pre_epg_1},
- {post_epg_1, [pre_epg_b], pre_epg_2},
- {post_epg_2, [post_epg_b], post_epg_1},
- {pre_eps_1, [], post_ips_2},
- {pre_eps_2, [pre_eps_b], pre_eps_1},
- {post_eps_1, [pre_eps_a], pre_eps_2},
- {post_eps_2, [post_eps_a], post_eps_1},
- {term_1, [post_eps_a], post_eps_1},
- {term_2, [post_eps_b], post_eps_1}
+ {post_eps_2, [post_eps_b], post_eps_1}
],
hooks_order_events_helper(Suite, Recipe);
test_events(state_update_cth) ->
@@ -3179,13 +3127,13 @@ hooks_order_events_helper(Suite, Recipe) ->
?cth_event4(pre_init_per_testcase, Suite, test_case, contains(V(pre_ipt_1, M))),
?cth_event4(pre_init_per_testcase, Suite, test_case, contains(V(pre_ipt_2, M))),
?cth_event5(post_init_per_testcase, Suite, test_case,
- contains(V(post_ipt_1, M)), ok), %% FIXME why ok on last argument here?
+ contains(V(post_ipt_1, M)), ok),
?cth_event5(post_init_per_testcase, Suite, test_case,
'$proplist', contains(V(post_ipt_2, M))),
?cth_event4(pre_end_per_testcase, Suite, test_case, contains(V(pre_ept_1, M))),
?cth_event4(pre_end_per_testcase, Suite, test_case, contains(V(pre_ept_2, M))),
?cth_event5(post_end_per_testcase, Suite, test_case,
- contains(V(post_ept_1, M)), ok), %% FIXME why ok on last argument here?
+ contains(V(post_ept_1, M)), ok),
?cth_event5(post_end_per_testcase, Suite, test_case,
'$proplist', contains(V(post_ept_2, M))),
{?eh,tc_done,{Suite,test_case,ok}},
@@ -3208,12 +3156,5 @@ hooks_order_events_helper(Suite, Recipe) ->
?cth_event4(post_end_per_suite, Suite, '$proplist', contains(V(post_eps_1, M))),
{?eh,tc_done,{Suite,end_per_suite,ok}},
{?eh,test_done,{'DEF','STOP_TIME'}},
- %% FIXME-2 why terminate callbacks receive only one post_end_per_suite?
- {?eh,cth,{'_', terminate,
- [contains(V(term_1, M))]}},
- %% [contains([post_eps_a] ++ ConfigBPostEndPerSuite)]}},
- {?eh,cth,{'_', terminate,
- [contains(V(term_2, M))]}},
- %% [contains([post_eps_b] ++ ConfigBPostEndPerSuite)]}},
{?eh,stop_logging,[]}
].
diff --git a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_a_cth.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_a_cth.erl
index dba08bd1aa..ddb829dcbb 100644
--- a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_a_cth.erl
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_a_cth.erl
@@ -18,7 +18,6 @@
%% %CopyrightEnd%
%%
-
-module(ct_hooks_order_a_cth).
-include_lib("common_test/src/ct_util.hrl").
@@ -47,9 +46,7 @@ pre_end_per_suite(Suite,Config,State) ->
post_end_per_suite(Suite,Config,Return,State) ->
empty_cth:post_end_per_suite(Suite,Config,Return,?ADD_LOC(State)),
- %% FIXME what is the purpose of code below, why it's different
- NewConfig = [{post_eps_a,?now}|Config],
- {NewConfig,NewConfig}.
+ {[{post_eps_a,?now}|Config],State}.
pre_init_per_group(Suite, Group,Config,State) ->
empty_cth:pre_init_per_group(Suite,Group,Config,?ADD_LOC(State)),
@@ -73,7 +70,13 @@ pre_init_per_testcase(Suite,TC,Config,State) ->
post_init_per_testcase(Suite,TC,Config,Return,State) ->
empty_cth:post_init_per_testcase(Suite,TC,Config,Return,?ADD_LOC(State)),
- {[{post_ipt_a,?now}|Config],State}.
+ Data = case Return of
+ ok ->
+ Config;
+ Return when is_list(Return) ->
+ Return
+ end,
+ {[{post_ipt_a,?now}|Data],State}.
pre_end_per_testcase(Suite,TC,Config,State) ->
empty_cth:pre_end_per_testcase(Suite,TC,Config,?ADD_LOC(State)),
diff --git a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_b_cth.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_b_cth.erl
index ff422865d2..f8aba2fc10 100644
--- a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_b_cth.erl
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_b_cth.erl
@@ -47,8 +47,7 @@ pre_end_per_suite(Suite,Config,State) ->
post_end_per_suite(Suite,Config,Return,State) ->
empty_cth:post_end_per_suite(Suite,Config,Return,?ADD_LOC(State)),
- NewConfig = [{post_eps_b,?now}|Config],
- {NewConfig,NewConfig}.
+ {[{post_eps_b,?now}|Config],State}.
pre_init_per_group(Suite, Group,Config,State) ->
empty_cth:pre_init_per_group(Suite,Group,Config,?ADD_LOC(State)),
@@ -72,7 +71,13 @@ pre_init_per_testcase(Suite,TC,Config,State) ->
post_init_per_testcase(Suite,TC,Config,Return,State) ->
empty_cth:post_init_per_testcase(Suite,TC,Config,Return,?ADD_LOC(State)),
- {[{post_ipt_b,?now}|Config],State}.
+ Data = case Return of
+ ok ->
+ Config;
+ Return when is_list(Return) ->
+ Return
+ end,
+ {[{post_ipt_b,?now}|Data],State}.
pre_end_per_testcase(Suite,TC,Config,State) ->
empty_cth:pre_end_per_testcase(Suite,TC,Config,?ADD_LOC(State)),
diff --git a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_group_SUITE.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_group_SUITE.erl
deleted file mode 100644
index 978ed735e8..0000000000
--- a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_group_SUITE.erl
+++ /dev/null
@@ -1,71 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2023. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%% http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-%%
-
--module(ct_hooks_order_config_group_SUITE).
-
--suite_defaults([{timetrap, {minutes, 10}}]).
-
-%% Note: This directive should only be used in test suites.
--compile([export_all, nowarn_export_all]).
-
--include("ct.hrl").
-
--define(now, ct_test_support:unique_timestamp()).
-
-group(group1) ->
- [{ct_hooks_order, config}].
-
-%% Test server callback functions
-init_per_suite(Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- [{ips, ?now} | Config].
-
-end_per_suite(Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- %% result from end functions is not provided to any other callback
- Config.
-
-init_per_testcase(_TestCase, Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- [{ipt, ?now} | Config].
-
-end_per_testcase(_TestCase, Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- %% result from end functions is not provided to any other callback
- Config.
-
-init_per_group(_GroupName, Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- [{ipg, ?now} | Config].
-
-end_per_group(_GroupName, Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- %% result from end functions is not provided to any other callback
- Config.
-
-all() ->
- [{group,group1}].
-
-groups() ->
- [{group1,[],[test_case]}].
-
-test_case(Config) when is_list(Config) ->
- ok.
-
diff --git a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_ipg_SUITE.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_ipg_SUITE.erl
deleted file mode 100644
index ce181459ad..0000000000
--- a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_ipg_SUITE.erl
+++ /dev/null
@@ -1,71 +0,0 @@
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2023. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%% http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-%%
-
--module(ct_hooks_order_config_ipg_SUITE).
-
--suite_defaults([{timetrap, {minutes, 10}}]).
-
-%% Note: This directive should only be used in test suites.
--compile([export_all, nowarn_export_all]).
-
--include("ct.hrl").
-
--define(now, ct_test_support:unique_timestamp()).
-
-suite() ->
- [].
-
-%% Test server callback functions
-init_per_suite(Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- [{ips, ?now} | Config].
-
-end_per_suite(Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- %% result from end functions is not provided to any other callback
- Config.
-
-init_per_testcase(_TestCase, Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- [{ipt, ?now} | Config].
-
-end_per_testcase(_TestCase, Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- %% result from end functions is not provided to any other callback
- Config.
-
-init_per_group(_GroupName, Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- [{ipg, ?now}, {ct_hooks_order, config} | Config].
-
-end_per_group(_GroupName, Config) ->
- undefined = proplists:get_value(ct_hooks_order, Config),
- %% result from end functions is not provided to any other callback
- Config.
-
-all() ->
- [{group,group1}].
-
-groups() ->
- [{group1,[],[test_case]}].
-
-test_case(Config) when is_list(Config) ->
- ok.
-
diff --git a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_test_SUITE.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_test_SUITE.erl
index 8270f4e3af..13b92ea8e7 100644
--- a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_test_SUITE.erl
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_test_SUITE.erl
@@ -34,23 +34,29 @@ suite() ->
%% Test server callback functions
init_per_suite(Config) ->
+ undefined = proplists:get_value(ct_hooks_order, Config),
[{ips, ?now} | Config].
end_per_suite(Config) ->
+ undefined = proplists:get_value(ct_hooks_order, Config),
%% result from end functions is not provided to any other callback
Config.
init_per_testcase(_TestCase, Config) ->
+ undefined = proplists:get_value(ct_hooks_order, Config),
[{ipt, ?now} | Config].
end_per_testcase(_TestCase, Config) ->
+ undefined = proplists:get_value(ct_hooks_order, Config),
%% result from end functions is not provided to any other callback
Config.
init_per_group(_GroupName, Config) ->
+ undefined = proplists:get_value(ct_hooks_order, Config),
[{ipg, ?now} | Config].
end_per_group(_GroupName, Config) ->
+ undefined = proplists:get_value(ct_hooks_order, Config),
%% result from end functions is not provided to any other callback
Config.
@@ -61,5 +67,6 @@ groups() ->
[{group1,[],[test_case]}].
test_case(Config) when is_list(Config) ->
+ undefined = proplists:get_value(ct_hooks_order, Config),
ok.
--
2.35.3