From 87e6e270d78e883f59398f75686534ac3e5aa41c Mon Sep 17 00:00:00 2001 From: Jakub Witczak Date: Fri, 30 Jun 2023 09:54:58 +0200 Subject: [PATCH 1/6] ct: remove Windows line endings in test code --- .../cth/tests/ct_cth_prio_SUITE.erl | 104 +++++++++--------- 1 file changed, 52 insertions(+), 52 deletions(-) diff --git a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_cth_prio_SUITE.erl b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_cth_prio_SUITE.erl index 0de27621bb89..c06c701e2a18 100644 --- a/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_cth_prio_SUITE.erl +++ b/lib/common_test/test/ct_hooks_SUITE_data/cth/tests/ct_cth_prio_SUITE.erl @@ -1,8 +1,8 @@ -%% -%% %CopyrightBegin% -%% -%% Copyright Ericsson AB 2010-2016. All Rights Reserved. -%% +%% +%% %CopyrightBegin% +%% +%% 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. %% You may obtain a copy of the License at @@ -14,50 +14,50 @@ %% 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_cth_prio_SUITE). - -%% Note: This directive should only be used in test suites. --compile(export_all). - --include("ct.hrl"). - -suite() -> - ([{timetrap, {minutes, 10}}, - {ct_hooks, [{empty_cth,[800],800}, - {prio_cth,[1200]},{prio_cth,[1200,1050],1050}]}]). - -%% Test server callback functions -init_per_suite(Config) -> - [{ct_hooks, [{empty_cth,[700],700}, - {prio_cth,[600,600]}, - {prio_cth,[600,200],200}]}|Config]. - -end_per_suite(_Config) -> - ok. - -init_per_group(_G, Config) -> - [{ct_hooks, [{empty_cth,[600],600}, - {prio_cth,[900,900]},{prio_cth,[500,900],900}]}|Config]. - -end_per_group(_G, _Config) -> - ok. - -init_per_testcase(_TestCase, Config) -> - Config. - -end_per_testcase(_TestCase, _Config) -> - ok. - -all() -> - [{group,test_group}]. - -groups() -> - [{test_group,[],[test_case]}]. - -%% Test cases starts here. -test_case(Config) when is_list(Config) -> - ok. +%% +%% %CopyrightEnd% +%% + +-module(ct_cth_prio_SUITE). + +%% Note: This directive should only be used in test suites. +-compile(export_all). + +-include("ct.hrl"). + +suite() -> + ([{timetrap, {minutes, 10}}, + {ct_hooks, [{empty_cth,[800],800}, + {prio_cth,[1200]},{prio_cth,[1200,1050],1050}]}]). + +%% Test server callback functions +init_per_suite(Config) -> + [{ct_hooks, [{empty_cth,[700],700}, + {prio_cth,[600,600]}, + {prio_cth,[600,200],200}]}|Config]. + +end_per_suite(_Config) -> + ok. + +init_per_group(_G, Config) -> + [{ct_hooks, [{empty_cth,[600],600}, + {prio_cth,[900,900]},{prio_cth,[500,900],900}]}|Config]. + +end_per_group(_G, _Config) -> + ok. + +init_per_testcase(_TestCase, Config) -> + Config. + +end_per_testcase(_TestCase, _Config) -> + ok. + +all() -> + [{group,test_group}]. + +groups() -> + [{test_group,[],[test_case]}]. + +%% Test cases starts here. +test_case(Config) when is_list(Config) -> + ok. From b7a76df5e0a1138ab1b5ecdad78e2968a25ccf55 Mon Sep 17 00:00:00 2001 From: Jakub Witczak Date: Wed, 12 Jul 2023 14:20:38 +0200 Subject: [PATCH 2/6] ct: ct_notes.md update --- lib/common_test/internal_doc/ct_notes.md | 44 +++++++++++------------- 1 file changed, 20 insertions(+), 24 deletions(-) diff --git a/lib/common_test/internal_doc/ct_notes.md b/lib/common_test/internal_doc/ct_notes.md index 84c70b97efaa..a72c39666353 100644 --- a/lib/common_test/internal_doc/ct_notes.md +++ b/lib/common_test/internal_doc/ct_notes.md @@ -5,10 +5,7 @@ I think the most confusing thing is that today OTP behavior and design seems to 1. (Configuration centric) CT hook callback looks as designed to wrap around CT Configuration functions (i.e. you have *pre* and *post* to wrapp around init_per_testcase or end_per_testcase) - Furthermore if you consider hook callback function names, there are no hooks wrapping around Testcase function at all! 2. (Testcase centric) AND at the same the hook execution order is determined by relation to CT Testcase callback -### Next step ideas -1. improve existing documentation for hooks (actually it was planned for many years but down prioritized) -2. add mermaid diagrams to docs when that is possible -3. introduce a CT option for Configuration centric hook execution order (maybe named ct_hooks_order := [testcase(default) | configuration]) + ### CT hooks priorities (documentation sketch) Let's assume: 1. cth_A and cth_B being CT hook modules to be installed @@ -37,29 +34,28 @@ title: Testcase centric CT hook execution order (default) --- flowchart TD subgraph hooks - pre_init_pt_A["(A) pre_init_per_testcase"] --> pre_init_pt_B + pre_ipt_A["(A) pre_init_per_testcase"] --Config--> pre_ipt_B end subgraph suite - pre_init_pt_B["(B) pre_init_per_testcase"] --> init_pt[/"init_per_testcase"/] + pre_ipt_B["(B) pre_init_per_testcase"] --Config--> ipt[/"init_per_testcase"/] end - init_pt --> post_init_pt_A + ipt --Config,Return--> post_ipt_A subgraph hooks - post_init_pt_A["(A) post_init_per_testcase"] --> post_init_pt_B + post_ipt_A["(A) post_init_per_testcase"] --Config,Return--> post_ipt_B end subgraph suite - post_init_pt_B["(B) post_init_per_testcase"] --> testcase + post_ipt_B["(B) post_init_per_testcase"] --Config--> testcase testcase((("Testcase"))) end subgraph hooks - testcase --> pre_end_pt_B - pre_end_pt_B["(B) pre_end_per_testcase"] --> pre_end_pt_A + testcase --Config,Return--> pre_ept_B + pre_ept_B["(B) pre_end_per_testcase"] --Config,Return--> pre_ept_A end subgraph suite - pre_end_pt_A["(A) pre_end_per_testcase"] --> end_per_test_case + pre_ept_A["(A) pre_end_per_testcase"] --Config--> end_per_test_case end subgraph hooks - end_per_test_case[/"end_per_testcase"/] --> post_end_pt_B - post_end_pt_B["(B) post_end_per_testcase"] --> post_end_pt_A["(A) post_end_per_testcase"] + end_per_test_case[/"end_per_testcase"/] --Config,Return--> post_ept_B end ``` #### Configuration centric (option candidate) @@ -76,29 +72,29 @@ title: Configuration centric CT hook execution order (option) --- flowchart TD subgraph hooks - pre_init_pt_A["(A) pre_init_per_testcase"] --> pre_init_pt_B + pre_ipt_A["(A) pre_init_per_testcase"] --> pre_ipt_B end subgraph suite - pre_init_pt_B["(B) pre_init_per_testcase"] --> init_pt((("init_per_testcase"))) + pre_ipt_B["(B) pre_init_per_testcase"] --> ipt((("init_per_testcase"))) end - init_pt --> post_init_pt_B + ipt --> post_ipt_B subgraph hooks - post_init_pt_B["(B) post_init_per_testcase"] --> post_init_pt_A + post_ipt_B["(B) post_init_per_testcase"] --> post_ipt_A end subgraph suite - post_init_pt_A["(A) post_init_per_testcase"] --> testcase + post_ipt_A["(A) post_init_per_testcase"] --> testcase testcase[/"Testcase"/] end subgraph hooks - testcase --> pre_end_pt_A - pre_end_pt_A["(A) pre_end_per_testcase"] --> pre_end_pt_B + testcase --> pre_ept_A + pre_ept_A["(A) pre_end_per_testcase"] --> pre_ept_B end subgraph suite - pre_end_pt_B["(B) pre_end_per_testcase"] --> end_per_test_case + pre_ept_B["(B) pre_end_per_testcase"] --> end_per_test_case end subgraph hooks - end_per_test_case((("end_per_testcase"))) --> post_end_pt_B - post_end_pt_B["(B) post_end_per_testcase"] --> post_end_pt_A["(A) post_end_per_testcase"] + end_per_test_case((("end_per_testcase"))) --> post_ept_B + post_ept_B["(B) post_end_per_testcase"] --> post_ept_A["(A) post_end_per_testcase"] end ``` From c4e0179da6b1d26dfba7c187e5ac3d1e0c938b27 Mon Sep 17 00:00:00 2001 From: Jakub Witczak Date: Wed, 12 Jul 2023 14:21:06 +0200 Subject: [PATCH 3/6] ct: ct_hooks_order option --- lib/common_test/src/ct.erl | 4 +- lib/common_test/src/ct_framework.erl | 2 + lib/common_test/src/ct_hooks.erl | 148 +++++++++++++++++++++------ lib/common_test/src/ct_run.erl | 29 +++++- lib/common_test/src/ct_testspec.erl | 4 + lib/common_test/src/ct_util.hrl | 3 +- 6 files changed, 151 insertions(+), 39 deletions(-) diff --git a/lib/common_test/src/ct.erl b/lib/common_test/src/ct.erl index 012bb5c7403f..0c4166783efa 100644 --- a/lib/common_test/src/ct.erl +++ b/lib/common_test/src/ct.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2003-2022. All Rights Reserved. +%% Copyright Ericsson AB 2003-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. @@ -170,6 +170,7 @@ run(TestDirs) -> | {esc_chars, boolean()} | {keep_logs,KeepSpec} | {ct_hooks, CTHs} + | {ct_hooks_order, CTHsOrder} | {enable_builtin_hooks, boolean()} | {release_shell, boolean()}, TestDirs :: [string()] | string(), @@ -211,6 +212,7 @@ run(TestDirs) -> Category :: atom(), KeepSpec :: all | pos_integer(), CTHs :: [CTHModule | {CTHModule, CTHInitArgs}], + CTHsOrder :: atom(), CTHModule :: atom(), CTHInitArgs :: term(), Result :: {Ok, Failed, {UserSkipped, AutoSkipped}} | TestRunnerPid | {error, Reason}, diff --git a/lib/common_test/src/ct_framework.erl b/lib/common_test/src/ct_framework.erl index ad01da29f604..7c704e36be9b 100644 --- a/lib/common_test/src/ct_framework.erl +++ b/lib/common_test/src/ct_framework.erl @@ -606,6 +606,8 @@ configure([{timetrap,Time}|Rest],Info,SuiteInfo,Scope,PostInitHook,Config) -> configure(Rest,Info,SuiteInfo,Scope,PostInitHook1,Config); configure([{ct_hooks,Hook}|Rest],Info,SuiteInfo,Scope,PostInitHook,Config) -> configure(Rest,Info,SuiteInfo,Scope,PostInitHook,[{ct_hooks,Hook}|Config]); +configure([{ct_hooks_order,Order}|Rest],Info,SuiteInfo,Scope,PostInitHook,Config) -> + configure(Rest,Info,SuiteInfo,Scope,PostInitHook,[{ct_hooks_order,Order}|Config]); configure([_|Rest],Info,SuiteInfo,Scope,PostInitHook,Config) -> configure(Rest,Info,SuiteInfo,Scope,PostInitHook,Config); configure([],_,_,_,PostInitHook,Config) -> diff --git a/lib/common_test/src/ct_hooks.erl b/lib/common_test/src/ct_hooks.erl index 23fadcbc2c5e..6144b2458c8c 100644 --- a/lib/common_test/src/ct_hooks.erl +++ b/lib/common_test/src/ct_hooks.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2004-2021. All Rights Reserved. +%% Copyright Ericsson AB 2004-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. @@ -31,7 +31,8 @@ -export([on_tc_fail/2]). %% If you change this, remember to update ct_util:look -> stop clause as well. --define(config_name, ct_hooks). +-define(hooks_name, ct_hooks). +-define(hooks_order_name, ct_hooks_order). %% All of the hooks which are to be started by default. Remove by issuing %% -enable_builtin_hooks false to when starting common test. @@ -49,6 +50,7 @@ -spec init(State :: term()) -> ok | {fail, Reason :: term()}. init(Opts) -> + process_hooks_order(?FUNCTION_NAME, Opts), call(get_builtin_hooks(Opts) ++ get_new_hooks(Opts, undefined), ok, init, []). @@ -56,16 +58,16 @@ init(Opts) -> groups(Mod, Groups) -> Info = try proplists:get_value(ct_hooks, Mod:suite(), []) of CTHooks when is_list(CTHooks) -> - [{?config_name,CTHooks}]; + [{?hooks_name,CTHooks}]; CTHook when is_atom(CTHook) -> - [{?config_name,[CTHook]}] + [{?hooks_name,[CTHook]}] catch _:_ -> %% since this might be the first time Mod:suite() %% is called, and it might just fail or return %% something bad, we allow any failure here - it %% will be caught later if there is something %% really wrong. - [{?config_name,[]}] + [{?hooks_name,[]}] end, case call(fun call_generic/3, Info ++ [{'$ct_groups',Groups}], [post_groups, Mod]) of [{'$ct_groups',NewGroups}] -> @@ -78,13 +80,13 @@ groups(Mod, Groups) -> all(Mod, Tests) -> Info = try proplists:get_value(ct_hooks, Mod:suite(), []) of CTHooks when is_list(CTHooks) -> - [{?config_name,CTHooks}]; + [{?hooks_name,CTHooks}]; CTHook when is_atom(CTHook) -> - [{?config_name,[CTHook]}] + [{?hooks_name,[CTHook]}] catch _:_ -> %% just allow any failure here - it will be caught %% later if there is something really wrong. - [{?config_name,[]}] + [{?hooks_name,[]}] end, case call(fun call_generic/3, Info ++ [{'$ct_all',Tests}], [post_all, Mod]) of [{'$ct_all',NewTests}] -> @@ -118,11 +120,11 @@ terminate(Hooks) -> init_tc(Mod, init_per_suite, Config) -> Info = try proplists:get_value(ct_hooks, Mod:suite(),[]) of List when is_list(List) -> - [{?config_name,List}]; + [{?hooks_name,List}]; CTHook when is_atom(CTHook) -> - [{?config_name,[CTHook]}] + [{?hooks_name,[CTHook]}] catch error:undef -> - [{?config_name,[]}] + [{?hooks_name,[]}] end, call(fun call_generic/3, Config ++ Info, [pre_init_per_suite, Mod]); @@ -158,13 +160,15 @@ init_tc(Mod, TC = error_in_suite, Config) -> {fail, Reason :: term()} | ok | '$ct_no_change'. -end_tc(Mod, init_per_suite, Config, _Result, Return) -> +end_tc(Mod, CFunc = init_per_suite, Config, _Result, Return) -> + process_hooks_order(CFunc, 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, {init_per_group, GroupName, _}, Config, _Result, Return) -> +end_tc(Mod, {CFunc = init_per_group, GroupName, _}, Config, _Result, Return) -> + process_hooks_order(CFunc, 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) -> @@ -249,13 +253,15 @@ do_call_generic(#ct_hook_config{ module = Mod, state = State} = Hook, {NewValue, Hook#ct_hook_config{ state = NewState } }. %% Generic call function -call(Fun, Config, Meta) -> +call(Fun, Config, [CFunc | _] = Meta) -> maybe_lock(), Hooks = get_hooks(), Calls = get_new_hooks(Config, Fun) ++ [{HookId,Fun} || #ct_hook_config{id = HookId} <- Hooks], - Res = call(resort(Calls,Hooks,Meta), - remove(?config_name,Config), Meta, Hooks), + Order = process_hooks_order(CFunc, Config), + Res = call(resort(Calls,Hooks,Meta, Order), + remove([?hooks_name, ?hooks_order_name], Config), + Meta, Hooks), maybe_unlock(), Res. @@ -264,7 +270,6 @@ call(Fun, Config, Meta, NoChangeRet) when is_function(Fun) -> Config -> NoChangeRet; NewReturn -> NewReturn end; - call([{Hook, call_id, NextFun} | Rest], Config, Meta, Hooks) -> try {Config, #ct_hook_config{ id = NewId } = NewHook} = @@ -286,7 +291,9 @@ call([{Hook, call_id, NextFun} | Rest], Config, Meta, Hooks) -> {Hooks ++ [NewHook], Rest ++ [{NewId, call_init}, {NewId,NextFun}]} end, - call(resort(NewRest,NewHooks,Meta), Config, Meta, NewHooks) + {_, Order} = get_hooks_order(), + call(resort(NewRest, NewHooks, Meta, Order), Config, Meta, + NewHooks) catch Error:Reason:Trace -> ct_logs:log("Suite Hook","Failed to start a CTH: ~tp:~tp", [Error,{Reason,Trace}]), @@ -301,8 +308,12 @@ 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), - call(resort(NewCalls ++ Rest,NewHooks,Meta), %% Resort if call_init changed prio - remove(?config_name, NewConf), Meta, + %% FIXME - not needed, but maybe logical? + %% process_hooks_order(NewConf), + {_, 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, terminate_if_scope_ends(HookId, Meta, NewHooks)) catch throw:{error_in_cth_call,Reason} -> call(Rest, {fail, Reason}, Meta, @@ -310,8 +321,14 @@ 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) -> + List; +remove([Key|T], List) when is_list(List) -> + NewList = remove(Key, List), + remove(T, NewList); remove(Key,List) when is_list(List) -> [Conf || Conf <- List, is_tuple(Conf) =:= false orelse element(1, Conf) =/= Key]; @@ -392,9 +409,9 @@ get_new_hooks(Config, Fun) -> end, get_new_hooks(Config)). get_new_hooks(Config) when is_list(Config) -> - lists:flatmap(fun({?config_name, HookConfigs}) when is_list(HookConfigs) -> + lists:flatmap(fun({?hooks_name, HookConfigs}) when is_list(HookConfigs) -> HookConfigs; - ({?config_name, HookConfig}) when is_atom(HookConfig) -> + ({?hooks_name, HookConfig}) when is_atom(HookConfig) -> [HookConfig]; (_) -> [] @@ -411,10 +428,10 @@ get_builtin_hooks(Opts) -> end. save_suite_data_async(Hooks) -> - ct_util:save_suite_data_async(?config_name, Hooks). + ct_util:save_suite_data_async(?hooks_name, Hooks). get_hooks() -> - lists:keysort(#ct_hook_config.prio,ct_util:read_suite_data(?config_name)). + lists:keysort(#ct_hook_config.prio,ct_util:read_suite_data(?hooks_name)). %% Sort all calls in this order: %% call_id < call_init < ctfirst < Priority 1 < .. < Priority N < ctlast @@ -423,17 +440,38 @@ get_hooks() -> %% If we are doing a cleanup call i.e. {post,pre}_end_per_*, all priorities %% are reversed. Probably want to make this sorting algorithm pluginable %% as some point... -resort(Calls,Hooks,[F|_R]) when F == pre_end_per_testcase; - F == post_end_per_testcase; - F == pre_end_per_group; - F == post_end_per_group; - F == pre_end_per_suite; - F == post_end_per_suite -> - lists:reverse(resort(Calls,Hooks)); - -resort(Calls,Hooks,_Meta) -> +resort(Calls, Hooks, [CFunc|_R], HooksOrder) -> + Resorted = resort(Calls, Hooks), + ReversedHooks = + case HooksOrder of + config -> + %% reversed order for all post hooks (config centric order) + %% ct_hooks_order is 'config' + [post_init_per_testcase, + post_end_per_testcase, + post_init_per_group, + post_end_per_group, + post_init_per_suite, + post_end_per_suite]; + _ -> + %% reversed order for all end hooks (testcase centric order) + %% default or when ct_hooks_order is 'test' + [pre_end_per_testcase, + post_end_per_testcase, + pre_end_per_group, + post_end_per_group, + pre_end_per_suite, + post_end_per_suite] + end, + case lists:member(CFunc, ReversedHooks) of + true -> + lists:reverse(Resorted); + _ -> + Resorted + end; +resort(Calls,Hooks,_Meta, _HooksOrder) -> resort(Calls,Hooks). - + resort(Calls, Hooks) -> lists:sort( fun({_,_,_},_) -> @@ -498,6 +536,48 @@ 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 + undefined -> + maybe_save_hooks_order(Stage, Return); + _ -> + 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. + +maybe_save_hooks_order(Stage, 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}), + Order; + _ -> + test + end. %% We need to lock around the state for parallel groups only. This is because %% we will get several processes reading and writing the state for a single diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index fa72f4e68acf..3507f3513d4e 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -59,6 +59,7 @@ config = [], event_handlers = [], ct_hooks = [], + ct_hooks_order, enable_builtin_hooks, include = [], auto_compile, @@ -248,6 +249,10 @@ script_start1(Parent, Args) -> end, Args), EvHandlers = event_handler_args2opts(Args), CTHooks = ct_hooks_args2opts(Args), + CTHooksOrder = get_start_opt(ct_hooks_order, + fun([CTHO]) -> list_to_atom(CTHO); + ([]) -> undefined + end, undefined, Args), EnableBuiltinHooks = get_start_opt(enable_builtin_hooks, fun([CT]) -> list_to_atom(CT); ([]) -> undefined @@ -352,6 +357,7 @@ script_start1(Parent, Args) -> verbosity = Verbosity, event_handlers = EvHandlers, ct_hooks = CTHooks, + ct_hooks_order = CTHooksOrder, enable_builtin_hooks = EnableBuiltinHooks, auto_compile = AutoCompile, abort_if_missing_suites = AbortIfMissing, @@ -539,6 +545,10 @@ combine_test_opts(TS, Specs, Opts) -> [Opts#opts.ct_hooks, TSOpts#opts.ct_hooks]), + AllCTHooksOrder = + choose_val(Opts#opts.ct_hooks_order, + TSOpts#opts.ct_hooks_order), + EnableBuiltinHooks = choose_val( Opts#opts.enable_builtin_hooks, @@ -603,6 +613,7 @@ combine_test_opts(TS, Specs, Opts) -> config = TSOpts#opts.config, event_handlers = AllEvHs, ct_hooks = AllCTHooks, + ct_hooks_order = AllCTHooksOrder, enable_builtin_hooks = EnableBuiltinHooks, stylesheet = Stylesheet, auto_compile = AutoCompile, @@ -614,14 +625,16 @@ combine_test_opts(TS, Specs, Opts) -> check_and_install_configfiles( Configs, LogDir, #opts{ - event_handlers = EvHandlers, - ct_hooks = CTHooks, - enable_builtin_hooks = EnableBuiltinHooks} ) -> + event_handlers = EvHandlers, + ct_hooks = CTHooks, + ct_hooks_order = CTHooksOrder, + enable_builtin_hooks = EnableBuiltinHooks} ) -> case ct_config:check_config_files(Configs) of false -> install([{config,Configs}, {event_handler,EvHandlers}, {ct_hooks,CTHooks}, + {ct_hooks_order,CTHooksOrder}, {enable_builtin_hooks,EnableBuiltinHooks}], LogDir); {value,{error,{nofile,File}}} -> {error,{cant_read_config_file,File}}; @@ -957,6 +970,11 @@ run_test2(StartOpts) -> %% CT Hooks CTHooks = get_start_opt(ct_hooks, value, [], StartOpts), + CTHooksOrder = get_start_opt(ct_hooks_order, + fun(CHO) when CHO == test; + CHO == config -> + CHO + end, undefined, StartOpts), EnableBuiltinHooks = get_start_opt(enable_builtin_hooks, fun(EBH) when EBH == true; EBH == false -> @@ -1073,6 +1091,7 @@ run_test2(StartOpts) -> verbosity = Verbosity, event_handlers = EvHandlers, ct_hooks = CTHooks, + ct_hooks_order = CTHooksOrder, enable_builtin_hooks = EnableBuiltinHooks, auto_compile = AutoCompile, abort_if_missing_suites = AbortIfMissing, @@ -1200,6 +1219,7 @@ run_dir(Opts = #opts{logdir = LogDir, config = CfgFiles, event_handlers = EvHandlers, ct_hooks = CTHook, + ct_hooks_order = CTHooksOrder, enable_builtin_hooks = EnableBuiltinHooks}, StartOpts) -> LogDir1 = which(logdir, LogDir), @@ -1226,6 +1246,7 @@ run_dir(Opts = #opts{logdir = LogDir, case install([{config,AbsCfgFiles}, {event_handler,EvHandlers}, {ct_hooks, CTHook}, + {ct_hooks_order, CTHooksOrder}, {enable_builtin_hooks,EnableBuiltinHooks}], LogDir1) of ok -> ok; {error,_IReason} = IError -> exit(IError) @@ -1417,6 +1438,7 @@ get_data_for_node(#testspec{label = Labels, userconfig = UsrCfgs, event_handler = EvHs, ct_hooks = CTHooks, + ct_hooks_order = CTHooksOrder, enable_builtin_hooks = EnableBuiltinHooks, auto_compile = ACs, abort_if_missing_suites = AiMSs, @@ -1471,6 +1493,7 @@ get_data_for_node(#testspec{label = Labels, config = ConfigFiles, event_handlers = EvHandlers, ct_hooks = FiltCTHooks, + ct_hooks_order = CTHooksOrder, enable_builtin_hooks = EnableBuiltinHooks, auto_compile = AutoCompile, abort_if_missing_suites = AbortIfMissing, diff --git a/lib/common_test/src/ct_testspec.erl b/lib/common_test/src/ct_testspec.erl index 9b63c0d60b6a..1b9fc8ee156a 100644 --- a/lib/common_test/src/ct_testspec.erl +++ b/lib/common_test/src/ct_testspec.erl @@ -981,6 +981,9 @@ add_tests([{event_handler,Node,HOrHs,Args}|Ts],Spec) -> add_tests([{enable_builtin_hooks,Bool}|Ts],Spec) -> add_tests(Ts, Spec#testspec{enable_builtin_hooks = Bool}); +add_tests([{ct_hooks_order,Order}|Ts],Spec) -> + add_tests(Ts, Spec#testspec{ct_hooks_order = Order}); + add_tests([{release_shell,Bool}|Ts],Spec) -> add_tests(Ts, Spec#testspec{release_shell = Bool}); @@ -1592,6 +1595,7 @@ valid_terms() -> {event_handler,4}, {ct_hooks,2}, {ct_hooks,3}, + {ct_hooks_order,2}, {enable_builtin_hooks,2}, {release_shell,2}, {multiply_timetraps,2}, diff --git a/lib/common_test/src/ct_util.hrl b/lib/common_test/src/ct_util.hrl index 7eba02d1482a..e0145b05888c 100644 --- a/lib/common_test/src/ct_util.hrl +++ b/lib/common_test/src/ct_util.hrl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2003-2020. All Rights Reserved. +%% Copyright Ericsson AB 2003-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. @@ -47,6 +47,7 @@ userconfig=[], event_handler=[], ct_hooks=[], + ct_hooks_order, enable_builtin_hooks=true, release_shell=false, include=[], From 2322dc23c322b87d9ffa8f876c44fd22457eb8dd Mon Sep 17 00:00:00 2001 From: Jakub Witczak 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 63ff69eef80d..0e77f37eb9b9 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 000000000000..dba08bd1aa5c --- /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 000000000000..ff422865d2bc --- /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 000000000000..978ed735e811 --- /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 000000000000..ce181459ada9 --- /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 000000000000..00063e65ba0a --- /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 000000000000..90b15d9ec456 --- /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 000000000000..8270f4e3afe3 --- /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 7b0c1f599fe9..35885b4f32e5 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 1bab80942aee..6678c4c2237b 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, From 913a311447a73aa086902c1c81a897b1035b9b31 Mon Sep 17 00:00:00 2001 From: Jakub Witczak Date: Thu, 13 Jul 2023 12:43:49 +0200 Subject: [PATCH 5/6] ct: ct_hooks_order docs --- lib/common_test/doc/src/ct_hooks_chapter.xml | 28 +++++++++++++++----- lib/common_test/doc/src/ct_run_cmd.xml | 2 ++ lib/common_test/doc/src/ct_suite.xml | 9 ++++--- lib/common_test/doc/src/run_test_chapter.xml | 8 ++++++ lib/common_test/src/ct_run.erl | 1 + 5 files changed, 38 insertions(+), 10 deletions(-) diff --git a/lib/common_test/doc/src/ct_hooks_chapter.xml b/lib/common_test/doc/src/ct_hooks_chapter.xml index 840bd58cc4b5..78678c0ebe9d 100644 --- a/lib/common_test/doc/src/ct_hooks_chapter.xml +++ b/lib/common_test/doc/src/ct_hooks_chapter.xml @@ -119,13 +119,27 @@ CTH Execution Order

