~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/inets/src/http_lib.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

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 Mobile Arts AB
13
 
%% Portions created by Mobile Arts are Copyright 2002, Mobile Arts AB
14
 
%% All Rights Reserved.''
15
 
%% 
16
 
%%
17
 
%%% File    : http_lib.erl
18
 
%%% Author  : Johan Blom <johan.blom@mobilearts.se>
19
 
%%% Description : Generic, HTTP specific helper functions
20
 
%%% Created :  4 Mar 2002 by Johan Blom
21
 
 
22
 
%%% TODO
23
 
%%% - Check if I need to do anything special when parsing
24
 
%%%   "Content-Type:multipart/form-data"
25
 
 
26
 
-module(http_lib).
27
 
-author("johan.blom@mobilearts.se").
28
 
 
29
 
-include("http.hrl").
30
 
-include("jnets_httpd.hrl").
31
 
 
32
 
-export([connection_close/1,
33
 
         accept/3,deliver/3,recv/4,recv0/3,
34
 
         connect/1,send/3,close/2,controlling_process/3,setopts/3,
35
 
         getParameterValue/2,
36
 
%        get_var/2,
37
 
         create_request_line/3]).
38
 
 
39
 
-export([read_client_headers/2,read_server_headers/2,
40
 
         get_auth_data/1,create_header_list/1,
41
 
         read_client_body/2,read_client_multipartrange_body/3,
42
 
         read_server_body/2]).
43
 
 
44
 
 
45
 
%%% Server response:
46
 
%%%    Check "Connection" header if server requests session to be closed.
47
 
%%%    No 'close' means returns false
48
 
%%% Client Request:
49
 
%%%    Check if 'close' in request headers 
50
 
%%% Only care about HTTP 1.1 clients!
51
 
connection_close(Headers) when record(Headers,req_headers) ->
52
 
    case Headers#req_headers.connection of
53
 
        "close" ->
54
 
            true;
55
 
        "keep-alive" ->
56
 
            false;
57
 
        Value when list(Value) ->
58
 
            true;
59
 
        _ ->
60
 
            false
61
 
    end;
62
 
connection_close(Headers) when record(Headers,res_headers) ->
63
 
    case Headers#res_headers.connection of
64
 
        "close" ->
65
 
            true;
66
 
        "keep-alive" ->
67
 
            false;
68
 
        Value when list(Value) ->
69
 
            true;
70
 
        _ ->
71
 
            false
72
 
    end.
73
 
 
74
 
 
75
 
getHeaderValue(_Attr,[]) ->
76
 
    [];
77
 
getHeaderValue(Attr,[{Attr,Value}|_Rest]) ->
78
 
    Value;
79
 
getHeaderValue(Attr,[_|Rest]) ->
80
 
    getHeaderValue(Attr,Rest).
81
 
 
82
 
getParameterValue(_Attr,undefined) ->
83
 
    undefined;
84
 
getParameterValue(Attr,List) ->
85
 
    case lists:keysearch(Attr,1,List) of
86
 
        {value,{Attr,Val}} ->
87
 
            Val;
88
 
        _ ->
89
 
            undefined
90
 
    end.
91
 
 
92
 
create_request_line(Method,Path,{Major,Minor}) ->
93
 
    [atom_to_list(Method)," ",Path,
94
 
     " HTTP/",integer_to_list(Major),".",integer_to_list(Minor)];
95
 
create_request_line(Method,Path,Minor) ->
96
 
    [atom_to_list(Method)," ",Path," HTTP/1.",integer_to_list(Minor)].
97
 
 
98
 
 
99
 
%%% ============================================================================
100
 
