~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/test_server/test/test_server_parallel01_SUITE.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%
2
 
%% %CopyrightBegin%
3
 
%%
4
 
%% Copyright Ericsson AB 2009-2010. 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
 
%%% Test Server self test. 
22
 
%%%------------------------------------------------------------------
23
 
-module(test_server_parallel01_SUITE).
24
 
-include_lib("test_server/include/test_server.hrl").
25
 
 
26
 
-compile(export_all).
27
 
 
28
 
%% -------------------------------------------------------------------
29
 
%% Notes on parallel execution of test cases
30
 
%% -------------------------------------------------------------------
31
 
%%
32
 
%% A group nested under a parallel group will start executing in
33
 
%% parallel with previous (parallel) test cases (no matter what
34
 
%% properties the nested group has). Test cases are however never 
35
 
%% executed in parallel with the start or end conf case of the same
36
 
%% group! Because of this, the test_server_ctrl loop waits at
37
 
%% the end conf of a group for all parallel cases to finish
38
 
%% before the end conf case actually executes. This has the effect
39
 
%% that it's only after a nested group has finished that any
40
 
%% remaining parallel cases in the previous group get spawned (*). 
41
 
%% Example (all parallel cases):
42
 
%%
43
 
%% group1_init   |---->
44
 
%% group1_case1        | --------->
45
 
%% group1_case2        | --------------------------------->
46
 
%% group2_init         | ---->
47
 
%% group2_case1               | ------>
48
 
%% group2_case2               | ---------->
49
 
%% group2_end                              | --->
50
 
%% group1_case3                               (*)| ---->
51
 
%% group1_case4                               (*)| -->
52
 
%% group1_end                                              | --->
53
 
%%
54
 
 
55
 
all(doc) -> ["Test simple conf case structure, with and without nested cases"];
56
 
all(suite) -> 
57
 
    [
58
 
     {conf, [parallel], conf1_init, [conf1_tc1, conf1_tc2], conf1_end},
59
 
 
60
 
     {conf, [parallel], conf2_init, [conf2_tc1, conf2_tc2], conf2_end},
61
 
 
62
 
     {conf, [parallel], conf3_init, [conf3_tc1, conf3_tc1,
63
 
                                     
64
 
                                     {conf, [], 
65
 
                                      conf4_init, [conf4_tc1, conf4_tc2], conf4_end},
66
 
                                     
67
 
                                     conf3_tc2], conf3_end},
68
 
 
69
 
     conf5,
70
 
 
71
 
     {conf, [parallel], conf7_init, [conf7_tc1, conf7_tc1,
72
 
                                     
73
 
                                     {conf, [parallel], 
74
 
                                      conf8_init, [conf8_tc1, conf8_tc2], conf8_end},
75
 
                                     
76
 
                                     conf7_tc2], conf7_end}
77
 
     
78
 
    ].
79
 
 
80
 
 
81
 
%%---------- conf cases ----------
82
 
 
83
 
init_per_suite(Config) ->
84
 
    case ?config(data_dir,Config) of
85
 
        undefined -> exit(no_data_dir);
86
 
        _ -> ok
87
 
    end,    
88
 
    [{suite,init}|Config].
89
 
end_per_suite(Config) ->
90
 
    case ?config(data_dir,Config) of
91
 
        undefined -> exit(no_data_dir);
92
 
        _ -> ok
93
 
    end,    
94
 
    init = ?config(suite,Config),
95
 
    ok.
96
 
 
97
 
init_per_testcase(TC=conf1_tc1, Config) ->
98
 
    init = ?config(suite,Config),
99
 
    [{tc11,TC}|Config];
100
 
init_per_testcase(TC=conf1_tc2, Config) ->
101
 
    [{tc12,TC}|Config];
102
 
init_per_testcase(TC=conf2_tc1, Config) ->
103
 
    [{tc21,TC}|Config];
104
 
init_per_testcase(TC=conf2_tc2, Config) ->
105
 
    [{tc22,TC}|Config];
106
 
init_per_testcase(TC=conf3_tc1, Config) ->
107
 
    [{tc31,TC}|Config];
108
 
init_per_testcase(TC=conf3_tc2, Config) ->
109
 
    [{tc32,TC}|Config];
