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

« back to all changes in this revision

Viewing changes to lib/inets/test/inets_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 1997-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
-module(inets_SUITE).
 
21
 
 
22
-include_lib("common_test/include/ct.hrl").
 
23
-include("test_server_line.hrl").
 
24
-include("inets_test_lib.hrl").
 
25
 
 
26
%% Note: This directive should only be used in test suites.
 
27
-compile(export_all).
 
28
 
 
29
-define(NUM_DEFAULT_SERVICES, 1).
 
30
 
 
31
suite() -> [{ct_hooks,[ts_install_cth]}].
 
32
 
 
33
all() -> 
 
34
    [{group, app_test}, {group, appup_test},
 
35
     {group, services_test}, httpd_reload].
 
36
 
 
37
groups() -> 
 
38
    [{services_test, [],
 
39
      [start_inets, start_httpc, start_httpd, start_ftpc,
 
40
       start_tftpd]},
 
41
     {app_test, [], [{inets_app_test, all}]},
 
42
     {appup_test, [], [{inets_appup_test, all}]}].
 
43
 
 
44
init_per_group(_GroupName, Config) ->
 
45
    Config.
 
46
 
 
47
end_per_group(_GroupName, Config) ->
 
48
    Config.
 
49
 
 
50
 
 
51
 
 
52
 
 
53
%%--------------------------------------------------------------------
 
54
%% Function: init_per_suite(Config) -> Config
 
55
%% Config - [tuple()]
 
56
%%   A list of key/value pairs, holding the test case configuration.
 
57
%% Description: Initiation before the whole suite
 
58
%%
 
59
%% Note: This function is free to add any key/value pairs to the Config
 
60
%% variable, but should NOT alter/remove any existing entries.
 
61
%%--------------------------------------------------------------------
 
62
init_per_suite(Config) ->
 
63
    Config.
 
64
 
 
65
%%--------------------------------------------------------------------
 
66
%% Function: end_per_suite(Config) -> _
 
67
%% Config - [tuple()]
 
68
%%   A list of key/value pairs, holding the test case configuration.
 
69
%% Description: Cleanup after the whole suite
 
70
%%--------------------------------------------------------------------
 
71
end_per_suite(_Config) ->
 
72
    ok.
 
73
 
 
74
%%--------------------------------------------------------------------
 
75
%% Function: init_per_testcase(Case, Config) -> Config
 
76
% Case - atom()
 
77
%%   Name of the test case that is about to be run.
 
78
%% Config - [tuple()]
 
79
%%   A list of key/value pairs, holding the test case configuration.
 
80
%%
 
81
%% Description: Initiation before each test case
 
82
%%
 
83
%% Note: This function is free to add any key/value pairs to the Config
 
84
%% variable, but should NOT alter/remove any existing entries.
 
85
%%--------------------------------------------------------------------
 
86
init_per_testcase(_Case, Config) ->
 
87
    inets:stop(),
 
88
    Config.
 
89
 
 
90
%%--------------------------------------------------------------------
 
91
%% Function: end_per_testcase(Case, Config) -> _
 
92
%% Case - atom()
 
93
%%   Name of the test case that is about to be run.
 
94
%% Config - [tuple()]
 
95
%%   A list of key/value pairs, holding the test case configuration.
 
96
%% Description: Cleanup after each test case
 
97
%%--------------------------------------------------------------------
 
98
end_per_testcase(_, Config) ->
 
99
    Config.
 
100
 
 
101
%%-------------------------------------------------------------------------
 
102
%% Test cases starts here.
 
103
%%-------------------------------------------------------------------------
 
104
 
 
105
 
 
106
 
 
107
%%-------------------------------------------------------------------------
 
108
 
 
109
start_inets(doc) ->
 
110
    ["Test inets API functions"];
 
111
start_inets(suite) ->
 
112
    [];
 
113
start_inets(Config) when is_list(Config) ->
 
114
    [_|_] = inets:service_names(),
 
