~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/inets/test/inets_sup_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2004-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
-module(inets_sup_SUITE).
 
22
 
 
23
-include("test_server.hrl").
 
24
-include("test_server_line.hrl").
 
25
 
 
26
%% Note: This directive should only be used in test suites.
 
27
-compile(export_all).
 
28
 
 
29
all(doc) ->
 
30
    ["Test that the inets supervisorstructur is the expected one."];
 
31
all(suite) ->
 
32
    [
 
33
     default_tree, 
 
34
     ftpc_worker, 
 
35
     tftpd_worker,
 
36
     httpd_subtree, 
 
37
     httpc_subtree
 
38
    ].
 
39
 
 
40
%%--------------------------------------------------------------------
 
41
%% Function: init_per_suite(Config) -> Config
 
42
%% Config - [tuple()]
 
43
%%   A list of key/value pairs, holding the test case configuration.
 
44
%% Description: Initiation before the whole suite
 
45
%%
 
46
%% Note: This function is free to add any key/value pairs to the Config
 
47
%% variable, but should NOT alter/remove any existing entries.
 
48
%%--------------------------------------------------------------------
 
49
init_per_suite(Config) ->
 
50
    Config.
 
51
 
 
52
%%--------------------------------------------------------------------
 
53
%% Function: end_per_suite(Config) -> _
 
54
%% Config - [tuple()]
 
55
%%   A list of key/value pairs, holding the test case configuration.
 
56
%% Description: Cleanup after the whole suite
 
57
%%--------------------------------------------------------------------
 
58
end_per_suite(_) ->
 
59
    inets:stop(),
 
60
    ok.
 
61
 
 
62
%%--------------------------------------------------------------------
 
63
%% Function: init_per_testcase(Case, Config) -> Config
 
64
%% Case - atom()
 
65
%%   Name of the test case that is about to be run.
 
66
%% Config - [tuple()]
 
67
%%   A list of key/value pairs, holding the test case configuration.
 
68
%%
 
69
%% Description: Initiation before each test case
 
70
%%
 
71
%% Note: This function is free to add any key/value pairs to the Config
 
72
%% variable, but should NOT alter/remove any existing entries.
 
73
%%--------------------------------------------------------------------
 
74
init_per_testcase(httpd_subtree, Config) ->
 
75
    io:format("init_per_testcase(httpd_subtree) -> entry with"
 
76
              "~n   Config: ~p"
 
77
              "~n", [Config]),
 
78
    Dog = test_server:timetrap(?t:minutes(1)),
 
79
    NewConfig = lists:keydelete(watchdog, 1, Config),
 
80
 
 
81
    DataDir = ?config(data_dir, Config), 
 
82
    PrivDir = ?config(priv_dir, Config),                           
 
83
    ServerROOT = filename:join(PrivDir, "server_root"),
 
84
    DocROOT = filename:join(PrivDir, "htdocs"),
 
85
    ConfDir = filename:join(ServerROOT, "conf"),
 
86
 
 
87
    io:format("init_per_testcase(httpd_subtree) -> create dir(s)"
 
88
              "~n", []),
 
89
    file:make_dir(ServerROOT), %% until http_test is cleaned up!
 
90
    ok = file:make_dir(DocROOT),
 
91
    ok = file:make_dir(ConfDir),    
 
92
 
 
93
    io:format("init_per_testcase(httpd_subtree) -> copy file(s)"
 
94
              "~n", []),
 
95
    {ok, _} = inets_test_lib:copy_file("simple.conf", DataDir, PrivDir),
 
96
    {ok, _} = inets_test_lib:copy_file("mime.types", DataDir, ConfDir),
 
97
    
 
98
    io:format("init_per_testcase(httpd_subtree) -> write file(s)"
 
99
              "~n", []),
 
100
    ConfFile = filename:join(PrivDir, "simple.conf"),
 
101
    {ok, Fd} = file:open(ConfFile, [append]),
 
