~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/common_test/test/ct_hooks_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2009-2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
%%%-------------------------------------------------------------------
 
21
%%% File: ct_error_SUITE
 
22
%%%
 
23
%%% Description: 
 
24
%%% Test various errors in Common Test suites.
 
25
%%%
 
26
%%% The suites used for the test are located in the data directory.
 
27
%%%-------------------------------------------------------------------
 
28
-module(ct_hooks_SUITE).
 
29
 
 
30
-compile(export_all).
 
31
 
 
32
-include_lib("test_server/include/test_server.hrl").
 
33
-include_lib("common_test/include/ct_event.hrl").
 
34
 
 
35
-define(eh, ct_test_support_eh).
 
36
 
 
37
%%--------------------------------------------------------------------
 
38
%% TEST SERVER CALLBACK FUNCTIONS
 
39
%%--------------------------------------------------------------------
 
40
 
 
41
%%--------------------------------------------------------------------
 
42
%% Description: Since Common Test starts another Test Server
 
43
%% instance, the tests need to be performed on a separate node (or
 
44
%% there will be clashes with logging processes etc).
 
45
%%--------------------------------------------------------------------
 
46
init_per_suite(Config) ->
 
47
    DataDir = ?config(data_dir, Config),
 
48
    TestDir = filename:join(DataDir,"cth/tests/"),
 
49
    CTHs = filelib:wildcard(filename:join(TestDir,"*_cth.erl")),
 
50
    io:format("CTHs: ~p",[CTHs]),
 
51
    [io:format("Compiling ~p: ~p",
 
52
            [FileName,compile:file(FileName,[{outdir,TestDir},debug_info])]) ||
 
53
        FileName <- CTHs],
 
54
    ct_test_support:init_per_suite([{path_dirs,[TestDir]} | Config]).
 
55
 
 
56
end_per_suite(Config) ->
 
57
    ct_test_support:end_per_suite(Config).
 
58
 
 
59
init_per_testcase(TestCase, Config) ->
 
60
    ct_test_support:init_per_testcase(TestCase, Config).
 
61
 
 
62
end_per_testcase(TestCase, Config) ->
 
63
    ct_test_support:end_per_testcase(TestCase, Config).
 
64
 
 
65
 
 
66
suite() ->
 
67
    [{timetrap,{seconds,20}}].
 
68
 
 
69
all() ->
 
70
    all(suite).
 
71
 
 
72
all(suite) -> 
 
73
    lists:reverse(
 
74
      [
 
75
       one_cth, two_cth, faulty_cth_no_init, faulty_cth_id_no_init,
 
76
       faulty_cth_exit_in_init, faulty_cth_exit_in_id,
 
77
       faulty_cth_exit_in_init_scope_suite, minimal_cth, 
 
78
       minimal_and_maximal_cth, faulty_cth_undef, 
 
79
       scope_per_suite_cth, scope_per_group_cth, scope_suite_cth,
 
80
       scope_per_suite_state_cth, scope_per_group_state_cth, 
 
81
       scope_suite_state_cth,
 
82
       fail_pre_suite_cth, fail_post_suite_cth, skip_pre_suite_cth,
 
83
       skip_post_suite_cth, recover_post_suite_cth, update_config_cth,
 
84
       state_update_cth, options_cth, same_id_cth, 
 
85
       fail_n_skip_with_minimal_cth
 
86
      ]
 
87
    )
 
88
        .
 
89
 
 
90
 
 
91
%%--------------------------------------------------------------------
 
92
%% TEST CASES
 
93
%%--------------------------------------------------------------------
 
94
 
 
95
%%%-----------------------------------------------------------------
 
96
%%% 
 
97
one_cth(Config) when is_list(Config) -> 
 
98
    do_test(one_empty_cth, "ct_cth_empty_SUITE.erl",[empty_cth], Config).
 
99
 
 
100
two_cth(Config) when is_list(Config) -> 
 
101
    do_test(two_empty_cth, "ct_cth_empty_SUITE.erl",[empty_cth,empty_cth],
 
102
            Config).
 
103
 
 
104
faulty_cth_no_init(Config) when is_list(Config) ->
 
105
    do_test(faulty_cth_no_init, "ct_cth_empty_SUITE.erl",[askjhdkljashdkaj],
 
106
            Config,{error,"Failed to start CTH, see the "
 
107
                   "CT Log for details"}).
 
108
 
 
109
faulty_cth_id_no_init(Config) when is_list(Config) ->
 
110
    do_test(faulty_cth_id_no_init, "ct_cth_empty_SUITE.erl",[id_no_init_cth],
 
111
            Config,{error,"Failed to start CTH, see the "
 
112
                   "CT Log for details"}).
 
113
 
 
114
minimal_cth(Config) when is_list(Config) ->
 
115
    do_test(minimal_cth, "ct_cth_empty_SUITE.erl",[minimal_cth],Config).
 
116
 
 
117
minimal_and_maximal_cth(Config) when is_list(Config) ->
 
118
    do_test(minimal_and_maximal_cth, "ct_cth_empty_SUITE.erl",
 
119
            [minimal_cth, empty_cth],Config).
 
120
    
 
121
faulty_cth_undef(Config) when is_list(Config) ->
 
122
    do_test(faulty_cth_undef, "ct_cth_empty_SUITE.erl",
 
123
            [undef_cth],Config).
 
124
 
 
125
faulty_cth_exit_in_init_scope_suite(Config) when is_list(Config) ->
 
126
    do_test(faulty_cth_exit_in_init_scope_suite, 
 
127
            "ct_exit_in_init_scope_suite_cth_SUITE.erl",
 
128
            [],Config).
 
129
 
 
130
faulty_cth_exit_in_init(Config) when is_list(Config) ->
 
131
    do_test(faulty_cth_exit_in_init, "ct_cth_empty_SUITE.erl",
 
132
            [crash_init_cth], Config,
 
133
            {error,"Failed to start CTH, see the "
 
134
             "CT Log for details"}).
 
135
 
 
136
faulty_cth_exit_in_id(Config) when is_list(Config) ->
 
137
    do_test(faulty_cth_exit_in_id, "ct_cth_empty_SUITE.erl",
 
138
            [crash_id_cth], Config,
 
139
            {error,"Failed to start CTH, see the "
 
140
             "CT Log for details"}).
 
141
 
 
142
scope_per_suite_cth(Config) when is_list(Config) ->
 
143
    do_test(scope_per_suite_cth, "ct_scope_per_suite_cth_SUITE.erl",
 
144
            [],Config).
 
145
 
 
146
scope_suite_cth(Config) when is_list(Config) ->
 
147
    do_test(scope_suite_cth, "ct_scope_suite_cth_SUITE.erl",
 
148
            [],Config).
 
149
 
 
150
scope_per_group_cth(Config) when is_list(Config) ->
 