115
 
 
116
    {error,inets_not_started} = inets:services(),
 
117
    {error,inets_not_started} = inets:services_info(),
 
118
 
 
119
    ok = inets:start(),
 
120
    
 
121
    %% httpc default profile always started
 
122
    [_|_] = inets:services(), 
 
123
    [_|_] =  inets:services_info(),
 
124
 
 
125
    {error,{already_started,inets}} = inets:start(),
 
126
    
 
127
    ok = inets:stop(),
 
128
    {error,{not_started,inets}} = inets:stop(),
 
129
 
 
130
    ok = inets:start(transient),
 
131
    ok = inets:stop(),
 
132
   
 
133
    ok = inets:start(permanent),
 
134
    ok = inets:stop().
 
135
 
 
136
 
 
137
%%-------------------------------------------------------------------------
 
138
 
 
139
start_httpc(doc) ->
 
140
    ["Start/stop of httpc service"];
 
141
start_httpc(suite) ->
 
142
    [];
 
143
start_httpc(Config) when is_list(Config) ->
 
144
    process_flag(trap_exit, true),
 
145
    tsp("start_httpc -> entry with"
 
146
        "~n   Config: ~p", [Config]),
 
147
 
 
148
    PrivDir = ?config(priv_dir, Config),
 
149
 
 
150
    tsp("start_httpc -> start (empty) inets"),
 
151
    ok = inets:start(),
 
152
 
 
153
    tsp("start_httpc -> start httpc (as inets service) with profile foo"),
 
154
    {ok, Pid0} = inets:start(httpc, [{profile, foo}]),
 
155
 
 
156
    tsp("start_httpc -> check running services"),
 
157
    Pids0 =  [ServicePid || {_, ServicePid} <- inets:services()],  
 
158
    true = lists:member(Pid0, Pids0),
 
159
    [_|_] = inets:services_info(),      
 
160
 
 
161
    tsp("start_httpc -> stop httpc"),
 
162
    inets:stop(httpc, Pid0),
 
163
 
 
164
    tsp("start_httpc -> sleep some"),
 
165
    test_server:sleep(100),
 
166
 
 
167
    tsp("start_httpc -> check running services"),
 
168
    Pids1 =  [ServicePid || {_, ServicePid} <- inets:services()], 
 
169
    false = lists:member(Pid0, Pids1),        
 
170
 
 
171
    tsp("start_httpc -> start httpc (stand-alone) with profile bar"),
 
172
    {ok, Pid1} = inets:start(httpc, [{profile, bar}], stand_alone),
 
173
 
 
174
    tsp("start_httpc -> check running services"),
 
175
    Pids2 =  [ServicePid || {_, ServicePid} <- inets:services()], 
 
176
    false = lists:member(Pid1, Pids2),   
 
177
 
 
178
    tsp("start_httpc -> stop httpc"),
 
179
    ok = inets:stop(stand_alone, Pid1),
 
180
    receive 
 
181
        {'EXIT', Pid1, shutdown} ->
 
182
            ok
 
183
    after 100 ->
 
184
            tsf(stand_alone_not_shutdown)
 
185
    end,
 
186
 
 
187
    tsp("start_httpc -> stop inets"),
 
188
    ok = inets:stop(),
 
189
 
 
190
    tsp("start_httpc -> unload inets"),
 
191
    application:load(inets),
 
192
 
 
193
    tsp("start_httpc -> set inets environment (httpc profile foo)"),
 
194
    application:set_env(inets, services, [{httpc,[{profile, foo}, 
 
195
                                                  {data_dir, PrivDir}]}]),
 
196
 
 
197
    tsp("start_httpc -> start inets"),
 
198
    ok = inets:start(),
 
199
 
 
200
    tsp("start_httpc -> check running services"),
 
201
    (?NUM_DEFAULT_SERVICES + 1) = length(inets:services()),
 
202
 
 
203
    tsp("start_httpc -> unset inets env"),
 
