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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/inets/httpd_request_handler.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
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id: httpd_request_handler.erl,v 1.1 2008/12/17 09:53:34 mikpe Exp $
 
17
%%
 
18
-module(httpd_request_handler).
 
19
 
 
20
%% app internal api
 
21
-export([start_link/2, synchronize/3]).
 
22
 
 
23
%% module internal api
 
24
-export([connection/2, do_next_connection/6, read_header/7]). 
 
25
-export([parse_trailers/1, newline/1]).
 
26
 
 
27
-include("httpd.hrl").
 
28
-include("httpd_verbosity.hrl").
 
29
 
 
30
 
 
31
%% start_link
 
32
 
 
33
start_link(Manager, ConfigDB) ->
 
34
    Pid = proc_lib:spawn(?MODULE, connection, [Manager, ConfigDB]),
 
35
    {ok, Pid}.
 
36
 
 
37
 
 
38
%% synchronize
 
39
 
 
40
synchronize(Pid, SocketType, Socket) ->
 
41
    Pid ! {synchronize, SocketType, Socket}.
 
42
 
 
43
% connection 
 
44
 
 
45
connection(Manager, ConfigDB) ->
 
46
    {SocketType, Socket, {Status, Verbosity}} = await_synchronize(Manager),
 
47
    put(sname,self()),
 
48
    put(verbosity,?vvalidate(Verbosity)),
 
49
    connection1(Status, Manager, ConfigDB, SocketType, Socket).
 
50
 
 
51
 
 
52
connection1({reject, busy}, Manager, ConfigDB, SocketType, Socket) ->
 
53
    handle_busy(Manager, ConfigDB, SocketType, Socket);
 
54
 
 
55
connection1({reject, blocked}, Manager, ConfigDB, SocketType, Socket) ->
 
56
    handle_blocked(Manager, ConfigDB, SocketType, Socket);
 
57
 
 
58
connection1(accept, Manager, ConfigDB, SocketType, Socket) ->
 
59
    handle_connection(Manager, ConfigDB, SocketType, Socket).
 
60
 
 
61
 
 
62
%% await_synchronize
 
63
 
 
64
await_synchronize(Manager) ->
 
65
    receive
 
66
        {synchronize, SocketType, Socket} ->
 
67
            ?vlog("received syncronize: "
 
68
                  "~n   SocketType: ~p"
 
69
                  "~n   Socket:     ~p", [SocketType, Socket]),
 
70
            {SocketType, Socket, httpd_manager:new_connection(Manager)}
 
71
    after 5000 ->
 
72
            exit(synchronize_timeout)
 
73
    end.
 
74
 
 
75
 
 
76
% handle_busy
 
77
 
 
78
handle_busy(Manager, ConfigDB, SocketType, Socket) ->
 
79
    ?vlog("handle busy: ~p", [Socket]),
 
80
    MaxClients = httpd_util:lookup(ConfigDB, max_clients, 150),
 
81
    String = io_lib:format("heavy load (>~w processes)", [MaxClients]),
 
82
    reject_connection(Manager, ConfigDB, SocketType, Socket, String).
 
83
 
 
84
 
 
85
% handle_blocked 
 
86
 
 
87
handle_blocked(Manager, ConfigDB, SocketType, Socket) ->
 
88
    ?vlog("handle blocked: ~p", [Socket]),
 
89
    String = "Server maintenance performed, try again later",
 
90
    reject_connection(Manager, ConfigDB, SocketType, Socket, String).
 
91
 
 
92
 
 
93
% reject_connection
 
94
 
 
95
reject_connection(Manager, ConfigDB, SocketType, Socket, Info) ->
 
96
    String = lists:flatten(Info),
 
97
    ?vtrace("send status (503) message", []),
 
98
    httpd_response:send_status(SocketType, Socket, 503, String, ConfigDB),
 
99
    %% This ugly thing is to make ssl deliver the message, before the close...
 
100
    close_sleep(SocketType, 1000),  
 
101
    ?vtrace("close the socket", []),
 
102
    close(SocketType, Socket, ConfigDB).
 
103
 
 
104
 
 
105
% handle_connection
 
106
 
 
107
handle_connection(Manager, ConfigDB, SocketType, Socket) ->
 
108
    ?vlog("handle connection: ~p", [Socket]),
 
109
    Resolve     = httpd_socket:resolve(SocketType),
 
110
    Peername    = httpd_socket:peername(SocketType, Socket),
 
111
    InitData    = #init_data{peername=Peername, resolve=Resolve},
 
112
    TimeOut     = httpd_util:lookup(ConfigDB, keep_alive_timeout, 150000),
 
113
    NrOfRequest = httpd_util:lookup(ConfigDB, max_keep_alive_request, forever),
 
114
    ?MODULE:do_next_connection(ConfigDB, InitData, 
 
115
                               SocketType, Socket,NrOfRequest,TimeOut),
 
116
    ?vlog("handle connection: done", []),
 
117
    httpd_manager:done_connection(Manager),
 
118
    ?vlog("handle connection: close socket", []),
 
119
    close(SocketType, Socket, ConfigDB).
 
120
 
 
121
 
 
122
% do_next_connection
 
123
do_next_connection(_ConfigDB, _InitData, _SocketType, _Socket, NrOfRequests, 
 
124
                   _Timeout) when NrOfRequests < 1 -> 
 
125
    ?vtrace("do_next_connection: done", []),
 
126
    ok;
 
127
do_next_connection(ConfigDB, InitData, SocketType, Socket, NrOfRequests, 
 
128
                   Timeout) ->
 
129
    Peername = InitData#init_data.peername,
 
130
    case (catch read(ConfigDB, SocketType, Socket, InitData, Timeout)) of
 
131
        {'EXIT', Reason} ->
 
132
            ?vlog("exit reading from socket: ~p",[Reason]),
 
133
            error_logger:error_report({'EXIT',Reason}),
 
134
            String = 
 
135
                lists:flatten(
 
136
                  io_lib:format("exit reading from socket: ~p => ~n~p~n",
 
137
                                [Socket, Reason])),
 
138
            error_log(mod_log, 
 
139
                      SocketType, Socket, ConfigDB, Peername, String),
 