151
    do_test(scope_per_group_cth, "ct_scope_per_group_cth_SUITE.erl",
 
152
            [],Config).
 
153
 
 
154
scope_per_suite_state_cth(Config) when is_list(Config) ->
 
155
    do_test(scope_per_suite_state_cth, "ct_scope_per_suite_state_cth_SUITE.erl",
 
156
            [],Config).
 
157
 
 
158
scope_suite_state_cth(Config) when is_list(Config) ->
 
159
    do_test(scope_suite_state_cth, "ct_scope_suite_state_cth_SUITE.erl",
 
160
            [],Config).
 
161
 
 
162
scope_per_group_state_cth(Config) when is_list(Config) ->
 
163
    do_test(scope_per_group_state_cth, "ct_scope_per_group_state_cth_SUITE.erl",
 
164
            [],Config).
 
165
 
 
166
fail_pre_suite_cth(Config) when is_list(Config) ->
 
167
    do_test(fail_pre_suite_cth, "ct_cth_empty_SUITE.erl",
 
168
            [fail_pre_suite_cth],Config).
 
169
 
 
170
fail_post_suite_cth(Config) when is_list(Config) ->
 
171
    do_test(fail_post_suite_cth, "ct_cth_empty_SUITE.erl",
 
172
            [fail_post_suite_cth],Config).
 
173
 
 
174
skip_pre_suite_cth(Config) when is_list(Config) ->
 
175
    do_test(skip_pre_suite_cth, "ct_cth_empty_SUITE.erl",
 
176
            [skip_pre_suite_cth],Config).
 
177
 
 
178
skip_post_suite_cth(Config) when is_list(Config) ->
 
179
    do_test(skip_post_suite_cth, "ct_cth_empty_SUITE.erl",
 
180
            [skip_post_suite_cth],Config).
 
181
 
 
182
recover_post_suite_cth(Config) when is_list(Config) ->
 
183
    do_test(recover_post_suite_cth, "ct_cth_fail_per_suite_SUITE.erl",
 
184
            [recover_post_suite_cth],Config).
 
185
 
 
186
update_config_cth(Config) when is_list(Config) ->
 
187
    do_test(update_config_cth, "ct_update_config_SUITE.erl",
 
188
            [update_config_cth],Config).
 
189
 
 
190
state_update_cth(Config) when is_list(Config) ->
 
191
    do_test(state_update_cth, "ct_cth_fail_one_skip_one_SUITE.erl",
 
192
            [state_update_cth,state_update_cth],Config).
 
193
 
 
194
options_cth(Config) when is_list(Config) ->
 
195
    do_test(options_cth, "ct_cth_empty_SUITE.erl",
 
196
            [{empty_cth,[test]}],Config).
 
197
    
 
198
same_id_cth(Config) when is_list(Config) ->
 
199
    do_test(same_id_cth, "ct_cth_empty_SUITE.erl",
 
200
            [same_id_cth,same_id_cth],Config).
 
201
 
 
202
fail_n_skip_with_minimal_cth(Config) when is_list(Config) ->
 
203
    do_test(fail_n_skip_with_minimal_cth, "ct_cth_fail_one_skip_one_SUITE.erl",
 
204
            [minimal_terminate_cth],Config).
 
205
 
 
206
%%%-----------------------------------------------------------------
 
207
%%% HELP FUNCTIONS
 
208
%%%-----------------------------------------------------------------
 
209
 
 
210
do_test(Tag, SWC, CTHs, Config) ->
 
211
    do_test(Tag, SWC, CTHs, Config, ok).
 
212
do_test(Tag, SWC, CTHs, Config, {error,_} = Res) ->
 
213
    do_test(Tag, SWC, CTHs, Config, Res, 1);
 
214
do_test(Tag, SWC, CTHs, Config, Res) ->
 
215
    do_test(Tag, SWC, CTHs, Config, Res, 2).
 
216
 
 
217
do_test(Tag, SuiteWildCard, CTHs, Config, Res, EC) ->
 
218
    
 
219
    DataDir = ?config(data_dir, Config),
 
220
    Suites = filelib:wildcard(
 
221
               filename:join([DataDir,"cth/tests",SuiteWildCard])),
 
222
    {Opts,ERPid} = setup([{suite,Suites},
 
223
                          {ct_hooks,CTHs},{label,Tag}], Config),
 
224
    Res = ct_test_support:run(Opts, Config),
 
225
    Events = ct_test_support:get_events(ERPid, Config),
 
226
 
 
227
    ct_test_support:log_events(Tag, 
 
228
                               reformat(Events, ?eh), 
 
229
                               ?config(priv_dir, Config)),
 
230
 
 
231
    TestEvents = events_to_check(Tag, EC),
 
232
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
233
 
 
234
setup(Test, Config) ->
 
235
    Opts0 = ct_test_support:get_opts(Config),
 
236
    Level = ?config(trace_level, Config),
 
237
    EvHArgs = [{cbm,ct_test_support},{trace_level,Level}],
 
238
    Opts = Opts0 ++ [{event_handler,{?eh,EvHArgs}}|Test],
 
239
    ERPid = ct_test_support:start_event_receiver(Config),
 
240
    {Opts,ERPid}.
 
241
 
 
242
reformat(Events, EH) ->
 
243
    ct_test_support:reformat(Events, EH).
 
244
%reformat(Events, _EH) ->
 
245
%    Events.
 
246
 
 
247
%%%-----------------------------------------------------------------
 
248
%%% TEST EVENTS
 
249
%%%-----------------------------------------------------------------
 
250
events_to_check(Test) ->
 
251
    %% 2 tests (ct:run_test + script_start) is default
 
252
    events_to_check(Test, 2).
 
253
 
 
254
events_to_check(_, 0) ->
 
255
    [];
 
256
events_to_check(Test, N) ->
 
257
    test_events(Test) ++ events_to_check(Test, N-1).
 
258
 
 
259
test_events(one_empty_cth) ->
 
260
    [
 
261
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
262
     {?eh,cth,{empty_cth,id,[[]]}},
 
263
     {?eh,cth,{empty_cth,init,[{'_','_','_'},[]]}},
 
264
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
265
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
266
     {?eh,cth,{empty_cth,pre_init_per_suite,
 
267
               [ct_cth_empty_SUITE,'$proplist',[]]}},
 
268
     {?eh,cth,{empty_cth,post_init_per_suite,
 
269
               [ct_cth_empty_SUITE,'$proplist','$proplist',[]]}},
 
270
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,ok}},
 
271
 
 
272
     {?eh,tc_start,{ct_cth_empty_SUITE,test_case}},
 
273
     {?eh,cth,{empty_cth,pre_init_per_testcase,[test_case,'$proplist',[]]}},
 