204
    application:unset_env(inets, services),
 
205
 
 
206
    tsp("start_httpc -> stop inets"),
 
207
    ok = inets:stop(),
 
208
 
 
209
    tsp("start_httpc -> start (empty) inets"),
 
210
    ok = inets:start(),
 
211
 
 
212
    tsp("start_httpc -> start inets httpc service with profile foo"),
 
213
    {ok, Pid3} = inets:start(httpc, [{profile, foo}]),
 
214
 
 
215
    tsp("start_httpc -> stop inets service httpc with profile foo"),
 
216
    ok = inets:stop(httpc, foo),
 
217
 
 
218
    tsp("start_httpc -> check running services"),
 
219
    Pids3 =  [ServicePid || {_, ServicePid} <- inets:services()], 
 
220
    false = lists:member(Pid3, Pids3),      
 
221
 
 
222
    tsp("start_httpc -> stop inets"),
 
223
    ok = inets:stop(),
 
224
 
 
225
    tsp("start_httpc -> done"),    
 
226
    ok.
 
227
 
 
228
 
 
229
%%-------------------------------------------------------------------------
 
230
 
 
231
start_httpd(doc) ->
 
232
    ["Start/stop of httpd service"];
 
233
start_httpd(suite) ->
 
234
    [];
 
235
start_httpd(Config) when is_list(Config) ->
 
236
    process_flag(trap_exit, true),
 
237
    i("start_httpd -> entry with"
 
238
      "~n   Config: ~p", [Config]),
 
239
    PrivDir = ?config(priv_dir, Config),
 
240
    HttpdConf = [{server_name, "httpd_test"}, {server_root, PrivDir},
 
241
                 {document_root, PrivDir}, {bind_address, "localhost"}],
 
242
    
 
243
    i("start_httpd -> start inets"),
 
244
    ok = inets:start(),
 
245
 
 
246
    i("start_httpd -> start httpd service"),
 
247
    {ok, Pid0} = inets:start(httpd, [{port, 0}, {ipfamily, inet} | HttpdConf]),
 
248
    Pids0 =  [ServicePid || {_, ServicePid} <- inets:services()],  
 
249
    true = lists:member(Pid0, Pids0),
 
250
    [_|_] = inets:services_info(),      
 
251
 
 
252
    i("start_httpd -> stop httpd service"),
 
253
    inets:stop(httpd, Pid0),
 
254
    test_server:sleep(500),
 
255
    Pids1 =  [ServicePid || {_, ServicePid} <- inets:services()], 
 
256
    false = lists:member(Pid0, Pids1),        
 
257
    i("start_httpd -> start (stand-alone) httpd service"),
 
258
    {ok, Pid1} = 
 
259
        inets:start(httpd, [{port, 0}, {ipfamily, inet} | HttpdConf], 
 
260
                    stand_alone),
 
261
    Pids2 =  [ServicePid || {_, ServicePid} <- inets:services()], 
 
262
    false = lists:member(Pid1, Pids2),   
 
263
    i("start_httpd -> stop (stand-alone) httpd service"),
 
264
    ok = inets:stop(stand_alone, Pid1),
 
265
    receive 
 
266
        {'EXIT', Pid1, shutdown} ->
 
267
            ok
 
268
    after 100 ->
 
269
            test_server:fail(stand_alone_not_shutdown)
 
270
    end,
 
271
    i("start_httpd -> stop inets"),
 
272
    ok = inets:stop(),
 
273
    File0 = filename:join(PrivDir, "httpd.conf"),
 
274
    {ok, Fd0} =  file:open(File0, [write]),
 
275
    Str = io_lib:format("~p.~n", [[{port, 0}, {ipfamily, inet} | HttpdConf]]),
 
276
    ok = file:write(Fd0, Str),
 
277
    file:close(Fd0),
 
278
 
 
279
    i("start_httpd -> [application] load inets"),
 
