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

« back to all changes in this revision

Viewing changes to lib/inets/test/httpd_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 2005-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
 
 
21
-module(httpd_SUITE).
 
22
 
 
23
-include_lib("test_server/include/test_server.hrl").
 
24
-include("test_server_line.hrl").
 
25
-include("inets_test_lib.hrl").
 
26
 
 
27
-include_lib("kernel/include/file.hrl").
 
28
 
 
29
%% Test server specific exports
 
30
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2]).
 
31
-export([init_per_testcase/2, end_per_testcase/2,
 
32
         init_per_suite/1, end_per_suite/1]).
 
33
 
 
34
%% Core Server tests
 
35
-export([
 
36
         ip_mod_alias/1, 
 
37
         ip_mod_actions/1, 
 
38
         ip_mod_security/1, 
 
39
         ip_mod_auth/1,
 
40
         ip_mod_auth_api/1, 
 
41
         ip_mod_auth_mnesia_api/1, 
 
42
         ip_mod_htaccess/1, 
 
43
         ip_mod_cgi/1, 
 
44
         ip_mod_esi/1,
 
45
         ip_mod_get/1, 
 
46
         ip_mod_head/1, 
 
47
         ip_mod_all/1, 
 
48
         ip_load_light/1,
 
49
         ip_load_medium/1, 
 
50
         ip_load_heavy/1, 
 
51
         ip_dos_hostname/1, 
 
52
         ip_time_test/1, 
 
53
         ip_block_disturbing_idle/1, 
 
54
         ip_block_non_disturbing_idle/1, 
 
55
         ip_block_503/1, 
 
56
         ip_block_disturbing_active/1, 
 
57
         ip_block_non_disturbing_active/1, 
 
58
         ip_block_disturbing_active_timeout_not_released/1, 
 
59
         ip_block_disturbing_active_timeout_released/1, 
 
60
         ip_block_non_disturbing_active_timeout_not_released/1, 
 
61
         ip_block_non_disturbing_active_timeout_released/1, 
 
62
         ip_block_disturbing_blocker_dies/1, 
 
63
         ip_block_non_disturbing_blocker_dies/1, 
 
64
         ip_restart_no_block/1, 
 
65
         ip_restart_disturbing_block/1, 
 
66
         ip_restart_non_disturbing_block/1
 
67
        ]).
 
68
 
 
69
-export([
 
70
         pssl_mod_alias/1, 
 
71
         ossl_mod_alias/1, 
 
72
         essl_mod_alias/1, 
 
73
         
 
74
         pssl_mod_actions/1, 
 
75
         ossl_mod_actions/1, 
 
76
         essl_mod_actions/1, 
 
77
         
 
78
         pssl_mod_security/1, 
 
79
         ossl_mod_security/1, 
 
80
         essl_mod_security/1, 
 
81
         
 
82
         pssl_mod_auth/1, 
 
83
         ossl_mod_auth/1, 
 
84
         essl_mod_auth/1, 
 
85
 
 
86
         pssl_mod_auth_api/1,  
 
87
         ossl_mod_auth_api/1,  
 
88
         essl_mod_auth_api/1,  
 
89
         
 
90
         pssl_mod_auth_mnesia_api/1, 
 
91
         ossl_mod_auth_mnesia_api/1, 
 
92
         essl_mod_auth_mnesia_api/1, 
 
93
         
 
94
         pssl_mod_htaccess/1, 
 
95
         ossl_mod_htaccess/1, 
 
96
         essl_mod_htaccess/1, 
 
97
         
 
98
         pssl_mod_cgi/1, 
 
99
         ossl_mod_cgi/1, 
 
100
         essl_mod_cgi/1,
 
101
 
 
102
         pssl_mod_esi/1, 
 
103
         ossl_mod_esi/1, 
 
104
         essl_mod_esi/1, 
 
105
 
 
106
         pssl_mod_get/1, 
 
107
         ossl_mod_get/1, 
 
108
         essl_mod_get/1, 
 
109
 
 
110
         pssl_mod_head/1, 
 
111
         ossl_mod_head/1, 
 
112
         essl_mod_head/1, 
 
113
         
 
114
         pssl_mod_all/1, 
 
115
         ossl_mod_all/1, 
 
116
         essl_mod_all/1, 
 
117
         
 
118
         pssl_load_light/1, 
 
119
         ossl_load_light/1, 
 
120
         essl_load_light/1, 
 
121
         
 
122
         pssl_load_medium/1, 
 
123
         ossl_load_medium/1, 
 
124
         essl_load_medium/1, 
 
125
 
 
126
         pssl_load_heavy/1, 
 
127
         ossl_load_heavy/1, 
 
128
         essl_load_heavy/1, 
 
129
 
 
130
         pssl_dos_hostname/1, 
 
131
         ossl_dos_hostname/1, 
 
132
         essl_dos_hostname/1, 
 
133
 
 
134
         pssl_time_test/1, 
 
135
         ossl_time_test/1, 
 
136
         essl_time_test/1,
 
137
         
 
138
         pssl_restart_no_block/1, 
 
139
         ossl_restart_no_block/1, 
 
140
         essl_restart_no_block/1, 
 
141
         
 
142
         pssl_restart_disturbing_block/1, 
 
143
         ossl_restart_disturbing_block/1, 
 
144
         essl_restart_disturbing_block/1,
 
145
         
 
146
         pssl_restart_non_disturbing_block/1, 
 
147
         ossl_restart_non_disturbing_block/1, 
 
148
         essl_restart_non_disturbing_block/1, 
 
149
         
 
150
         pssl_block_disturbing_idle/1, 
 
151
         ossl_block_disturbing_idle/1, 
 
152
         essl_block_disturbing_idle/1, 
 
153
 
 
154
         pssl_block_non_disturbing_idle/1, 
 
155
         ossl_block_non_disturbing_idle/1, 
 
156
         essl_block_non_disturbing_idle/1, 
 
157
         
 
158
         pssl_block_503/1, 
 
159
         ossl_block_503/1, 
 
160
         essl_block_503/1, 
 
161
 
 
162
         pssl_block_disturbing_active/1, 
 
163
         ossl_block_disturbing_active/1, 
 
164
         essl_block_disturbing_active/1, 
 
165
 
 
166
         pssl_block_non_disturbing_active/1, 
 
167
         ossl_block_non_disturbing_active/1, 
 
168
         essl_block_non_disturbing_active/1, 
 
169
 
 
170
         pssl_block_disturbing_active_timeout_not_released/1, 
 
171
         ossl_block_disturbing_active_timeout_not_released/1, 
 
172
         essl_block_disturbing_active_timeout_not_released/1, 
 
173
 
 
174
         pssl_block_disturbing_active_timeout_released/1, 
 
175
         ossl_block_disturbing_active_timeout_released/1, 
 
176
         essl_block_disturbing_active_timeout_released/1, 
 
177
 
 
178
         pssl_block_non_disturbing_active_timeout_not_released/1, 
 
179
         ossl_block_non_disturbing_active_timeout_not_released/1, 
 
180
         essl_block_non_disturbing_active_timeout_not_released/1, 
 
181
         
 
182
         pssl_block_non_disturbing_active_timeout_released/1, 
 
183
         ossl_block_non_disturbing_active_timeout_released/1, 
 
184
         essl_block_non_disturbing_active_timeout_released/1, 
 
185
 
 
186
         pssl_block_disturbing_blocker_dies/1, 
 
187
         ossl_block_disturbing_blocker_dies/1, 
 
188
         essl_block_disturbing_blocker_dies/1, 
 
189
 
 
190
         pssl_block_non_disturbing_blocker_dies/1, 
 
191
         ossl_block_non_disturbing_blocker_dies/1, 
 
192
         essl_block_non_disturbing_blocker_dies/1
 
193
        ]).
 
194
 
 
195
%%% HTTP 1.1 tests
 
196
-export([ip_host/1, ip_chunked/1, ip_expect/1, ip_range/1,
 
197
         ip_if_test/1, ip_http_trace/1, ip_http1_1_head/1, 
 
198
         ip_mod_cgi_chunked_encoding_test/1]).
 
199
 
 
200
%%% HTTP 1.0 tests
 
201
-export([ip_head_1_0/1, ip_get_1_0/1, ip_post_1_0/1]).
 
202
 
 
203
%%% HTTP 0.9 tests
 
204
-export([ip_get_0_9/1]).
 
205
 
 
206
%%% Ticket tests
 
207
-export([ticket_5775/1,ticket_5865/1,ticket_5913/1,ticket_6003/1,
 
208
         ticket_7304/1]).
 
209
 
 
210
%%% Misc
 
211
-export([ipv6_hostname/1, ipv6_address/1]).
 
212
 
 
213
%% Help functions 
 
214
-export([cleanup_mnesia/0, setup_mnesia/0, setup_mnesia/1]).
 
215
 
 
216
-define(IP_PORT, 8898).
 
217
-define(SSL_PORT, 8899).
 
218
-define(MAX_HEADER_SIZE, 256).
 
219
-define(IPV6_LOCAL_HOST, "0:0:0:0:0:0:0:1").
 
220
 
 
221
%% Minutes before failed auths timeout.
 
222
-define(FAIL_EXPIRE_TIME,1). 
 
223
 
 
224
%% Seconds before successful auths timeout.
 
225
-define(AUTH_TIMEOUT,5).
 
226
 
 
227
-record(httpd_user,  {user_name, password, user_data}).
 
228
-record(httpd_group, {group_name, userlist}).
 
229
 
 
230
 
 
231
%%--------------------------------------------------------------------
 
232
%% all(Arg) -> [Doc] | [Case] | {skip, Comment}
 
233
%% Arg - doc | suite
 
234
%% Doc - string()
 
235
%% Case - atom() 
 
236
%%      Name of a test case function. 
 
237
%% Comment - string()
 
238
%% Description: Returns documentation/test cases in this test suite
 
239
%%              or a skip tuple if the platform is not supported.  
 
240
%%--------------------------------------------------------------------
 
241
suite() -> [{ct_hooks,[ts_install_cth]}].
 
242
 
 
243
all() -> 
 
244
    [{group, ip}, {group, ssl}, {group, http_1_1_ip},
 
245
     {group, http_1_0_ip}, {group, http_0_9_ip},
 
246
     {group, tickets}].
 
247
 
 
248
groups() -> 
 
249
    [{ip, [],
 
250
      [ip_mod_alias, ip_mod_actions, ip_mod_security,
 
251
       ip_mod_auth, ip_mod_auth_api, ip_mod_auth_mnesia_api,
 
252
       ip_mod_htaccess, ip_mod_cgi, ip_mod_esi, ip_mod_get,
 
253
       ip_mod_head, ip_mod_all, ip_load_light, ip_load_medium,
 
254
       ip_load_heavy, ip_dos_hostname, ip_time_test,
 
255
       ip_restart_no_block, ip_restart_disturbing_block,
 
256
       ip_restart_non_disturbing_block,
 
257
       ip_block_disturbing_idle, ip_block_non_disturbing_idle,
 
258
       ip_block_503, ip_block_disturbing_active,
 
259
       ip_block_non_disturbing_active,
 
260
       ip_block_disturbing_active_timeout_not_released,
 
261
       ip_block_disturbing_active_timeout_released,
 
262
       ip_block_non_disturbing_active_timeout_not_released,
 
263
       ip_block_non_disturbing_active_timeout_released,
 
264
       ip_block_disturbing_blocker_dies,
 
265
       ip_block_non_disturbing_blocker_dies]},
 
266
     {ssl, [],
 
267
      [{group, pssl}, {group, ossl}, {group, essl}]},
 
268
     {pssl, [],
 
269
      [pssl_mod_alias, pssl_mod_actions, pssl_mod_security,
 
270
       pssl_mod_auth, pssl_mod_auth_api,
 
271
       pssl_mod_auth_mnesia_api, pssl_mod_htaccess,
 
272
       pssl_mod_cgi, pssl_mod_esi, pssl_mod_get, pssl_mod_head,
 
273
       pssl_mod_all, pssl_load_light, pssl_load_medium,
 
274
       pssl_load_heavy, pssl_dos_hostname, pssl_time_test,
 
275
       pssl_restart_no_block, pssl_restart_disturbing_block,
 
276
       pssl_restart_non_disturbing_block,
 
277
       pssl_block_disturbing_idle,
 
278
       pssl_block_non_disturbing_idle, pssl_block_503,
 
279
       pssl_block_disturbing_active,
 
280
       pssl_block_non_disturbing_active,
 
281
       pssl_block_disturbing_active_timeout_not_released,
 
282
       pssl_block_disturbing_active_timeout_released,
 
283
       pssl_block_non_disturbing_active_timeout_not_released,
 
284
       pssl_block_non_disturbing_active_timeout_released,
 
285
       pssl_block_disturbing_blocker_dies,
 
286
       pssl_block_non_disturbing_blocker_dies]},
 
287
     {ossl, [],
 
288
      [ossl_mod_alias, ossl_mod_actions, ossl_mod_security,
 
289
       ossl_mod_auth, ossl_mod_auth_api,
 
290
       ossl_mod_auth_mnesia_api, ossl_mod_htaccess,
 
291
       ossl_mod_cgi, ossl_mod_esi, ossl_mod_get, ossl_mod_head,
 
292
       ossl_mod_all, ossl_load_light, ossl_load_medium,
 
293
       ossl_load_heavy, ossl_dos_hostname, ossl_time_test,
 
294
       ossl_restart_no_block, ossl_restart_disturbing_block,
 
295
       ossl_restart_non_disturbing_block,
 
296
       ossl_block_disturbing_idle,
 
297
       ossl_block_non_disturbing_idle, ossl_block_503,
 
298
       ossl_block_disturbing_active,
 
299
       ossl_block_non_disturbing_active,
 
300
       ossl_block_disturbing_active_timeout_not_released,
 
301
       ossl_block_disturbing_active_timeout_released,
 
302
       ossl_block_non_disturbing_active_timeout_not_released,
 
303
       ossl_block_non_disturbing_active_timeout_released,
 
304
       ossl_block_disturbing_blocker_dies,
 
305
       ossl_block_non_disturbing_blocker_dies]},
 
306
     {essl, [],
 
307
      [essl_mod_alias, essl_mod_actions, essl_mod_security,
 
308
       essl_mod_auth, essl_mod_auth_api,
 
309
       essl_mod_auth_mnesia_api, essl_mod_htaccess,
 
310
       essl_mod_cgi, essl_mod_esi, essl_mod_get, essl_mod_head,
 
311
       essl_mod_all, essl_load_light, essl_load_medium,
 
312
       essl_load_heavy, essl_dos_hostname, essl_time_test,
 
313
       essl_restart_no_block, essl_restart_disturbing_block,
 
314
       essl_restart_non_disturbing_block,
 
315
       essl_block_disturbing_idle,
 
316
       essl_block_non_disturbing_idle, essl_block_503,
 
317
       essl_block_disturbing_active,
 
318
       essl_block_non_disturbing_active,
 
319
       essl_block_disturbing_active_timeout_not_released,
 
320
       essl_block_disturbing_active_timeout_released,
 
321
       essl_block_non_disturbing_active_timeout_not_released,
 
322
       essl_block_non_disturbing_active_timeout_released,
 
323
       essl_block_disturbing_blocker_dies,
 
324
       essl_block_non_disturbing_blocker_dies]},
 
325
     {http_1_1_ip, [],
 
326
      [ip_host, ip_chunked, ip_expect, ip_range, ip_if_test,
 
327
       ip_http_trace, ip_http1_1_head,
 
328
       ip_mod_cgi_chunked_encoding_test]},
 
329
     {http_1_0_ip, [],
 
330
      [ip_head_1_0, ip_get_1_0, ip_post_1_0]},
 
331
     {http_0_9_ip, [], [ip_get_0_9]},
 
332
     {ipv6, [], [ipv6_hostname, ipv6_address]},
 
333
     {tickets, [],
 
334
      [ticket_5775, ticket_5865, ticket_5913, ticket_6003,
 
335
       ticket_7304]}].
 
336
 
 
337
init_per_group(_GroupName, Config) ->
 
338
    Config.
 
339
 
 
340
end_per_group(_GroupName, Config) ->
 
341
    Config.
 
342
 
 
343
 
 
344
%%--------------------------------------------------------------------
 
345
%% Function: init_per_suite(Config) -> Config
 
346
%% Config - [tuple()]
 
347
%%   A list of key/value pairs, holding the test case configuration.
 
348
%% Description: Initiation before the whole suite
 
349
%%
 
350
%% Note: This function is free to add any key/value pairs to the Config
 
351
%% variable, but should NOT alter/remove any existing entries.
 
352
%%--------------------------------------------------------------------
 
353
init_per_suite(Config) ->
 
354
    io:format(user, "init_per_suite -> entry with"
 
355
              "~n   Config: ~p"
 
356
              "~n", [Config]),
 
357
 
 
358
    PrivDir = ?config(priv_dir, Config),
 
359
    SuiteTopDir = filename:join(PrivDir, ?MODULE),
 
360
    case file:make_dir(SuiteTopDir) of
 
361
        ok ->
 
362
            ok;
 
363
        {error, eexist} ->
 
364
            ok;
 
365
        Error ->
 
366
            throw({error, {failed_creating_suite_top_dir, Error}})
 
367
    end,
 
368
 
 
369
    [{suite_top_dir, SuiteTopDir},
 
370
     {node,          node()},
 
371
     {host,          inets_test_lib:hostname()},
 
372
     {address,       getaddr()} | Config].
 
373
 
 
374
 
 
375
%%--------------------------------------------------------------------
 
376
%% Function: end_per_suite(Config) -> _
 
377
%% Config - [tuple()]
 
378
%%   A list of key/value pairs, holding the test case configuration.
 
379
%% Description: Cleanup after the whole suite
 
380
%%--------------------------------------------------------------------
 
381
 
 
382
end_per_suite(_Config) ->
 
383
    %% SuiteTopDir = ?config(suite_top_dir, Config), 
 
384
    %% inets_test_lib:del_dirs(SuiteTopDir),
 
385
    ok.
 
386
 
 
387
 
 
388
%%--------------------------------------------------------------------
 
389
%% Function: init_per_testcase(Case, Config) -> Config
 
390
%% Case - atom()
 
391
%%   Name of the test case that is about to be run.
 
392
%% Config - [tuple()]
 
393
%%   A list of key/value pairs, holding the test case configuration.
 
394
%%
 