110
 
init_per_testcase(TC=conf4_tc1, Config) ->
111
 
    [{tc41,TC}|Config];
112
 
init_per_testcase(TC=conf4_tc2, Config) ->
113
 
    [{tc42,TC}|Config];
114
 
init_per_testcase(TC=conf5_tc1, Config) ->
115
 
    [{tc51,TC}|Config];
116
 
init_per_testcase(TC=conf5_tc2, Config) ->
117
 
    [{tc52,TC}|Config];
118
 
init_per_testcase(TC=conf6_tc1, Config) ->
119
 
    [{tc61,TC}|Config];
120
 
init_per_testcase(TC=conf6_tc2, Config) ->
121
 
    init = ?config(suite,Config),
122
 
    [{tc62,TC}|Config];
123
 
init_per_testcase(TC=conf7_tc1, Config) ->
124
 
    [{tc71,TC}|Config];
125
 
init_per_testcase(TC=conf7_tc2, Config) ->
126
 
    [{tc72,TC}|Config];
127
 
init_per_testcase(TC=conf8_tc1, Config) ->
128
 
    [{tc81,TC}|Config];
129
 
init_per_testcase(TC=conf8_tc2, Config) ->
130
 
    init = ?config(suite,Config),
131
 
    [{tc82,TC}|Config].
132
 
 
133
 
end_per_testcase(TC=conf1_tc1, Config) ->
134
 
    init = ?config(suite,Config),
135
 
    TC = ?config(tc11,Config),
136
 
    ok;
137
 
end_per_testcase(TC=conf1_tc2, Config) ->
138
 
    TC = ?config(tc12,Config),
139
 
    ok;
140
 
end_per_testcase(TC=conf2_tc1, Config) ->
141
 
    TC = ?config(tc21,Config),
142
 
    ok;
143
 
end_per_testcase(TC=conf2_tc2, Config) ->
144
 
    TC = ?config(tc22,Config),
145
 
    ok;
146
 
end_per_testcase(TC=conf3_tc1, Config) ->
147
 
    TC = ?config(tc31,Config),
148
 
    ok;
149
 
end_per_testcase(TC=conf3_tc2, Config) ->
150
 
    TC = ?config(tc32,Config),
151
 
    ok;
152
 
end_per_testcase(TC=conf4_tc1, Config) ->
153
 
    TC = ?config(tc41,Config),
154
 
    ok;
155
 
end_per_testcase(TC=conf4_tc2, Config) ->
156
 
    TC = ?config(tc42,Config),
157
 
    ok;
158
 
end_per_testcase(TC=conf5_tc1, Config) ->
159
 
    TC = ?config(tc51,Config),
160
 
    ok;
161
 
end_per_testcase(TC=conf5_tc2, Config) ->
162
 
    TC = ?config(tc52,Config),
163
 
    ok;
164
 
end_per_testcase(TC=conf6_tc1, Config) ->
165
 
    TC = ?config(tc61,Config),
166
 
    ok;
167
 
end_per_testcase(TC=conf6_tc2, Config) ->
168
 
    init = ?config(suite,Config),
169
 
    TC = ?config(tc62,Config),
170
 
    ok;
171
 
end_per_testcase(TC=conf7_tc1, Config) ->
172
 
    TC = ?config(tc71,Config),
173
 
    ok;
174
 
end_per_testcase(TC=conf7_tc2, Config) ->
175
 
    TC = ?config(tc72,Config),
176
 
    ok;
177
 
end_per_testcase(TC=conf8_tc1, Config) ->
178
 
    TC = ?config(tc81,Config),
179
 
    ok;
180
 
end_per_testcase(TC=conf8_tc2, Config) ->
181
 
    init = ?config(suite,Config),
182
 
    TC = ?config(tc82,Config),
183
 
    ok.
184
 
 
185
 
conf1_init(Config) when is_list(Config) ->
186
 
    test_server:comment(io_lib:format("~p",[now()])),
187
 
    [parallel] = ?config(tc_group_properties,Config),
188
 
    init = ?config(suite,Config),
189
 
    [{t0,now()},{cc1,conf1}|Config].
190
 