280
    application:load(inets),
 
281
    i("start_httpd -> [application] set httpd services env with proplist-file"),
 
282
    application:set_env(inets, 
 
283
                        services, [{httpd, [{proplist_file, File0}]}]),
 
284
    i("start_httpd -> start inets"),
 
285
    ok = inets:start(),
 
286
    (?NUM_DEFAULT_SERVICES + 1) = length(inets:services()),
 
287
    i("start_httpd -> [application] unset services env"),
 
288
    application:unset_env(inets, services),
 
289
    i("start_httpd -> stop inets"),
 
290
    ok = inets:stop(),
 
291
    
 
292
    File1 = filename:join(PrivDir, "httpd_apache.conf"),
 
293
    
 
294
    {ok, Fd1} =  file:open(File1, [write]),
 
295
    file:write(Fd1, "ServerName   httpd_test\r\n"),
 
296
    file:write(Fd1, "ServerRoot   " ++ PrivDir ++ "\r\n"),
 
297
    file:write(Fd1, "DocumentRoot " ++ PrivDir ++" \r\n"),    
 
298
    file:write(Fd1, "BindAddress  *|inet\r\n"),
 
299
    file:write(Fd1, "Port 0\r\n"),
 
300
    file:close(Fd1),
 
301
 
 
302
    i("start_httpd -> [application] load inets"),
 
303
    application:load(inets),
 
304
    i("start_httpd -> [application] set httpd services env with file"),
 
305
    application:set_env(inets, 
 
306
                        services, [{httpd, [{file, File1}]}]),
 
307
    i("start_httpd -> start inets"),
 
308
    ok = inets:start(),
 
309
    (?NUM_DEFAULT_SERVICES + 1) = length(inets:services()),
 
310
    i("start_httpd -> [application] unset services env"),
 
311
    application:unset_env(inets, services),
 
312
    i("start_httpd -> stop inets"),
 
313
    ok = inets:stop(),
 
314
    
 
315
    %% OLD format
 
316
    i("start_httpd -> [application] load inets"),
 
317
    application:load(inets),
 
318
    i("start_httpd -> [application] set httpd services OLD env"),
 
319
    application:set_env(inets, 
 
320
                        services, [{httpd, File1}]),
 
321
    i("start_httpd -> start inets"),
 
322
    ok = inets:start(),
 
323
    (?NUM_DEFAULT_SERVICES + 1) = length(inets:services()),
 
324
    i("start_httpd -> [application] unset services enc"),
 
325
    application:unset_env(inets, services),
 
326
    i("start_httpd -> stop inets"),
 
327
    ok = inets:stop(),
 
328
 
 
329
    i("start_httpd -> start inets"),
 
330
    ok = inets:start(),
 
331
    i("start_httpd -> try (and fail) start httpd service - server_name"),
 
332
    {error, {missing_property, server_name}} = 
 
333
        inets:start(httpd, [{port, 0},
 
334
                            {server_root, PrivDir},
 
335
                            {document_root, PrivDir}, 
 
336
                            {bind_address, "localhost"}]),
 
337
    i("start_httpd -> try (and fail) start httpd service - missing document_root"),
 
338
    {error, {missing_property, document_root}} = 
 
339
        inets:start(httpd, [{port, 0},
 
340
                            {server_name, "httpd_test"}, 
 
341
                            {server_root, PrivDir},
 
342
                            {bind_address, "localhost"}]),
 
343
    i("start_httpd -> try (and fail) start httpd service - missing server_root"),
 
344
    {error, {missing_property, server_root}} = 
 
345
        inets:start(httpd, [{port, 0},
 
346
                            {server_name, "httpd_test"}, 
 
347
                            {document_root, PrivDir},
 
348
                            {bind_address, "localhost"}]),
 
349
    i("start_httpd -> try (and fail) start httpd service - missing port"),
 
350
    {error, {missing_property, port}} = 
 
351
        inets:start(httpd, HttpdConf),
 
