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

« back to all changes in this revision

Viewing changes to lib/kernel/test/global_group_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
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 1998-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1998-2011. All Rights Reserved.
5
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
19
19
 
20
20
-module(global_group_SUITE).
21
21
 
22
 
-export([all/1]).
 
22
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2,
 
23
         init_per_suite/1, end_per_suite/1]).
23
24
-export([start_gg_proc/1, no_gg_proc/1, no_gg_proc_sync/1, compatible/1, 
24
25
         one_grp/1, one_grp_x/1, two_grp/1, hidden_groups/1, test_exit/1]).
25
26
-export([init/1, init/2, init2/2, start_proc/1, start_proc_rereg/1]).
26
27
 
27
 
-export([init_per_testcase/2, fin_per_testcase/2]).
 
28
-export([init_per_testcase/2, end_per_testcase/2]).
28
29
 
29
30
%-compile(export_all).
30
31
 
31
 
-include("test_server.hrl").
 
32
-include_lib("test_server/include/test_server.hrl").
32
33
 
33
34
-define(NODES, [node()|nodes()]).
34
35
 
35
36
-define(UNTIL(Seq), loop_until_true(fun() -> Seq end)).
36
37
 
37
 
all(suite) -> 
38
 
    [start_gg_proc, no_gg_proc, no_gg_proc_sync, 
39
 
     compatible, one_grp, one_grp_x, two_grp, test_exit,
40
 
     hidden_groups].
 
38
suite() -> [{ct_hooks,[ts_install_cth]}].
 
39
 
 
40
all() -> 
 
41
    [start_gg_proc, no_gg_proc, no_gg_proc_sync, compatible,
 
42
     one_grp, one_grp_x, two_grp, test_exit, hidden_groups].
 
43
 
 
44
groups() -> 
 
45
    [].
 
46
 
 
47
init_per_group(_GroupName, Config) ->
 
48
        Config.
 
49
 
 
50
end_per_group(_GroupName, Config) ->
 
51
        Config.
 
52
 
 
53
 
 
54
init_per_suite(Config) ->
 
55
 
 
56
    %% Copied from test_server_ctrl ln 647, we have to do this here as
 
57
    %% the test_server only does this when run without common_test
 
58
    global:sync(),
 
59
    case global:whereis_name(test_server) of
 
60
        undefined ->
 
61
            io:format(user, "Registering test_server globally!~n",[]),
 
62
            global:register_name(test_server, whereis(test_server_ctrl));
 
63
        Pid ->
 
64
            case node() of
 
65
                N when N == node(Pid) ->
 
66
                    io:format(user, "Warning: test_server already running!\n", []),
 
67
                    global:re_register_name(test_server,self());
 
68
                _ ->
 
69
                    ok
 
70
            end
 
71
    end,
 
72
    Config.
 
73
 
 
74
end_per_suite(_Config) ->
 
75
    global:unregister_name(test_server),
 
76
    ok.
41
77
 
42
78
-define(TESTCASE, testcase_name).
43
79
-define(testcase, ?config(?TESTCASE, Config)).
46
82
    Dog=?t:timetrap(?t:minutes(5)),
47
83
    [{?TESTCASE, Case}, {watchdog, Dog}|Config].
48
84
 
49
 
fin_per_testcase(_Func, Config) ->
 
85
end_per_testcase(_Func, Config) ->
50
86
    Dog=?config(watchdog, Config),
51
87
    ?t:timetrap_cancel(Dog).
52
88
 
64
100
 
65
101
    ?line Dir = ?config(priv_dir, Config),
66
102
    ?line File = filename:join(Dir, "global_group.config"),
67
 
    ?line {ok, Fd}=file:open(File, write),
 
103
    ?line {ok, Fd}=file:open(File, [write]),
68
104
    [Ncp1,Ncp2,Ncp3] = node_names([cp1, cp2, cp3], Config),
69
105
    ?line config(Fd, Ncp1, Ncp2, Ncp3, "cpx", "cpy", "cpz", "cpq"),
70
106
 
99
135
 
100
136
    ?line Dir = ?config(priv_dir, Config),
101
137
    ?line File = filename:join(Dir, "no_global_group.config"),
102
 
    ?line {ok, Fd} = file:open(File, write),
 
138
    ?line {ok, Fd} = file:open(File, [write]),
103
139
    ?line config_no(Fd),
104
140
 
105
141
    ?line NN = node_name(atom_to_list(node())),
164
200
    ?line Own_nodes_should = [node(), Cp1nn, Cp2nn, Cp3nn, 
165
201
                              Cpxnn, Cpynn, Cpznn],
166
202
    ?line Own_nodes = rpc:call(Cp3, global_group, own_nodes, []), 
167
 
    ?line true = (Own_nodes -- Own_nodes_should) =:= [],
168
 
    ?line true = (Own_nodes_should -- Own_nodes) =:= [],
 
203
    ?line [] = (Own_nodes -- Own_nodes_should),
 