140
            error_log(mod_disk_log, 
 
141
                      SocketType, Socket, ConfigDB, Peername, String);
 
142
        {error, Reason} ->
 
143
            handle_read_error(Reason,SocketType,Socket,ConfigDB,Peername);
 
144
        Info when record(Info, mod) ->
 
145
            case Info#mod.connection of
 
146
                true ->
 
147
                    ReqTimeout = httpd_util:lookup(ConfigDB, 
 
148
                                                   keep_alive_timeout, 150000),
 
149
                    ?MODULE:do_next_connection(ConfigDB,          InitData,
 
150
                                               SocketType,        Socket,
 
151
                                               dec(NrOfRequests), ReqTimeout);
 
152
                _ ->
 
153
                    ok
 
154
            end;
 
155
        _ ->
 
156
            ok
 
157
    end.
 
158
 
 
159
    
 
160
 
 
161
%% read
 
162
read(ConfigDB, SocketType, Socket, InitData, Timeout) ->
 
163
    ?vdebug("read from socket ~p with Timeout ~p",[Socket, Timeout]),
 
164
    MaxHdrSz = httpd_util:lookup(ConfigDB, max_header_size, 10240),
 
165
    case ?MODULE:read_header(SocketType, Socket, Timeout, MaxHdrSz, 
 
166
                             ConfigDB, InitData, []) of
 
167
        {socket_closed, Reason} ->
 
168
            ?vlog("Socket closed while reading request header: "
 
169
                  "~n   ~p", [Reason]),
 
170
            socket_close;
 
171
        {error, Error} ->
 
172
            {error, Error};
 
173
        {ok, Info, EntityBodyPart} ->
 
174
            read1(SocketType, Socket, ConfigDB, InitData, Timeout, Info,
 
175
                  EntityBodyPart)
 
176
    end.
 
177
 
 
178
%% Got the head and maybe a part of the body: read in the rest
 
179
read1(SocketType, Socket, ConfigDB, InitData, Timeout, Info, BodyPart)->
 
180
    MaxBodySz     = httpd_util:lookup(ConfigDB, max_body_size, nolimit),
 
181
    ContentLength = content_length(Info),
 
182
    ?vtrace("ContentLength: ~p", [ContentLength]),
 
183
    case read_entity_body(SocketType, Socket, Timeout, MaxBodySz,
 
184
                          ContentLength, BodyPart, Info, ConfigDB) of
 
185
        {socket_closed, Reason} ->
 
186
            ?vlog("Socket closed while reading request body: "
 
187
                  "~n   ~p", [Reason]),
 
188
            socket_close;
 
189
        {ok, EntityBody} ->
 
190
            finish_request(EntityBody, [], Info); 
 
191
        {ok, ExtraHeader, EntityBody} ->
 
192
            finish_request(EntityBody, ExtraHeader, Info);
 
193
        Response ->
 
194
            httpd_socket:close(SocketType, Socket),
 
195
            socket_closed
 
196
            %% Catch up all bad return values
 
197
    end.
 
198
 
 
199
 
 
200
%% The request is read in send it forward to the module that 
 
201
%% generates the response
 
202
 
 
203
finish_request(EntityBody, ExtraHeader, 
 
204
               #mod{parsed_header = ParsedHeader} = Info)->
 
205
    ?DEBUG("finish_request -> ~n"
 
206
        "    EntityBody:   ~p~n"
 
207
        "    ExtraHeader:  ~p~n"
 
208
        "    ParsedHeader: ~p~n",
 
209
        [EntityBody, ExtraHeader, ParsedHeader]),
 
210
    httpd_response:send(Info#mod{parsed_header = ParsedHeader ++ ExtraHeader,
 
211
                                 entity_body   = EntityBody}).
 
212
 
 
213
 
 
214
%% read_header
 
215
 
 
216
%% This algorithm rely on the buffer size of the inet driver together
 
217
%% with the {active, once} socket option. Atmost one message of this 
 
218
%% size will be received at a given time. When a full header has been 
 
219
%% read, the body is read with the recv function (the body size is known). 
 
220
%%
 
221
read_header(SocketType, Socket, Timeout, MaxHdrSz, ConfigDB, 
 
222
            InitData, SoFar0) ->
 
223
    T = t(),
 
224
    %% remove any newlines at the begining, they might be crap from ?
 
225
    SoFar = remove_newline(SoFar0),
 
226
                                   
 
227
    case terminated_header(MaxHdrSz, SoFar) of
 
228
        {true, Header, EntityBodyPart} ->
 
229
            ?vdebug("read_header -> done reading header: "
 
230
                    "~n   length(Header):         ~p"
 
231
                    "~n   length(EntityBodyPart): ~p", 
 
232
                    [length(Header), length(EntityBodyPart)]),
 
233
            transform_header(SocketType, Socket, Header, ConfigDB, InitData, 
 
234
                             EntityBodyPart);
 
235
        false ->
 
236
            ?vtrace("read_header -> "
 
237
                    "~n   set active = 'once' and "
 
238
                    "await a chunk of the header", []),
 
239
            
 
240
            case httpd_socket:active_once(SocketType, Socket) of
 
241
                ok ->
 
242
                    receive
 
243
                        %% 
 
244
                        %% TCP
 
245
                        %% 
 
246
                        {tcp, Socket, Data} ->
 
247
                            ?vtrace("read_header(ip) -> got some data: ~p", 
 
248
                                [sz(Data)]),
 
249
                            ?MODULE:read_header(SocketType, Socket, 
 
250
                                                Timeout - (t()-T), 
 
251
                                                MaxHdrSz, ConfigDB, 
 
252
                                                InitData, SoFar ++ Data);
 
253
                        {tcp_closed, Socket} ->
 
254
                            ?vtrace("read_header(ip) -> socket closed",[]),
 
255
                            {socket_closed,normal};
 
256
                        {tcp_error, Socket, Reason} ->
 
257
                            ?vtrace("read_header(ip) -> socket error: ~p",
 
258
                                [Reason]),
 
259
                            {socket_closed, Reason};
 
260
                        
 
261
                        %% 
 
262
                        %% SSL
 
263
                        %% 
 
264
                        {ssl, Socket, Data} ->
 
