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

« back to all changes in this revision

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

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2005-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
 
 
21
-module(httpd_1_1).
 
22
-author('ingela@erix.ericsson.se').
 
23
 
 
24
-include("test_server.hrl").
 
25
-include("test_server_line.hrl").
 
26
-include_lib("kernel/include/file.hrl").
 
27
 
 
28
-export([host/4, chunked/4, expect/4, range/4, if_test/5, http_trace/4,
 
29
         head/4, mod_cgi_chunked_encoding_test/5]).
 
30
 
 
31
%% -define(all_keys_lower_case,true).
 
32
-ifndef(all_keys_lower_case).
 
33
-define(CONTENT_LENGTH, "Content-Length: ").
 
34
-define(CONTENT_RANGE,  "Content-Range: ").
 
35
-define(CONTENT_TYPE,   "Content-Type: ").
 
36
-else.
 
37
-define(CONTENT_LENGTH, "content-length:").
 
38
-define(CONTENT_RANGE,  "content-range:").
 
39
-define(CONTENT_TYPE,   "content-type:").
 
40
-endif.
 
41
 
 
42
 
 
43
%%-------------------------------------------------------------------------
 
44
%% Test cases starts here.
 
45
%%-------------------------------------------------------------------------
 
46
host(Type, Port, Host, Node) ->
 
47
    %% No host needed for HTTP/1.0
 
48
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
49
                                       "GET / HTTP/1.0\r\n\r\n", 
 
50
                                       [{statuscode, 200},
 
51
                                        {version, "HTTP/1.0"}]),
 
52
    %% No host must generate an error
 
53
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
54
                                       "GET / HTTP/1.1\r\n\r\n",
 
55
                                       [{statuscode, 400}]),
 
56
    
 
57
    %% If it is a fully qualified URL no host is needed
 
58
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
59
                                       "GET HTTP://"++ Host ++ ":" ++ 
 
60
                                       integer_to_list(Port)++
 
61
                                       "/ HTTP/1.1\r\n\r\n",
 
62
                                       [{statuscode, 200}]),
 
63
 
 
64
    %% If both look at the url.
 
65
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
 
66
                                       "GET HTTP://"++ Host ++ ":"++ 
 
67
                                       integer_to_list(Port) ++ 
 
68
                                       "/ HTTP/1.1\r\nHost:"++ Host ++
 
69
                                       "\r\n\r\n",[{statuscode, 200}]),
 
70
    
 
71
    %% Allow the request if its a Host field  
 
72
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
73
                                       "GET / HTTP/1.1\r\nHost:"++ 
 
74
                                       Host ++ "\r\n\r\n",
 
75
                                       [{statuscode, 200}]),
 
76
    ok.
 
77
    
 
78
chunked(Type, Port, Host, Node)->
 
79
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
80
                                       "GET / HTTP/1.1\r\n" 
 
81
                                       "Host:"++ Host ++"\r\n"
 
82
                                       "Transfer-Encoding:chunked\r\n"
 
83
                                       "\r\n"
 
84
                                       "A\r\n"
 
85
                                       "1234567890\r\n"
 
86
                                       "4\r\n"
 
87
                                       "HEJ!\r\n"
 
88
                                       "0\r\n\r\n",
 
89
                                       [{statuscode, 200}]),
 
90
    
 
91
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
92
                                       "GET / HTTP/1.1\r\n" 
 
93
                                       "Host:"++ Host ++"\r\n"
 
94
                                       "Transfer-Encoding:chunked\r\n"
 
95
                                       "Trailer:Content-Type\r\n"
 
96
                                       "\r\n" 
 
97
                                       "A\r\n" 
 
98
                                       "1234567890\r\n"
 
99
                                       "4\r\n" 
 
100
                                       "HEJ!\r\n"
 
101
                                       "0\r\n"
 
102
                                       "Content-Type:text/plain\r\n\r\n",
 
103
                                       [{statuscode, 200}]),
 
104
    ok.
 
105
 
 
106
expect(Type, Port, Host, Node)->
 
107
    Request="GET / HTTP/1.1\r\nHost:" ++ Host ++ 
 
108
        "\r\nContent-Length:22\r\nExpect:100-continue\r\n\r\n",
 
109
   
 
110
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
 
111
                                       Request, 
 
112
                                       [{statuscode, 100}]).
 
113
range(Type, Port, Host, Node)->
 
114
    
 
115
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
 
116
                                       "GET /range.txt HTTP/1.1\r\nHost:"
 
117
                                       ++ Host
 