274
     {?eh,cth,{empty_cth,post_end_per_testcase,[test_case,'$proplist','_',[]]}},
 
275
     {?eh,tc_done,{ct_cth_empty_SUITE,test_case,ok}},
 
276
     
 
277
     {?eh,tc_start,{ct_cth_empty_SUITE,end_per_suite}},
 
278
     {?eh,cth,{empty_cth,pre_end_per_suite,
 
279
               [ct_cth_empty_SUITE,'$proplist',[]]}},
 
280
     {?eh,cth,{empty_cth,post_end_per_suite,[ct_cth_empty_SUITE,'$proplist','_',[]]}},
 
281
     {?eh,tc_done,{ct_cth_empty_SUITE,end_per_suite,ok}},
 
282
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
283
     {?eh,cth,{empty_cth,terminate,[[]]}},
 
284
     {?eh,stop_logging,[]}
 
285
    ];
 
286
 
 
287
test_events(two_empty_cth) ->
 
288
    [
 
289
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
290
     {?eh,cth,{'_',id,[[]]}},
 
291
     {?eh,cth,{'_',init,['_',[]]}},
 
292
     {?eh,cth,{'_',id,[[]]}},
 
293
     {?eh,cth,{'_',init,['_',[]]}},
 
294
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
295
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
296
     {?eh,cth,{'_',pre_init_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
297
     {?eh,cth,{'_',pre_init_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
298
     {?eh,cth,{'_',post_init_per_suite,[ct_cth_empty_SUITE,'$proplist','$proplist',[]]}},
 
299
     {?eh,cth,{'_',post_init_per_suite,[ct_cth_empty_SUITE,'$proplist','$proplist',[]]}},
 
300
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,ok}},
 
301
 
 
302
     {?eh,tc_start,{ct_cth_empty_SUITE,test_case}},
 
303
     {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[]]}},
 
304
     {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[]]}},
 
305
     {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[]]}},
 
306
     {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[]]}},
 
307
     {?eh,tc_done,{ct_cth_empty_SUITE,test_case,ok}},
 
308
     
 
309
     {?eh,tc_start,{ct_cth_empty_SUITE,end_per_suite}},
 
310
     {?eh,cth,{'_',pre_end_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
311
     {?eh,cth,{'_',pre_end_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
312
     {?eh,cth,{'_',post_end_per_suite,[ct_cth_empty_SUITE,'$proplist','_',[]]}},
 
313
     {?eh,cth,{'_',post_end_per_suite,[ct_cth_empty_SUITE,'$proplist','_',[]]}},
 
314
     {?eh,tc_done,{ct_cth_empty_SUITE,end_per_suite,ok}},
 
315
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
316
     {?eh,cth,{'_',terminate,[[]]}},
 
317
     {?eh,cth,{'_',terminate,[[]]}},
 
318
     {?eh,stop_logging,[]}
 
319
    ];
 
320
 
 
321
test_events(faulty_cth_no_init) ->
 
322
    [
 
323
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
324
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
325
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
326
     {?eh,stop_logging,[]}
 
327
    ];
 
328
 
 
329
test_events(faulty_cth_id_no_init) ->
 
330
    [
 
331
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
332
     {?eh,cth,{'_',id,[[]]}},
 
333
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
334
     {negative,{?eh,tc_start,'_'},
 
335
      {?eh,test_done,{'DEF','STOP_TIME'}}},
 
336
     {?eh,stop_logging,[]}
 
337
    ];
 
338
 
 
339
test_events(minimal_cth) ->
 
340
    [
 
341
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
342
     {negative,{?eh,cth,{'_',id,['_',[]]}},
 
343
      {?eh,cth,{'_',init,['_',[]]}}},
 
344
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
345
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
346
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,ok}},
 
347
 
 
348
     {?eh,tc_start,{ct_cth_empty_SUITE,test_case}},
 
349
     {?eh,tc_done,{ct_cth_empty_SUITE,test_case,ok}},
 
350
     
 
351
     {?eh,tc_start,{ct_cth_empty_SUITE,end_per_suite}},
 
352
     {?eh,tc_done,{ct_cth_empty_SUITE,end_per_suite,ok}},
 
353
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
354
     {?eh,stop_logging,[]}
 
355
    ];
 
356
 
 
357
test_events(minimal_and_maximal_cth) ->
 
358
    [
 
359
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
360
     {negative,{?eh,cth,{'_',id,['_',[]]}},
 
361
      {?eh,cth,{'_',init,['_',[]]}}},
 
362
     {?eh,cth,{'_',id,[[]]}},
 
363
     {?eh,cth,{'_',init,['_',[]]}},
 
364
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
365
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
366
     {?eh,cth,{'_',pre_init_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
367
     {?eh,cth,{'_',post_init_per_suite,[ct_cth_empty_SUITE,'$proplist','$proplist',[]]}},
 
368
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,ok}},
 
369
 
 
370
     {?eh,tc_start,{ct_cth_empty_SUITE,test_case}},
 
371
     {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[]]}},
 
372
     {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[]]}},
 
373
     {?eh,tc_done,{ct_cth_empty_SUITE,test_case,ok}},
 
374
     
 
375
     {?eh,tc_start,{ct_cth_empty_SUITE,end_per_suite}},
 
376
     {?eh,cth,{'_',pre_end_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
377
     {?eh,cth,{'_',post_end_per_suite,[ct_cth_empty_SUITE,'$proplist','_',[]]}},
 
378
     {?eh,tc_done,{ct_cth_empty_SUITE,end_per_suite,ok}},
 
379
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
380
     {?eh,cth,{'_',terminate,[[]]}},
 
381
     {?eh,stop_logging,[]}
 
382
    ];
 
383
 
 
384
test_events(faulty_cth_undef) ->
 
385
    FailReasonStr = "undef_cth:pre_init_per_suite/3 CTH call failed",
 
386
    FailReason = {ct_cth_empty_SUITE,init_per_suite,
 
387
                  {failed,FailReasonStr}},
 
388
    [
 
389
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
390
     {?eh,cth,{'_',init,['_',[]]}},
 
391
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
392
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
393
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,
 
394
                  {failed, {error,FailReasonStr}}}},
 
395
     {?eh,cth,{'_',on_tc_fail,'_'}},
 
396
 
 
397
     {?eh,tc_auto_skip,{ct_cth_empty_SUITE,test_case,
 
398
                        {failed, FailReason}}},
 
399
     {?eh,cth,{'_',on_tc_skip,'_'}},
 
400
     
 
401
     {?eh,tc_auto_skip,{ct_cth_empty_SUITE,end_per_suite,
 
402
                        {failed, FailReason}}},
 
403
     {?eh,cth,{'_',on_tc_skip,'_'}},
 
404
     
 
405
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
406
     {?eh,stop_logging,[]}
 
407
    ];
 
