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

« back to all changes in this revision

Viewing changes to lib/common_test/test/ct_smoke_test_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 2008-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_smoke_test_SUITE.erl
 
22
%%%
 
23
%%% Description: The purpose of this suite is to test that Common Test
 
24
%%% can be started properly and that simple dummy test suites are
 
25
%%% executed without unexpected crashes or hangings. The suites used
 
26
%%% for the test are located in the data directory.
 
27
%%%-------------------------------------------------------------------
 
28
-module(ct_smoke_test_SUITE).
 
29
 
 
30
-compile(export_all).
 
31
 
 
32
-include_lib("common_test/include/ct.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
%% Function: init_per_suite(Config0) -> Config1 | {skip,Reason}
 
43
%%
 
44
%% Config0 = Config1 = [tuple()]
 
45
%%   A list of key/value pairs, holding the test case configuration.
 
46
%% Reason = term()
 
47
%%   The reason for skipping the suite.
 
48
%%
 
49
%% Description: Since Common Test starts another Test Server
 
50
%% instance, the tests need to be performed on a separate node (or
 
51
%% there will be clashes with logging processes etc).
 
52
%%--------------------------------------------------------------------
 
53
init_per_suite(Config) ->
 
54
    Config1 = ct_test_support:init_per_suite(Config),
 
55
    Config1.
 
56
 
 
57
%%--------------------------------------------------------------------
 
58
%% Function: end_per_suite(Config) -> void()
 
59
%%
 
60
%% Config = [tuple()]
 
61
%%   A list of key/value pairs, holding the test case configuration.
 
62
%%
 
63
%% Description: Cleanup after the suite.
 
64
%%--------------------------------------------------------------------
 
65
end_per_suite(Config) ->
 
66
    ct_test_support:end_per_suite(Config).
 
67
 
 
68
%%--------------------------------------------------------------------
 
69
%% Function: init_per_testcase(TestCase, Config0) -> Config1 |
 
70
%%                                                   {skip,Reason}
 
71
%% TestCase = atom()
 
72
%%   Name of the test case that is about to run.
 
73
%% Config0 = Config1 = [tuple()]
 
74
%%   A list of key/value pairs, holding the test case configuration.
 
75
%% Reason = term()
 
76
%%   The reason for skipping the test case.
 
77
%%
 
78
%% Description: Initialization before each test case.
 
79
%%
 
80
%% Note: This function is free to add any key/value pairs to the Config
 
81
%% variable, but should NOT alter/remove any existing entries.
 
82
%%--------------------------------------------------------------------
 
83
init_per_testcase(TestCase, Config) ->
 
84
    ct_test_support:init_per_testcase(TestCase, Config).
 
85
 
 
86
%%--------------------------------------------------------------------
 
87
%% Function: end_per_testcase(TestCase, Config) -> void()
 
88
%%
 
89
%% TestCase = atom()
 
90
%%   Name of the test case that is finished.
 
91
%% Config = [tuple()]
 
92
%%   A list of key/value pairs, holding the test case configuration.
 
93
%%
 
94
%% Description: Cleanup after each test case.
 
95
%%--------------------------------------------------------------------
 
96
end_per_testcase(TestCase, Config) ->
 
97
    ct_test_support:end_per_testcase(TestCase, Config).
 
98
 
 
99
%%--------------------------------------------------------------------
 
100
%% Function: all(Clause) -> Descr | TestCases | {skip,Reason}
 
101
%%
 
102
%% Clause = doc | suite
 
103
%%   Indicates expected return value.
 
104
%% Descr = [string()] | []
 
105
%%   String that describes the test suite.
 
106
%% TestCases = [TestCase] 
 
107
%% TestCase = atom()
 
108
%%   Name of a test case.
 
109
%% Reason = term()
 
110
%%   The reason for skipping the test suite.
 
111
%%
 
112
%% Description: Returns a description of the test suite (doc) and a
 
113
%%              list of all test cases in the suite (suite).
 
114
%%--------------------------------------------------------------------
 
115
suite() -> [{ct_hooks,[ts_install_cth]}].
 
116
 
 
117
all() -> 
 
118
    [dir1, dir2, dir1_2, suite11, suite21, suite11_21,
 
119
     tc111, tc211, tc111_112].
 
120
 
 
121
groups() -> 
 
122
    [].
 
123
 
 
124
init_per_group(_GroupName, Config) ->
 
125
        Config.
 
126
 
 
127
end_per_group(_GroupName, Config) ->
 
128
        Config.
 
129
 
 
130
 
 
131
 
 
132
%%--------------------------------------------------------------------
 
133
%% TEST CASES
 
134
%%--------------------------------------------------------------------
 
135
 
 
136
%%--------------------------------------------------------------------
 
137
%% Function: TestCase(Arg) -> Descr | Spec | ok | exit() | {skip,Reason}
 
138
%%
 
139
%% Arg = doc | suite | Config
 
140
%%   Indicates expected behaviour and return value.
 
141
%% Config = [tuple()]
 
142
%%   A list of key/value pairs, holding the test case configuration.
 
143
%% Descr = [string()] | []
 
144
%%   String that describes the test case.
 
145
%% Spec = [tuple()] | []
 
146
%%   A test specification.
 
147
%% Reason = term()
 
148
%%   The reason for skipping the test case.
 
149
%%
 
150
%% Description: Test case function. Returns a description of the test
 
151
%%              case (doc), then returns a test specification (suite),
 
152
%%              or performs the actual test (Config).
 
153
%%--------------------------------------------------------------------
 
154
 
 
155
%%%-----------------------------------------------------------------
 
156
%%% 
 
157
 
 
158
dir1(doc) -> 
 
159
    [];
 
160
dir1(suite) -> 
 
161
    [];
 
162
dir1(Config) when is_list(Config) -> 
 
163
    DataDir = ?config(data_dir, Config),
 
164
 
 
165
    Happy1 = filename:join(DataDir, "happy_1"),
 
166
    Happy1Cfg = filename:join(Happy1, "cfg/config1.cfg"),
 
167
 
 
168
    Opts0 = ct_test_support:get_opts(Config),
 
169
    Opts = eh_opts(Config) ++ Opts0 ++ [{config,Happy1Cfg}, {dir,Happy1}],
 
170
 
 
171
    ERPid = ct_test_support:start_event_receiver(Config),
 
172
 
 
173
    ok = ct_test_support:run(Opts, Config),
 
174
 
 
175
    Events = ct_test_support:get_events(ERPid, Config),
 
176
 
 
177
    ct_test_support:log_events(dir1, 
 
178
                               ct_test_support:reformat(Events, ?eh), 
 
179
                               ?config(priv_dir, Config)),
 
180
 
 
181
    TestEvents = events_to_check(dir1),
 
182
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
183
 
 
184
%%%-----------------------------------------------------------------
 
185
%%% 
 
186
 
 
187
dir2(doc) -> 
 
188
    [];
 
189
dir2(suite) -> 
 
190
    [];
 
191
dir2(Config) when is_list(Config) -> 
 
192
    DataDir = ?config(data_dir, Config),
 
193
 
 
194
    Happy2 = filename:join(DataDir, "happy_2_test"),
 
195
    Happy2Cfg = filename:join(DataDir, "happy_2_cfg/config1.cfg"),
 
196
 
 
197
    Opts0 = ct_test_support:get_opts(Config),
 
198
    Opts = eh_opts(Config) ++ Opts0 ++ [{config,Happy2Cfg}, {dir,Happy2}],
 
199
 
 
200
    ERPid = ct_test_support:start_event_receiver(Config),
 
201
 
 
202
    ok = ct_test_support:run(Opts, Config),
 
203
 
 
204
    Events = ct_test_support:get_events(ERPid, Config),
 
205
    
 
206
    ct_test_support:log_events(dir2, 
 
207
                               ct_test_support:reformat(Events, ?eh), 
 
208
                               ?config(priv_dir, Config)),
 
209
 
 
210
    TestEvents = events_to_check(dir2),
 
211
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
212
 
 
213
%%%-----------------------------------------------------------------
 
214
%%% 
 
215
 
 
216
dir1_2(doc) -> 
 
217
    [];
 
218
dir1_2(suite) -> 
 
219
    [];
 
220
dir1_2(Config) when is_list(Config) -> 
 
221
    DataDir = ?config(data_dir, Config),
 
222
 
 
223
    Happy1 = filename:join(DataDir, "happy_1"),
 
224
    Happy2 = filename:join(DataDir, "happy_2_test"),
 
225
    Happy1Cfg = filename:join(Happy1, "cfg/config1.cfg"),
 
226
 
 
227
    Opts0 = ct_test_support:get_opts(Config),
 
228
    Opts = eh_opts(Config) ++ Opts0 ++ [{config,Happy1Cfg}, {dir,[Happy1,Happy2]}],
 
229
 
 
230
    ERPid = ct_test_support:start_event_receiver(Config),
 
231
 
 
232
    ok = ct_test_support:run(Opts, Config),
 
233
 
 
234
    Events = ct_test_support:get_events(ERPid, Config),
 
235
    
 
236
    ct_test_support:log_events(dir1_2, 
 
237
                               ct_test_support:reformat(Events, ?eh), 
 
238
                               ?config(priv_dir, Config)),
 
239
 
 
240
    TestEvents = events_to_check(dir1_2),
 
241
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
242
 
 
243
%%%-----------------------------------------------------------------
 
244
%%% 
 
245
 
 
246
suite11(doc) -> 
 
247
    [];
 
248
suite11(suite) -> 
 
249
    [];
 
250
suite11(Config) when is_list(Config) -> 
 
251
    DataDir = ?config(data_dir, Config),
 
252
 
 
253
    Happy1 = filename:join(DataDir, "happy_1"),
 
254
    Suite = filename:join(Happy1, "test/happy_11_SUITE"),
 
255
    Happy1Cfg = filename:join(Happy1, "cfg/config1.cfg"),
 
256
 
 
257
    Opts0 = ct_test_support:get_opts(Config),
 
258
    Opts = eh_opts(Config) ++ Opts0 ++ [{config,Happy1Cfg}, {suite,Suite}],
 
259
 
 
260
    ERPid = ct_test_support:start_event_receiver(Config),
 
261
 
 
262
    ok = ct_test_support:run(Opts, Config),
 
263
 
 
264
    Events = ct_test_support:get_events(ERPid, Config),
 
265
    
 
266
    ct_test_support:log_events(suite11, 
 
267
                               ct_test_support:reformat(Events, ?eh), 
 
268
                               ?config(priv_dir, Config)),
 
269
 
 
270
    TestEvents = events_to_check(suite11),
 
271
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
272
 
 
273
%%%-----------------------------------------------------------------
 
274
%%% 
 
275
 
 
276
suite21(doc) -> 
 
277
    [];
 
278
suite21(suite) -> 
 
279
    [];
 
280
suite21(Config) when is_list(Config) -> 
 
281
    DataDir = ?config(data_dir, Config),
 
282
 
 
283
    Suite = filename:join(DataDir, "happy_2_test/happy_21_SUITE"),
 
284
    Happy2Cfg = filename:join(DataDir, "happy_2_cfg/config1.cfg"),
 
285
 
 
286
    Opts0 = ct_test_support:get_opts(Config),
 
287
    Opts = eh_opts(Config) ++ Opts0 ++ [{config,Happy2Cfg}, {suite,Suite}],
 
288
 
 
289
    ERPid = ct_test_support:start_event_receiver(Config),
 
290
 
 
291
    ok = ct_test_support:run(Opts, Config),
 
292
 
 
293
    Events = ct_test_support:get_events(ERPid, Config),
 
294
    
 
295
    ct_test_support:log_events(suite21, 
 
296
                               ct_test_support:reformat(Events, ?eh), 
 
297
                               ?config(priv_dir, Config)),
 
298
 
 
299
    TestEvents = events_to_check(suite21),
 
300
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
301
 
 
302
%%%-----------------------------------------------------------------
 
303
%%% 
 
304
 
 
305
suite11_21(doc) -> 
 
306
    [];
 
307
suite11_21(suite) -> 
 
308
    [];
 
309
suite11_21(Config) when is_list(Config) -> 
 
310
    DataDir = ?config(data_dir, Config),
 
311
 
 
312
    Happy1 = filename:join(DataDir, "happy_1"),
 
313
    Suite11 = filename:join(Happy1, "test/happy_11_SUITE"),
 
314
    Happy1Cfg = filename:join(Happy1, "cfg/config1.cfg"),
 
315
    Suite21 = filename:join(DataDir, "happy_2_test/happy_21_SUITE"),
 
316
 
 
317
    Opts0 = ct_test_support:get_opts(Config),
 
318
    Opts = eh_opts(Config) ++ Opts0 ++ [{config,Happy1Cfg}, {suite,[Suite11,Suite21]}],
 
319
 
 
320
    ERPid = ct_test_support:start_event_receiver(Config),
 
321
 
 
322
    ok = ct_test_support:run(Opts, Config),
 
323
 
 
324
    Events = ct_test_support:get_events(ERPid, Config),
 
325
    
 
326
    ct_test_support:log_events(suite11_21, 
 
327
                               ct_test_support:reformat(Events, ?eh), 
 
328
                               ?config(priv_dir, Config)),
 
329
 
 
330
    TestEvents = events_to_check(suite11_21),
 
331
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
332
 
 
333
%%%-----------------------------------------------------------------
 
334
%%% 
 
335
 
 
336
tc111(doc) -> 
 
337
    [];
 
338
tc111(suite) -> 
 
339
    [];
 
340
tc111(Config) when is_list(Config) -> 
 
341
    DataDir = ?config(data_dir, Config),
 
342
 
 
343
    Happy1 = filename:join(DataDir, "happy_1"),
 
344
    Suite = filename:join(Happy1, "test/happy_11_SUITE"),
 
345
    Happy1Cfg = filename:join(Happy1, "cfg/config1.cfg"),
 
346
 
 
347
    Opts0 = ct_test_support:get_opts(Config),
 
348
    Opts = eh_opts(Config) ++ Opts0 ++ [{config,Happy1Cfg}, {suite,Suite}, 
 
349
                                        {testcase,tc1}],
 
350
 
 
351
    ERPid = ct_test_support:start_event_receiver(Config),
 
352
 
 
353
    ok = ct_test_support:run(Opts, Config),
 
354
 
 
355
    Events = ct_test_support:get_events(ERPid, Config),
 
356
    
 
357
    ct_test_support:log_events(tc111, 
 
358
                               ct_test_support:reformat(Events, ?eh), 
 
359
                               ?config(priv_dir, Config)),
 
360
 
 
361
    TestEvents = events_to_check(tc111),
 
362
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
363
 
 
364
%%%-----------------------------------------------------------------
 
365
%%% 
 
366
 
 
367
tc211(doc) -> 
 
368
    [];
 
369
tc211(suite) -> 
 
370
    [];
 
371
tc211(Config) when is_list(Config) -> 
 
372
    DataDir = ?config(data_dir, Config),
 
373
 
 
374
    Suite = filename:join(DataDir, "happy_2_test/happy_21_SUITE"),
 
375
    Happy2Cfg = filename:join(DataDir, "happy_2_cfg/config1.cfg"),
 
376
 
 
377
    Opts0 = ct_test_support:get_opts(Config),
 
378
    Opts = eh_opts(Config) ++ Opts0 ++ [{config,Happy2Cfg}, {suite,Suite}, 
 
379
                                        {testcase,tc1}],
 
380
 
 
381
    ERPid = ct_test_support:start_event_receiver(Config),
 
382
 
 
383
    ok = ct_test_support:run(Opts, Config),
 
384
 
 
385
    Events = ct_test_support:get_events(ERPid, Config),
 
386
    
 
387
    ct_test_support:log_events(tc211, 
 
388
                               ct_test_support:reformat(Events, ?eh), 
 
389
                               ?config(priv_dir, Config)),
 
390
 
 
391
    TestEvents = events_to_check(tc211),
 
392
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
393
 
 
394
%%%-----------------------------------------------------------------
 
395
%%% 
 
396
 
 
397
tc111_112(doc) -> 
 
398
    [];
 
399
tc111_112(suite) -> 
 
400
    [];
 
401
tc111_112(Config) when is_list(Config) -> 
 
402
    DataDir = ?config(data_dir, Config),
 
403
 
 
404
    Happy1 = filename:join(DataDir, "happy_1"),
 
405
    Suite = filename:join(Happy1, "test/happy_11_SUITE"),
 
406
    Happy1Cfg = filename:join(Happy1, "cfg/config1.cfg"),
 
407
 
 
408
    Opts0 = ct_test_support:get_opts(Config),
 
409
    Opts = eh_opts(Config) ++ Opts0 ++ [{config,Happy1Cfg}, {suite,Suite}, 
 
410
                                        {testcase,[tc1,tc2]}],
 
411
 
 
412
    ERPid = ct_test_support:start_event_receiver(Config),
 
413
 
 
414
    ok = ct_test_support:run(Opts, Config),
 
415
    
 
416
    Events = ct_test_support:get_events(ERPid, Config),
 
417
    
 
418
    ct_test_support:log_events(tc111_112, 
 
419
                               ct_test_support:reformat(Events, ?eh), 
 
420
                               ?config(priv_dir, Config)),
 
421
 
 
422
    TestEvents = events_to_check(tc111_112),
 
423
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
424
 
 
425
 
 
426
%%%-----------------------------------------------------------------
 
427
%%% HELP FUNCTIONS
 
428
%%%-----------------------------------------------------------------
 
429
 
 
430
eh_opts(Config) ->        
 
431
    Level = ?config(trace_level, Config),
 
432
    [{event_handler,{?eh,[{cbm,ct_test_support},{trace_level,Level}]}}].
 
433
 
 
434
events_to_check(Test) ->
 
435
    %% 2 tests (ct:run_test + script_start) is default
 
436
    events_to_check(Test, 2).
 
437
 
 
438
events_to_check(_, 0) ->
 
439
    [];
 
440
events_to_check(Test, N) ->
 
441
    events(Test) ++ events_to_check(Test, N-1).
 
442
 
 
443
events(Test) when Test == dir1 ; Test == dir2 ;
 
444
                       Test == suite11 ; Test == suite21 ->
 
445
    Suite = if Test == dir1 ; Test == suite11 -> happy_11_SUITE;
 
446
               true -> happy_21_SUITE
 
447
            end,
 
448
    [
 
449
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
450
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
451
     {?eh,start_info,{1,1,8}},
 
452
     {?eh,tc_start,{Suite,init_per_suite}},
 
453
     {?eh,tc_done,{Suite,init_per_suite,ok}},
 
454
     {?eh,tc_start,{Suite,tc1}},
 
455
     {?eh,tc_done,{Suite,tc1,ok}},
 
456
     {?eh,test_stats,{1,0,{0,0}}},
 
457
     {?eh,tc_start,{Suite,tc2}},
 
458
     {?eh,tc_done,{Suite,tc2,ok}},
 
459
     {?eh,test_stats,{2,0,{0,0}}},
 
460
     {?eh,tc_start,{Suite,seq1_tc1}},
 
461
     {?eh,tc_done,{Suite,seq1_tc1,ok}},
 
462
     {?eh,test_stats,{3,0,{0,0}}},
 
463
     {?eh,tc_start,{Suite,seq1_tc2}},
 
464
     {?eh,tc_done,{Suite,seq1_tc2,ok}},
 
465
     {?eh,test_stats,{4,0,{0,0}}},
 
466
     {?eh,tc_start,{Suite,tc3}},
 
467
     {?eh,tc_done,{Suite,tc3,ok}},
 
468
     {?eh,test_stats,{5,0,{0,0}}},
 
469
     {?eh,tc_start,{Suite,seq2_tc1}},
 
470
     {?eh,tc_done,{Suite,seq2_tc1,ok}},
 
471
     {?eh,test_stats,{6,0,{0,0}}},
 
472
     {?eh,tc_start,{Suite,seq2_tc2}},
 
473
     {?eh,tc_done,{Suite,seq2_tc2,ok}},
 
474
     {?eh,test_stats,{7,0,{0,0}}},
 
475
     {?eh,tc_start,{Suite,tc4}},
 
476
     {?eh,tc_done,
 
477
      {Suite,tc4,{skipped,"Skipping this one"}}},
 
478
     {?eh,test_stats,{7,0,{1,0}}},
 
479
     {?eh,tc_start,{Suite,end_per_suite}},
 
480
     {?eh,tc_done,{Suite,end_per_suite,ips_data}},
 
481
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
482
     {?eh,stop_logging,[]}
 
483
    ];
 
484
events(Test) when Test == dir1_2 ; Test == suite11_21 ->
 
485
    [
 
486
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
487
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
488
     {?eh,start_info,{2,2,16}},
 
489
     {?eh,tc_start,{happy_11_SUITE,init_per_suite}},
 
490
     {?eh,tc_done,{happy_11_SUITE,init_per_suite,ok}},
 
491
     {?eh,tc_start,{happy_11_SUITE,tc1}},
 
492
     {?eh,tc_done,{happy_11_SUITE,tc1,ok}},
 
493
     {?eh,test_stats,{1,0,{0,0}}},
 
494
     {?eh,tc_start,{happy_11_SUITE,tc2}},
 
495
     {?eh,tc_done,{happy_11_SUITE,tc2,ok}},
 
496
     {?eh,test_stats,{2,0,{0,0}}},
 
497
     {?eh,tc_start,{happy_11_SUITE,seq1_tc1}},
 
498
     {?eh,tc_done,{happy_11_SUITE,seq1_tc1,ok}},
 
499
     {?eh,test_stats,{3,0,{0,0}}},
 
500
     {?eh,tc_start,{happy_11_SUITE,seq1_tc2}},
 
501
     {?eh,tc_done,{happy_11_SUITE,seq1_tc2,ok}},
 
502
     {?eh,test_stats,{4,0,{0,0}}},
 
503
     {?eh,tc_start,{happy_11_SUITE,tc3}},
 
504
     {?eh,tc_done,{happy_11_SUITE,tc3,ok}},
 
505
     {?eh,test_stats,{5,0,{0,0}}},
 
506
     {?eh,tc_start,{happy_11_SUITE,seq2_tc1}},
 
507
     {?eh,tc_done,{happy_11_SUITE,seq2_tc1,ok}},
 
508
     {?eh,test_stats,{6,0,{0,0}}},
 
509
     {?eh,tc_start,{happy_11_SUITE,seq2_tc2}},
 
510
     {?eh,tc_done,{happy_11_SUITE,seq2_tc2,ok}},
 
511
     {?eh,test_stats,{7,0,{0,0}}},
 
512
     {?eh,tc_start,{happy_11_SUITE,tc4}},
 
513
     {?eh,tc_done,
 
514
      {happy_11_SUITE,tc4,{skipped,"Skipping this one"}}},
 
515
     {?eh,test_stats,{7,0,{1,0}}},
 
516
     {?eh,tc_start,{happy_11_SUITE,end_per_suite}},
 
517
     {?eh,tc_done,{happy_11_SUITE,end_per_suite,ips_data}},
 
518
     {?eh,tc_start,{happy_21_SUITE,init_per_suite}},
 
519
     {?eh,tc_done,{happy_21_SUITE,init_per_suite,ok}},
 
520
     {?eh,tc_start,{happy_21_SUITE,tc1}},
 
521
     {?eh,tc_done,{happy_21_SUITE,tc1,ok}},
 
522
     {?eh,test_stats,{8,0,{1,0}}},
 
523
     {?eh,tc_start,{happy_21_SUITE,tc2}},
 
524
     {?eh,tc_done,{happy_21_SUITE,tc2,ok}},
 
525
     {?eh,test_stats,{9,0,{1,0}}},
 
526
     {?eh,tc_start,{happy_21_SUITE,seq1_tc1}},
 
527
     {?eh,tc_done,{happy_21_SUITE,seq1_tc1,ok}},
 
528
     {?eh,test_stats,{10,0,{1,0}}},
 
529
     {?eh,tc_start,{happy_21_SUITE,seq1_tc2}},
 
530
     {?eh,tc_done,{happy_21_SUITE,seq1_tc2,ok}},
 
531
     {?eh,test_stats,{11,0,{1,0}}},
 
532
     {?eh,tc_start,{happy_21_SUITE,tc3}},
 
533
     {?eh,tc_done,{happy_21_SUITE,tc3,ok}},
 
534
     {?eh,test_stats,{12,0,{1,0}}},
 
535
     {?eh,tc_start,{happy_21_SUITE,seq2_tc1}},
 
536
     {?eh,tc_done,{happy_21_SUITE,seq2_tc1,ok}},
 
537
     {?eh,test_stats,{13,0,{1,0}}},
 
538
     {?eh,tc_start,{happy_21_SUITE,seq2_tc2}},
 
539
     {?eh,tc_done,{happy_21_SUITE,seq2_tc2,ok}},
 
540
     {?eh,test_stats,{14,0,{1,0}}},
 
541
     {?eh,tc_start,{happy_21_SUITE,tc4}},
 
542
     {?eh,tc_done,
 
543
      {happy_21_SUITE,tc4,{skipped,"Skipping this one"}}},
 
544
     {?eh,test_stats,{14,0,{2,0}}},
 
545
     {?eh,tc_start,{happy_21_SUITE,end_per_suite}},
 
546
     {?eh,tc_done,{happy_21_SUITE,end_per_suite,ips_data}},
 
547
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
548
     {?eh,stop_logging,[]}
 
549
    ];
 
550
 
 
551
events(Test) when Test == tc111 ; Test == tc211 ->
 
552
    Suite = if Test == tc111 -> happy_11_SUITE; true -> happy_21_SUITE end,
 
553
    [
 
554
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
555
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
556
     {?eh,start_info,{1,1,1}},
 
557
     {?eh,tc_start,{Suite,init_per_suite}},
 
558
     {?eh,tc_done,{Suite,init_per_suite,ok}},
 
559
     {?eh,tc_start,{Suite,tc1}},
 
560
     {?eh,tc_done,{Suite,tc1,ok}},
 
561
     {?eh,test_stats,{1,0,{0,0}}},
 
562
     {?eh,tc_start,{Suite,end_per_suite}},
 
563
     {?eh,tc_done,{Suite,end_per_suite,ips_data}},
 
564
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
565
     {?eh,stop_logging,[]}
 
566
    ];
 
567
 
 
568
events(tc111_112) ->
 
569
    [
 
570
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
571
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
572
     {?eh,start_info,{1,1,2}},
 
573
     {?eh,tc_start,{happy_11_SUITE,init_per_suite}},
 
574
     {?eh,tc_done,{happy_11_SUITE,init_per_suite,ok}},
 
575
     {?eh,tc_start,{happy_11_SUITE,tc1}},
 
576
     {?eh,tc_done,{happy_11_SUITE,tc1,ok}},
 
577
     {?eh,test_stats,{1,0,{0,0}}},
 
578
     {?eh,tc_start,{happy_11_SUITE,tc2}},
 
579
     {?eh,tc_done,{happy_11_SUITE,tc2,ok}},
 
580
     {?eh,test_stats,{2,0,{0,0}}},
 
581
     {?eh,tc_start,{happy_11_SUITE,end_per_suite}},
 
582
     {?eh,tc_done,{happy_11_SUITE,end_per_suite,ips_data}},
 
583
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
584
     {?eh,stop_logging,[]}
 
585
    ].