118
                                       ++ "\r\nRange:bytes=110-120\r\n\r\n",
 
119
                                       [{statuscode,416}]),
 
120
    %%The simples of all range request a range
 
121
    Request1="GET /range.txt HTTP/1.1\r\nHost:" ++ Host ++
 
122
        "\r\nRange:bytes=0-9\r\n\r\n",    
 
123
    {ok, Socket1} = inets_test_lib:connect_byte(Type, Host, Port),
 
124
    inets_test_lib:send(Type, Socket1,Request1),
 
125
    ok = validateRangeRequest(Socket1,[],"1234567890",$2,$0,$6),
 
126
    inets_test_lib:close(Type,Socket1),
 
127
    
 
128
    %% Request the end of the file
 
129
    Request2 =
 
130
        "GET /range.txt HTTP/1.1\r\nHost:" ++ Host ++
 
131
        "\r\nRange:bytes=90-\r\n\r\n",    
 
132
    
 
133
    {ok, Socket2} = inets_test_lib:connect_byte(Type, Host, Port),
 
134
    inets_test_lib:send(Type, Socket2, Request2),
 
135
    ok = validateRangeRequest(Socket2,[],"1234567890",$2,$0,$6),
 
136
    inets_test_lib:close(Type,Socket2),
 
137
    
 
138
    %% The last byte in the file
 
139
    Request3 =
 
140
        "GET /range.txt HTTP/1.1\r\nHost:"++
 
141
        Host ++ "\r\nRange:bytes=-1\r\n\r\n",    
 
142
    {ok, Socket3} = inets_test_lib:connect_byte(Type, Host, Port),
 
143
    inets_test_lib:send(Type, Socket3,Request3),
 
144
     ok = validateRangeRequest(Socket3,[],"0",$2,$0,$6),
 
145
    inets_test_lib:close(Type, Socket3),
 
146
 
 
147
    %%Multi Range
 
148
    Request4 = "GET /range.txt HTTP/1.1\r\nHost:" ++ Host ++
 
149
        "\r\nRange:bytes=0-0,2-2,-1\r\n\r\n",    
 
150
    {ok, Socket4} = inets_test_lib:connect_byte(Type, Host, Port),
 
151
    inets_test_lib:send(Type, Socket4, Request4),
 
152
    ok = validateRangeRequest(Socket4,[],"130",$2,$0,$6),
 
153
    inets_test_lib:close(Type, Socket4).
 
154
 
 
155
if_test(Type, Port, Host, Node, DocRoot)->
 
156
    {ok, FileInfo} = 
 
157
        file:read_file_info(filename:join([DocRoot,"index.html"])),
 
158
    CreatedSec = 
 
159
        calendar:datetime_to_gregorian_seconds(FileInfo#file_info.mtime),
 
160
    
 
161
    Mod = httpd_util:rfc1123_date(calendar:gregorian_seconds_to_datetime(
 
162
                                      CreatedSec-1)),
 
163
 
 
164
    %% Test that we get the data when the file is modified
 
165
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
166
                                          "GET / HTTP/1.1\r\nHost:" ++ Host ++
 
167
                                          "\r\nIf-Modified-Since:" ++
 
168
                                          Mod ++ "\r\n\r\n",
 
169
                                          [{statuscode, 200}]),
 
170
     Mod1 = httpd_util:rfc1123_date(calendar:gregorian_seconds_to_datetime(
 
171
                                     CreatedSec+100)),
 
172
     ok = httpd_test_lib:verify_request(Type,Host,Port,Node, 
 
173
                                       "GET / HTTP/1.1\r\nHost:"
 
174
                                       ++ Host ++"\r\nIf-Modified-Since:"
 
175
                                       ++ Mod1 ++"\r\n\r\n",
 
176
                                       [{statuscode, 304}]),
 
177
    
 
178
     Mod2 =  httpd_util:rfc1123_date(calendar:gregorian_seconds_to_datetime(
 
179
                                      CreatedSec+1)),
 
180
     %% Control that the If-Unmodified-Header lmits the response
 
181
     ok = httpd_test_lib:verify_request(Type,Host,Port,Node, 
 
182
                                          "GET / HTTP/1.1\r\nHost:"
 
183
                                          ++ Host ++ 
 
184
                                          "\r\nIf-Unmodified-Since:" ++ Mod2 
 
185
                                          ++ "\r\n\r\n",
 
186
                                          [{statuscode, 200}]),
 
187
     Mod3 = httpd_util:rfc1123_date(calendar:gregorian_seconds_to_datetime(
 
188
                                     CreatedSec-1)),
 