408
 
 
409
test_events(faulty_cth_exit_in_init_scope_suite) ->
 
410
    [{?eh,start_logging,{'DEF','RUNDIR'}},
 
411
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
412
     {?eh,tc_start,{'_',init_per_suite}},
 
413
     {?eh,cth,{empty_cth,init,['_',[]]}},
 
414
     {?eh,tc_done,
 
415
      {ct_exit_in_init_scope_suite_cth_SUITE,init_per_suite,
 
416
       {failed,
 
417
        {error,
 
418
         "Failed to start CTH, see the CT Log for details"}}}},
 
419
     {?eh,tc_auto_skip,
 
420
      {ct_exit_in_init_scope_suite_cth_SUITE,test_case,
 
421
       {failed,
 
422
        {ct_exit_in_init_scope_suite_cth_SUITE,init_per_suite,
 
423
         {failed,
 
424
          "Failed to start CTH, see the CT Log for details"}}}}},
 
425
     {?eh,tc_auto_skip,
 
426
      {ct_exit_in_init_scope_suite_cth_SUITE,end_per_suite,
 
427
       {failed,
 
428
        {ct_exit_in_init_scope_suite_cth_SUITE,init_per_suite,
 
429
         {failed,
 
430
          "Failed to start CTH, see the CT Log for details"}}}}},
 
431
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
432
     {?eh,stop_logging,[]}];
 
433
 
 
434
test_events(faulty_cth_exit_in_init) ->
 
435
    [{?eh,start_logging,{'DEF','RUNDIR'}},
 
436
     {?eh,cth,{empty_cth,init,['_',[]]}},
 
437
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
438
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
439
     {?eh,stop_logging,[]}];
 
440
 
 
441
test_events(faulty_cth_exit_in_id) ->
 
442
    [{?eh,start_logging,{'DEF','RUNDIR'}},
 
443
     {?eh,cth,{empty_cth,id,[[]]}},
 
444
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
445
     {negative, {?eh,tc_start,'_'},
 
446
      {?eh,test_done,{'DEF','STOP_TIME'}}},
 
447
     {?eh,stop_logging,[]}];
 
448
 
 
449
test_events(scope_per_suite_cth) ->
 
450
    [
 
451
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
452
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
453
     {?eh,tc_start,{ct_scope_per_suite_cth_SUITE,init_per_suite}},
 
454
     {?eh,cth,{'_',id,[[]]}},
 
455
     {?eh,cth,{'_',init,['_',[]]}},
 
456
     {?eh,cth,{'_',post_init_per_suite,[ct_scope_per_suite_cth_SUITE,'$proplist','$proplist',[]]}},
 
457
     {?eh,tc_done,{ct_scope_per_suite_cth_SUITE,init_per_suite,ok}},
 
458
 
 
459
     {?eh,tc_start,{ct_scope_per_suite_cth_SUITE,test_case}},
 
460
     {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[]]}},
 
461
     {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[]]}},
 
462
     {?eh,tc_done,{ct_scope_per_suite_cth_SUITE,test_case,ok}},
 
463
     
 
464
     {?eh,tc_start,{ct_scope_per_suite_cth_SUITE,end_per_suite}},
 
465
     {?eh,cth,{'_',pre_end_per_suite,
 
466
               [ct_scope_per_suite_cth_SUITE,'$proplist',[]]}},
 
467
     {?eh,cth,{'_',post_end_per_suite,[ct_scope_per_suite_cth_SUITE,'$proplist','_',[]]}},
 
468
     {?eh,cth,{'_',terminate,[[]]}},
 
469
     {?eh,tc_done,{ct_scope_per_suite_cth_SUITE,end_per_suite,ok}},
 
470
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
471
     {?eh,stop_logging,[]}
 
472
    ];
 
473
 
 
474
test_events(scope_suite_cth) ->
 
475
    [
 
476
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
477
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
478
     {?eh,tc_start,{ct_scope_suite_cth_SUITE,init_per_suite}},
 
479
     {?eh,cth,{'_',id,[[]]}},
 
480
     {?eh,cth,{'_',init,['_',[]]}},
 
481
     {?eh,cth,{'_',pre_init_per_suite,[ct_scope_suite_cth_SUITE,'$proplist',[]]}},
 
482
     {?eh,cth,{'_',post_init_per_suite,[ct_scope_suite_cth_SUITE,'$proplist','$proplist',[]]}},
 
483
     {?eh,tc_done,{ct_scope_suite_cth_SUITE,init_per_suite,ok}},
 
484
 
 
485
     {?eh,tc_start,{ct_scope_suite_cth_SUITE,test_case}},
 
486
     {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[]]}},
 
487
     {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[]]}},
 
488
     {?eh,tc_done,{ct_scope_suite_cth_SUITE,test_case,ok}},
 
489
     
 
490
     {?eh,tc_start,{ct_scope_suite_cth_SUITE,end_per_suite}},
 
491
     {?eh,cth,{'_',pre_end_per_suite,[ct_scope_suite_cth_SUITE,'$proplist',[]]}},
 
492
     {?eh,cth,{'_',post_end_per_suite,[ct_scope_suite_cth_SUITE,'$proplist','_',[]]}},
 
493
     {?eh,cth,{'_',terminate,[[]]}},
 
494
     {?eh,tc_done,{ct_scope_suite_cth_SUITE,end_per_suite,ok}},
 
495
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
496
     {?eh,stop_logging,[]}
 
497
    ];
 
498
 
 
499
test_events(scope_per_group_cth) ->
 
500
    [
 
501
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
502
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
503
     {?eh,tc_start,{ct_scope_per_group_cth_SUITE,init_per_suite}},
 
504
     {?eh,tc_done,{ct_scope_per_group_cth_SUITE,init_per_suite,ok}},
 
505
 
 
506
     [{?eh,tc_start,{ct_scope_per_group_cth_SUITE,{init_per_group,group1,[]}}},
 
507
      {?eh,cth,{'_',id,[[]]}},
 
508
      {?eh,cth,{'_',init,['_',[]]}},
 
509
      {?eh,cth,{'_',post_init_per_group,[group1,'$proplist','$proplist',[]]}},
 
510
      {?eh,tc_done,{ct_scope_per_group_cth_SUITE,{init_per_group,group1,[]},ok}},
 
511
      
 
512
      {?eh,tc_start,{ct_scope_per_group_cth_SUITE,test_case}},
 
513
      {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[]]}},
 
514
      {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[]]}},
 
515
      {?eh,tc_done,{ct_scope_per_group_cth_SUITE,test_case,ok}},
 
516
      
 
517
      {?eh,tc_start,{ct_scope_per_group_cth_SUITE,{end_per_group,group1,[]}}},
 
518
      {?eh,cth,{'_',pre_end_per_group,[group1,'$proplist',[]]}},
 