204
    ?line [] = (Own_nodes_should -- Own_nodes),
169
205
    
170
206
    ?line Pid2 = rpc:call(Cp1, global_group, send, [test2, {ping, self()}]),
171
207
    ?line receive
272
308
 
273
309
    ?line Dir = ?config(priv_dir, Config),
274
310
    ?line File = filename:join(Dir, "no_global_group_sync.config"),
275
 
    ?line {ok, Fd} = file:open(File, write),
 
311
    ?line {ok, Fd} = file:open(File, [write]),
276
312
 
277
313
    [Ncp1,Ncp2,Ncp3,Ncpx,Ncpy,Ncpz] = 
278
314
        node_names([cp1,cp2,cp3,cpx,cpy,cpz], Config),
339
375
    ?line Own_nodes_should = [node(), Cp1nn, Cp2nn, Cp3nn, 
340
376
                              Cpxnn, Cpynn, Cpznn],
341
377
    ?line Own_nodes = rpc:call(Cp3, global_group, own_nodes, []), 
342
 
    ?line true = (Own_nodes -- Own_nodes_should) =:= [],
343
 
    ?line true = (Own_nodes_should -- Own_nodes) =:= [],
 
378
    ?line [] = (Own_nodes -- Own_nodes_should),
 
379
    ?line [] = (Own_nodes_should -- Own_nodes),
344
380
    
345
381
    ?line Pid2 = rpc:call(Cp1, global_group, send, [test2, {ping, self()}]),
346
382
    ?line receive
446
482
 
447
483
    ?line Dir = ?config(priv_dir, Config),
448
484
    ?line File = filename:join(Dir, "global_group_comp.config"),
449
 
    ?line {ok, Fd} = file:open(File, write),
 
485
    ?line {ok, Fd} = file:open(File, [write]),
450
486
 
451
487
    [Ncp1,Ncp2,Ncp3,Ncpx,Ncpy,Ncpz] = 
452
488
        node_names([cp1,cp2,cp3,cpx,cpy,cpz], Config),
513
549
    ?line Own_nodes_should = [node(), Cp1nn, Cp2nn, Cp3nn, 
514
550
                              Cpxnn, Cpynn, Cpznn],
515
551
    ?line Own_nodes = rpc:call(Cp3, global_group, own_nodes, []), 
516
 
    ?line true = (Own_nodes -- Own_nodes_should) =:= [],
517
 
    ?line true = (Own_nodes_should -- Own_nodes) =:= [],
 
552
    ?line [] = (Own_nodes -- Own_nodes_should),
 
553
    ?line [] = (Own_nodes_should -- Own_nodes),
518
554
    
519
555
    ?line Pid2 = rpc:call(Cp1, global_group, send, [test2, {ping, self()}]),
520
556
    ?line receive
619
655
 
620
656
    ?line Dir = ?config(priv_dir, Config),
621
657
    ?line File = filename:join(Dir, "global_group.config"),
622
 
    ?line {ok, Fd} = file:open(File, write),
 
658
    ?line {ok, Fd} = file:open(File, [write]),
623
659
    [Ncp1,Ncp2,Ncp3] = node_names([cp1, cp2, cp3], Config),
624
660
    ?line config(Fd, Ncp1, Ncp2, Ncp3, "cpx", "cpy", "cpz", "cpq"),
625
661
 
706
742
 
707
743
    ?line Dir = ?config(priv_dir, Config),
708
744
    ?line File = filename:join(Dir, "global_group.config"),
709
 
    ?line {ok, Fd} = file:open(File, write),
 
745
    ?line {ok, Fd} = file:open(File, [write]),
710
746
    [Ncp1,Ncp2,Ncp3] = node_names([cp1, cp2, cp3], Config),
711
747
    ?line config(Fd, Ncp1, Ncp2, Ncp3, "cpx", "cpy", "cpz", "cpq"),
712
748
 
768
804
 
769
805
    ?line Dir = ?config(priv_dir, Config),
770
806
    ?line File = filename:join(Dir, "global_group.config"),
771
 
    ?line {ok, Fd} = file:open(File, write),
 
807
    ?line {ok, Fd} = file:open(File, [write]),
772
808
 
773
809
    [Ncp1,Ncp2,Ncp3,Ncpx,Ncpy,Ncpz,Ncpq] = 
774
810
        node_names([cp1,cp2,cp3,cpx,cpy,cpz,cpq], Config),
1068
1104
 
1069
1105
    ?line Dir = ?config(priv_dir, Config),
1070
1106
    ?line File = filename:join(Dir, "global_group.config"),
1071
 
    ?line {ok, Fd} = file:open(File, write),
 
1107
    ?line {ok, Fd} = file:open(File, [write]),
1072
1108
 
1073
1109
    [Ncp1,Ncp2,Ncp3,Ncpx,Ncpy,Ncpz,Ncpq] = 
1074
1110
        node_names([cp1,cp2,cp3,cpx,cpy,cpz,cpq], Config),