conf1_end(Config) ->
191
 
    %% check 2s & 3s < 4s
192
 
    Ms = timer:now_diff(now(),?config(t0,Config)),
193
 
    test_server:comment(io_lib:format("~p",[now()])),
194
 
    if Ms > 3500000 -> exit({bad_parallel_exec,Ms});
195
 
       Ms < 3000000 -> exit({bad_parallel_exec,Ms});
196
 
       true -> ok
197
 
    end.
198
 
 
199
 
conf2_init(Config) when is_list(Config) ->
200
 
    test_server:comment(io_lib:format("~p",[now()])),
201
 
    [parallel] = ?config(tc_group_properties,Config),
202
 
    [{t0,now()},{cc2,conf2}|Config].
203
 
conf2_end(Config) ->
204
 
    %% check 3s & 2s < 4s
205
 
    Ms = timer:now_diff(now(),?config(t0,Config)),
206
 
    test_server:comment(io_lib:format("~p",[now()])),
207
 
    if Ms > 3500000 -> exit({bad_parallel_exec,Ms});
208
 
       Ms < 3000000 -> exit({bad_parallel_exec,Ms});
209
 
       true -> ok
210
 
    end.
211
 
 
212
 
conf3_init(Config) when is_list(Config) ->
213
 
    test_server:comment(io_lib:format("~p",[now()])),
214
 
    [parallel] = ?config(tc_group_properties,Config),
215
 
    [{t0,now()},{cc3,conf3}|Config].
216
 
conf3_end(Config) ->
217
 
    %% check 6s & 6s & (2s & 3s) & 1s = ~6s
218
 
    Ms = timer:now_diff(now(),?config(t0,Config)),
219
 
    test_server:comment(io_lib:format("~p",[now()])),
220
 
    if Ms > 6500000 -> exit({bad_parallel_exec,Ms});
221
 
       Ms < 6000000 -> exit({bad_parallel_exec,Ms});
222
 
       true -> ok
223
 
    end.
224
 
 
225
 
conf4_init(Config) when is_list(Config) ->
226
 
    test_server:comment(io_lib:format("~p",[now()])),
227
 
    [] = ?config(tc_group_properties,Config),
228
 
    [{t0,now()},{cc4,conf4}|Config].
229
 
conf4_end(Config) ->
230
 
    %% check 2s & 3s >= 5s
231
 
    Ms = timer:now_diff(now(),?config(t0,Config)),
232
 
    test_server:comment(io_lib:format("~p",[now()])),
233
 
    if Ms > 5500000 -> exit({bad_parallel_exec,Ms});
234
 
       Ms < 5000000 -> exit({bad_parallel_exec,Ms});
235
 
       true -> ok
236
 
    end.
237
 
 
238
 
conf5_init(Config) when is_list(Config) ->
239
 
    test_server:comment(io_lib:format("~p",[now()])),
240
 
    [] = ?config(tc_group_properties,Config),
241
 
    [{t0,now()},{cc5,conf5}|Config].
242
 
conf5_end(Config) ->
243
 
    %% check 1s & 1s & (3s & 2s) & 1s = ~6s
244
 
    Ms = timer:now_diff(now(),?config(t0,Config)),
245
 
    test_server:comment(io_lib:format("~p",[now()])),
246
 
    if Ms > 7000000 -> exit({bad_parallel_exec,Ms});
247
 
       Ms < 6000000 -> exit({bad_parallel_exec,Ms});
248
 
       true -> ok
249
 
    end.
250
 
 
251
 
conf6_init(Config) when is_list(Config) ->
252
 
    test_server:comment(io_lib:format("~p",[now()])),
253
 
    [parallel] = ?config(tc_group_properties,Config),
254
 
    init = ?config(suite,Config),
255
 
    [{t0,now()},{cc6,conf6}|Config].
256
 
conf6_end(Config) ->
257
 
    %% check 3s & 2s < 5s
258
 
    Ms = timer:now_diff(now(),?config(t0,Config)),
259
 
    test_server:comment(io_lib:format("~p",[now()])),
260
 
    if Ms > 3500000 -> exit({bad_parallel_exec,Ms});
261
 
       Ms < 3000000 -> exit({bad_parallel_exec,Ms});
