File 4884-ct-ct_hooks_order-option-tests.patch of Package erlang
From 2322dc23c322b87d9ffa8f876c44fd22457eb8dd Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Wed, 12 Jul 2023 14:21:30 +0200
Subject: [PATCH 4/6] ct: ct_hooks_order option tests
---
lib/common_test/test/ct_hooks_SUITE.erl | 240 +++++++++++++++++-
.../cth/tests/ct_hooks_order_a_cth.erl | 93 +++++++
.../cth/tests/ct_hooks_order_b_cth.erl | 92 +++++++
.../ct_hooks_order_config_group_SUITE.erl | 71 ++++++
.../tests/ct_hooks_order_config_ipg_SUITE.erl | 71 ++++++
.../tests/ct_hooks_order_config_ips_SUITE.erl | 71 ++++++
.../ct_hooks_order_config_suite_SUITE.erl | 71 ++++++
.../cth/tests/ct_hooks_order_test_SUITE.erl | 65 +++++
.../cth/tests/update_config_cth.erl | 4 +-
lib/common_test/test/ct_testspec_2_SUITE.erl | 6 +-
10 files changed, 777 insertions(+), 7 deletions(-)
create mode 100644 lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_a_cth.erl
create mode 100644 lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_b_cth.erl
create mode 100644 lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_group_SUITE.erl
create mode 100644 lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_ipg_SUITE.erl
create mode 100644 lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_ips_SUITE.erl
create mode 100644 lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_suite_SUITE.erl
create mode 100644 lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_test_SUITE.erl
diff --git a/lib/common_test/test/ct_hooks_SUITE.erl b/lib/common_test/test/ct_hooks_SUITE.erl
index 63ff69eef8..0e77f37eb9 100644
--- a/lib/common_test/test/ct_hooks_SUITE.erl
+++ b/lib/common_test/test/ct_hooks_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2009-2021. All Rights Reserved.
+%% Copyright Ericsson AB 2009-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.
@@ -35,7 +35,15 @@
-include_lib("kernel/src/logger_internal.hrl").
-define(eh, ct_test_support_eh).
-
+-define(cth_event3(CALLBACK, SUITE, VAR1),
+ {?eh, cth, {'_', CALLBACK,
+ [SUITE, VAR1, '_']}}).
+-define(cth_event4(CALLBACK, SUITE, VAR1, VAR2),
+ {?eh, cth, {'_', CALLBACK,
+ [SUITE, VAR1, VAR2, '_']}}).
+-define(cth_event5(CALLBACK, SUITE, VAR1, VAR2, VAR3),
+ {?eh, cth, {'_', CALLBACK,
+ [SUITE, VAR1, VAR2, VAR3, '_']}}).
%%--------------------------------------------------------------------
%% TEST SERVER CALLBACK FUNCTIONS
%%--------------------------------------------------------------------
@@ -95,7 +103,11 @@ all(suite) ->
fail_pre_suite_cth, double_fail_pre_suite_cth,
fail_post_suite_cth, skip_pre_suite_cth, skip_pre_end_cth,
skip_pre_init_tc_cth, fail_post_init_tc_cth,
- skip_post_suite_cth, recover_post_suite_cth, update_config_cth, update_config_cth2,
+ 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,
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,
@@ -231,6 +243,26 @@ update_config_cth2(Config) when is_list(Config) ->
do_test(update_config_cth2, "ct_update_config_SUITE2.erl",
[update_config_cth],Config).
+ct_hooks_order_test_cth(Config) when is_list(Config) ->
+ do_test(ct_hooks_order_test_cth, "ct_hooks_order_test_SUITE.erl",
+ [ct_hooks_order_a_cth, ct_hooks_order_b_cth],Config).
+
+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).
@@ -1325,6 +1357,122 @@ test_events(update_config_cth2) ->
]
end,
update_config_cth_test_events(TestCaseEvents, Suite);
+test_events(ct_hooks_order_test_cth) ->
+ Suite = ct_hooks_order_test_SUITE,
+ 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},
+ {post_ipg_1, [ipg, pre_ipg_b], pre_ipg_2},
+ {post_ipg_2, [post_ipg_a], post_ipg_1},
+ {pre_ipt_1, [post_ipg_b], 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_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_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},
+ {pre_epg_1, [], pre_ipt_1},
+ {pre_epg_2, [pre_epg_b], pre_epg_1},
+ {post_epg_1, [pre_epg_a], 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_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_suite_cth;
+ TC == ct_hooks_order_config_ips_cth ->
+ Suite = case TC of
+ ct_hooks_order_config_suite_cth ->
+ ct_hooks_order_config_suite_SUITE;
+ _ ->
+ ct_hooks_order_config_ips_SUITE
+ end,
+ 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_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_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}
+ ],
+ hooks_order_events_helper(Suite, Recipe);
test_events(state_update_cth) ->
[
{?eh,start_logging,{'DEF','RUNDIR'}},
@@ -2983,3 +3131,89 @@ not_contains(List) ->
Test <- List,
Test =:= Ele]
end.
+
+hooks_order_events_helper(Suite, Recipe) ->
+ BuildSettingsMap =
+ fun F([{NewKey, Addition, []} | T], Acc) ->
+ F(T, Acc#{NewKey => Addition});
+ F([{NewKey, Addition, RefKey} | T], Acc) ->
+ V = fun(Key, Map) -> maps:get(Key, Map) end,
+ F(T, Acc#{NewKey => Addition ++ V(RefKey, Acc)});
+ F([], Acc) ->
+ Acc
+ end,
+ ExpectedExeSeq = BuildSettingsMap(Recipe, #{}),
+ Print = fun(Key, Map) ->
+ io_lib:format("~n~10s || ~s",
+ [atom_to_list(Key),
+ [io_lib:format("~s|", [I])||
+ I <- lists:reverse(maps:get(Key, Map))]])
+ end,
+ ExpectedExeSeqStr = [Print(Key, ExpectedExeSeq) || {Key, _, _} <- Recipe],
+ ct:log("~n~nLegend: ips - init_per_suite, ipg - init_per_group, "
+ "ipt - init_per_testcase~n~n"
+ "SLOT || EXPECTED EXECUTION SEQUENCE~n"
+ "-----------++----------------------------~s", [ExpectedExeSeqStr]),
+ M = ExpectedExeSeq,
+ V = fun(Key, Map) -> maps:get(Key, Map) end,
+ [{?eh,start_logging,{'DEF','RUNDIR'}},
+ {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
+ {?eh,cth,{'_',init,['_',[]]}},
+
+ {?eh,tc_start,{Suite,init_per_suite}},
+ ?cth_event3(pre_init_per_suite, Suite, contains(V(pre_ips_1, M))),
+ ?cth_event3(pre_init_per_suite, Suite, contains(V(pre_ips_2, M))),
+ ?cth_event4(post_init_per_suite, Suite, '$proplist', contains(V(post_ips_1, M))),
+ ?cth_event4(post_init_per_suite, Suite, '$proplist', contains(V(post_ips_2, M))),
+ {?eh,tc_done,{Suite,init_per_suite,ok}},
+ {?eh,tc_start,{Suite, {init_per_group,group1,[]}}},
+ ?cth_event4(pre_init_per_group, Suite, group1, contains(V(pre_ipg_1, M))),
+ ?cth_event4(pre_init_per_group, Suite, group1, contains(V(pre_ipg_2, M))),
+ ?cth_event5(post_init_per_group, Suite, group1,
+ '$proplist', contains(V(post_ipg_1, M))),
+ ?cth_event5(post_init_per_group, Suite, group1,
+ '$proplist', contains(V(post_ipg_2, M))),
+ {?eh,tc_done,{Suite,{init_per_group,group1,[]},ok}},
+
+ {?eh,tc_start,{Suite,test_case}},
+ ?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?
+ ?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?
+ ?cth_event5(post_end_per_testcase, Suite, test_case,
+ '$proplist', contains(V(post_ept_2, M))),
+ {?eh,tc_done,{Suite,test_case,ok}},
+
+ {?eh,tc_start,{Suite, {end_per_group,group1,[]}}},
+ ?cth_event4(pre_end_per_group, Suite, group1, contains(V(pre_epg_1, M))),
+ ?cth_event4(pre_end_per_group, Suite, group1, contains(V(pre_epg_2, M))),
+ ?cth_event5(post_end_per_group, Suite, group1,
+ contains(V(post_epg_1, M)), ok),
+ ?cth_event5(post_end_per_group, Suite, group1,
+ '$proplist', contains(V(post_epg_2, M))),
+ {?eh,tc_done,{Suite,{end_per_group,group1,[]},ok}},
+
+ {?eh,tc_start,{Suite,end_per_suite}},
+ ?cth_event3(pre_end_per_suite, Suite, contains(V(pre_eps_1, M))),
+ ?cth_event3(pre_end_per_suite, Suite, contains(V(pre_eps_2, M))),
+ ?cth_event4(post_end_per_suite, Suite,
+ contains(V(post_eps_1, M)),
+ ok),
+ ?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
new file mode 100644
index 0000000000..dba08bd1aa
--- /dev/null
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_a_cth.erl
@@ -0,0 +1,93 @@
+%%
+%% %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_a_cth).
+
+-include_lib("common_test/src/ct_util.hrl").
+-include_lib("common_test/include/ct_event.hrl").
+
+-define(now, ct_test_support:unique_timestamp()).
+-define(ADD_LOC(L), [{self(), ?MODULE, ?FUNCTION_NAME} | L]).
+
+%% CT Hooks
+-compile([export_all, nowarn_export_all]).
+
+init(Id, Opts) ->
+ empty_cth:init(Id, Opts).
+
+pre_init_per_suite(Suite, Config, State) ->
+ empty_cth:pre_init_per_suite(Suite,Config,?ADD_LOC(State)),
+ {[{pre_ips_a,?now}|Config],State}.
+
+post_init_per_suite(Suite,Config,Return,State) ->
+ empty_cth:post_init_per_suite(Suite,Config,Return,?ADD_LOC(State)),
+ {[{post_ips_a,?now}|Return],State}.
+
+pre_end_per_suite(Suite,Config,State) ->
+ empty_cth:pre_end_per_suite(Suite,Config,?ADD_LOC(State)),
+ {[{pre_eps_a,?now}|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}.
+
+pre_init_per_group(Suite, Group,Config,State) ->
+ empty_cth:pre_init_per_group(Suite,Group,Config,?ADD_LOC(State)),
+ {[{pre_ipg_a,?now}|Config],State}.
+
+post_init_per_group(Suite,Group,Config,Return,State) ->
+ empty_cth:post_init_per_group(Suite,Group,Config,Return,?ADD_LOC(State)),
+ {[{post_ipg_a,?now}|Return],State}.
+
+pre_end_per_group(Suite,Group,Config,State) ->
+ empty_cth:pre_end_per_group(Suite,Group,Config,?ADD_LOC(State)),
+ {[{pre_epg_a,?now}|Config],State}.
+
+post_end_per_group(Suite,Group,Config,Return,State) ->
+ empty_cth:post_end_per_group(Suite,Group,Config,Return,?ADD_LOC(State)),
+ {[{post_epg_a,?now}|Config],State}.
+
+pre_init_per_testcase(Suite,TC,Config,State) ->
+ empty_cth:pre_init_per_testcase(Suite,TC,Config,?ADD_LOC(State)),
+ {[{pre_ipt_a,?now}|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}.
+
+pre_end_per_testcase(Suite,TC,Config,State) ->
+ empty_cth:pre_end_per_testcase(Suite,TC,Config,?ADD_LOC(State)),
+ {[{pre_ept_a,?now}|Config],State}.
+
+post_end_per_testcase(Suite,TC,Config,Return,State) ->
+ empty_cth:post_end_per_testcase(Suite,TC,Config,Return,?ADD_LOC(State)),
+ {[{post_ept_a,?now}|Config],State}.
+
+on_tc_fail(Suite,TC, Reason, State) ->
+ empty_cth:on_tc_fail(Suite,TC,Reason,?ADD_LOC(State)).
+
+on_tc_skip(Suite,TC, Reason, State) ->
+ empty_cth:on_tc_skip(Suite,TC,Reason,?ADD_LOC(State)).
+
+terminate(State) ->
+ empty_cth:terminate(?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
new file mode 100644
index 0000000000..ff422865d2
--- /dev/null
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_b_cth.erl
@@ -0,0 +1,92 @@
+%%
+%% %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_b_cth).
+
+-include_lib("common_test/src/ct_util.hrl").
+-include_lib("common_test/include/ct_event.hrl").
+
+-define(now, ct_test_support:unique_timestamp()).
+-define(ADD_LOC(L), [{self(), ?MODULE, ?FUNCTION_NAME} | L]).
+
+%% CT Hooks
+-compile([export_all, nowarn_export_all]).
+
+init(Id, Opts) ->
+ empty_cth:init(Id, Opts).
+
+pre_init_per_suite(Suite, Config, State) ->
+ empty_cth:pre_init_per_suite(Suite,Config,?ADD_LOC(State)),
+ {[{pre_ips_b,?now}|Config],State}.
+
+post_init_per_suite(Suite,Config,Return,State) ->
+ empty_cth:post_init_per_suite(Suite,Config,Return,?ADD_LOC(State)),
+ {[{post_ips_b,?now}|Return],State}.
+
+pre_end_per_suite(Suite,Config,State) ->
+ empty_cth:pre_end_per_suite(Suite,Config,?ADD_LOC(State)),
+ {[{pre_eps_b,?now}|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}.
+
+pre_init_per_group(Suite, Group,Config,State) ->
+ empty_cth:pre_init_per_group(Suite,Group,Config,?ADD_LOC(State)),
+ {[{pre_ipg_b,?now}|Config],State}.
+
+post_init_per_group(Suite,Group,Config,Return,State) ->
+ empty_cth:post_init_per_group(Suite,Group,Config,Return,?ADD_LOC(State)),
+ {[{post_ipg_b,?now}|Return],State}.
+
+pre_end_per_group(Suite,Group,Config,State) ->
+ empty_cth:pre_end_per_group(Suite,Group,Config,?ADD_LOC(State)),
+ {[{pre_epg_b,?now}|Config],State}.
+
+post_end_per_group(Suite,Group,Config,Return,State) ->
+ empty_cth:post_end_per_group(Suite,Group,Config,Return,?ADD_LOC(State)),
+ {[{post_epg_b,?now}|Config],State}.
+
+pre_init_per_testcase(Suite,TC,Config,State) ->
+ empty_cth:pre_init_per_testcase(Suite,TC,Config,?ADD_LOC(State)),
+ {[{pre_ipt_b,?now}|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}.
+
+pre_end_per_testcase(Suite,TC,Config,State) ->
+ empty_cth:pre_end_per_testcase(Suite,TC,Config,?ADD_LOC(State)),
+ {[{pre_ept_b,?now}|Config],State}.
+
+post_end_per_testcase(Suite,TC,Config,Return,State) ->
+ empty_cth:post_end_per_testcase(Suite,TC,Config,Return,?ADD_LOC(State)),
+ {[{post_ept_b,?now}|Config],State}.
+
+on_tc_fail(Suite,TC, Reason, State) ->
+ empty_cth:on_tc_fail(Suite,TC,Reason,?ADD_LOC(State)).
+
+on_tc_skip(Suite,TC, Reason, State) ->
+ empty_cth:on_tc_skip(Suite,TC,Reason,?ADD_LOC(State)).
+
+terminate(State) ->
+ empty_cth:terminate(?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
new file mode 100644
index 0000000000..978ed735e8
--- /dev/null
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_group_SUITE.erl
@@ -0,0 +1,71 @@
+%%
+%% %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
new file mode 100644
index 0000000000..ce181459ad
--- /dev/null
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_ipg_SUITE.erl
@@ -0,0 +1,71 @@
+%%
+%% %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_config_ips_SUITE.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_ips_SUITE.erl
new file mode 100644
index 0000000000..00063e65ba
--- /dev/null
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_ips_SUITE.erl
@@ -0,0 +1,71 @@
+%%
+%% %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_ips_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}, {ct_hooks_order, config} | 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_suite_SUITE.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_suite_SUITE.erl
new file mode 100644
index 0000000000..90b15d9ec4
--- /dev/null
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_config_suite_SUITE.erl
@@ -0,0 +1,71 @@
+%%
+%% %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_suite_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() ->
+ [{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_test_SUITE.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_test_SUITE.erl
new file mode 100644
index 0000000000..8270f4e3af
--- /dev/null
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_hooks_order_test_SUITE.erl
@@ -0,0 +1,65 @@
+%%
+%% %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_test_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() ->
+ [{ct_hooks_order, test}]. % default
+
+%% Test server callback functions
+init_per_suite(Config) ->
+ [{ips, ?now} | Config].
+
+end_per_suite(Config) ->
+ %% result from end functions is not provided to any other callback
+ Config.
+
+init_per_testcase(_TestCase, Config) ->
+ [{ipt, ?now} | Config].
+
+end_per_testcase(_TestCase, Config) ->
+ %% result from end functions is not provided to any other callback
+ Config.
+
+init_per_group(_GroupName, Config) ->
+ [{ipg, ?now} | Config].
+
+end_per_group(_GroupName, 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/update_config_cth.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/update_config_cth.erl
index 7b0c1f599f..35885b4f32 100644
--- a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/update_config_cth.erl
+++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/update_config_cth.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2010-2017. All Rights Reserved.
+%% Copyright Ericsson AB 2010-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.
@@ -18,10 +18,8 @@
%% %CopyrightEnd%
%%
-
-module(update_config_cth).
-
-include_lib("common_test/src/ct_util.hrl").
-include_lib("common_test/include/ct_event.hrl").
diff --git a/lib/common_test/test/ct_testspec_2_SUITE.erl b/lib/common_test/test/ct_testspec_2_SUITE.erl
index 1bab80942a..6678c4c223 100644
--- a/lib/common_test/test/ct_testspec_2_SUITE.erl
+++ b/lib/common_test/test/ct_testspec_2_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2009-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2009-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.
@@ -152,6 +152,7 @@ basic_compatible_no_nodes(_Config) ->
{event_handler,[evh2,evh3],[[2,3]]},
{ct_hooks,[{cth_mod1,[]}]},
{ct_hooks,[{cth_mod2,[]}]},
+ {ct_hooks_order,config},
{multiply_timetraps,2},
{include,IncludeDir1},
{include,IncludeDir2},
@@ -198,6 +199,7 @@ basic_compatible_no_nodes(_Config) ->
{Node,evh3,[[2,3]]}],
ct_hooks = [{Node,{cth_mod1,[]}},
{Node,{cth_mod2,[]}}],
+ ct_hooks_order = config,
enable_builtin_hooks = true,
release_shell = false,
include = Incls,
@@ -274,6 +276,7 @@ basic_compatible_nodes(_Config) ->
{event_handler,[n1,n2],[evh2,evh3],[[2,3]]},
{ct_hooks,all_nodes,[{cth_mod1,[]}]},
{ct_hooks,[{cth_mod2,[]}]},
+ {ct_hooks_order, config},
{multiply_timetraps,node1@host1,2},
{include,n1,IncludeDir1},
{include,[n1,n2],IncludeDir2},
@@ -342,6 +345,7 @@ basic_compatible_nodes(_Config) ->
{Node,{cth_mod2,[]}},
{Node1,{cth_mod2,[]}},
{Node2,{cth_mod2,[]}}],
+ ct_hooks_order = config,
enable_builtin_hooks = true,
release_shell = false,
include = Incls,
--
2.35.3