395
%% Description: Initiation before each test case
 
396
%%
 
397
%% Note: This function is free to add any key/value pairs to the Config
 
398
%% variable, but should NOT alter/remove any existing entries.
 
399
%%--------------------------------------------------------------------
 
400
init_per_testcase(Case, Config) ->
 
401
    NewConfig = init_per_testcase2(Case, Config), 
 
402
    init_per_testcase3(Case, NewConfig).
 
403
 
 
404
 
 
405
init_per_testcase2(Case, Config) ->
 
406
 
 
407
    io:format(user, "~w:init_per_testcase2(~w) -> entry with"
 
408
              "~n   Config: ~p"
 
409
              "~n", [?MODULE, Case, Config]),
 
410
 
 
411
    IpNormal   = integer_to_list(?IP_PORT)    ++ ".conf",
 
412
    IpHtacess  = integer_to_list(?IP_PORT)   ++ "htacess.conf",
 
413
    SslNormal  = integer_to_list(?SSL_PORT)  ++ ".conf",
 
414
    SslHtacess = integer_to_list(?SSL_PORT) ++ "htacess.conf",
 
415
 
 
416
    DataDir     = ?config(data_dir, Config),
 
417
    SuiteTopDir = ?config(suite_top_dir, Config),
 
418
 
 
419
    io:format(user, "~w:init_per_testcase2(~w) -> "
 
420
              "~n   SuiteDir: ~p"
 
421
              "~n   DataDir: ~p"
 
422
              "~n", [?MODULE, Case, SuiteTopDir, DataDir]),
 
423
    
 
424
    TcTopDir = filename:join(SuiteTopDir, Case),
 
425
    ?line ok = file:make_dir(TcTopDir),
 
426
 
 
427
    io:format(user, "~w:init_per_testcase2(~w) -> "
 
428
              "~n   TcTopDir: ~p"
 
429
              "~n", [?MODULE, Case, TcTopDir]),
 
430
 
 
431
    DataSrc    = filename:join([DataDir, "server_root"]),
 
432
    ServerRoot = filename:join([TcTopDir, "server_root"]),
 
433
    
 
434
    io:format(user, "~w:init_per_testcase2(~w) -> "
 
435
              "~n   DataSrc: ~p"
 
436
              "~n   ServerRoot: ~p"
 
437
              "~n", [?MODULE, Case, DataSrc, ServerRoot]),
 
438
 
 
439
    ok = file:make_dir(ServerRoot),
 
440
    ok = file:make_dir(filename:join([TcTopDir, "logs"])),
 
441
 
 
442
    NewConfig = [{tc_top_dir, TcTopDir}, {server_root, ServerRoot} | Config],
 
443
 
 
444
    io:format(user, "~w:init_per_testcase2(~w) -> "
 
445
              "copy DataSrc to ServerRoot~n", 
 
446
              [?MODULE, Case]),
 
447
 
 
448
    inets_test_lib:copy_dirs(DataSrc, ServerRoot),
 
449
 
 
450
    io:format(user, "~w:init_per_testcase2(~w) -> fix cgi~n", 
 
451
              [?MODULE, Case]),
 
452
    EnvCGI =  filename:join([ServerRoot, "cgi-bin", "printenv.sh"]),
 
453
    {ok, FileInfo} = file:read_file_info(EnvCGI),
 