102
    ok = file:write(Fd, "ServerRoot " ++ ServerROOT ++ "\n"),
 
103
    ok = file:write(Fd, "DocumentRoot " ++ DocROOT ++ "\n"),
 
104
    ok = file:close(Fd),
 
105
    
 
106
    %% To make sure application:set_env is not overwritten by any
 
107
    %% app-file settings.
 
108
    io:format("init_per_testcase(httpd_subtree) -> load inets app"
 
109
              "~n", []),
 
110
    application:load(inets),
 
111
    io:format("init_per_testcase(httpd_subtree) -> update inets env"
 
112
              "~n", []),
 
113
    ok = application:set_env(inets, services, [{httpd, ConfFile}]),
 
114
    
 
115
    try
 
116
        io:format("init_per_testcase(httpd_subtree) -> start inets app"
 
117
                  "~n", []),
 
118
        ok = inets:start(),
 
119
        io:format("init_per_testcase(httpd_subtree) -> done"
 
120
                  "~n", []),
 
121
        [{watchdog, Dog}, {server_root, ServerROOT}, {doc_root, DocROOT},
 
122
         {conf_dir, ConfDir}| NewConfig]
 
123
    catch
 
124
        _:Reason ->
 
125
            io:format("init_per_testcase(httpd_subtree) -> "
 
126
                      "failed starting inets - cleanup"
 
127
                      "~n   Reason: ~p"
 
128
                      "~n", [Reason]),
 
129
            application:unset_env(inets, services),
 
130
            application:unload(inets),
 
131
            exit({failed_starting_inets, Reason})
 
132
    end;
 
133
    
 
134
 
 
135
init_per_testcase(Case, Config) ->
 
136
    io:format("init_per_testcase(~p) -> entry with"
 
137
              "~n   Config: ~p"
 
138
              "~n", [Case, Config]),
 
139
    Dog = test_server:timetrap(?t:minutes(5)),
 
140
    NewConfig = lists:keydelete(watchdog, 1, Config),
 
141
    Stop = inets:stop(),
 
142
    io:format("init_per_testcase(~p) -> Stop: ~p"
 
143
              "~n", [Case, Stop]),
 
144
    ok = inets:start(),
 
145
    [{watchdog, Dog} | NewConfig].
 
146
 
 
147
 
 
148
%%--------------------------------------------------------------------
 
149
%% Function: end_per_testcase(Case, Config) -> _
 
150
%% Case - atom()
 
151
%%   Name of the test case that is about to be run.
 
152
%% Config - [tuple()]
 
153
%%   A list of key/value pairs, holding the test case configuration.
 
154
%% Description: Cleanup after each test case
 
155
%%--------------------------------------------------------------------
 
156
end_per_testcase(httpd_subtree, Config) ->
 
157
    Dog = ?config(watchdog, Config),
 
158
    test_server:timetrap_cancel(Dog),
 
159
    PrivDir = ?config(priv_dir, Config),                           
 
160
    inets_test_lib:del_dirs(PrivDir),
 
161
    ok;
 
162
 
 
163
end_per_testcase(_, Config) ->
 
164
    Dog = ?config(watchdog, Config),
 
165
    test_server:timetrap_cancel(Dog),
 
166
    inets:stop(),
 
167
    ok.
 
168
 
 
169
%%-------------------------------------------------------------------------
 
170
%% Test cases starts here.
 
171
%%-------------------------------------------------------------------------
 
172
 
 
173
 
 
174
%%-------------------------------------------------------------------------
 
175
%% default_tree
 
176
%%-------------------------------------------------------------------------
 
177
default_tree(doc) ->
 
178
    ["Makes sure the correct processes are started and linked," 
 
179
     "in the default case."];
 
180
default_tree(suite) ->
 
181
    [];
 
182
default_tree(Config) when is_list(Config) ->
 
183
    TopSupChildren = supervisor:which_children(inets_sup),
 
184
    4 = length(TopSupChildren),
 