189
    
 
190
     ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
191
                                          "GET / HTTP/1.1\r\nHost:"
 
192
                                          ++ Host ++ 
 
193
                                          "\r\nIf-Unmodified-Since:"++ Mod3 
 
194
                                          ++"\r\n\r\n",
 
195
                                          [{statuscode, 412}]),
 
196
 
 
197
     %% Control that we get the body when the etag match
 
198
     ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
199
                                          "GET / HTTP/1.1\r\nHost:" ++ Host 
 
200
                                          ++"\r\n"++
 
201
                                          "If-Match:"++ 
 
202
                                          httpd_util:create_etag(FileInfo)++
 
203
                                          "\r\n\r\n",
 
204
                                          [{statuscode, 200}]),
 
205
     ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
206
                                          "GET / HTTP/1.1\r\nHost:" ++ 
 
207
                                          Host ++ "\r\n"++
 
208
                                          "If-Match:NotEtag\r\n\r\n",
 
209
                                          [{statuscode, 412}]),
 
210
    
 
211
     %% Control the response when the if-none-match header is there
 
212
     ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
213
                                          "GET / HTTP/1.1\r\nHost:"
 
214
                                          ++ Host ++"\r\n"++
 
215
                                          "If-None-Match:NoTaag," ++ 
 
216
                                          httpd_util:create_etag(FileInfo) ++
 
217
                                          "\r\n\r\n",
 
218
                                          [{statuscode, 304}]),
 
219
  
 
220
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
221
                                          "GET / HTTP/1.1\r\nHost:"
 
222
                                          ++ Host ++ "\r\n"++
 
223
                                          "If-None-Match:NotEtag,"
 
224
                                          "NeihterEtag\r\n\r\n",
 
225
                                          [{statuscode,200}]).
 
226
    
 
227
http_trace(Type, Port, Host, Node)->
 
228
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
229
                                          "TRACE / HTTP/1.1\r\n" ++
 
230
                                          "Host:" ++ Host ++ "\r\n" ++
 
231
                                          "Max-Forwards:2\r\n\r\n",
 
232
                                          [{statuscode, 200}]),
 
233
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, 
 
234
                                       "TRACE / HTTP/1.0\r\n\r\n",
 
235
                                       [{statuscode, 501}, 
 
236
                                        {version, "HTTP/1.0"}]).
 
237
head(Type, Port, Host, Node)->
 
238
    %% mod_include 
 
239
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
 
240
                                       "HEAD /fsize.shtml HTTP/1.0\r\n\r\n", 
 
241
                                       [{statuscode, 200},
 
242
                                       {version, "HTTP/1.0"}]),
 
243
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
 
244
                        "HEAD /fsize.shtml HTTP/1.1\r\nhost:" ++ 
 
245
                        Host  ++ "\r\n\r\n", [{statuscode, 200}]),
 
246
    %% mod_esi
 
247
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
 
248
                        "HEAD /cgi-bin/erl/httpd_example/newformat"
 
249
                        " HTTP/1.0\r\n\r\n", [{statuscode, 200},
 
250
                                              {version, "HTTP/1.0"}]),
 
251
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node,
 
252
                        "HEAD /cgi-bin/erl/httpd_example/newformat "
 
253
                        "HTTP/1.1\r\nhost:" ++ Host  ++ "\r\n\r\n", 
 
254
                         [{statuscode, 200}]),
 
255
    %% mod_cgi
 
256
    Script =
 
257
        case test_server:os_type() of
 
258
            {win32, _} ->
 
259
                "printenv.bat";
 
260
            _ ->
 
261
                "printenv.sh"
 
262
        end,
 
263
    ok = httpd_test_lib:verify_request(Type,Host,Port,Node,"HEAD /cgi-bin/" 
 
264
                                       ++ Script ++ " HTTP/1.0\r\n\r\n", 
 
265
                                       [{statuscode, 200},
 
266
                                        {version, "HTTP/1.0"}]),
 
267
    ok = httpd_test_lib:verify_request(Type,Host,Port,Node, "HEAD /cgi-bin/"
 
268
                                       ++ Script ++ " HTTP/1.1\r\nhost:" ++ 
 
269
                                       Host  ++ "\r\n\r\n", 
 
270
                                       [{statuscode, 200}]).
 
271
 
 
272
mod_cgi_chunked_encoding_test(_, _, _, _, [])->
 
273
    ok;
 
274
mod_cgi_chunked_encoding_test(Type, Port, Host, Node, [Request| Rest])->
 
