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

« back to all changes in this revision

Viewing changes to lib/inets/test/httpd_test_lib.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 2001-2010. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
-module(httpd_test_lib).
 
21
 
 
22
-include("inets_test_lib.hrl").
 
23
 
 
24
%% Poll functions
 
25
-export([verify_request/6, verify_request/7, is_expect/1]).
 
26
 
 
27
-record(state, {request,        % string()
 
28
                socket,         % socket()
 
29
                status_line,    % {Version, StatusCode, ReasonPharse}
 
30
                headers,        % #http_response_h{}
 
31
                body,           % binary()
 
32
                mfa = {httpc_response, parse, [nolimit, false]}, 
 
33
                canceled = [],         % [RequestId]
 
34
                max_header_size = nolimit,   % nolimit | integer() 
 
35
                max_body_size = nolimit,    % nolimit | integer()
 
36
                print = false
 
37
               }).
 
38
 
 
39
%%% Part of http.hrl - Temporary solution %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
40
%%% Response headers
 
41
-record(http_response_h,{
 
42
%%% --- Standard "General" headers
 
43
          'cache-control',
 
44
          connection,
 
45
          date,
 
46
          pragma,
 
47
          trailer,
 
48
          'transfer-encoding',
 
49
          upgrade,
 
50
          via,
 
51
          warning,
 
52
%%% --- Standard "Response" headers
 
53
          'accept-ranges',
 
54
          age,
 
55
          etag,
 
56
          location,
 
57
          'proxy-authenticate',
 
58
          'retry-after',
 
59
          server,
 
60
          vary,
 
61
          'www-authenticate',
 
62
%%% --- Standard "Entity" headers
 
63
          allow,
 
64
          'content-encoding',
 
65
          'content-language',
 
66
          'content-length' = "0",
 
67
          'content-location',
 
68
          'content-md5',
 
69
          'content-range',
 
70
          'content-type',
 
71
          expires,
 
72
          'last-modified',
 
73
          other=[]        % list() - Key/Value list with other headers
 
74
         }).
 
75
 
 
76
 
 
77
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
78
 
 
79
%%--------------------------------------------------------------------
 
80
%% API
 
81
%%------------------------------------------------------------------
 
82
verify_request(SocketType, Host, Port, Node, RequestStr, Options) ->
 
83
    verify_request(SocketType, Host, Port, Node, RequestStr, Options, 30000).
 
84
verify_request(SocketType, Host, Port, Node, RequestStr, Options, TimeOut) ->
 
85
    {ok, Socket} = inets_test_lib:connect_bin(SocketType, Host, Port),
 
86
 
 
87
    _SendRes = inets_test_lib:send(SocketType, Socket, RequestStr),
 
88
    
 
89
    State = case inets_regexp:match(RequestStr, "printenv") of
 
90
                nomatch ->
 
91
                    #state{};
 
92
                _ ->
 
93
                    #state{print = true}
 
94
            end,
 
95
                
 
96
    case request(State#state{request = RequestStr, 
 
97
                             socket  = Socket}, TimeOut) of
 
98
        {error, Reason} ->
 
99
            tsp("request failed: "
 
100
                "~n   Reason: ~p", [Reason]),
 
101
            {error, Reason};
 
102
        NewState ->
 
103
            tsp("validate reply: "
 
104
                "~n   NewState: ~p", [NewState]),
 
105
            ValidateResult = validate(RequestStr, NewState, Options,
 
106
                                      Node, Port),
 
107
            tsp("validation result: "
 
108
                "~n   ~p", [ValidateResult]),
 
109
            inets_test_lib:close(SocketType, Socket),
 
110
            ValidateResult
 
111
    end.
 
112
 
 
113
request(#state{mfa = {Module, Function, Args}, 
 
114
               request = RequestStr, socket = Socket} = State, TimeOut) ->
 
115
            
 
116
    HeadRequest = lists:sublist(RequestStr, 1, 4),
 
117
    receive 
 
118
        {tcp, Socket, Data} ->
 
119
            print(tcp, Data, State),
 
120
            case Module:Function([Data | Args]) of
 
121
                {ok, Parsed} ->
 
122
                    handle_http_msg(Parsed, State); 
 
123
                {_, whole_body, _} when HeadRequest =:= "HEAD" ->
 
124
                    State#state{body = <<>>}; 
 
125
                NewMFA ->
 