By default, each CTH installed is executed in the order that - they are installed for init calls, and then reversed for end calls. - This is not always desired, so Common Test allows - the user to specify a priority for each hook. The priority can either - be specified in the CTH function - init/2 or when - installing the hook. The priority specified at installation overrides the - priority returned by the CTH.

+ 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 test of ct_hooks_order option.

+

Installation based order is not always + desired, so Common Test allows the user to specify a + priority for each hook. The priority can either be specified in + the CTH function init/2 or when + installing the hook. The priority specified at installation + overrides the priority returned by the CTH.

+

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 + ct_hooks_order option with config value. When + option is enabled, execution order is configuration centric, as + the reversed order happens after each configuration function and + not in relation to testcase.

+

Note that ct_hooks_order option is considered as a + global framework setting. In case when option is configured + multiple times framework with process only the first value.

diff --git a/lib/common_test/doc/src/ct_run_cmd.xml b/lib/common_test/doc/src/ct_run_cmd.xml index be3dc8a72619..94c955a6ffa9 100644 --- a/lib/common_test/doc/src/ct_run_cmd.xml +++ b/lib/common_test/doc/src/ct_run_cmd.xml @@ -128,6 +128,7 @@ [-keep_logs all | NLogs] [-ct_hooks CTHModule1 CTHOpts1 and CTHModule2 CTHOpts2 and .. CTHModuleN CTHOptsN] + [-ct_hooks_order test | config] [-exit_status ignore_config] [-help] @@ -168,6 +169,7 @@ [-keep_logs all | NLogs] [-ct_hooks CTHModule1 CTHOpts1 and CTHModule2 CTHOpts2 and .. CTHModuleN CTHOptsN] + [-ct_hooks_order test | config] [-exit_status ignore_config] diff --git a/lib/common_test/doc/src/ct_suite.xml b/lib/common_test/doc/src/ct_suite.xml index 8e5a73143e3e..4c99181e2c0f 100644 --- a/lib/common_test/doc/src/ct_suite.xml +++ b/lib/common_test/doc/src/ct_suite.xml @@ -161,7 +161,7 @@ Test suite info function (providing default data for the suite). - ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} + ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} | {ct_hooks_order, CTHOrder} Time = TimeVal | TimeFunc TimeVal = MilliSec | {seconds, integer()} | {minutes, integer()} | {hours, integer()} TimeFunc = {Mod, Func, Args} | Fun @@ -184,6 +184,7 @@ CTHModule = atom() CTHInitArgs = term() CTHPriority = integer() + CTHOrder = test | config @@ -292,7 +293,7 @@ subgroups). GroupName = ct_groupname() - ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} + ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} | {ct_hooks_order, CTHOrder} Time = TimeVal | TimeFunc TimeVal = MilliSec | {seconds, integer()} | {minutes, integer()} | {hours, integer()} TimeFunc = {Mod, Func, Args} | Fun @@ -315,6 +316,7 @@ CTHModule = atom() CTHInitArgs = term() CTHPriority = integer() + CTHOrder = test | config @@ -497,7 +499,7 @@ Module:Testcase() -> [ct_info()] Test case information function. - ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} + ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} | {ct_hooks_order, CTHOrder} Time = TimeVal | TimeFunc TimeVal = MilliSec | {seconds, integer()} | {minutes, integer()} | {hours, integer()} TimeFunc = {Mod, Func, Args} | Fun @@ -520,6 +522,7 @@ CTHModule = atom() CTHInitArgs = term() CTHPriority = integer() + CTHOrder = test | config diff --git a/lib/common_test/doc/src/run_test_chapter.xml b/lib/common_test/doc/src/run_test_chapter.xml index dfdaf2badb44..94a137b7fb8d 100644 --- a/lib/common_test/doc/src/run_test_chapter.xml +++ b/lib/common_test/doc/src/run_test_chapter.xml @@ -210,6 +210,11 @@ Common Test Hooks including start arguments.