265
                            ?vtrace("read_header(ssl) -> got some data: ~p", 
 
266
                                [sz(Data)]),
 
267
                            ?MODULE:read_header(SocketType, Socket, 
 
268
                                                Timeout - (t()-T), 
 
269
                                                MaxHdrSz, ConfigDB, 
 
270
                                                InitData, SoFar ++ Data);
 
271
                        {ssl_closed, Socket} ->
 
272
                            ?vtrace("read_header(ssl) -> socket closed", []),
 
273
                            {socket_closed, normal};
 
274
                        {ssl_error, Socket, Reason} ->
 
275
                            ?vtrace("read_header(ssl) -> socket error: ~p", 
 
276
                                [Reason]),
 
277
                            {socket_closed, Reason}
 
278
                    
 
279
                    after Timeout ->
 
280
                            ?vlog("read_header -> timeout", []),
 
281
                            {socket_closed, timeout}
 
282
                    end;
 
283
 
 
284
                Error ->
 
285
                    httpd_response:send_status(SocketType, Socket, 
 
286
                                               500, none, ConfigDB),
 
287
                    Error
 
288
            end
 
289
    end.
 
290
 
 
291
 
 
292
terminated_header(MaxHdrSz, Data) ->
 
293
    D1 = lists:flatten(Data),
 
294
    ?vtrace("terminated_header -> Data size: ~p",[sz(D1)]),
 
295
    case hsplit(MaxHdrSz,[],D1) of
 
296
        not_terminated ->
 
297
            false;
 
298
        [Header, EntityBodyPart] ->
 
299
            {true, Header++"\r\n\r\n",EntityBodyPart}
 
300
    end.
 
301
 
 
302
 
 
303
transform_header(SocketType, Socket, Request, ConfigDB, InitData, BodyPart) ->
 
304
    case httpd_parse:request_header(Request) of
 
305
        {not_implemented, RequestLine, Method, RequestURI, ParsedHeader,
 
306
         HTTPVersion} ->
 
307
            httpd_response:send_status(SocketType, Socket, 501,
 
308
                                       {Method, RequestURI, HTTPVersion},
 
309
                                       ConfigDB),
 
310
            {error,"Not Implemented"};
 
311
        {bad_request, {forbidden, URI}} ->
 
312
            httpd_response:send_status(SocketType, Socket, 403, URI, ConfigDB),
 
313
            {error,"Forbidden Request"};
 
314
        {bad_request, Reason} ->
 
315
            httpd_response:send_status(SocketType, Socket, 400, none, 
 
316
                                       ConfigDB),
 
317
            {error,"Malformed request"};
 
318
        {ok,[Method, RequestURI, HTTPVersion, RequestLine, ParsedHeader]} ->
 
319
            ?DEBUG("send -> ~n"
 
320
                   "    Method:      ~p~n"
 
321
                   "    RequestURI:  ~p~n"
 
322
                   "    HTTPVersion: ~p~n"
 
323
                   "    RequestLine: ~p~n",
 
324
                   [Method, RequestURI, HTTPVersion, RequestLine]),
 
325
            {ok, Info} = 
 
326
                httpd_parse:get_request_record(Socket, SocketType, ConfigDB,
 
327
                                               Method, RequestURI, HTTPVersion,
 
328
                                               RequestLine, ParsedHeader,
 
329
                                               [], InitData),
 
330
            %% Control that the Host header field is provided
 
331
            case Info#mod.absolute_uri of
 
332
                nohost ->
 
333
                    case Info#mod.http_version of
 
334
                        "HTTP/1.1" ->
 
335
                            httpd_response:send_status(Info, 400, none),
 
336
                            {error,"No host specified"};
 
337
                        _ ->
 
338
                            {ok, Info, BodyPart}
 
339
                    end;
 
340
                _ ->
 
341
                    {ok, Info, BodyPart}
 
342
            end
 
343
    end.
 
344
 
 
345
 
 
346
hsplit(_MaxHdrSz, Accu,[]) ->
 
347
    not_terminated;
 
348
hsplit(_MaxHdrSz, Accu, [ $\r, $\n, $\r, $\n | Tail]) ->
 
349
    [lists:reverse(Accu), Tail];
 
350
hsplit(nolimit, Accu, [H|T]) ->
 
351
    hsplit(nolimit,[H|Accu],T);
 
352
hsplit(MaxHdrSz, Accu, [H|T]) when length(Accu) < MaxHdrSz ->
 
353
    hsplit(MaxHdrSz,[H|Accu],T);
 
354
hsplit(MaxHdrSz, Accu, D) ->
 
355
    throw({error,{header_too_long,length(Accu),length(D)}}).
 
356
 
 
357
 
 
358
 
 
359
%%----------------------------------------------------------------------
 
360
%% The http/1.1 standard chapter 8.2.3 says that a request containing
 
361
%% An Except header-field must be responded to by 100 (Continue) by 
 
362
%% the server before the client sends the body.
 
363
%%----------------------------------------------------------------------
 
364
 
 
365
read_entity_body(SocketType, Socket, Timeout, Max, Length, BodyPart, Info,
 
366
                 ConfigDB) when integer(Max) ->
 