519
      {?eh,cth,{'_',post_end_per_group,[group1,'$proplist','_',[]]}},
 
520
      {?eh,cth,{'_',terminate,[[]]}},
 
521
      {?eh,tc_done,{ct_scope_per_group_cth_SUITE,{end_per_group,group1,[]},ok}}],
 
522
     
 
523
     {?eh,tc_start,{ct_scope_per_group_cth_SUITE,end_per_suite}},
 
524
     {?eh,tc_done,{ct_scope_per_group_cth_SUITE,end_per_suite,ok}},
 
525
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
526
     {?eh,stop_logging,[]}
 
527
    ];
 
528
 
 
529
test_events(scope_per_suite_state_cth) ->
 
530
    [
 
531
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
532
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
533
     {?eh,tc_start,{ct_scope_per_suite_state_cth_SUITE,init_per_suite}},
 
534
     {?eh,cth,{'_',id,[[test]]}},
 
535
     {?eh,cth,{'_',init,['_',[test]]}},
 
536
     {?eh,cth,{'_',post_init_per_suite,[ct_scope_per_suite_state_cth_SUITE,'$proplist','$proplist',[test]]}},
 
537
     {?eh,tc_done,{ct_scope_per_suite_state_cth_SUITE,init_per_suite,ok}},
 
538
 
 
539
     {?eh,tc_start,{ct_scope_per_suite_state_cth_SUITE,test_case}},
 
540
     {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[test]]}},
 
541
     {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[test]]}},
 
542
     {?eh,tc_done,{ct_scope_per_suite_state_cth_SUITE,test_case,ok}},
 
543
     
 
544
     {?eh,tc_start,{ct_scope_per_suite_state_cth_SUITE,end_per_suite}},
 
545
     {?eh,cth,{'_',pre_end_per_suite,
 
546
               [ct_scope_per_suite_state_cth_SUITE,'$proplist',[test]]}},
 
547
     {?eh,cth,{'_',post_end_per_suite,[ct_scope_per_suite_state_cth_SUITE,'$proplist','_',[test]]}},
 
548
     {?eh,cth,{'_',terminate,[[test]]}},
 
549
     {?eh,tc_done,{ct_scope_per_suite_state_cth_SUITE,end_per_suite,ok}},
 
550
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
551
     {?eh,stop_logging,[]}
 
552
    ];
 
553
 
 
554
test_events(scope_suite_state_cth) ->
 
555
    [
 
556
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
557
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
558
     {?eh,tc_start,{ct_scope_suite_state_cth_SUITE,init_per_suite}},
 
559
     {?eh,cth,{'_',id,[[test]]}},
 
560
     {?eh,cth,{'_',init,['_',[test]]}},
 
561
     {?eh,cth,{'_',pre_init_per_suite,[ct_scope_suite_state_cth_SUITE,'$proplist',[test]]}},
 
562
     {?eh,cth,{'_',post_init_per_suite,[ct_scope_suite_state_cth_SUITE,'$proplist','$proplist',[test]]}},
 
563
     {?eh,tc_done,{ct_scope_suite_state_cth_SUITE,init_per_suite,ok}},
 
564
 
 
565
     {?eh,tc_start,{ct_scope_suite_state_cth_SUITE,test_case}},
 
566
     {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[test]]}},
 
567
     {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[test]]}},
 
568
     {?eh,tc_done,{ct_scope_suite_state_cth_SUITE,test_case,ok}},
 
569
     
 
570
     {?eh,tc_start,{ct_scope_suite_state_cth_SUITE,end_per_suite}},
 
571
     {?eh,cth,{'_',pre_end_per_suite,[ct_scope_suite_state_cth_SUITE,'$proplist',[test]]}},
 
572
     {?eh,cth,{'_',post_end_per_suite,[ct_scope_suite_state_cth_SUITE,'$proplist','_',[test]]}},
 
573
     {?eh,cth,{'_',terminate,[[test]]}},
 
574
     {?eh,tc_done,{ct_scope_suite_state_cth_SUITE,end_per_suite,ok}},
 
575
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
576
     {?eh,stop_logging,[]}
 
577
    ];
 
578
 
 
579
test_events(scope_per_group_state_cth) ->
 
580
    [
 
581
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
582
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
583
     {?eh,tc_start,{ct_scope_per_group_state_cth_SUITE,init_per_suite}},
 
584
     {?eh,tc_done,{ct_scope_per_group_state_cth_SUITE,init_per_suite,ok}},
 
585
 
 
586
     [{?eh,tc_start,{ct_scope_per_group_state_cth_SUITE,{init_per_group,group1,[]}}},
 
587
      {?eh,cth,{'_',id,[[test]]}},
 
588
      {?eh,cth,{'_',init,['_',[test]]}},
 
589
      {?eh,cth,{'_',post_init_per_group,[group1,'$proplist','$proplist',[test]]}},
 
590
      {?eh,tc_done,{ct_scope_per_group_state_cth_SUITE,{init_per_group,group1,[]},ok}},
 
591
      
 
592
      {?eh,tc_start,{ct_scope_per_group_state_cth_SUITE,test_case}},
 
593
      {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[test]]}},
 
594
      {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[test]]}},
 
595
      {?eh,tc_done,{ct_scope_per_group_state_cth_SUITE,test_case,ok}},
 
596
      
 
597
      {?eh,tc_start,{ct_scope_per_group_state_cth_SUITE,{end_per_group,group1,[]}}},
 
598
      {?eh,cth,{'_',pre_end_per_group,[group1,'$proplist',[test]]}},
 
599
      {?eh,cth,{'_',post_end_per_group,[group1,'$proplist','_',[test]]}},
 
600
      {?eh,cth,{'_',terminate,[[test]]}},
 
601
      {?eh,tc_done,{ct_scope_per_group_state_cth_SUITE,{end_per_group,group1,[]},ok}}],
 
602
     
 
603
     {?eh,tc_start,{ct_scope_per_group_state_cth_SUITE,end_per_suite}},
 
604
     {?eh,tc_done,{ct_scope_per_group_state_cth_SUITE,end_per_suite,ok}},
 
605
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
606
     {?eh,stop_logging,[]}
 
607
    ];
 
608
 
 
609
test_events(fail_pre_suite_cth) ->
 