262
 
       true -> ok
263
 
    end.
264
 
 
265
 
conf5(suite) ->                                 % test specification
266
 
    [{conf, conf5_init, [conf5_tc1, conf5_tc1,
267
 
 
268
 
                         {conf, [parallel], conf6_init, [conf6_tc1, conf6_tc2], conf6_end},
269
 
 
270
 
                         conf5_tc2], conf5_end}].
271
 
 
272
 
conf7_init(Config) when is_list(Config) ->
273
 
    test_server:comment(io_lib:format("~p",[now()])),
274
 
    [parallel] = ?config(tc_group_properties,Config),
275
 
    [{t0,now()},{cc7,conf7}|Config].
276
 
conf7_end(Config) ->
277
 
    %% check 1s & 1s & (2s & 2s) & 1s = ~3s 
278
 
    Ms = timer:now_diff(now(),?config(t0,Config)),
279
 
    test_server:comment(io_lib:format("~p",[now()])),
280
 
    if Ms > 3500000 -> exit({bad_parallel_exec,Ms});
281
 
       Ms < 3000000 -> exit({bad_parallel_exec,Ms});
282
 
       true -> ok
283
 
    end.
284
 
 
285
 
conf8_init(Config) when is_list(Config) ->
286
 
    test_server:comment(io_lib:format("~p",[now()])),
287
 
    [parallel] = ?config(tc_group_properties,Config),
288
 
    init = ?config(suite,Config),
289
 
    [{t0,now()},{cc8,conf8}|Config].
290
 
conf8_end(Config) ->
291
 
    %% check 2s & 2s < 4s
292
 
    Ms = timer:now_diff(now(),?config(t0,Config)),
293
 
    test_server:comment(io_lib:format("~p",[now()])),
294
 
    if Ms > 2500000 -> exit({bad_parallel_exec,Ms});
295
 
       Ms < 2000000 -> exit({bad_parallel_exec,Ms});
296
 
       true -> ok
297
 
    end.
298
 
 
299
 
 
300
 
%%---------- test cases ----------
301
 
 
302
 
conf1_tc1(Config) when is_list(Config) ->
303
 
    case ?config(data_dir,Config) of
304
 
        undefined -> exit(no_data_dir);
305
 
        _ -> ok
306
 
    end,    
307
 
    init = ?config(suite,Config),
308
 
    conf1 = ?config(cc1,Config),
309
 
    conf1_tc1 = ?config(tc11,Config),
310
 
    timer:sleep(2000),
311
 
    test_server:comment(io_lib:format("~p",[now()])),
312
 
    ok.
313
 
conf1_tc2(Config) when is_list(Config) ->
314
 
    case ?config(priv_dir,Config) of
315
 
        undefined -> exit(no_priv_dir);
316
 
        _ -> ok
317
 
    end,    
318
 
    init = ?config(suite,Config),
319
 
    conf1 = ?config(cc1,Config),
320
 
    conf1_tc2 = ?config(tc12,Config),
321
 
    timer:sleep(3000),
322
 
    test_server:comment(io_lib:format("~p",[now()])),
323
 
    ok.
324
 
 
325
 
conf2_tc1(Config) when is_list(Config) ->
326
 
    init = ?config(suite,Config),
327
 
    undefined = ?config(cc1,Config),
328
 
    undefined = ?config(tc11,Config),
329
 
    conf2 = ?config(cc2,Config),
330
 
    conf2_tc1 = ?config(tc21,Config),
331
 
    timer:sleep(3000),
332
 
    test_server:comment(io_lib:format("~p",[now()])),
333
 
    ok.
334
 
conf2_tc2(Config) when is_list(Config) ->
335
 
    init = ?config(suite,Config),
336
 
    conf2 = ?config(cc2,Config),
337
 
    undefined = ?config(tc21,Config),
338
 
    conf2_tc2 = ?config(tc22,Config),
339
 
    timer:sleep(2000),
340
 
    test_server:comment(io_lib:format("~p",[now()])),
341
 
    ok.
342
 
 
343
 
conf3_tc1(Config) when is_list(Config) ->
344
 
    init = ?config(suite,Config),
345
 
    undefined = ?config(cc2,Config),