367
    case expect(Info#mod.http_version, Info#mod.parsed_header, ConfigDB) of
 
368
        continue when Max > Length ->
 
369
            ?DEBUG("read_entity_body()->100 Continue  ~n", []),
 
370
            httpd_response:send_status(Info, 100, ""),
 
371
            read_entity_body2(SocketType, Socket, Timeout, Max, Length, 
 
372
                              BodyPart, Info, ConfigDB);
 
373
        continue when Max < Length ->
 
374
            httpd_response:send_status(Info, 417, "Body to big"),
 
375
            httpd_socket:close(SocketType, Socket),
 
376
            {socket_closed,"Expect denied according to size"};
 
377
        break ->
 
378
            httpd_response:send_status(Info, 417, "Method not allowed"),
 
379
            httpd_socket:close(SocketType, Socket),
 
380
            {socket_closed,"Expect conditions was not fullfilled"};
 
381
        no_expect_header ->
 
382
            read_entity_body2(SocketType, Socket, Timeout, Max, Length,
 
383
                              BodyPart, Info, ConfigDB);
 
384
        http_1_0_expect_header ->
 
385
            httpd_response:send_status(Info, 400, 
 
386
                                       "Only HTTP/1.1 Clients "
 
387
                                       "may use the Expect Header"),
 
388
            httpd_socket:close(SocketType, Socket),
 
389
            {socket_closed,"Due to a HTTP/1.0 expect header"}
 
390
    end;
 
391
 
 
392
read_entity_body(SocketType, Socket, Timeout, Max, Length, BodyPart,
 
393
                 Info, ConfigDB) ->
 
394
    case expect(Info#mod.http_version, Info#mod.parsed_header, ConfigDB) of
 
395
        continue ->
 
396
            ?DEBUG("read_entity_body() -> 100 Continue  ~n", []),
 
397
            httpd_response:send_status(Info, 100, ""),
 
398
            read_entity_body2(SocketType, Socket, Timeout, Max, Length,
 
399
                              BodyPart, Info, ConfigDB);
 
400
        break->
 
401
            httpd_response:send_status(Info, 417, "Method not allowed"),
 
402
            httpd_socket:close(SocketType, Socket),
 
403
            {socket_closed,"Expect conditions was not fullfilled"};
 
404
        no_expect_header ->
 
405
            read_entity_body2(SocketType, Socket, Timeout, Max, Length, 
 
406
                              BodyPart, Info, ConfigDB);
 
407
        http_1_0_expect_header ->
 
408
            httpd_response:send_status(Info, 400, 
 
409
                                       "HTTP/1.0 Clients are not allowed "
 
410
                                       "to use the Expect Header"),
 
411
            httpd_socket:close(SocketType, Socket),
 
412
            {socket_closed,"Expect header field in an HTTP/1.0 request"}
 
413
        end.    
 
414
    
 
415
%%----------------------------------------------------------------------
 
416
%% control if the body is transfer encoded
 
417
%%----------------------------------------------------------------------
 
418
read_entity_body2(SocketType, Socket, Timeout, Max, Length, BodyPart, 
 
419
                  Info, ConfigDB) ->
 
420
    ?DEBUG("read_entity_body2() -> "
 
421
        "~n   Max:    ~p"
 
422
        "~n   Length: ~p"
 
423
        "~n   Socket: ~p", [Max, Length, Socket]),
 
424
      
 
425
    case transfer_coding(Info) of
 
426
        {chunked, ChunkedData} ->
 
427
            ?DEBUG("read_entity_body2() -> "
 
428
                "Transfer-encoding: Chunked Data: BodyPart ~s", [BodyPart]),
 
429
            read_chunked_entity(Info, Timeout, Max, Length, ChunkedData, [],
 
430
                                BodyPart);
 
431
        unknown_coding ->
 
432
            ?DEBUG("read_entity_body2() -> Transfer-encoding: Unknown",[]),
 
433
            httpd_response:send_status(Info, 501, "Unknown Transfer-Encoding"),
 
434
            httpd_socket:close(SocketType, Socket),
 
435
            {socket_closed,"Expect conditions was not fullfilled"};
 
436
        none ->
 
437
              ?DEBUG("read_entity_body2() -> Transfer-encoding: none",[]),
 
438
            read_entity_body(SocketType, Socket, Timeout, Max, Length, 
 
439
                             BodyPart)
 
440
    end.
 
441
 
 
442
        
 
443
%%----------------------------------------------------------------------
 
444
%% The body was plain read it from the socket
 
445
%% ----------------------------------------------------------------------
 
446
read_entity_body(_SocketType, _Socket, _Timeout, _Max, 0, _BodyPart) ->
 
447
    {ok, []};
 
448
 
 
449
read_entity_body(_SocketType, _Socket, _Timeout, Max, Len, _BodyPart) 
 
450
  when Max < Len ->
 
451
    ?vlog("body to long: "
 
452
          "~n   Max: ~p"
 
453
          "~n   Len: ~p", [Max,Len]),
 
454
    throw({error,{body_too_long,Max,Len}});
 
455
 
 
456
%% OTP-4409: Fixing POST problem
 
457
read_entity_body(_,_,_,_, Len, BodyPart) when Len == length(BodyPart) ->
 
458
    ?vtrace("read_entity_body -> done when"
 
459
        "~n   Len = length(BodyPart): ~p", [Len]),
 
460
    {ok, BodyPart};
 
461
 
 
462
%% OTP-4550: Fix problem with trailing garbage produced by some clients.
 
463
read_entity_body(_, _, _, _, Len, BodyPart) when Len < length(BodyPart) ->
 
464
    ?vtrace("read_entity_body -> done when"
 
465
        "~n   Len:              ~p"
 
466
        "~n   length(BodyPart): ~p", [Len, length(BodyPart)]),
 
467
    {ok, lists:sublist(BodyPart,Len)};
 
468
 
 
469
read_entity_body(SocketType, Socket, Timeout, Max, Len, BodyPart) ->
 
470
    ?vtrace("read_entity_body -> entry when"
 
471
        "~n   Len:              ~p"
 
472
        "~n   length(BodyPart): ~p", [Len, length(BodyPart)]),
 
473
    %% OTP-4548:
 
474
    %% The length calculation was previously (inets-2.*) done in the 
 
475
    %% read function. As of 3.0 it was removed from read but not 
 
476
    %% included here.
 
477
    L = Len - length(BodyPart), 
 
478
    case httpd_socket:recv(SocketType, Socket, L, Timeout) of
 
479
        {ok, Body} ->
 
480
            ?vtrace("read_entity_body -> received some data:"
 
481
                "~n   length(Body): ~p", [length(Body)]),
 
482
            {ok, BodyPart ++ Body};
 
483
        {error,closed} ->
 
484
            {socket_closed,normal};
 
485
        {error,etimedout} ->
 
486
            {socket_closed, timeout};
 
487
        {error,Reason} ->
 
488
            {socket_closed, Reason}; 
 
489
        Other ->
 
490
            {socket_closed, Other}
 
491
    end.
 
492
 
 
493
 
 
494
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
495
%% If the body of the message is encoded used the chunked transfer encoding 
 
496
%% it looks somethin like this:
 
497
%% METHOD URI HTTP/VSN
 
498
%% Transfer-Encoding: chunked
 
499
%% CRLF
 
500
%% ChunkSize
 
501
%% Chunk
 
502
%% ChunkSize
 
503
%% Chunk
 
504
%% 0
 
505
%% Trailer
 
506
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
507
 
 
508
read_chunked_entity(Info, Timeout, Max, Length, ChunkedData, Body, []) ->
 
509
    ?DEBUG("read_chunked_entity()->:no_chunks ~n", []),
 
510
    read_chunked_entity(Info#mod.socket_type, Info#mod.socket,
 
511
                        Timeout, Max, Length, ChunkedData, Body, 
 
512
                        Info#mod.config_db, Info);
 
513
 
 
514
read_chunked_entity(Info, Timeout, Max, Length, ChunkedData, Body, BodyPart) ->
 
515
    %% Get the size
 
516
    ?DEBUG("read_chunked_entity() -> PrefetchedBodyPart: ~p ~n",[BodyPart]),
 
517
    case parse_chunk_size(Info, Timeout, BodyPart) of
 
518
        {ok, Size, NewBodyPart} when Size > 0 ->
 
519
            ?DEBUG("read_chunked_entity() -> Size: ~p ~n", [Size]),
 
520
            case parse_chunked_entity_body(Info, Timeout, Max, length(Body),
 
521
                                           Size, NewBodyPart) of
 
522
                {ok, Chunk, NewBodyPart1} ->
 
523
                    ?DEBUG("read_chunked_entity()->Size: ~p ~n", [Size]),
 
524
                    read_chunked_entity(Info, Timeout, Max, Length, 
 
525
                                        ChunkedData, Body ++ Chunk,
 
526
                                        NewBodyPart1);
 
527
                OK ->
 
528
                    httpd_socket:close(Info#mod.socket_type, Info#mod.socket),
 
529
                    {socket_closed, error}
 
530
            end;
 
531
        {ok, 0, Trailers} ->
 
532
           ?DEBUG("read_chunked_entity()->Size: 0, Trailers: ~s Body: ~s ~n", 
 
533
                [Trailers, Body]),
 
534
            case parse_chunk_trailer(Info, Timeout, Info#mod.config_db,
 
535
                                     Trailers) of
 
536
                {ok, TrailerFields} ->
 
537
                    {ok, TrailerFields, Body};
 
538
                _->
 
539
                    {ok, []}
 
540
            end;
 
541
        Error ->
 
542
            Error
 
543
    end.
 
544
 
 
545
 
 
546
parse_chunk_size(Info, Timeout, BodyPart) ->
 
547
    case httpd_util:split(remove_newline(BodyPart), "\r\n", 2) of
 
548
        {ok, [Size, Body]} ->
 
549
            ?DEBUG("parse_chunk_size()->Size: ~p ~n", [Size]),
 
550
            {ok, httpd_util:hexlist_to_integer(Size), Body};
 
551
        {ok, [Size]} ->
 
552
            ?DEBUG("parse_chunk_size()->Size: ~p ~n", [Size]),
 
553
            Sz = get_chunk_size(Info#mod.socket_type,
 
554
                                Info#mod.socket, Timeout, 
 
555
                                lists:reverse(Size)),
 
556
            {ok, Sz, []}
 
557
    end.
 
558
 
 
559
%%----------------------------------------------------------------------
 
560
%% We got the chunk size get the chunk
 
561
%%
 
562
%% Max:     Max numbers of bytes to read may also be undefined 
 
563
%% Length:  Numbers of bytes already read
 
564
%% Size     Numbers of byte to read for the chunk
 
565
%%----------------------------------------------------------------------
 
566
 
 
567
%% body to big
 
568
parse_chunked_entity_body(Info, Timeout, Max, Length, Size, BodyPart) 
 
569
  when Max =< (Length + Size) ->
 
570
    {error, body_to_big};
 
571
 
 
572
%% Prefetched body part is bigger than the current chunk
 
573
%% (i.e. BodyPart includes more than one chunk)
 
574
parse_chunked_entity_body(Info, Timeout, Max, Length, Size, BodyPart) 
 
575
  when (Size+2) =< length(BodyPart) ->
 
576
    Chunk = string:substr(BodyPart, 1, Size),
 
577
    Rest  = string:substr(BodyPart, Size+3),
 
578
    ?DEBUG("parse_chunked_entity_body() -> ~nChunk: ~s ~nRest: ~s ~n", 
 
579
        [Chunk, Rest]),
 
580
    {ok, Chunk, Rest};
 
581
 
 
582
 
 
583
%% We just got a part of the current chunk
 
584
parse_chunked_entity_body(Info, Timeout, Max, Length, Size, BodyPart) ->
 
585
    %% OTP-4551:
 
586
    %% Subtracting BodyPart from Size does not produce an integer 
 
587
    %% when BodyPart is a list...
 
588
    Remaining = Size - length(BodyPart), 
 
589
    LastPartOfChunk = read_chunked_entity_body(Info#mod.socket_type,
 
590
                                               Info#mod.socket,
 
591
                                               Timeout, Max, 
 
592
                                               Length, Remaining),
 
593
    %% Remove newline
 
594
    httpd_socket:recv(Info#mod.socket_type, Info#mod.socket, 2, Timeout),
 
595
    ?DEBUG("parse_chunked_entity_body() -> "
 
596
        "~nBodyPart: ~s"
 
597
        "~nLastPartOfChunk: ~s  ~n",
 
598
        [BodyPart, LastPartOfChunk]),
 
599
    {ok, BodyPart ++ LastPartOfChunk, []}.
 
600
    
 
601
 
 
602
%%----------------------------------------------------------------------
 
603
%% If the data we got along with the header contained the whole chunked body 
 
604
%% It may aswell contain the trailer :-(
 
605
%%----------------------------------------------------------------------
 
606
%% Either trailer begins with  \r\n and then all data is there or 
 
607
%% The trailer has data  then read upto \r\n\r\n
 
608
parse_chunk_trailer(Info,Timeout,ConfigDB,"\r\n")->
 
609
    {ok,[]};
 
610
parse_chunk_trailer(Info,Timeout,ConfigDB,Trailers) ->
 
611
    ?DEBUG("parse_chunk_trailer()->Trailers: ~s ~n", [Trailers]),
 
612
    case string:rstr(Trailers,"\r\n\r\n") of
 
613
        0 ->
 
614
            MaxHdrSz=httpd_util:lookup(ConfigDB, max_header_size, 10240),
 
615
            read_trailer_end(Info,Timeout,MaxHdrSz,Trailers);
 
616
        _->
 
617
            %%We got the whole header parse it up
 
618
            parse_trailers(Trailers)
 
619
    end.
 
620
 
 
621
parse_trailers(Trailer)->
 
622
    ?DEBUG("parse_trailer()->Trailer: ~s",[Trailer]),
 
623
    {ok,[Fields0|Crap]}=httpd_util:split(Trailer,"\r\n\r\n",2),
 
624
    Fields=string:tokens(Fields0,"\r\n"),
 
625
        [getTrailerField(X)||X<-Fields,lists:member($:,X)].
 
626
 
 
627
 
 
628
read_trailer_end(Info,Timeout,MaxHdrSz,[])->
 
629
    ?DEBUG("read_trailer_end()->[]",[]),
 
630
    case read_trailer(Info#mod.socket_type,Info#mod.socket,
 
631
                 Timeout,MaxHdrSz,[],[],
 
632
                      httpd_util:key1search(Info#mod.parsed_header,"trailer",[])) of
 
633
        {ok,Trailers}->
 
634
            Trailers;
 
635
        _->
 
636
            []
 
637
    end;
 
638
read_trailer_end(Info,Timeout,MaxHdrSz,Trailers)->
 
639
    ?DEBUG("read_trailer_end()->Trailers: ~s ~n ",[Trailers]),
 
640
    %% Get the last paart of the the last headerfield
 
641
    End=lists:reverse(lists:takewhile(fun(X)->case X of 10 ->false;13->false;_ ->true end end,lists:reverse(Trailers))),
 
642
    Fields0=regexp:split(Trailers,"\r\n"),
 
643
    %%Get rid of the last header field
 
644
    [_Last|Fields]=lists:reverse(Fields0),
 
645
    Headers=[getTrailerField(X)||X<-Fields,lists:member($:,X)],
 
646
    case read_trailer(Info#mod.socket_type,Info#mod.socket,
 
647
                 Timeout,MaxHdrSz,Headers,End,
 
648
                      httpd_util:key1search(Info#mod.parsed_header,"trailer",[])) of
 
649
        {ok,Trailers}->
 
650
            Trailers;
 
651
        _->
 
652
            []
 
653
    end.
 
654
 
 
655
 
 
656
 
 
657
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
658
%% The code below is a a good way to read in chunked encoding but 
 
659
%% that require that the encoding comes from a stream and not from a list 
 
660
%%&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&&
 
661
 
 
662
%%----------------------------------------------------------------------
 
663
%% The body is encoded by chubnked encoding read it in
 
664
%% ChunkedData= Chunked extensions
 
665
%% Body= the inread chunked body
 
666
%% Max:     Max numbers of bytes to read
 
667
%% Length:  Numbers of bytes already readed
 
668
%% Size     Numbers of byte to read for the chunk
 
669
%%----------------------------------------------------------------------    
 
670
 
 
671
 
 
672
 
 
673
read_chunked_entity(SocketType, Socket, Timeout, Max, Length, ChunkedData,
 
674
                    Body, ConfigDB, Info) ->
 
675
    T = t(),
 
676
    case get_chunk_size(SocketType,Socket,Timeout,[]) of
 
677
        Size when integer(Size), Size>0 ->
 
678
            case read_chunked_entity_body(SocketType, Socket, 
 
679
                                          Timeout-(t()-T),
 
680
                                          Max, length(Body), Size) of
 
681
                {ok,Chunk} ->
 
682
                    ?DEBUG("read_chunked_entity/9 Got a chunk: ~p " ,[Chunk]),
 
683
                    %% Two bytes are left of the chunk, that is the CRLF 
 
684
                    %% at the end that is not a part of the message
 
685
                    %% So we read it and do nothing with it.
 
686
                    httpd_socket:recv(SocketType,Socket,2,Timeout-(t()-T)),
 
687
                    read_chunked_entity(SocketType, Socket, Timeout-(t()-T),
 
688
                                        Max, Length, ChunkedData, Body++Chunk,
 
689
                                        ConfigDB, Info);
 
690
                Error ->
 
691
                    ?DEBUG("read_chunked_entity/9 Error: ~p " ,[Error]),
 
692
                    httpd_socket:close(SocketType,Socket),
 
693
                    {socket_closed,error}
 
694
            end;
 
695
        Size when integer(Size), Size == 0 ->
 
696
            %% Must read in any trailer fields here
 
697
            read_chunk_trailer(SocketType, Socket, Timeout,
 
698
                               Max, Info, ChunkedData, Body, ConfigDB);
 
699
        Error ->
 
700
            Error
 
701
    end.
 
702
 
 
703
 
 
704
%% If a user wants to send header data after the chunked data we 
 
705
%% must pick it out
 
706
read_chunk_trailer(SocketType, Socket, Timeout, Max, Info, ChunkedData,
 
707
                   Body, ConfigDB) ->
 
708
    ?DEBUG("read_chunk_trailer/8: ~p " ,[Body]),
 
709
    MaxHdrSz = httpd_util:lookup(ConfigDB,max_header_size,10240),
 
710
    case httpd_util:key1search(Info#mod.parsed_header,"trailer")of
 
711
        undefined ->
 
712
            {ok,Body};
 
713
        Fields ->
 
714
            case read_trailer(SocketType, Socket, Timeout,
 
715
                              MaxHdrSz, [], [],
 
716
                              string:tokens(
 
717
                                httpd_util:to_lower(Fields),",")) of
 
718
                {ok,[]} ->
 
719
                    {ok,Body};
 
720
                {ok,HeaderFields} ->
 
721
                    % ParsedExtraHeaders = 
 
722
                    % httpd_parse:tagup_header(httpd_parse:split_lines(HeaderFields)),
 
723
                    {ok,HeaderFields,Body};
 
724
                Error ->
 
725
                    Error
 
726
            end
 
727
    end.
 
728
 
 
729
read_chunked_entity_body(SocketType, Socket, Timeout, Max, Length, Size) 
 
730
  when integer(Max) ->
 
731
    read_entity_body(SocketType, Socket, Timeout, Max-Length, Size, []);
 
732
 
 
733
read_chunked_entity_body(SocketType, Socket, Timeout, Max, _Length, Size) ->
 
734
    read_entity_body(SocketType, Socket, Timeout, Max, Size, []).
 
735
 
 
736
%% If we read in the \r\n the httpd_util:hexlist_to_integer
 
737
%% Will remove it and we get rid of it emmediatly :-) 
 
738
get_chunk_size(SocketType, Socket, Timeout, Size) ->
 
739
    T = t(),
 
740
    ?DEBUG("get_chunk_size: ~p " ,[Size]),
 
741
    case httpd_socket:recv(SocketType,Socket,1,Timeout) of
 
742
        {ok,[Digit]} when Digit==$\n ->
 
743
            httpd_util:hexlist_to_integer(lists:reverse(Size));
 
744
       {ok,[Digit]} ->
 
745
            get_chunk_size(SocketType,Socket,Timeout-(t()-T),[Digit|Size]);
 
746
        {error,closed} ->
 
747
            {socket_closed,normal};
 
748
        {error,etimedout} ->
 
749
            {socket_closed, timeout};
 
750
        {error,Reason} ->
 
751
            {socket_closed, Reason}; 
 
752
        Other ->
 
753
            {socket_closed,Other}
 
754
    end.
 
755
 
 
756
 
 
757
 
 
758
 
 
759
%%----------------------------------------------------------------------
 
760
%% Reads the HTTP-trailer
 
761
%% Would be easy to tweak the read_head to do this but in this way
 
762
%% the chunked encoding can be updated better.
 
763
%%----------------------------------------------------------------------
 
764
 
 
765
 
 
766
%% When end is reached
 
767
%% read_trailer(SocketType,Socket,Timeout,MaxHdrSz,Headers,Last,[]) ->
 
768
%%    {ok,Headers};
 
769
 
 
770
%% When header to big    
 
771
read_trailer(_,_,_,MaxHdrSz,Headers,Bs,_Fields) 
 
772
  when MaxHdrSz < length(Headers) ->
 
773
    ?vlog("header to long: "
 
774
          "~n   MaxHdrSz:   ~p"
 
775
          "~n   length(Bs): ~p", [MaxHdrSz,length(Bs)]),
 
776
    throw({error,{header_too_long,MaxHdrSz,length(Bs)}});
 
777
 
 
778
%% The last Crlf is there 
 
779
read_trailer(_, _, _, _, Headers, [$\n, $\r], _) ->
 
780
    {ok,Headers};
 
781
 
 
782
read_trailer(SocketType, Socket, Timeout, MaxHdrSz, Headers,
 
783
             [$\n, $\r|Rest], Fields) ->
 
784
    case getTrailerField(lists:reverse(Rest))of
 
785
        {error,Reason}->
 
786
            {error,"Bad trailer"};
 
787
        {HeaderField,Value}->
 
788
            case lists:member(HeaderField,Fields) of
 
789
                true ->
 
790
                    read_trailer(SocketType,Socket,Timeout,MaxHdrSz,
 
791
                                 [{HeaderField,Value} |Headers],[],
 
792
                                 lists:delete(HeaderField,Fields));
 
793
                false ->
 
794
                    read_trailer(SocketType,Socket,Timeout,MaxHdrSz,
 
795
                                 Headers,[],Fields)
 
796
            end
 
797
    end;
 
798
 
 
799
% read_trailer(SocketType,Socket,Timeout,MaxHdrSz,Headers,[$\n, $\r|Rest],Fields) ->
 
800
%     case Rest of
 
801
%       [] ->
 
802
%          read_trailer(SocketType,Socket,Timeout,MaxHdrSz,Headers,Rest,Fields);
 
803
%       Field ->
 
804
%           case getTrailerField(lists:reverse(Rest))of
 
805
%               {error,Reason}->
 
806
%                   {error,"Bad trailer"};
 
807
%               {HeaderField,Value}->
 
808
%                   case lists:member(HeaderField,Fields) of
 
809
%                       true ->
 
810
%                           read_trailer(SocketType,Socket,Timeout,MaxHdrSz,
 
811
%                                        [{HeaderField,Value} |Headers],[],
 
812
%                                        lists:delete(HeaderField,Fields));
 
813
%                       false ->
 
814
%                           read_trailer(SocketType,Socket,Timeout,MaxHdrSz,
 
815
%                                        Headers,[],Fields)
 
816
%                   end
 
817
%           end
 
818
%     end;
 
819
 
 
820
read_trailer(SocketType,Socket,Timeout,MaxHdrSz,Headers,Bs,Fields) ->
 
821
    %% ?vlog("read_header -> entry with Timeout: ~p",[Timeout]),
 
822
    T = t(),
 
823
    case (catch httpd_socket:recv(SocketType,Socket,1,Timeout)) of
 
824
        {ok,[B]} ->
 
825
            read_trailer(SocketType, Socket, Timeout-(t()-T),
 
826
                         MaxHdrSz, Headers, [B|Bs], Fields);
 
827
        {error,closed} ->
 
828
            {socket_closed,normal};
 
829
        {error,etimedout} ->
 
830
            {socket_closed, timeout};
 
831
        {error,Reason} ->
 
832
            {socket_closed, Reason};
 
833
        Other ->
 
834
            {socket_closed,Other}
 
835
    end.
 
836
 
 
837
getTrailerField(HeaderField)->
 
838
   case string:str(HeaderField,":") of
 
839
       0->
 
840
           {error,"badheaderfield"};
 
841
       Number ->
 
842
           {httpd_util:to_lower(string:substr(HeaderField,1,Number-1)),
 
843
            httpd_util:to_lower(string:substr(HeaderField,Number+1))}
 
844
   end.
 
845
 
 
846
            
 
847
    
 
848
 
 
849
%% Time in milli seconds
 
850
t() ->
 
851
    {A,B,C} = erlang:now(),
 
852
    A*1000000000+B*1000+(C div 1000).
 
853
 
 
854
%%----------------------------------------------------------------------
 
855
%% If the user sends an expect header-field with the value 100-continue
 
856
%% We must send a 100 status message if he is a HTTP/1.1 client. 
 
857
 
 
858
%% If it is an HTTP/1.0 client it's little more difficult.
 
859
%% If expect is not defined it is easy but in the other case shall we 
 
860
%% Break or the transmission or let it continue the standard is not clear 
 
861
%% if to break connection or wait for data.  
 
862
%%----------------------------------------------------------------------
 
863
expect(HTTPVersion,ParsedHeader,ConfigDB)->    
 
864
    case HTTPVersion of
 
865
        [$H,$T,$T,$P,$\/,$1,$.,N|_Whatever]when N>=1->
 
866
            case httpd_util:key1search(ParsedHeader,"expect") of
 
867
                "100-continue" ->
 
868
                    continue; 
 
869
                undefined ->
 
870
                    no_expect_header;
 
871
                NewValue ->
 
872
                    break
 
873
            end;
 
874
        _OldVersion ->
 
875
            case httpd_util:key1search(ParsedHeader,"expect") of
 
876
                undefined ->
 
877
                    no_expect_header;
 
878
                NewValue ->
 
879
                    case httpd_util:lookup(ConfigDB,expect,continue) of
 
880
                        continue->
 
881
                            no_expect_header;
 
882
                        _ ->
 
883
                            http_1_0_expect_header
 
884
                    end
 
885
            end
 
886
    end.
 
887
 
 
888
 
 
889
%%----------------------------------------------------------------------
 
890
%% According to the http/1.1 standard all applications must understand
 
891
%% Chunked encoded data. (Last line chapter 3.6.1).             
 
892
transfer_coding(#mod{parsed_header = Ph}) ->
 
893
    case httpd_util:key1search(Ph, "transfer-encoding", none) of
 
894
        none ->
 
895
            none;
 
896
        [$c,$h,$u,$n,$k,$e,$d|Data]->
 
897
            {chunked,Data};
 
898
        _ ->
 
899
            unknown_coding
 
900
    end.
 
901
 
 
902
 
 
903
 
 
904
handle_read_error({header_too_long,Max,Rem},
 
905
                  SocketType,Socket,ConfigDB,Peername) ->
 
906
    String = io_lib:format("header too long: ~p : ~p",[Max,Rem]),
 
907
    handle_read_error(ConfigDB,String,SocketType,Socket,Peername,
 
908
                      max_header_action,close);
 
909
handle_read_error({body_too_long,Max,Actual},
 
910
                  SocketType,Socket,ConfigDB,Peername) ->
 
911
    String = io_lib:format("body too long: ~p : ~p",[Max,Actual]),
 
912
    handle_read_error(ConfigDB,String,SocketType,Socket,Peername,
 
913
                      max_body_action,close);
 
914
handle_read_error(Error,SocketType,Socket,ConfigDB,Peername) ->
 
915
    ok.
 
916
 
 
917
 
 
918
handle_read_error(ConfigDB, ReasonString, SocketType, Socket, Peername,
 
919
                  Item, Default) ->
 
920
    ?vlog("error reading request: ~s",[ReasonString]),
 
921
    E = lists:flatten(
 
922
          io_lib:format("Error reading request: ~s",[ReasonString])),
 
923
    error_log(mod_log, SocketType, Socket, ConfigDB, Peername, E),
 
924
    error_log(mod_disk_log, SocketType, Socket, ConfigDB, Peername, E),
 
925
    case httpd_util:lookup(ConfigDB,Item,Default) of
 
926
        reply414 ->
 
927
            send_read_status(SocketType, Socket, 414, ReasonString, ConfigDB);
 
928
        _ ->
 
929
            ok
 
930
    end.
 
931
    
 
932
send_read_status(SocketType, Socket, Code, ReasonString, ConfigDB) ->
 
933
    httpd_response:send_status(SocketType, Socket, Code, ReasonString, 
 
934
                               ConfigDB).
 
935
 
 
936
 
 
937
error_log(Mod, SocketType, Socket, ConfigDB, Peername, String) ->
 
938
    Modules = httpd_util:lookup(ConfigDB, modules,
 
939
                                [mod_get, mod_head, mod_log]),
 
940
    case lists:member(Mod, Modules) of
 
941
        true ->
 
942
            Mod:error_log(SocketType, Socket, ConfigDB, Peername, String);
 
943
        _ ->
 
944
            ok
 
945
    end.
 
946
 
 
947
    
 
948
sz(L) when list(L) ->
 
949
    length(L);
 
950
sz(B) when binary(B) ->
 
951
    size(B);
 
952
sz(O) ->
 
953
    {unknown_size,O}.
 
954
 
 
955
 
 
956
%% Socket utility functions:
 
957
 
 
958
close(SocketType, Socket, ConfigDB) ->
 
959
    case httpd_socket:close(SocketType, Socket) of
 
960
        ok ->
 
961
            ok;
 
962
        {error, Reason} ->
 
963
            ?vlog("error while closing socket: ~p",[Reason]),
 
964
            ok
 
965
    end.
 
966
 
 
967
close_sleep({ssl, _}, Time) ->
 
968
    sleep(Time);
 
969
close_sleep(_, _) ->
 
970
    ok.
 
971
 
 
972
 
 
973
sleep(T) -> receive after T -> ok end.
 
974
 
 
975
 
 
976
dec(N) when integer(N) ->
 
977
    N-1;
 
978
dec(N) ->
 
979
    N.
 
980
 
 
981
 
 
982
content_length(#mod{parsed_header = Ph}) ->
 
983
    list_to_integer(httpd_util:key1search(Ph, "content-length","0")).
 
984
 
 
985
 
 
986
remove_newline(List)->
 
987
    lists:dropwhile(fun newline/1,List).
 
988
 
 
989
newline($\r) ->
 
990
    true;
 
991
newline($\n) ->
 
992
    true;
 
993
newline(_Sign) ->
 
994
    false.
 
995