352
    i("start_httpd -> stop inets"),
 
353
    ok = inets:stop(),
 
354
    i("start_httpd -> done"),
 
355
    ok.
 
356
    
 
357
 
 
358
%%-------------------------------------------------------------------------
 
359
 
 
360
start_ftpc(doc) ->
 
361
    ["Start/stop of ftpc service"];
 
362
start_ftpc(suite) ->
 
363
    [];
 
364
start_ftpc(Config) when is_list(Config) ->
 
365
    process_flag(trap_exit, true),
 
366
    inets:disable_trace(),
 
367
    inets:enable_trace(max, io, ftpc), 
 
368
    ok = inets:start(),
 
369
    try
 
370
        begin
 
371
            {_Tag, FtpdHost} = ftp_suite_lib:dirty_select_ftpd_host(Config),
 
372
            case inets:start(ftpc, [{host, FtpdHost}]) of
 
373
                {ok, Pid0} ->
 
374
                    Pids0 = [ServicePid || {_, ServicePid} <- 
 
375
                                               inets:services()],  
 
376
                    true = lists:member(Pid0, Pids0),
 
377
                    [_|_] = inets:services_info(),      
 
378
                    inets:stop(ftpc, Pid0),
 
379
                    test_server:sleep(100),
 
380
                    Pids1 =  [ServicePid || {_, ServicePid} <- 
 
381
                                                inets:services()], 
 
382
                    false = lists:member(Pid0, Pids1),        
 
383
                    {ok, Pid1} = 
 
384
                        inets:start(ftpc, [{host, FtpdHost}], stand_alone),
 
385
                    Pids2 =  [ServicePid || {_, ServicePid} <- 
 
386
                                                inets:services()], 
 
387
                    false = lists:member(Pid1, Pids2),   
 
388
                    ok = inets:stop(stand_alone, Pid1),
 
389
                    receive 
 
390
                        {'EXIT', Pid1, shutdown} ->
 
391
                            ok
 
392
                    after 100 ->
 
393
                            tsf(stand_alone_not_shutdown)
 
394
                    end,
 
395
                    ok = inets:stop(),
 
396
                    inets:disable_trace(),
 
397
                    ok;
 
398
                _ ->
 
399
                    inets:disable_trace(),
 
400
                    {skip, "Unable to reach selected FTP server " ++ FtpdHost}
 
401
            end
 
402
        end
 
403
    catch
 
404
        throw:{error, not_found} ->
 
405
            inets:disable_trace(),
 
406
            {skip, "No available FTP servers"}
 
407
    end.
 
408
            
 
409
 
 
410
 
 
411
%%-------------------------------------------------------------------------
 
412
 
 
413
start_tftpd(doc) ->
 
414
    ["Start/stop of tfpd service"];
 
415
start_tftpd(suite) ->
 
416
    [];
 
417
start_tftpd(Config) when is_list(Config) ->
 
418
    process_flag(trap_exit, true),
 
419
    ok = inets:start(),
 
420
    {ok, Pid0} = inets:start(tftpd, [{host, "localhost"}, {port, 0}]),
 
421
    Pids0 =  [ServicePid || {_, ServicePid} <- inets:services()],  
 
422
    true = lists:member(Pid0, Pids0),
 
423
    [_|_] = inets:services_info(),      
 
424
    inets:stop(tftpd, Pid0),
 
425
    test_server:sleep(100),
 
426
    Pids1 =  [ServicePid || {_, ServicePid} <- inets:services()], 
 
427
    false = lists:member(Pid0, Pids1),        
 
428
    {ok, Pid1} = 
 
429
        inets:start(tftpd, [{host, "localhost"}, {port, 0}], stand_alone),
 
430
    Pids2 =  [ServicePid || {_, ServicePid} <- inets:services()], 
 
431
    false = lists:member(Pid1, Pids2),   
 
432
    ok = inets:stop(stand_alone, Pid1),
 