275
    ok = httpd_test_lib:verify_request(Type, Host, Port, Node, Request, 
 
276
                                       [{statuscode, 200}]),
 
277
    mod_cgi_chunked_encoding_test(Type, Port, Host, Node, Rest).
 
278
 
 
279
%%--------------------------------------------------------------------
 
280
%% Internal functions
 
281
%%--------------------------------------------------------------------
 
282
validateRangeRequest(Socket,Response,ValidBody,C,O,DE)->
 
283
    receive
 
284
        {tcp,Socket,Data} ->
 
285
            case string:str(Data,"\r\n") of
 
286
                0->
 
287
                    validateRangeRequest(Socket,
 
288
                                         Response ++ Data,
 
289
                                         ValidBody, C, O, DE);
 
290
                _N ->
 
291
                    case Response ++ Data of
 
292
                        [$H,$T,$T,$P,$/,$1,$.,$1,$ ,C,O,DE | _Rest]->
 
293
                            case [C,O,DE] of
 
294
                                "206" ->
 
295
                                    validateRangeRequest1(Socket,
 
296
                                                          Response ++ Data,
 
297
                                                          ValidBody);
 
298
                                _ ->
 
299
                                    bad_code
 
300
                            end;
 
301
                        _->
 
302
                            error
 
303
                    end
 
304
            end;
 
305
        _Error ->
 
306
            error
 
307
    end.
 
308
 
 
309
validateRangeRequest1(Socket, Response, ValidBody) ->
 
310
    case end_of_header(Response) of
 
311
        false ->
 
312
            receive
 
313
                {tcp,Socket,Data} ->
 
314
                    validateRangeRequest1(Socket, Response ++ Data, 
 
315
                                          ValidBody);
 
316
                _->
 
317
                    error
 
318
            end;
 
319
        {true, Head1, Body, _Size} ->
 
320
            %% In this case size will be 0 if it is a multipart so
 
321
            %% don't use it.
 
322
            validateRangeRequest2(Socket, Head1, Body, ValidBody,
 
323
                                  getRangeSize(Head1))
 
324
    end.
 
325
 
 
326
validateRangeRequest2(Socket, Head, Body, ValidBody, {multiPart,Boundary})->
 
327
    case endReached(Body,Boundary) of
 
328
        true ->
 
329
            validateMultiPartRangeRequest(Body, ValidBody, Boundary);
 
330
        false->
 
331
            receive
 
332
                {tcp, Socket, Data} ->
 
333
                    validateRangeRequest2(Socket, Head, Body ++ Data,
 
334
                                          ValidBody, {multiPart, Boundary});
 
335
                {tcp_closed, Socket} ->
 
336
                    error;
 
337
                _ ->
 
338
                    error
 
339
            end
 
340
    end;
 
341
 
 
342
validateRangeRequest2(Socket, Head, Body, ValidBody, BodySize) 
 
343
  when is_integer(BodySize) ->
 
344
    case length(Body)  of
 
345
        Size when Size =:= BodySize ->
 
346
            case Body of
 
347
                ValidBody ->
 
348
                    ok;
 
349
                Body ->
 
350
                    error
 
351
            end;        
 
352
        Size when Size < BodySize ->
 
353
            receive
 
354
                {tcp, Socket, Data} ->
 
355
                    validateRangeRequest2(Socket, Head,
 
356
                                          Body ++ Data, ValidBody, BodySize);
 
357
                _ ->
 
358
                    error
 
359
            end;
 
360
        _ ->
 
361
            error
 
362
    end.
 
363
 
 
364
 
 
365
validateMultiPartRangeRequest(Body, ValidBody, Boundary)->
 
366
    case inets_regexp:split(Body,"--"++Boundary++"--") of
 
367
        %%Last is the epilogue and must be ignored 
 
368
        {ok,[First | _Last]}->
 
369
            %%First is now the actuall http request body.
 
370
            case inets_regexp:split(First, "--" ++ Boundary) of
 
371
                %%Parts is now a list of ranges and the heads for each range
 
372
                %%Gues we try to split out the body
 
373
                {ok,Parts}->
 
374
                    case lists:flatten(lists:map(fun splitRange/1,Parts)) of
 
375
                        ValidBody->
 
376
                            ok;
 
377
                       ParsedBody->
 
378
                            error = ParsedBody
 
379
                    end
 
380
            end;
 
381
        _ ->
 
382
            error
 
383
    end.
 
384
 
 
385
 
 
386
splitRange(Part)->          
 
387
    case inets_regexp:split(Part, "\r\n\r\n") of
 