454
    ok = file:write_file_info(EnvCGI, 
 
455
                              FileInfo#file_info{mode = 8#00755}),
 
456
    
 
457
    EchoCGI = case test_server:os_type() of
 
458
              {win32, _} ->
 
459
                  "cgi_echo.exe";
 
460
              _ ->
 
461
                  "cgi_echo"
 
462
              end,
 
463
    CGIDir = filename:join([ServerRoot, "cgi-bin"]),
 
464
    inets_test_lib:copy_file(EchoCGI, DataDir,  CGIDir),
 
465
    NewEchoCGI = filename:join([CGIDir, EchoCGI]),
 
466
    {ok, FileInfo1} = file:read_file_info(NewEchoCGI),
 
467
    ok = file:write_file_info(NewEchoCGI, 
 
468
                              FileInfo1#file_info{mode = 8#00755}),
 
469
    
 
470
    %% To be used by IP test cases
 
471
    io:format(user, "~w:init_per_testcase2(~w) -> ip testcase setups~n", 
 
472
              [?MODULE, Case]),
 
473
    create_config([{port, ?IP_PORT}, {sock_type, ip_comm} | NewConfig], 
 
474
                  normal_acess, IpNormal), 
 
475
    create_config([{port, ?IP_PORT}, {sock_type, ip_comm} | NewConfig], 
 
476
                  mod_htaccess, IpHtacess), 
 
477
 
 
478
    %% To be used by SSL test cases
 
479
    io:format(user, "~w:init_per_testcase2(~w) -> ssl testcase setups~n", 
 
480
              [?MODULE, Case]),
 
481
    SocketType = 
 
482
        case atom_to_list(Case) of
 
483
            [X, $s, $s, $l | _] ->
 
484
                case X of
 
485
                    $p -> ssl;
 
486
                    $o -> ossl;
 
487
                    $e -> essl
 
488
                end;
 
489
            _ ->
 
490
                ssl
 
491
        end,
 
492
 
 
493
    create_config([{port, ?SSL_PORT}, {sock_type, SocketType} | NewConfig], 
 
494
                  normal_acess, SslNormal),
 
495
    create_config([{port, ?SSL_PORT}, {sock_type, SocketType} | NewConfig],
 
496
                  mod_htaccess, SslHtacess),  
 
497
  
 
498
    %% To be used by IPv6 test cases. Case-clause is so that
 
499
    %% you can do ts:run(inets, httpd_SUITE, <test case>)
 
500
    %% for all cases except the ipv6 cases as they depend
 
501
    %% on  'test_host_ipv6_only' that will only be present
 
502
    %% when you run the whole test suite due  to shortcomings
 
503
    %% of the test server.
 
504
    %% case (catch ?config(test_host_ipv6_only, Config)) of
 
505
    %%  {_,IPv6Host,IPv6Adress,_,_} ->
 
506
    %%      create_ipv6_config([{port, ?IP_PORT}, 
 
507
    %%                          {sock_type, ip_comm} | NewConfig],
 
508
    %%                         "ipv6_hostname.conf", IPv6Host),
 
509
    %%      create_ipv6_config([{port, ?IP_PORT}, 
 
510
    %%                          {sock_type, ip_comm} | NewConfig],
 
511
    %%                         "ipv6_address.conf", IPv6Adress);
 
512
    %%  _ ->
 
513
    %%      ok
 
514
    %%     end,
 
515
    
 
516
    io:format(user, "~w:init_per_testcase2(~w) -> done~n", 
 
517
              [?MODULE, Case]),
 
518
 
 
519
    NewConfig.
 
520
 
 
521
 
 
522
init_per_testcase3(Case, Config) ->
 
523
    io:format(user, "~w:init_per_testcase3(~w) -> entry with"
 
524
              "~n   Config: ~p", [?MODULE, Case, Config]),
 
525
 
 
526
    
 
527
%%     %% Create a new fresh node to be used by the server in this test-case
 
528
    
 
529
%%     NodeName = list_to_atom(atom_to_list(Case) ++ "_httpd"), 
 
530
%%     Node     = inets_test_lib:start_node(NodeName),
 
531
    
 
532
    %% Clean up (we do not want this clean up in end_per_testcase
 
533
    %% if init_per_testcase crashes for some testcase it will
 
534
    %% have contaminated the environment and there will be no clean up.)
 
535
    %% This init can take a few different paths so that one crashes
 
536
    %% does not mean that all invocations will.
 
537
 
 
538
    application:unset_env(inets, services),
 
539
    application:stop(inets),
 
540
    application:stop(ssl),
 
541
    cleanup_mnesia(),
 
542
 
 
543
    %% Set trace
 
544
    case lists:reverse(atom_to_list(Case)) of
 
545
        "tset_emit" ++ _Rest -> % test-cases ending with time_test
 
546
            io:format(user, "~w:init_per_testcase3(~w) -> disabling trace", 
 
547
                      [?MODULE, Case]),
 
548
            inets:disable_trace();
 
549
        _ ->
 
550
            %% TraceLevel = max, 
 
551
            io:format(user, "~w:init_per_testcase3(~w) -> enabling trace", 
 
552
                      [?MODULE, Case]),
 
553
            TraceLevel = 70, 
 
554
            TraceDest  = io, 
 
555
            inets:enable_trace(TraceLevel, TraceDest, httpd)
 
556
    end,
 
557
            
 
558
    %% Start initialization
 
559
    io:format(user, "~w:init_per_testcase3(~w) -> start init", 
 
560
              [?MODULE, Case]),
 
561
    
 
562
 
 
563
    Dog = test_server:timetrap(inets_test_lib:minutes(10)),
 
564
    NewConfig = lists:keydelete(watchdog, 1, Config),
 
565
    TcTopDir = ?config(tc_top_dir, Config),
 
566
    CaseRest = 
 
567
        case atom_to_list(Case) of
 
568
            "ip_mod_htaccess" ->
 
569
                inets_test_lib:start_http_server(
 
570
                  filename:join(TcTopDir,
 
571
                                integer_to_list(?IP_PORT) ++
 
572
                                "htacess.conf")),
 
573
                "mod_htaccess";
 
574
            "ip_" ++ Rest ->
 
575
                inets_test_lib:start_http_server(
 
576
                  filename:join(TcTopDir,
 
577
                                integer_to_list(?IP_PORT) ++ ".conf")),
 
578
                Rest;
 
579
            "ticket_5913" ->
 
580
                HttpdOptions =
 
581
                    [{file,
 
582
                      filename:join(TcTopDir,
 
583
                                    integer_to_list(?IP_PORT) ++ ".conf")},
 
584
                     {accept_timeout,30000},
 
585
                     {debug,[{exported_functions,
 
586
                              [httpd_manager,httpd_request_handler]}]}],
 
587
                inets_test_lib:start_http_server(HttpdOptions);
 
588
            "ticket_"++Rest ->
 
589
                %% OTP-5913 use the new syntax of inets.config 
 
590
                inets_test_lib:start_http_server([{file,
 
591
                  filename:join(TcTopDir,
 
592
                                integer_to_list(?IP_PORT) ++ ".conf")}]),
 
593
                Rest;
 
594
 
 
595
            [X, $s, $s, $l, $_, $m, $o, $d, $_, $h, $t, $a, $c, $c, $e, $s, $s] ->
 
596
                SslTag = 
 
597
                    case X of
 
598
                        $p -> ssl;  % plain
 
599
                        $o -> ossl; % OpenSSL based ssl
 
600
                        $e -> essl  % Erlang based ssl
 
601
                    end,
 
602
                case inets_test_lib:start_http_server_ssl(
 
603
                       filename:join(TcTopDir,
 
604
                                     integer_to_list(?SSL_PORT) ++ 
 
605
                                     "htacess.conf"), SslTag) of
 
606
                    ok ->
 
607
                        "mod_htaccess";
 
608
                    Other ->
 
609
                        error_logger:info_report("Other: ~p~n", [Other]),
 
610
                        {skip, "SSL does not seem to be supported"}
 
611
                end;
 
612
            [X, $s, $s, $l, $_ | Rest] ->
 
613
                SslTag = 
 
614
                    case X of
 
615
                        $p -> ssl;
 
616
                        $o -> ossl;
 
617
                        $e -> essl
 
618
                    end,
 
619
                case inets_test_lib:start_http_server_ssl(
 
620
                       filename:join(TcTopDir,
 
621
                                     integer_to_list(?SSL_PORT) ++ 
 
622
                                     ".conf"), SslTag) of
 
623
                    ok ->
 
624
                        Rest;
 
625
                    Other ->
 
626
                        error_logger:info_report("Other: ~p~n", [Other]),
 
627
                        {skip, "SSL does not seem to be supported"}
 
628
                end;
 
629
            "ipv6_" ++ _  = TestCaseStr ->
 
630
                {ok, Hostname} = inet:gethostname(),
 
631
                
 
632
                case lists:member(list_to_atom(Hostname), 
 
633
                                  ?config(ipv6_hosts, Config)) of
 
634
                    true ->
 
635
                        inets_test_lib:start_http_server(
 
636
                          filename:join(TcTopDir,
 
637
                                        TestCaseStr ++ ".conf"));
 
638
                    
 
639
                    false ->
 
640
                        {skip, "Host does not support IPv6"}
 
641
                end
 
642
        end,
 
643
 
 
644
    case CaseRest of
 
645
        {skip, _} = Skip ->
 
646
            Skip;
 
647
        "mod_auth_" ++ _ ->
 
648
            start_mnesia(?config(node, Config)),
 
649
            [{watchdog, Dog} | NewConfig];
 
650
        "mod_htaccess" ->
 
651
            ServerRoot = ?config(server_root, Config), 
 
652
            Path = filename:join([ServerRoot, "htdocs"]),
 
653
            catch remove_htacess(Path),
 
654
            create_htacess_data(Path, ?config(address, Config)),
 
655
            [{watchdog, Dog} | NewConfig];
 
656
        "range" ->
 
657
            ServerRoot = ?config(server_root, Config), 
 
658
            Path = filename:join([ServerRoot, "htdocs"]),
 
659
            create_range_data(Path),
 
660
            [{watchdog, Dog} | NewConfig];
 
661
        _ ->
 
662
            [{watchdog, Dog} | NewConfig]
 
663
    end.
 
664
 
 
665
 
 
666
%%--------------------------------------------------------------------
 
667
%% Function: end_per_testcase(Case, Config) -> _
 
668
%% Case - atom()
 
669
%%   Name of the test case that is about to be run.
 
670
%% Config - [tuple()]
 
671
%%   A list of key/value pairs, holding the test case configuration.
 
672
%% Description: Cleanup after each test case
 
673
%%--------------------------------------------------------------------
 
674
end_per_testcase(Case, Config) ->
 
675
    Dog = ?config(watchdog, Config),
 
676
    test_server:timetrap_cancel(Dog),
 
677
    end_per_testcase2(Case, lists:keydelete(watchdog, 1, Config)),
 
678
    ok.
 
679
 
 
680
end_per_testcase2(Case, Config) ->
 
681
    io:format(user, "~w:end_per_testcase2(~w) -> entry with"
 
682
              "~n   Config: ~p~n", 
 
683
              [?MODULE, Case, Config]),
 
684
    application:unset_env(inets, services),
 
685
    application:stop(inets),
 
686
    application:stop(ssl),     
 
687
    application:stop(crypto), % used by the new ssl (essl test cases)  
 
688
    cleanup_mnesia(),
 
689
    io:format(user, "~w:end_per_testcase2(~w) -> done~n", 
 
690
              [?MODULE, Case]),
 
691
    ok.
 
692
 
 
693
 
 
694
%%-------------------------------------------------------------------------
 
695
%% Test cases starts here.
 
696
%%-------------------------------------------------------------------------
 
697
 
 
698
%%-------------------------------------------------------------------------
 
699
 
 
700
 
 
701
 
 
702
 
 
703
 
 
704
 
 
705
%%-------------------------------------------------------------------------
 
706
 
 
707
%%-------------------------------------------------------------------------
 
708
 
 
709
%%-------------------------------------------------------------------------
 
710
 
 
711
%%-------------------------------------------------------------------------
 
712
 
 
713
%%-------------------------------------------------------------------------
 
714
 
 
715
%%-------------------------------------------------------------------------
 
716
ip_mod_alias(doc) -> 
 
717
    ["Module test: mod_alias"];
 
718
ip_mod_alias(suite) -> 
 
719
    [];
 
720
ip_mod_alias(Config) when is_list(Config) ->
 
721
    httpd_mod:alias(ip_comm, ?IP_PORT, 
 
722
                    ?config(host, Config), ?config(node, Config)),
 
723
    ok.
 
724
%%-------------------------------------------------------------------------
 
725
ip_mod_actions(doc) -> 
 
726
    ["Module test: mod_actions"];
 
727
ip_mod_actions(suite) -> 
 
728
    [];
 
729
ip_mod_actions(Config) when is_list(Config) ->
 
730
    httpd_mod:actions(ip_comm, ?IP_PORT, 
 
731
                      ?config(host, Config), ?config(node, Config)),
 
732
    ok.
 
733
%%-------------------------------------------------------------------------
 
734
ip_mod_security(doc) -> 
 
735
    ["Module test: mod_security"];
 
736
ip_mod_security(suite) -> 
 
737
    [];
 
738
ip_mod_security(Config) when is_list(Config) ->
 
739
    ServerRoot = ?config(server_root, Config), 
 
740
    httpd_mod:security(ServerRoot, ip_comm, ?IP_PORT, 
 
741
                       ?config(host, Config), ?config(node, Config)),
 
742
    ok.
 
743
 
 
744
%%-------------------------------------------------------------------------
 
745
ip_mod_auth(doc) -> 
 
746
    ["Module test: mod_auth"];
 
747
ip_mod_auth(suite) -> 
 
748
    [];
 
749
ip_mod_auth(Config) when is_list(Config) ->
 
750
    httpd_mod:auth(ip_comm, ?IP_PORT, 
 
751
                   ?config(host, Config), ?config(node, Config)),
 
752
    ok.
 
753
 
 
754
%%-------------------------------------------------------------------------
 
755
ip_mod_auth_api(doc) -> 
 
756
    ["Module test: mod_auth_api"];
 
757
ip_mod_auth_api(suite) -> 
 
758
    [];
 
759
ip_mod_auth_api(Config) when is_list(Config) ->
 
760
    ServerRoot = ?config(server_root, Config), 
 
761
    Host =  ?config(host, Config),
 
762
    Node = ?config(node, Config),
 
763
    httpd_mod:auth_api(ServerRoot, "", ip_comm, ?IP_PORT, Host, Node),
 
764
    httpd_mod:auth_api(ServerRoot, "dets_", ip_comm, ?IP_PORT, Host, Node),
 
765
    httpd_mod:auth_api(ServerRoot, "mnesia_", ip_comm, ?IP_PORT, Host, Node),
 
766
    ok. 
 
767
%%-------------------------------------------------------------------------
 
768
ip_mod_auth_mnesia_api(doc) -> 
 
769
    ["Module test: mod_auth_mnesia_api"];
 
770
ip_mod_auth_mnesia_api(suite) -> 
 
771
    [];
 
772
ip_mod_auth_mnesia_api(Config) when is_list(Config) ->
 
773
    httpd_mod:auth_mnesia_api(ip_comm, ?IP_PORT, 
 
774
                   ?config(host, Config), ?config(node, Config)),
 
775
    ok.
 
776
%%-------------------------------------------------------------------------
 
777
ip_mod_htaccess(doc) -> 
 
778
    ["Module test: mod_htaccess"];
 
779
ip_mod_htaccess(suite) -> 
 
780
    [];
 
781
ip_mod_htaccess(Config) when is_list(Config) ->
 
782
    httpd_mod:htaccess(ip_comm, ?IP_PORT, 
 
783
                       ?config(host, Config), ?config(node, Config)),
 
784
    ok.
 
785
%%-------------------------------------------------------------------------
 
786
ip_mod_cgi(doc) ->
 
787
    ["Module test: mod_cgi"];
 
788
ip_mod_cgi(suite) ->
 
789
    [];
 
790
ip_mod_cgi(Config) when is_list(Config) ->
 
791
    case test_server:os_type() of
 
792
        vxworks ->
 
793
            {skip, cgi_not_supported_on_vxwoks};
 
794
        _ ->
 
795
            httpd_mod:cgi(ip_comm, ?IP_PORT, 
 
796
                          ?config(host, Config), ?config(node, Config)),
 
797
            ok
 
798
    end.
 
799
%%-------------------------------------------------------------------------
 
800
ip_mod_esi(doc) ->
 
801
    ["Module test: mod_esi"];
 
802
ip_mod_esi(suite) ->
 
803
    [];
 
804
ip_mod_esi(Config) when is_list(Config) ->
 
805
    httpd_mod:esi(ip_comm, ?IP_PORT, 
 
806
                  ?config(host, Config), ?config(node, Config)),
 
807
    ok.
 
808
 
 
809
%%-------------------------------------------------------------------------
 
810
ip_mod_get(doc) ->
 
811
    ["Module test: mod_get"];
 
812
ip_mod_get(suite) ->
 
813
    [];
 
814
ip_mod_get(Config) when is_list(Config) ->
 
815
    httpd_mod:get(ip_comm, ?IP_PORT, 
 
816
                  ?config(host, Config), ?config(node, Config)),
 
817
    ok.
 
818
 
 
819
%%-------------------------------------------------------------------------
 
820
ip_mod_head(doc) ->
 
821
    ["Module test: mod_head"];
 
822
ip_mod_head(suite) ->
 
823
    [];
 
824
ip_mod_head(Config) when is_list(Config) ->
 
825
    httpd_mod:head(ip_comm, ?IP_PORT, 
 
826
                   ?config(host, Config), ?config(node, Config)),
 
827
    ok.
 
828
%%-------------------------------------------------------------------------
 
829
ip_mod_all(doc) ->
 
830
    ["All modules test"];
 
831
ip_mod_all(suite) ->
 
832
    [];
 
833
ip_mod_all(Config) when is_list(Config) ->
 
834
    httpd_mod:all(ip_comm, ?IP_PORT, 
 
835
                  ?config(host, Config), ?config(node, Config)),
 
836
    ok.
 
837
%%-------------------------------------------------------------------------
 
838
ip_load_light(doc) ->
 
839
    ["Test light load"];
 
840
ip_load_light(suite) ->
 
841
    [];
 
842
ip_load_light(Config) when is_list(Config) ->
 
843
    httpd_load:load_test(ip_comm, ?IP_PORT, ?config(host, Config), 
 
844
                         ?config(node, Config),
 
845
                         get_nof_clients(ip_comm, light)),
 
846
    ok.
 
847
%%-------------------------------------------------------------------------
 
848
ip_load_medium(doc) ->
 
849
    ["Test  medium load"];
 
850
ip_load_medium(suite) ->
 
851
    [];
 
852
ip_load_medium(Config) when is_list(Config) ->
 
853
      httpd_load:load_test(ip_comm, ?IP_PORT, ?config(host, Config),
 
854
                           ?config(node, Config),
 
855
                           get_nof_clients(ip_comm, medium)),
 
856
    ok.
 
857
%%-------------------------------------------------------------------------
 
858
ip_load_heavy(doc) ->
 
859
    ["Test heavy load"];
 
860
ip_load_heavy(suite) ->
 
861
    [];
 
862
ip_load_heavy(Config) when is_list(Config) ->
 
863
     httpd_load:load_test(ip_comm, ?IP_PORT, ?config(host, Config),
 
864
                          ?config(node, Config),
 
865
                          get_nof_clients(ip_comm, heavy)),
 
866
    ok.
 
867
 
 
868
 
 
869
%%-------------------------------------------------------------------------
 
870
ip_dos_hostname(doc) ->
 
871
    ["Denial Of Service (DOS) attack test case"];
 
872
ip_dos_hostname(suite) ->
 
873
    [];
 
874
ip_dos_hostname(Config) when is_list(Config) ->
 
875
    dos_hostname(ip_comm, ?IP_PORT, ?config(host, Config), 
 
876
                 ?config(node, Config), ?MAX_HEADER_SIZE),
 
877
    ok.
 
878
 
 
879
 
 
880
%%-------------------------------------------------------------------------
 
881
ip_time_test(doc) ->
 
882
    [""];
 
883
ip_time_test(suite) ->
 
884
    [];
 
885
ip_time_test(Config) when is_list(Config) ->
 
886
    %% <CONDITIONAL-SKIP>
 
887
    Skippable = [win32],
 
888
    Condition = fun() -> ?OS_BASED_SKIP(Skippable) end,
 
889
    ?NON_PC_TC_MAYBE_SKIP(Config, Condition),
 
890
    %% </CONDITIONAL-SKIP>
 
891
    
 
892
    httpd_time_test:t(ip_comm, ?config(host, Config), ?IP_PORT),
 
893
    ok.
 
894
 
 
895
%%-------------------------------------------------------------------------
 
896
ip_block_503(doc) ->
 
897
    ["Check that you will receive status code 503 when the server"
 
898
     " is blocked and 200 when its not blocked."];
 
899
ip_block_503(suite) ->
 
900
    [];
 
901
ip_block_503(Config) when is_list(Config) ->
 
902
    httpd_block:block_503(ip_comm, ?IP_PORT, ?config(host, Config), 
 
903
                                 ?config(node, Config)),
 
904
    ok.
 
905
%%-------------------------------------------------------------------------
 
906
ip_block_disturbing_idle(doc) ->
 
907
    ["Check that you can block/unblock an idle server. The strategy " 
 
908
     "distribing does not really make a difference in this case."];
 
909
ip_block_disturbing_idle(suite) ->
 
910
    [];
 
911
ip_block_disturbing_idle(Config) when is_list(Config) ->
 
912
    httpd_block:block_disturbing_idle(ip_comm, ?IP_PORT, 
 
913
                                      ?config(host, Config), 
 
914
                                      ?config(node, Config)),
 
915
    ok.
 
916
%%-------------------------------------------------------------------------
 
917
ip_block_non_disturbing_idle(doc) ->
 
918
    ["Check that you can block/unblock an idle server. The strategy " 
 
919
     "non distribing does not really make a difference in this case."];
 
920
ip_block_non_disturbing_idle(suite) ->
 
921
    [];
 
922
ip_block_non_disturbing_idle(Config) when is_list(Config) ->
 
923
    httpd_block:block_non_disturbing_idle(ip_comm, ?IP_PORT, 
 
924
                                          ?config(host, Config), 
 
925
                                          ?config(node, Config)),
 
926
    ok.
 
927
%%-------------------------------------------------------------------------
 
928
ip_block_disturbing_active(doc) ->
 
929
    ["Check that you can block/unblock an active server. The strategy " 
 
930
     "distribing means ongoing requests should be terminated."];
 
931
ip_block_disturbing_active(suite) ->
 
932
    [];
 
933
ip_block_disturbing_active(Config) when is_list(Config) ->
 
934
    httpd_block:block_disturbing_active(ip_comm, ?IP_PORT, 
 
935
                                        ?config(host, Config), 
 
936
                                        ?config(node, Config)),
 
937
    ok.
 
938
%%-------------------------------------------------------------------------
 
939
ip_block_non_disturbing_active(doc) ->
 
940
    ["Check that you can block/unblock an idle server. The strategy " 
 
941
     "non distribing means the ongoing requests should be compleated."];
 
942
ip_block_non_disturbing_active(suite) ->
 
943
    [];
 
944
ip_block_non_disturbing_active(Config) when is_list(Config) ->
 
945
    httpd_block:block_non_disturbing_idle(ip_comm, ?IP_PORT, 
 
946
                                          ?config(host, Config), 
 
947
                                          ?config(node, Config)),
 
948
    ok.
 
949
 
 
950
%%-------------------------------------------------------------------------
 
951
ip_block_disturbing_active_timeout_not_released(doc) ->
 
952
    ["Check that you can block an active server. The strategy " 
 
953
     "distribing means ongoing requests should be compleated"
 
954
     "if the timeout does not occur."];
 
955
ip_block_disturbing_active_timeout_not_released(suite) ->
 
956
    [];
 
957
ip_block_disturbing_active_timeout_not_released(Config) 
 
958
  when is_list(Config) ->
 
959
    httpd_block:block_disturbing_active_timeout_not_released(ip_comm, 
 
960
                                                             ?IP_PORT, 
 
961
                                                             ?config(host,
 
962
                                                                     Config), 
 
963
                                                             ?config(node, 
 
964
                                                                     Config)),
 
965
    ok.
 
966
%%-------------------------------------------------------------------------
 
967
ip_block_disturbing_active_timeout_released(doc) ->
 
968
    ["Check that you can block an active server. The strategy " 
 
969
     "distribing means ongoing requests should be terminated when"
 
970
     "the timeout occurs."];
 
971
ip_block_disturbing_active_timeout_released(suite) ->
 
972
    [];
 
973
ip_block_disturbing_active_timeout_released(Config) 
 
974
  when is_list(Config) ->
 
975
    httpd_block:block_disturbing_active_timeout_released(ip_comm, 
 
976
                                                         ?IP_PORT, 
 
977
                                                         ?config(host,
 
978
                                                                 Config), 
 
979
                                                         ?config(node, 
 
980
                                                                 Config)),
 
981
    ok.
 
982
 
 
983
%%-------------------------------------------------------------------------
 
984
ip_block_non_disturbing_active_timeout_not_released(doc) ->
 
985
    ["Check that you can block an active server. The strategy " 
 
986
     "non non distribing means ongoing requests should be completed."];
 
987
ip_block_non_disturbing_active_timeout_not_released(suite) ->
 
988
    [];
 
989
ip_block_non_disturbing_active_timeout_not_released(Config)
 
990
  when is_list(Config) ->
 
991
    httpd_block:
 
992
        block_non_disturbing_active_timeout_not_released(ip_comm,
 
993
                                                         ?IP_PORT, 
 
994
                                                         ?config(host, 
 
995
                                                                 Config), 
 
996
                                                         ?config(node, 
 
997
                                                                 Config)),
 
998
    ok.
 
999
%%-------------------------------------------------------------------------
 
1000
ip_block_non_disturbing_active_timeout_released(doc) ->
 
1001
    ["Check that you can block an active server. The strategy " 
 
1002
     "non non distribing means ongoing requests should be completed. "
 
1003
     "When the timeout occurs the block operation sohould be canceled." ];
 
1004
ip_block_non_disturbing_active_timeout_released(suite) ->
 
1005
    [];
 
1006
ip_block_non_disturbing_active_timeout_released(Config)
 
1007
  when is_list(Config) ->
 
1008
    httpd_block:
 
1009
        block_non_disturbing_active_timeout_released(ip_comm,
 
1010
                                                     ?IP_PORT, 
 
1011
                                                     ?config(host, 
 
1012
                                                             Config), 
 
1013
                                                     ?config(node, 
 
1014
                                                             Config)),
 
1015
    ok.
 
1016
%%-------------------------------------------------------------------------
 
1017
ip_block_disturbing_blocker_dies(doc) ->
 
1018
    [];
 
1019
ip_block_disturbing_blocker_dies(suite) ->
 
1020
    [];
 
1021
ip_block_disturbing_blocker_dies(Config) when is_list(Config) ->
 
1022
    httpd_block:disturbing_blocker_dies(ip_comm, ?IP_PORT, 
 
1023
                                        ?config(host, Config), 
 
1024
                                        ?config(node, Config)),
 
1025
    ok.
 
1026
%%-------------------------------------------------------------------------
 
1027
ip_block_non_disturbing_blocker_dies(doc) ->
 
1028
    [];
 
1029
ip_block_non_disturbing_blocker_dies(suite) ->
 
1030
    [];
 
1031
ip_block_non_disturbing_blocker_dies(Config) when is_list(Config) ->
 
1032
    httpd_block:non_disturbing_blocker_dies(ip_comm, ?IP_PORT, 
 
1033
                                            ?config(host, Config), 
 
1034
                                            ?config(node, Config)),
 
1035
    ok.
 
1036
%%-------------------------------------------------------------------------
 
1037
ip_restart_no_block(doc) ->
 
1038
    [""];
 
1039
ip_restart_no_block(suite) ->
 
1040
    [];
 
1041
ip_restart_no_block(Config) when is_list(Config) ->
 
1042
    httpd_block:restart_no_block(ip_comm, ?IP_PORT, ?config(host, Config), 
 
1043
                                 ?config(node, Config)),
 
1044
    ok.
 
1045
%%-------------------------------------------------------------------------
 
1046
ip_restart_disturbing_block(doc) ->
 
1047
    [""];
 
1048
ip_restart_disturbing_block(suite) ->
 
1049
    [];
 
1050
ip_restart_disturbing_block(Config) when is_list(Config) ->
 
1051
    %% <CONDITIONAL-SKIP>
 
1052
    Condition = 
 
1053
        fun() -> 
 
1054
                case os:type() of
 
1055
                    {unix, linux} ->
 
1056
                        HW = string:strip(os:cmd("uname -m"), right, $\n),
 
1057
                        case HW of
 
1058
                            "ppc" ->
 
1059
                                case inet:gethostname() of
 
1060
                                    {ok, "peach"} ->
 
1061
                                        true;
 
1062
                                    _ ->
 
1063
                                        false
 
1064
                                end;
 
1065
                            _ ->
 
1066
                                false
 
1067
                        end;
 
1068
                    _ ->
 
1069
                        false
 
1070
                end
 
1071
        end,
 
1072
    ?NON_PC_TC_MAYBE_SKIP(Config, Condition),
 
1073
    %% </CONDITIONAL-SKIP>
 
1074
 
 
1075
    httpd_block:restart_disturbing_block(ip_comm, ?IP_PORT, 
 
1076
                                         ?config(host, Config),
 
1077
                                         ?config(node, Config)),
 
1078
    ok.
 
1079
 
 
1080
%%-------------------------------------------------------------------------
 
1081
ip_restart_non_disturbing_block(doc) ->
 
1082
    [""];
 
1083
ip_restart_non_disturbing_block(suite) ->
 
1084
    [];
 
1085
ip_restart_non_disturbing_block(Config) when is_list(Config) ->
 
1086
    %% <CONDITIONAL-SKIP>
 
1087
    Condition = 
 
1088
        fun() -> 
 
1089
                case os:type() of
 
1090
                    {unix, linux} ->
 
1091
                        HW = string:strip(os:cmd("uname -m"), right, $\n),
 
1092
                        case HW of
 
1093
                            "ppc" ->
 
1094
                                case inet:gethostname() of
 
1095
                                    {ok, "peach"} ->
 
1096
                                        true;
 
1097
                                    _ ->
 
1098
                                        false
 
1099
                                end;
 
1100
                            _ ->
 
1101
                                false
 
1102
                        end;
 
1103
                    _ ->
 
1104
                        false
 
1105
                end
 
1106
        end,
 
1107
    ?NON_PC_TC_MAYBE_SKIP(Config, Condition),
 
1108
    %% </CONDITIONAL-SKIP>
 
1109
 
 
1110
    httpd_block:restart_non_disturbing_block(ip_comm, ?IP_PORT,
 
1111
                                            ?config(host, Config), 
 
1112
                                            ?config(node, Config)),
 
1113
    ok.
 
1114
 
 
1115
%%-------------------------------------------------------------------------
 
1116
 
 
1117
pssl_mod_alias(doc) -> 
 
1118
    ["Module test: mod_alias - old SSL config"];
 
1119
pssl_mod_alias(suite) -> 
 
1120
    [];
 
1121
pssl_mod_alias(Config) when is_list(Config) ->
 
1122
    ssl_mod_alias(ssl, Config).
 
1123
 
 
1124
ossl_mod_alias(doc) -> 
 
1125
    ["Module test: mod_alias - using new of configure old SSL"];
 
1126
ossl_mod_alias(suite) -> 
 
1127
    [];
 
1128
ossl_mod_alias(Config) when is_list(Config) ->
 
1129
    ssl_mod_alias(ossl, Config).
 
1130
 
 
1131
essl_mod_alias(doc) -> 
 
1132
    ["Module test: mod_alias - using new of configure new SSL"];
 
1133
essl_mod_alias(suite) -> 
 
1134
    [];
 
1135
essl_mod_alias(Config) when is_list(Config) ->
 
1136
    ssl_mod_alias(essl, Config).
 
1137
 
 
1138
 
 
1139
ssl_mod_alias(Tag, Config) ->
 
1140
    httpd_mod:alias(Tag, ?SSL_PORT, 
 
1141
                    ?config(host, Config), ?config(node, Config)),
 
1142
    ok. 
 
1143
 
 
1144
 
 
1145
%%-------------------------------------------------------------------------
 
1146
 
 
1147
pssl_mod_actions(doc) -> 
 
1148
    ["Module test: mod_actions - old SSL config"];
 
1149
pssl_mod_actions(suite) -> 
 
1150
    [];
 
1151
pssl_mod_actions(Config) when is_list(Config) ->
 
1152
    ssl_mod_actions(ssl, Config).
 
1153
 
 
1154
ossl_mod_actions(doc) -> 
 
1155
    ["Module test: mod_actions - using new of configure old SSL"];
 
1156
ossl_mod_actions(suite) -> 
 
1157
    [];
 
1158
ossl_mod_actions(Config) when is_list(Config) ->
 
1159
    ssl_mod_actions(ossl, Config).
 
1160
 
 
1161
essl_mod_actions(doc) -> 
 
1162
    ["Module test: mod_actions - using new of configure new SSL"];
 
1163
essl_mod_actions(suite) -> 
 
1164
    [];
 
1165
essl_mod_actions(Config) when is_list(Config) ->
 
1166
    ssl_mod_actions(essl, Config).
 
1167
 
 
1168
 
 
1169
ssl_mod_actions(Tag, Config) ->
 
1170
    httpd_mod:actions(Tag, 
 
1171
                      ?SSL_PORT, 
 
1172
                      ?config(host, Config), 
 
1173
                      ?config(node, Config)),
 
1174
    ok.
 
1175
 
 
1176
 
 
1177
%%-------------------------------------------------------------------------
 
1178
 
 
1179
pssl_mod_security(doc) -> 
 
1180
    ["Module test: mod_security - old SSL config"];
 
1181
pssl_mod_security(suite) -> 
 
1182
    [];
 
1183
pssl_mod_security(Config) when is_list(Config) ->
 
1184
    ssl_mod_security(ssl, Config).
 
1185
 
 
1186
ossl_mod_security(doc) -> 
 
1187
    ["Module test: mod_security - using new of configure old SSL"];
 
1188
ossl_mod_security(suite) -> 
 
1189
    [];
 
1190
ossl_mod_security(Config) when is_list(Config) ->
 
1191
    ssl_mod_security(ossl, Config).
 
1192
 
 
1193
essl_mod_security(doc) -> 
 
1194
    ["Module test: mod_security - using new of configure new SSL"];
 
1195
essl_mod_security(suite) -> 
 
1196
    [];
 
1197
essl_mod_security(Config) when is_list(Config) ->
 
1198
    ssl_mod_security(essl, Config).
 
1199
 
 
1200
ssl_mod_security(Tag, Config) ->
 
1201
    ServerRoot = ?config(server_root, Config), 
 
1202
    httpd_mod:security(ServerRoot, 
 
1203
                       Tag, 
 
1204
                       ?SSL_PORT, 
 
1205
                       ?config(host, Config), 
 
1206
                       ?config(node, Config)),
 
1207
    ok.
 
1208
 
 
1209
 
 
1210
%%-------------------------------------------------------------------------
 
1211
 
 
1212
pssl_mod_auth(doc) -> 
 
1213
    ["Module test: mod_auth - old SSL config"];
 
1214
pssl_mod_auth(suite) -> 
 
1215
    [];
 
1216
pssl_mod_auth(Config) when is_list(Config) ->
 
1217
    ssl_mod_auth(ssl, Config).
 
1218
 
 
1219
ossl_mod_auth(doc) -> 
 
1220
    ["Module test: mod_auth - using new of configure old SSL"];
 
1221
ossl_mod_auth(suite) -> 
 
1222
    [];
 
1223
ossl_mod_auth(Config) when is_list(Config) ->
 
1224
    ssl_mod_auth(ossl, Config).
 
1225
 
 
1226
essl_mod_auth(doc) -> 
 
1227
    ["Module test: mod_auth - using new of configure new SSL"];
 
1228
essl_mod_auth(suite) -> 
 
1229
    [];
 
1230
essl_mod_auth(Config) when is_list(Config) ->
 
1231
    ssl_mod_auth(essl, Config).
 
1232
 
 
1233
ssl_mod_auth(Tag, Config) ->
 
1234
    httpd_mod:auth(Tag, 
 
1235
                   ?SSL_PORT, 
 
1236
                   ?config(host, Config), 
 
1237
                   ?config(node, Config)),
 
1238
    ok.
 
1239
 
 
1240
 
 
1241
%%-------------------------------------------------------------------------
 
1242
 
 
1243
pssl_mod_auth_api(doc) -> 
 
1244
    ["Module test: mod_auth - old SSL config"];
 
1245
pssl_mod_auth_api(suite) -> 
 
1246
    [];
 
1247
pssl_mod_auth_api(Config) when is_list(Config) ->
 
1248
    ssl_mod_auth_api(ssl, Config).
 
1249
 
 
1250
ossl_mod_auth_api(doc) -> 
 
1251
    ["Module test: mod_auth - using new of configure old SSL"];
 
1252
ossl_mod_auth_api(suite) -> 
 
1253
    [];
 
1254
ossl_mod_auth_api(Config) when is_list(Config) ->
 
1255
    ssl_mod_auth_api(ossl, Config).
 
1256
 
 
1257
essl_mod_auth_api(doc) -> 
 
1258
    ["Module test: mod_auth - using new of configure new SSL"];
 
1259
essl_mod_auth_api(suite) -> 
 
1260
    [];
 
1261
essl_mod_auth_api(Config) when is_list(Config) ->
 
1262
    ssl_mod_auth_api(essl, Config).
 
1263
 
 
1264
ssl_mod_auth_api(Tag, Config) ->
 
1265
    ServerRoot = ?config(server_root, Config), 
 
1266
    Host       =  ?config(host, Config),
 
1267
    Node       = ?config(node, Config),
 
1268
    httpd_mod:auth_api(ServerRoot, "",        Tag, ?SSL_PORT, Host, Node),
 
1269
    httpd_mod:auth_api(ServerRoot, "dets_",   Tag, ?SSL_PORT, Host, Node),
 
1270
    httpd_mod:auth_api(ServerRoot, "mnesia_", Tag, ?SSL_PORT, Host, Node),
 
1271
    ok. 
 
1272
 
 
1273
 
 
1274
%%-------------------------------------------------------------------------
 
1275
 
 
1276
pssl_mod_auth_mnesia_api(doc) -> 
 
1277
    ["Module test: mod_auth_mnesia_api - old SSL config"];
 
1278
pssl_mod_auth_mnesia_api(suite) -> 
 
1279
    [];
 
1280
pssl_mod_auth_mnesia_api(Config) when is_list(Config) ->
 
1281
    ssl_mod_auth_mnesia_api(ssl, Config).
 
1282
 
 
1283
ossl_mod_auth_mnesia_api(doc) -> 
 
1284
    ["Module test: mod_auth_mnesia_api - using new of configure old SSL"];
 
1285
ossl_mod_auth_mnesia_api(suite) -> 
 
1286
    [];
 
1287
ossl_mod_auth_mnesia_api(Config) when is_list(Config) ->
 
1288
    ssl_mod_auth_mnesia_api(ossl, Config).
 
1289
 
 
1290
essl_mod_auth_mnesia_api(doc) -> 
 
1291
    ["Module test: mod_auth_mnesia_api - using new of configure new SSL"];
 
1292
essl_mod_auth_mnesia_api(suite) -> 
 
1293
    [];
 
1294
essl_mod_auth_mnesia_api(Config) when is_list(Config) ->
 
1295
    ssl_mod_auth_mnesia_api(essl, Config).
 
1296
 
 
1297
ssl_mod_auth_mnesia_api(Tag, Config) ->
 
1298
    httpd_mod:auth_mnesia_api(Tag, 
 
1299
                              ?SSL_PORT, 
 
1300
                              ?config(host, Config), 
 
1301
                              ?config(node, Config)),
 
1302
    ok.
 
1303
 
 
1304
 
 
1305
%%-------------------------------------------------------------------------
 
1306
 
 
1307
pssl_mod_htaccess(doc) -> 
 
1308
    ["Module test: mod_htaccess - old SSL config"];
 
1309
pssl_mod_htaccess(suite) -> 
 
1310
    [];
 
1311
pssl_mod_htaccess(Config) when is_list(Config) ->
 
1312
    ssl_mod_htaccess(ssl, Config).
 
1313
 
 
1314
ossl_mod_htaccess(doc) -> 
 
1315
    ["Module test: mod_htaccess - using new of configure old SSL"];
 
1316
ossl_mod_htaccess(suite) -> 
 
1317
    [];
 
1318
ossl_mod_htaccess(Config) when is_list(Config) ->
 
1319
    ssl_mod_htaccess(ossl, Config).
 
1320
 
 
1321
essl_mod_htaccess(doc) -> 
 
1322
    ["Module test: mod_htaccess - using new of configure new SSL"];
 
1323
essl_mod_htaccess(suite) -> 
 
1324
    [];
 
1325
essl_mod_htaccess(Config) when is_list(Config) ->
 
1326
    ssl_mod_htaccess(essl, Config).
 
1327
 
 
1328
ssl_mod_htaccess(Tag, Config) ->
 
1329
    httpd_mod:htaccess(Tag, 
 
1330
                       ?SSL_PORT, 
 
1331
                       ?config(host, Config), 
 
1332
                       ?config(node, Config)),
 
1333
    ok.
 
1334
 
 
1335
 
 
1336
%%-------------------------------------------------------------------------
 
1337
 
 
1338
pssl_mod_cgi(doc) ->
 
1339
    ["Module test: mod_cgi - old SSL config"];
 
1340
pssl_mod_cgi(suite) ->
 
1341
    [];
 
1342
pssl_mod_cgi(Config) when is_list(Config) ->
 
1343
    ssl_mod_cgi(ssl, Config).
 
1344
 
 
1345
ossl_mod_cgi(doc) ->
 
1346
    ["Module test: mod_cgi - using new of configure old SSL"];
 
1347
ossl_mod_cgi(suite) ->
 
1348
    [];
 
1349
ossl_mod_cgi(Config) when is_list(Config) ->
 
1350
    ssl_mod_cgi(ossl, Config).
 
1351
 
 
1352
essl_mod_cgi(doc) ->
 
1353
    ["Module test: mod_cgi - using new of configure new SSL"];
 
1354
essl_mod_cgi(suite) ->
 
1355
    [];
 
1356
essl_mod_cgi(Config) when is_list(Config) ->
 
1357
    ssl_mod_cgi(essl, Config).
 
1358
 
 
1359
ssl_mod_cgi(Tag, Config) ->
 
1360
    case test_server:os_type() of
 
1361
        vxworks ->
 
1362
            {skip, cgi_not_supported_on_vxwoks};
 
1363
        _ ->
 
1364
            httpd_mod:cgi(Tag, 
 
1365
                          ?SSL_PORT, 
 
1366
                          ?config(host, Config), 
 
1367
                          ?config(node, Config)),
 
1368
            ok
 
1369
    end.
 
1370
 
 
1371
 
 
1372
%%-------------------------------------------------------------------------
 
1373
 
 
1374
pssl_mod_esi(doc) ->
 
1375
    ["Module test: mod_esi - old SSL config"];
 
1376
pssl_mod_esi(suite) ->
 
1377
    [];
 
1378
pssl_mod_esi(Config) when is_list(Config) ->
 
1379
    ssl_mod_esi(ssl, Config).
 
1380
 
 
1381
ossl_mod_esi(doc) ->
 
1382
    ["Module test: mod_esi - using new of configure old SSL"];
 
1383
ossl_mod_esi(suite) ->
 
1384
    [];
 
1385
ossl_mod_esi(Config) when is_list(Config) ->
 
1386
    ssl_mod_esi(ossl, Config).
 
1387
 
 
1388
essl_mod_esi(doc) ->
 
1389
    ["Module test: mod_esi - using new of configure new SSL"];
 
1390
essl_mod_esi(suite) ->
 
1391
    [];
 
1392
essl_mod_esi(Config) when is_list(Config) ->
 
1393
    ssl_mod_esi(essl, Config).
 
1394
 
 
1395
ssl_mod_esi(Tag, Config) ->
 
1396
    httpd_mod:esi(Tag, 
 
1397
                  ?SSL_PORT, 
 
1398
                  ?config(host, Config), 
 
1399
                  ?config(node, Config)),
 
1400
    ok.
 
1401
 
 
1402
 
 
1403
%%-------------------------------------------------------------------------
 
1404
 
 
1405
pssl_mod_get(doc) ->
 
1406
    ["Module test: mod_get - old SSL config"];
 
1407
pssl_mod_get(suite) ->
 
1408
    [];
 
1409
pssl_mod_get(Config) when is_list(Config) ->
 
1410
    ssl_mod_get(ssl, Config).
 
1411
 
 
1412
ossl_mod_get(doc) ->
 
1413
    ["Module test: mod_get - using new of configure old SSL"];
 
1414
ossl_mod_get(suite) ->
 
1415
    [];
 
1416
ossl_mod_get(Config) when is_list(Config) ->
 
1417
    ssl_mod_get(ossl, Config).
 
1418
 
 
1419
essl_mod_get(doc) ->
 
1420
    ["Module test: mod_get - using new of configure new SSL"];
 
1421
essl_mod_get(suite) ->
 
1422
    [];
 
1423
essl_mod_get(Config) when is_list(Config) ->
 
1424
    ssl_mod_get(essl, Config).
 
1425
 
 
1426
ssl_mod_get(Tag, Config) ->
 
1427
    httpd_mod:get(Tag, 
 
1428
                  ?SSL_PORT, 
 
1429
                  ?config(host, Config), 
 
1430
                  ?config(node, Config)),
 
1431
    ok.
 
1432
 
 
1433
 
 
1434
%%-------------------------------------------------------------------------
 
1435
 
 
1436
pssl_mod_head(doc) ->
 
1437
    ["Module test: mod_head - old SSL config"];
 
1438
pssl_mod_head(suite) ->
 
1439
    [];
 
1440
pssl_mod_head(Config) when is_list(Config) ->
 
1441
    ssl_mod_head(ssl, Config).
 
1442
 
 
1443
ossl_mod_head(doc) ->
 
1444
    ["Module test: mod_head - using new of configure old SSL"];
 
1445
ossl_mod_head(suite) ->
 
1446
    [];
 
1447
ossl_mod_head(Config) when is_list(Config) ->
 
1448
    ssl_mod_head(ossl, Config).
 
1449
 
 
1450
essl_mod_head(doc) ->
 
1451
    ["Module test: mod_head - using new of configure new SSL"];
 
1452
essl_mod_head(suite) ->
 
1453
    [];
 
1454
essl_mod_head(Config) when is_list(Config) ->
 
1455
    ssl_mod_head(essl, Config).
 
1456
 
 
1457
ssl_mod_head(Tag, Config) ->
 
1458
    httpd_mod:head(Tag, 
 
1459
                   ?SSL_PORT, 
 
1460
                   ?config(host, Config), 
 
1461
                   ?config(node, Config)),
 
1462
    ok.
 
1463
 
 
1464
 
 
1465
%%-------------------------------------------------------------------------
 
1466
 
 
1467
pssl_mod_all(doc) ->
 
1468
    ["All modules test - old SSL config"];
 
1469
pssl_mod_all(suite) ->
 
1470
    [];
 
1471
pssl_mod_all(Config) when is_list(Config) ->
 
1472
    ssl_mod_all(ssl, Config).
 
1473
 
 
1474
ossl_mod_all(doc) ->
 
1475
    ["All modules test - using new of configure old SSL"];
 
1476
ossl_mod_all(suite) ->
 
1477
    [];
 
1478
ossl_mod_all(Config) when is_list(Config) ->
 
1479
    ssl_mod_all(ossl, Config).
 
1480
 
 
1481
essl_mod_all(doc) ->
 
1482
    ["All modules test - using new of configure new SSL"];
 
1483
essl_mod_all(suite) ->
 
1484
    [];
 
1485
essl_mod_all(Config) when is_list(Config) ->
 
1486
    ssl_mod_all(essl, Config).
 
1487
 
 
1488
ssl_mod_all(Tag, Config) ->
 
1489
    httpd_mod:all(Tag, 
 
1490
                  ?SSL_PORT, 
 
1491
                  ?config(host, Config), 
 
1492
                  ?config(node, Config)),
 
1493
    ok.
 
1494
 
 
1495
 
 
1496
%%-------------------------------------------------------------------------
 
1497
 
 
1498
pssl_load_light(doc) ->
 
1499
    ["Test light load - old SSL config"];
 
1500
pssl_load_light(suite) ->
 
1501
    [];
 
1502
pssl_load_light(Config) when is_list(Config) ->
 
1503
    ssl_load_light(ssl, Config).
 
1504
 
 
1505
ossl_load_light(doc) ->
 
1506
    ["Test light load - using new of configure old SSL"];
 
1507
ossl_load_light(suite) ->
 
1508
    [];
 
1509
ossl_load_light(Config) when is_list(Config) ->
 
1510
    ssl_load_light(ossl, Config).
 
1511
 
 
1512
essl_load_light(doc) ->
 
1513
    ["Test light load - using new of configure new SSL"];
 
1514
essl_load_light(suite) ->
 
1515
    [];
 
1516
essl_load_light(Config) when is_list(Config) ->
 
1517
    ssl_load_light(essl, Config).
 
1518
 
 
1519
ssl_load_light(Tag, Config) ->
 
1520
    httpd_load:load_test(Tag, 
 
1521
                         ?SSL_PORT, 
 
1522
                         ?config(host, Config), 
 
1523
                         ?config(node, Config),
 
1524
                         get_nof_clients(ssl, light)),
 
1525
    ok.
 
1526
 
 
1527
 
 
1528
%%-------------------------------------------------------------------------
 
1529
 
 
1530
pssl_load_medium(doc) ->
 
1531
    ["Test medium load - old SSL config"];
 
1532
pssl_load_medium(suite) ->
 
1533
    [];
 
1534
pssl_load_medium(Config) when is_list(Config) ->
 
1535
    ssl_load_medium(ssl, Config).
 
1536
 
 
1537
ossl_load_medium(doc) ->
 
1538
    ["Test medium load - using new of configure old SSL"];
 
1539
ossl_load_medium(suite) ->
 
1540
    [];
 
1541
ossl_load_medium(Config) when is_list(Config) ->
 
1542
    ssl_load_medium(ossl, Config).
 
1543
 
 
1544
essl_load_medium(doc) ->
 
1545
    ["Test medium load - using new of configure new SSL"];
 
1546
essl_load_medium(suite) ->
 
1547
    [];
 
1548
essl_load_medium(Config) when is_list(Config) ->
 
1549
    ssl_load_medium(essl, Config).
 
1550
 
 
1551
ssl_load_medium(Tag, Config) ->
 
1552
    %% <CONDITIONAL-SKIP>
 
1553
    Skippable = [win32],
 
1554
    Condition = fun() -> ?OS_BASED_SKIP(Skippable) end,
 
1555
    ?NON_PC_TC_MAYBE_SKIP(Config, Condition),
 
1556
    %% </CONDITIONAL-SKIP>
 
1557
 
 
1558
    httpd_load:load_test(Tag, 
 
1559
                         ?SSL_PORT, 
 
1560
                         ?config(host, Config), 
 
1561
                         ?config(node, Config),
 
1562
                         get_nof_clients(ssl, medium)),
 
1563
    ok.
 
1564
 
 
1565
 
 
1566
%%-------------------------------------------------------------------------
 
1567
 
 
1568
pssl_load_heavy(doc) ->
 
1569
    ["Test heavy load - old SSL config"];
 
1570
pssl_load_heavy(suite) ->
 
1571
    [];
 
1572
pssl_load_heavy(Config) when is_list(Config) ->
 
1573
    ssl_load_heavy(ssl, Config).
 
1574
 
 
1575
ossl_load_heavy(doc) ->
 
1576
    ["Test heavy load - using new of configure old SSL"];
 
1577
ossl_load_heavy(suite) ->
 
1578
    [];
 
1579
ossl_load_heavy(Config) when is_list(Config) ->
 
1580
    ssl_load_heavy(ossl, Config).
 
1581
 
 
1582
essl_load_heavy(doc) ->
 
1583
    ["Test heavy load - using new of configure new SSL"];
 
1584
essl_load_heavy(suite) ->
 
1585
    [];
 
1586
essl_load_heavy(Config) when is_list(Config) ->
 
1587
    ssl_load_heavy(essl, Config).
 
1588
 
 
1589
ssl_load_heavy(Tag, Config) ->
 
1590
    %% <CONDITIONAL-SKIP>
 
1591
    Skippable = [win32],
 
1592
    Condition = fun() -> ?OS_BASED_SKIP(Skippable) end,
 
1593
    ?NON_PC_TC_MAYBE_SKIP(Config, Condition),
 
1594
    %% </CONDITIONAL-SKIP>
 
1595
 
 
1596
    httpd_load:load_test(Tag, 
 
1597
                         ?SSL_PORT, 
 
1598
                         ?config(host, Config), 
 
1599
                         ?config(node, Config),
 
1600
                         get_nof_clients(ssl, heavy)),
 
1601
    ok.
 
1602
 
 
1603
 
 
1604
%%-------------------------------------------------------------------------
 
1605
 
 
1606
pssl_dos_hostname(doc) ->
 
1607
    ["Denial Of Service (DOS) attack test case - old SSL config"];
 
1608
pssl_dos_hostname(suite) ->
 
1609
    [];
 
1610
pssl_dos_hostname(Config) when is_list(Config) ->
 
1611
    ssl_dos_hostname(ssl, Config).
 
1612
 
 
1613
ossl_dos_hostname(doc) ->
 
1614
    ["Denial Of Service (DOS) attack test case - using new of configure old SSL"];
 
1615
ossl_dos_hostname(suite) ->
 
1616
    [];
 
1617
ossl_dos_hostname(Config) when is_list(Config) ->
 
1618
    ssl_dos_hostname(ossl, Config).
 
1619
 
 
1620
essl_dos_hostname(doc) ->
 
1621
    ["Denial Of Service (DOS) attack test case - using new of configure new SSL"];
 
1622
essl_dos_hostname(suite) ->
 
1623
    [];
 
1624
essl_dos_hostname(Config) when is_list(Config) ->
 
1625
    ssl_dos_hostname(essl, Config).
 
1626
 
 
1627
ssl_dos_hostname(Tag, Config) ->
 
1628
    dos_hostname(Tag, 
 
1629
                 ?SSL_PORT, 
 
1630
                 ?config(host, Config), 
 
1631
                 ?config(node, Config), 
 
1632
                 ?MAX_HEADER_SIZE),
 
1633
    ok.
 
1634
 
 
1635
 
 
1636
%%-------------------------------------------------------------------------
 
1637
 
 
1638
pssl_time_test(doc) ->
 
1639
    ["old SSL config"];
 
1640
pssl_time_test(suite) ->
 
1641
    [];
 
1642
pssl_time_test(Config) when is_list(Config) ->
 
1643
    ssl_time_test(ssl, Config).
 
1644
 
 
1645
ossl_time_test(doc) ->
 
1646
    ["using new of configure old SSL"];
 
1647
ossl_time_test(suite) ->
 
1648
    [];
 
1649
ossl_time_test(Config) when is_list(Config) ->
 
1650
    ssl_time_test(ossl, Config).
 
1651
 
 
1652
essl_time_test(doc) ->
 
1653
    ["using new of configure new SSL"];
 
1654
essl_time_test(suite) ->
 
1655
    [];
 
1656
essl_time_test(Config) when is_list(Config) ->
 
1657
    ssl_time_test(essl, Config).
 
1658
 
 
1659
ssl_time_test(Tag, Config) when is_list(Config) ->
 
1660
    %% <CONDITIONAL-SKIP>
 
1661
    FreeBSDVersionVerify = 
 
1662
        fun() ->
 
1663
                case os:version() of
 
1664
                    {7, 1, _} -> % We only have one such machine, so...
 
1665
                        true;
 
1666
                    _ ->
 
1667
                        false
 
1668
                end
 
1669
        end,
 
1670
    Skippable = [win32, {unix, [{freebsd, FreeBSDVersionVerify}]}],
 
1671
    Condition = fun() -> ?OS_BASED_SKIP(Skippable) end,
 
1672
    ?NON_PC_TC_MAYBE_SKIP(Config, Condition),
 
1673
    %% </CONDITIONAL-SKIP>
 
1674
    
 
1675
    httpd_time_test:t(Tag, 
 
1676
                      ?config(host, Config), 
 
1677
                      ?SSL_PORT),
 
1678
    ok.
 
1679
 
 
1680
 
 
1681
%%-------------------------------------------------------------------------
 
1682
 
 
1683
pssl_block_503(doc) ->
 
1684
    ["Check that you will receive status code 503 when the server"
 
1685
     " is blocked and 200 when its not blocked - old SSL config."];
 
1686
pssl_block_503(suite) ->
 
1687
    [];
 
1688
pssl_block_503(Config) when is_list(Config) ->
 
1689
    ssl_block_503(ssl, Config).
 
1690
 
 
1691
ossl_block_503(doc) ->
 
1692
    ["Check that you will receive status code 503 when the server"
 
1693
     " is blocked and 200 when its not blocked - using new of configure old SSL."];
 
1694
ossl_block_503(suite) ->
 
1695
    [];
 
1696
ossl_block_503(Config) when is_list(Config) ->
 
1697
    ssl_block_503(ossl, Config).
 
1698
 
 
1699
essl_block_503(doc) ->
 
1700
    ["Check that you will receive status code 503 when the server"
 
1701
     " is blocked and 200 when its not blocked - using new of configure new SSL."];
 
1702
essl_block_503(suite) ->
 
1703
    [];
 
1704
essl_block_503(Config) when is_list(Config) ->
 
1705
    ssl_block_503(essl, Config).
 
1706
 
 
1707
ssl_block_503(Tag, Config) ->
 
1708
    httpd_block:block_503(Tag, 
 
1709
                          ?SSL_PORT, 
 
1710
                          ?config(host, Config), 
 
1711
                          ?config(node, Config)),
 
1712
    ok.
 
1713
 
 
1714
 
 
1715
%%-------------------------------------------------------------------------
 
1716
 
 
1717
pssl_block_disturbing_idle(doc) ->
 
1718
    ["Check that you can block/unblock an idle server. The strategy " 
 
1719
     "distribing does not really make a difference in this case." 
 
1720
     "Old SSL config"];
 
1721
pssl_block_disturbing_idle(suite) ->
 
1722
    [];
 
1723
pssl_block_disturbing_idle(Config) when is_list(Config) ->
 
1724
    ssl_block_disturbing_idle(ssl, Config).
 
1725
 
 
1726
ossl_block_disturbing_idle(doc) ->
 
1727
    ["Check that you can block/unblock an idle server. The strategy " 
 
1728
     "distribing does not really make a difference in this case." 
 
1729
     "Using new of configure old SSL"];
 
1730
ossl_block_disturbing_idle(suite) ->
 
1731
    [];
 
1732
ossl_block_disturbing_idle(Config) when is_list(Config) ->
 
1733
    ssl_block_disturbing_idle(ossl, Config).
 
1734
 
 
1735
essl_block_disturbing_idle(doc) ->
 
1736
    ["Check that you can block/unblock an idle server. The strategy " 
 
1737
     "distribing does not really make a difference in this case." 
 
1738
     "Using new of configure new SSL"];
 
1739
essl_block_disturbing_idle(suite) ->
 
1740
    [];
 
1741
essl_block_disturbing_idle(Config) when is_list(Config) ->
 
1742
    ssl_block_disturbing_idle(essl, Config).
 
1743
 
 
1744
ssl_block_disturbing_idle(Tag, Config) ->
 
1745
    httpd_block:block_disturbing_idle(Tag, 
 
1746
                                      ?SSL_PORT, 
 
1747
                                      ?config(host, Config), 
 
1748
                                      ?config(node, Config)),
 
1749
    ok.
 
1750
 
 
1751
 
 
1752
%%-------------------------------------------------------------------------
 
1753
 
 
1754
pssl_block_non_disturbing_idle(doc) ->
 
1755
    ["Check that you can block/unblock an idle server. The strategy " 
 
1756
     "non distribing does not really make a difference in this case." 
 
1757
     "Old SSL config"];
 
1758
pssl_block_non_disturbing_idle(suite) ->
 
1759
    [];
 
1760
pssl_block_non_disturbing_idle(Config) when is_list(Config) ->
 
1761
    ssl_block_non_disturbing_idle(ssl, Config).
 
1762
 
 
1763
ossl_block_non_disturbing_idle(doc) ->
 
1764
    ["Check that you can block/unblock an idle server. The strategy " 
 
1765
     "non distribing does not really make a difference in this case." 
 
1766
     "Using new of configure old SSL"];
 
1767
ossl_block_non_disturbing_idle(suite) ->
 
1768
    [];
 
1769
ossl_block_non_disturbing_idle(Config) when is_list(Config) ->
 
1770
    ssl_block_non_disturbing_idle(ossl, Config).
 
1771
 
 
1772
essl_block_non_disturbing_idle(doc) ->
 
1773
    ["Check that you can block/unblock an idle server. The strategy " 
 
1774
     "non distribing does not really make a difference in this case." 
 
1775
     "Using new of configure new SSL"];
 
1776
essl_block_non_disturbing_idle(suite) ->
 
1777
    [];
 
1778
essl_block_non_disturbing_idle(Config) when is_list(Config) ->
 
1779
    ssl_block_non_disturbing_idle(essl, Config).
 
1780
 
 
1781
ssl_block_non_disturbing_idle(Tag, Config) ->
 
1782
    httpd_block:block_non_disturbing_idle(Tag, 
 
1783
                                          ?SSL_PORT, 
 
1784
                                          ?config(host, Config), 
 
1785
                                          ?config(node, Config)),
 
1786
    ok.
 
1787
 
 
1788
 
 
1789
%%-------------------------------------------------------------------------
 
1790
 
 
1791
pssl_block_disturbing_active(doc) ->
 
1792
    ["Check that you can block/unblock an active server. The strategy " 
 
1793
     "distribing means ongoing requests should be terminated." 
 
1794
     "Old SSL config"];
 
1795
pssl_block_disturbing_active(suite) ->
 
1796
    [];
 
1797
pssl_block_disturbing_active(Config) when is_list(Config) ->
 
1798
    ssl_block_disturbing_active(ssl, Config).
 
1799
 
 
1800
ossl_block_disturbing_active(doc) ->
 
1801
    ["Check that you can block/unblock an active server. The strategy " 
 
1802
     "distribing means ongoing requests should be terminated." 
 
1803
     "Using new of configure old SSL"];
 
1804
ossl_block_disturbing_active(suite) ->
 
1805
    [];
 
1806
ossl_block_disturbing_active(Config) when is_list(Config) ->
 
1807
    ssl_block_disturbing_active(ossl, Config).
 
1808
 
 
1809
essl_block_disturbing_active(doc) ->
 
1810
    ["Check that you can block/unblock an active server. The strategy " 
 
1811
     "distribing means ongoing requests should be terminated." 
 
1812
     "Using new of configure new SSL"];
 
1813
essl_block_disturbing_active(suite) ->
 
1814
    [];
 
1815
essl_block_disturbing_active(Config) when is_list(Config) ->
 
1816
    ssl_block_disturbing_active(essl, Config).
 
1817
 
 
1818
ssl_block_disturbing_active(Tag, Config) ->
 
1819
    httpd_block:block_disturbing_active(Tag, 
 
1820
                                        ?SSL_PORT, 
 
1821
                                        ?config(host, Config), 
 
1822
                                        ?config(node, Config)),
 
1823
    ok.
 
1824
 
 
1825
 
 
1826
%%-------------------------------------------------------------------------
 
1827
 
 
1828
pssl_block_non_disturbing_active(doc) ->
 
1829
    ["Check that you can block/unblock an idle server. The strategy " 
 
1830
     "non distribing means the ongoing requests should be compleated." 
 
1831
     "Old SSL config"];
 
1832
pssl_block_non_disturbing_active(suite) ->
 
1833
    [];
 
1834
pssl_block_non_disturbing_active(Config) when is_list(Config) ->
 
1835
    ssl_block_non_disturbing_active(ssl, Config).
 
1836
 
 
1837
ossl_block_non_disturbing_active(doc) ->
 
1838
    ["Check that you can block/unblock an idle server. The strategy " 
 
1839
     "non distribing means the ongoing requests should be compleated." 
 
1840
     "Using new of configure old SSL"];
 
1841
ossl_block_non_disturbing_active(suite) ->
 
1842
    [];
 
1843
ossl_block_non_disturbing_active(Config) when is_list(Config) ->
 
1844
    ssl_block_non_disturbing_active(ossl, Config).
 
1845
 
 
1846
essl_block_non_disturbing_active(doc) ->
 
1847
    ["Check that you can block/unblock an idle server. The strategy " 
 
1848
     "non distribing means the ongoing requests should be compleated." 
 
1849
     "Using new of configure new SSL"];
 
1850
essl_block_non_disturbing_active(suite) ->
 
1851
    [];
 
1852
essl_block_non_disturbing_active(Config) when is_list(Config) ->
 
1853
    ssl_block_non_disturbing_active(essl, Config).
 
1854
 
 
1855
ssl_block_non_disturbing_active(Tag, Config) ->
 
1856
    httpd_block:block_non_disturbing_idle(Tag, 
 
1857
                                          ?SSL_PORT, 
 
1858
                                          ?config(host, Config), 
 
1859
                                          ?config(node, Config)),
 
1860
    ok.
 
1861
 
 
1862
 
 
1863
%%-------------------------------------------------------------------------
 
1864
 
 
1865
pssl_block_disturbing_active_timeout_not_released(doc) ->
 
1866
    ["Check that you can block an active server. The strategy " 
 
1867
     "distribing means ongoing requests should be compleated"
 
1868
     "if the timeout does not occur." 
 
1869
     "Old SSL config"];
 
1870
pssl_block_disturbing_active_timeout_not_released(suite) ->
 
1871
    [];
 
1872
pssl_block_disturbing_active_timeout_not_released(Config) 
 
1873
  when is_list(Config) ->
 
1874
    ssl_block_disturbing_active_timeout_not_released(ssl, Config).
 
1875
 
 
1876
ossl_block_disturbing_active_timeout_not_released(doc) ->
 
1877
    ["Check that you can block an active server. The strategy " 
 
1878
     "distribing means ongoing requests should be compleated"
 
1879
     "if the timeout does not occur." 
 
1880
    "Using new of configure old SSL"];
 
1881
ossl_block_disturbing_active_timeout_not_released(suite) ->
 
1882
    [];
 
1883
ossl_block_disturbing_active_timeout_not_released(Config) 
 
1884
  when is_list(Config) ->
 
1885
    ssl_block_disturbing_active_timeout_not_released(ossl, Config).
 
1886
 
 
1887
essl_block_disturbing_active_timeout_not_released(doc) ->
 
1888
    ["Check that you can block an active server. The strategy " 
 
1889
     "distribing means ongoing requests should be compleated"
 
1890
     "if the timeout does not occur." 
 
1891
    "Using new of configure new SSL"];
 
1892
essl_block_disturbing_active_timeout_not_released(suite) ->
 
1893
    [];
 
1894
essl_block_disturbing_active_timeout_not_released(Config) 
 
1895
  when is_list(Config) ->
 
1896
    ssl_block_disturbing_active_timeout_not_released(essl, Config).
 
1897
 
 
1898
ssl_block_disturbing_active_timeout_not_released(Tag, Config) ->
 
1899
    Port = ?SSL_PORT, 
 
1900
    Host = ?config(host, Config), 
 
1901
    Node = ?config(node, Config), 
 
1902
    httpd_block:block_disturbing_active_timeout_not_released(Tag, 
 
1903
                                                             Port, Host, Node),
 
1904
    ok.
 
1905
 
 
1906
 
 
1907
%%-------------------------------------------------------------------------
 
1908
 
 
1909
pssl_block_disturbing_active_timeout_released(doc) ->
 
1910
    ["Check that you can block an active server. The strategy " 
 
1911
     "distribing means ongoing requests should be terminated when"
 
1912
     "the timeout occurs." 
 
1913
     "Old SSL config"];
 
1914
pssl_block_disturbing_active_timeout_released(suite) ->
 
1915
    [];
 
1916
pssl_block_disturbing_active_timeout_released(Config) 
 
1917
  when is_list(Config) ->
 
1918
    ssl_block_disturbing_active_timeout_released(ssl, Config).
 
1919
 
 
1920
ossl_block_disturbing_active_timeout_released(doc) ->
 
1921
    ["Check that you can block an active server. The strategy " 
 
1922
     "distribing means ongoing requests should be terminated when"
 
1923
     "the timeout occurs." 
 
1924
    "Using new of configure old SSL"];
 
1925
ossl_block_disturbing_active_timeout_released(suite) ->
 
1926
    [];
 
1927
ossl_block_disturbing_active_timeout_released(Config) 
 
1928
  when is_list(Config) ->
 
1929
    ssl_block_disturbing_active_timeout_released(ossl, Config).
 
1930
 
 
1931
essl_block_disturbing_active_timeout_released(doc) ->
 
1932
    ["Check that you can block an active server. The strategy " 
 
1933
     "distribing means ongoing requests should be terminated when"
 
1934
     "the timeout occurs." 
 
1935
    "Using new of configure new SSL"];
 
1936
essl_block_disturbing_active_timeout_released(suite) ->
 
1937
    [];
 
1938
essl_block_disturbing_active_timeout_released(Config) 
 
1939
  when is_list(Config) ->
 
1940
    ssl_block_disturbing_active_timeout_released(essl, Config).
 
1941
 
 
1942
ssl_block_disturbing_active_timeout_released(Tag, Config) ->
 
1943
    Port = ?SSL_PORT, 
 
1944
    Host = ?config(host, Config), 
 
1945
    Node = ?config(node, Config),     
 
1946
    httpd_block:block_disturbing_active_timeout_released(Tag, 
 
1947
                                                         Port, 
 
1948
                                                         Host, 
 
1949
                                                         Node), 
 
1950
    ok.
 
1951
 
 
1952
 
 
1953
%%-------------------------------------------------------------------------
 
1954
 
 
1955
pssl_block_non_disturbing_active_timeout_not_released(doc) ->
 
1956
    ["Check that you can block an active server. The strategy " 
 
1957
     "non non distribing means ongoing requests should be completed." 
 
1958
     "Old SSL config"];
 
1959
pssl_block_non_disturbing_active_timeout_not_released(suite) ->
 
1960
    [];
 
1961
pssl_block_non_disturbing_active_timeout_not_released(Config)
 
1962
  when is_list(Config) ->
 
1963
    ssl_block_non_disturbing_active_timeout_not_released(ssl, Config).
 
1964
 
 
1965
ossl_block_non_disturbing_active_timeout_not_released(doc) ->
 
1966
    ["Check that you can block an active server. The strategy " 
 
1967
     "non non distribing means ongoing requests should be completed." 
 
1968
    "Using new of configure old SSL"];
 
1969
ossl_block_non_disturbing_active_timeout_not_released(suite) ->
 
1970
    [];
 
1971
ossl_block_non_disturbing_active_timeout_not_released(Config)
 
1972
  when is_list(Config) ->
 
1973
    ssl_block_non_disturbing_active_timeout_not_released(ossl, Config).
 
1974
 
 
1975
essl_block_non_disturbing_active_timeout_not_released(doc) ->
 
1976
    ["Check that you can block an active server. The strategy " 
 
1977
     "non non distribing means ongoing requests should be completed." 
 
1978
    "Using new of configure new SSL"];
 
1979
essl_block_non_disturbing_active_timeout_not_released(suite) ->
 
1980
    [];
 
1981
essl_block_non_disturbing_active_timeout_not_released(Config)
 
1982
  when is_list(Config) ->
 
1983
    ssl_block_non_disturbing_active_timeout_not_released(essl, Config).
 
1984
 
 
1985
ssl_block_non_disturbing_active_timeout_not_released(Tag, Config) ->
 
1986
    Port = ?SSL_PORT, 
 
1987
    Host = ?config(host, Config), 
 
1988
    Node = ?config(node, Config), 
 
1989
    httpd_block:block_non_disturbing_active_timeout_not_released(Tag,
 
1990
                                                                 Port, 
 
1991
                                                                 Host, 
 
1992
                                                                 Node),
 
1993
    ok.
 
1994
 
 
1995
 
 
1996
%%-------------------------------------------------------------------------
 
1997
 
 
1998
pssl_block_non_disturbing_active_timeout_released(doc) ->
 
1999
    ["Check that you can block an active server. The strategy " 
 
2000
     "non distribing means ongoing requests should be completed. "
 
2001
     "When the timeout occurs the block operation sohould be canceled." 
 
2002
     "Old SSL config"];
 
2003
pssl_block_non_disturbing_active_timeout_released(suite) ->
 
2004
    [];
 
2005
pssl_block_non_disturbing_active_timeout_released(Config)
 
2006
  when is_list(Config) ->
 
2007
    ssl_block_non_disturbing_active_timeout_released(ssl, Config).
 
2008
 
 
2009
ossl_block_non_disturbing_active_timeout_released(doc) ->
 
2010
    ["Check that you can block an active server. The strategy " 
 
2011
     "non distribing means ongoing requests should be completed. "
 
2012
     "When the timeout occurs the block operation sohould be canceled." 
 
2013
     "Using new of configure old SSL"];
 
2014
ossl_block_non_disturbing_active_timeout_released(suite) ->
 
2015
    [];
 
2016
ossl_block_non_disturbing_active_timeout_released(Config)
 
2017
  when is_list(Config) ->
 
2018
    ssl_block_non_disturbing_active_timeout_released(ossl, Config).
 
2019
 
 
2020
essl_block_non_disturbing_active_timeout_released(doc) ->
 
2021
    ["Check that you can block an active server. The strategy " 
 
2022
     "non distribing means ongoing requests should be completed. "
 
2023
     "When the timeout occurs the block operation sohould be canceled." 
 
2024
     "Using new of configure new SSL"];
 
2025
essl_block_non_disturbing_active_timeout_released(suite) ->
 
2026
    [];
 
2027
essl_block_non_disturbing_active_timeout_released(Config)
 
2028
  when is_list(Config) ->
 
2029
    ssl_block_non_disturbing_active_timeout_released(essl, Config).
 
2030
 
 
2031
ssl_block_non_disturbing_active_timeout_released(Tag, Config)
 
2032
  when is_list(Config) ->
 
2033
    Port = ?SSL_PORT, 
 
2034
    Host = ?config(host, Config), 
 
2035
    Node = ?config(node, Config), 
 
2036
    httpd_block:block_non_disturbing_active_timeout_released(Tag, 
 
2037
                                                             Port, 
 
2038
                                                             Host, 
 
2039
                                                             Node), 
 
2040
 
 
2041
    ok.
 
2042
 
 
2043
 
 
2044
%%-------------------------------------------------------------------------
 
2045
 
 
2046
pssl_block_disturbing_blocker_dies(doc) ->
 
2047
    ["old SSL config"];
 
2048
pssl_block_disturbing_blocker_dies(suite) ->
 
2049
    [];
 
2050
pssl_block_disturbing_blocker_dies(Config) when is_list(Config) ->
 
2051
    ssl_block_disturbing_blocker_dies(ssl, Config).
 
2052
 
 
2053
ossl_block_disturbing_blocker_dies(doc) ->
 
2054
    ["using new of configure old SSL"];
 
2055
ossl_block_disturbing_blocker_dies(suite) ->
 
2056
    [];
 
2057
ossl_block_disturbing_blocker_dies(Config) when is_list(Config) ->
 
2058
    ssl_block_disturbing_blocker_dies(ossl, Config).
 
2059
 
 
2060
essl_block_disturbing_blocker_dies(doc) ->
 
2061
    ["using new of configure new SSL"];
 
2062
essl_block_disturbing_blocker_dies(suite) ->
 
2063
    [];
 
2064
essl_block_disturbing_blocker_dies(Config) when is_list(Config) ->
 
2065
    ssl_block_disturbing_blocker_dies(essl, Config).
 
2066
 
 
2067
ssl_block_disturbing_blocker_dies(Tag, Config) ->
 
2068
    httpd_block:disturbing_blocker_dies(Tag, 
 
2069
                                        ?SSL_PORT, 
 
2070
                                        ?config(host, Config), 
 
2071
                                        ?config(node, Config)),
 
2072
    ok.
 
2073
 
 
2074
 
 
2075
%%-------------------------------------------------------------------------
 
2076
 
 
2077
pssl_block_non_disturbing_blocker_dies(doc) ->
 
2078
    ["old SSL config"];
 
2079
pssl_block_non_disturbing_blocker_dies(suite) ->
 
2080
    [];
 
2081
pssl_block_non_disturbing_blocker_dies(Config) when is_list(Config) ->
 
2082
    ssl_block_non_disturbing_blocker_dies(ssl, Config).
 
2083
 
 
2084
ossl_block_non_disturbing_blocker_dies(doc) ->
 
2085
    ["using new of configure old SSL"];
 
2086
ossl_block_non_disturbing_blocker_dies(suite) ->
 
2087
    [];
 
2088
ossl_block_non_disturbing_blocker_dies(Config) when is_list(Config) ->
 
2089
    ssl_block_non_disturbing_blocker_dies(ossl, Config).
 
2090
 
 
2091
essl_block_non_disturbing_blocker_dies(doc) ->
 
2092
    ["using new of configure new SSL"];
 
2093
essl_block_non_disturbing_blocker_dies(suite) ->
 
2094
    [];
 
2095
essl_block_non_disturbing_blocker_dies(Config) when is_list(Config) ->
 
2096
    ssl_block_non_disturbing_blocker_dies(essl, Config).
 
2097
 
 
2098
ssl_block_non_disturbing_blocker_dies(Tag, Config) ->
 
2099
    httpd_block:non_disturbing_blocker_dies(Tag, 
 
2100
                                            ?SSL_PORT, 
 
2101
                                            ?config(host, Config), 
 
2102
                                            ?config(node, Config)),
 
2103
    ok.
 
2104
 
 
2105
 
 
2106
%%-------------------------------------------------------------------------
 
2107
 
 
2108
pssl_restart_no_block(doc) ->
 
2109
    ["old SSL config"];
 
2110
pssl_restart_no_block(suite) ->
 
2111
    [];
 
2112
pssl_restart_no_block(Config) when is_list(Config) ->
 
2113
    ssl_restart_no_block(ssl, Config).
 
2114
 
 
2115
ossl_restart_no_block(doc) ->
 
2116
    ["using new of configure old SSL"];
 
2117
ossl_restart_no_block(suite) ->
 
2118
    [];
 
2119
ossl_restart_no_block(Config) when is_list(Config) ->
 
2120
    ssl_restart_no_block(ossl, Config).
 
2121
 
 
2122
essl_restart_no_block(doc) ->
 
2123
    ["using new of configure new SSL"];
 
2124
essl_restart_no_block(suite) ->
 
2125
    [];
 
2126
essl_restart_no_block(Config) when is_list(Config) ->
 
2127
    ssl_restart_no_block(essl, Config).
 
2128
 
 
2129
ssl_restart_no_block(Tag, Config) ->
 
2130
    httpd_block:restart_no_block(Tag, 
 
2131
                                 ?SSL_PORT, 
 
2132
                                 ?config(host, Config), 
 
2133
                                 ?config(node, Config)),
 
2134
    ok.
 
2135
 
 
2136
 
 
2137
%%-------------------------------------------------------------------------
 
2138
 
 
2139
pssl_restart_disturbing_block(doc) ->
 
2140
    ["old SSL config"];
 
2141
pssl_restart_disturbing_block(suite) ->
 
2142
    [];
 
2143
pssl_restart_disturbing_block(Config) when is_list(Config) ->
 
2144
    ssl_restart_disturbing_block(ssl, Config).
 
2145
 
 
2146
ossl_restart_disturbing_block(doc) ->
 
2147
    ["using new of configure old SSL"];
 
2148
ossl_restart_disturbing_block(suite) ->
 
2149
    [];
 
2150
ossl_restart_disturbing_block(Config) when is_list(Config) ->
 
2151
    ssl_restart_disturbing_block(ossl, Config).
 
2152
 
 
2153
essl_restart_disturbing_block(doc) ->
 
2154
    ["using new of configure new SSL"];
 
2155
essl_restart_disturbing_block(suite) ->
 
2156
    [];
 
2157
essl_restart_disturbing_block(Config) when is_list(Config) ->
 
2158
    ssl_restart_disturbing_block(essl, Config).
 
2159
 
 
2160
ssl_restart_disturbing_block(Tag, Config) ->
 
2161
    %% <CONDITIONAL-SKIP>
 
2162
    Condition = 
 
2163
        fun() -> 
 
2164
                case os:type() of
 
2165
                    {unix, linux} ->
 
2166
                        case ?OSCMD("uname -m") of
 
2167
                            "ppc" ->
 
2168
                                case file:read_file_info("/etc/fedora-release") of
 
2169
                                    {ok, _} ->
 
2170
                                        case ?OSCMD("awk '{print $2}' /etc/fedora-release") of
 
2171
                                            "release" ->
 
2172
                                                %% Fedora 7 and later
 
2173
                                                case ?OSCMD("awk '{print $3}' /etc/fedora-release") of
 
2174
                                                    "7" ->
 
2175
                                                        true;
 
2176
                                                    _ ->
 
2177
                                                        false
 
2178
                                                end;
 
2179
                                            _ ->
 
2180
                                                false
 
2181
                                        end;
 
2182
                                    _ ->
 
2183
                                        false
 
2184
                                end;
 
2185
                            _ ->
 
2186
                                false
 
2187
                        end;
 
2188
                    _ ->
 
2189
                        false
 
2190
                end
 
2191
        end,
 
2192
    ?NON_PC_TC_MAYBE_SKIP(Config, Condition),
 
2193
    %% </CONDITIONAL-SKIP>
 
2194
 
 
2195
    httpd_block:restart_disturbing_block(Tag, ?SSL_PORT, 
 
2196
                                         ?config(host, Config), 
 
2197
                                         ?config(node, Config)),
 
2198
    ok.
 
2199
 
 
2200
 
 
2201
%%-------------------------------------------------------------------------
 
2202
 
 
2203
pssl_restart_non_disturbing_block(doc) ->
 
2204
    ["old SSL config"];
 
2205
pssl_restart_non_disturbing_block(suite) ->
 
2206
    [];
 
2207
pssl_restart_non_disturbing_block(Config) when is_list(Config) ->
 
2208
    ssl_restart_non_disturbing_block(ssl, Config).
 
2209
 
 
2210
ossl_restart_non_disturbing_block(doc) ->
 
2211
    ["using new of configure old SSL"];
 
2212
ossl_restart_non_disturbing_block(suite) ->
 
2213
    [];
 
2214
ossl_restart_non_disturbing_block(Config) when is_list(Config) ->
 
2215
    ssl_restart_non_disturbing_block(ossl, Config).
 
2216
 
 
2217
essl_restart_non_disturbing_block(doc) ->
 
2218
    ["using new of configure new SSL"];
 
2219
essl_restart_non_disturbing_block(suite) ->
 
2220
    [];
 
2221
essl_restart_non_disturbing_block(Config) when is_list(Config) ->
 
2222
    ssl_restart_non_disturbing_block(essl, Config).
 
2223
 
 
2224
ssl_restart_non_disturbing_block(Tag, Config) ->
 
2225
    %% <CONDITIONAL-SKIP>
 
2226
    Condition = 
 
2227
        fun() -> 
 
2228
                case os:type() of
 
2229
                    {unix, linux} ->
 
2230
                        HW = string:strip(os:cmd("uname -m"), right, $\n),
 
2231
                        case HW of
 
2232
                            "ppc" ->
 
2233
                                case inet:gethostname() of
 
2234
                                    {ok, "peach"} ->
 
2235
                                        true;
 
2236
                                    _ ->
 
2237
                                        false
 
2238
                                end;
 
2239
                            _ ->
 
2240
                                false
 
2241
                        end;
 
2242
                    _ ->
 
2243
                        false
 
2244
                end
 
2245
        end,
 
2246
    ?NON_PC_TC_MAYBE_SKIP(Config, Condition),
 
2247
    %% </CONDITIONAL-SKIP>
 
2248
 
 
2249
    httpd_block:restart_non_disturbing_block(Tag, 
 
2250
                                             ?SSL_PORT, 
 
2251
                                             ?config(host, Config), 
 
2252
                                             ?config(node, Config)),
 
2253
    ok.
 
2254
 
 
2255
 
 
2256
%%-------------------------------------------------------------------------
 
2257
ip_host(doc) ->   
 
2258
    ["Control that the server accepts/rejects requests with/ without host"];
 
2259
ip_host(suite)->
 
2260
    [];
 
2261
ip_host(Config) when is_list(Config) ->
 
2262
    httpd_1_1:host(ip_comm, ?IP_PORT, ?config(host, Config),
 
2263
                   ?config(node, Config)),
 
2264
    ok.
 
2265
%%------------------------------------------------------------------------- 
 
2266
ip_chunked(doc) ->   
 
2267
    ["Control that the server accepts chunked requests"];
 
2268
ip_chunked(suite) ->
 
2269
    [];
 
2270
ip_chunked(Config) when is_list(Config) ->
 
2271
    httpd_1_1:chunked(ip_comm, ?IP_PORT, ?config(host, Config),
 
2272
                      ?config(node, Config)),
 
2273
    ok.
 
2274
%%------------------------------------------------------------------------- 
 
2275
ip_expect(doc) ->   
 
2276
    ["Control that the server handles request with the expect header "
 
2277
     "field appropiate"];
 
2278
ip_expect(suite)->
 
2279
    [];
 
2280
ip_expect(Config) when is_list(Config) ->
 
2281
    httpd_1_1:expect(ip_comm, ?IP_PORT, ?config(host, Config),
 
2282
                     ?config(node, Config)),
 
2283
    ok.
 
2284
%%------------------------------------------------------------------------- 
 
2285
ip_range(doc) ->   
 
2286
    ["Control that the server can handle range requests to plain files"];
 
2287
ip_range(suite)->
 
2288
    [];
 
2289
ip_range(Config) when is_list(Config) ->
 
2290
    httpd_1_1:range(ip_comm, ?IP_PORT, ?config(host, Config),
 
2291
                    ?config(node, Config)),
 
2292
    ok.
 
2293
%%------------------------------------------------------------------------- 
 
2294
ip_if_test(doc) ->   
 
2295
    ["Test that the if - request header fields is handled correclty"];
 
2296
ip_if_test(suite) ->
 
2297
    [];
 
2298
ip_if_test(Config) when is_list(Config) ->
 
2299
    ServerRoot = ?config(server_root, Config), 
 
2300
    DocRoot = filename:join([ServerRoot, "htdocs"]),
 
2301
    httpd_1_1:if_test(ip_comm, ?IP_PORT, ?config(host, Config),
 
2302
                      ?config(node, Config), DocRoot),
 
2303
    ok.
 
2304
%%------------------------------------------------------------------------- 
 
2305
ip_http_trace(doc) ->   
 
2306
    ["Test the trace module "];
 
2307
ip_http_trace(suite) -> 
 
2308
    [];
 
2309
ip_http_trace(Config) when is_list(Config) ->
 
2310
    httpd_1_1:http_trace(ip_comm, ?IP_PORT, ?config(host, Config),
 
2311
                         ?config(node, Config)),
 
2312
    ok.
 
2313
%%------------------------------------------------------------------------- 
 
2314
ip_http1_1_head(doc) ->  
 
2315
    ["Test the trace module "];
 
2316
ip_http1_1_head(suite)->
 
2317
    [];
 
2318
ip_http1_1_head(Config) when is_list(Config) ->
 
2319
    httpd_1_1:head(ip_comm, ?IP_PORT, ?config(host, Config),
 
2320
                           ?config(node, Config)),
 
2321
    ok.
 
2322
 
 
2323
%%------------------------------------------------------------------------- 
 
2324
ip_get_0_9(doc) ->  
 
2325
    ["Test simple HTTP/0.9 GET"];
 
2326
ip_get_0_9(suite)->
 
2327
    [];
 
2328
ip_get_0_9(Config) when is_list(Config) ->
 
2329
    Host =  ?config(host, Config),
 
2330
    Node =  ?config(node, Config),
 
2331
    ok = httpd_test_lib:verify_request(ip_comm, Host, ?IP_PORT, Node, 
 
2332
                                       "GET / \r\n\r\n", 
 
2333
                                       [{statuscode, 200},
 
2334
                                        {version, "HTTP/0.9"} ]),
 
2335
    %% Without space after uri
 
2336
    ok = httpd_test_lib:verify_request(ip_comm, Host, ?IP_PORT, Node, 
 
2337
                                       "GET /\r\n\r\n", 
 
2338
                                       [{statuscode, 200},
 
2339
                                        {version, "HTTP/0.9"} ]),
 
2340
    ok = httpd_test_lib:verify_request(ip_comm, Host, ?IP_PORT, Node, 
 
2341
                                       "GET / HTTP/0.9\r\n\r\n", 
 
2342
                                       [{statuscode, 200},
 
2343
                                        {version, "HTTP/0.9"}]),
 
2344
    
 
2345
    ok.
 
2346
%%------------------------------------------------------------------------- 
 
2347
ip_head_1_0(doc) ->  
 
2348
    ["Test HTTP/1.0 HEAD"];
 
2349
ip_head_1_0(suite)->
 
2350
    [];
 
2351
ip_head_1_0(Config) when is_list(Config) ->
 
2352
    Host =  ?config(host, Config),
 
2353
    Node =  ?config(node, Config),
 
2354
    ok = httpd_test_lib:verify_request(ip_comm, Host, ?IP_PORT, Node, 
 
2355
                         "HEAD / HTTP/1.0\r\n\r\n", [{statuscode, 200},
 
2356
                                                    {version, "HTTP/1.0"}]),
 
2357
    
 
2358
    ok.
 
2359
%%------------------------------------------------------------------------- 
 
2360
ip_get_1_0(doc) ->  
 
2361
    ["Test HTTP/1.0 GET"];
 
2362
ip_get_1_0(suite)->
 
2363
    [];
 
2364
ip_get_1_0(Config) when is_list(Config) ->
 
2365
    Host =  ?config(host, Config),
 
2366
    Node =  ?config(node, Config),
 
2367
    ok = httpd_test_lib:verify_request(ip_comm, Host, ?IP_PORT, Node, 
 
2368
                         "GET / HTTP/1.0\r\n\r\n", [{statuscode, 200},
 
2369
                                                    {version, "HTTP/1.0"}]),
 
2370
    
 
2371
    ok.
 
2372
%%------------------------------------------------------------------------- 
 
2373
ip_post_1_0(doc) ->  
 
2374
    ["Test HTTP/1.0 POST"];
 
2375
ip_post_1_0(suite)->
 
2376
    [];
 
2377
ip_post_1_0(Config) when is_list(Config) ->
 
2378
    Host =  ?config(host, Config),
 
2379
    Node =  ?config(node, Config),
 
2380
    %% Test the post message formatin 1.0! Real post are testes elsewhere
 
2381
    ok = httpd_test_lib:verify_request(ip_comm, Host, ?IP_PORT, Node, 
 
2382
                         "POST / HTTP/1.0\r\n\r\n "  
 
2383
                         "Content-Length:6 \r\n\r\nfoobar", 
 
2384
                         [{statuscode, 500}, {version, "HTTP/1.0"}]),
 
2385
    
 
2386
    ok.
 
2387
%%------------------------------------------------------------------------- 
 
2388
ip_mod_cgi_chunked_encoding_test(doc) ->  
 
2389
    ["Test the trace module "];
 
2390
ip_mod_cgi_chunked_encoding_test(suite)->
 
2391
    [];
 
2392
ip_mod_cgi_chunked_encoding_test(Config) when is_list(Config) ->
 
2393
    Host = ?config(host, Config),
 
2394
    Script =
 
2395
        case test_server:os_type() of
 
2396
            {win32, _} ->
 
2397
                "/cgi-bin/printenv.bat";
 
2398
            _ ->
 
2399
                "/cgi-bin/printenv.sh"
 
2400
        end,
 
2401
    Requests = 
 
2402
        ["GET " ++ Script ++ " HTTP/1.1\r\nHost:"++ Host ++"\r\n\r\n",
 
2403
         "GET /cgi-bin/erl/httpd_example/newformat  HTTP/1.1\r\nHost:"
 
2404
         ++ Host ++"\r\n\r\n"],
 
2405
    httpd_1_1:mod_cgi_chunked_encoding_test(ip_comm, ?IP_PORT,
 
2406
                                            Host,
 
2407
                                            ?config(node, Config),
 
2408
                                            Requests),
 
2409
    ok.
 
2410
 
 
2411
%------------------------------------------------------------------------- 
 
2412
ipv6_hostname(doc) ->  
 
2413
    ["Test standard ipv6 address"];
 
2414
ipv6_hostname(suite)->
 
2415
    [];
 
2416
ipv6_hostname(Config) when is_list(Config) -> 
 
2417
    Host = ?config(host, Config),
 
2418
    httpd_test_lib:verify_request(ip_comm, Host, ?IP_PORT, node(), 
 
2419
                                  "GET / HTTP/1.1\r\n\r\n",
 
2420
                                  [{statuscode, 200},
 
2421
                                   {version, "HTTP/1.1"}]),
 
2422
    ok.
 
2423
 
 
2424
%%------------------------------------------------------------------------- 
 
2425
ipv6_address(doc) ->  
 
2426
    ["Test standard ipv6 address"];
 
2427
ipv6_address(suite)->
 
2428
    [];
 
2429
ipv6_address(Config) when is_list(Config) ->   
 
2430
    httpd_test_lib:verify_request(ip_comm, ?IPV6_LOCAL_HOST, ?IP_PORT, 
 
2431
                                  node(), "GET / HTTP/1.1\r\n\r\n",
 
2432
                                  [{statuscode, 200},
 
2433
                                   {version, "HTTP/1.1"}]),
 
2434
    ok.
 
2435
 
 
2436
%%--------------------------------------------------------------------
 
2437
ticket_5775(doc) ->
 
2438
    ["Tests that content-length is correct"];
 
2439
ticket_5775(suite) ->
 
2440
    [];
 
2441
ticket_5775(Config) ->
 
2442
    ok=httpd_test_lib:verify_request(ip_comm, ?config(host, Config),
 
2443
                                     ?IP_PORT, ?config(node, Config),
 
2444
                                       "GET /cgi-bin/erl/httpd_example:get_bin "
 
2445
                                       "HTTP/1.0\r\n\r\n", 
 
2446
                                       [{statuscode, 200},
 
2447
                                       {version, "HTTP/1.0"}]),
 
2448
    ok.
 
2449
ticket_5865(doc) ->
 
2450
    ["Tests that a header without last-modified is handled"];
 
2451
ticket_5865(suite) ->
 
2452
    [];
 
2453
ticket_5865(Config) ->
 
2454
    Host = ?config(host,Config),
 
2455
    ServerRoot = ?config(server_root, Config), 
 
2456
    DocRoot = filename:join([ServerRoot, "htdocs"]),
 
2457
    File = filename:join([DocRoot,"last_modified.html"]),
 
2458
 
 
2459
    Bad_mtime = case test_server:os_type() of
 
2460
                    {win32, _} ->
 
2461
                        {{1600,12,31},{23,59,59}};
 
2462
                    {unix, _} ->
 
2463
                        {{1969,12,31},{23,59,59}}
 
2464
                end,
 
2465
    
 
2466
    {ok,FI}=file:read_file_info(File),
 
2467
    
 
2468
    case file:write_file_info(File,FI#file_info{mtime=Bad_mtime}) of
 
2469
        ok ->
 
2470
            ok = httpd_test_lib:verify_request(ip_comm, Host,
 
2471
                                               ?IP_PORT, ?config(node, Config),
 
2472
                                               "GET /last_modified.html"
 
2473
                                               " HTTP/1.1\r\nHost:"
 
2474
                                               ++Host++"\r\n\r\n", 
 
2475
                                               [{statuscode, 200},
 
2476
                                                {no_last_modified,
 
2477
                                                 "last-modified"}]),
 
2478
            ok;
 
2479
        {error, Reason} ->
 
2480
            Fault = 
 
2481
                io_lib:format("Attempt to change the file info to set the"
 
2482
                              " preconditions of the test case failed ~p~n",
 
2483
                              [Reason]),
 
2484
            {skip, Fault}
 
2485
    end.
 
2486
 
 
2487
ticket_5913(doc) ->
 
2488
    ["Tests that a header without last-modified is handled"];
 
2489
ticket_5913(suite) -> [];
 
2490
ticket_5913(Config) ->
 
2491
    ok=httpd_test_lib:verify_request(ip_comm, ?config(host, Config),
 
2492
                                     ?IP_PORT, ?config(node, Config),
 
2493
                                       "GET /cgi-bin/erl/httpd_example:get_bin "
 
2494
                                       "HTTP/1.0\r\n\r\n", 
 
2495
                                       [{statuscode, 200},
 
2496
                                       {version, "HTTP/1.0"}]),
 
2497
    ok.
 
2498
 
 
2499
ticket_6003(doc) ->
 
2500
    ["Tests that a URI with a bad hexadecimal code is handled"];
 
2501
ticket_6003(suite) -> [];
 
2502
ticket_6003(Config) ->
 
2503
    ok=httpd_test_lib:verify_request(ip_comm, ?config(host, Config),
 
2504
                                     ?IP_PORT, ?config(node, Config),
 
2505
                                     "GET http://www.erlang.org/%skalle "
 
2506
                                     "HTTP/1.0\r\n\r\n",
 
2507
                                     [{statuscode, 400},
 
2508
                                      {version, "HTTP/1.0"}]),
 
2509
    ok.
 
2510
 
 
2511
ticket_7304(doc) ->
 
2512
     ["Tests missing CR in delimiter"];
 
2513
ticket_7304(suite) -> 
 
2514
    [];
 
2515
ticket_7304(Config) ->
 
2516
    ok = httpd_test_lib:verify_request(ip_comm, ?config(host, Config),
 
2517
                                       ?IP_PORT, ?config(node, Config),
 
2518
                                       "GET / HTTP/1.0\r\n\n",
 
2519
                                       [{statuscode, 200},
 
2520
                                        {version, "HTTP/1.0"}]),
 
2521
    ok.
 
2522
 
 
2523
%%--------------------------------------------------------------------
 
2524
%% Internal functions
 
2525
%%--------------------------------------------------------------------
 
2526
dos_hostname(Type, Port, Host, Node, Max) ->
 
2527
    H1 = {"", 200},
 
2528
    H2 = {"dummy-host.ericsson.se", 200},
 
2529
    TooLongHeader = lists:append(lists:duplicate(Max + 1, "a")),
 
2530
    H3 = {TooLongHeader, 403},
 
2531
    Hosts = [H1,H2,H3],
 
2532
    dos_hostname_poll(Type, Host, Port, Node, Hosts).
 
2533
 
 
2534
%% make_ipv6(T) when is_tuple(T) andalso (size(T) =:= 8) ->
 
2535
%%     make_ipv6(tuple_to_list(T));
 
2536
 
 
2537
%% make_ipv6([_, _, _, _, _, _, _, _] = IPV6) ->
 
2538
%%     lists:flatten(io_lib:format("~s:~s:~s:~s:~s:~s:~s:~s", IPV6)).
 
2539
 
 
2540
 
 
2541
%%--------------------------------------------------------------------
 
2542
%% Other help functions
 
2543
create_config(Config, Access, FileName) ->
 
2544
    ServerRoot = ?config(server_root, Config),
 
2545
    TcTopDir   = ?config(tc_top_dir,  Config),
 
2546
    Port       = ?config(port,        Config),
 
2547
    Type       = ?config(sock_type,   Config),
 
2548
    Host       = ?config(host,        Config),
 
2549
    Mods       = io_lib:format("~p", [httpd_mod]),
 
2550
    Funcs      = io_lib:format("~p", [ssl_password_cb]),
 
2551
    MaxHdrSz   = io_lib:format("~p", [256]),
 
2552
    MaxHdrAct  = io_lib:format("~p", [close]),
 
2553
 
 
2554
    io:format(user, 
 
2555
              "create_config -> "
 
2556
              "~n   ServerRoot: ~p"
 
2557
              "~n   TcTopDir:   ~p"
 
2558
              "~n   Type:       ~p"
 
2559
              "~n   Port:       ~p"
 
2560
              "~n   Host:       ~p"
 
2561
              "~n", [ServerRoot, TcTopDir, Port, Type, Host]),
 
2562
 
 
2563
    SSL =
 
2564
        if
 
2565
            (Type =:= ssl)  orelse 
 
2566
            (Type =:= ossl) orelse 
 
2567
            (Type =:= essl) ->
 
2568
                [cline(["SSLCertificateFile ", 
 
2569
                        filename:join(ServerRoot, "ssl/ssl_server.pem")]),
 
2570
                 cline(["SSLCertificateKeyFile ",
 
2571
                        filename:join(ServerRoot, "ssl/ssl_server.pem")]),
 
2572
                 cline(["SSLCACertificateFile ",
 
2573
                        filename:join(ServerRoot, "ssl/ssl_server.pem")]),
 
2574
                 cline(["SSLPasswordCallbackModule ", Mods]),
 
2575
                 cline(["SSLPasswordCallbackFunction ", Funcs]),
 
2576
                 cline(["SSLVerifyClient 0"]),
 
2577
                 cline(["SSLVerifyDepth 1"])];
 
2578
            true ->
 
2579
                []
 
2580
        end,
 
2581
    ModOrder = case Access of
 
2582
                   mod_htaccess ->
 
2583
                       "Modules mod_alias mod_htaccess mod_auth "
 
2584
                           "mod_security "
 
2585
                           "mod_responsecontrol mod_trace mod_esi "
 
2586
                           "mod_actions mod_cgi mod_include mod_dir "
 
2587
                           "mod_range mod_get "
 
2588
                           "mod_head mod_log mod_disk_log";
 
2589
                   _ ->
 
2590
                       "Modules mod_alias mod_auth mod_security "
 
2591
                           "mod_responsecontrol mod_trace mod_esi "
 
2592
                           "mod_actions mod_cgi mod_include mod_dir "
 
2593
                           "mod_range mod_get "
 
2594
                           "mod_head mod_log mod_disk_log"
 
2595
               end,
 
2596
    
 
2597
%% The test suite currently does not handle an explicit BindAddress.
 
2598
%% They assume any has been used, that is Addr is always set to undefined!
 
2599
 
 
2600
%%     {ok, Hostname} = inet:gethostname(), 
 
2601
%%     {ok, Addr} = inet:getaddr(Hostname, inet6),
 
2602
%%     AddrStr = make_ipv6(Addr), 
 
2603
%%     BindAddress = lists:flatten(io_lib:format("~s|inet6", [AddrStr])),
 
2604
 
 
2605
    %% BindAddress = "*|inet", 
 
2606
    BindAddress = "*", 
 
2607
 
 
2608
    HttpConfig = [
 
2609
                  cline(["Port ", integer_to_list(Port)]),
 
2610
                  cline(["ServerName ", Host]),
 
2611
                  cline(["SocketType ", atom_to_list(Type)]),
 
2612
                  cline([ModOrder]),
 
2613
                  %% cline(["LogFormat ", "erlang"]),
 
2614
                  cline(["ServerAdmin mattias@erix.ericsson.se"]),
 
2615
                  cline(["BindAddress ", BindAddress]),
 
2616
                  cline(["ServerRoot ", ServerRoot]),
 
2617
                  cline(["ErrorLog ", TcTopDir, 
 
2618
                     "/logs/error_log_", integer_to_list(Port)]),
 
2619
                  cline(["TransferLog ", TcTopDir, 
 
2620
                         "/logs/access_log_", integer_to_list(Port)]),
 
2621
                  cline(["SecurityLog ", TcTopDir, 
 
2622
                         "/logs/security_log_", integer_to_list(Port)]),
 
2623
                  cline(["ErrorDiskLog ", TcTopDir, 
 
2624
                         "/logs/error_disk_log_", integer_to_list(Port)]),
 
2625
                  cline(["ErrorDiskLogSize ", "190000 ", "11"]),
 
2626
                  cline(["TransferDiskLog ", TcTopDir, 
 
2627
                         "/logs/access_disk_log_", integer_to_list(Port)]),
 
2628
                  cline(["TransferDiskLogSize ", "200000 ", "10"]),
 
2629
                  cline(["SecurityDiskLog ", TcTopDir, 
 
2630
                         "/logs/security_disk_log_", integer_to_list(Port)]),
 
2631
                  cline(["SecurityDiskLogSize ", "210000 ", "9"]),
 
2632
                  cline(["MaxClients 10"]),
 
2633
                  cline(["MaxHeaderSize ", MaxHdrSz]),
 
2634
                  cline(["MaxHeaderAction ", MaxHdrAct]),
 
2635
                  cline(["DocumentRoot ", 
 
2636
                         filename:join(ServerRoot, "htdocs")]),
 
2637
                  cline(["DirectoryIndex ", "index.html ", "welcome.html"]),
 
2638
                  cline(["DefaultType ", "text/plain"]),
 
2639
                  SSL,
 
2640
                  mod_alias_config(ServerRoot),
 
2641
                  
 
2642
                  config_directory(filename:join([ServerRoot,"htdocs",
 
2643
                                                  "open"]),
 
2644
                                   "Open Area", 
 
2645
                                   filename:join(ServerRoot, "auth/passwd"),
 
2646
                                   filename:join(ServerRoot, "auth/group"),
 
2647
                                   plain,
 
2648
                                   "user one Aladdin",
 
2649
                                   filename:join(ServerRoot, "security_data")),
 
2650
                  config_directory(filename:join([ServerRoot,"htdocs", 
 
2651
                                                  "secret"]),
 
2652
                                   "Secret Area", 
 
2653
                                   filename:join(ServerRoot, "auth/passwd"),
 
2654
                                   filename:join(ServerRoot, "auth/group"),
 
2655
                                   plain,
 
2656
                                   "group group1 group2",
 
2657
                                   filename:join(ServerRoot, "security_data")),
 
2658
                  config_directory(filename:join([ServerRoot,"htdocs", 
 
2659
                                                  "secret", 
 
2660
                                                  "top_secret"]),
 
2661
                                   "Top Secret Area", 
 
2662
                                   filename:join(ServerRoot, "auth/passwd"),
 
2663
                                   filename:join(ServerRoot, "auth/group"),
 
2664
                                   plain,
 
2665
                                   "group group3",
 
2666
                                   filename:join(ServerRoot, "security_data")),
 
2667
                  
 
2668
                  config_directory(filename:join([ServerRoot,"htdocs", 
 
2669
                                                  "dets_open"]),
 
2670
                                   "Dets Open Area", 
 
2671
                                   filename:join(ServerRoot, "passwd"),
 
2672
                                   filename:join(ServerRoot, "group"),
 
2673
                                   dets,
 
2674
                                   "user one Aladdin",
 
2675
                                   filename:join(ServerRoot, "security_data")),
 
2676
                  config_directory(filename:join([ServerRoot,"htdocs", 
 
2677
                                                  "dets_secret"]),
 
2678
                               "Dets Secret Area", 
 
2679
                                   filename:join(ServerRoot, "passwd"),
 
2680
                                   filename:join(ServerRoot, "group"),
 
2681
                                   dets,
 
2682
                                   "group group1 group2",
 
2683
                                   filename:join(ServerRoot, "security_data")),
 
2684
                  config_directory(filename:join([ServerRoot,"htdocs", 
 
2685
                                                  "dets_secret", 
 
2686
                                                  "top_secret"]),
 
2687
                                   "Dets Top Secret Area", 
 
2688
                                   filename:join(ServerRoot, "passwd"),
 
2689
                                   filename:join(ServerRoot, "group"),
 
2690
                                   dets,
 
2691
                                   "group group3",
 
2692
                                   filename:join(ServerRoot, "security_data")),
 
2693
                  
 
2694
                  config_directory(filename:join([ServerRoot,"htdocs", 
 
2695
                                                  "mnesia_open"]),
 
2696
                                   "Mnesia Open Area", 
 
2697
                                   false,
 
2698
                                   false,
 
2699
                                   mnesia,
 
2700
                                   "user one Aladdin",
 
2701
                               filename:join(ServerRoot, "security_data")),
 
2702
                  config_directory(filename:join([ServerRoot,"htdocs", 
 
2703
                                                  "mnesia_secret"]),
 
2704
                                   "Mnesia Secret Area", 
 
2705
                                   false,
 
2706
                                   false,
 
2707
                                   mnesia,
 
2708
                                   "group group1 group2",
 
2709
                                   filename:join(ServerRoot, "security_data")),
 
2710
                  config_directory(filename:join(
 
2711
                                     [ServerRoot, "htdocs", "mnesia_secret",
 
2712
                                      "top_secret"]),
 
2713
                                   "Mnesia Top Secret Area", 
 
2714
                                   false,
 
2715
                                   false,
 
2716
                                   mnesia,
 
2717
                                   "group group3",
 
2718
                                   filename:join(ServerRoot, "security_data"))
 
2719
                 ],
 
2720
    ConfigFile = filename:join([TcTopDir, FileName]),
 
2721
    {ok, Fd} = file:open(ConfigFile, [write]),
 
2722
    ok = file:write(Fd, lists:flatten(HttpConfig)),
 
2723
    ok = file:close(Fd).
 
2724
 
 
2725
config_directory(Dir, AuthName, AuthUserFile, AuthGroupFile, AuthDBType, 
 
2726
                 Require, SF) ->
 
2727
    file:delete(SF),
 
2728
    [
 
2729
     cline(["<Directory ", Dir, ">"]),
 
2730
     cline(["SecurityDataFile ", SF]),
 
2731
     cline(["SecurityMaxRetries 3"]),
 
2732
     cline(["SecurityFailExpireTime ", integer_to_list(?FAIL_EXPIRE_TIME)]),
 
2733
     cline(["SecurityBlockTime 1"]),
 
2734
     cline(["SecurityAuthTimeout ", integer_to_list(?AUTH_TIMEOUT)]),
 
2735
     cline(["SecurityCallbackModule ", "httpd_mod"]),
 
2736
     cline_if_set("AuthUserFile", AuthUserFile),
 
2737
     cline_if_set("AuthGroupFile", AuthGroupFile),
 
2738
     cline_if_set("AuthName", AuthName),
 
2739
     cline_if_set("AuthDBType", AuthDBType),
 
2740
     cline(["require ", Require]),
 
2741
     cline(["</Directory>\r\n"])
 
2742
    ].
 
2743
 
 
2744
mod_alias_config(Root) ->
 
2745
    [
 
2746
     cline(["Alias /icons/ ", filename:join(Root,"icons"), "/"]),
 
2747
     cline(["Alias /pics/ ", filename:join(Root, "icons"), "/"]),
 
2748
     cline(["ScriptAlias /cgi-bin/ ", filename:join(Root, "cgi-bin"), "/"]),
 
2749
     cline(["ScriptAlias /htbin/ ", filename:join(Root, "cgi-bin"), "/"]),
 
2750
     cline(["ErlScriptAlias /cgi-bin/erl httpd_example io"]),
 
2751
     cline(["EvalScriptAlias /eval httpd_example io"])
 
2752
    ].
 
2753
 
 
2754
cline(List) ->
 
2755
    lists:flatten([List, "\r\n"]).
 
2756
 
 
2757
cline_if_set(_, false) ->
 
2758
    [];
 
2759
cline_if_set(Name, Var) when is_list(Var) ->
 
2760
    cline([Name, " ", Var]);
 
2761
cline_if_set(Name, Var) when is_atom(Var) ->
 
2762
    cline([Name, " ", atom_to_list(Var)]).
 
2763
 
 
2764
getaddr() ->
 
2765
    {ok,HostName} = inet:gethostname(),
 
2766
    {ok,{A1,A2,A3,A4}} = inet:getaddr(HostName,inet),
 
2767
    lists:flatten(io_lib:format("~p.~p.~p.~p",[A1,A2,A3,A4])).
 
2768
 
 
2769
start_mnesia(Node) ->
 
2770
    case rpc:call(Node, ?MODULE, cleanup_mnesia, []) of
 
2771
        ok ->
 
2772
            ok;
 
2773
        Other ->
 
2774
            tsf({failed_to_cleanup_mnesia, Other})
 
2775
    end,
 
2776
    case rpc:call(Node, ?MODULE, setup_mnesia, []) of
 
2777
        {atomic, ok} ->
 
2778
            ok;
 
2779
        Other2 ->
 
2780
            tsf({failed_to_setup_mnesia, Other2})
 
2781
    end,
 
2782
    ok.
 
2783
 
 
2784
setup_mnesia() ->
 
2785
    setup_mnesia([node()]).
 
2786
 
 
2787
setup_mnesia(Nodes) ->
 
2788
    ok = mnesia:create_schema(Nodes),
 
2789
    ok = mnesia:start(),
 
2790
    {atomic, ok} = mnesia:create_table(httpd_user,
 
2791
                                       [{attributes, 
 
2792
                                         record_info(fields, httpd_user)}, 
 
2793
                                        {disc_copies,Nodes}, {type, set}]),
 
2794
    {atomic, ok} = mnesia:create_table(httpd_group,
 
2795
                                       [{attributes, 
 
2796
                                         record_info(fields,
 
2797
                                                     httpd_group)}, 
 
2798
                                        {disc_copies,Nodes}, {type,bag}]).
 
2799
 
 
2800
cleanup_mnesia() ->
 
2801
    mnesia:start(),
 
2802
    mnesia:delete_table(httpd_user),
 
2803
    mnesia:delete_table(httpd_group),
 
2804
    stopped = mnesia:stop(),
 
2805
    mnesia:delete_schema([node()]),
 
2806
    ok.
 
2807
 
 
2808
create_htacess_data(Path, IpAddress)->
 
2809
    create_htacess_dirs(Path),
 
2810
    
 
2811
    create_html_file(filename:join([Path,"ht/open/dummy.html"])),
 
2812
    create_html_file(filename:join([Path,"ht/blocknet/dummy.html"])),
 
2813
    create_html_file(filename:join([Path,"ht/secret/dummy.html"])),
 
2814
    create_html_file(filename:join([Path,"ht/secret/top_secret/dummy.html"])),
 
2815
    
 
2816
    create_htacess_file(filename:join([Path,"ht/open/.htaccess"]),
 
2817
                         Path, "user one Aladdin"),
 
2818
    create_htacess_file(filename:join([Path,"ht/secret/.htaccess"]),
 
2819
                         Path, "group group1 group2"),
 
2820
    create_htacess_file(filename:join([Path,
 
2821
                                       "ht/secret/top_secret/.htaccess"]),
 
2822
                        Path, "user four"),
 
2823
    create_htacess_file(filename:join([Path,"ht/blocknet/.htaccess"]),
 
2824
                        Path, nouser, IpAddress),
 
2825
   
 
2826
    create_user_group_file(filename:join([Path,"ht","users.file"]),
 
2827
                           "one:OnePassword\ntwo:TwoPassword\nthree:"
 
2828
                           "ThreePassword\nfour:FourPassword\nAladdin:"
 
2829
                           "AladdinPassword"),
 
2830
    create_user_group_file(filename:join([Path,"ht","groups.file"]),
 
2831
                           "group1: two one\ngroup2: two three").
 
2832
 
 
2833
create_html_file(PathAndFileName)->
 
2834
    file:write_file(PathAndFileName,list_to_binary(
 
2835
         "<html><head><title>test</title></head>
 
2836
         <body>testar</body></html>")).
 
2837
 
 
2838
create_htacess_file(PathAndFileName, BaseDir, RequireData)->
 
2839
    file:write_file(PathAndFileName,
 
2840
                    list_to_binary(
 
2841
                      "AuthUserFile "++ BaseDir ++
 
2842
                      "/ht/users.file\nAuthGroupFile "++ BaseDir
 
2843
                      ++ "/ht/groups.file\nAuthName Test\nAuthType"
 
2844
                      " Basic\n<Limit>\nrequire " ++ RequireData ++
 
2845
                      "\n</Limit>")).
 
2846
 
 
2847
create_htacess_file(PathAndFileName, BaseDir, nouser, IpAddress)->
 
2848
    file:write_file(PathAndFileName,list_to_binary(
 
2849
                                      "AuthUserFile "++ BaseDir ++
 
2850
                                      "/ht/users.file\nAuthGroupFile " ++ 
 
2851
                                      BaseDir ++ "/ht/groups.file\nAuthName"
 
2852
                                      " Test\nAuthType"
 
2853
                                      " Basic\n<Limit GET>\n\tallow from " ++ 
 
2854
                                      format_ip(IpAddress,
 
2855
                                                string:rchr(IpAddress,$.)) ++ 
 
2856
                                      "\n</Limit>")).
 
2857
 
 
2858
create_user_group_file(PathAndFileName, Data)->
 
2859
    file:write_file(PathAndFileName, list_to_binary(Data)).
 
2860
 
 
2861
create_htacess_dirs(Path)->
 
2862
    ok = file:make_dir(filename:join([Path,"ht"])),
 
2863
    ok = file:make_dir(filename:join([Path,"ht/open"])),
 
2864
    ok = file:make_dir(filename:join([Path,"ht/blocknet"])),
 
2865
    ok = file:make_dir(filename:join([Path,"ht/secret"])),
 
2866
    ok = file:make_dir(filename:join([Path,"ht/secret/top_secret"])).
 
2867
 
 
2868
remove_htacess_dirs(Path)->
 
2869
    file:del_dir(filename:join([Path,"ht/secret/top_secret"])),
 
2870
    file:del_dir(filename:join([Path,"ht/secret"])),
 
2871
    file:del_dir(filename:join([Path,"ht/blocknet"])),
 
2872
    file:del_dir(filename:join([Path,"ht/open"])),
 
2873
    file:del_dir(filename:join([Path,"ht"])).
 
2874
 
 
2875
format_ip(IpAddress,Pos)when Pos > 0->
 
2876
    case lists:nth(Pos,IpAddress) of
 
2877
        $.->
 
2878
            case lists:nth(Pos-2,IpAddress) of
 
2879
                $.->
 
2880
                   format_ip(IpAddress,Pos-3);
 
2881
                _->
 
2882
                    lists:sublist(IpAddress,Pos-2) ++ "."
 
2883
            end;
 
2884
        _ ->
 
2885
            format_ip(IpAddress,Pos-1)
 
2886
    end;
 
2887
 
 
2888
format_ip(IpAddress, _Pos)->
 
2889
    "1" ++ IpAddress.
 
2890
 
 
2891
remove_htacess(Path)->
 
2892
    file:delete(filename:join([Path,"ht/open/dummy.html"])),
 
2893
    file:delete(filename:join([Path,"ht/secret/dummy.html"])),
 
2894
    file:delete(filename:join([Path,"ht/secret/top_secret/dummy.html"])),
 
2895
    file:delete(filename:join([Path,"ht/blocknet/dummy.html"])),
 
2896
    file:delete(filename:join([Path,"ht/blocknet/.htaccess"])),
 
2897
    file:delete(filename:join([Path,"ht/open/.htaccess"])),
 
2898
    file:delete(filename:join([Path,"ht/secret/.htaccess"])),
 
2899
    file:delete(filename:join([Path,"ht/secret/top_secret/.htaccess"])),
 
2900
    file:delete(filename:join([Path,"ht","users.file"])),
 
2901
    file:delete(filename:join([Path,"ht","groups.file"])),
 
2902
    remove_htacess_dirs(Path).
 
2903
 
 
2904
 
 
2905
dos_hostname_poll(Type, Host, Port, Node, Hosts) ->
 
2906
    [dos_hostname_poll1(Type, Host, Port, Node, Host1, Code)
 
2907
     || {Host1,Code} <- Hosts].
 
2908
 
 
2909
dos_hostname_poll1(Type, Host, Port, Node, Host1, Code) ->
 
2910
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
2911
                                       dos_hostname_request(Host1),
 
2912
                                       [{statuscode, Code},
 
2913
                                        {version, "HTTP/1.0"}]).
 
2914
        
 
2915
dos_hostname_request(Host) ->
 
2916
    "GET / HTTP/1.0\r\n" ++ Host ++ "\r\n\r\n".
 
2917
 
 
2918
get_nof_clients(Mode, Load) ->
 
2919
    get_nof_clients(test_server:os_type(), Mode, Load).
 
2920
 
 
2921
get_nof_clients(vxworks, _,       light)  -> 1;
 
2922
get_nof_clients(vxworks, ip_comm, medium) -> 3;
 
2923
get_nof_clients(vxworks, ssl,     medium) -> 3;
 
2924
get_nof_clients(vxworks, ip_comm, heavy)  -> 5;
 
2925
get_nof_clients(vxworks, ssl,     heavy)  -> 5;
 
2926
get_nof_clients(_,       ip_comm, light)  -> 5;
 
2927
get_nof_clients(_,       ssl,     light)  -> 2;
 
2928
get_nof_clients(_,       ip_comm, medium) -> 10;
 
2929
get_nof_clients(_,       ssl,     medium) -> 4;
 
2930
get_nof_clients(_,       ip_comm, heavy)  -> 20;
 
2931
get_nof_clients(_,       ssl,     heavy)  -> 6.
 
2932
 
 
2933
%% Make a file 100 bytes long containing 012...9*10
 
2934
create_range_data(Path) ->
 
2935
    PathAndFileName=filename:join([Path,"range.txt"]),
 
2936
    file:write_file(PathAndFileName,list_to_binary(["12345678901234567890",
 
2937
                                                   "12345678901234567890",
 
2938
                                                   "12345678901234567890",
 
2939
                                                   "12345678901234567890",
 
2940
                                                   "12345678901234567890"])).
 
2941
 
 
2942
%% create_ipv6_config(Config, FileName, Ipv6Address) ->
 
2943
%%     ServerRoot = ?config(server_root, Config),
 
2944
%%     TcTopDir = ?config(tc_top_dir, Config),
 
2945
%%     Port =  ?config(port, Config),
 
2946
%%     SockType = ?config(sock_type, Config),
 
2947
%%
 
2948
%%     MaxHdrSz     = io_lib:format("~p", [256]),
 
2949
%%     MaxHdrAct    = io_lib:format("~p", [close]),
 
2950
%%   
 
2951
%%     Mod_order = "Modules mod_alias mod_auth mod_esi mod_actions mod_cgi" 
 
2952
%%      " mod_include mod_dir mod_get mod_head" 
 
2953
%%      " mod_log mod_disk_log mod_trace",
 
2954
%%          
 
2955
%%     HttpConfig = [cline(["BindAddress ", "[" ++ Ipv6Address ++"]|inet6"]),
 
2956
%%                cline(["Port ", integer_to_list(Port)]),
 
2957
%%                cline(["ServerName ", "httpc_test"]),
 
2958
%%                cline(["SocketType ", atom_to_list(SockType)]),
 
2959
%%                cline([Mod_order]),
 
2960
%%                cline(["ServerRoot ", ServerRoot]),
 
2961
%%                cline(["DocumentRoot ",  
 
2962
%%                       filename:join(ServerRoot, "htdocs")]),
 
2963
%%                cline(["MaxHeaderSize ",MaxHdrSz]),
 
2964
%%                cline(["MaxHeaderAction ",MaxHdrAct]),
 
2965
%%                cline(["DirectoryIndex ", "index.html "]),
 
2966
%%                cline(["DefaultType ", "text/plain"])],
 
2967
%%     ConfigFile = filename:join([TcTopDir,FileName]),
 
2968
%%     {ok, Fd} = file:open(ConfigFile, [write]),
 
2969
%%     ok = file:write(Fd, lists:flatten(HttpConfig)),
 
2970
%%     ok = file:close(Fd).
 
2971
 
 
2972
tsf(Reason) ->
 
2973
    test_server:fail(Reason).