433
    receive 
 
434
        {'EXIT', Pid1, shutdown} ->
 
435
            ok
 
436
    after 100 ->
 
437
            test_server:fail(stand_alone_not_shutdown)
 
438
    end,
 
439
    ok = inets:stop(),
 
440
    application:load(inets),
 
441
    application:set_env(inets, services, [{tftpd,[{host, "localhost"}, 
 
442
                                                  {port, 0}]}]),
 
443
    ok = inets:start(),
 
444
    (?NUM_DEFAULT_SERVICES + 1) = length(inets:services()),
 
445
    application:unset_env(inets, services),
 
446
    ok = inets:stop().
 
447
 
 
448
 
 
449
%%-------------------------------------------------------------------------
 
450
 
 
451
httpd_reload(doc) ->
 
452
    ["Reload httpd configuration without restarting service"];
 
453
httpd_reload(suite) ->
 
454
    [];
 
455
httpd_reload(Config) when is_list(Config) ->
 
456
    process_flag(trap_exit, true),
 
457
    i("httpd_reload -> starting"),
 
458
    PrivDir = ?config(priv_dir, Config),
 
459
    DataDir =  ?config(data_dir, Config),
 
460
    HttpdConf = [{server_name,   "httpd_test"}, 
 
461
                 {server_root,   PrivDir},
 
462
                 {document_root, PrivDir}, 
 
463
                 {bind_address,  "localhost"}],
 
464
 
 
465
    inets:enable_trace(max, io),
 
466
 
 
467
    i("httpd_reload -> start inets"),
 
468
 
 
469
    ok = inets:start(),
 
470
    test_server:sleep(5000),
 
471
    i("httpd_reload -> inets started - start httpd service"),
 
472
 
 
473
    {ok, Pid0} = inets:start(httpd, [{port, 0}, {ipfamily, inet} | HttpdConf]),
 
474
    test_server:sleep(5000),
 
475
    i("httpd_reload -> httpd service started (~p) - get port", [Pid0]),
 
476
 
 
477
    [{port, Port0}] = httpd:info(Pid0, [port]),         
 
478
    test_server:sleep(5000),
 
479
    i("httpd_reload -> Port: ~p - get document root", [Port0]),
 
480
 
 
481
    [{document_root, PrivDir}] =  httpd:info(Pid0, [document_root]),
 
482
    test_server:sleep(5000),
 
483
    i("httpd_reload -> document root: ~p - reload config", [PrivDir]),
 
484
 
 
485
    ok = httpd:reload_config([{port, Port0}, {ipfamily, inet},
 
486
                              {server_name, "httpd_test"}, 
 
487
                              {server_root, PrivDir},
 
488
                              {document_root, DataDir}, 
 
489
                              {bind_address, "localhost"}], non_disturbing),
 
490
    test_server:sleep(5000),    
 
491
    io:format("~w:~w:httpd_reload - reloaded - get document root~n", [?MODULE, ?LINE]),
 
492
 
 
493
    [{document_root, DataDir}] =  httpd:info(Pid0, [document_root]),
 
494
    test_server:sleep(5000),    
 
495
    i("httpd_reload -> document root: ~p - reload config", [DataDir]),
 
496
 
 
497
    ok = httpd:reload_config([{port, Port0}, {ipfamily, inet},
 
498
                              {server_name, "httpd_test"}, 
 
499
                              {server_root, PrivDir},
 
500
                              {document_root, PrivDir}, 
 
501
                              {bind_address, "localhost"}], disturbing),
 
502
 
 
503
    [{document_root, PrivDir}] =  httpd:info(Pid0, [document_root]),
 
504
    ok = inets:stop(httpd, Pid0),
 
505
    ok = inets:stop(),
 
506
 
 
507
    File = filename:join(PrivDir, "httpd_apache.conf"),
 
508
      
 
509
    {ok, Fd0} =  file:open(File, [write]),
 