346
 
    undefined = ?config(tc22,Config),
347
 
    conf3 = ?config(cc3,Config),
348
 
    conf3_tc1 = ?config(tc31,Config),
349
 
    timer:sleep(6000),
350
 
    test_server:comment(io_lib:format("~p",[now()])),
351
 
    ok.
352
 
conf3_tc2(Config) when is_list(Config) ->
353
 
    init = ?config(suite,Config),
354
 
    conf3 = ?config(cc3,Config),
355
 
    undefined = ?config(cc4,Config),
356
 
    undefined = ?config(tc31,Config),
357
 
    undefined = ?config(tc41,Config),
358
 
    conf3_tc2 = ?config(tc32,Config),
359
 
    timer:sleep(1000),
360
 
    test_server:comment(io_lib:format("~p",[now()])),
361
 
    ok.
362
 
 
363
 
conf4_tc1(Config) when is_list(Config) ->
364
 
    init = ?config(suite,Config),
365
 
    case ?config(data_dir,Config) of
366
 
        undefined -> exit(no_data_dir);
367
 
        _ -> ok
368
 
    end,    
369
 
    undefined = ?config(cc1,Config),
370
 
    undefined = ?config(cc2,Config),
371
 
    conf3 = ?config(cc3,Config),
372
 
    conf4 = ?config(cc4,Config),
373
 
    undefined = ?config(tc32,Config),
374
 
    conf4_tc1 = ?config(tc41,Config),
375
 
    timer:sleep(2000),
376
 
    test_server:comment(io_lib:format("~p",[now()])),
377
 
    ok.
378
 
conf4_tc2(Config) when is_list(Config) ->
379
 
    init = ?config(suite,Config),
380
 
    case ?config(priv_dir,Config) of
381
 
        undefined -> exit(no_priv_dir);
382
 
        _ -> ok
383
 
    end,    
384
 
    conf3 = ?config(cc3,Config),
385
 
    conf4 = ?config(cc4,Config),
386
 
    undefined = ?config(tc41,Config),
387
 
    conf4_tc2 = ?config(tc42,Config),
388
 
    timer:sleep(3000),
389
 
    test_server:comment(io_lib:format("~p",[now()])),
390
 
    ok.
391
 
 
392
 
conf5_tc1(Config) when is_list(Config) ->
393
 
    init = ?config(suite,Config),
394
 
    case ?config(data_dir,Config) of
395
 
        undefined -> exit(no_data_dir);
396
 
        _ -> ok
397
 
    end,    
398
 
    undefined = ?config(cc1,Config),
399
 
    undefined = ?config(cc2,Config),
400
 
    undefined = ?config(cc3,Config),
401
 
    undefined = ?config(cc4,Config),
402
 
    conf5 = ?config(cc5,Config),
403
 
    undefined = ?config(tc42,Config),
404
 
    conf5_tc1 = ?config(tc51,Config),
405
 
    timer:sleep(1000),
406
 
    test_server:comment(io_lib:format("~p",[now()])),
407
 
    ok.
408
 
conf5_tc2(Config) when is_list(Config) ->
409
 
    init = ?config(suite,Config),
410
 
    case ?config(priv_dir,Config) of
411
 
        undefined -> exit(no_priv_dir);
412
 
        _ -> ok
413
 
    end,    
414
 
    conf5 = ?config(cc5,Config),
415
 
    undefined = ?config(cc6,Config),
416
 
    undefined = ?config(tc51,Config),
417
 
    undefined = ?config(tc62,Config),
418
 
    conf5_tc2 = ?config(tc52,Config),
419
 
    timer:sleep(1000),
420
 
    test_server:comment(io_lib:format("~p",[now()])),
421
 
    ok.
422
 
 
423
 
conf6_tc1(Config) when is_list(Config) ->
424
 
    init = ?config(suite,Config),
425
 
    case ?config(data_dir,Config) of
426
 
        undefined -> exit(no_data_dir);
427
 
        _ -> ok
428
 
    end,    
429
 
    undefined = ?config(cc1,Config),
430
 
    undefined = ?config(cc2,Config),
431
 
    undefined = ?config(cc3,Config),
432
 
    undefined = ?config(cc4,Config),