185
    {value, {httpd_sup, _, supervisor,[httpd_sup]}} =
 
186
        lists:keysearch(httpd_sup, 1, TopSupChildren),
 
187
    {value, {httpc_sup, _,supervisor,[httpc_sup]}} = 
 
188
        lists:keysearch(httpc_sup, 1, TopSupChildren),
 
189
    {value, {ftp_sup,_,supervisor,[ftp_sup]}} = 
 
190
        lists:keysearch(ftp_sup, 1, TopSupChildren),
 
191
    {value, {tftp_sup,_,supervisor,[tftp_sup]}} = 
 
192
        lists:keysearch(tftp_sup, 1, TopSupChildren),
 
193
 
 
194
    HttpcSupChildren = supervisor:which_children(httpc_sup),
 
195
    {value, {httpc_profile_sup,_, supervisor, [httpc_profile_sup]}} =
 
196
        lists:keysearch(httpc_profile_sup, 1, HttpcSupChildren),
 
197
    {value, {httpc_handler_sup,_, supervisor, [httpc_handler_sup]}} =
 
198
        lists:keysearch(httpc_handler_sup, 1, HttpcSupChildren),
 
199
    
 
200
    [] = supervisor:which_children(ftp_sup),
 
201
 
 
202
    [] = supervisor:which_children(httpd_sup),
 
203
 
 
204
    %% Default profile
 
205
    [{httpc_manager, _, worker,[httpc_manager]}]
 
206
        = supervisor:which_children(httpc_profile_sup),
 
207
    
 
208
    [] = supervisor:which_children(httpc_handler_sup),
 
209
     
 
210
    [] = supervisor:which_children(tftp_sup),
 
211
 
 
212
    ok.
 
213
 
 
214
 
 
215
%%-------------------------------------------------------------------------
 
216
%% ftpc_worker
 
217
%%-------------------------------------------------------------------------
 
218
ftpc_worker(doc) ->
 
219
    ["Makes sure the ftp worker processes are added and removed "
 
220
     "appropriatly to/from the supervison tree."]; 
 
221
ftpc_worker(suite) ->
 
222
    [];
 
223
ftpc_worker(Config) when is_list(Config) ->
 
224
    inets:disable_trace(),
 
225
    inets:enable_trace(max, io, ftpc), 
 
226
    [] = supervisor:which_children(ftp_sup),
 
227
    try
 
228
        begin
 
229
            {_Tag, FtpdHost} = ftp_suite_lib:dirty_select_ftpd_host(Config),
 
230
            case inets:start(ftpc, [{host, FtpdHost}]) of
 
231
                {ok, Pid} ->
 
232
                    case supervisor:which_children(ftp_sup) of
 
233
                        [{_,_, worker, [ftp]}] ->
 
234
                            inets:stop(ftpc, Pid), 
 
235
                            test_server:sleep(5000),
 
236
                            [] = supervisor:which_children(ftp_sup),
 
237
                            inets:disable_trace(),
 
238
                            ok;
 
239
                        Children ->
 
240
                            inets:disable_trace(),
 
241
                            exit({unexpected_children, Children})
 
242
                    end;
 
243
                _ ->
 
244
                    inets:disable_trace(),
 
245
                    {skip, "Unable to reach test FTP server"}
 
246
            end
 
247
        end
 
248
    catch
 
249
        throw:{error, not_found} ->
 
250
            inets:disable_trace(),
 
251
            {skip, "No available FTP servers"}
 
252
    end.
 
253
 
 
254
 
 
255
%%-------------------------------------------------------------------------
 
256
%% tftpd_worker
 
257
%%-------------------------------------------------------------------------
 
258
tftpd_worker(doc) ->
 
259
    ["Makes sure the tftp sub tree is correct."]; 
 
260
tftpd_worker(suite) ->
 
261
    [];
 
262
tftpd_worker(Config) when is_list(Config) ->
 