510
    file:write(Fd0, "ServerName   httpd_test\r\n"),
 
511
    file:write(Fd0, "ServerRoot   " ++ PrivDir ++ "\r\n"),
 
512
    file:write(Fd0, "DocumentRoot " ++ PrivDir ++" \r\n"),    
 
513
    file:write(Fd0, "BindAddress  *\r\n"),
 
514
    file:write(Fd0, "Port 0\r\n"),
 
515
    file:close(Fd0),
 
516
 
 
517
    application:load(inets),
 
518
    application:set_env(inets, 
 
519
                        services, [{httpd, [{file, File}]}]),
 
520
    
 
521
    ok = inets:start(),
 
522
    [Pid1] = [HttpdPid || {httpd, HttpdPid} <- inets:services()],
 
523
    [{server_name, "httpd_test"}] =  httpd:info(Pid1, [server_name]),
 
524
    [{port, Port1}] = httpd:info(Pid1, [port]),         
 
525
    {ok, Fd1} =  file:open(File, [write]),
 
526
    file:write(Fd1, "ServerName   httpd_test2\r\n"),
 
527
    file:write(Fd1, "ServerRoot   " ++ PrivDir ++ "\r\n"),
 
528
    file:write(Fd1, "DocumentRoot " ++ PrivDir ++" \r\n"),    
 
529
    file:write(Fd1, "BindAddress  *\r\n"),
 
530
    file:write(Fd1, "Port " ++ integer_to_list(Port1) ++ "\r\n"),
 
531
    file:close(Fd1),
 
532
 
 
533
    ok = httpd:reload_config(File, non_disturbing),
 
534
    [{server_name, "httpd_test2"}] =  httpd:info(Pid1, [server_name]),
 
535
 
 
536
    {ok, Fd2} =  file:open(File, [write]),
 
537
    file:write(Fd2, "ServerName   httpd_test\r\n"),
 
538
    file:write(Fd2, "ServerRoot   " ++ PrivDir ++ "\r\n"),
 
539
    file:write(Fd2, "DocumentRoot " ++ PrivDir ++" \r\n"),    
 
540
    file:write(Fd2, "BindAddress  *\r\n"),
 
541
    file:write(Fd2, "Port " ++ integer_to_list(Port1) ++ "\r\n"),
 
542
    file:close(Fd2),
 
543
    ok = httpd:reload_config(File, disturbing),
 
544
    [{server_name, "httpd_test"}] = httpd:info(Pid1, [server_name]),
 
545
    
 
546
    ok = inets:stop(httpd, Pid1),
 
547
    application:unset_env(inets, services),
 
548
    ok = inets:stop(),
 
549
    i("httpd_reload -> starting"),
 
550
    ok.
 
551
    
 
552
 
 
553
tsf(Reason) ->
 
554
    test_server:fail(Reason).
 
555
 
 
556
tsp(F) ->
 
557
    tsp(F, []).
 
558
tsp(F, A) ->
 
559
    Timestamp = formated_timestamp(), 
 
560
    test_server:format("** ~s ** ~p ~p:" ++ F ++ "~n", [Timestamp, self(), ?MODULE | A]).
 
561
 
 
562
i(F) ->
 
563
    i(F, []).
 
564
 
 
565
i(F, A) ->
 
566
    Timestamp = formated_timestamp(), 
 
567
    io:format("*** ~s ~w:" ++ F ++ "~n", [Timestamp, ?MODULE | A]).
 
568
 
 
569
formated_timestamp() ->
 
570
    format_timestamp( os:timestamp() ).
 
571
 
 
572
format_timestamp({_N1, _N2, N3} = Now) ->
 
573
    {Date, Time}   = calendar:now_to_datetime(Now),
 
574
    {YYYY,MM,DD}   = Date,
 
575
    {Hour,Min,Sec} = Time,
 
576
    FormatDate =
 
577
        io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
 
578
                      [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),
 
579
    lists:flatten(FormatDate).
 
580