388
        {ok,[_, Body]} ->
 
389
            string:substr(Body, 1, length(Body) - 2);
 
390
        _ ->
 
391
            []
 
392
    end.
 
393
 
 
394
endReached(Body, Boundary)->
 
395
    EndBound = "--" ++ Boundary ++ "--",
 
396
    case string:str(Body, EndBound) of
 
397
        0 -> 
 
398
            false;
 
399
        _ ->
 
400
            true
 
401
    end.
 
402
            
 
403
getRangeSize(Head)->
 
404
    case controlMimeType(Head) of
 
405
        {multiPart, BoundaryString}->
 
406
            {multiPart, BoundaryString};
 
407
        _X1 ->
 
408
            case inets_regexp:match(Head, ?CONTENT_RANGE "bytes=.*\r\n") of
 
409
                {match, Start, Lenght} ->
 
410
                    %% Get the range data remove the fieldname and the
 
411
                    %% end of line.
 
412
                    RangeInfo = string:substr(Head, Start + 20, 
 
413
                                              Lenght - (20 - 2)),
 
414
                    rangeSize(RangeInfo);
 
415
                _X2 ->
 
416
                    error
 
417
            end
 
418
    end.
 
419
%%RangeInfo is NNN1-NNN2/NNN3
 
420
%%NNN1=RangeStartByte
 
421
%%NNN2=RangeEndByte
 
422
%%NNN3=total amount of bytes in file 
 
423
rangeSize([$=|RangeInfo]) ->
 
424
    rangeSize(RangeInfo);
 
425
rangeSize(RangeInfo) ->
 
426
    StartByte = lists:takewhile(fun(X)->
 
427
                                        num(X, true)
 
428
                                end, RangeInfo),
 
429
    RangeInfo2 = string:substr(RangeInfo, length(StartByte) + 2),
 
430
    EndByte = lists:takewhile(fun(X)->
 
431
                                      num(X,true)
 
432
                              end, RangeInfo2),
 
433
    case list_to_integer(EndByte) - list_to_integer(StartByte) of
 
434
        Val when is_number(Val) ->
 
435
            %%Add one since it is startByte to endbyte ie 0-0 is 1
 
436
            %%byte 0-99 is 100 bytes
 
437
            Val + 1; 
 
438
        _Val ->
 
439
            error
 
440
    end.
 
441
    
 
442
num(CharVal, RetVal) when (CharVal >= 48) andalso (CharVal =< 57) ->
 
443
    RetVal;
 
444
num(_CharVal, true) ->
 
445
    false;
 
446
num(_CharVal, false) ->
 
447
    true.
 
448
 
 
449
controlMimeType(Head)->
 
450
    case inets_regexp:match(Head,?CONTENT_TYPE "multipart/byteranges.*\r\n") of
 
451
        {match,Start,Length}->
 
452
            FieldNameLen = length(?CONTENT_TYPE "multipart/byteranges"),
 
453
            case clearBoundary(string:substr(Head, Start + FieldNameLen,
 
454
                                             Length - (FieldNameLen+2))) of
 
455
                error ->
 
456
                    error;
 
457
                BoundaryStr ->
 
458
                    {multiPart,BoundaryStr}
 
459
            end;
 
460
        nomatch->
 
461
            0;
 
462
        _ ->
 
463
            error
 
464
    end.
 
465
 
 
466
clearBoundary(Boundary)->
 
467
    case inets_regexp:match(Boundary, "boundary=.*\$") of
 
468
        {match, Start1, Length1}->
 
469
            BoundLen = length("boundary="),
 
470
            string:substr(Boundary, Start1 + BoundLen, Length1 - BoundLen);
 
471
        _ ->
 
472
            error
 
473
    end.
 
474
 
 
475
 
 
476
end_of_header(HeaderPart) ->
 
477
    case httpd_util:split(HeaderPart,"\r\n\r\n",2) of
 
478
        {ok, [Head, Body]} ->   
 
479
            {true, Head, Body, get_body_size(Head)};
 
480
        _Pos ->
 
481
            false
 
482
    end.
 
483
 
 
484
get_body_size(Head) ->
 
485
    case inets_regexp:match(Head,?CONTENT_LENGTH ".*\r\n") of
 
486
        {match, Start, Length} ->
 
487
            %% 15 is length of Content-Length, 
 
488
            %% 17 Is length of Content-Length and \r\
 
489
            S = list_to_integer(
 
490
                  string:strip(string:substr(Head, Start + 15, Length-17))),
 
491
            S;
 
492
        _->
 
493
            0
 
494
     end.