610
    [
 
611
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
612
     {?eh,cth,{'_',init,['_',[]]}},
 
613
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
614
 
 
615
     
 
616
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
617
     {?eh,cth,{'_',pre_init_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
618
     {?eh,cth,{'_',post_init_per_suite,[ct_cth_empty_SUITE,'$proplist',
 
619
                                        {fail,"Test failure"},[]]}},
 
620
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,
 
621
                   {failed, {error,"Test failure"}}}},
 
622
     {?eh,cth,{'_',on_tc_fail,
 
623
               [init_per_suite,{failed,"Test failure"},[]]}},
 
624
 
 
625
     
 
626
     {?eh,tc_auto_skip,{ct_cth_empty_SUITE,test_case,
 
627
                        {failed,{ct_cth_empty_SUITE,init_per_suite,
 
628
                                 {failed,"Test failure"}}}}},
 
629
     {?eh,cth,{'_',on_tc_skip,
 
630
               [test_case, {tc_auto_skip,
 
631
                            {failed, {ct_cth_empty_SUITE, init_per_suite,
 
632
                                     {failed, "Test failure"}}}},[]]}},
 
633
 
 
634
     
 
635
     {?eh,tc_auto_skip, {ct_cth_empty_SUITE, end_per_suite,
 
636
                         {failed, {ct_cth_empty_SUITE, init_per_suite,
 
637
                                   {failed, "Test failure"}}}}},
 
638
     {?eh,cth,{'_',on_tc_skip,
 
639
               [end_per_suite, {tc_auto_skip,
 
640
                                {failed, {ct_cth_empty_SUITE, init_per_suite,
 
641
                                          {failed, "Test failure"}}}},[]]}},
 
642
 
 
643
     
 
644
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
645
     {?eh,cth, {'_',terminate,[[]]}},
 
646
     {?eh,stop_logging,[]}
 
647
    ];
 
648
 
 
649
test_events(fail_post_suite_cth) ->
 
650
    [
 
651
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
652
     {?eh,cth,{'_',init,['_',[]]}},
 
653
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
654
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
655
     {?eh,cth,{'_',pre_init_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
656
     {?eh,cth,{'_',post_init_per_suite,[ct_cth_empty_SUITE,'$proplist','$proplist',[]]}},
 
657
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,
 
658
                   {failed,{error,"Test failure"}}}},
 
659
     {?eh,cth,{'_',on_tc_fail,[init_per_suite, {failed,"Test failure"}, []]}},
 
660
 
 
661
     {?eh,tc_auto_skip,{ct_cth_empty_SUITE,test_case,
 
662
                        {failed,{ct_cth_empty_SUITE,init_per_suite,
 
663
                                 {failed,"Test failure"}}}}},
 
664
     {?eh,cth,{'_',on_tc_skip,[test_case,{tc_auto_skip,'_'},[]]}},
 
665
     
 
666
     {?eh,tc_auto_skip, {ct_cth_empty_SUITE, end_per_suite,
 
667
                         {failed, {ct_cth_empty_SUITE, init_per_suite,
 
668
                                   {failed, "Test failure"}}}}},
 
669
     {?eh,cth,{'_',on_tc_skip,[end_per_suite,{tc_auto_skip,'_'},[]]}},
 
670
 
 
671
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
672
     {?eh,cth, {'_',terminate,[[]]}},
 
673
     {?eh,stop_logging,[]}
 
674
    ];
 
675
 
 
676
test_events(skip_pre_suite_cth) ->
 
677
    [
 
678
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
679
     {?eh,cth,{'_',init,['_',[]]}},
 
680
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
681
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
682
     {?eh,cth,{'_',pre_init_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
683
     {?eh,cth,{'_',post_init_per_suite,[ct_cth_empty_SUITE,'$proplist',{skip,"Test skip"},[]]}},
 
684
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,{skipped,"Test skip"}}},
 
685
     {?eh,cth,{'_',on_tc_skip,
 
686
               [init_per_suite,{tc_user_skip,{skipped,"Test skip"}},[]]}},
 
687
 
 
688
     {?eh,tc_auto_skip,{ct_cth_empty_SUITE,test_case,"Test skip"}},
 
689
     {?eh,cth,{'_',on_tc_skip,[test_case,{tc_auto_skip,"Test skip"},[]]}},
 
690
     
 
691
     {?eh,tc_auto_skip, {ct_cth_empty_SUITE, end_per_suite,"Test skip"}},
 
692
     {?eh,cth,{'_',on_tc_skip,[end_per_suite,{tc_auto_skip,"Test skip"},[]]}},
 
693
 
 
694
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
695
     {?eh,cth, {'_',terminate,[[]]}},
 
696
     {?eh,stop_logging,[]}
 
697
    ];
 
698
 
 
699
test_events(skip_post_suite_cth) ->
 
700
    [
 
701
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
702
     {?eh,cth,{'_',init,['_',[]]}},
 
703
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
704
     
 
705
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
706
     {?eh,cth,{'_',pre_init_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
707
     {?eh,cth,{'_',post_init_per_suite,[ct_cth_empty_SUITE,'$proplist','$proplist',[]]}},
 
708
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,{skipped,"Test skip"}}},
 
709
     {?eh,cth,{'_',on_tc_skip,
 
710
               [init_per_suite,{tc_user_skip,{skipped,"Test skip"}},[]]}},
 
711
 
 
712
     {?eh,tc_auto_skip,{ct_cth_empty_SUITE,test_case,"Test skip"}},
 
713
     {?eh,cth,{'_',on_tc_skip,[test_case,{tc_auto_skip,"Test skip"},[]]}},
 
714
     
 
715
     {?eh,tc_auto_skip, {ct_cth_empty_SUITE, end_per_suite,"Test skip"}},
 
716
     {?eh,cth,{'_',on_tc_skip,[end_per_suite,{tc_auto_skip,"Test skip"},[]]}},
 
717
     
 
718
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
719
     {?eh,cth,{'_',terminate,[[]]}},
 
720
     {?eh,stop_logging,[]}
 
721
    ];
 
722
 
 
723
test_events(recover_post_suite_cth) ->
 
724
    Suite = ct_cth_fail_per_suite_SUITE,
 
725
    [
 
726
     {?eh,start_logging,'_'},
 
727
     {?eh,cth,{'_',init,['_',[]]}},
 
728
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
729
     {?eh,tc_start,{Suite,init_per_suite}},
 
730
     {?eh,cth,{'_',pre_init_per_suite,[Suite,'$proplist','$proplist']}},
 
731
     {?eh,cth,{'_',post_init_per_suite,[Suite,contains([tc_status]),
 
732
                                        {'EXIT',{'_','_'}},[]]}},
 
733
     {?eh,tc_done,{Suite,init_per_suite,ok}},
 
734
 
 
735
     {?eh,tc_start,{Suite,test_case}},
 
736
     {?eh,cth,{'_',pre_init_per_testcase,
 
737
               [test_case, not_contains([tc_status]),[]]}},
 
738
     {?eh,cth,{'_',post_end_per_testcase,
 
739
               [test_case, contains([tc_status]),'_',[]]}},
 
740
     {?eh,tc_done,{Suite,test_case,ok}},
 
741
     
 
742
     {?eh,tc_start,{Suite,end_per_suite}},
 
743
     {?eh,cth,{'_',pre_end_per_suite,
 
744
               [Suite,not_contains([tc_status]),[]]}},
 
745
     {?eh,cth,{'_',post_end_per_suite,
 
746
               [Suite,not_contains([tc_status]),'_',[]]}},
 
747
     {?eh,tc_done,{Suite,end_per_suite,ok}},
 
748
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
749
     {?eh,cth,{'_',terminate,[[]]}},
 
750
     {?eh,stop_logging,[]}
 
751
    ];
 