126
                    request(State#state{mfa = NewMFA}, TimeOut)
 
127
            end;
 
128
        {tcp_closed, Socket} when Function =:= whole_body ->
 
129
            print(tcp, "closed", State),
 
130
            State#state{body = hd(Args)}; 
 
131
        {tcp_closed, Socket} ->
 
132
            test_server:fail(connection_closed);
 
133
        {tcp_error, Socket, Reason} ->
 
134
            test_server:fail({tcp_error, Reason});    
 
135
        {ssl, Socket, Data} ->
 
136
            print(ssl, Data, State),
 
137
            case Module:Function([Data | Args]) of
 
138
                {ok, Parsed} ->
 
139
                    handle_http_msg(Parsed, State); 
 
140
                {_, whole_body, _} when HeadRequest =:= "HEAD" ->
 
141
                    State#state{body = <<>>}; 
 
142
                NewMFA ->
 
143
                    request(State#state{mfa = NewMFA}, TimeOut)
 
144
            end;
 
145
        {ssl_closed, Socket}  when Function =:= whole_body ->
 
146
            print(ssl, "closed", State),
 
147
            State#state{body = hd(Args)};
 
148
        {ssl_closed, Socket} ->
 
149
            test_server:fail(connection_closed);
 
150
        {ssl_error, Socket, Reason} ->
 
151
            test_server:fail({ssl_error, Reason})
 
152
    after TimeOut ->
 
153
            test_server:fail(connection_timed_out)    
 
154
    end.
 
155
 
 
156
handle_http_msg({Version, StatusCode, ReasonPharse, Headers, Body}, 
 
157
                State = #state{request = RequestStr}) ->
 
158
    case is_expect(RequestStr) of
 
159
        true ->
 
160
            State#state{status_line = {Version, 
 
161
                                       StatusCode,
 
162
                                       ReasonPharse},
 
163
                        headers = Headers};
 
164
        false ->
 
165
            handle_http_body(Body, 
 
166
                             State#state{status_line = {Version, 
 
167
                                                        StatusCode,
 
168
                                                        ReasonPharse},
 
169
                                         headers = Headers})
 
170
    end;
 