263
    [] = supervisor:which_children(tftp_sup),   
 
264
    {ok, Pid0} = inets:start(tftpd, [{host, "localhost"}, 
 
265
                                     {port, inet_port()}]),
 
266
    {ok, _Pid1} = inets:start(tftpd, [{host, "localhost"}, 
 
267
                                      {port, inet_port()}], stand_alone),
 
268
    
 
269
    [{_,Pid0, worker, _}] = supervisor:which_children(tftp_sup),
 
270
    inets:stop(tftpd, Pid0),
 
271
    test_server:sleep(5000),
 
272
    [] = supervisor:which_children(tftp_sup),
 
273
    ok.
 
274
 
 
275
 
 
276
%%-------------------------------------------------------------------------
 
277
%% httpd_subtree
 
278
%%-------------------------------------------------------------------------
 
279
httpd_subtree(doc) ->
 
280
    ["Makes sure the httpd sub tree is correct."]; 
 
281
httpd_subtree(suite) ->
 
282
    [];
 
283
httpd_subtree(Config) when is_list(Config) ->
 
284
    io:format("httpd_subtree -> entry with"
 
285
              "~n   Config: ~p"
 
286
              "~n", [Config]),
 
287
 
 
288
    %% Check that we have the httpd top supervisor
 
289
    io:format("httpd_subtree -> verify inets~n", []),
 
290
    {ok, _} = verify_child(inets_sup, httpd_sup, supervisor),
 
291
 
 
292
    %% Check that we have the httpd instance supervisor
 
293
    io:format("httpd_subtree -> verify httpd~n", []),
 
294
    {ok, Id} = verify_child(httpd_sup, httpd_instance_sup, supervisor),
 
295
    {httpd_instance_sup, Addr, Port} = Id,
 
296
    Instance = httpd_util:make_name("httpd_instance_sup", Addr, Port),
 
297
    
 
298
    %% Check that we have the expected httpd instance children
 
299
    io:format("httpd_subtree -> verify httpd instance children "
 
300
              "(acceptor, misc and manager)~n", []),
 
301
    {ok, _} = verify_child(Instance, httpd_acceptor_sup, supervisor),
 
302
    {ok, _} = verify_child(Instance, httpd_misc_sup, supervisor),
 
303
    {ok, _} = verify_child(Instance, httpd_manager, worker),
 
304
 
 
305
    %% Check that the httpd instance acc supervisor has children
 
306
    io:format("httpd_subtree -> verify acc~n", []),
 
307
    InstanceAcc = httpd_util:make_name("httpd_acc_sup", Addr, Port),
 
308
    case supervisor:which_children(InstanceAcc) of
 
309
        [_ | _] -> 
 
310
            ok;
 
311
        InstanceAccUnexpectedChildren ->
 
312
            exit({unexpected_children, 
 
313
                  InstanceAcc, InstanceAccUnexpectedChildren})
 
314
    end,
 
315
    
 
316
    %% Check that the httpd instance misc supervisor has no children
 
317
    io:format("httpd_subtree -> verify misc~n", []),
 
318
    InstanceMisc = httpd_util:make_name("httpd_misc_sup", Addr, Port),
 
319
    case supervisor:which_children(InstanceMisc) of
 
320
        [] ->
 
321
            ok;
 
322
        InstanceMiscUnexpectedChildren ->
 
323
            exit({unexpected_children, 
 
324
                  InstanceMisc, InstanceMiscUnexpectedChildren})
 
325
    end,
 
326
    io:format("httpd_subtree -> done~n", []),
 
327
    ok.
 
328
 
 
329
 
 
330
verify_child(Parent, Child, Type) ->
 
331
%%     io:format("verify_child -> entry with"
 
332
%%            "~n   Parent: ~p"
 
333
%%            "~n   Child:  ~p"
 
334
%%            "~n   Type:   ~p"
 
335
%%            "~n", [Parent, Child, Type]),
 
336
    Children = supervisor:which_children(Parent),
 
