~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_SUITE_data/src/inets/http_lib.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

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