read_client_headers(Info,Timeout) ->
101
 
    Headers=read_response_h(Info#response.scheme,Info#response.socket,Timeout,
102
 
                            Info#response.headers),
103
 
    Info#response{headers=Headers}.
104
 
 
105
 
read_server_headers(Info,Timeout) ->
106
 
    Headers=read_request_h(Info#mod.socket_type,Info#mod.socket,Timeout,
107
 
                           Info#mod.headers),
108
 
    Info#mod{headers=Headers}.
109
 
 
110
 
 
111
 
%% Parses the header of a HTTP request and returns a key,value tuple 
112
 
%% list containing Name and Value of each header directive as of:
113
 
%%
114
 
%% Content-Type: multipart/mixed -> {"Content-Type", "multipart/mixed"}
115
 
%%
116
 
%% But in http/1.1 the field-names are case insencitive so now it must be 
117
 
%% Content-Type: multipart/mixed -> {"content-type", "multipart/mixed"}
118
 
%% The standard furthermore says that leading and traling white space 
119
 
%% is not a part of the fieldvalue and shall therefore be removed.
120
 
read_request_h(SType,S,Timeout,H) ->
121
 
    case recv0(SType,S,Timeout) of
122
 
        {ok,{http_header,_,'Connection',_,Value}} ->
123
 
            read_request_h(SType,S,Timeout,H#req_headers{connection=Value});
124
 
        {ok,{http_header,_,'Content-Type',_,Val}} ->
125
 
            read_request_h(SType,S,Timeout,H#req_headers{content_type=Val});
126
 
        {ok,{http_header,_,'Host',_,Value}} ->
127
 
            read_request_h(SType,S,Timeout,H#req_headers{host=Value});
128
 
        {ok,{http_header,_,'Content-Length',_,Value}} ->
129
 
            read_request_h(SType,S,Timeout,H#req_headers{content_length=Value});
130
 
%       {ok,{http_header,_,'Expect',_,Value}} -> % FIXME! Update inet_drv.c!!
131
 
%           read_request_h(SType,S,Timeout,H#req_headers{expect=Value});
132
 
        {ok,{http_header,_,'Transfer-Encoding',_,V}} ->
133
 
            read_request_h(SType,S,Timeout,H#req_headers{transfer_encoding=V});
134
 
        {ok,{http_header,_,'Authorization',_,Value}} ->
135
 
            read_request_h(SType,S,Timeout,H#req_headers{authorization=Value});
136
 
        {ok,{http_header,_,'User-Agent',_,Value}} ->
137
 
            read_request_h(SType,S,Timeout,H#req_headers{user_agent=Value});
138
 
        {ok,{http_header,_,'Range',_,Value}} ->
139
 
            read_request_h(SType,S,Timeout,H#req_headers{range=Value});
140
 
        {ok,{http_header,_,'If-Range',_,Value}} ->
141
 
            read_request_h(SType,S,Timeout,H#req_headers{if_range=Value});
142
 
        {ok,{http_header,_,'If-Match',_,Value}} ->
143
 
            read_request_h(SType,S,Timeout,H#req_headers{if_match=Value});
144
 
        {ok,{http_header,_,'If-None-Match',_,Value}} ->
145
 
            read_request_h(SType,S,Timeout,H#req_headers{if_none_match=Value});
146
 
        {ok,{http_header,_,'If-Modified-Since',_,V}} ->
147
 
            read_request_h(SType,S,Timeout,H#req_headers{if_modified_since=V});
148
 
        {ok,{http_header,_,'If-Unmodified-Since',_,V}} ->
149
 
            read_request_h(SType,S,Timeout,H#req_headers{if_unmodified_since=V});
150
 
        {ok,{http_header,_,K,_,V}} ->
151
 
            read_request_h(SType,S,Timeout,
152
 
                           H#req_headers{other=H#req_headers.other++[{K,V}]});
153
 
        {ok,http_eoh} ->
154
 
            H;
155
 
        {error, timeout} when SType==http ->
156
 
            throw({error, session_local_timeout});
157
 
        {error, etimedout} when SType==https ->
158
 
            throw({error, session_local_timeout});
159
 
        {error, Reason} when Reason==closed;Reason==enotconn ->
160
 
            throw({error, session_remotely_closed});
161
 
        {error, Reason} ->
162
 
            throw({error,Reason})
163
 
    end.
164
 
 
165
 
 
166
 
read_response_h(SType,S,Timeout,H) ->
167
 
    case recv0(SType,S,Timeout) of
168
 
        {ok,{http_header,_,'Connection',_,Val}} ->
169
 
            read_response_h(SType,S,Timeout,H#res_headers{connection=Val});
170
 
        {ok,{http_header,_,'Content-Length',_,Val}} ->
171
 
            read_response_h(SType,S,Timeout,H#res_headers{content_length=Val});
172
 
        {ok,{http_header,_,'Content-Type',_,Val}} ->
173
 
            read_response_h(SType,S,Timeout,H#res_headers{content_type=Val});
174
 
        {ok,{http_header,_,'Transfer-Encoding',_,V}} ->
175
 
            read_response_h(SType,S,Timeout,H#res_headers{transfer_encoding=V});
176
 
        {ok,{http_header,_,'Location',_,V}} ->
177
 
            read_response_h(SType,S,Timeout,H#res_headers{location=V});
178
 
        {ok,{http_header,_,'Retry-After',_,V}} ->
179
 
            read_response_h(SType,S,Timeout,H#res_headers{retry_after=V});
180
 
        {ok,{http_header,_,K,_,V}} ->
181
 
            read_response_h(SType,S,Timeout,
182
 
                            H#res_headers{other=H#res_headers.other++[{K,V}]});
183
 
        {ok,http_eoh} ->
184
 
            H;
185
 
        {error, timeout} when SType==http ->
186
 
            throw({error, session_local_timeout});
187
 
        {error, etimedout} when SType==https ->
188
 
            throw({error, session_local_timeout});
189
 
        {error, Reason} when Reason==closed;Reason==enotconn ->
190
 
            throw({error, session_remotely_closed});
191
 
        {error, Reason} ->
192
 
            throw({error,Reason})
193
 
    end.
194
 
 
195
 
 
196
 
%%% Got the headers, and maybe a part of the body, now read in the rest
197
 
%%% Note:
198
 
%%% - No need to check for Expect header if client 
199
 
%%% - Currently no support for setting MaxHeaderSize in client, set to
200
 
%%%   unlimited.
201
 
%%% - Move to raw packet mode as we are finished with HTTP parsing
202
 
read_client_body(Info,Timeout) ->
203
 
    Headers=Info#response.headers,    
204
 
    case Headers#res_headers.transfer_encoding of
205
 
        "chunked" ->
206
 
            ?DEBUG("read_entity_body2()->"
207
 
                "Transfer-encoding:Chunked Data:",[]),
208
 
            read_client_chunked_body(Info,Timeout,?MAXBODYSIZE);
209
 
        Encoding when list(Encoding) ->
210
 
            ?DEBUG("read_entity_body2()->"
211
 
                "Transfer-encoding:Unknown",[]),
212
 
            throw({error,unknown_coding});
213
 
        _ ->
214
 
            ContLen=list_to_integer(Headers#res_headers.content_length),
215
 
            if
216
 
                ContLen>?MAXBODYSIZE -> 
217
 
                    throw({error,body_too_big});
218
 
                true ->
219
 
                    ?DEBUG("read_entity_body2()->"
220
 
                        "Transfer-encoding:none ",[]),
221
 
                    Info#response{body=read_plain_body(Info#response.scheme,
222
 
                                                       Info#response.socket,
223
 
                                                       ContLen,
224
 
                                                       Info#response.body,
225
 
                                                       Timeout)}
226
 
            end
227
 
    end.
228
 
 
229
 
 
230
 
%%% ----------------------------------------------------------------------
231
 
read_server_body(Info,Timeout) ->
232
 
    MaxBodySz=httpd_util:lookup(Info#mod.config_db,max_body_size,?MAXBODYSIZE),
233
 
    ContLen=list_to_integer((Info#mod.headers)#req_headers.content_length),
234
 
    %% ?vtrace("ContentLength: ~p", [ContLen]),
235
 
    if
236
 
        integer(ContLen),integer(MaxBodySz),ContLen>MaxBodySz ->
237
 
            throw({error,body_too_big});
238
 
        true ->
239
 
            read_server_body2(Info,Timeout,ContLen,MaxBodySz)
240
 
    end.
241
 
 
242
 
 
243
 
%%----------------------------------------------------------------------
244
 
%% Control if the body is transfer encoded, if so decode it.
245
 
%% Note:
246
 
%% - MaxBodySz has an integer value or 'nolimit'
247
 
%% - ContLen has an integer value or 'undefined'
248
 
%% All applications MUST be able to receive and decode the "chunked"
249
 
%% transfer-coding, see RFC 2616 Section 3.6.1
250
 
read_server_body2(Info,Timeout,ContLen,MaxBodySz) ->
251
 
    ?DEBUG("read_entity_body2()->Max: ~p ~nLength:~p ~nSocket: ~p ~n",
252
 
        [MaxBodySz,ContLen,Info#mod.socket]),
253
 
    case (Info#mod.headers)#req_headers.transfer_encoding of
254
 
        "chunked" ->
255
 
            ?DEBUG("read_entity_body2()->"
256
 
                "Transfer-encoding:Chunked Data:",[]),
257
 
            read_server_chunked_body(Info,Timeout,MaxBodySz);
258
 
        Encoding when list(Encoding) ->
259
 
            ?DEBUG("read_entity_body2()->"
260
 
                "Transfer-encoding:Unknown",[]),
261
 
            httpd_response:send_status(Info,501,"Unknown Transfer-Encoding"),
262
 
            http_lib:close(Info#mod.socket_type,Info#mod.socket),
263
 
            throw({error,{status_sent,"Unknown Transfer-Encoding "++Encoding}});
264
 
        _ when integer(ContLen),integer(MaxBodySz),ContLen>MaxBodySz -> 
265
 
            throw({error,body_too_big});
266
 
        _ when integer(ContLen) ->
267
 
            ?DEBUG("read_entity_body2()->"
268
 
                "Transfer-encoding:none ",[]),
269
 
            Info#mod{entity_body=read_plain_body(Info#mod.socket_type,
270
 
                                                 Info#mod.socket,
271
 
                                                 ContLen,Info#mod.entity_body,
272
 
                                                 Timeout)}
273
 
    end.
274
 
 
275
 
 
276
 
%%% ----------------------------------------------------------------------------
277
 
%%% The body was plain, just read it from the socket.
278
 
read_plain_body(_SocketType,Socket,0,Cont,_Timeout) ->
279
 
    Cont;
280
 
read_plain_body(SocketType,Socket,ContLen,Cont,Timeout) ->
281
 
    Body=read_more_data(SocketType,Socket,ContLen,Timeout),
282
 
    <<Cont/binary,Body/binary>>.
283
 
 
284
 
%%% ----------------------------------------------------------------------------
285
 
%%% The body was chunked, decode it.
286
 
%%% From RFC2616, Section 3.6.1
287
 
%%        Chunked-Body   = *chunk
288
 
%%                         last-chunk
289
 
%%                         trailer
290
 
%%                         CRLF
291
 
%%
292
 
%%        chunk          = chunk-size [ chunk-extension ] CRLF
293
 
%%                         chunk-data CRLF
294
 
%%        chunk-size     = 1*HEX
295
 
%%        last-chunk     = 1*("0") [ chunk-extension ] CRLF
296
 
%%
297
 
%%        chunk-extension= *( ";" chunk-ext-name [ "=" chunk-ext-val ] )
298
 
%%        chunk-ext-name = token
299
 
%%        chunk-ext-val  = token | quoted-string
300
 
%%        chunk-data     = chunk-size(OCTET)
301
 
%%        trailer        = *(entity-header CRLF)
302
 
%%
303
 
%%% "All applications MUST ignore chunk-extension extensions they do not
304
 
%%% understand.", see RFC 2616 Section 3.6.1
305
 
%%% We don't understand any extension...
306
 
read_client_chunked_body(Info,Timeout,MaxChunkSz) ->
307
 
    case read_chunk(Info#response.scheme,Info#response.socket,
308
 
                    Timeout,0,MaxChunkSz) of
309
 
        {last_chunk,_ExtensionList} -> % Ignore extension
310
 
            TrailH=read_headers_old(Info#response.scheme,Info#response.socket,
311
 
                                    Timeout),
312
 
            H=Info#response.headers,
313
 
            OtherHeaders=H#res_headers.other++TrailH,
314
 
            Info#response{headers=H#res_headers{other=OtherHeaders}};
315
 
        {Chunk,ChunkSize,_ExtensionList} -> % Ignore extension
316
 
            Info1=Info#response{body= <<(Info#response.body)/binary,
317
 
                                        Chunk/binary>>},
318
 
            read_client_chunked_body(Info1,Timeout,MaxChunkSz-ChunkSize);
319
 
        {error,Reason} ->
320
 
            throw({error,Reason})
321
 
    end.
322
 
 
323
 
 
324
 
read_server_chunked_body(Info,Timeout,MaxChunkSz) ->
325
 
    case read_chunk(Info#mod.socket_type,Info#mod.socket,
326
 
                    Timeout,0,MaxChunkSz) of
327
 
        {last_chunk,_ExtensionList} -> % Ignore extension
328
 
            TrailH=read_headers_old(Info#mod.socket_type,Info#mod.socket,
329
 
                                    Timeout),
330
 
            H=Info#mod.headers,
331
 
            OtherHeaders=H#req_headers.other++TrailH,
332
 
            Info#mod{headers=H#req_headers{other=OtherHeaders}};
333
 
        {Chunk,ChunkSize,_ExtensionList} -> % Ignore extension
334
 
            Info1=Info#mod{entity_body= <<(Info#mod.entity_body)/binary,
335
 
                                           Chunk/binary>>},
336
 
            read_server_chunked_body(Info1,Timeout,MaxChunkSz-ChunkSize);
337
 
        {error,Reason} ->
338
 
            throw({error,Reason})
339
 
    end.
340
 
 
341
 
 
342
 
read_chunk(Scheme,Socket,Timeout,Int,MaxChunkSz) when MaxChunkSz>Int ->
343
 
    case read_more_data(Scheme,Socket,1,Timeout) of
344
 
        <<C>> when $0=<C,C=<$9 ->
345
 
            read_chunk(Scheme,Socket,Timeout,16*Int+(C-$0),MaxChunkSz);
346
 
        <<C>> when $a=<C,C=<$f ->
347
 
            read_chunk(Scheme,Socket,Timeout,16*Int+10+(C-$a),MaxChunkSz);
348
 
        <<C>> when $A=<C,C=<$F ->
349
 
            read_chunk(Scheme,Socket,Timeout,16*Int+10+(C-$A),MaxChunkSz);
350
 
        <<$;>> when Int>0 ->
351
 
            ExtensionList=read_chunk_ext_name(Scheme,Socket,Timeout,[],[]),
352
 
            read_chunk_data(Scheme,Socket,Int+1,ExtensionList,Timeout);
353
 
        <<$;>> when Int==0 ->
354
 
            ExtensionList=read_chunk_ext_name(Scheme,Socket,Timeout,[],[]),
355
 
            read_data_lf(Scheme,Socket,Timeout),
356
 
            {last_chunk,ExtensionList};
357
 
        <<?CR>> when Int>0 ->
358
 
            read_chunk_data(Scheme,Socket,Int+1,[],Timeout);
359
 
        <<?CR>> when Int==0 ->
360
 
            read_data_lf(Scheme,Socket,Timeout),
361
 
            {last_chunk,[]};
362
 
        <<C>> when C==$ -> % Some servers (e.g., Apache 1.3.6) throw in
363
 
                           % additional whitespace...
364
 
            read_chunk(Scheme,Socket,Timeout,Int,MaxChunkSz);
365
 
        _Other ->
366
 
            {error,unexpected_chunkdata}
367
 
    end;
368
 
read_chunk(_Scheme,_Socket,_Timeout,_Int,_MaxChunkSz) ->
369
 
    {error,body_too_big}.
370
 
 
371
 
 
372
 
%%% Note:
373
 
%%% - Got the initial ?CR already!
374
 
%%% - Bitsyntax does not allow matching of ?CR,?LF in the end of the first read
375
 
read_chunk_data(Scheme,Socket,Int,ExtensionList,Timeout) ->
376
 
    case read_more_data(Scheme,Socket,Int,Timeout) of
377
 
        <<?LF,Chunk/binary>> ->
378
 
            case read_more_data(Scheme,Socket,2,Timeout) of
379
 
                <<?CR,?LF>> ->
380
 
                    {Chunk,size(Chunk),ExtensionList};
381
 
                _ ->
382
 
                    {error,bad_chunkdata}
383
 
            end;
384
 
        _ ->
385
 
            {error,bad_chunkdata}
386
 
    end.
387
 
 
388
 
read_chunk_ext_name(Scheme,Socket,Timeout,Name,Acc) ->
389
 
    Len=length(Name),
390
 
    case read_more_data(Scheme,Socket,1,Timeout) of
391
 
        $= when Len>0 ->
392
 
            read_chunk_ext_val(Scheme,Socket,Timeout,Name,[],Acc);
393
 
        $; when Len>0 ->
394
 
            read_chunk_ext_name(Scheme,Socket,Timeout,[],
395
 
                                [{lists:reverse(Name),""}|Acc]);
396
 
        ?CR when Len>0 ->
397
 
            lists:reverse([{lists:reverse(Name,"")}|Acc]);
398
 
        Token -> % FIXME Check that it is "token"
399
 
            read_chunk_ext_name(Scheme,Socket,Timeout,[Token|Name],Acc);
400
 
        _ ->
401
 
            {error,bad_chunk_extension_name}
402
 
    end.
403
 
 
404
 
read_chunk_ext_val(Scheme,Socket,Timeout,Name,Val,Acc) ->
405
 
    Len=length(Val),
406
 
    case read_more_data(Scheme,Socket,1,Timeout) of
407
 
        $; when Len>0 ->
408
 
            read_chunk_ext_name(Scheme,Socket,Timeout,[],
409
 
                                [{Name,lists:reverse(Val)}|Acc]);
410
 
        ?CR when Len>0 ->
411
 
            lists:reverse([{Name,lists:reverse(Val)}|Acc]);
412
 
        Token -> % FIXME Check that it is "token" or "quoted-string"
413
 
            read_chunk_ext_val(Scheme,Socket,Timeout,Name,[Token|Val],Acc);
414
 
        _ ->
415
 
            {error,bad_chunk_extension_value}
416
 
    end.
417
 
 
418
 
read_data_lf(Scheme,Socket,Timeout) ->
419
 
    case read_more_data(Scheme,Socket,1,Timeout) of
420
 
        ?LF ->
421
 
            ok;
422
 
        _ ->
423
 
            {error,bad_chunkdata}
424
 
    end.
425
 
 
426
 
%%% ----------------------------------------------------------------------------
427
 
%%% The body was "multipart/byteranges", decode it.
428
 
%%% Example from RFC 2616, Appendix 19.2
429
 
%%%    HTTP/1.1 206 Partial Content
430
 
%%%    Date: Wed, 15 Nov 1995 06:25:24 GMT
431
 
%%%    Last-Modified: Wed, 15 Nov 1995 04:58:08 GMT
432
 
%%%    Content-type: multipart/byteranges; boundary=THIS_STRING_SEPARATES
433
 
%%%
434
 
%%%    --THIS_STRING_SEPARATES
435
 
%%%    Content-type: application/pdf
436
 
%%%    Content-range: bytes 500-999/8000
437
 
%%%
438
 
%%%    ...the first range...
439
 
%%%    --THIS_STRING_SEPARATES
440
 
%%%    Content-type: application/pdf
441
 
%%%    Content-range: bytes 7000-7999/8000
442
 
%%%
443
 
%%%    ...the second range
444
 
%%%    --THIS_STRING_SEPARATES--
445
 
%%%
446
 
%%%       Notes:
447
 
%%%
448
 
%%%       1) Additional CRLFs may precede the first boundary string in the
449
 
%%%          entity.
450
 
%%% FIXME!!
451
 
read_client_multipartrange_body(Info,Parstr,Timeout) ->
452
 
    Boundary=get_boundary(Parstr),
453
 
    scan_boundary(Info,Boundary),
454
 
    Info#response{body=read_multipart_body(Info,Boundary,Timeout)}.
455
 
 
456
 
read_multipart_body(Info,Boundary,Timeout) ->
457
 
    Info.
458
 
 
459
 
%     Headers=read_headers_old(Info#response.scheme,Info#response.socket,Timeout),
460
 
%     H=Info#response.headers,
461
 
%     OtherHeaders=H#res_headers.other++TrailH,
462
 
%     Info#response{headers=H#res_headers{other=OtherHeaders}}.
463
 
 
464
 
 
465
 
scan_boundary(Info,Boundary) ->
466
 
    Info.
467
 
 
468
 
 
469
 
get_boundary(Parstr) ->
470
 
    case skip_lwsp(Parstr) of
471
 
        [] ->
472
 
            throw({error,missing_range_boundary_parameter});
473
 
        Val ->
474
 
            get_boundary2(string:tokens(Val, ";"))
475
 
    end.
476
 
 
477
 
get_boundary2([]) ->
478
 
    undefined;
479
 
get_boundary2([Param|Rest]) ->
480
 
    case string:tokens(skip_lwsp(Param), "=") of
481
 
        ["boundary"++Attribute,Value] ->
482
 
            Value;
483
 
        _ ->
484
 
            get_boundary2(Rest)
485
 
    end.
486
 
 
487
 
 
488
 
%% skip space & tab
489
 
skip_lwsp([$ | Cs]) -> skip_lwsp(Cs);
490
 
skip_lwsp([$\t | Cs]) -> skip_lwsp(Cs);
491
 
skip_lwsp(Cs) -> Cs.
492
 
 
493
 
%%% ----------------------------------------------------------------------------
494
 
 
495
 
%%% Read the incoming data from the open socket.
496
 
read_more_data(http,Socket,Len,Timeout) ->
497
 
    case gen_tcp:recv(Socket,Len,Timeout) of
498
 
        {ok,Val} ->
499
 
            Val;
500
 
        {error, timeout} ->
501
 
            throw({error, session_local_timeout});
502
 
        {error, Reason} when Reason==closed;Reason==enotconn ->
503
 
            throw({error, session_remotely_closed});
504
 
        {error, Reason} ->
505
 
%           httpd_response:send_status(Info,400,none),
506
 
            throw({error, Reason})
507
 
    end;
508
 
read_more_data(https,Socket,Len,Timeout) ->
509
 
    case ssl:recv(Socket,Len,Timeout) of
510
 
        {ok,Val} ->
511
 
            Val;
512
 
        {error, etimedout} ->
513
 
            throw({error, session_local_timeout});
514
 
        {error, Reason} when Reason==closed;Reason==enotconn ->
515
 
            throw({error, session_remotely_closed});
516
 
        {error, Reason} ->
517
 
%           httpd_response:send_status(Info,400,none),
518
 
            throw({error, Reason})
519
 
    end.
520
 
 
521
 
 
522
 
%% =============================================================================
523
 
%%% Socket handling
524
 
 
525
 
accept(http,ListenSocket, Timeout) ->
526
 
    gen_tcp:accept(ListenSocket, Timeout);
527
 
accept(https,ListenSocket, Timeout) ->
528
 
    ssl:accept(ListenSocket, Timeout).
529
 
 
530
 
 
531
 
close(http,Socket) ->
532
 
    gen_tcp:close(Socket);
533
 
close(https,Socket) ->
534
 
    ssl:close(Socket).
535
 
 
536
 
 
537
 
connect(#request{scheme=http,settings=Settings,address=Addr}) ->
538
 
    case proxyusage(Addr,Settings) of
539
 
        {error,Reason} ->
540
 
            {error,Reason};
541
 
        {Host,Port} ->
542
 
            Opts=[binary,{active,false},{reuseaddr,true}],    
543
 
            gen_tcp:connect(Host,Port,Opts)
544
 
    end;
545
 
connect(#request{scheme=https,settings=Settings,address=Addr}) ->
546
 
    case proxyusage(Addr,Settings) of
547
 
        {error,Reason} ->
548
 
            {error,Reason};
549
 
        {Host,Port} ->
550
 
            Opts=case Settings#client_settings.ssl of
551
 
                     false ->
552
 
                         [binary,{active,false}];
553
 
                     SSLSettings ->
554
 
                         [binary,{active,false}]++SSLSettings
555
 
                 end,
556
 
            ssl:connect(Host,Port,Opts)
557
 
    end.
558
 
 
559
 
 
560
 
%%% Check to see if the given {Host,Port} tuple is in the NoProxyList
561
 
%%% Returns an eventually updated {Host,Port} tuple, with the proxy address
562
 
proxyusage(HostPort,Settings) ->
563
 
    case Settings#client_settings.useproxy of
564
 
        true ->
565
 
            case noProxy(HostPort,Settings#client_settings.noproxylist) of
566
 
                true ->
567
 
                    HostPort;
568
 
                _ ->
569
 
                    case Settings#client_settings.proxy of
570
 
                        undefined ->
571
 
                            {error,no_proxy_defined};
572
 
                        ProxyHostPort ->
573
 
                            ProxyHostPort
574
 
                    end
575
 
            end;
576
 
        _ ->
577
 
            HostPort
578
 
    end.
579
 
 
580
 
noProxy(_HostPort,[]) ->
581
 
    false;
582
 
noProxy({Host,Port},[{Host,Port}|Rest]) ->
583
 
    true;
584
 
noProxy(HostPort,[_|Rest]) ->
585
 
    noProxy(HostPort,Rest).
586
 
 
587
 
 
588
 
controlling_process(http,Socket,Pid) ->
589
 
    gen_tcp:controlling_process(Socket,Pid);
590
 
controlling_process(https,Socket,Pid) ->
591
 
    ssl:controlling_process(Socket,Pid).
592
 
    
593
 
 
594
 
deliver(SocketType, Socket, Message)  ->
595
 
    case send(SocketType, Socket, Message) of
596
 
        {error, einval} ->
597
 
            close(SocketType, Socket), 
598
 
            socket_closed;
599
 
        {error, _Reason} ->
600
 
%           ?vlog("deliver(~p) failed for reason:"
601
 
%                 "~n   Reason: ~p",[SocketType,_Reason]),
602
 
            close(SocketType, Socket), 
603
 
            socket_closed;
604
 
        _Other ->
605
 
            ok
606
 
    end.
607
 
 
608
 
 
609
 
recv0(http,Socket,Timeout) ->
610
 
    gen_tcp:recv(Socket,0,Timeout);
611
 
recv0(https,Socket,Timeout) ->
612
 
    ssl:recv(Socket,0,Timeout).
613
 
 
614
 
recv(http,Socket,Len,Timeout) ->
615
 
    gen_tcp:recv(Socket,Len,Timeout);
616
 
recv(https,Socket,Len,Timeout) ->
617
 
    ssl:recv(Socket,Len,Timeout).
618
 
 
619
 
 
620
 
setopts(http,Socket,Options) ->
621
 
    inet:setopts(Socket,Options);
622
 
setopts(https,Socket,Options) ->
623
 
    ssl:setopts(Socket,Options).
624
 
 
625
 
 
626
 
send(http,Socket,Message) ->
627
 
    gen_tcp:send(Socket,Message);
628
 
send(https,Socket,Message) ->
629
 
    ssl:send(Socket,Message).
630
 
 
631
 
 
632
 
%%% ============================================================================
633
 
%%% HTTP Server only
634
 
 
635
 
%%% Returns the Authenticating data in the HTTP request
636
 
get_auth_data("Basic "++EncodedString) ->
637
 
    UnCodedString=httpd_util:decode_base64(EncodedString),
638
 
    case catch string:tokens(UnCodedString,":") of
639
 
        [User,PassWord] ->
640
 
            {User,PassWord};
641
 
        {error,Error}->
642
 
            {error,Error}
643
 
    end;
644
 
get_auth_data(BadCredentials) when list(BadCredentials) ->
645
 
    {error,BadCredentials};
646
 
get_auth_data(_) ->
647
 
    {error,nouser}.
648
 
 
649
 
create_header_list(H) ->
650
 
    lookup("Connection",H#req_headers.connection)++
651
 
        lookup("Host",H#req_headers.host)++
652
 
        lookup("Content-Length",H#req_headers.content_length)++
653
 
        lookup("Transfer-Encoding",H#req_headers.transfer_encoding)++
654
 
        lookup("Authorization",H#req_headers.authorization)++
655
 
        lookup("User-Agent",H#req_headers.user_agent)++
656
 
        lookup("Range",H#req_headers.range)++
657
 
        lookup("If-Range",H#req_headers.if_range)++
658
 
        lookup("If-Match",H#req_headers.if_match)++
659
 
        lookup("If-None-Match",H#req_headers.if_none_match)++
660
 
        lookup("If-Modified-Since",H#req_headers.if_modified_since)++
661
 
        lookup("If-Unmodified-Since",H#req_headers.if_unmodified_since)++
662
 
        H#req_headers.other.
663
 
 
664
 
lookup(_Key,undefined) ->
665
 
    [];
666
 
lookup(Key,Val) ->
667
 
    [{Key,Val}].
668
 
 
669
 
 
670
 
 
671
 
%%% ============================================================================
672
 
%%% This code is for parsing trailer headers in chunked messages.
673
 
%%% Will be deprecated whenever I have found an alternative working solution!
674
 
%%% Note:
675
 
%%% - The header names are returned slighly different from what the what
676
 
%%%   inet_drv returns
677
 
read_headers_old(Scheme,Socket,Timeout) ->
678
 
    read_headers_old(<<>>,Scheme,Socket,Timeout,[],[]).
679
 
 
680
 
read_headers_old(<<>>,Scheme,Socket,Timeout,Acc,AccHdrs) ->
681
 
    read_headers_old(read_more_data(Scheme,Socket,1,Timeout),
682
 
                     Scheme,Socket,Timeout,Acc,AccHdrs);
683
 
read_headers_old(<<$\r>>,Scheme,Socket,Timeout,Acc,AccHdrs) ->
684
 
    read_headers_old(<<$\r,(read_more_data(Scheme,Socket,1,Timeout))/binary>>,
685
 
                     Scheme,Socket,Timeout,Acc,AccHdrs);
686
 
read_headers_old(<<$\r,$\n>>,Scheme,Socket,Timeout,Acc,AccHdrs) ->
687
 
    if
688
 
        Acc==[] -> % Done!
689
 
            tagup_header(lists:reverse(AccHdrs));
690
 
        true ->
691
 
            read_headers_old(read_more_data(Scheme,Socket,1,Timeout),
692
 
                             Scheme,Socket,
693
 
                             Timeout,[],[lists:reverse(Acc)|AccHdrs])
694
 
    end;
695
 
read_headers_old(<<C>>,Scheme,Socket,Timeout,Acc,AccHdrs) ->
696
 
    read_headers_old(read_more_data(Scheme,Socket,1,Timeout),
697
 
                     Scheme,Socket,Timeout,[C|Acc],AccHdrs);
698
 
read_headers_old(Bin,_Scheme,_Socket,_Timeout,_Acc,_AccHdrs) ->
699
 
    io:format("ERROR: Unexpected data from inet driver: ~p",[Bin]),
700
 
    throw({error,this_is_a_bug}).
701
 
 
702
 
 
703
 
%% Parses the header of a HTTP request and returns a key,value tuple 
704
 
%% list containing Name and Value of each header directive as of:
705
 
%%
706
 
%% Content-Type: multipart/mixed -> {"Content-Type", "multipart/mixed"}
707
 
%%
708
 
%% But in http/1.1 the field-names are case insencitive so now it must be 
709
 
%% Content-Type: multipart/mixed -> {"content-type", "multipart/mixed"}
710
 
%% The standard furthermore says that leading and traling white space 
711
 
%% is not a part of the fieldvalue and shall therefore be removed.
712
 
tagup_header([]) ->          [];
713
 
tagup_header([Line|Rest]) -> [tag(Line, [])|tagup_header(Rest)].
714
 
 
715
 
tag([], Tag) ->
716
 
    {httpd_util:to_lower(lists:reverse(Tag)), ""};
717
 
tag([$:|Rest], Tag) ->
718
 
    {httpd_util:to_lower(lists:reverse(Tag)), httpd_util:strip(Rest)};
719
 
tag([Chr|Rest], Tag) ->
720
 
    tag(Rest, [Chr|Tag]).
721
 
 
722
 
%% =============================================================================
723
 
%%% Debugging:
724
 
 
725
 
% format_time(TS) ->
726
 
%     {_,_,MicroSecs}=TS,
727
 
%     {{Y,Mon,D},{H,M,S}}=calendar:now_to_universal_time(TS),
728
 
%     lists:flatten(io_lib:format("~4.4.0w-~2.2.0w-~2.2.0w,~2.2.0w:~2.2.0w:~6.3.0f",
729
 
%                               [Y,Mon,D,H,M,S+(MicroSecs/1000000)])).
730
 
 
731
 
%% Time in milli seconds
732
 
% t() ->
733
 
%     {A,B,C} = erlang:now(),
734
 
%     A*1000000000+B*1000+(C div 1000).
735
 
 
736
 
% sz(L) when list(L) ->
737
 
%     length(L);
738
 
% sz(B) when binary(B) ->
739
 
%     size(B);
740
 
% sz(O) ->
741
 
%     {unknown_size,O}.
742
 
 
743