1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2013-2021. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20%%
21
22%%
23%% ct:run("../inets_test", httpd_SUITE).
24%%
25
26-module(httpd_SUITE).
27
28-include_lib("kernel/include/file.hrl").
29-include_lib("common_test/include/ct.hrl").
30-include_lib("public_key/include/public_key.hrl").
31-include_lib("inets/include/httpd.hrl").
32-include("inets_test_lib.hrl").
33
34%% Note: This directive should only be used in test suites.
35-compile(export_all).
36
37-record(httpd_user,  {user_name, password, user_data}).
38-record(httpd_group, {group_name, userlist}).
39-define(MAX_HEADER_SIZE, 256).
40%% Minutes before failed auths timeout.
41-define(FAIL_EXPIRE_TIME,1).
42%% Seconds before successful auths timeout.
43-define(AUTH_TIMEOUT,5).
44-define(URL_START, "http://").
45
46%%--------------------------------------------------------------------
47%% Common Test interface functions -----------------------------------
48%%--------------------------------------------------------------------
49suite() ->
50    [{ct_hooks,[ts_install_cth]},
51     {timetrap,{seconds, 120}}
52    ].
53
54all() ->
55    [
56     {group, http_basic},
57     {group, https_basic},
58     {group, http_limit},
59     {group, https_limit},
60     {group, http_custom},
61     {group, https_custom},
62     {group, https_custom},
63     {group, http_basic_auth},
64     {group, https_basic_auth},
65     {group, http_auth_api},
66     {group, https_auth_api},
67     {group, http_auth_api_dets},
68     {group, https_auth_api_dets},
69     {group, http_auth_api_mnesia},
70     {group, https_auth_api_mnesia},
71     {group, http_security},
72     {group, https_security},
73     {group, http_reload},
74     {group, https_reload},
75     {group, http_mime_types},
76     {group, http_logging},
77     {group, http_post},
78     {group, http_rel_path_script_alias},
79     {group, http_not_sup},
80     {group, https_alert},
81     {group, https_not_sup},
82     mime_types_format,
83     erl_script_timeout_default,
84     erl_script_timeout_option,
85     erl_script_timeout_proplist
86    ].
87
88groups() ->
89    [
90     {http_basic, [], basic_groups()},
91     {https_basic, [], basic_groups()},
92     {http_limit, [], [{group, limit}]},
93     {https_limit, [], [{group, limit}]},
94     {http_custom, [], [{group,  custom}]},
95     {https_custom, [], [{group,  custom}]},
96     {http_basic_auth, [], [{group, basic_auth}]},
97     {https_basic_auth, [], [{group, basic_auth}]},
98     {http_auth_api, [], [{group, auth_api}]},
99     {https_auth_api, [], [{group, auth_api}]},
100     {http_auth_api_dets, [], [{group, auth_api_dets}]},
101     {https_auth_api_dets, [], [{group, auth_api_dets}]},
102     {http_auth_api_mnesia, [], [{group, auth_api_mnesia}]},
103     {https_auth_api_mnesia, [], [{group, auth_api_mnesia}]},
104     {http_security, [], [{group, security}]},
105     {https_security, [], [{group, security}]},
106     {http_logging, [], [{group, logging}]},
107     {http_reload, [], [{group, reload}]},
108     {https_reload, [], [{group, reload}]},
109     {http_post, [], [{group, post}]},
110     {http_not_sup, [], [{group, not_sup}]},
111     {https_not_sup, [], [{group, not_sup}]},
112     {https_alert, [], [tls_alert]},
113     {http_mime_types, [], [alias_1_1, alias_1_0]},
114     {limit, [],  [content_length, max_clients_1_1]},
115     {custom, [],  [customize, add_default]},
116     {reload, [], [non_disturbing_reconfiger_dies,
117		   disturbing_reconfiger_dies,
118		   non_disturbing_1_1,
119		   non_disturbing_1_0,
120           disturbing_1_1,
121           disturbing_1_0,
122		   reload_config_file
123		  ]},
124     {post, [], [chunked_post, chunked_chunked_encoded_post, post_204]},
125     {basic_auth, [], [basic_auth_1_1, basic_auth_1_0, verify_href_1_1]},
126     {auth_api, [], [auth_api_1_1, auth_api_1_0]},
127     {auth_api_dets, [], [auth_api_1_1, auth_api_1_0]},
128     {auth_api_mnesia, [], [auth_api_1_1, auth_api_1_0]},
129     {security, [], [security_1_1, security_1_0]},
130     {logging, [], [disk_log_internal, disk_log_exists,
131             disk_log_bad_size, disk_log_bad_file]},
132     {http_1_1, [],
133      [host, chunked, expect, cgi, cgi_chunked_encoding_test,
134       trace, range, if_modified_since, mod_esi_chunk_timeout,
135       esi_put, esi_patch, esi_post, esi_proagate, esi_atom_leak, esi_headers]
136      ++ http_head() ++ http_get() ++ load()},
137     {http_1_0, [], [host, cgi, trace] ++ http_head() ++ http_get() ++ load()},
138     {http_rel_path_script_alias, [], [cgi]},
139     {not_sup, [], [put_not_sup]}
140    ].
141
142basic_groups ()->
143    [{group, http_1_1},
144     {group, http_1_0}
145    ].
146
147http_head() ->
148    [head].
149http_get() ->
150    [alias,
151     get,
152     bad_dot_paths,
153     %%actions, Add configuration so that this test mod_action
154     esi,
155     bad_hex,
156     missing_CR,
157     max_header,
158     max_content_length,
159     ignore_invalid_header,
160     ipv6
161    ].
162
163
164load() ->
165    [light, medium
166     %%,heavy
167    ].
168
169init_per_suite(Config) ->
170    PrivDir = proplists:get_value(priv_dir, Config),
171    DataDir = proplists:get_value(data_dir, Config),
172    inets_test_lib:stop_apps([inets]),
173    ServerRoot = filename:join(PrivDir, "server_root"),
174    inets_test_lib:del_dirs(ServerRoot),
175    DocRoot = filename:join(ServerRoot, "htdocs"),
176    setup_tmp_dir(PrivDir),
177    setup_server_dirs(ServerRoot, DocRoot, DataDir),
178    {ok, Hostname0} = inet:gethostname(),
179    logger:add_handler_filter(default, inets_httpd, {fun logger_filters:domain/2,
180                                                     {log, equal,[otp,inets, httpd, httpd_test, error]}}),
181    %%logger:set_handler_config(default, formatter, {logger_formatter, #{}}),
182    Inet =
183	case (catch ct:get_config(ipv6_hosts)) of
184	    undefined ->
185		inet;
186	    Hosts when is_list(Hosts) ->
187		case lists:member(list_to_atom(Hostname0), Hosts) of
188		    true ->
189			inet6;
190		    false ->
191			inet
192		end;
193	    _ ->
194		inet
195	end,
196    [{server_root, ServerRoot},
197     {doc_root, DocRoot},
198     {ipfamily, Inet},
199     {node,             node()},
200     {host,             inets_test_lib:hostname()},
201     {address,          getaddr()} | Config].
202
203end_per_suite(_Config) ->
204    ok.
205
206%%--------------------------------------------------------------------
207init_per_group(Group, Config0) when Group == https_basic;
208				    Group == https_limit;
209				    Group == https_custom;
210				    Group == https_basic_auth;
211				    Group == https_auth_api;
212				    Group == https_auth_api_dets;
213				    Group == https_auth_api_mnesia;
214				    Group == https_security;
215				    Group == https_reload;
216                                    Group == https_not_sup;
217                                    Group == https_alert
218				    ->
219    catch crypto:stop(),
220    try crypto:start() of
221        ok ->
222            init_ssl(Group,  [{http_version, "HTTP/1.0"} | Config0])
223    catch
224        _:_ ->
225            {skip, "Crypto did not start"}
226    end;
227init_per_group(Group, Config0)  when  Group == http_basic;
228				      Group == http_limit;
229				      Group == http_custom;
230				      Group == http_basic_auth;
231				      Group == http_auth_api;
232				      Group == http_auth_api_dets;
233				      Group == http_auth_api_mnesia;
234				      Group == http_security;
235				      Group == http_reload;
236                                      Group == http_not_sup;
237                                      Group == http_post;
238                                      Group == http_mime_types
239				      ->
240    ok = start_apps(Group),
241    init_httpd(Group, [{http_version, "HTTP/1.0"}, {type, ip_comm} | Config0]);
242init_per_group(http_1_1, Config) ->
243    [{http_version, "HTTP/1.1"} | Config];
244init_per_group(http_1_0, Config) ->
245    [{http_version, "HTTP/1.0"} | Config];
246init_per_group(auth_api, Config) ->
247    [{auth_prefix, ""} | Config];
248init_per_group(auth_api_dets, Config) ->
249    [{auth_prefix, "dets_"} | Config];
250init_per_group(auth_api_mnesia, Config) ->
251    start_mnesia(proplists:get_value(node, Config)),
252    [{auth_prefix, "mnesia_"} | Config];
253init_per_group(http_logging, Config) ->
254    Config1 = [{http_version, "HTTP/1.1"} | Config],
255    ServerRoot = proplists:get_value(server_root, Config1),
256    Path = ServerRoot ++ "/httpd_log_transfer",
257    [{transfer_log, Path} | Config1];
258init_per_group(http_rel_path_script_alias = Group, Config) ->
259    ok = start_apps(Group),
260    init_httpd(Group, [{type, ip_comm},{http_version, "HTTP/1.1"}| Config]);
261init_per_group(not_sup, Config) ->
262    [{http_version, "HTTP/1.1"} | Config];
263init_per_group(_, Config) ->
264    Config.
265
266end_per_group(Group, _Config)  when  Group == http_basic;
267				     Group == http_limit;
268				     Group == http_basic_auth;
269				     Group == http_auth_api;
270				     Group == http_auth_api_dets;
271				     Group == http_auth_api_mnesia;
272				     Group == http_security;
273				     Group == http_reload;
274                                     Group == http_post;
275                                     Group == http_mime_types
276				     ->
277    inets:stop();
278end_per_group(Group, _Config) when  Group == https_basic;
279				    Group == https_limit;
280				    Group == https_basic_auth;
281				    Group == https_auth_api;
282				    Group == https_auth_api_dets;
283				    Group == https_auth_api_mnesia;
284				    Group == https_security;
285				    Group == https_reload
286				    ->
287    ssl:stop(),
288    inets:stop();
289
290end_per_group(auth_api_mnesia, _) ->
291    cleanup_mnesia();
292
293end_per_group(_, _) ->
294    ok.
295
296%%--------------------------------------------------------------------
297init_per_testcase(Case, Config) when Case == host; Case == trace ->
298    ct:timetrap({seconds, 40}),
299    Prop = proplists:get_value(tc_group_properties, Config),
300    Name = proplists:get_value(name, Prop),
301    Cb = case Name of
302	     http_1_0 ->
303		 httpd_1_0;
304	     http_1_1 ->
305		 httpd_1_1
306	 end,
307    dbg(
308      Case,
309      [{version_cb, Cb} | proplists:delete(version_cb, Config)],
310      init);
311
312init_per_testcase(range, Config) ->
313    ct:timetrap({seconds, 20}),
314    DocRoot = proplists:get_value(doc_root, Config),
315    create_range_data(DocRoot),
316    dbg(range, Config, init);
317
318init_per_testcase(disk_log_internal, Config0) ->
319    ok = start_apps(http_logging),
320    Config1 = init_httpd(http_logging, [{type, ip_comm} | Config0]),
321    ct:timetrap({seconds, 20}),
322    dbg(disk_log_internal, Config1, init);
323
324init_per_testcase(disk_log_exists, Config0) ->
325    ServerRoot = proplists:get_value(server_root, Config0),
326    Filename = ServerRoot ++ "/httpd_log_transfer",
327    {ok, Log} = disk_log:open([{name, Filename}, {file, Filename},
328            {repair, truncate}, {format, internal},
329            {type, wrap}, {size, {1048576, 5}}]),
330    ok = disk_log:log(Log, {bogus, node(), self()}),
331    ok = disk_log:close(Log),
332    ok = start_apps(http_logging),
333    Config1 = init_httpd(http_logging, [{type, ip_comm} | Config0]),
334    ct:timetrap({seconds, 20}),
335    dbg(disk_log_internal, Config1, init);
336
337init_per_testcase(disk_log_bad_size, Config0) ->
338    ServerRoot = proplists:get_value(server_root, Config0),
339    Filename = ServerRoot ++ "/httpd_log_transfer",
340    {ok, Log} = disk_log:open([{name, Filename}, {file, Filename},
341            {repair, truncate}, {format, internal},
342            {type, wrap}, {size, {1048576, 5}}]),
343    ok = disk_log:log(Log, {bogus, node(), self()}),
344    ok = disk_log:close(Log),
345    ok = file:delete(Filename ++ ".siz"),
346    ok = start_apps(http_logging),
347    Config1 = init_httpd(http_logging, [{type, ip_comm} | Config0]),
348    ct:timetrap({seconds, 20}),
349    dbg(disk_log_internal, Config1, init);
350
351init_per_testcase(disk_log_bad_file, Config0) ->
352    ServerRoot = proplists:get_value(server_root, Config0),
353    Filename = ServerRoot ++ "/httpd_log_transfer",
354    ok = file:write_file(Filename ++ ".1", <<>>),
355    ok = start_apps(http_logging),
356    Config1 = init_httpd(http_logging, [{type, ip_comm} | Config0]),
357    ct:timetrap({seconds, 20}),
358    dbg(disk_log_internal, Config1, init);
359
360init_per_testcase(erl_script_timeout_default, Config) ->
361    ct:timetrap({seconds, 60}),
362    dbg(erl_script_timeout_default, Config, init);
363init_per_testcase(medium = Case, Config) ->
364    ct:timetrap({seconds, 150}),
365    dbg(Case, Config, init);
366init_per_testcase(Case, Config) ->
367    ct:timetrap({seconds, 20}),
368    dbg(Case, Config, init).
369
370end_per_testcase(Case, Config) when
371        Case == disk_log_internal;
372        Case == disk_log_exists;
373        Case == disk_log_bad_size;
374        Case == disk_log_bad_file ->
375    inets:stop(),
376    dbg(Case, Config, 'end');
377
378end_per_testcase(Case, Config) ->
379    dbg(Case, Config, 'end').
380
381
382dbg(Case, Config, Status) ->
383    Cases = [esi_put],
384    case lists:member(Case, Cases) of
385	true ->
386	    case Status of
387		init ->
388		    dbg:tracer(),
389		    dbg:p(all, c),
390		    dbg:tpl(httpd_example, cx),
391		    dbg:tpl(mod_esi, generate_webpage, cx),
392		    io:format("dbg: started~n"),
393		    Config;
394		'end' ->
395		    io:format("dbg: stopped~n"),
396		    dbg:stop_clear(),
397		    ok
398	    end;
399	false ->
400	    case Status of
401		init ->
402		    Config;
403		'end' ->
404		    ok
405	    end
406    end.
407
408%%-------------------------------------------------------------------------
409%% Test cases starts here.
410%%-------------------------------------------------------------------------
411
412head() ->
413    [{doc, "HTTP HEAD request for static page"}].
414
415head(Config) when is_list(Config) ->
416    Version = proplists:get_value(http_version, Config),
417    Host = proplists:get_value(host, Config),
418    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
419				       proplists:get_value(port, Config),
420                                       proplists:get_value(node, Config),
421				       http_request("HEAD /index.html ", Version, Host),
422				       [{statuscode, head_status(Version, 200)},
423					{version, Version}]),
424
425    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
426				       proplists:get_value(port, Config),
427				       proplists:get_value(node, Config),
428				       http_request("HEAD /open/ ", Version, Host),
429				       [{statuscode, head_status(Version, 403)},
430					{header, "Content-Type", "text/html"},
431					{header, "Date"},
432					{header, "Server"},
433					{version, Version}]).
434
435get() ->
436    [{doc, "HTTP GET request for static page"}].
437
438get(Config) when is_list(Config) ->
439    Version = proplists:get_value(http_version, Config),
440    Host = proplists:get_value(host, Config),
441    Type = proplists:get_value(type, Config),
442    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
443				       proplists:get_value(port, Config),
444				       transport_opts(Type, Config),
445				       proplists:get_value(node, Config),
446				       http_request("GET /index.html ", Version, Host),
447				       [{statuscode, 200},
448					{header, "Content-Type", "text/html"},
449					{header, "Date"},
450					{header, "Server"},
451					{version, Version}]),
452
453    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
454				       proplists:get_value(port, Config),
455				       transport_opts(Type, Config),
456				       proplists:get_value(node, Config),
457				       http_request("GET /open/ ", Version, Host),
458				       [{statuscode, 403},
459					{header, "Content-Type", "text/html"},
460					{header, "Date"},
461					{header, "Server"},
462					{version, Version}]),
463
464    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
465				       proplists:get_value(port, Config),
466				       transport_opts(Type, Config),
467				       proplists:get_value(node, Config),
468				       http_request("GET /.%252e/.%252e/.%252e/.%252e/.%252e/home/ ", Version, Host),
469				       [{statuscode, 404},
470					{header, "Content-Type", "text/html"},
471					{header, "Date"},
472					{header, "Server"},
473					{version, Version}]).
474
475bad_dot_paths() ->
476    [{doc, "Do not allow ..-paths to acesse files outside of doc root"}].
477bad_dot_paths(Config) when is_list(Config) ->
478    Version = proplists:get_value(http_version, Config),
479    Host = proplists:get_value(host, Config),
480    Type = proplists:get_value(type, Config),
481
482    BadDotPath0 = "/..%2f..%2f...%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2fetc/passwd ",
483    BadDotPath1 = "/..%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2f..%2fetc/passwd ",
484    BadDotPath2 = "/%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2f%2e%2e%2fetc/passwd ",
485
486    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
487				       proplists:get_value(port, Config),
488				       transport_opts(Type, Config),
489				       proplists:get_value(node, Config),
490				       http_request("GET " ++ BadDotPath0 , Version, Host),
491				       [{statuscode, 404},
492					{header, "Content-Type", "text/html"},
493					{header, "Date"},
494					{header, "Server"},
495					{version, Version}]),
496
497    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
498				       proplists:get_value(port, Config),
499				       transport_opts(Type, Config),
500				       proplists:get_value(node, Config),
501				       http_request("GET " ++ BadDotPath1, Version, Host),
502				       [{statuscode, 404},
503					{header, "Content-Type", "text/html"},
504					{header, "Date"},
505					{header, "Server"},
506					{version, Version}]),
507
508    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
509				       proplists:get_value(port, Config),
510				       transport_opts(Type, Config),
511				       proplists:get_value(node, Config),
512				       http_request("GET " ++ BadDotPath2, Version, Host),
513				       [{statuscode, 404},
514					{header, "Content-Type", "text/html"},
515					{header, "Date"},
516					{header, "Server"},
517					{version, Version}]).
518
519basic_auth_1_1(Config) when is_list(Config) ->
520    basic_auth([{http_version, "HTTP/1.1"} | Config]).
521
522basic_auth_1_0(Config) when is_list(Config) ->
523    basic_auth([{http_version, "HTTP/1.0"} | Config]).
524
525basic_auth() ->
526    [{doc, "Test Basic authentication with WWW-Authenticate header"}].
527
528basic_auth(Config) ->
529    Version = proplists:get_value(http_version, Config),
530    Host = proplists:get_value(host, Config),
531    basic_auth_requiered(Config),
532    %% Authentication OK! ["one:OnePassword" user first in user list]
533    ok = auth_status(auth_request("/open/dummy.html", "one", "onePassword", Version, Host), Config,
534		     [{statuscode, 200}]),
535    %% Authentication OK and a directory listing is supplied!
536    %% ["Aladdin:open sesame" user second in user list]
537    ok = auth_status(auth_request("/open/", "Aladdin", "AladdinPassword", Version, Host), Config,
538		     [{statuscode, 200}]),
539     %% User correct but wrong password! ["one:one" user first in user list]
540    ok = auth_status(auth_request("/open/dummy.html", "one", "one", Version, Host), Config,
541		     [{statuscode, 401},
542		      {header, "WWW-Authenticate"}]),
543    %% Make sure Authenticate header is received even the second time
544    %% we try a incorrect password! Otherwise a browser client will hang!
545    ok = auth_status(auth_request("/open/dummy.html", "one", "one", Version, Host), Config,
546		     [{statuscode, 401},
547		      {header, "WWW-Authenticate"}]),
548    %% Neither user or password correct! ["dummy:dummy"]
549    ok = auth_status(auth_request("/open/dummy.html", "dummy", "dummy", Version, Host), Config,
550		     [{statuscode, 401}]),
551    %% Nested secret/top_secret OK! ["Aladdin:open sesame"]
552    ok = http_status(auth_request("/secret/top_secret/", "Aladdin", "AladdinPassword", Version, Host),
553		     Config, [{statuscode, 200}]),
554    %% Authentication still required!
555    basic_auth_requiered(Config).
556
557verify_href_1_1(Config) when is_list(Config) ->
558    verify_href([{http_version, "HTTP/1.1"} | Config]).
559
560verify_href() ->
561    [{doc, "Test generated hrefs (related to GH-4677), check that hrefs for dir listing work"}].
562
563verify_href(Config) when is_list(Config) ->
564    Version = proplists:get_value(http_version, Config),
565    Host = proplists:get_value(host, Config),
566    Go = fun(Path, User, Password, Opts) ->
567                 ct:pal("Navigating to ~p", [Path]),
568                 auth_status(auth_request(Path, User, Password, Version, Host),
569                             Config, Opts)
570         end,
571    {ok, Hrefs} = Go("/open/", "Aladdin", "AladdinPassword", [{statuscode, 200}, {fetch_hrefs, true}]),
572    [ok = Go(H, "one", "onePassword", [{statuscode, 200}]) || H <- Hrefs],
573    ok.
574
575auth_api_1_1(Config) when is_list(Config) ->
576    auth_api([{http_version, "HTTP/1.1"} | Config]).
577
578auth_api_1_0(Config) when is_list(Config) ->
579    auth_api([{http_version, "HTTP/1.0"} | Config]).
580
581auth_api() ->
582    [{doc, "Test mod_auth API"}].
583
584auth_api(Config) when is_list(Config) ->
585    Prefix = proplists:get_value(auth_prefix, Config),
586    do_auth_api(Prefix, Config).
587
588do_auth_api(AuthPrefix, Config) ->
589    Version = proplists:get_value(http_version, Config),
590    Host = proplists:get_value(host, Config),
591    Port =  proplists:get_value(port, Config),
592    Node = proplists:get_value(node, Config),
593    ServerRoot = proplists:get_value(server_root, Config),
594    ok = http_status("GET / ", Config,
595 		     [{statuscode, 200}]),
596    ok = auth_status(auth_request("/", "one", "WrongPassword", Version, Host), Config,
597 		     [{statuscode, 200}]),
598
599    %% Make sure Authenticate header is received even the second time
600    %% we try a incorrect password! Otherwise a browser client will hang!
601    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/",
602 				  "dummy", "WrongPassword", Version, Host), Config,
603 		     [{statuscode, 401},
604 		      {header, "WWW-Authenticate"}]),
605    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/", "dummy", "WrongPassword",
606 				  Version, Host), Config, [{statuscode, 401},
607 						  {header, "WWW-Authenticate"}]),
608
609    %% Change the password to DummyPassword then try to add a user
610    %% Get an error and set it to NoPassword
611    ok = update_password(Node, ServerRoot, Host, Port, AuthPrefix,
612			     "open", "NoPassword", "DummyPassword"),
613    {error,bad_password} =
614 	add_user(Node, ServerRoot, Port, AuthPrefix, "open", "one",
615 		 "onePassword", []),
616     ok = update_password(Node, ServerRoot, Host, Port, AuthPrefix, "open",
617			  "DummyPassword", "NoPassword"),
618
619    %% Test /*open, require user one Aladdin
620    remove_users(Node, ServerRoot, Host, Port, AuthPrefix, "open"),
621
622    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/",
623     				  "one", "onePassword", Version, Host), Config,
624		     [{statuscode, 401}]),
625
626    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/",
627				  "two", "twoPassword", Version, Host), Config,
628		     [{statuscode, 401}]),
629
630    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/",
631				  "Aladdin", "onePassword", Version, Host),
632		     Config, [{statuscode, 401}]),
633
634    true = add_user(Node, ServerRoot, Port, AuthPrefix, "open", "one",
635		    "onePassword", []),
636    true = add_user(Node, ServerRoot, Port, AuthPrefix, "open", "two",
637     		    "twoPassword", []),
638    true = add_user(Node, ServerRoot, Port, AuthPrefix, "open", "Aladdin",
639		    "AladdinPassword", []),
640    {ok, [_|_]} = list_users(Node, ServerRoot, Host, Port,
641      			     AuthPrefix, "open"),
642    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/",
643      				  "one", "WrongPassword", Version, Host),
644      		     Config, [{statuscode, 401}]),
645    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/",
646      				  "one", "onePassword", Version, Host),
647      		     Config, [{statuscode, 200}]),
648    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/",
649      				  "two", "twoPassword",  Version, Host),
650      		     Config,[{statuscode, 401}]),
651    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/",
652      				  "Aladdin", "WrongPassword",  Version, Host),
653      		     Config,[{statuscode, 401}]),
654    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "open/",
655				  "Aladdin", "AladdinPassword", Version, Host),
656		     Config, [{statuscode, 200}]),
657
658    remove_users(Node, ServerRoot, Host, Port, AuthPrefix, "open"),
659    {ok, []} = list_users(Node, ServerRoot, Host, Port,
660			  AuthPrefix, "open"),
661
662    %% Phase 2
663      remove_users(Node, ServerRoot, Host, Port, AuthPrefix, "secret"),
664    {ok, []} = list_users(Node, ServerRoot, Host, Port, AuthPrefix,
665			  "secret"),
666    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "secret/",
667       				  "one", "onePassword", Version, Host),
668       		     Config, [{statuscode, 401}]),
669    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "secret/",
670				    "two", "twoPassword", Version, Host),
671		       Config, [{statuscode, 401}]),
672    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "secret/",
673      				  "three", "threePassword", Version, Host),
674       		     Config, [{statuscode, 401}]),
675    add_user(Node, ServerRoot, Port, AuthPrefix, "secret", "one",
676      	     "onePassword",
677      	     []),
678    add_user(Node, ServerRoot, Port, AuthPrefix, "secret",
679      	     "two", "twoPassword", []),
680    add_user(Node, ServerRoot, Port, AuthPrefix, "secret", "Aladdin",
681	     "AladdinPassword",[]),
682    add_group_member(Node, ServerRoot, Port, AuthPrefix, "secret",
683      		     "one", "group1"),
684    add_group_member(Node, ServerRoot, Port, AuthPrefix, "secret",
685      		     "two", "group1"),
686    add_group_member(Node, ServerRoot, Port, AuthPrefix,
687      			 "secret", "Aladdin", "group2"),
688    {ok, Members} = list_group_members(Node, ServerRoot, Port, AuthPrefix, "secret", "group1"),
689    true = lists:member("one", Members),
690    true = lists:member("two", Members),
691    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "secret/",
692      				  "one", "onePassword", Version, Host),
693      		     Config, [{statuscode, 200}]),
694    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "secret/",
695				  "two", "twoPassword", Version, Host),
696		       Config,[{statuscode, 200}]),
697    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "secret/",
698       				  "Aladdin", "AladdinPassword", Version, Host),
699       		     Config, [{statuscode, 200}]),
700    ok = auth_status(auth_request("/" ++ AuthPrefix ++ "secret/",
701       				  "three", "threePassword", Version, Host),
702       		     Config, [{statuscode, 401}]),
703    remove_users(Node, ServerRoot, Host, Port, AuthPrefix, "secret"),
704    {ok, []} = list_users(Node, ServerRoot, Host, Port,
705       			  AuthPrefix, "secret"),
706    remove_groups(Node, ServerRoot, Host, Port, AuthPrefix, "secret"),
707
708    {ok, []} = list_groups(Node, ServerRoot, Host, Port, AuthPrefix, "secret"),
709
710    %% Phase 3
711    remove_users(Node, ServerRoot, Host, Port, AuthPrefix, "secret/top_secret"),
712    remove_groups(Node, ServerRoot, Host, Port, AuthPrefix, "secret/top_secret"),
713
714    ok = auth_status(auth_request("/" ++ AuthPrefix ++
715      				      "secret/top_secret/",
716      				  "three", "threePassword", Version, Host),
717      		     Config, [{statuscode, 401}]),
718    ok = auth_status(auth_request("/" ++ AuthPrefix ++
719      				      "secret/top_secret/", "two", "twoPassword", Version, Host),
720      		     Config, [{statuscode, 401}]),
721     add_user(Node, ServerRoot, Port, AuthPrefix,
722	      "secret/top_secret","three",
723	      "threePassword",[]),
724    add_user(Node, ServerRoot, Port, AuthPrefix, "secret/top_secret",
725      	     "two","twoPassword", []),
726    add_group_member(Node, ServerRoot, Port, AuthPrefix, "secret/top_secret", "three", "group3"),
727    ok = auth_status(auth_request("/" ++ AuthPrefix ++
728     				      "secret/top_secret/", "three", "threePassword",
729     				  Version, Host),
730		     Config, [{statuscode, 200}]),
731     ok = auth_status(auth_request("/" ++ AuthPrefix ++
732				       "secret/top_secret/", "two", "twoPassword", Version, Host),
733		      Config, [{statuscode, 401}]),
734    add_group_member(Node, ServerRoot, Port, AuthPrefix, "secret/top_secret", "two", "group3"),
735     ok = auth_status(auth_request("/" ++ AuthPrefix ++
736				       "secret/top_secret/",
737				   "two", "twoPassword", Version, Host),
738		      Config, [{statuscode, 200}]),
739     remove_users(Node, ServerRoot, Host, Port, AuthPrefix, "secret/top_secret"),
740    {ok, []} = list_users(Node, ServerRoot, Host, Port,
741     			  AuthPrefix, "secret/top_secret"),
742    remove_groups(Node, ServerRoot, Host, Port, AuthPrefix, "secret/top_secret"),
743     {ok, []} = list_groups(Node, ServerRoot, Host, Port, AuthPrefix,  "secret/top_secret"),
744    ok = auth_status(auth_request("/" ++ AuthPrefix ++
745       				      "secret/top_secret/", "two", "twoPassword", Version, Host),
746		     Config, [{statuscode, 401}]),
747    ok = auth_status(auth_request("/" ++ AuthPrefix ++
748       				      "secret/top_secret/","three", "threePassword", Version, Host),
749       		     Config, [{statuscde, 401}]).
750%%-------------------------------------------------------------------------
751ipv6() ->
752    [{require, ipv6_hosts},
753     {doc,"Test ipv6."}].
754ipv6(Config) when is_list(Config) ->
755    {ok, Hostname0} = inet:gethostname(),
756     case lists:member(list_to_atom(Hostname0), ct:get_config(ipv6_hosts)) of
757	 true ->
758	     Version = proplists:get_value(http_version, Config),
759	     Host = proplists:get_value(host, Config),
760	     URI = http_request("GET / ", Version, Host),
761	     httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
762 					  proplists:get_value(port, Config), [inet6],
763					   proplists:get_value(code, Config),
764					   URI,
765					   [{statuscode, 200}, {version, Version}]);
766	 false ->
767	     {skip, "Host does not support IPv6"}
768     end.
769
770%%-------------------------------------------------------------------------
771chunked_post() ->
772    [{doc,"Test option max_client_body_chunk"}].
773chunked_post(Config) when is_list(Config) ->
774    ok = http_status("POST /cgi-bin/erl/httpd_example:post_chunked ",
775                       {"Content-Length:833 \r\n",
776                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
777                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
778                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
779                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
780                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
781                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
782                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
783                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
784                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
785                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
786                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
787                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
788                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
789                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
790                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
791                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
792                        "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"},
793                     [{http_version, "HTTP/1.1"} |Config],
794                     [{statuscode, 200}]),
795    ok = http_status("POST /cgi-bin/erl/httpd_example:post_chunked ",
796                     {"Content-Length:2 \r\n",
797                        "ZZ"
798                     },
799                     [{http_version, "HTTP/1.1"} |Config],
800                     [{statuscode, 200}]).
801
802chunked_chunked_encoded_post() ->
803    [{doc,"Test option max_client_body_chunk with chunked client encoding"}].
804chunked_chunked_encoded_post(Config) when is_list(Config) ->
805    Chunk = http_chunk:encode("ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"),
806    LastChunk = http_chunk:encode_last(),
807    Chunks = lists:duplicate(10000, Chunk),
808    ok = http_status("POST /cgi-bin/erl/httpd_example:post_chunked ",
809                     {"Transfer-Encoding:chunked \r\n",
810                      [Chunks | LastChunk]},
811                     [{http_version, "HTTP/1.1"} | Config],
812                     [{statuscode, 200}]).
813
814%%-------------------------------------------------------------------------
815post_204() ->
816    [{doc,"Test that 204 responses are not chunk encoded"}].
817post_204(Config) ->
818    Host = proplists:get_value(host, Config),
819    Port =  proplists:get_value(port, Config),
820    SockType = proplists:get_value(type, Config),
821    TranspOpts = transport_opts(SockType, Config),
822    Request = "POST /cgi-bin/erl/httpd_example:post_204 ",
823
824    try inets_test_lib:connect_bin(SockType, Host, Port, TranspOpts) of
825	{ok, Socket} ->
826            RequestStr = http_request(Request, "HTTP/1.1", Host),
827	    ok = inets_test_lib:send(SockType, Socket, RequestStr),
828            receive
829                {tcp, Socket, Data} ->
830                    case binary:match(Data, <<"chunked">>,[]) of
831                        nomatch ->
832                            ok;
833                        {_, _} ->
834                            ct:fail("Chunked encoding detected.")
835                    end
836            after 2000 ->
837                    ct:fail(connection_timed_out)
838            end;
839	ConnectError ->
840	    ct:fail({connect_error, ConnectError,
841		     [SockType, Host, Port, TranspOpts]})
842    catch
843	T:E:Stk ->
844	    ct:fail({connect_failure,
845		     [{type,       T},
846		      {error,      E},
847		      {stacktrace, Stk},
848		      {args,       [SockType, Host, Port, TranspOpts]}]})
849    end.
850
851%%-------------------------------------------------------------------------
852host() ->
853    [{doc, "Test host header"}].
854
855host(Config) when is_list(Config) ->
856    Cb = proplists:get_value(version_cb, Config),
857    Cb:host(proplists:get_value(type, Config), proplists:get_value(port, Config),
858	    proplists:get_value(host, Config), proplists:get_value(node, Config)).
859%%-------------------------------------------------------------------------
860chunked() ->
861    [{doc, "Check that the server accepts chunked requests."}].
862
863chunked(Config) when is_list(Config) ->
864    httpd_1_1:chunked(proplists:get_value(type, Config), proplists:get_value(port, Config),
865		      proplists:get_value(host, Config), proplists:get_value(node, Config)).
866%%-------------------------------------------------------------------------
867expect() ->
868    ["Check that the server handles request with the expect header "
869     "field appropiate"].
870expect(Config) when is_list(Config) ->
871    httpd_1_1:expect(proplists:get_value(type, Config), proplists:get_value(port, Config),
872		     proplists:get_value(host, Config), proplists:get_value(node, Config)).
873%%-------------------------------------------------------------------------
874max_clients_1_1() ->
875    [{doc, "Test max clients limit"}].
876
877max_clients_1_1(Config) when is_list(Config) ->
878    do_max_clients([{http_version, "HTTP/1.1"} | Config]).
879
880%%-------------------------------------------------------------------------
881put_not_sup() ->
882    [{doc, "Test unhandled request"}].
883
884put_not_sup(Config) when is_list(Config) ->
885    ok = http_status("PUT /index.html ",
886                     {"Content-Length:100 \r\n",
887     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
888     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
889     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
890     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
891     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
892     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
893     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
894     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
895     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
896     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
897     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
898     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
899     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
900     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
901     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
902     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
903     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"},
904		     Config, [{statuscode, 501}]).
905%%-------------------------------------------------------------------------
906esi() ->
907    [{doc, "Test mod_esi"}].
908
909esi(Config) when is_list(Config) ->
910    ok = http_status("GET /cgi-bin/erl/httpd_example ",
911		     Config, [{statuscode, 400}]),
912    ok = http_status("GET /cgi-bin/erl/httpd_example:get ",
913		     Config, [{statuscode, 200}]),
914    ok = http_status("GET /cgi-bin/erl/httpd_example:"
915		     "get?input=4711 ", Config,
916		     [{statuscode, 200}]),
917    ok = http_status("GET /cgi-bin/erl/httpd_example:post ",
918		     Config, [{statuscode, 200}]),
919    ok = http_status("GET /cgi-bin/erl/not_allowed:post ",
920		     Config, [{statuscode, 403}]),
921    ok = http_status("GET /cgi-bin/erl/httpd_example:undef ",
922		     Config, [{statuscode, 404}]),
923    ok = http_status("GET /cgi-bin/erl/httpd_example/yahoo ",
924		     Config, [{statuscode, 302}]),
925    %% Check "ErlScriptNoCache" directive (default: false)
926    ok = http_status("GET /cgi-bin/erl/httpd_example:get ",
927		     Config, [{statuscode, 200},
928		      {no_header, "cache-control"}]),
929    ok = http_status("GET /cgi-bin/erl/httpd_example:peer ",
930	  	     Config, [{statuscode, 200},
931                              {header, "peer-cert-exist", peer(Config)}]),
932    ok = http_status("GET /cgi-bin/erl/httpd_example:new_status_and_location ",
933                     Config, [{statuscode, 201},
934                              {header, "location"}]).
935
936%%-------------------------------------------------------------------------
937esi_put() ->
938    [{doc, "Test mod_esi PUT"}].
939
940esi_put(Config) when is_list(Config) ->
941    ok = http_status("PUT /cgi-bin/erl/httpd_example/put/123342234123 ",
942		     Config, [{statuscode, 200}]).
943
944%%-------------------------------------------------------------------------
945esi_patch() ->
946    [{doc, "Test mod_esi PATCH"}].
947
948esi_patch(Config) when is_list(Config) ->
949    ok = http_status("PATCH /cgi-bin/erl/httpd_example/patch/1234567890 ",
950		     Config, [{statuscode, 200}]).
951
952%%-------------------------------------------------------------------------
953esi_post() ->
954    [{doc, "Test mod_esi POST"}].
955
956esi_post(Config) when is_list(Config) ->
957    Chunk = "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ",
958    Data = lists:duplicate(10000, Chunk),
959    Length = lists:flatlength(Data),
960    ok = http_status("POST /cgi-bin/erl/httpd_example/post ",
961                     {"Content-Length:" ++ integer_to_list(Length) ++ "\r\n",
962                      Data},
963                     [{http_version, "HTTP/1.1"} |Config],
964                     [{statuscode, 200}]).
965
966%%-------------------------------------------------------------------------
967mod_esi_chunk_timeout(Config) when is_list(Config) ->
968    ok = httpd_1_1:mod_esi_chunk_timeout(proplists:get_value(type, Config),
969					 proplists:get_value(port, Config),
970					 proplists:get_value(host, Config),
971					 proplists:get_value(node, Config)).
972%%-------------------------------------------------------------------------
973esi_proagate(Config)  when is_list(Config) ->
974    register(propagate_test, self()),
975    ok = http_status("GET /cgi-bin/erl/httpd_example:new_status_and_location ",
976                  Config, [{statuscode, 201}]),
977    receive
978        {status, 201} ->
979            ok;
980        Err ->
981            ct:fail(Err)
982    end.
983%%-------------------------------------------------------------------------
984esi_atom_leak() ->
985    [{doc, "Test mod_esi for atom leakage - verify module, function names and HTTP headers"}].
986
987esi_atom_leak(Config) when is_list(Config) ->
988    NumberStrings = [integer_to_list(N) || N <- lists:seq(1, 10)],
989
990    NotExistingModule =
991        ["GET /cgi-bin/erl/not_existing_" ++ S ++":get " || S <- NumberStrings],
992    %% check atom count after first HTTP call, to ignore count increase upon initial module loading
993    GetFun = fun(Url, HeadersAndBody, Expected) ->
994                     ok = http_status(Url, HeadersAndBody, Config, Expected),
995                     erlang:system_info(atom_count)
996             end,
997    AtomCount1 = [GetFun(U, {"", ""}, [{statuscode, 404}]) || U <- NotExistingModule],
998    IsStable = fun(L) -> lists:max(L) == lists:min(L) end,
999    true = IsStable(AtomCount1),
1000
1001    NotExistingFunction =
1002        ["GET /cgi-bin/erl/httpd_example:not_existing" ++ S ++ " "
1003         || S <- NumberStrings],
1004    AtomCount2 = [GetFun(U, {"", ""}, [{statuscode, 404}]) || U <- NotExistingFunction],
1005    true = IsStable(AtomCount2),
1006
1007    NotExistingHdr =
1008        [{"NotExistingHeader_" ++ S ++ ":100 \r\n", ""} || S <- NumberStrings],
1009    AtomCount3 = [GetFun("GET /cgi-bin/erl/httpd_example:get ", H, [{statuscode, 200}])
1010                  || H <- NotExistingHdr],
1011    true = IsStable(AtomCount3).
1012
1013%%-------------------------------------------------------------------------
1014esi_headers() ->
1015    [{doc, "Test mod_esi HTTP headers support"}].
1016
1017esi_headers(Config) when is_list(Config) ->
1018    ok = http_status("GET /cgi-bin/erl/httpd_example:get_reply_headers ",
1019                     {"Accept-Encoding: gzip \r\nNotExistingHeader_1: 100 \r\n", ""},
1020                     Config, [{statuscode, 200}, {header, "notexistingheader_1", "100"},
1021                              {header, "accept-encoding", "gzip"}]).
1022
1023%%-------------------------------------------------------------------------
1024cgi() ->
1025    [{doc, "Test mod_cgi"}].
1026
1027cgi(Config) when is_list(Config) ->
1028    {Script, Script2, Script3} =
1029	case test_server:os_type() of
1030	    {win32, _} ->
1031		{"printenv.bat", "printenv.sh", "cgi_echo.exe"};
1032	    _ ->
1033		{"printenv.sh", "printenv.bat", "cgi_echo"}
1034	end,
1035
1036     %%The length (> 100) is intentional
1037     ok = http_status("POST /cgi-bin/" ++ Script3 ++ " ",
1038     		     {"Content-Length:100 \r\n",
1039     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1040     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1041     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1042     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1043     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1044     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1045     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1046     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1047     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1048     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1049     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1050     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1051     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1052     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1053     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1054     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"
1055     		      "ZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZZ"},
1056		      Config,
1057     		     [{statuscode, 200},
1058     		      {header, "content-type", "text/plain"}]),
1059
1060    ok = http_status("GET /cgi-bin/"++ Script ++ " ", Config, [{statuscode, 200}]),
1061
1062    ok = http_status("GET /cgi-bin/not_there ", Config,
1063		     [{statuscode, 404}, {statuscode, 500}]),
1064
1065    ok = http_status("GET /cgi-bin/"++ Script ++ "?Nisse:kkk?sss/lll ",
1066     		     Config,
1067     		     [{statuscode, 200}]),
1068
1069    ok = http_status("POST /cgi-bin/"++ Script  ++ " ", Config,
1070		     [{statuscode, 200}]),
1071
1072    ok = http_status("GET /htbin/"++ Script ++ " ",  Config,
1073		     [{statuscode, 200}]),
1074
1075    ok = http_status("GET /htbin/not_there ", Config,
1076		     [{statuscode, 404},{statuscode, 500}]),
1077
1078    ok = http_status("GET /htbin/"++ Script ++ "?Nisse:kkk?sss/lll ", Config,
1079     		     [{statuscode, 200}]),
1080
1081    ok = http_status("POST /htbin/"++ Script ++ " ",   Config,
1082		     [{statuscode, 200}]),
1083
1084    ok = http_status("POST /htbin/"++ Script ++ " ",  Config,
1085		     [{statuscode, 200}]),
1086
1087    %% Execute an existing, but bad CGI script..
1088    ok = http_status("POST /htbin/"++ Script2 ++ " ",  Config,
1089		     [{statuscode, 404}]),
1090
1091    ok = http_status("POST /cgi-bin/"++ Script2 ++ " ", Config,
1092		     [{statuscode, 404}]),
1093
1094    %% Check "ScriptNoCache" directive (default: false)
1095    ok = http_status("GET /cgi-bin/" ++ Script ++ " ", Config,
1096		     [{statuscode, 200},
1097		      {no_header, "cache-control"}]).
1098%%-------------------------------------------------------------------------
1099cgi_chunked_encoding_test() ->
1100    [{doc, "Test chunked encoding together with mod_cgi "}].
1101cgi_chunked_encoding_test(Config) when is_list(Config) ->
1102    Host = proplists:get_value(host, Config),
1103    Script =
1104	case test_server:os_type() of
1105	    {win32, _} ->
1106		"/cgi-bin/printenv.bat";
1107	    _ ->
1108		"/cgi-bin/printenv.sh"
1109	end,
1110    Requests =
1111	["GET " ++ Script ++ " HTTP/1.1\r\nHost:"++ Host ++"\r\n\r\n",
1112	 "GET /cgi-bin/erl/httpd_example/newformat  HTTP/1.1\r\nHost:"
1113	 ++ Host ++"\r\n\r\n"],
1114    httpd_1_1:mod_cgi_chunked_encoding_test(proplists:get_value(type, Config), proplists:get_value(port, Config),
1115					    Host,
1116					    proplists:get_value(node, Config),
1117					    Requests).
1118%%-------------------------------------------------------------------------
1119alias_1_1() ->
1120    [{doc, "Test mod_alias"}].
1121
1122alias_1_1(Config) when is_list(Config) ->
1123    alias([{http_version, "HTTP/1.1"} | Config]).
1124
1125alias_1_0() ->
1126    [{doc, "Test mod_alias"}].
1127
1128alias_1_0(Config) when is_list(Config) ->
1129    alias([{http_version, "HTTP/1.0"} | Config]).
1130
1131alias() ->
1132    [{doc, "Test mod_alias"}].
1133
1134alias(Config) when is_list(Config) ->
1135    ok = http_status("GET /pics/icon.sheet.gif ", Config,
1136		     [{statuscode, 200},
1137		      {header, "Content-Type","image/gif"},
1138		      {header, "Server"},
1139		      {header, "Date"}]),
1140
1141    ok = http_status("GET / ", Config,
1142		     [{statuscode, 200},
1143		      {header, "Content-Type","text/html"},
1144		      {header, "Server"},
1145		      {header, "Date"}]),
1146
1147    ok = http_status("GET /misc/ ", Config,
1148		     [{statuscode, 200},
1149		      {header, "Content-Type","text/html"},
1150		      {header, "Server"},
1151		      {header, "Date"}]),
1152
1153    %% Check redirection if trailing slash is missing.
1154    ok = http_status("GET /misc ", Config,
1155		     [{statuscode, 301},
1156		      {header, "Location"},
1157		      {header, "Content-Type","text/html"}]).
1158%%-------------------------------------------------------------------------
1159actions() ->
1160    [{doc, "Test mod_actions"}].
1161
1162actions(Config) when is_list(Config) ->
1163    ok = http_status("GET /", Config, [{statuscode, 200}]).
1164
1165%%-------------------------------------------------------------------------
1166range() ->
1167    [{doc, "Test Range header"}].
1168
1169range(Config) when is_list(Config) ->
1170    httpd_1_1:range(proplists:get_value(type, Config), proplists:get_value(port, Config),
1171		    proplists:get_value(host, Config), proplists:get_value(node, Config)).
1172
1173%%-------------------------------------------------------------------------
1174if_modified_since() ->
1175    [{doc, "Test If-Modified-Since header"}].
1176
1177if_modified_since(Config) when is_list(Config) ->
1178    httpd_1_1:if_test(proplists:get_value(type, Config), proplists:get_value(port, Config),
1179		      proplists:get_value(host, Config), proplists:get_value(node, Config),
1180		      proplists:get_value(doc_root, Config)).
1181%%-------------------------------------------------------------------------
1182trace() ->
1183    [{doc, "Test TRACE method"}].
1184
1185trace(Config) when is_list(Config) ->
1186    Cb = proplists:get_value(version_cb, Config),
1187    Cb:trace(proplists:get_value(type, Config), proplists:get_value(port, Config),
1188	     proplists:get_value(host, Config), proplists:get_value(node, Config)).
1189%%-------------------------------------------------------------------------
1190light() ->
1191    ["Test light load"].
1192light(Config) when is_list(Config) ->
1193    httpd_load:load_test(proplists:get_value(type, Config), proplists:get_value(port, Config), proplists:get_value(host, Config),
1194			 proplists:get_value(node, Config), 10).
1195%%-------------------------------------------------------------------------
1196medium() ->
1197    ["Test  medium load"].
1198medium(Config) when is_list(Config) ->
1199    httpd_load:load_test(proplists:get_value(type, Config), proplists:get_value(port, Config), proplists:get_value(host, Config),
1200			 proplists:get_value(node, Config), 100).
1201%%-------------------------------------------------------------------------
1202heavy() ->
1203    ["Test heavy load"].
1204heavy(Config) when is_list(Config) ->
1205    httpd_load:load_test(proplists:get_value(type, Config), proplists:get_value(port, Config), proplists:get_value(host, Config),
1206			 proplists:get_value(node, Config),
1207			 1000).
1208%%-------------------------------------------------------------------------
1209content_length() ->
1210    ["Tests that content-length is correct OTP-5775"].
1211content_length(Config) ->
1212    Version = proplists:get_value(http_version, Config),
1213    Host = proplists:get_value(host, Config),
1214    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
1215				       proplists:get_value(port, Config), proplists:get_value(node, Config),
1216				       http_request("GET /cgi-bin/erl/httpd_example:get_bin ",
1217						    Version, Host),
1218				       [{statuscode, 200},
1219					{content_length, 274},
1220					{version, Version}]).
1221%%-------------------------------------------------------------------------
1222bad_hex() ->
1223    ["Tests that a URI with a bad hexadecimal code is handled OTP-6003"].
1224bad_hex(Config) ->
1225    Version = proplists:get_value(http_version, Config),
1226    Host = proplists:get_value(host, Config),
1227    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
1228				       proplists:get_value(port, Config), proplists:get_value(node, Config),
1229				       http_request("GET http://www.erlang.org/%skalle ",
1230						    Version, Host),
1231				       [{statuscode, 400},
1232					{version, Version}]).
1233%%-------------------------------------------------------------------------
1234missing_CR() ->
1235     ["Tests missing CR in delimiter OTP-7304"].
1236missing_CR(Config) ->
1237    Version = proplists:get_value(http_version, Config),
1238    Host =  proplists:get_value(host, Config),
1239    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
1240				       proplists:get_value(port, Config), proplists:get_value(node, Config),
1241				       http_request_missing_CR("GET /index.html ", Version, Host),
1242				       [{statuscode, 200},
1243					{version, Version}]).
1244
1245%%-------------------------------------------------------------------------
1246customize() ->
1247    [{doc, "Test filtering of headers with custom callback"}].
1248
1249customize(Config) when is_list(Config) ->
1250    Version = "HTTP/1.1",
1251    Host = proplists:get_value(host, Config),
1252    Type = proplists:get_value(type, Config),
1253    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
1254				       proplists:get_value(port, Config),
1255				       transport_opts(Type, Config),
1256				       proplists:get_value(node, Config),
1257				       http_request("GET /index.html ", Version, Host),
1258				       [{statuscode, 200},
1259					{header, "Content-Type", "text/html"},
1260					{header, "Date"},
1261					{no_header, "Server"},
1262					{version, Version}]).
1263
1264add_default() ->
1265    [{doc, "Test adding default header with custom callback"}].
1266
1267add_default(Config) when is_list(Config) ->
1268    Version = "HTTP/1.1",
1269    Host = proplists:get_value(host, Config),
1270    Type = proplists:get_value(type, Config),
1271    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
1272				       proplists:get_value(port, Config),
1273				       transport_opts(Type, Config),
1274				       proplists:get_value(node, Config),
1275				       http_request("GET /index.html ", Version, Host),
1276				       [{statuscode, 200},
1277					{header, "Content-Type", "text/html"},
1278					{header, "Date", "Override-date"},
1279					{header, "X-Frame-Options"},
1280					{version, Version}]).
1281
1282%%-------------------------------------------------------------------------
1283max_header() ->
1284    ["Denial Of Service (DOS) attack, prevented by max_header"].
1285max_header(Config) when is_list(Config) ->
1286    Version = proplists:get_value(http_version, Config),
1287    Host =  proplists:get_value(host, Config),
1288    case Version of
1289 	"HTTP/0.9" ->
1290 	    {skip, not_implemented};
1291 	_ ->
1292 	    dos_hostname(proplists:get_value(type, Config), proplists:get_value(port, Config), Host,
1293 			 proplists:get_value(node, Config), Version, ?MAX_HEADER_SIZE)
1294    end.
1295
1296%%-------------------------------------------------------------------------
1297max_content_length() ->
1298    ["Denial Of Service (DOS) attack, prevented by max_content_length"].
1299max_content_length(Config) when is_list(Config) ->
1300    Version = proplists:get_value(http_version, Config),
1301    Host =  proplists:get_value(host, Config),
1302    garbage_content_length(proplists:get_value(type, Config), proplists:get_value(port, Config), Host,
1303			   proplists:get_value(node, Config), Version).
1304
1305%%-------------------------------------------------------------------------
1306ignore_invalid_header() ->
1307    ["RFC 7230 - 3.2.4 ... No whitespace is allowed between the header field-name and colon"].
1308ignore_invalid_header(Config) when is_list(Config) ->
1309     Host =  proplists:get_value(host, Config),
1310     Port =  proplists:get_value(port, Config),
1311    {Url, Header, Opts} =
1312        case proplists:get_value(type, Config) of
1313            ip_comm ->
1314                {"http://"  ++ Host ++  ":" ++ integer_to_list(Port) ++ "/cgi-bin/erl/httpd_example:ignore_invalid_header",
1315                 [{"Host", "localhost"},{"Te", ""}, {"Content-Length ", "0"}], []};
1316            ssl ->
1317                Conf = proplists:get_value(client_config, proplists:get_value(ssl_conf, Config)),
1318                {"https://"  ++ Host ++  ":" ++ integer_to_list(Port) ++ "/cgi-bin/erl/httpd_example:ignore_invalid_header",
1319                 [{"Host", "localhost"},{"Te", ""}, {"Content-Length ", "0"}], [{ssl, Conf}]}
1320        end,
1321    {ok,{{_,204,_}, _, _}}
1322        = httpc:request(get, {Url, Header}, [{timeout, 45000} | Opts], [{headers_as_is, true}]).
1323
1324%%-------------------------------------------------------------------------
1325security_1_1(Config) when is_list(Config) ->
1326    security([{http_version, "HTTP/1.1"} | Config]).
1327
1328security_1_0(Config) when is_list(Config) ->
1329    security([{http_version, "HTTP/1.0"} | Config]).
1330
1331security() ->
1332    ["Test mod_security"].
1333security(Config) ->
1334    Version = proplists:get_value(http_version, Config),
1335    Host = proplists:get_value(host, Config),
1336    Port =  proplists:get_value(port, Config),
1337    Node = proplists:get_value(node, Config),
1338    ServerRoot = proplists:get_value(server_root, Config),
1339
1340    global:register_name(mod_security_test, self()),   % Receive events
1341
1342    ct:sleep(5000),
1343
1344    OpenDir = filename:join([ServerRoot, "htdocs", "open"]),
1345
1346    %% Test blocking / unblocking of users.
1347
1348    %% /open, require user one Aladdin
1349    remove_users(Node, ServerRoot, Host, Port, "", "open"),
1350
1351    ok = auth_status(auth_request("/open/",
1352     				  "one", "onePassword", Version, Host), Config,
1353		     [{statuscode, 401}]),
1354
1355    receive_security_event({event, auth_fail, Port, OpenDir,
1356			    [{user, "one"}, {password, "onePassword"}]},
1357			   Node, Port),
1358
1359     ok = auth_status(auth_request("/open/",
1360				  "two", "twoPassword", Version, Host), Config,
1361		     [{statuscode, 401}]),
1362
1363    receive_security_event({event, auth_fail, Port, OpenDir,
1364			    [{user, "two"}, {password, "twoPassword"}]},
1365			   Node, Port),
1366
1367    ok = auth_status(auth_request("/open/",
1368				  "Aladdin", "AladdinPassword", Version, Host),
1369		     Config, [{statuscode, 401}]),
1370
1371    receive_security_event({event, auth_fail, Port, OpenDir,
1372			    [{user, "Aladdin"},
1373			     {password, "AladdinPassword"}]},
1374			   Node, Port),
1375
1376    add_user(Node, ServerRoot, Port, "", "open", "one", "onePassword", []),
1377    add_user(Node, ServerRoot, Port, "", "open", "two", "twoPassword", []),
1378
1379    ok = auth_status(auth_request("/open/", "one", "WrongPassword",  Version, Host), Config,
1380		     [{statuscode, 401}]),
1381
1382    receive_security_event({event, auth_fail, Port, OpenDir,
1383			    [{user, "one"}, {password, "WrongPassword"}]},
1384			   Node, Port),
1385
1386    ok = auth_status(auth_request("/open/", "one", "WrongPassword",  Version, Host), Config,
1387				  [{statuscode, 401}]),
1388
1389    receive_security_event({event, auth_fail, Port, OpenDir,
1390			    [{user, "one"}, {password, "WrongPassword"}]},
1391			   Node, Port),
1392    receive_security_event({event, user_block, Port, OpenDir,
1393			    [{user, "one"}]}, Node, Port),
1394
1395    global:unregister_name(mod_security_test),   % No more events.
1396
1397    ok = auth_status(auth_request("/open/", "one", "WrongPassword",  Version, Host), Config,
1398				  [{statuscode, 401}]),
1399
1400    %% User "one" should be blocked now..
1401    case list_blocked_users(Node, Port) of
1402	[{"one",_, Port, OpenDir,_}] ->
1403	    ok;
1404	Blocked ->
1405	    ct:fail({unexpected_blocked, Blocked})
1406    end,
1407
1408    [{"one",_, Port, OpenDir,_}] = list_blocked_users(Node, Port, OpenDir),
1409
1410    true = unblock_user(Node, "one", Port, OpenDir),
1411    %% User "one" should not be blocked any more.
1412
1413    [] = list_blocked_users(Node, Port),
1414
1415    ok = auth_status(auth_request("/open/", "one", "onePassword", Version, Host), Config,
1416		     [{statuscode, 200}]),
1417
1418    %% Test list_auth_users & auth_timeout
1419
1420    ["one"] = list_auth_users(Node, Port),
1421
1422    ok = auth_status(auth_request("/open/", "two", "onePassword", Version, Host), Config,
1423		     [{statuscode, 401}]),
1424
1425    ["one"] = list_auth_users(Node, Port),
1426
1427
1428    ["one"] = list_auth_users(Node, Port, OpenDir),
1429
1430
1431    ok = auth_status(auth_request("/open/", "two", "twoPassword",  Version, Host), Config,
1432				  [{statuscode, 401}]),
1433
1434    ["one"] = list_auth_users(Node, Port),
1435
1436
1437    ["one"] = list_auth_users(Node, Port, OpenDir),
1438
1439    %% Wait for successful auth to timeout.
1440    ct:sleep(?AUTH_TIMEOUT*1001),
1441
1442    [] = list_auth_users(Node, Port),
1443
1444    [] = list_auth_users(Node, Port, OpenDir),
1445
1446    %% "two" is blocked.
1447
1448    true = unblock_user(Node, "two", Port, OpenDir),
1449
1450
1451    %% Test explicit blocking. Block user 'two'.
1452
1453    [] = list_blocked_users(Node,Port,OpenDir),
1454
1455    true = block_user(Node, "two", Port, OpenDir, 10),
1456
1457    ok = auth_status(auth_request("/open/", "two", "twoPassword",  Version, Host), Config,
1458		     [{statuscode, 401}]),
1459
1460    true = unblock_user(Node, "two", Port, OpenDir).
1461
1462%%-------------------------------------------------------------------------
1463
1464disk_log_internal() ->
1465    ["Test mod_disk_log"].
1466
1467disk_log_internal(Config) ->
1468    Version = proplists:get_value(http_version, Config),
1469    Request = "GET /" ++ integer_to_list(rand:uniform(1000000)) ++ " ",
1470    ok = http_status(Request, Config, [{statuscode, 404}]),
1471    Log = proplists:get_value(transfer_log, Config),
1472    Match = list_to_binary(Request ++ Version),
1473    disk_log_internal1(Log, Match, disk_log:chunk(Log, start)).
1474disk_log_internal1(_, _, eof) ->
1475    ct:fail(eof);
1476disk_log_internal1(Log, Match, {Cont, [H | T]}) ->
1477    case binary:match(H, Match) of
1478        nomatch ->
1479            disk_log_internal1(Log, Match, {Cont, T});
1480        _ ->
1481            ok
1482    end;
1483disk_log_internal1(Log, Match, {Cont, []}) ->
1484    disk_log_internal1(Log, Match, disk_log:chunk(Log, Cont)).
1485
1486disk_log_exists() ->
1487    ["Test mod_disk_log with existing logs"].
1488
1489disk_log_exists(Config) ->
1490    Log = proplists:get_value(transfer_log, Config),
1491    Self = self(),
1492    Node = node(),
1493    Log = proplists:get_value(transfer_log, Config),
1494    {_, [{bogus, Node, Self} | _]} = disk_log:chunk(Log, start).
1495
1496disk_log_bad_size() ->
1497    ["Test mod_disk_log with existing log, missing .siz"].
1498
1499disk_log_bad_size(Config) ->
1500    Log = proplists:get_value(transfer_log, Config),
1501    Self = self(),
1502    Node = node(),
1503    Log = proplists:get_value(transfer_log, Config),
1504    {_, [{bogus, Node, Self} | _]} = disk_log:chunk(Log, start).
1505
1506disk_log_bad_file() ->
1507    ["Test mod_disk_log with bad file"].
1508
1509disk_log_bad_file(Config) ->
1510    Log = proplists:get_value(transfer_log, Config),
1511    Version = proplists:get_value(http_version, Config),
1512    Request = "GET /" ++ integer_to_list(rand:uniform(1000000)) ++ " ",
1513    ok = http_status(Request, Config, [{statuscode, 404}]),
1514    Log = proplists:get_value(transfer_log, Config),
1515    Match = list_to_binary(Request ++ Version),
1516    {_, [H | _]} = disk_log:chunk(Log, start),
1517    {_, _} = binary:match(H, Match).
1518
1519%%-------------------------------------------------------------------------
1520non_disturbing_reconfiger_dies(Config) when is_list(Config) ->
1521    do_reconfiger_dies([{http_version, "HTTP/1.1"} | Config], non_disturbing).
1522disturbing_reconfiger_dies(Config) when is_list(Config) ->
1523    do_reconfiger_dies([{http_version, "HTTP/1.1"} | Config], disturbing).
1524
1525do_reconfiger_dies(Config, DisturbingType) ->
1526    Server =  proplists:get_value(server_pid, Config),
1527    Version = proplists:get_value(http_version, Config),
1528    Host = proplists:get_value(host, Config),
1529    Port = proplists:get_value(port, Config),
1530    Type = proplists:get_value(type, Config),
1531
1532    HttpdConfig = httpd:info(Server),
1533    BlockRequest = http_request("GET /cgi-bin/erl/httpd_example:delay ", Version, Host),
1534    {ok, Socket} = inets_test_lib:connect_bin(Type, Host, Port, transport_opts(Type, Config)),
1535    inets_test_lib:send(Type, Socket, BlockRequest),
1536    ct:sleep(100), %% Avoid possible timing issues
1537    Pid = spawn(fun() -> httpd:reload_config([{server_name, "httpd_kill_" ++ Version},
1538                                              {port, Port}|
1539                                              proplists:delete(server_name, HttpdConfig)], DisturbingType)
1540                end),
1541
1542    monitor(process, Pid),
1543    exit(Pid, kill),
1544    receive
1545        {'DOWN', _, _, _, _} ->
1546            ok
1547    end,
1548    inets_test_lib:close(Type, Socket),
1549    [{server_name, "httpd_test"}] =  httpd:info(Server, [server_name]).
1550%%-------------------------------------------------------------------------
1551disturbing_1_1(Config) when is_list(Config) ->
1552    disturbing([{http_version, "HTTP/1.1"} | Config]).
1553
1554disturbing_1_0(Config) when is_list(Config) ->
1555    disturbing([{http_version, "HTTP/1.0"} | Config]).
1556
1557disturbing(Config) when is_list(Config)->
1558    Server =  proplists:get_value(server_pid, Config),
1559    Version = proplists:get_value(http_version, Config),
1560    Host = proplists:get_value(host, Config),
1561    Port = proplists:get_value(port, Config),
1562    Type = proplists:get_value(type, Config),
1563    HttpdConfig = httpd:info(Server),
1564
1565    BlockRequest = http_request("GET /cgi-bin/erl/httpd_example:delay ", Version,  Host),
1566    {ok, Socket} = inets_test_lib:connect_bin(Type, Host, Port, transport_opts(Type, Config)),
1567    inets_test_lib:send(Type, Socket, BlockRequest),
1568    ct:sleep(100), %% Avoid possible timing issues
1569    ok = httpd:reload_config([{server_name, "httpd_disturbing_" ++ Version}, {port, Port}|
1570			      proplists:delete(server_name, HttpdConfig)], disturbing),
1571    Close = list_to_atom((typestr(Type)) ++ "_closed"),
1572    receive
1573	{Close, Socket} ->
1574	    ok;
1575	Msg ->
1576	    ct:fail({{expected, {Close, Socket}}, {got, Msg}})
1577    end,
1578    inets_test_lib:close(Type, Socket),
1579    [{server_name, "httpd_disturbing_" ++ Version}] =  httpd:info(Server, [server_name]).
1580%%-------------------------------------------------------------------------
1581non_disturbing_1_1(Config) when is_list(Config) ->
1582    non_disturbing([{http_version, "HTTP/1.1"} | Config]).
1583
1584non_disturbing_1_0(Config) when is_list(Config) ->
1585    non_disturbing([{http_version, "HTTP/1.0"} | Config]).
1586
1587non_disturbing(Config) when is_list(Config)->
1588    Server =  proplists:get_value(server_pid, Config),
1589    Version = proplists:get_value(http_version, Config),
1590    Host = proplists:get_value(host, Config),
1591    Port = proplists:get_value(port, Config),
1592    Type = proplists:get_value(type, Config),
1593
1594    HttpdConfig = httpd:info(Server),
1595    BlockRequest = http_request("GET /cgi-bin/erl/httpd_example:delay ", Version, Host),
1596    {ok, Socket} = inets_test_lib:connect_bin(Type, Host, Port, transport_opts(Type, Config)),
1597    inets_test_lib:send(Type, Socket, BlockRequest),
1598    ct:sleep(100), %% Avoid possible timing issues
1599    ok = httpd:reload_config([{server_name, "httpd_non_disturbing_" ++ Version}, {port, Port}|
1600			      proplists:delete(server_name, HttpdConfig)], non_disturbing),
1601    Transport = type(Type),
1602    receive
1603	{Transport, Socket, Msg} ->
1604	    ct:pal("Received message ~p~n", [Msg]),
1605	    ok
1606    after 2000 ->
1607	  ct:fail(timeout)
1608    end,
1609    inets_test_lib:close(Type, Socket),
1610    [{server_name, "httpd_non_disturbing_" ++ Version}] =  httpd:info(Server, [server_name]).
1611%%-------------------------------------------------------------------------
1612reload_config_file(Config) when is_list(Config) ->
1613    ServerRoot = proplists:get_value(server_root, Config),
1614    HttpdConf = filename:join(get_tmp_dir(Config), "inets_httpd_server.conf"),
1615    ServerConfig =
1616        "[\n" ++
1617        "{bind_address, \"localhost\"}," ++
1618        "{port,0}," ++
1619        "{server_name,\"httpd_test\"}," ++
1620        "{server_root,\"" ++ ServerRoot ++  "\"}," ++
1621        "{document_root,\"" ++ proplists:get_value(doc_root, Config) ++ "\"}" ++
1622        "].",
1623    ok = file:write_file(HttpdConf, ServerConfig),
1624    {ok, Server} = inets:start(httpd, [{proplist_file, HttpdConf}]),
1625    Port = proplists:get_value(port, httpd:info(Server)),
1626    NewConfig =
1627        "[\n" ++
1628        "{bind_address, \"localhost\"}," ++
1629        "{port," ++ integer_to_list(Port) ++ "}," ++
1630        "{server_name,\"httpd_test_new\"}," ++
1631        "{server_root,\"" ++ ServerRoot ++  "\"}," ++
1632        "{document_root,\"" ++ proplists:get_value(doc_root, Config) ++ "\"}" ++
1633        "].",
1634
1635    %% Test Erlang term format
1636    ok = file:write_file(HttpdConf, NewConfig),
1637    ok = httpd:reload_config(HttpdConf, non_disturbing),
1638    "httpd_test_new" = proplists:get_value(server_name, httpd:info(Server)).
1639
1640%%-------------------------------------------------------------------------
1641mime_types_format(Config) when is_list(Config) ->
1642    DataDir = proplists:get_value(data_dir, Config),
1643    MimeTypes = filename:join(DataDir, "mime_types.txt"),
1644    {ok,[{"wrl","x-world/x-vrml"},
1645     {"vrml","x-world/x-vrml"},
1646     {"ice","x-conference/x-cooltalk"},
1647     {"movie","video/x-sgi-movie"},
1648     {"avi","video/x-msvideo"},
1649     {"qt","video/quicktime"},
1650     {"mov","video/quicktime"},
1651     {"mpeg","video/mpeg"},
1652     {"mpg","video/mpeg"},
1653     {"mpe","video/mpeg"},
1654     {"sgml","text/x-sgml"},
1655     {"sgm","text/x-sgml"},
1656     {"etx","text/x-setext"},
1657     {"tsv","text/tab-separated-values"},
1658     {"rtx","text/richtext"},
1659     {"txt","text/plain"},
1660     {"html","text/html"},
1661     {"htm","text/html"},
1662     {"css","text/css"},
1663     {"xwd","image/x-xwindowdump"},
1664     {"xpm","image/x-xpixmap"},
1665     {"xbm","image/x-xbitmap"},
1666     {"rgb","image/x-rgb"},
1667     {"ppm","image/x-portable-pixmap"},
1668     {"pgm","image/x-portable-graymap"},
1669     {"pbm","image/x-portable-bitmap"},
1670     {"pnm","image/x-portable-anymap"},
1671     {"ras","image/x-cmu-raster"},
1672     {"tiff","image/tiff"},
1673     {"tif","image/tiff"},
1674     {"png","image/png"},
1675     {"jpeg","image/jpeg"},
1676     {"jpg","image/jpeg"},
1677     {"jpe","image/jpeg"},
1678     {"ief","image/ief"},
1679     {"gif","image/gif"},
1680     {"pdb","chemical/x-pdb"},
1681     {"xyz","chemical/x-pdb"},
1682     {"wav","audio/x-wav"},
1683     {"ra","audio/x-realaudio"},
1684     {"rpm","audio/x-pn-realaudio-plugin"},
1685     {"ram","audio/x-pn-realaudio"},
1686     {"aif","audio/x-aiff"},
1687     {"aiff","audio/x-aiff"},
1688     {"aifc","audio/x-aiff"},
1689     {"mpga","audio/mpeg"},
1690     {"mp2","audio/mpeg"},
1691     {"au","audio/basic"},
1692     {"snd","audio/basic"},
1693     {"zip","application/zip"},
1694     {"src","application/x-wais-source"},
1695     {"ustar","application/x-ustar"},
1696     {"ms","application/x-troff-ms"},
1697     {"me","application/x-troff-me"},
1698     {"man","application/x-troff-man"},
1699     {"t","application/x-troff"},
1700     {"tr","application/x-troff"},
1701     {"roff","application/x-troff"},
1702     {"texinfo","application/x-texinfo"},
1703     {"texi","application/x-texinfo"},
1704     {"tex","application/x-tex"},
1705     {"tcl","application/x-tcl"},
1706     {"tar","application/x-tar"},
1707     {"sv4crc","application/x-sv4crc"},
1708     {"sv4cpio","application/x-sv4cpio"},
1709     {"sit","application/x-stuffit"},
1710     {"shar","application/x-shar"},
1711     {"sh","application/x-sh"},
1712     {"nc","application/x-netcdf"},
1713     {"cdf","application/x-netcdf"},
1714     {"mif","application/x-mif"},
1715     {"latex","application/x-latex"},
1716     {"skp","application/x-koan"},
1717     {"skd","application/x-koan"},
1718     {"skt","application/x-koan"},
1719     {"skm","application/x-koan"},
1720     {"cgi","application/x-httpd-cgi"},
1721     {"hdf","application/x-hdf"},
1722     {"gz","application/x-gzip"},
1723     {"gtar","application/x-gtar"},
1724     {"dvi","application/x-dvi"},
1725     {"dcr","application/x-director"},
1726     {"dir","application/x-director"},
1727     {"dxr","application/x-director"},
1728     {"csh","application/x-csh"},
1729     {"cpio","application/x-cpio"},
1730     {"Z","application/x-compress"},
1731     {"vcd","application/x-cdlink"},
1732     {"bcpio","application/x-bcpio"},
1733     {"rtf","application/rtf"},
1734     {"ppt","application/powerpoint"},
1735     {"ai","application/postscript"},
1736     {"eps","application/postscript"},
1737     {"ps","application/postscript"},
1738     {"pdf","application/pdf"},
1739     {"oda","application/oda"},
1740     {"bin","application/octet-stream"},
1741     {"dms","application/octet-stream"},
1742     {"lha","application/octet-stream"},
1743     {"lzh","application/octet-stream"},
1744     {"exe","application/octet-stream"},
1745     {"class","application/octet-stream"},
1746     {"doc","application/msword"},
1747     {"cpt","application/mac-compactpro"},
1748     {"hqx","application/mac-binhex40"}]} = httpd_conf:load_mime_types(MimeTypes).
1749
1750erl_script_timeout_default(Config) when is_list(Config) ->
1751    inets:start(),
1752    {ok, Pid} =	inets:start(httpd,
1753                            [{port, 0},
1754                             {server_name,"localhost"},
1755                             {server_root,"./"},
1756                             {document_root,"./"},
1757                             {bind_address, any},
1758                             {mimetypes, [{"html", "text/html"}]},
1759                             {modules,[mod_esi]},
1760                             {erl_script_alias, {"/erl", [httpd_example]}}
1761                            ]),
1762    Info = httpd:info(Pid),
1763
1764    Port = proplists:get_value(port, Info),
1765
1766    %% Default erl_script_timeout is 15.
1767    %% Verify:  13 =< erl_script_timeout =< 17
1768    Url = http_get_url(Port, 500, 13000, 4000),
1769
1770    {ok, {_, _, Body}} = httpc:request(get, {Url, []}, [{timeout, 45000}], []),
1771    ct:log("Response: ~p~n", [Body]),
1772    verify_body(Body, 13000),
1773    inets:stop().
1774
1775erl_script_timeout_option(Config) when is_list(Config) ->
1776    inets:start(),
1777    {ok, Pid} =	inets:start(httpd,
1778                            [{port, 0},
1779                             {server_name,"localhost"},
1780                             {server_root,"./"},
1781                             {document_root,"./"},
1782                             {bind_address, any},
1783                             {mimetypes, [{"html", "text/html"}]},
1784                             {modules,[mod_esi]},
1785                             {erl_script_timeout, 2},
1786                             {erl_script_alias, {"/erl", [httpd_example]}}
1787                            ]),
1788    Info = httpd:info(Pid),
1789    verify_timeout(Info, 2),
1790
1791    Port = proplists:get_value(port, Info),
1792
1793    %% Verify:  1 =< erl_script_timeout =< 3
1794    Url = http_get_url(Port, 500, 1000, 2000),
1795
1796    {ok, {_, _, Body}} = httpc:request(Url),
1797    ct:log("Response: ~p~n", [Body]),
1798    verify_body(Body, 1000),
1799    inets:stop().
1800
1801erl_script_timeout_proplist(Config) when is_list(Config) ->
1802    HttpdConf = filename:join(get_tmp_dir(Config),
1803                              "httpd_erl_script_timeout_proplist.conf"),
1804    ServerConfig =
1805        "[{port, 0},\n" ++
1806        " {server_name,\"localhost\"},\n" ++
1807        " {server_root,\"./\"},\n" ++
1808        " {document_root,\"./\"},\n" ++
1809        " {bind_address, any},\n" ++
1810        " {mimetypes, [{\"html\", \"text/html\"}]},\n" ++
1811        " {modules,[mod_esi]},\n" ++
1812        " {erl_script_timeout, 5},\n" ++
1813        " {erl_script_alias, {\"/erl\", [httpd_example]}}\n" ++
1814        "].",
1815    ok = file:write_file(HttpdConf, ServerConfig),
1816
1817    inets:start(),
1818    {ok, Pid} =	inets:start(httpd,
1819                            [{proplist_file, HttpdConf}]),
1820    Info = httpd:info(Pid),
1821    verify_timeout(Info, 5),
1822
1823    Port = proplists:get_value(port, Info),
1824
1825    %% Verify:  3 =< erl_script_timeout =< 7
1826    Url = http_get_url(Port, 500, 3000, 4000),
1827
1828    {ok, {_, _, Body}} = httpc:request(Url),
1829    ct:log("Response: ~p~n", [Body]),
1830    verify_body(Body, 3000),
1831    inets:stop().
1832
1833tls_alert(Config) when is_list(Config) ->
1834    SSLOpts = proplists:get_value(client_alert_conf, Config),
1835    Port = proplists:get_value(port, Config),
1836    {error, {tls_alert, _}} = ssl:connect("localhost", Port, [{verify, verify_peer} | SSLOpts]).
1837
1838%%--------------------------------------------------------------------
1839%% Internal functions -----------------------------------
1840%%--------------------------------------------------------------------
1841url(http, End, Config) ->
1842    Port = proplists:get_value(port, Config),
1843    {ok,Host} = inet:gethostname(),
1844    ?URL_START ++ Host ++ ":" ++ integer_to_list(Port) ++ End.
1845
1846http_get_url(Port0, HeaderDelay, ChunkDelay, BadChunkDelay) ->
1847    {ok, Host} = inet:gethostname(),
1848    Port = integer_to_list(Port0),
1849    HD = integer_to_list(HeaderDelay),
1850    CD = integer_to_list(ChunkDelay),
1851    BD = integer_to_list(BadChunkDelay),
1852    "http://" ++ Host ++ ":" ++ Port ++
1853        "/erl/httpd_example/get_chunks?header_delay=" ++ HD ++
1854        "&chunk_delay=" ++ CD ++
1855        "&bad_chunk_delay=" ++ BD.
1856
1857verify_body(Body, Timeout0) ->
1858    Timeout = integer_to_list(Timeout0),
1859    Res = string:find(Body, Timeout),
1860    ct:log("Result: ~p~n", [Res]),
1861    %% Fail if BAD chunk is found.
1862    case Res =:= Timeout ++ " ms\r\n" of
1863        true ->
1864            ok;
1865        false ->
1866            ct:fail("Unexpected chunk received!")
1867    end.
1868
1869verify_timeout(Info, Expected) ->
1870    Timeout = proplists:get_value(erl_script_timeout, Info),
1871    case Timeout =:= Expected of
1872        true ->
1873            ok;
1874        false ->
1875            ct:fail("Bad Timeout - Expected: ~p Got: ~p", [Expected, Timeout])
1876    end.
1877
1878do_max_clients(Config) ->
1879    Version = proplists:get_value(http_version, Config),
1880    Host    = proplists:get_value(host, Config),
1881    Port    = proplists:get_value(port, Config),
1882    Type    = proplists:get_value(type, Config),
1883
1884    Request = http_request("GET /index.html ", Version, Host),
1885    BlockRequest = http_request("GET /cgi_bin/erl/httpd_example:delay ", Version, Host),
1886    {ok, Socket} = inets_test_lib:connect_bin(Type, Host, Port, transport_opts(Type, Config)),
1887    inets_test_lib:send(Type, Socket, BlockRequest),
1888    ok = httpd_test_lib:verify_request(Type, Host,
1889				       Port,
1890				       transport_opts(Type, Config),
1891				       proplists:get_value(node, Config),
1892				       Request,
1893				       [{statuscode, 503},
1894					{version, Version}]),
1895    receive
1896	{_, Socket, _Msg} ->
1897	    ok
1898    end,
1899    inets_test_lib:close(Type, Socket),
1900    ct:sleep(100), %% Avoid possible timing issues
1901    ok = httpd_test_lib:verify_request(Type, Host,
1902				       Port,
1903				       transport_opts(Type, Config),
1904				       proplists:get_value(node, Config),
1905				       Request,
1906				       [{statuscode, 200},
1907					{version, Version}]).
1908
1909setup_server_dirs(ServerRoot, DocRoot, DataDir) ->
1910    CgiDir =  filename:join(ServerRoot, "cgi-bin"),
1911    AuthDir =  filename:join(ServerRoot, "auth"),
1912    PicsDir =  filename:join(ServerRoot, "icons"),
1913    ConfigDir =  filename:join(ServerRoot, "config"),
1914
1915    ok = file:make_dir(ServerRoot),
1916    ok = file:make_dir(DocRoot),
1917    ok = file:make_dir(CgiDir),
1918    ok = file:make_dir(AuthDir),
1919    ok = file:make_dir(PicsDir),
1920    ok = file:make_dir(ConfigDir),
1921
1922    DocSrc = filename:join(DataDir, "server_root/htdocs"),
1923    AuthSrc = filename:join(DataDir, "server_root/auth"),
1924    CgiSrc =  filename:join(DataDir, "server_root/cgi-bin"),
1925    PicsSrc =  filename:join(DataDir, "server_root/icons"),
1926    ConfigSrc = filename:join(DataDir, "server_root/config"),
1927
1928    inets_test_lib:copy_dirs(DocSrc, DocRoot),
1929    inets_test_lib:copy_dirs(AuthSrc, AuthDir),
1930    inets_test_lib:copy_dirs(CgiSrc, CgiDir),
1931    inets_test_lib:copy_dirs(PicsSrc, PicsDir),
1932    inets_test_lib:copy_dirs(ConfigSrc, ConfigDir),
1933
1934    Cgi = case test_server:os_type() of
1935	      {win32, _} ->
1936		  "cgi_echo.exe";
1937	      _ ->
1938		  "cgi_echo"
1939	  end,
1940
1941    inets_test_lib:copy_file(Cgi, DataDir, CgiDir),
1942    AbsCgi = filename:join([CgiDir, Cgi]),
1943    {ok, FileInfo} = file:read_file_info(AbsCgi),
1944    ok = file:write_file_info(AbsCgi, FileInfo#file_info{mode = 8#00755}),
1945
1946    EnvCGI =  filename:join([ServerRoot, "cgi-bin", "printenv.sh"]),
1947    {ok, FileInfo1} = file:read_file_info(EnvCGI),
1948    ok = file:write_file_info(EnvCGI,
1949			      FileInfo1#file_info{mode = 8#00755}).
1950
1951setup_tmp_dir(PrivDir) ->
1952    TmpDir =  filename:join(PrivDir, "tmp"),
1953    ok = file:make_dir(TmpDir).
1954
1955get_tmp_dir(Config) ->
1956    PrivDir = proplists:get_value(priv_dir, Config),
1957    filename:join(PrivDir, "tmp").
1958
1959start_apps(Group) when  Group == https_basic;
1960			Group == https_limit;
1961			Group == https_custom;
1962			Group == https_basic_auth;
1963			Group == https_auth_api;
1964			Group == https_auth_api_dets;
1965			Group == https_auth_api_mnesia;
1966			Group == https_security;
1967			Group == https_reload;
1968                        Group == https_not_sup;
1969                        Group == https_alert
1970			->
1971    inets_test_lib:start_apps([inets, asn1, crypto, public_key, ssl]);
1972start_apps(Group) when  Group == http_basic;
1973			Group == http_limit;
1974			Group == http_custom;
1975			Group == http_basic_auth;
1976			Group == http_auth_api;
1977			Group == http_auth_api_dets;
1978			Group == http_auth_api_mnesia;
1979			Group == http_security;
1980			Group == http_logging;
1981			Group == http_reload;
1982                        Group == http_post;
1983                        Group == http_mime_types;
1984                        Group == http_rel_path_script_alias;
1985                        Group == http_not_sup;
1986                        Group == http_mime_types->
1987    inets_test_lib:start_apps([inets]).
1988
1989server_start(_, HttpdConfig) ->
1990    {ok, Pid} = inets:start(httpd, HttpdConfig),
1991    Serv = inets:services_info(),
1992    {value, {_, _, Info}} = lists:keysearch(Pid, 2, Serv),
1993    {Pid, proplists:get_value(port, Info)}.
1994
1995init_ssl(Group, Config) ->
1996    ClientFileBase = filename:join([proplists:get_value(priv_dir, Config), "client"]),
1997    ServerFileBase = filename:join([proplists:get_value(priv_dir, Config), "server"]),
1998    GenCertData = #{client_config := CConf} =
1999        public_key:pkix_test_data(#{server_chain =>
2000                                        #{root => [{key, inets_test_lib:hardcode_rsa_key(1)}],
2001                                          intermediates => [[{key, inets_test_lib:hardcode_rsa_key(2)}]],
2002                                          peer => [{key, inets_test_lib:hardcode_rsa_key(3)}
2003                                                  ]},
2004                                    client_chain =>
2005                                        #{root => [{key, inets_test_lib:hardcode_rsa_key(4)}],
2006                                          intermediates => [[{key, inets_test_lib:hardcode_rsa_key(5)}]],
2007                                          peer => [{key, inets_test_lib:hardcode_rsa_key(6)}]}}),
2008    [_ | CAs] = proplists:get_value(cacerts, CConf),
2009    AlertConf = [{cacerts, CAs} |  proplists:delete(cacerts, CConf)],
2010    Conf = inets_test_lib:gen_pem_config_files(GenCertData, ClientFileBase, ServerFileBase),
2011    case start_apps(Group) of
2012	ok ->
2013	    init_httpd(Group, [{client_alert_conf, AlertConf}, {type, ssl}, {ssl_conf, Conf} | Config]);
2014	_ ->
2015	    {skip, "Could not start https apps"}
2016    end.
2017
2018server_config(http_basic, Config) ->
2019    basic_conf() ++ server_config(http, Config);
2020server_config(https_basic, Config) ->
2021    basic_conf() ++ server_config(https, Config);
2022server_config(http_not_sup, Config) ->
2023    not_sup_conf() ++ server_config(http, Config);
2024server_config(https_not_sup, Config) ->
2025    not_sup_conf() ++ server_config(https, Config);
2026server_config(http_reload, Config) ->
2027    [{keep_alive_timeout, 2}]  ++ server_config(http, Config);
2028server_config(http_post, Config) ->
2029    [{max_client_body_chunk, 10}]  ++ server_config(http, Config);
2030server_config(https_reload, Config) ->
2031    [{keep_alive_timeout, 2}]  ++ server_config(https, Config);
2032server_config(http_limit, Config) ->
2033    Conf = [{max_clients, 1},
2034            {disable_chunked_transfer_encoding_send, true},
2035	    %% Make sure option checking code is run
2036	    {max_content_length, 100000002}]  ++ server_config(http, Config),
2037    ct:pal("Received message ~p~n", [Conf]),
2038    Conf;
2039server_config(http_custom, Config) ->
2040    [{customize, ?MODULE}]  ++ server_config(http, Config);
2041server_config(https_custom, Config) ->
2042    [{customize, ?MODULE}]  ++ server_config(https, Config);
2043server_config(https_limit, Config) ->
2044    [{max_clients, 1},
2045     {disable_chunked_transfer_encoding_send, true}
2046    ]  ++ server_config(https, Config);
2047server_config(http_basic_auth, Config) ->
2048    ServerRoot = proplists:get_value(server_root, Config),
2049    auth_conf(ServerRoot)  ++  server_config(http, Config);
2050server_config(https_basic_auth, Config) ->
2051    ServerRoot = proplists:get_value(server_root, Config),
2052    auth_conf(ServerRoot)  ++  server_config(https, Config);
2053server_config(http_auth_api, Config) ->
2054    ServerRoot = proplists:get_value(server_root, Config),
2055    auth_api_conf(ServerRoot, plain)  ++  server_config(http, Config);
2056server_config(https_auth_api, Config) ->
2057    ServerRoot = proplists:get_value(server_root, Config),
2058    auth_api_conf(ServerRoot, plain)  ++  server_config(https, Config);
2059server_config(http_auth_api_dets, Config) ->
2060    ServerRoot = proplists:get_value(server_root, Config),
2061    auth_api_conf(ServerRoot, dets)  ++  server_config(http, Config);
2062server_config(https_auth_api_dets, Config) ->
2063    ServerRoot = proplists:get_value(server_root, Config),
2064    auth_api_conf(ServerRoot, dets)  ++  server_config(https, Config);
2065server_config(http_auth_api_mnesia, Config) ->
2066    ServerRoot = proplists:get_value(server_root, Config),
2067    auth_api_conf(ServerRoot, mnesia)  ++  server_config(http, Config);
2068server_config(https_auth_api_mnesia, Config) ->
2069    ServerRoot = proplists:get_value(server_root, Config),
2070    auth_api_conf(ServerRoot, mnesia)  ++  server_config(https, Config);
2071server_config(http_security, Config) ->
2072    ServerRoot = proplists:get_value(server_root, Config),
2073    tl(auth_conf(ServerRoot)) ++ security_conf(ServerRoot) ++ server_config(http, Config);
2074server_config(https_security, Config) ->
2075    ServerRoot = proplists:get_value(server_root, Config),
2076    tl(auth_conf(ServerRoot)) ++ security_conf(ServerRoot) ++ server_config(https, Config);
2077server_config(http_logging, Config) ->
2078    log_conf() ++ server_config(http, Config);
2079server_config(http_mime_types, Config0) ->
2080    Config1 = basic_conf() ++  server_config(http, Config0),
2081    ServerRoot = proplists:get_value(server_root, Config0),
2082    MimeTypesFile = filename:join([ServerRoot,"config", "mime.types"]),
2083    [{mime_types, MimeTypesFile} | proplists:delete(mime_types, Config1)];
2084server_config(https_alert, Config) ->
2085    basic_conf() ++ server_config(https, Config);
2086server_config(http, Config) ->
2087    ServerRoot = proplists:get_value(server_root, Config),
2088    [{port, 0},
2089     {socket_type, {ip_comm, [{nodelay, true}]}},
2090     {server_name,"httpd_test"},
2091     {server_root, ServerRoot},
2092     {document_root, proplists:get_value(doc_root, Config)},
2093     {bind_address, any},
2094     {ipfamily, proplists:get_value(ipfamily, Config)},
2095     {max_header_size, 256},
2096     {max_header_action, close},
2097     {directory_index, ["index.html", "welcome.html"]},
2098     {mime_types, [{"html","text/html"},{"htm","text/html"}, {"shtml","text/html"},
2099		   {"gif", "image/gif"}]},
2100     {alias, {"/icons/", filename:join(ServerRoot,"icons") ++ "/"}},
2101     {alias, {"/pics/",  filename:join(ServerRoot,"icons") ++ "/"}},
2102     {script_alias, {"/cgi-bin/", filename:join(ServerRoot, "cgi-bin") ++ "/"}},
2103     {script_alias, {"/htbin/", filename:join(ServerRoot, "cgi-bin") ++ "/"}},
2104     {erl_script_alias, {"/cgi-bin/erl", [httpd_example, io]}}
2105    ];
2106server_config(http_rel_path_script_alias, Config) ->
2107    ServerRoot = proplists:get_value(server_root, Config),
2108    [{port, 0},
2109     {socket_type, {ip_comm, [{nodelay, true}]}},
2110     {server_name,"httpd_test"},
2111     {server_root, ServerRoot},
2112     {document_root, proplists:get_value(doc_root, Config)},
2113     {bind_address, any},
2114     {ipfamily, proplists:get_value(ipfamily, Config)},
2115     {max_header_size, 256},
2116     {max_header_action, close},
2117     {directory_index, ["index.html", "welcome.html"]},
2118     {mime_types, [{"html","text/html"},{"htm","text/html"}, {"shtml","text/html"},
2119		   {"gif", "image/gif"}]},
2120     {alias, {"/icons/", filename:join(ServerRoot,"icons") ++ "/"}},
2121     {alias, {"/pics/",  filename:join(ServerRoot,"icons") ++ "/"}},
2122     {script_alias, {"/cgi-bin/", "./cgi-bin/"}},
2123     {script_alias, {"/htbin/", "./cgi-bin/"}},
2124     {erl_script_alias, {"/cgi-bin/erl", [httpd_example, io]}}
2125    ];
2126server_config(https, Config) ->
2127    SSLConf = proplists:get_value(ssl_conf, Config),
2128    ServerConf = proplists:get_value(server_config, SSLConf),
2129    [{socket_type, {essl,
2130		    [{nodelay, true} | ServerConf]}}]
2131        ++ proplists:delete(socket_type, server_config(http, Config)).
2132
2133init_httpd(Group, Config0) ->
2134    Config1 = proplists:delete(port, Config0),
2135    Config = proplists:delete(server_pid, Config1),
2136    {Pid, Port} = server_start(Group, server_config(Group, Config)),
2137    [{server_pid, Pid}, {port, Port} | Config].
2138
2139http_request(Request, "HTTP/1.1" = Version, Host, {Headers, Body}) ->
2140    Request ++ Version ++ "\r\nhost:" ++ Host ++ "\r\n" ++ Headers ++ "\r\n" ++ Body;
2141http_request(Request, Version, _, {Headers, Body}) ->
2142    Request ++ Version ++ "\r\n" ++ Headers  ++ "\r\n" ++ Body.
2143
2144http_request(Request, "HTTP/1.1" = Version, Host) ->
2145    Request ++ Version ++ "\r\nhost:" ++ Host  ++ "\r\n\r\n";
2146http_request(Request, Version, _) ->
2147    Request ++ Version ++ "\r\n\r\n".
2148
2149auth_request(Path, User, Passwd, "HTTP/1.1" = Version, Host) ->
2150    "GET " ++ Path ++ " " ++ Version ++  "\r\nhost:" ++ Host  ++
2151	"\r\nAuthorization: Basic " ++
2152	base64:encode_to_string(User++":"++Passwd) ++
2153	"\r\n\r\n";
2154auth_request(Path, User, Passwd, Version, _Host) ->
2155    "GET " ++ Path ++ " " ++ Version ++
2156	"\r\nAuthorization: Basic " ++
2157	base64:encode_to_string(User++":"++Passwd) ++
2158	"\r\n\r\n".
2159
2160http_request_missing_CR(Request, "HTTP/1.1" = Version, Host) ->
2161    Request ++ Version ++ "\r\nhost:" ++ Host  ++ "\r\n\r\n\n";
2162http_request_missing_CR(Request, Version, _) ->
2163    Request ++ Version ++ "\r\n\n".
2164
2165head_status("HTTP/0.9", _) ->
2166    501; %% Not implemented in HTTP/0.9
2167head_status(_, Expected) ->
2168    Expected.
2169
2170
2171basic_conf() ->
2172    [{modules, [mod_alias, mod_range, mod_responsecontrol,
2173		mod_trace, mod_esi, ?MODULE, mod_cgi, mod_get, mod_head]},
2174     {logger, [{error, httpd_test}]}].
2175
2176do(ModData) ->
2177    case whereis(propagate_test) of
2178        undefined ->
2179            ok;
2180        _ ->
2181            {already_sent, Status, _Size} = proplists:get_value(response, ModData#mod.data),
2182            propagate_test ! {status, Status}
2183    end,
2184    {proceed, ModData#mod.data}.
2185
2186not_sup_conf() ->
2187    [{modules, [mod_get]}].
2188
2189auth_access_conf() ->
2190    [{modules, [mod_alias, mod_dir, mod_get, mod_head]}].
2191
2192auth_conf(Root) ->
2193    [{modules, [mod_alias, mod_auth, mod_dir, mod_get, mod_head]},
2194     {directory, {filename:join(Root, "htdocs/open"),
2195		  [{auth_type, plain},
2196		   {auth_name, "Open Area"},
2197		   {auth_user_file, filename:join(Root, "auth/passwd")},
2198		   {auth_group_file, filename:join(Root, "auth/group")},
2199		   {require_user, ["one", "Aladdin"]}]}},
2200     {directory, {filename:join(Root, "htdocs/secret"),
2201		  [{auth_type, plain},
2202		   {auth_name, "Secret Area"},
2203		   {auth_user_file, filename:join(Root, "auth/passwd")},
2204		   {auth_group_file, filename:join(Root, "auth/group")},
2205		   {require_group, ["group1", "group2"]}]}},
2206     {directory, {filename:join(Root, "htdocs/secret/top_secret"),
2207		  [{auth_type, plain},
2208		   {auth_name, "Top Secret Area"},
2209		   {auth_user_file, filename:join(Root, "auth/passwd")},
2210		   {auth_group_file, filename:join(Root, "auth/group")},
2211		   {require_group, ["group3"]}]}}].
2212
2213auth_api_conf(Root, plain) ->
2214    [{modules, [mod_alias, mod_auth, mod_dir, mod_get, mod_head]},
2215     {directory, {filename:join(Root, "htdocs/open"),
2216		  [{auth_type, plain},
2217		   {auth_name, "Open Area"},
2218		   {auth_user_file, filename:join(Root, "auth/passwd")},
2219		   {auth_group_file, filename:join(Root, "auth/group")},
2220		   {require_user, ["one", "Aladdin"]}]}},
2221     {directory, {filename:join(Root, "htdocs/secret"),
2222		  [{auth_type, plain},
2223		   {auth_name, "Secret Area"},
2224		   {auth_user_file, filename:join(Root, "auth/passwd")},
2225		   {auth_group_file, filename:join(Root, "auth/group")},
2226		   {require_group, ["group1", "group2"]}]}},
2227     {directory, {filename:join(Root, "htdocs/secret/top_secret"),
2228		  [{auth_type, plain},
2229		   {auth_name, "Top Secret Area"},
2230		   {auth_user_file, filename:join(Root, "auth/passwd")},
2231		   {auth_group_file, filename:join(Root, "auth/group")},
2232		   {require_group, ["group3"]}]}}];
2233
2234auth_api_conf(Root, dets) ->
2235    [
2236     {modules, [mod_alias, mod_auth, mod_dir, mod_get, mod_head]},
2237     {directory, {filename:join(Root, "htdocs/dets_open"),
2238		  [{auth_type, dets},
2239		   {auth_name, "Dets Open Area"},
2240		   {auth_user_file, filename:join(Root, "passwd")},
2241		   {auth_group_file, filename:join(Root, "group")},
2242		   {require_user, ["one", "Aladdin"]}]}},
2243     {directory, {filename:join(Root, "htdocs/dets_secret"),
2244		  [{auth_type, dets},
2245		   {auth_name, "Dests Secret Area"},
2246		   {auth_user_file, filename:join(Root, "passwd")},
2247		   {auth_group_file, filename:join(Root, "group")},
2248		  {require_group, ["group1", "group2"]}]}},
2249     {directory, {filename:join(Root, "htdocs/dets_secret/top_secret"),
2250		  [{auth_type, dets},
2251		   {auth_name, "Dets Top Secret Area"},
2252		   {auth_user_file, filename:join(Root, "passwd")},
2253		   {auth_group_file, filename:join(Root, "group")},
2254		   {require_group, ["group3"]}]}}
2255    ];
2256
2257auth_api_conf(Root, mnesia) ->
2258    [{modules, [mod_alias, mod_auth, mod_dir, mod_get, mod_head]},
2259     {directory, {filename:join(Root, "htdocs/mnesia_open"),
2260		  [{auth_type, mnesia},
2261		   {auth_name, "Mnesia Open Area"},
2262		   {require_user, ["one", "Aladdin"]}]}},
2263     {directory, {filename:join(Root, "htdocs/mnesia_secret"),
2264		  [{auth_type, mnesia},
2265		   {auth_name, "Mnesia Secret Area"},
2266		   {require_group, ["group1", "group2"]}]}},
2267     {directory, {filename:join(Root, "htdocs/mnesia_secret/top_secret"),
2268		  [{auth_type, mnesia},
2269		   {auth_name, "Mnesia Top Secret Area"},
2270		   {require_group, ["group3"]}]}}].
2271
2272security_conf(Root) ->
2273    SecFile = filename:join(Root, "security_data"),
2274    Open = filename:join(Root, "htdocs/open"),
2275    Secret = filename:join(Root, "htdocs/secret"),
2276    TopSecret = filename:join(Root, "htdocs/secret/top_secret"),
2277
2278    [{modules, [mod_alias, mod_auth, mod_security, mod_dir, mod_get, mod_head]},
2279     {security_directory, {Open,
2280			   [{auth_name, "Open Area"},
2281			    {auth_user_file, filename:join(Root, "auth/passwd")},
2282			    {auth_group_file, filename:join(Root, "auth/group")},
2283			    {require_user, ["one", "Aladdin"]} |
2284			    mod_security_conf(SecFile, Open)]}},
2285     {security_directory, {Secret,
2286			   [{auth_name, "Secret Area"},
2287			    {auth_user_file, filename:join(Root, "auth/passwd")},
2288			    {auth_group_file, filename:join(Root, "auth/group")},
2289			    {require_group, ["group1", "group2"]} |
2290			    mod_security_conf(SecFile, Secret)]}},
2291     {security_directory, {TopSecret,
2292			   [{auth_name, "Top Secret Area"},
2293			    {auth_user_file, filename:join(Root, "auth/passwd")},
2294			    {auth_group_file, filename:join(Root, "auth/group")},
2295			    {require_group, ["group3"]} |
2296			    mod_security_conf(SecFile, TopSecret)]}}].
2297
2298mod_security_conf(SecFile, Dir) ->
2299    [{data_file, SecFile},
2300     {max_retries, 3},
2301     {fail_expire_time, ?FAIL_EXPIRE_TIME},
2302     {block_time, 1},
2303     {auth_timeout, ?AUTH_TIMEOUT},
2304     {callback_module, ?MODULE},
2305     {path, Dir} %% This is should not be needed, but is atm, awful design!
2306    ].
2307
2308log_conf() ->
2309    [{modules, [mod_alias, mod_dir, mod_get, mod_head, mod_disk_log]},
2310     {transfer_disk_log, "httpd_log_transfer"},
2311     {security_disk_log, "httpd_log_security"},
2312     {error_disk_log, "httpd_log_error"},
2313     {transfer_disk_log_size, {1048576, 5}},
2314     {error_disk_log_size, {1048576, 5}},
2315     {error_disk_log_size, {1048576, 5}},
2316     {security_disk_log_size, {1048576, 5}},
2317     {disk_log_format, internal}].
2318
2319http_status(Request, Config, Expected) ->
2320    Version = proplists:get_value(http_version, Config),
2321    Host = proplists:get_value(host, Config),
2322    Type = proplists:get_value(type, Config),
2323    httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
2324				  proplists:get_value(port, Config),
2325				  transport_opts(Type, Config),
2326				  proplists:get_value(node, Config),
2327				  http_request(Request, Version, Host),
2328				  Expected ++ [{version, Version}]).
2329
2330http_status(Request, HeadersAndBody, Config, Expected) ->
2331    Version = proplists:get_value(http_version, Config),
2332    Host = proplists:get_value(host, Config),
2333    Type = proplists:get_value(type, Config),
2334    httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
2335				  proplists:get_value(port, Config),
2336				  transport_opts(Type, Config),
2337				  proplists:get_value(node, Config),
2338				  http_request(Request, Version, Host, HeadersAndBody),
2339				  Expected ++ [{version, Version}]).
2340
2341auth_status(AuthRequest, Config, Expected) ->
2342    Version = proplists:get_value(http_version, Config),
2343    Host = proplists:get_value(host, Config),
2344    Type = proplists:get_value(type, Config),
2345    httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
2346				  proplists:get_value(port, Config),
2347				  transport_opts(Type, Config),
2348				  proplists:get_value(node, Config),
2349				  AuthRequest,
2350				  Expected ++ [{version, Version}]).
2351
2352basic_auth_requiered(Config) ->
2353    ok = http_status("GET /open/ ", Config,  [{statuscode, 401},
2354					      {header, "WWW-Authenticate"}]),
2355    ok = http_status("GET /secret/ ", Config,  [{statuscode, 401},
2356						{header, "WWW-Authenticate"}]),
2357    ok = http_status("GET /secret/top_secret/ ", Config,  [{statuscode, 401},
2358						      {header, "WWW-Authenticate"}]).
2359
2360start_mnesia(Node) ->
2361    case rpc:call(Node, ?MODULE, cleanup_mnesia, []) of
2362	ok ->
2363	    ok;
2364	Other ->
2365	    ct:fail({failed_to_cleanup_mnesia, Other})
2366    end,
2367    case rpc:call(Node, ?MODULE, setup_mnesia, []) of
2368	{atomic, ok} ->
2369	    ok;
2370	Other2 ->
2371	    ct:fail({failed_to_setup_mnesia, Other2})
2372    end,
2373    ok.
2374
2375setup_mnesia() ->
2376    setup_mnesia([node()]).
2377
2378setup_mnesia(Nodes) ->
2379    ok = mnesia:create_schema(Nodes),
2380    ok = mnesia:start(),
2381    {atomic, ok} = mnesia:create_table(httpd_user,
2382				       [{attributes,
2383					 record_info(fields, httpd_user)},
2384					{disc_copies,Nodes}, {type, set}]),
2385    {atomic, ok} = mnesia:create_table(httpd_group,
2386				       [{attributes,
2387					 record_info(fields,
2388						     httpd_group)},
2389					{disc_copies,Nodes}, {type,bag}]).
2390
2391cleanup_mnesia() ->
2392    mnesia:start(),
2393    mnesia:delete_table(httpd_user),
2394    mnesia:delete_table(httpd_group),
2395    stopped = mnesia:stop(),
2396    mnesia:delete_schema([node()]),
2397    ok.
2398
2399transport_opts(ssl, Config) ->
2400    SSLConf = proplists:get_value(ssl_conf, Config),
2401    ClientConf = proplists:get_value(client_config, SSLConf),
2402    [proplists:get_value(ipfamily, Config) | ClientConf];
2403transport_opts(_, Config) ->
2404    [proplists:get_value(ipfamily, Config)].
2405
2406
2407%%% mod_range
2408create_range_data(Path) ->
2409    PathAndFileName=filename:join([Path,"range.txt"]),
2410    case file:read_file(PathAndFileName) of
2411	{error, enoent} ->
2412	    file:write_file(PathAndFileName,list_to_binary(["12345678901234567890",
2413							    "12345678901234567890",
2414							    "12345678901234567890",
2415							    "12345678901234567890",
2416							    "12345678901234567890"]));
2417	_ ->
2418	    ok
2419    end.
2420
2421dos_hostname(Type, Port, Host, Node, Version, Max) ->
2422    TooLongHeader = lists:append(lists:duplicate(Max + 1, "a")),
2423
2424    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
2425 				       dos_hostname_request("", Version),
2426 				       [{statuscode, 200},
2427 					{version, Version}]),
2428
2429    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
2430 				       dos_hostname_request("dummy-host.ericsson.se", Version),
2431 				       [{statuscode, 200},
2432 					{version, Version}]),
2433
2434    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
2435 				       dos_hostname_request(TooLongHeader, Version),
2436 				       [{statuscode, request_entity_too_large_code(Version)},
2437 					{version, Version}]).
2438dos_hostname_request(Host, Version) ->
2439    dos_http_request("GET / ", Version, Host).
2440
2441dos_http_request(Request,  "HTTP/1.1" = Version, Host) ->
2442    http_request(Request, Version, Host);
2443dos_http_request(Request, Version, Host) ->
2444    Request ++ Version ++ "\r\nhost:" ++ Host  ++ "\r\n\r\n".
2445
2446request_entity_too_large_code("HTTP/1.0") ->
2447    403; %% 413 not defined in HTTP/1.0
2448request_entity_too_large_code(_) ->
2449    413.
2450
2451length_required_code("HTTP/1.0") ->
2452    403; %% 411 not defined in HTTP/1.0
2453length_required_code(_) ->
2454    411.
2455
2456garbage_content_length(Type, Port, Host, Node, Version) ->
2457    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
2458     				       garbage_content_length_request("GET / ", Version, Host, "aaaa"),
2459     				       [{statuscode, length_required_code(Version)},
2460      					{version, Version}]),
2461    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
2462				       garbage_content_length_request("GET / ", Version, Host,
2463								      lists:duplicate($a, 100)),
2464 				       [{statuscode, request_entity_too_large_code(Version)},
2465 					{version, Version}]).
2466
2467garbage_content_length_request(Request, Version, Host, Garbage) ->
2468    http_request(Request, Version, Host,
2469		 {"content-length:" ++ Garbage, "Body with garbage content length indicator"}).
2470
2471
2472update_password(Node, ServerRoot, _Address, Port, AuthPrefix, Dir, Old, New)->
2473    Directory = filename:join([ServerRoot, "htdocs", AuthPrefix ++ Dir]),
2474    rpc:call(Node, mod_auth, update_password,
2475	     [undefined, Port, Directory, Old, New, New]).
2476
2477add_user(Node, Root, Port, AuthPrefix, Dir, User, Password, UserData) ->
2478    Addr = undefined,
2479    Directory = filename:join([Root, "htdocs", AuthPrefix ++ Dir]),
2480    rpc:call(Node, mod_auth, add_user,
2481	     [User, Password, UserData, Addr, Port, Directory]).
2482
2483
2484delete_user(Node, Root, _Host, Port, AuthPrefix, Dir, User) ->
2485    Addr = undefined,
2486    Directory = filename:join([Root, "htdocs", AuthPrefix ++ Dir]),
2487    rpc:call(Node, mod_auth, delete_user, [User, Addr, Port, Directory]).
2488remove_users(Node, ServerRoot, Host, Port, AuthPrefix, Dir) ->
2489    %% List users, delete them, and make sure they are gone.
2490    case list_users(Node, ServerRoot, Host, Port, AuthPrefix, Dir) of
2491	{ok, Users} ->
2492	    lists:foreach(fun(User) ->
2493				  delete_user(Node, ServerRoot, Host,
2494					      Port, AuthPrefix, Dir, User)
2495			  end,
2496			  Users),
2497		  {ok, []} = list_users(Node, ServerRoot, Host, Port, AuthPrefix, Dir);
2498	_ ->
2499	    ok
2500    end.
2501
2502list_users(Node, Root, _Host, Port, AuthPrefix, Dir) ->
2503    Addr = undefined,
2504    Directory = filename:join([Root, "htdocs", AuthPrefix ++ Dir]),
2505    rpc:call(Node, mod_auth, list_users, [Addr, Port, Directory]).
2506
2507remove_groups(Node, ServerRoot, Host, Port,  AuthPrefix, Dir) ->
2508    {ok, Groups} = list_groups(Node, ServerRoot, Host, Port, AuthPrefix, Dir),
2509    lists:foreach(fun(Group) ->
2510			  delete_group(Node, Group, Port, ServerRoot, AuthPrefix, Dir)
2511		  end,
2512		  Groups),
2513    {ok, []} = list_groups(Node, ServerRoot, Host, Port, AuthPrefix, Dir).
2514
2515delete_group(Node, Group, Port, Root, AuthPrefix, Dir) ->
2516    Addr = undefined,
2517    Directory = filename:join([Root, "htdocs", AuthPrefix ++ Dir]),
2518    rpc:call(Node, mod_auth, delete_group, [Group, Addr, Port, Directory]).
2519
2520list_groups(Node, Root, _, Port, AuthPrefix, Dir) ->
2521    Addr = undefined,
2522    Directory = filename:join([Root, "htdocs", AuthPrefix ++ Dir]),
2523    rpc:call(Node, mod_auth, list_groups, [Addr, Port, Directory]).
2524
2525add_group_member(Node, Root, Port, AuthPrefix, Dir, User, Group) ->
2526    Addr = undefined,
2527    Directory = filename:join([Root, "htdocs", AuthPrefix ++ Dir]),
2528    rpc:call(Node, mod_auth, add_group_member, [Group, User, Addr, Port,
2529					  Directory]).
2530list_group_members(Node, Root, Port, AuthPrefix, Dir, Group) ->
2531    Directory = filename:join([Root, "htdocs", AuthPrefix ++ Dir]),
2532    rpc:call(Node, mod_auth, list_group_members, [Group, [{port, Port}, {dir, Directory}]]).
2533
2534getaddr() ->
2535    {ok,HostName} = inet:gethostname(),
2536    {ok,{A1,A2,A3,A4}} = inet:getaddr(HostName,inet),
2537    lists:flatten(io_lib:format("~p.~p.~p.~p",[A1,A2,A3,A4])).
2538
2539receive_security_event(Event, Node, Port) ->
2540    receive
2541	Event ->
2542	    ok;
2543	{'EXIT', _, _} ->
2544	    receive_security_event(Event, Node, Port)
2545    after 5000 ->
2546	    %% Flush the message queue, to see if we got something...
2547	    inets_test_lib:flush()
2548    end.
2549
2550list_blocked_users(Node,Port) ->
2551    Addr = undefined, % Assumed to be on the same host
2552    rpc:call(Node, mod_security, list_blocked_users, [Addr,Port]).
2553
2554list_blocked_users(Node,Port,Dir) ->
2555    Addr = undefined, % Assumed to be on the same host
2556    rpc:call(Node, mod_security, list_blocked_users, [Addr,Port,Dir]).
2557
2558block_user(Node,User,Port,Dir,Sec) ->
2559    Addr = undefined, % Assumed to be on the same host
2560    rpc:call(Node, mod_security, block_user, [User, Addr, Port, Dir, Sec]).
2561
2562unblock_user(Node,User,Port,Dir) ->
2563    Addr = undefined, % Assumed to be on the same host
2564    rpc:call(Node, mod_security, unblock_user, [User, Addr, Port, Dir]).
2565
2566list_auth_users(Node,Port) ->
2567    Addr = undefined, % Assumed to be on the same host
2568    rpc:call(Node, mod_security, list_auth_users, [Addr,Port]).
2569
2570list_auth_users(Node,Port,Dir) ->
2571    Addr = undefined, % Assumed to be on the same host
2572    rpc:call(Node, mod_security, list_auth_users, [Addr,Port,Dir]).
2573
2574event(What, Port, Dir, Data) ->
2575    Msg = {event, What, Port, Dir, Data},
2576    case global:whereis_name(mod_security_test) of
2577	undefined ->
2578	    ok;
2579	_Pid ->
2580	    global:send(mod_security_test, Msg)
2581    end.
2582
2583type(ip_comm) ->
2584    tcp;
2585type(_) ->
2586    ssl.
2587
2588typestr(ip_comm) ->
2589    "tcp";
2590typestr(_) ->
2591    "ssl".
2592
2593response_header({"server", _}) ->
2594    false;
2595response_header(Header) ->
2596    {true, Header}.
2597
2598response_default_headers() ->
2599    [%% Add new header
2600     {"X-Frame-Options", "SAMEORIGIN"},
2601     %% Override built-in default
2602     {"Date", "Override-date"}].
2603
2604peer(Config) ->
2605   case proplists:get_value(type, Config) of
2606      ssl ->
2607        "true";
2608      _ ->
2609        "false"
2610   end.
2611