+ +

To modify + Common Test Hooks + execution order.

+ ]]>

To enable or disable Built-in Common Test Hooks. @@ -883,6 +888,8 @@ {ct_hooks, CTHModules}. {ct_hooks, NodeRefs, CTHModules}. + {ct_hooks_order, CTHOrder}. + {enable_builtin_hooks, Bool}. {basic_html, Bool}. @@ -952,6 +959,7 @@ {CTHModule, CTHInitArgs, CTHPriority}] CTHModule = atom() CTHInitArgs = term() + CTHOrder = test | config Dir = string() Suites = atom() | [atom()] | all Suite = atom() diff --git a/lib/common_test/src/ct_run.erl b/lib/common_test/src/ct_run.erl index 3507f3513d4e..e16dc79c2780 100644 --- a/lib/common_test/src/ct_run.erl +++ b/lib/common_test/src/ct_run.erl @@ -766,6 +766,7 @@ script_usage() -> "\n\t [-cover_stop Bool]" "\n\t [-event_handler EvHandler1 EvHandler2 .. EvHandlerN]" "\n\t [-ct_hooks CTHook1 CTHook2 .. CTHookN]" + "\n\t [-ct_hooks_order test | config]" "\n\t [-include InclDir1 InclDir2 .. InclDirN]" "\n\t [-no_auto_compile]" "\n\t [-abort_if_missing_suites]" From abde78fc4f7b57915ce491b42053f51c601dd06b Mon Sep 17 00:00:00 2001 From: Jakub Witczak 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 78678c0ebe9d..ca8c0d2e0ef2 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 @@