752
 
 
753
test_events(update_config_cth) ->
 
754
    [
 
755
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
756
     {?eh,cth,{'_',init,['_',[]]}},
 
757
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
758
     
 
759
     {?eh,tc_start,{ct_update_config_SUITE,init_per_suite}},
 
760
     {?eh,cth,{'_',pre_init_per_suite,
 
761
               [ct_update_config_SUITE,contains([]),[]]}},
 
762
     {?eh,cth,{'_',post_init_per_suite,
 
763
               [ct_update_config_SUITE,
 
764
                '$proplist',
 
765
                contains(
 
766
                          [init_per_suite,
 
767
                           pre_init_per_suite]),
 
768
                []]}},
 
769
     {?eh,tc_done,{ct_update_config_SUITE,init_per_suite,ok}},
 
770
 
 
771
     {?eh,tc_start,{ct_update_config_SUITE, {init_per_group,group1,[]}}},
 
772
     {?eh,cth,{'_',pre_init_per_group,
 
773
               [group1,contains(
 
774
                         [post_init_per_suite,
 
775
                          init_per_suite,
 
776
                          pre_init_per_suite]),
 
777
                []]}},
 
778
     {?eh,cth,{'_',post_init_per_group,
 
779
               [group1,
 
780
                contains(
 
781
                  [post_init_per_suite,
 
782
                   init_per_suite,
 
783
                   pre_init_per_suite]),
 
784
                contains(
 
785
                  [init_per_group,
 
786
                   pre_init_per_group,
 
787
                   post_init_per_suite,
 
788
                   init_per_suite,
 
789
                   pre_init_per_suite]),
 
790
               []]}},
 
791
     {?eh,tc_done,{ct_update_config_SUITE,{init_per_group,group1,[]},ok}},
 
792
 
 
793
     {?eh,tc_start,{ct_update_config_SUITE,test_case}},
 
794
     {?eh,cth,{'_',pre_init_per_testcase,
 
795
               [test_case,contains(
 
796
                            [post_init_per_group,
 
797
                             init_per_group,
 
798
                             pre_init_per_group,
 
799
                             post_init_per_suite,
 
800
                             init_per_suite,
 
801
                             pre_init_per_suite]),
 
802
                []]}},
 
803
     {?eh,cth,{'_',post_end_per_testcase,
 
804
               [test_case,contains(
 
805
                            [init_per_testcase,
 
806
                             pre_init_per_testcase,
 
807
                             post_init_per_group,
 
808
                             init_per_group,
 
809
                             pre_init_per_group,
 
810
                             post_init_per_suite,
 
811
                             init_per_suite,
 
812
                             pre_init_per_suite]),
 
813
                ok,[]]}},
 
814
     {?eh,tc_done,{ct_update_config_SUITE,test_case,ok}},
 
815
 
 
816
     {?eh,tc_start,{ct_update_config_SUITE, {end_per_group,group1,[]}}},
 
817
     {?eh,cth,{'_',pre_end_per_group,
 
818
               [group1,contains(
 
819
                         [post_init_per_group,
 
820
                          init_per_group,
 
821
                          pre_init_per_group,
 
822
                          post_init_per_suite,
 
823
                          init_per_suite,
 
824
                          pre_init_per_suite]),
 
825
                []]}},
 
826
     {?eh,cth,{'_',post_end_per_group,
 
827
               [group1,
 
828
                contains(
 
829
                  [pre_end_per_group,
 
830
                   post_init_per_group,
 
831
                   init_per_group,
 
832
                   pre_init_per_group,
 
833
                   post_init_per_suite,
 
834
                   init_per_suite,
 
835
                   pre_init_per_suite]),
 
836
               ok,[]]}},
 
837
     {?eh,tc_done,{ct_update_config_SUITE,{end_per_group,group1,[]},ok}},
 
838
     
 
839
     {?eh,tc_start,{ct_update_config_SUITE,end_per_suite}},
 
840
     {?eh,cth,{'_',pre_end_per_suite,
 
841
               [ct_update_config_SUITE,contains(
 
842
                                         [post_init_per_suite,
 
843
                                          init_per_suite,
 
844
                                          pre_init_per_suite]),
 
845
                []]}},
 
846
     {?eh,cth,{'_',post_end_per_suite,
 
847
               [ct_update_config_SUITE,contains(
 
848
                                         [pre_end_per_suite,
 
849
                                          post_init_per_suite,
 
850
                                          init_per_suite,
 
851
                                          pre_init_per_suite]),
 
852
               '_',[]]}},
 
853
     {?eh,tc_done,{ct_update_config_SUITE,end_per_suite,ok}},
 
854
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
855
     {?eh,cth,{'_',terminate,[contains(
 
856
                                [post_end_per_suite,
 
857
                                 pre_end_per_suite,
 
858
                                 post_init_per_suite,
 
859
                                 init_per_suite,
 
860
                                 pre_init_per_suite])]}},
 
861
     {?eh,stop_logging,[]}
 
862
    ];
 
863
 
 
864
test_events(state_update_cth) ->
 
865
    [
 
866
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
867
     {?eh,cth,{'_',init,['_',[]]}},
 
868
     {?eh,cth,{'_',init,['_',[]]}},
 
869
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
870
     {?eh,tc_start,{'_',init_per_suite}},
 
871
     
 
872
     {?eh,tc_done,{'_',end_per_suite,ok}},
 
873
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
874
     {?eh,cth,{'_',terminate,[contains(
 
875
                                [post_end_per_suite,pre_end_per_suite,
 
876
                                 post_end_per_group,pre_end_per_group,
 
877
                                 {not_in_order,
 
878
                                  [post_end_per_testcase,pre_init_per_testcase,
 
879
                                   on_tc_skip,post_end_per_testcase,
 
880
                                   pre_init_per_testcase,on_tc_fail,
 
881
                                   post_end_per_testcase,pre_init_per_testcase]
 
882
                                 },
 
883
                                 post_init_per_group,pre_init_per_group,
 
884
                                 post_init_per_suite,pre_init_per_suite,
 
885
                                 init])]}},
 
886
     {?eh,cth,{'_',terminate,[contains(
 
887
                                [post_end_per_suite,pre_end_per_suite,
 
888
                                 post_end_per_group,pre_end_per_group,
 
889
                                 {not_in_order,
 
890
                                  [post_end_per_testcase,pre_init_per_testcase,
 
891
                                   on_tc_skip,post_end_per_testcase,
 
892
                                   pre_init_per_testcase,on_tc_fail,
 
893
                                   post_end_per_testcase,pre_init_per_testcase]
 
894
                                 },
 
895
                                 post_init_per_group,pre_init_per_group,
 
896
                                 post_init_per_suite,pre_init_per_suite,
 
897
                                 init]
 
898
                               )]}},
 
899
     {?eh,stop_logging,[]}
 
900
    ];
 