433
 
    conf5 = ?config(cc5,Config),
434
 
    conf6 = ?config(cc6,Config),
435
 
    undefined = ?config(tc52,Config),
436
 
    conf6_tc1 = ?config(tc61,Config),
437
 
    timer:sleep(3000),
438
 
    test_server:comment(io_lib:format("~p",[now()])),
439
 
    ok.
440
 
conf6_tc2(Config) when is_list(Config) ->
441
 
    init = ?config(suite,Config),
442
 
    case ?config(priv_dir,Config) of
443
 
        undefined -> exit(no_priv_dir);
444
 
        _ -> ok
445
 
    end,    
446
 
    conf5 = ?config(cc5,Config),
447
 
    conf6 = ?config(cc6,Config),
448
 
    undefined = ?config(tc61,Config),
449
 
    conf6_tc2 = ?config(tc62,Config),
450
 
    timer:sleep(2000),
451
 
    test_server:comment(io_lib:format("~p",[now()])),
452
 
    ok.
453
 
 
454
 
conf7_tc1(Config) when is_list(Config) ->
455
 
    init = ?config(suite,Config),
456
 
    case ?config(data_dir,Config) of
457
 
        undefined -> exit(no_data_dir);
458
 
        _ -> ok
459
 
    end,    
460
 
    undefined = ?config(cc1,Config),
461
 
    undefined = ?config(cc2,Config),
462
 
    undefined = ?config(cc3,Config),
463
 
    undefined = ?config(cc4,Config),
464
 
    undefined = ?config(cc5,Config),
465
 
    undefined = ?config(cc6,Config),
466
 
    conf7 = ?config(cc7,Config),
467
 
    undefined = ?config(tc62,Config),
468
 
    conf7_tc1 = ?config(tc71,Config),
469
 
    timer:sleep(1000),
470
 
    test_server:comment(io_lib:format("~p",[now()])),
471
 
    ok.
472
 
conf7_tc2(Config) when is_list(Config) ->
473
 
    init = ?config(suite,Config),
474
 
    case ?config(priv_dir,Config) of
475
 
        undefined -> exit(no_priv_dir);
476
 
        _ -> ok
477
 
    end,    
478
 
    conf7 = ?config(cc7,Config),
479
 
    undefined = ?config(cc8,Config),
480
 
    undefined = ?config(tc71,Config),
481
 
    undefined = ?config(tc82,Config),
482
 
    conf7_tc2 = ?config(tc72,Config),
483
 
    timer:sleep(1000),
484
 
    test_server:comment(io_lib:format("~p",[now()])),
485
 
    ok.
486
 
 
487
 
conf8_tc1(Config) when is_list(Config) ->
488
 
    init = ?config(suite,Config),
489
 
    case ?config(data_dir,Config) of
490
 
        undefined -> exit(no_data_dir);
491
 
        _ -> ok
492
 
    end,    
493
 
    undefined = ?config(cc1,Config),
494
 
    undefined = ?config(cc2,Config),
495
 
    undefined = ?config(cc3,Config),
496
 
    undefined = ?config(cc4,Config),
497
 
    undefined = ?config(cc5,Config),
498
 
    undefined = ?config(cc6,Config),
499
 
    conf7 = ?config(cc7,Config),
500
 
    conf8 = ?config(cc8,Config),
501
 
    undefined = ?config(tc72,Config),
502
 
    conf8_tc1 = ?config(tc81,Config),
503
 
    timer:sleep(2000),
504
 
    test_server:comment(io_lib:format("~p",[now()])),
505
 
    ok.
506
 
conf8_tc2(Config) when is_list(Config) ->
507
 
    init = ?config(suite,Config),
508
 
    case ?config(priv_dir,Config) of
509
 
        undefined -> exit(no_priv_dir);
510
 
        _ -> ok
511
 
    end,    
512
 
    conf7 = ?config(cc7,Config),
513
 
    conf8 = ?config(cc8,Config),
514
 
    undefined = ?config(tc81,Config),
515
 
    conf8_tc2 = ?config(tc82,Config),
516
 
    timer:sleep(2000),
517
 
    test_server:comment(io_lib:format("~p",[now()])),
518
 
    ok.