~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Elliot Murphy
  • Date: 2010-06-08 03:55:44 UTC
  • mfrom: (3.5.6 squeeze)
  • Revision ID: elliot@elliotmurphy.com-20100608035544-dd8zh2swk7jr5rz2
* Merge with Debian unstable; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - 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.
* Added missing symlinks to /usr/include for a few new header files.
* Fixed generation of ${erlang-base:Depends} and ${erlang-x11:Depends}
  substitution variables.
* Added a fix for a re:compile/2 crash on a long regular expression.
* Changed urgency to medium as the change fixes a security bug.
* Manpages in section 1 are needed even if only arch-dependent packages are
  built. So, re-enabled them.
* Fixed HiPE architecture recognition for powerpc Debian architecture.
* Moved xsltproc and fop to build-depends-indep and do not build
  documentation if only architecture-specific packages are built.
* Refreshed all patches.
* Made Emacs look in man5 and man7 for Erlang manpages and added code
  skeleton files to erlang-mode package.
* New upstream release.
* Moved manpages from incorrect sections 4 and 6 to correct 5 and 7
  (closes: #498492).
* Made manpages regexp in Emacs mode match only 3erl pages in section 3.
* Removed docb_gen script which is no longer needed to build manpages.
* Added erlang-doc package which contains documentation in HTML and PDF
  formats. This package replaces erlang-doc-html package and it's easier
  to synchronize it with the main Erlang packages as it's built from
  a single source package (closes: #558451).
* Removed RPATH from ssl and crypto application binaries as required by
  Debian policy.
* Added libwxgtk2.4-dev and libwxgtk2.6-dev to build conflicts.
* Added a few dpendencies for erlang-dialyzer, erlang-et, erlang-observer
  and erlang-examples packages which now call functions from more modules
  than in 1:13.b.3.
* Added a workaround which disables vfork() for hppa architecture
  (closes: #562218).
* Strictened check for JDK 1.5 adding a call to String(int[], int, int)
  because GCJ 4.4 doesn't implement it and OpenJDK isn't available for all
  architectures.
* Fixed erlang-manpages package section.
* Made erlang-depends add only substvars which are requested in
  debian/control file. This minimizes number of warnings from dh_gencontrol.
  Also, improved descriptions of the functions in erlang-depends escript.
* Added erlang-erl-docgen package to erlang-nox dependencies.
* Made dummy packages erlang-nox and erlang-x11 architecture all.
* Cleaned up working with custom substitution variables in debian/rules.
* Reorganized debian/rules to ensure that manpages arent built twice, and
  aren't built at all if only architecture-dependent packages are requested.
* Fixed project links in README.Debian.
* Added a new package erlang-jinterface which provides tools for
  communication of Java programs with Erlang processes. This adds build
  depandency on default-jdk and as a result enables Java module for IDL
  compiler.
* Bumped standards version to 3.8.4.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 1997-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_SUITE).
 
24
-include_lib("test_server/include/test_server.hrl").
 
25
-include_lib("test_server/include/test_server_line.hrl").
 
26
-include_lib("kernel/include/file.hrl").
 
27
-export([all/1]).
 
28
 
 
29
-export([init_per_suite/1, end_per_suite/1]).
 
30
-export([init_per_testcase/2, end_per_testcase/2, fin_per_testcase/2]).
 
31
-export([config/1, comment/1, timetrap/1, timetrap_cancel/1, multiply_timetrap/1,
 
32
         init_per_s/1, init_per_tc/1, end_per_tc/1,
 
33
         timeconv/1, msgs/1, capture/1, timecall/1,
 
34
         do_times/1, do_times_mfa/1, do_times_fun/1,
 
35
         skip_cases/1, skip_case1/1, skip_case2/1, skip_case3/1, 
 
36
         skip_case4/1, skip_case5/1, skip_case6/1, skip_case7/1,
 
37
         skip_case8/1, skip_case9/1, undefined_functions/1,
 
38
         conf_init/1, check_new_conf/1, conf_cleanup/1,
 
39
         check_old_conf/1, conf_init_fail/1, start_stop_node/1,
 
40
         cleanup_nodes_init/1, check_survive_nodes/1, cleanup_nodes_fin/1,
 
41
         commercial/1]).
 
42
 
 
43
-export([dummy_function/0,dummy_function/1,doer/1]).
 
44
 
 
45
all(doc) -> ["Test Server self test"];
 
46
all(suite) ->
 
47
    [config, comment, timetrap, timetrap_cancel, multiply_timetrap,
 
48
     init_per_s, init_per_tc, end_per_tc,
 
49
     timeconv, msgs, capture, timecall, do_times, skip_cases,
 
50
     undefined_functions, commercial,
 
51
     {conf, conf_init, [check_new_conf], conf_cleanup},
 
52
     check_old_conf,
 
53
     {conf, conf_init_fail,[conf_member_skip],conf_cleanup_skip},
 
54
     start_stop_node,
 
55
     {conf, cleanup_nodes_init,[check_survive_nodes],cleanup_nodes_fin},
 
56
     config
 
57
    ].
 
58
 
 
59
 
 
60
init_per_suite(Config) ->
 
61
    [{init_per_suite_var,ok}|Config].
 
62
 
 
63
end_per_suite(_Config) ->
 
64
    ok.
 
65
 
 
66
init_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
 
67
    Dog = ?t:timetrap(?t:minutes(2)),
 
68
    Config1 = [{watchdog, Dog}|Config],
 
69
    case Func of
 
70
        init_per_tc ->
 
71
            [{strange_var, 1}|Config1];
 
72
        skip_case8 -> 
 
73
            {skipped, "This case should be noted as `Skipped'"};
 
74
        skip_case9 ->
 
75
            {skip, "This case should be noted as `Skipped'"};
 
76
        _ ->
 
77
            Config1
 
78
    end;
 
79
init_per_testcase(Func, Config) ->
 
80
    io:format("Func:~p",[Func]),
 
81
    io:format("Config:~p",[Config]),
 
82
    ?t:fail("Arguments to init_per_testcase not correct").
 
83
 
 
84
end_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
 
85
    Dog=?config(watchdog, Config),
 
86
    ?t:timetrap_cancel(Dog),
 
87
    case Func of
 
88
        end_per_tc -> io:format("CLEANUP => this test case is ok\n");
 
89
        _Other -> ok
 
90
    end;
 
91
end_per_testcase(Func, Config) ->
 
92
    io:format("Func:~p",[Func]),
 
93
    io:format("Config:~p",[Config]),
 
94
    ?t:fail("Arguments to end_per_testcase not correct").
 
95
 
 
96
fin_per_testcase(Func, Config) ->
 
97
    io:format("Func:~p",[Func]),
 
98
    io:format("Config:~p",[Config]),
 
99
    ?t:fail("fin_per_testcase/2 called, should have called end_per_testcase/2").
 
100
    
 
101
 
 
102
config(suite) -> [];
 
103
config(doc) -> ["Test that the Config variable is decent, ",
 
104
                "and that the std config variables are correct ",
 
105
                "(check that data/priv dir exists)."
 
106
                "Also check that ?config macro works."];
 
107
config(Config) when is_list(Config) ->
 
108
    is_tuplelist(Config),
 
109
    {value,{data_dir,Dd}}=lists:keysearch(data_dir,1,Config),
 
110
    {value,{priv_dir,Dp}}=lists:keysearch(priv_dir,1,Config),
 
111
    true=is_dir(Dd),
 
112
    {ok, _Bin}=file:read_file(filename:join(Dd, "dummy_file")),
 
113
    true=is_dir(Dp),
 
114
 
 
115
    Dd = ?config(data_dir,Config),
 
116
    Dp = ?config(priv_dir,Config),
 
117
    ok;
 
118
config(_Config) ->
 
119
    ?t:fail("Config variable is not a list.").
 
120
 
 
121
is_tuplelist([]) ->
 
122
    true;
 
123
is_tuplelist([{_A,_B}|Rest]) ->
 
124
    is_tuplelist(Rest);
 
125
is_tuplelist(_) ->
 
126
    false.
 
127
 
 
128
is_dir(Dir) ->
 
129
    case file:read_file_info(Dir) of
 
130
        {ok, #file_info{type=directory}} ->
 
131
            true;
 
132
        _ ->
 
133
            false
 
134
    end.
 
135
 
 
136
comment(suite) -> [];
 
137
comment(doc) -> ["Print a comment in the HTML log"];
 
138
comment(Config) when is_list(Config) ->
 
139
    ?t:comment("This comment should not occur in the HTML log because a later"
 
140
               " comment shall overwrite it"),
 
141
    ?t:comment("This comment is printed with the comment/1 function."
 
142
               " It should occur in the HTML log").
 
143
 
 
144
 
 
145
 
 
146
timetrap(suite) -> [];
 
147
timetrap(doc) -> ["Test that timetrap works."];
 
148
timetrap(Config) when is_list(Config) ->
 
149
    TrapAfter = 3000,
 
150
    Dog=?t:timetrap(TrapAfter),
 
151
    process_flag(trap_exit, true),
 
152
    TimeOut = TrapAfter * test_server:timetrap_scale_factor() + 1000,
 
153
    receive
 
154
        {'EXIT', Dog, {timetrap_timeout, _, _}} ->
 
155
            ok;
 
156
        {'EXIT', _OtherPid, {timetrap_timeout, _, _}} ->
 
157
            ?t:fail("EXIT signal from wrong process")
 
158
    after
 
159
        TimeOut ->
 
160
            ?t:fail("Timetrap is not working.")
 
161
    end,
 
162
    ?t:timetrap_cancel(Dog),
 
163
    ok.
 
164
 
 
165
 
 
166
timetrap_cancel(suite) -> [];
 
167
timetrap_cancel(doc) -> ["Test that timetrap_cancel works."];
 
168
timetrap_cancel(Config) when is_list(Config) ->
 
169
    Dog=?t:timetrap(1000),
 
170
    receive
 
171
    after
 
172
        500 ->
 
173
            ok
 
174
    end,
 
175
    ?t:timetrap_cancel(Dog),
 
176
    receive
 
177
    after 1000 ->
 
178
            ok
 
179
    end,
 
180
    ok.
 
181
 
 
182
multiply_timetrap(suite) -> [];
 
183
multiply_timetrap(doc) -> ["Test multiply timetrap"];
 
184
multiply_timetrap(Config) when is_list(Config) ->
 
185
    %% This simulates the call to test_server_ctrl:multiply_timetraps/1:
 
186
    put(test_server_multiply_timetraps,2),
 
187
 
 
188
    Dog = ?t:timetrap(500),
 
189
    timer:sleep(800),
 
190
    ?t:timetrap_cancel(Dog),
 
191
 
 
192
    %% Reset
 
193
    put(test_server_multiply_timetraps,1),
 
194
    ok.
 
195
 
 
196
 
 
197
init_per_s(suite) -> [];
 
198
init_per_s(doc) -> ["Test that a Config that is altered in ",
 
199
                     "init_per_suite gets through to the testcases."];
 
200
init_per_s(Config) ->
 
201
    %% Check that the config var sent from init_per_suite
 
202
    %% really exists.
 
203
    {value, {init_per_suite_var, ok}} = 
 
204
        lists:keysearch(init_per_suite_var,1,Config),
 
205
 
 
206
    %% Check that the other variables still exist.
 
207
    {value,{data_dir,_Dd}}=lists:keysearch(data_dir,1,Config),
 
208
    {value,{priv_dir,_Dp}}=lists:keysearch(priv_dir,1,Config),
 
209
    ok.
 
210
 
 
211
init_per_tc(suite) -> [];
 
212
init_per_tc(doc) -> ["Test that a Config that is altered in ",
 
213
                     "init_per_testcase gets through to the ",
 
214
                     "actual testcase."];
 
215
init_per_tc(Config) ->
 
216
    %% Check that the config var sent from init_per_testcase
 
217
    %% really exists.
 
218
    {value, {strange_var, 1}} = lists:keysearch(strange_var,1,Config),
 
219
 
 
220
    %% Check that the other variables still exist.
 
221
    {value,{data_dir,_Dd}}=lists:keysearch(data_dir,1,Config),
 
222
    {value,{priv_dir,_Dp}}=lists:keysearch(priv_dir,1,Config),
 
223
    ok.
 
224
 
 
225
end_per_tc(suite) -> [];
 
226
end_per_tc(doc) -> ["Test that end_per_testcase/2 is called even if"
 
227
                    " test case fails"];
 
228
end_per_tc(Config) when is_list(Config) ->
 
229
    ?t:fail("This case should fail! Check that \"CLEANUP\" is"
 
230
            " printed in the minor log file.").
 
231
 
 
232
 
 
233
timeconv(suite) -> [];
 
234
timeconv(doc) -> ["Test that the time unit conversion functions ",
 
235
                  "works."];
 
236
timeconv(Config) when is_list(Config) ->
 
237
    Val=2,
 
238
    Secs=Val*1000,
 
239
    Mins=Secs*60,
 
240
    Hrs=Mins*60,
 
241
    Secs=?t:seconds(2),
 
242
    Mins=?t:minutes(2),
 
243
    Hrs=?t:hours(2),
 
244
    ok.
 
245
 
 
246
 
 
247
msgs(suite) -> [];
 
248
msgs(doc) -> ["Tests the messages_get function."];
 
249
msgs(Config) when is_list(Config) ->
 
250
    self() ! {hej, du},
 
251
    self() ! {lite, "data"},
 
252
    self() ! en_atom,
 
253
    [{hej, du}, {lite, "data"}, en_atom] = ?t:messages_get(),
 
254
    ok.
 
255
 
 
256
capture(suite) -> [];
 
257
capture(doc) -> ["Test that the capture functions work properly."];
 
258
capture(Config) when is_list(Config) ->
 
259
    String1="abcedfghjiklmnopqrstuvwxyz",
 
260
    String2="0123456789",
 
261
    ?t:capture_start(),
 
262
    io:format(String1),
 
263
    [String1]=?t:capture_get(),
 
264
    io:format(String2),
 
265
    [String2]=?t:capture_get(),
 
266
    ?t:capture_stop(),
 
267
    []=?t:capture_get(),
 
268
    io:format(String2),
 
269
    []=?t:capture_get(),
 
270
    ok.
 
271
 
 
272
timecall(suite) -> [];
 
273
timecall(doc) -> ["Tests that timed calls work."];
 
274
timecall(Config) when is_list(Config) ->
 
275
    {_Time1, liten_apa_e_oxo_farlig} = ?t:timecall(?MODULE, dummy_function, []),
 
276
    {Time2, jag_ar_en_gorilla} = ?t:timecall(?MODULE, dummy_function, [gorilla]),
 
277
    DTime=round(Time2),
 
278
    if
 
279
        DTime<1 ->
 
280
            ?t:fail("Timecall reported a too low time.");
 
281
        DTime==1 ->
 
282
            ok;
 
283
        DTime>1 ->
 
284
            ?t:fail("Timecall reported a too high time.")
 
285
    end,
 
286
    ok.
 
287
 
 
288
dummy_function() ->
 
289
    liten_apa_e_oxo_farlig.
 
290
dummy_function(gorilla) ->
 
291
    receive after 1000 -> ok end,
 
292
    jag_ar_en_gorilla.
 
293
 
 
294
 
 
295
do_times(suite) -> [do_times_mfa, do_times_fun];
 
296
do_times(doc) -> ["Test the do_times function."].
 
297
 
 
298
do_times_mfa(suite) -> [];
 
299
do_times_mfa(doc) -> ["Test the do_times function with M,F,A given."];
 
300
do_times_mfa(Config) when is_list(Config) ->
 
301
    ?t:do_times(100, ?MODULE, doer, [self()]),
 
302
    100=length(?t:messages_get()),
 
303
    ok.
 
304
 
 
305
do_times_fun(suite) -> [];
 
306
do_times_fun(doc) -> ["Test the do_times function with fun given."];
 
307
do_times_fun(Config) when is_list(Config) ->
 
308
    Self = self(),
 
309
    ?t:do_times(100, fun() -> doer(Self) end),
 
310
    100=length(?t:messages_get()),
 
311
    ok.
 
312
 
 
313
doer(From) ->
 
314
    From ! a,
 
315
    ok.
 
316
 
 
317
skip_cases(doc) -> ["Test all possible ways to skip a test case."];
 
318
skip_cases(suite) -> [skip_case1, skip_case2, skip_case3, skip_case4,
 
319
                      skip_case5, skip_case6, skip_case7, skip_case8,
 
320
                      skip_case9].
 
321
 
 
322
skip_case1(suite) -> [];
 
323
skip_case1(doc) -> ["Test that you can return {skipped, Reason},"
 
324
                    " and that Reason is in the comment field in the HTML log"];
 
325
skip_case1(Config) when is_list(Config) ->
 
326
    %% If this comment shows, the case failed!!
 
327
    ?t:comment("ERROR: This case should have been noted as `Skipped'"),
 
328
    %% The Reason in {skipped, Reason} should overwrite a 'comment'
 
329
    {skipped, "This case should be noted as `Skipped'"}.
 
330
 
 
331
skip_case2(suite) -> [];
 
332
skip_case2(doc) -> ["Test that you can return {skipped, Reason},"
 
333
                    " and that Reason is in the comment field in the HTML log"];
 
334
skip_case2(Config) when is_list(Config) ->
 
335
    %% If this comment shows, the case failed!!
 
336
    ?t:comment("ERROR: This case should have been noted as `Skipped'"),
 
337
    %% The Reason in {skipped, Reason} should overwrite a 'comment'
 
338
    exit({skipped, "This case should be noted as `Skipped'"}).    
 
339
 
 
340
skip_case3(suite) -> [];
 
341
skip_case3(doc) -> ["Test that you can return {skip, Reason},"
 
342
                    " and that Reason is in the comment field in the HTML log"];
 
343
skip_case3(Config) when is_list(Config) ->
 
344
    %% If this comment shows, the case failed!!
 
345
    ?t:comment("ERROR: This case should have been noted as `Skipped'"),
 
346
    %% The Reason in {skip, Reason} should overwrite a 'comment'
 
347
    {skip, "This case should be noted as `Skipped'"}.
 
348
 
 
349
skip_case4(suite) -> [];
 
350
skip_case4(doc) -> ["Test that you can return {skip, Reason},"
 
351
                    " and that Reason is in the comment field in the HTML log"];
 
352
skip_case4(Config) when is_list(Config) ->
 
353
    %% If this comment shows, the case failed!!
 
354
    ?t:comment("ERROR: This case should have been noted as `Skipped'"),
 
355
    %% The Reason in {skip, Reason} should overwrite a 'comment'
 
356
    exit({skip, "This case should be noted as `Skipped'"}).    
 
357
 
 
358
skip_case5(suite) -> {skipped, "This case should be noted as `Skipped'"};
 
359
skip_case5(doc) -> ["Test that you can return {skipped, Reason}"
 
360
                    " from the specification clause"].
 
361
 
 
362
skip_case6(suite) -> {skip, "This case should be noted as `Skipped'"};
 
363
skip_case6(doc) -> ["Test that you can return {skip, Reason}"
 
364
                    " from the specification clause"].
 
365
 
 
366
skip_case7(suite) -> [];
 
367
skip_case7(doc) -> ["Test that skip works from a test specification file"];
 
368
skip_case7(Config) when is_list(Config) ->
 
369
    %% This case shall be skipped by adding 
 
370
    %% {skip, {test_server_SUITE, skip_case7, Reason}}. 
 
371
    %% to the test specification file.
 
372
    ?t:fail("This case should have been Skipped by the .spec file").
 
373
 
 
374
skip_case8(suite) -> [];
 
375
skip_case8(doc) -> ["Test that {skipped, Reason} works from"
 
376
                    " init_per_testcase/2"];
 
377
skip_case8(Config) when is_list(Config) ->
 
378
    %% This case shall be skipped by adding a specific clause to 
 
379
    %% returning {skipped, Reason} from init_per_testcase/2 for this case. 
 
380
    ?t:fail("This case should have been Skipped by init_per_testcase/2").
 
381
 
 
382
skip_case9(suite) -> [];
 
383
skip_case9(doc) -> ["Test that {skip, Reason} works from a init_per_testcase/2"];
 
384
skip_case9(Config) when is_list(Config) ->
 
385
    %% This case shall be skipped by adding a specific clause to 
 
386
    %% returning {skip, Reason} from init_per_testcase/2 for this case. 
 
387
    ?t:fail("This case should have been Skipped by init_per_testcase/2").
 
388
 
 
389
undefined_functions(suite) -> [];
 
390
undefined_functions(doc) -> ["Check for calls to undefined functions in"
 
391
                             " test_server."
 
392
                             "Skip if cover is running"];
 
393
undefined_functions(Config) when is_list(Config) ->
 
394
    case whereis(cover_server) of
 
395
        Pid when is_pid(Pid) -> 
 
396
            {skip,"Cover is running"};
 
397
        undefined -> 
 
398
            undefined_functions()
 
399
    end.
 
400
 
 
401
undefined_functions() ->
 
402
    TestServerDir = filename:dirname(code:which(test_server)),
 
403
    Res = xref:d(TestServerDir),
 
404
    
 
405
    {value,{unused,Unused}} = lists:keysearch(unused, 1, Res),
 
406
    case Unused of
 
407
        [] -> ok;
 
408
        _ ->
 
409
            lists:foreach(fun (MFA) ->
 
410
                                  io:format("~s unused", [format_mfa(MFA)])
 
411
                          end, Unused)
 
412
    end,
 
413
    
 
414
    {value,{undefined,Undef0}} = lists:keysearch(undefined, 1, Res),
 
415
    Undef = [U || U <- Undef0, not unresolved(U)],
 
416
    case Undef of
 
417
        [] -> ok;
 
418
        _ ->
 
419
            lists:foreach(fun ({MFA1,MFA2}) ->
 
420
                                  io:format("~s calls undefined ~s",
 
421
                                            [format_mfa(MFA1),format_mfa(MFA2)])
 
422
                          end, Undef),
 
423
            ?t:fail({length(Undef),undefined_functions_in_otp})
 
424
    end,
 
425
    ok.
 
426
 
 
427
unresolved({_,{_,'$F_EXPR',_}}) -> true;
 
428
unresolved(_) -> false.
 
429
 
 
430
format_mfa({M,F,A}) ->
 
431
    lists:flatten(io_lib:format("~s:~s/~p", [M,F,A])).
 
432
 
 
433
conf_init(doc) -> ["Test successful conf case: Change Config parameter"];
 
434
conf_init(Config) when is_list(Config) ->
 
435
    [{conf_init_var,1389}|Config].
 
436
 
 
437
check_new_conf(suite) -> [];
 
438
check_new_conf(doc) -> ["Check that Config parameter changed by"
 
439
                        " conf_init is used"];
 
440
check_new_conf(Config) when is_list(Config) ->
 
441
    1389 = ?config(conf_init_var,Config),
 
442
    ok.
 
443
 
 
444
conf_cleanup(doc) -> ["Test successful conf case: Restore Config parameter"];
 
445
conf_cleanup(Config) when is_list(Config) ->
 
446
    lists:keydelete(conf_init_var,1,Config).
 
447
 
 
448
check_old_conf(suite) -> [];
 
449
check_old_conf(doc) -> ["Test that the restored Config is used after a"
 
450
                        " conf cleanup"];
 
451
check_old_conf(Config) when is_list(Config) ->
 
452
    undefined = ?config(conf_init_var,Config),
 
453
    ok.
 
454
 
 
455
conf_init_fail(doc) -> ["Test that config members are skipped if"
 
456
                        " conf init function fails."];
 
457
conf_init_fail(Config) when is_list(Config) -> 
 
458
    ?t:fail("This case should fail! Check that conf_member_skip and"
 
459
            " conf_cleanup_skip are skipped.").
 
460
 
 
461
 
 
462
 
 
463
start_stop_node(suite) -> [];
 
464
start_stop_node(doc) -> ["Test start and stop of slave and peer nodes"];
 
465
start_stop_node(Config) when is_list(Config) ->
 
466
    {ok,Node2} = ?t:start_node(node2,peer,[]),
 
467
    {error, _} = ?t:start_node(node2,peer,[{fail_on_error,false}]),
 
468
    true = lists:member(Node2,nodes()),
 
469
 
 
470
    {ok,Node3} = ?t:start_node(node3,slave,[]),
 
471
    {error, _} = ?t:start_node(node3,slave,[]),
 
472
    true = lists:member(Node3,nodes()),
 
473
 
 
474
    {ok,Node4} = ?t:start_node(node4,peer,[{wait,false}]),
 
475
    case lists:member(Node4,nodes()) of
 
476
        true -> 
 
477
            ?t:comment("WARNING: Node started with {wait,false}"
 
478
                             " is up faster than expected...");
 
479
        false ->
 
480
            wait_for_node(Node4,0),
 
481
            true = lists:member(Node4,nodes())
 
482
    end,
 
483
 
 
484
    true = ?t:stop_node(Node2),
 
485
    false = lists:member(Node2,nodes()),
 
486
 
 
487
    true = ?t:stop_node(Node3),
 
488
    false = lists:member(Node3,nodes()),
 
489
    
 
490
    true = ?t:stop_node(Node4),
 
491
    false = lists:member(Node4,nodes()),
 
492
    timer:sleep(2000),
 
493
    false = ?t:stop_node(Node4),
 
494
 
 
495
    ok.
 
496
 
 
497
 
 
498
wait_for_node(Node,Acc) ->
 
499
    case net_adm:ping(Node) of
 
500
        pang -> 
 
501
            timer:sleep(100),
 
502
            wait_for_node(Node,Acc+100);
 
503
        pong ->
 
504
            Acc
 
505
    end.
 
506
 
 
507
cleanup_nodes_init(doc) -> ["Test that nodes are terminated when test case"
 
508
                            " is finished unless {cleanup,false} is given."];
 
509
cleanup_nodes_init(Config) when is_list(Config) ->
 
510
    {ok,DieSlave} = ?t:start_node(die_slave, slave, []),
 
511
    {ok,SurviveSlave} = ?t:start_node(survive_slave, slave, [{cleanup,false}]),
 
512
    {ok,DiePeer} = ?t:start_node(die_peer, peer, []),
 
513
    {ok,SurvivePeer} = ?t:start_node(survive_peer, peer, [{cleanup,false}]),
 
514
    [{die_slave,DieSlave},
 
515
     {survive_slave,SurviveSlave},
 
516
     {die_peer,DiePeer},
 
517
     {survive_peer,SurvivePeer} | Config].
 
518
 
 
519
 
 
520
 
 
521
check_survive_nodes(suite) -> [];
 
522
check_survive_nodes(doc) -> ["Test that nodes with {cleanup,false} survived"];
 
523
check_survive_nodes(Config) when is_list(Config) ->
 
524
    timer:sleep(1000),
 
525
    false = lists:member(?config(die_slave,Config),nodes()),
 
526
    true = lists:member(?config(survive_slave,Config),nodes()),
 
527
    false = lists:member(?config(die_peer,Config),nodes()),
 
528
    true = lists:member(?config(survive_peer,Config),nodes()),
 
529
    ok.
 
530
 
 
531
 
 
532
cleanup_nodes_fin(doc) -> ["Test that nodes started with {cleanup,false}"
 
533
                           " can be stopped"];
 
534
cleanup_nodes_fin(Config) when is_list(Config) ->
 
535
    Slave = ?config(survive_slave,Config),
 
536
    Peer = ?config(survive_peer,Config),
 
537
    
 
538
    true = ?t:stop_node(Slave),
 
539
    false = lists:member(Slave,nodes()),
 
540
    true = ?t:stop_node(Peer),
 
541
    false = lists:member(Peer,nodes()),
 
542
    
 
543
    C1 = lists:keydelete(die_slave,1,Config),
 
544
    C2 = lists:keydelete(survive_slave,1,C1),
 
545
    C3 = lists:keydelete(die_peer,1,C2),
 
546
    lists:keydelete(survive_peer,1,C3).
 
547
 
 
548
commercial(Config) when is_list(Config) ->
 
549
    case ?t:is_commercial() of
 
550
        false -> {comment,"Open-source build"};
 
551
        true -> {comment,"Commercial build"}
 
552
    end.
 
553
 
 
554