CTH Execution Order -

By default, each CTH installed is executed in the order that +

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 test of ct_hooks_order option.

-

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 (test) of ct_hooks_order option.

+

The installation-based order is not always desired, so Common Test 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 init/2 or when installing the hook. The priority specified at installation overrides the priority returned by the CTH.

-

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 - ct_hooks_order option with config value. When - option is enabled, execution order is configuration centric, as +

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 + ct_hooks_order option with config 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.

-

Note that ct_hooks_order option is considered as a +

Note that the ct_hooks_order option is considered as a global framework setting. In case when option is configured multiple times framework with process only the first value.

+

The ct_hooks_order option can be set as: ct_run + argument, in test specification or suite/0 return + value.

diff --git a/lib/common_test/doc/src/ct_suite.xml b/lib/common_test/doc/src/ct_suite.xml index 4c99181e2c0f..3713d78f7a0a 100644 --- a/lib/common_test/doc/src/ct_suite.xml +++ b/lib/common_test/doc/src/ct_suite.xml @@ -293,7 +293,7 @@ subgroups). GroupName = ct_groupname() - ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} | {ct_hooks_order, CTHOrder} + ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} Time = TimeVal | TimeFunc TimeVal = MilliSec | {seconds, integer()} | {minutes, integer()} | {hours, integer()} TimeFunc = {Mod, Func, Args} | Fun @@ -316,7 +316,6 @@ CTHModule = atom() CTHInitArgs = term() CTHPriority = integer() - CTHOrder = test | config @@ -499,7 +498,7 @@ Module:Testcase() -> [ct_info()] Test case information function. - ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} | {ct_hooks_order, CTHOrder} + ct_info() = {timetrap, Time} | {require, Required} | {require, Name, Required} | {userdata, UserData} | {silent_connections, Conns} | {stylesheet, CSSFile} | {ct_hooks, CTHs} Time = TimeVal | TimeFunc TimeVal = MilliSec | {seconds, integer()} | {minutes, integer()} | {hours, integer()} TimeFunc = {Mod, Func, Args} | Fun @@ -522,7 +521,6 @@ CTHModule = atom() CTHInitArgs = term() CTHPriority = integer() - CTHOrder = test | config diff --git a/lib/common_test/internal_doc/ct_notes.md b/lib/common_test/internal_doc/ct_notes.md index a72c39666353..061e4d2cdb75 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 6144b2458c8c..d182e08efcd2 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 0e77f37eb9b9..a59bc3bd5a3e 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 dba08bd1aa5c..ddb829dcbb24 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 ff422865d2bc..f8aba2fc10c0 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 978ed735e811..000000000000 --- 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 ce181459ada9..000000000000 --- 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 8270f4e3afe3..13b92ea8e73c 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.