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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2007-2011. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
-module(httpd_basic_SUITE).
 
21
 
 
22
-include_lib("common_test/include/ct.hrl").
 
23
 
 
24
%% Note: This directive should only be used in test suites.
 
25
-compile(export_all).
 
26
 
 
27
-define(URL_START, "http://localhost:").
 
28
 
 
29
suite() -> [{ct_hooks,[ts_install_cth]}].
 
30
 
 
31
all() -> 
 
32
    [uri_too_long_414, header_too_long_413, escaped_url_in_error_body].
 
33
 
 
34
groups() -> 
 
35
    [].
 
36
 
 
37
init_per_group(_GroupName, Config) ->
 
38
    Config.
 
39
 
 
40
end_per_group(_GroupName, Config) ->
 
41
    Config.
 
42
 
 
43
%%--------------------------------------------------------------------
 
44
%% Function: init_per_suite(Config) -> Config
 
45
%% Config - [tuple()]
 
46
%%   A list of key/value pairs, holding the test case configuration.
 
47
%% Description: Initiation before the whole suite
 
48
%%
 
49
%% Note: This function is free to add any key/value pairs to the Config
 
50
%% variable, but should NOT alter/remove any existing entries.
 
51
%%--------------------------------------------------------------------
 
52
init_per_suite(Config) ->
 
53
    ok = inets:start(),
 
54
    PrivDir = ?config(priv_dir, Config),
 
55
    HttpdConf = [{port, 0}, {ipfamily, inet}, 
 
56
                 {server_name, "httpd_test"}, {server_root, PrivDir},
 
57
                 {document_root, PrivDir}, {bind_address, "localhost"}],
 
58
    [{httpd_conf, HttpdConf} |  Config].
 
59
 
 
60
%%--------------------------------------------------------------------
 
61
%% Function: end_per_suite(Config) -> _
 
62
%% Config - [tuple()]
 
63
%%   A list of key/value pairs, holding the test case configuration.
 
64
%% Description: Cleanup after the whole suite
 
65
%%--------------------------------------------------------------------
 
66
end_per_suite(_Config) ->
 
67
    inets:stop(),
 
68
    ok.
 
69
 
 
70
%%--------------------------------------------------------------------
 
71
%% Function: init_per_testcase(Case, Config) -> Config
 
72
% Case - atom()
 
73
%%   Name of the test case that is about to be run.
 
74
%% Config - [tuple()]
 
75
%%   A list of key/value pairs, holding the test case configuration.
 
76
%%
 
77
%% Description: Initiation before each test case
 
78
%%
 
79
%% Note: This function is free to add any key/value pairs to the Config
 
80
%% variable, but should NOT alter/remove any existing entries.
 
81
%%--------------------------------------------------------------------
 
82
init_per_testcase(_Case, Config) ->
 
83
    Config.
 
84
 
 
85
%%--------------------------------------------------------------------
 
86
%% Function: end_per_testcase(Case, Config) -> _
 
87
%% Case - atom()
 
88
%%   Name of the test case that is about to be run.
 
89
%% Config - [tuple()]
 
90
%%   A list of key/value pairs, holding the test case configuration.
 
91
%% Description: Cleanup after each test case
 
92
%%--------------------------------------------------------------------
 
93
end_per_testcase(_, Config) ->
 
94
    Config.
 
95
 
 
96
%%-------------------------------------------------------------------------
 
97
%% Test cases starts here.
 
98
%%-------------------------------------------------------------------------
 
99
uri_too_long_414(doc) ->
 
100
    ["Test that too long uri's get 414 HTTP code"];
 
101
uri_too_long_414(suite) ->
 
102
    [];
 
103
uri_too_long_414(Config) when is_list(Config) ->
 
104
    HttpdConf =   ?config(httpd_conf, Config),    
 
105
    {ok, Pid} = inets:start(httpd, [{port, 0}, {max_uri_size, 10} 
 
106
                                    | HttpdConf]),
 
107
    Info = httpd:info(Pid),
 
108
    Port = proplists:get_value(port, Info),
 
109
    Address = proplists:get_value(bind_address, Info),
 
110
    ok = httpd_test_lib:verify_request(ip_comm, Address, Port, node(), 
 
111
                                       "GET /morethantenchars "
 
112
                                       "HTTP/1.1\r\n\r\n",
 
113
                                       [{statuscode, 414},
 
114
                                        %% Server will send lowest version
 
115
                                        %% as it will not get to the 
 
116
                                        %% client version
 
117
                                        %% before aborting
 
118
                                        {version, "HTTP/0.9"}]),    
 
119
    inets:stop(httpd, Pid).
 
120
    
 
121
header_too_long_413(doc) ->
 
122
    ["Test that too long headers's get 413 HTTP code"];
 
123
header_too_long_413(suite) ->
 
124
    [];
 
125
header_too_long_413(Config) when is_list(Config) ->
 
126
    HttpdConf = ?config(httpd_conf, Config), 
 
127
    {ok, Pid} = inets:start(httpd, [{port, 0}, {max_header_size, 10}
 
128
                                    | HttpdConf]),
 
129
    Info = httpd:info(Pid),
 
130
    Port = proplists:get_value(port, Info),
 
131
    Address = proplists:get_value(bind_address, Info),
 
132
    ok = httpd_test_lib:verify_request(ip_comm, Address, Port, node(), 
 
133
                                       "GET index.html "
 
134
                                       "HTTP/1.1\r\n"
 
135
                                       "Connection:close \r\n\r\n ",
 
136
                                       [{statuscode, 413},
 
137
                                        {version, "HTTP/1.1"}]),
 
138
    inets:stop(httpd, Pid).
 
139
   
 
140
escaped_url_in_error_body(doc) ->
 
141
    ["Test Url-encoding see OTP-8940"];
 
142
escaped_url_in_error_body(suite) ->
 
143
    [];
 
144
escaped_url_in_error_body(Config) when is_list(Config) ->
 
145
    HttpdConf =   ?config(httpd_conf, Config),
 
146
    {ok, Pid} = inets:start(httpd, [{port, 0} | HttpdConf]),
 
147
    Info = httpd:info(Pid),
 
148
    Port = proplists:get_value(port, Info),
 
149
    Address = proplists:get_value(bind_address, Info),
 
150
    Path = "/<b>this_is_bold<b>",
 
151
    URL = ?URL_START ++ integer_to_list(Port) ++ Path,
 
152
    EscapedPath = http_uri:encode(Path),
 
153
    {ok, {404, Body}} = httpc:request(get, {URL, []},
 
154
                                      [{url_encode, true}],
 
155
                                      [{version, "HTTP/1.0"}, {full_result, false}]),
 
156
    EscapedPath = find_URL_path(string:tokens(Body, " ")),
 
157
    {ok, {404, Body1}} = httpc:request(get, {URL, []}, [],
 
158
                                       [{version, "HTTP/1.0"}, {full_result, false}]),
 
159
    EscapedPath = find_URL_path(string:tokens(Body1, " ")),
 
160
    inets:stop(httpd, Pid).
 
161
 
 
162
find_URL_path([]) ->
 
163
    "";
 
164
find_URL_path(["URL", URL | _]) ->
 
165
    URL;
 
166
find_URL_path([_ | Rest]) ->
 
167
    find_URL_path(Rest).