337
%%     io:format("verify_child -> which children"
 
338
%%            "~n   Children:   ~p"
 
339
%%            "~n", [Children]),
 
340
    verify_child(Children, Parent, Child, Type).
 
341
 
 
342
verify_child([], Parent, Child, _Type) ->
 
343
    {error, {child_not_found, Child, Parent}};
 
344
verify_child([{Id, _Pid, Type2, Mods}|Children], Parent, Child, Type) ->
 
345
    case lists:member(Child, Mods) of
 
346
        true when (Type2 =:= Type) ->
 
347
%%          io:format("verify_child -> found with expected type"
 
348
%%                    "~n   Id: ~p"
 
349
%%                    "~n", [Id]),
 
350
            {ok, Id};
 
351
        true when (Type2 =/= Type) ->
 
352
%%          io:format("verify_child -> found with unexpected type"
 
353
%%                    "~n   Type2: ~p"
 
354
%%                    "~n   Id:    ~p"
 
355
%%                    "~n", [Type2, Id]),
 
356
            {error, {wrong_type, Type2, Child, Parent}};
 
357
        false ->
 
358
            verify_child(Children, Parent, Child, Type)
 
359
    end.
 
360
                                          
 
361
 
 
362
 
 
363
%%-------------------------------------------------------------------------
 
364
%% httpc_subtree
 
365
%%-------------------------------------------------------------------------
 
366
httpc_subtree(doc) ->
 
367
    ["Makes sure the httpc sub tree is correct."]; 
 
368
httpc_subtree(suite) ->
 
369
    [];
 
370
httpc_subtree(Config) when is_list(Config) ->
 
371
    tsp("httpc_subtree -> entry with"
 
372
        "~n   Config: ~p", [Config]),
 
373
 
 
374
    tsp("httpc_subtree -> start inets service httpc with profile foo"),
 
375
    {ok, Foo} = inets:start(httpc, [{profile, foo}]),
 
376
 
 
377
    tsp("httpc_subtree -> "
 
378
        "start stand-alone inets service httpc with profile bar"),
 
379
    {ok, Bar} = inets:start(httpc, [{profile, bar}], stand_alone),
 
380
 
 
381
    tsp("httpc_subtree -> retreive list of httpc instances"),
 
382
    HttpcChildren = supervisor:which_children(httpc_profile_sup),
 
383
    tsp("httpc_subtree -> HttpcChildren: ~n~p", [HttpcChildren]),
 
384
    
 
385
    tsp("httpc_subtree -> verify httpc stand-alone instances"),
 
386
    {value, {httpc_manager, _, worker, [httpc_manager]}} =
 
387
        lists:keysearch(httpc_manager, 1, HttpcChildren),
 
388
 
 
389
    tsp("httpc_subtree -> verify httpc (named) instances"),
 
390
    {value,{{httpc,foo}, Pid, worker, [httpc_manager]}} = 
 
391
        lists:keysearch({httpc, foo}, 1, HttpcChildren),
 
392
    false = lists:keysearch({httpc, bar}, 1, HttpcChildren),
 
393
    
 
394
    tsp("httpc_subtree -> stop inets"),
 
395
    inets:stop(httpc, Pid),
 
396
 
 
397
    tsp("httpc_subtree -> done"),
 
398
    ok.
 
399
 
 
400
inet_port() ->
 
401
    {ok, Socket} = gen_tcp:listen(0, [{reuseaddr, true}]),
 
402
    {ok, Port} = inet:port(Socket),
 
403
    gen_tcp:close(Socket),
 
404
    Port.
 
405
 
 
406
 
 
407
tsp(F) ->
 
408
    tsp(F, []).
 
409
tsp(F, A) ->
 
410
    test_server:format("~p ~p:" ++ F ++ "~n", [self(), ?MODULE | A]).
 
411
 
 
412
tsf(Reason) ->
 
413
    test_server:fail(Reason).
 
414