901
 
 
902
test_events(options_cth) ->
 
903
    [
 
904
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
905
     {?eh,cth,{empty_cth,init,['_',[test]]}},
 
906
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
907
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
908
     {?eh,cth,{empty_cth,pre_init_per_suite,
 
909
               [ct_cth_empty_SUITE,'$proplist',[test]]}},
 
910
     {?eh,cth,{empty_cth,post_init_per_suite,
 
911
               [ct_cth_empty_SUITE,'$proplist','$proplist',[test]]}},
 
912
     {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,ok}},
 
913
 
 
914
     {?eh,tc_start,{ct_cth_empty_SUITE,test_case}},
 
915
     {?eh,cth,{empty_cth,pre_init_per_testcase,[test_case,'$proplist',[test]]}},
 
916
     {?eh,cth,{empty_cth,post_end_per_testcase,[test_case,'$proplist','_',[test]]}},
 
917
     {?eh,tc_done,{ct_cth_empty_SUITE,test_case,ok}},
 
918
     
 
919
     {?eh,tc_start,{ct_cth_empty_SUITE,end_per_suite}},
 
920
     {?eh,cth,{empty_cth,pre_end_per_suite,
 
921
               [ct_cth_empty_SUITE,'$proplist',[test]]}},
 
922
     {?eh,cth,{empty_cth,post_end_per_suite,[ct_cth_empty_SUITE,'$proplist','_',[test]]}},
 
923
     {?eh,tc_done,{ct_cth_empty_SUITE,end_per_suite,ok}},
 
924
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
925
     {?eh,cth,{empty_cth,terminate,[[test]]}},
 
926
     {?eh,stop_logging,[]}
 
927
    ];
 
928
 
 
929
test_events(same_id_cth) ->
 
930
    [
 
931
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
932
     {?eh,cth,{'_',id,[[]]}},
 
933
     {?eh,cth,{'_',init,[same_id_cth,[]]}},
 
934
     {?eh,cth,{'_',id,[[]]}},
 
935
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
936
     {?eh,tc_start,{ct_cth_empty_SUITE,init_per_suite}},
 
937
     {?eh,cth,{'_',pre_init_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
938
     {negative,
 
939
       {?eh,cth,{'_',pre_init_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
940
      {?eh,cth,{'_',post_init_per_suite,
 
941
                [ct_cth_empty_SUITE,'$proplist','$proplist',[]]}}},
 
942
     {negative,
 
943
      {?eh,cth,{'_',post_init_per_suite,
 
944
                [ct_cth_empty_SUITE,'$proplist','$proplist',[]]}},
 
945
      {?eh,tc_done,{ct_cth_empty_SUITE,init_per_suite,ok}}},
 
946
 
 
947
     {?eh,tc_start,{ct_cth_empty_SUITE,test_case}},
 
948
     {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[]]}},
 
949
     {negative,
 
950
      {?eh,cth,{'_',pre_init_per_testcase,[test_case,'$proplist',[]]}},
 
951
      {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[]]}}},
 
952
     {negative,
 
953
      {?eh,cth,{'_',post_end_per_testcase,[test_case,'$proplist',ok,[]]}},
 
954
      {?eh,tc_done,{ct_cth_empty_SUITE,test_case,ok}}},
 
955
     
 
956
     {?eh,tc_start,{ct_cth_empty_SUITE,end_per_suite}},
 
957
     {?eh,cth,{'_',pre_end_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
958
     {negative,
 
959
      {?eh,cth,{'_',pre_end_per_suite,[ct_cth_empty_SUITE,'$proplist',[]]}},
 
960
      {?eh,cth,{'_',post_end_per_suite,[ct_cth_empty_SUITE,'$proplist','_',[]]}}},
 
961
     {negative,
 
962
      {?eh,cth,{'_',post_end_per_suite,
 
963
                [ct_cth_empty_SUITE,'$proplist','_',[]]}},
 
964
      {?eh,tc_done,{ct_cth_empty_SUITE,end_per_suite,ok}}},
 
965
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
966
     {?eh,cth,{'_',terminate,[[]]}},
 
967
     {?eh,stop_logging,[]}
 
968
    ];
 
969
 
 
970
test_events(fail_n_skip_with_minimal_cth) ->
 
971
    [{?eh,start_logging,{'DEF','RUNDIR'}},
 
972
     {?eh,cth,{'_',init,['_',[]]}},
 
973
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
974
     {?eh,tc_start,{'_',init_per_suite}},
 
975
     
 
976
     {?eh,tc_done,{'_',end_per_suite,ok}},
 
977
     {?eh,cth,{'_',terminate,[[]]}},
 
978
     {?eh,stop_logging,[]}
 
979
    ];
 
980
 
 
981
test_events(ok) ->
 
982
    ok.
 
983
 
 
984
 
 
985
%% test events help functions
 
986
contains(List) ->
 
987
    fun(Proplist) when is_list(Proplist) ->
 
988
            contains(List,Proplist)
 
989
    end.
 
990
 
 
991
contains([{not_in_order,List}|T],Rest) ->
 
992
    contains_parallel(List,Rest),
 
993
    contains(T,Rest);
 
994
contains([{Ele,Pos}|T] = L,[H|T2]) ->
 
995
    case element(Pos,H) of
 
996
        Ele ->
 
997
            contains(T,T2);
 
998
        _ ->
 
999
            contains(L,T2)
 
1000
    end;
 
1001
contains([Ele|T],[{Ele,_}|T2])->
 
1002
    contains(T,T2);
 
1003
contains([Ele|T],[Ele|T2])->
 
1004
    contains(T,T2);
 
1005
contains(List,[_|T]) ->
 
1006
    contains(List,T);
 
1007
contains([],_) ->
 
1008
    match.
 
1009
 
 
1010
contains_parallel([Key | T], Elems) ->
 
1011
    contains([Key],Elems),
 
1012
    contains_parallel(T,Elems);
 
1013
contains_parallel([],_Elems) ->
 
1014
    match.
 
1015
 
 
1016
not_contains(List) ->
 
1017
    fun(Proplist) when is_list(Proplist) ->
 
1018
            [] = [Ele || {Ele,_} <- Proplist,
 
1019
                         Test <- List,
 
1020
                         Test =:= Ele]
 
1021
    end.