171
 
 
172
handle_http_msg({ChunkedHeaders, Body}, 
 
173
                State = #state{headers = Headers}) ->
 
174
    NewHeaders = http_chunk:handle_headers(Headers, ChunkedHeaders),
 
175
    State#state{headers = NewHeaders, body = Body};
 
176
 
 
177
handle_http_msg(Body, State) ->
 
178
    State#state{body = Body}.
 
179
 
 
180
handle_http_body(<<>>, State = #state{request = "HEAD" ++ _}) ->
 
181
    State#state{body = <<>>};
 
182
 
 
183
handle_http_body(Body, State = #state{headers = Headers, 
 
184
                                      max_body_size = MaxBodySize}) ->
 
185
     case Headers#http_response_h.'transfer-encoding' of
 
186
        "chunked" ->
 
187
            case http_chunk:decode(Body, State#state.max_body_size, 
 
188
                                   State#state.max_header_size) of
 
189
                {Module, Function, Args} ->
 
190
                   request(State#state{mfa = {Module, Function, Args}},
 
191
                           30000);
 
192
                {ok, {ChunkedHeaders, NewBody}} ->
 
193
                    NewHeaders = http_chunk:handle_headers(Headers, 
 
194
                                                           ChunkedHeaders),
 
195
                    State#state{headers = NewHeaders, body = NewBody}
 
196
            end;
 
197
         _ ->
 
198
             Length =
 
199
                 list_to_integer(Headers#http_response_h.'content-length'),
 
200
             case ((Length =< MaxBodySize) or (MaxBodySize == nolimit)) of
 
201
                 true ->
 
202
                     case httpc_response:whole_body(Body, Length) of
 
203
                         {ok, NewBody} ->
 
204
                             State#state{body = NewBody};
 
205
                         MFA ->
 
206
                             request(State#state{mfa = MFA}, 5000) 
 
207
                     end;
 
208
                 false ->
 
209
                     test_server:fail(body_too_big)
 
210
             end
 
211
     end.
 
212
 
 
213
validate(RequestStr, #state{status_line = {Version, StatusCode, _},
 
214
                headers = Headers, 
 
215
                body = Body}, Options, N, P) ->
 
216
    
 
217
    %io:format("Status~p: H:~p B:~p~n", [StatusCode, Headers, Body]),
 
218
    check_version(Version, Options),
 
219
    case lists:keysearch(statuscode, 1, Options) of
 
220
        {value, _} ->
 
221
            check_status_code(StatusCode, Options, Options);
 
222
        _ ->
 
223
            ok
 
224
    end,
 
225
    do_validate(http_response:header_list(Headers), Options, N, P),
 
226
    check_body(RequestStr, StatusCode, 
 
227
               Headers#http_response_h.'content-type',
 
228
               list_to_integer(Headers#http_response_h.'content-length'),
 
229
               Body).
 
230
 
 
231
%%--------------------------------------------------------------------
 
232
%% Internal functions
 
233
%%------------------------------------------------------------------
 
234
check_version(Version, Options) ->
 
235
    case lists:keysearch(version, 1, Options) of
 
236
        {value, {version, Version}} ->
 
237
                   ok;
 
238
        {value, {version, Ver}} ->
 
239
            test_server:fail({wrong_version, [{got, Version},
 
240
                                                     {expected, Ver}]});
 
241
        _ ->
 
242
           case Version of
 
243
               "HTTP/1.1" ->
 
244
                   ok;
 
245
               _ ->
 
246
                   test_server:fail({wrong_version, [{got, Version},
 
247
                                                     {expected, "HTTP/1.1"}]})
 
248
           end
 
249
    end.
 
250
 
 
251
check_status_code(StatusCode, [], Options) ->
 
252
    test_server:fail({wrong_status_code, [{got, StatusCode}, 
 
253
                                          {expected, Options}]});
 
254
check_status_code(StatusCode, Current = [_ | Rest], Options) ->
 
255
    case lists:keysearch(statuscode, 1, Current) of
 
256
        {value, {statuscode, StatusCode}} ->
 
257
            ok;
 
258
        {value, {statuscode, _OtherStatus}} ->
 
259
            check_status_code(StatusCode, Rest, Options);
 
260
        false ->
 
261
            test_server:fail({wrong_status_code, [{got, StatusCode}, 
 
262
                                       {expected, Options}]})
 
263
    end.
 
264
 
 
265
do_validate(_, [], _, _) ->
 
266
    ok;
 
267
do_validate(Header, [{statuscode, _Code} | Rest], N, P) ->
 
268
    do_validate(Header, Rest, N, P);
 
269
do_validate(Header, [{header, HeaderField}|Rest], N, P) ->
 
270
    LowerHeaderField = http_util:to_lower(HeaderField),
 
271
    case lists:keysearch(LowerHeaderField, 1, Header) of
 
272
        {value, {LowerHeaderField, _Value}} ->
 
273
            ok;
 
274
        false ->
 
275
            test_server:fail({missing_header_field, LowerHeaderField, Header});
 
276
        _ ->
 
277
            test_server:fail({missing_header_field, LowerHeaderField, Header})
 
278
    end,
 
279
    do_validate(Header, Rest, N, P);
 
280
do_validate(Header, [{header, HeaderField, Value}|Rest],N,P) ->
 
281
    LowerHeaderField = http_util:to_lower(HeaderField),
 
282
    case lists:keysearch(LowerHeaderField, 1, Header) of
 
283
        {value, {LowerHeaderField, Value}} ->
 
284
            ok;
 
285
        false ->
 
286
            test_server:fail({wrong_header_field_value, LowerHeaderField, 
 
287
                              Header});
 
288
        _ ->
 
289
            test_server:fail({wrong_header_field_value, LowerHeaderField, 
 
290
                              Header})
 
291
    end,
 
292
    do_validate(Header, Rest, N, P);
 
293
do_validate(Header,[{no_last_modified,HeaderField}|Rest],N,P) ->
 
294
%    io:format("Header: ~p~nHeaderField: ~p~n",[Header,HeaderField]),
 
295
    case lists:keysearch(HeaderField,1,Header) of
 
296
        {value,_} ->
 
297
            test_server:fail({wrong_header_field_value, HeaderField, 
 
298
                              Header});
 
299
        _ ->
 
300
            ok
 
301
    end,
 
302
    do_validate(Header, Rest, N, P);
 
303
do_validate(Header, [_Unknown | Rest], N, P) ->
 
304
    do_validate(Header, Rest, N, P).
 
305
 
 
306
is_expect(RequestStr) ->
 
307
   
 
308
    case inets_regexp:match(RequestStr, "xpect:100-continue") of
 
309
        {match, _, _}->
 
310
            true;
 
311
        _ ->
 
312
            false
 
313
    end.
 
314
 
 
315
%% OTP-5775, content-length
 
316
check_body("GET /cgi-bin/erl/httpd_example:get_bin HTTP/1.0\r\n\r\n", 200, "text/html", Length, _Body) when Length /= 274->
 
317
    test_server:fail(content_length_error);
 
318
check_body("GET /cgi-bin/cgi_echo HTTP/1.0\r\n\r\n", 200, "text/plain", 
 
319
           _, Body) ->
 
320
    case size(Body) of
 
321
        100 ->
 
322
            ok;
 
323
        _ ->
 
324
            test_server:fail(content_length_error)
 
325
    end;
 
326
 
 
327
check_body(RequestStr, 200, "text/html", _, Body) ->
 
328
    HeadRequest = lists:sublist(RequestStr, 1, 3),
 
329
    case HeadRequest of
 
330
        "GET" ->
 
331
            inets_test_lib:check_body(binary_to_list(Body));
 
332
        _ ->
 
333
            ok
 
334
    end;
 
335
 
 
336
check_body(_, _, _, _,_) ->
 
337
    ok.
 
338
 
 
339
print(Proto, Data, #state{print = true}) ->
 
340
    test_server:format("Received ~p: ~p~n", [Proto, Data]);
 
341
print(_, _,  #state{print = false}) ->
 
342
    ok.
 
343
 
 
344
 
 
345
%% tsp(F) ->
 
346
%%     tsp(F, []).
 
347
tsp(F, A) ->
 
348
    test_server:format("~p ~p:" ++ F ++ "~n", [self(), ?MODULE | A]).
 
349