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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_client/httpc.erl

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2009-2010. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
 
 
21
%% Description:
 
22
%%% This version of the HTTP/1.1 client supports:
 
23
%%%      - RFC 2616 HTTP 1.1 client part
 
24
%%%      - RFC 2818 HTTP Over TLS
 
25
 
 
26
-module(httpc).
 
27
 
 
28
-behaviour(inets_service).
 
29
 
 
30
%% API
 
31
-export([
 
32
         request/1, request/2, request/4, request/5,
 
33
         cancel_request/1, cancel_request/2,
 
34
         set_option/2, set_option/3,
 
35
         set_options/1, set_options/2,
 
36
         store_cookies/2, store_cookies/3, 
 
37
         cookie_header/1, cookie_header/2, 
 
38
         which_cookies/0, which_cookies/1, 
 
39
         reset_cookies/0, reset_cookies/1, 
 
40
         stream_next/1,
 
41
         default_profile/0, 
 
42
         profile_name/1, profile_name/2,
 
43
         info/0, info/1
 
44
        ]).
 
45
 
 
46
%% Behavior callbacks
 
47
-export([start_standalone/1, start_service/1, 
 
48
         stop_service/1, 
 
49
         services/0, service_info/1]).
 
50
 
 
51
-include_lib("inets/src/http_lib/http_internal.hrl").
 
52
-include("httpc_internal.hrl").
 
53
 
 
54
-define(DEFAULT_PROFILE, default).
 
55
 
 
56
 
 
57
%%%=========================================================================
 
58
%%%  API
 
59
%%%=========================================================================
 
60
 
 
61
default_profile() ->
 
62
    ?DEFAULT_PROFILE.
 
63
 
 
64
 
 
65
profile_name(?DEFAULT_PROFILE) ->
 
66
    httpc_manager;
 
67
profile_name(Profile) -> 
 
68
    profile_name("httpc_manager_", Profile).
 
69
 
 
70
profile_name(Prefix, Profile) when is_atom(Profile) ->
 
71
    list_to_atom(Prefix ++ atom_to_list(Profile));
 
72
profile_name(Prefix, Profile) when is_pid(Profile) ->
 
73
    ProfileStr0 = 
 
74
        string:strip(string:strip(erlang:pid_to_list(Profile), left, $<), right, $>),
 
75
    F = fun($.) -> $_; (X) -> X end, 
 
76
    ProfileStr = [F(C) || C <- ProfileStr0], 
 
77
    list_to_atom(Prefix ++ "pid_" ++ ProfileStr).
 
78
 
 
79
 
 
80
%%--------------------------------------------------------------------------
 
81
%% request(Url) -> {ok, {StatusLine, Headers, Body}} | {error,Reason} 
 
82
%% request(Url Profile) ->
 
83
%%           {ok, {StatusLine, Headers, Body}} | {error,Reason} 
 
84
%%
 
85
%%      Url - string() 
 
86
%% Description: Calls request/4 with default values.
 
87
%%--------------------------------------------------------------------------
 
88
 
 
89
request(Url) ->
 
90
    request(Url, default_profile()).
 
91
 
 
92
request(Url, Profile) ->
 
93
    request(get, {Url, []}, [], [], Profile).
 
94
 
 
95
 
 
96
%%--------------------------------------------------------------------------
 
97
%% request(Method, Request, HTTPOptions, Options [, Profile]) ->
 
98
%%           {ok, {StatusLine, Headers, Body}} | {ok, {Status, Body}} |
 
99
%%           {ok, RequestId} | {error,Reason} | {ok, {saved_as, FilePath}
 
100
%%
 
101
%%      Method - atom() = head | get | put | post | trace | options| delete 
 
102
%%      Request - {Url, Headers} | {Url, Headers, ContentType, Body} 
 
103
%%      Url - string() 
 
104
%%      HTTPOptions - [HttpOption]
 
105
%%      HTTPOption - {timeout, Time} | {connect_timeout, Time} | 
 
106
%%                   {ssl, SSLOptions} | {proxy_auth, {User, Password}}
 
107
%%      Ssloptions = ssl_options() | 
 
108
%%                   {ssl,  ssl_options()} | 
 
109
%%                   {ossl, ssl_options()} | 
 
110
%%                   {essl, ssl_options()}
 
111
%%      ssl_options() = [ssl_option()]
 
112
%%      ssl_option() =  {verify, code()} | 
 
113
%%                      {depth, depth()} | 
 
114
%%                      {certfile, path()} |
 
115
%%      {keyfile, path()} | {password, string()} | {cacertfile, path()} |
 
116
%%      {ciphers, string()} 
 
117
%%      Options - [Option]
 
118
%%      Option - {sync, Boolean} | {body_format, BodyFormat} | 
 
119
%%      {full_result, Boolean} | {stream, To} |
 
120
%%      {headers_as_is, Boolean}  
 
121
%%      StatusLine = {HTTPVersion, StatusCode, ReasonPhrase}</v>
 
122
%%      HTTPVersion = string()
 
123
%%      StatusCode = integer()
 
124
%%      ReasonPhrase = string()
 
125
%%      Headers = [Header]
 
126
%%      Header = {Field, Value}
 
127
%%      Field = string()
 
128
%%      Value = string()
 
129
%%      Body = string() | binary() - HTLM-code
 
130
%%
 
131
%% Description: Sends a HTTP-request. The function can be both
 
132
%% syncronus and asynchronous in the later case the function will
 
133
%% return {ok, RequestId} and later on a message will be sent to the
 
134
%% calling process on the format {http, {RequestId, {StatusLine,
 
135
%% Headers, Body}}} or {http, {RequestId, {error, Reason}}}
 
136
%%--------------------------------------------------------------------------
 
137
 
 
138
request(Method, Request, HttpOptions, Options) ->
 
139
    request(Method, Request, HttpOptions, Options, default_profile()). 
 
140
 
 
141
request(Method, {Url, Headers}, HTTPOptions, Options, Profile) 
 
142
  when (Method =:= options) orelse 
 
143
       (Method =:= get) orelse 
 
144
       (Method =:= head) orelse 
 
145
       (Method =:= delete) orelse 
 
146
       (Method =:= trace) andalso 
 
147
       (is_atom(Profile) orelse is_pid(Profile)) ->
 
148
    ?hcrt("request", [{method,       Method}, 
 
149
                      {url,          Url},
 
150
                      {headers,      Headers}, 
 
151
                      {http_options, HTTPOptions}, 
 
152
                      {options,      Options}, 
 
153
                      {profile,      Profile}]),
 
154
    case http_uri:parse(Url) of
 
155
        {error, Reason} ->
 
156
            {error, Reason};
 
157
        ParsedUrl ->
 
158
            handle_request(Method, Url, ParsedUrl, Headers, [], [], 
 
159
                           HTTPOptions, Options, Profile)
 
160
    end;
 
161
     
 
162
request(Method, {Url,Headers,ContentType,Body}, HTTPOptions, Options, Profile) 
 
163
  when ((Method =:= post) orelse (Method =:= put)) andalso 
 
164
       (is_atom(Profile) orelse is_pid(Profile)) ->
 
165
    ?hcrt("request", [{method,       Method}, 
 
166
                      {url,          Url},
 
167
                      {headers,      Headers}, 
 
168
                      {content_type, ContentType}, 
 
169
                      {body,         Body}, 
 
170
                      {http_options, HTTPOptions}, 
 
171
                      {options,      Options}, 
 
172
                      {profile,      Profile}]),
 
173
    case http_uri:parse(Url) of
 
174
        {error, Reason} ->
 
175
            {error, Reason};
 
176
        ParsedUrl ->
 
177
            handle_request(Method, Url, 
 
178
                           ParsedUrl, Headers, ContentType, Body, 
 
179
                           HTTPOptions, Options, Profile)
 
180
    end.
 
181
 
 
182
 
 
183
%%--------------------------------------------------------------------------
 
184
%% cancel_request(RequestId) -> ok
 
185
%% cancel_request(RequestId, Profile) -> ok
 
186
%%   RequestId - As returned by request/4  
 
187
%%                                 
 
188
%% Description: Cancels a HTTP-request.
 
189
%%-------------------------------------------------------------------------
 
190
cancel_request(RequestId) ->
 
191
    cancel_request(RequestId, default_profile()).
 
192
 
 
193
cancel_request(RequestId, Profile) 
 
194
  when is_atom(Profile) orelse is_pid(Profile) ->
 
195
    ?hcrt("cancel request", [{request_id, RequestId}, {profile, Profile}]),
 
196
    ok = httpc_manager:cancel_request(RequestId, profile_name(Profile)), 
 
197
    receive  
 
198
        %% If the request was already fulfilled throw away the 
 
199
        %% answer as the request has been canceled.
 
200
        {http, {RequestId, _}} ->
 
201
            ok 
 
202
    after 0 ->
 
203
            ok
 
204
    end.
 
205
 
 
206
 
 
207
%%--------------------------------------------------------------------------
 
208
%% set_options(Options) -> ok | {error, Reason}
 
209
%% set_options(Options, Profile) -> ok | {error, Reason}
 
210
%%   Options - [Option]
 
211
%%   Profile - atom()
 
212
%%   Option - {proxy, {Proxy, NoProxy}} | {max_sessions, MaxSessions} | 
 
213
%%            {max_pipeline_length, MaxPipeline} | 
 
214
%%            {pipeline_timeout, PipelineTimeout} | {cookies, CookieMode} | 
 
215
%%            {ipfamily, IpFamily}
 
216
%%   Proxy - {Host, Port}
 
217
%%   NoProxy - [Domain | HostName | IPAddress]   
 
218
%%   MaxSessions, MaxPipeline, PipelineTimeout = integer()   
 
219
%%   CookieMode - enabled | disabled | verify
 
220
%%   IpFamily - inet | inet6 | inet6fb4
 
221
%% Description: Informs the httpc_manager of the new settings. 
 
222
%%-------------------------------------------------------------------------
 
223
set_options(Options) ->
 
224
    set_options(Options, default_profile()).
 
225
set_options(Options, Profile) when is_atom(Profile) orelse is_pid(Profile) ->
 
226
    ?hcrt("set cookies", [{options, Options}, {profile, Profile}]),
 
227
    case validate_options(Options) of
 
228
        {ok, Opts} ->
 
229
            try 
 
230
                begin
 
231
                    httpc_manager:set_options(Opts, profile_name(Profile))
 
232
                end
 
233
            catch
 
234
                exit:{noproc, _} ->
 
235
                    {error, inets_not_started}
 
236
            end;
 
237
        {error, Reason} ->
 
238
            {error, Reason}
 
239
    end.
 
240
 
 
241
set_option(Key, Value) ->
 
242
    set_option(Key, Value, default_profile()).
 
243
 
 
244
set_option(Key, Value, Profile) ->
 
245
    set_options([{Key, Value}], Profile).
 
246
 
 
247
 
 
248
%%--------------------------------------------------------------------------
 
249
%% store_cookies(SetCookieHeaders, Url [, Profile]) -> ok | {error, reason} 
 
250
%%   
 
251
%%                                 
 
252
%% Description: Store the cookies from <SetCookieHeaders> 
 
253
%%              in the cookie database
 
254
%% for the profile <Profile>. This function shall be used when the option
 
255
%% cookies is set to verify.
 
256
%%-------------------------------------------------------------------------
 
257
store_cookies(SetCookieHeaders, Url) ->
 
258
    store_cookies(SetCookieHeaders, Url, default_profile()).
 
259
 
 
260
store_cookies(SetCookieHeaders, Url, Profile) 
 
261
  when is_atom(Profile) orelse is_pid(Profile) ->
 
262
    ?hcrt("store cookies", [{set_cookie_headers, SetCookieHeaders}, 
 
263
                            {url,                Url},
 
264
                            {profile,            Profile}]),
 
265
    try 
 
266
        begin
 
267
            {_, _, Host, Port, Path, _} = http_uri:parse(Url),
 
268
            Address     = {Host, Port}, 
 
269
            ProfileName = profile_name(Profile),
 
270
            Cookies     = httpc_cookie:cookies(SetCookieHeaders, Path, Host),
 
271
            httpc_manager:store_cookies(Cookies, Address, ProfileName), 
 
272
            ok
 
273
        end
 
274
    catch 
 
275
        exit:{noproc, _} ->
 
276
            {error, {not_started, Profile}};
 
277
        error:{badmatch, Bad} ->
 
278
            {error, {parse_failed, Bad}}
 
279
    end.
 
280
 
 
281
 
 
282
%%--------------------------------------------------------------------------
 
283
%% cookie_header(Url [, Profile]) -> Header | {error, Reason}
 
284
%%               
 
285
%% Description: Returns the cookie header that would be sent when making
 
286
%% a request to <Url>.
 
287
%%-------------------------------------------------------------------------
 
288
cookie_header(Url) ->
 
289
    cookie_header(Url, default_profile()).
 
290
 
 
291
cookie_header(Url, Profile) ->
 
292
    ?hcrt("cookie header", [{url,     Url},
 
293
                            {profile, Profile}]),
 
294
    try 
 
295
        begin
 
296
            httpc_manager:which_cookies(Url, profile_name(Profile))
 
297
        end
 
298
    catch 
 
299
        exit:{noproc, _} ->
 
300
            {error, {not_started, Profile}}
 
301
    end.
 
302
 
 
303
 
 
304
%%--------------------------------------------------------------------------
 
305
%% which_cookies() -> [cookie()]
 
306
%% which_cookies(Profile) -> [cookie()]
 
307
%%               
 
308
%% Description: Debug function, dumping the cookie database
 
309
%%-------------------------------------------------------------------------
 
310
which_cookies() ->
 
311
    which_cookies(default_profile()).
 
312
 
 
313
which_cookies(Profile) ->
 
314
    ?hcrt("which cookies", [{profile, Profile}]),
 
315
    try 
 
316
        begin
 
317
            httpc_manager:which_cookies(profile_name(Profile))
 
318
        end
 
319
    catch 
 
320
        exit:{noproc, _} ->
 
321
            {error, {not_started, Profile}}
 
322
    end.
 
323
 
 
324
 
 
325
%%--------------------------------------------------------------------------
 
326
%% info() -> list()
 
327
%% info(Profile) -> list()
 
328
%%               
 
329
%% Description: Debug function, retreive info about the profile
 
330
%%-------------------------------------------------------------------------
 
331
info() ->
 
332
    info(default_profile()).
 
333
 
 
334
info(Profile) ->
 
335
    ?hcrt("info", [{profile, Profile}]),
 
336
    try 
 
337
        begin
 
338
            httpc_manager:info(profile_name(Profile))
 
339
        end
 
340
    catch 
 
341
        exit:{noproc, _} ->
 
342
            {error, {not_started, Profile}}
 
343
    end.
 
344
 
 
345
 
 
346
%%--------------------------------------------------------------------------
 
347
%% reset_cookies() -> void()
 
348
%% reset_cookies(Profile) -> void()
 
349
%%               
 
350
%% Description: Debug function, reset the cookie database
 
351
%%-------------------------------------------------------------------------
 
352
reset_cookies() ->
 
353
    reset_cookies(default_profile()).
 
354
 
 
355
reset_cookies(Profile) ->
 
356
    ?hcrt("reset cookies", [{profile, Profile}]),
 
357
    try 
 
358
        begin
 
359
            httpc_manager:reset_cookies(profile_name(Profile))
 
360
        end
 
361
    catch 
 
362
        exit:{noproc, _} ->
 
363
            {error, {not_started, Profile}}
 
364
    end.
 
365
 
 
366
 
 
367
%%--------------------------------------------------------------------------
 
368
%% stream_next(Pid) -> Header | {error, Reason}
 
369
%%               
 
370
%% Description: Triggers the next message to be streamed, e.i. 
 
371
%%              same behavior as active once for sockets.
 
372
%%-------------------------------------------------------------------------
 
373
stream_next(Pid) ->
 
374
    ?hcrt("stream next", [{handler, Pid}]),
 
375
    httpc_handler:stream_next(Pid).
 
376
 
 
377
 
 
378
%%%========================================================================
 
379
%%% Behaviour callbacks
 
380
%%%========================================================================
 
381
start_standalone(PropList) ->
 
382
    ?hcrt("start standalone", [{proplist, PropList}]),
 
383
    case proplists:get_value(profile, PropList) of
 
384
        undefined ->
 
385
            {error, no_profile};
 
386
        Profile ->
 
387
            Dir = 
 
388
                proplists:get_value(data_dir, PropList, only_session_cookies),
 
389
            httpc_manager:start_link(Profile, Dir, stand_alone)
 
390
    end.
 
391
 
 
392
start_service(Config) ->
 
393
    ?hcrt("start service", [{config, Config}]),
 
394
    httpc_profile_sup:start_child(Config).
 
395
 
 
396
stop_service(Profile) when is_atom(Profile) ->
 
397
    ?hcrt("stop service", [{profile, Profile}]),
 
398
    httpc_profile_sup:stop_child(Profile);
 
399
stop_service(Pid) when is_pid(Pid) ->
 
400
    ?hcrt("stop service", [{pid, Pid}]),
 
401
    case service_info(Pid) of
 
402
        {ok, [{profile, Profile}]} ->
 
403
            stop_service(Profile);
 
404
        Error ->
 
405
            Error
 
406
    end.
 
407
 
 
408
services() ->
 
409
    [{httpc, Pid} || {_, Pid, _, _} <- 
 
410
                         supervisor:which_children(httpc_profile_sup)].
 
411
service_info(Pid) ->
 
412
    try [{ChildName, ChildPid} || 
 
413
            {ChildName, ChildPid, _, _} <- 
 
414
                supervisor:which_children(httpc_profile_sup)] of
 
415
        Children ->
 
416
            child_name2info(child_name(Pid, Children))
 
417
    catch
 
418
        exit:{noproc, _} ->
 
419
            {error, service_not_available} 
 
420
    end.
 
421
 
 
422
 
 
423
%%%========================================================================
 
424
%%% Internal functions
 
425
%%%========================================================================
 
426
 
 
427
handle_request(Method, Url, 
 
428
               {Scheme, UserInfo, Host, Port, Path, Query}, 
 
429
               Headers, ContentType, Body, 
 
430
               HTTPOptions0, Options0, Profile) ->
 
431
 
 
432
    Started    = http_util:timestamp(), 
 
433
    NewHeaders = [{http_util:to_lower(Key), Val} || {Key, Val} <- Headers],
 
434
 
 
435
    try
 
436
        begin
 
437
            HTTPOptions   = http_options(HTTPOptions0),
 
438
            Options       = request_options(Options0), 
 
439
            Sync          = proplists:get_value(sync,   Options),
 
440
            Stream        = proplists:get_value(stream, Options),
 
441
            Host2         = header_host(Scheme, Host, Port), 
 
442
            HeadersRecord = header_record(NewHeaders, Host2, HTTPOptions),
 
443
            Receiver   = proplists:get_value(receiver, Options),
 
444
            SocketOpts = proplists:get_value(socket_opts, Options),
 
445
            UrlEncodeBool =  HTTPOptions#http_options.url_encode,
 
446
            MaybeEscPath = url_encode(Path, UrlEncodeBool),
 
447
            MaybeEscQuery = url_encode(Query, UrlEncodeBool),
 
448
            AbsUri  = url_encode(Url, UrlEncodeBool),
 
449
 
 
450
            Request = #request{from          = Receiver,
 
451
                               scheme        = Scheme, 
 
452
                               address       = {Host, Port},
 
453
                               path          = MaybeEscPath,
 
454
                               pquery        = MaybeEscQuery,
 
455
                               method        = Method,
 
456
                               headers       = HeadersRecord, 
 
457
                               content       = {ContentType, Body},
 
458
                               settings      = HTTPOptions, 
 
459
                               abs_uri       = AbsUri,
 
460
                               userinfo      = UserInfo, 
 
461
                               stream        = Stream,
 
462
                               headers_as_is = headers_as_is(Headers, Options),
 
463
                               socket_opts   = SocketOpts, 
 
464
                               started       = Started},
 
465
            case httpc_manager:request(Request, profile_name(Profile)) of
 
466
                {ok, RequestId} ->
 
467
                    handle_answer(RequestId, Sync, Options);
 
468
                {error, Reason} ->
 
469
                    {error, Reason}
 
470
            end
 
471
        end
 
472
    catch
 
473
        error:{noproc, _} ->
 
474
            {error, {not_started, Profile}};
 
475
        throw:Error ->
 
476
            Error
 
477
    end.
 
478
 
 
479
url_encode(URI, true) ->
 
480
    http_uri:encode(URI);
 
481
url_encode(URI, false) ->
 
482
    URI.
 
483
 
 
484
handle_answer(RequestId, false, _) ->
 
485
    {ok, RequestId};
 
486
handle_answer(RequestId, true, Options) ->
 
487
    receive
 
488
        {http, {RequestId, saved_to_file}} ->
 
489
            {ok, saved_to_file};
 
490
        {http, {RequestId, {_,_,_} = Result}} ->
 
491
            return_answer(Options, Result);
 
492
        {http, {RequestId, {error, Reason}}} ->
 
493
            {error, Reason}
 
494
    end.
 
495
 
 
496
return_answer(Options, {{"HTTP/0.9",_,_}, _, BinBody}) ->
 
497
    Body = maybe_format_body(BinBody, Options),
 
498
    {ok, Body};
 
499
   
 
500
return_answer(Options, {StatusLine, Headers, BinBody}) ->
 
501
 
 
502
    Body = maybe_format_body(BinBody, Options),
 
503
    
 
504
    case proplists:get_value(full_result, Options, true) of
 
505
        true ->
 
506
            {ok, {StatusLine, Headers, Body}};
 
507
        false ->
 
508
            {_, Status, _} = StatusLine,
 
509
            {ok, {Status, Body}}
 
510
    end.
 
511
 
 
512
maybe_format_body(BinBody, Options) ->
 
513
    case proplists:get_value(body_format, Options, string) of
 
514
        string ->
 
515
            binary_to_list(BinBody);
 
516
        _ ->
 
517
            BinBody
 
518
    end.
 
519
 
 
520
%% This options is a workaround for http servers that do not follow the 
 
521
%% http standard and have case sensative header parsing. Should only be
 
522
%% used if there is no other way to communicate with the server or for
 
523
%% testing purpose.
 
524
headers_as_is(Headers, Options) ->
 
525
     case proplists:get_value(headers_as_is, Options, false) of
 
526
         false ->
 
527
             [];
 
528
         true  ->
 
529
             Headers
 
530
     end.
 
531
 
 
532
 
 
533
http_options(HttpOptions) ->
 
534
    HttpOptionsDefault = http_options_default(),
 
535
    http_options(HttpOptionsDefault, HttpOptions, #http_options{}).
 
536
 
 
537
http_options([], [], Acc) ->
 
538
    Acc;
 
539
http_options([], HttpOptions, Acc) ->
 
540
    Fun = fun(BadOption) ->
 
541
                    Report = io_lib:format("Invalid option ~p ignored ~n", 
 
542
                                           [BadOption]),
 
543
                    error_logger:info_report(Report)
 
544
          end,
 
545
    lists:foreach(Fun, HttpOptions),
 
546
    Acc;
 
547
http_options([{Tag, Default, Idx, Post} | Defaults], HttpOptions, Acc) ->
 
548
    case lists:keysearch(Tag, 1, HttpOptions) of
 
549
        {value, {Tag, Val0}} ->
 
550
            case Post(Val0) of
 
551
                {ok, Val} ->
 
552
                    Acc2 = setelement(Idx, Acc, Val),
 
553
                    HttpOptions2 = lists:keydelete(Tag, 1, HttpOptions),
 
554
                    http_options(Defaults, HttpOptions2, Acc2);
 
555
                error ->
 
556
                    Report = io_lib:format("Invalid option ~p:~p ignored ~n", 
 
557
                                           [Tag, Val0]),
 
558
                    error_logger:info_report(Report),
 
559
                    HttpOptions2 = lists:keydelete(Tag, 1, HttpOptions),
 
560
                    http_options(Defaults, HttpOptions2, Acc)
 
561
            end;
 
562
        false ->
 
563
            DefaultVal = 
 
564
                case Default of
 
565
                    {value, Val} ->
 
566
                        Val;
 
567
                    {field, DefaultIdx} ->
 
568
                        element(DefaultIdx, Acc)
 
569
                end,
 
570
            Acc2 = setelement(Idx, Acc, DefaultVal),
 
571
            http_options(Defaults, HttpOptions, Acc2)
 
572
    end.
 
573
                    
 
574
http_options_default() ->
 
575
    VersionPost = 
 
576
        fun(Value) when is_atom(Value) ->
 
577
                {ok, http_util:to_upper(atom_to_list(Value))};
 
578
           (Value) when is_list(Value) ->
 
579
                {ok, http_util:to_upper(Value)};
 
580
           (_) ->
 
581
                error
 
582
        end,
 
583
    TimeoutPost = fun(Value) when is_integer(Value) andalso (Value >= 0) ->
 
584
                          {ok, Value};
 
585
                     (infinity = Value) ->
 
586
                          {ok, Value};
 
587
                     (_) ->
 
588
                          error
 
589
                  end,
 
590
    AutoRedirectPost =  boolfun(),
 
591
 
 
592
    SslPost = fun(Value) when is_list(Value) ->
 
593
                      {ok, {?HTTP_DEFAULT_SSL_KIND, Value}};
 
594
                 ({ssl, SslOptions}) when is_list(SslOptions) ->
 
595
                      {ok, {?HTTP_DEFAULT_SSL_KIND, SslOptions}};
 
596
                 ({ossl, SslOptions}) when is_list(SslOptions) ->
 
597
                      {ok, {ossl, SslOptions}};
 
598
                 ({essl, SslOptions}) when is_list(SslOptions) ->
 
599
                      {ok, {essl, SslOptions}};
 
600
                 (_) ->
 
601
                      error
 
602
              end,
 
603
    ProxyAuthPost = fun({User, Passwd} = Value) when is_list(User) andalso 
 
604
                                                     is_list(Passwd) ->
 
605
                            {ok, Value};
 
606
                       (_) ->
 
607
                            error
 
608
                    end,
 
609
    RelaxedPost =  boolfun(),
 
610
 
 
611
    ConnTimeoutPost = 
 
612
        fun(Value) when is_integer(Value) andalso (Value >= 0) ->
 
613
                {ok, Value};
 
614
           (infinity = Value) ->
 
615
                {ok, Value};
 
616
           (_) ->
 
617
                error
 
618
        end,
 
619
 
 
620
    UrlDecodePost =  boolfun(),
 
621
    [
 
622
     {version,         {value, "HTTP/1.1"},            #http_options.version,         VersionPost}, 
 
623
     {timeout,         {value, ?HTTP_REQUEST_TIMEOUT}, #http_options.timeout,         TimeoutPost},
 
624
     {autoredirect,    {value, true},                  #http_options.autoredirect,    AutoRedirectPost},
 
625
     {ssl,             {value, {?HTTP_DEFAULT_SSL_KIND, []}}, #http_options.ssl,             SslPost},
 
626
     {proxy_auth,      {value, undefined},             #http_options.proxy_auth,      ProxyAuthPost},
 
627
     {relaxed,         {value, false},                 #http_options.relaxed,         RelaxedPost},
 
628
     {url_encode,      {value, false},                 #http_options.url_encode,      UrlDecodePost},
 
629
     %% this field has to be *after* the timeout option (as that field is used for the default value)
 
630
     {connect_timeout, {field, #http_options.timeout}, #http_options.connect_timeout, ConnTimeoutPost}
 
631
    ].
 
632
 
 
633
boolfun() ->
 
634
    fun(Value) when (Value =:= true) orelse
 
635
                    (Value =:= false) ->
 
636
            {ok, Value};
 
637
       (_) ->
 
638
            error
 
639
    end.
 
640
 
 
641
request_options_defaults() ->
 
642
    VerifyBoolean = boolfun(),
 
643
 
 
644
    VerifySync = VerifyBoolean,
 
645
 
 
646
    VerifyStream = 
 
647
        fun(none = _Value) -> 
 
648
                ok;
 
649
           (self = _Value) -> 
 
650
                ok;
 
651
           ({self, once} = _Value) -> 
 
652
                ok;
 
653
           (Value) when is_list(Value) -> 
 
654
                ok;
 
655
           (_) -> 
 
656
                error
 
657
        end,
 
658
 
 
659
    VerifyBodyFormat = 
 
660
        fun(string = _Value) ->
 
661
                ok;
 
662
           (binary = _Value) ->
 
663
                ok;
 
664
           (_) ->
 
665
                error
 
666
        end,
 
667
    
 
668
    VerifyFullResult = VerifyBoolean,
 
669
 
 
670
    VerifyHeaderAsIs = VerifyBoolean,
 
671
 
 
672
    VerifyReceiver = 
 
673
        fun(Value) when is_pid(Value) ->
 
674
                ok;
 
675
           ({M, F, A}) when (is_atom(M) andalso 
 
676
                             is_atom(F) andalso 
 
677
                             is_list(A)) ->
 
678
                ok;
 
679
           (Value) when is_function(Value, 1) ->
 
680
                ok;
 
681
           (_) ->
 
682
                error
 
683
        end,
 
684
 
 
685
    VerifySocketOpts = 
 
686
        fun([]) ->
 
687
                {ok, undefined};
 
688
           (Value) when is_list(Value) ->
 
689
                ok;
 
690
           (_) ->
 
691
                error
 
692
        end,
 
693
 
 
694
    [
 
695
     {sync,          true,      VerifySync}, 
 
696
     {stream,        none,      VerifyStream},
 
697
     {body_format,   string,    VerifyBodyFormat},
 
698
     {full_result,   true,      VerifyFullResult},
 
699
     {headers_as_is, false,     VerifyHeaderAsIs},
 
700
     {receiver,      self(),    VerifyReceiver},
 
701
     {socket_opts,   undefined, VerifySocketOpts}
 
702
    ]. 
 
703
 
 
704
request_options(Options) ->
 
705
    Defaults = request_options_defaults(), 
 
706
    request_options(Defaults, Options, []).
 
707
 
 
708
request_options([], [], Acc) ->
 
709
    request_options_sanity_check(Acc),
 
710
    lists:reverse(Acc);
 
711
request_options([], Options, Acc) ->
 
712
    Fun = fun(BadOption) ->
 
713
                    Report = io_lib:format("Invalid option ~p ignored ~n", 
 
714
                                           [BadOption]),
 
715
                    error_logger:info_report(Report)
 
716
          end,
 
717
    lists:foreach(Fun, Options),
 
718
    Acc;
 
719
request_options([{Key, DefaultVal, Verify} | Defaults], Options, Acc) ->
 
720
    case lists:keysearch(Key, 1, Options) of
 
721
        {value, {Key, Value}} ->
 
722
            case Verify(Value) of
 
723
                ok ->
 
724
                    Options2 = lists:keydelete(Key, 1, Options),
 
725
                    request_options(Defaults, Options2, [{Key, Value} | Acc]);
 
726
                {ok, Value2} ->
 
727
                    Options2 = lists:keydelete(Key, 1, Options),
 
728
                    request_options(Defaults, Options2, [{Key, Value2} | Acc]);
 
729
                error ->
 
730
                    Report = io_lib:format("Invalid option ~p:~p ignored ~n", 
 
731
                                           [Key, Value]),
 
732
                    error_logger:info_report(Report),
 
733
                    Options2 = lists:keydelete(Key, 1, Options),
 
734
                    request_options(Defaults, Options2, Acc)
 
735
            end;
 
736
        false ->
 
737
            request_options(Defaults, Options, [{Key, DefaultVal} | Acc])
 
738
    end.
 
739
 
 
740
request_options_sanity_check(Opts) ->
 
741
    case proplists:get_value(sync, Opts) of
 
742
        Sync when (Sync =:= true) ->
 
743
            case proplists:get_value(receiver, Opts) of
 
744
                Pid when is_pid(Pid) andalso (Pid =:= self()) ->
 
745
                    ok;
 
746
                BadReceiver ->
 
747
                    throw({error, {bad_options_combo, 
 
748
                                   [{sync, true}, {receiver, BadReceiver}]}})
 
749
            end,
 
750
            case proplists:get_value(stream, Opts) of
 
751
                Stream when (Stream =:= self) orelse 
 
752
                            (Stream =:= {self, once}) ->
 
753
                    throw({error, streaming_error});
 
754
                _ ->
 
755
                    ok
 
756
            end;
 
757
        _ ->
 
758
            ok
 
759
    end,
 
760
    ok.
 
761
 
 
762
validate_options(Options) ->
 
763
    (catch validate_options(Options, [])).
 
764
 
 
765
validate_options([], ValidateOptions) ->
 
766
    {ok, lists:reverse(ValidateOptions)};
 
767
 
 
768
validate_options([{proxy, Proxy} = Opt| Tail], Acc) ->
 
769
    validate_proxy(Proxy),
 
770
    validate_options(Tail, [Opt | Acc]);
 
771
 
 
772
validate_options([{max_sessions, Value} = Opt| Tail], Acc) ->
 
773
    validate_max_sessions(Value),
 
774
    validate_options(Tail, [Opt | Acc]);
 
775
 
 
776
validate_options([{keep_alive_timeout, Value} = Opt| Tail], Acc) ->
 
777
    validate_keep_alive_timeout(Value),
 
778
    validate_options(Tail, [Opt | Acc]);
 
779
 
 
780
validate_options([{max_keep_alive_length, Value} = Opt| Tail], Acc) ->
 
781
    validate_max_keep_alive_length(Value),
 
782
    validate_options(Tail, [Opt | Acc]);
 
783
 
 
784
validate_options([{pipeline_timeout, Value} = Opt| Tail], Acc) ->
 
785
    validate_pipeline_timeout(Value),
 
786
    validate_options(Tail, [Opt | Acc]);
 
787
 
 
788
validate_options([{max_pipeline_length, Value} = Opt| Tail], Acc) ->
 
789
    validate_max_pipeline_length(Value), 
 
790
    validate_options(Tail, [Opt | Acc]);
 
791
 
 
792
validate_options([{cookies, Value} = Opt| Tail], Acc) ->
 
793
    validate_cookies(Value),
 
794
    validate_options(Tail, [Opt | Acc]);
 
795
 
 
796
validate_options([{ipfamily, Value} = Opt| Tail], Acc) ->
 
797
    validate_ipfamily(Value), 
 
798
    validate_options(Tail, [Opt | Acc]);
 
799
 
 
800
%% For backward compatibillity
 
801
validate_options([{ipv6, Value}| Tail], Acc) ->
 
802
    NewValue = validate_ipv6(Value), 
 
803
    Opt = {ipfamily, NewValue},
 
804
    validate_options(Tail, [Opt | Acc]);
 
805
 
 
806
validate_options([{ip, Value} = Opt| Tail], Acc) ->
 
807
    validate_ip(Value),
 
808
    validate_options(Tail, [Opt | Acc]);
 
809
 
 
810
validate_options([{port, Value} = Opt| Tail], Acc) ->
 
811
    validate_port(Value), 
 
812
    validate_options(Tail, [Opt | Acc]);
 
813
 
 
814
validate_options([{socket_opts, Value} = Opt| Tail], Acc) ->
 
815
    validate_socket_opts(Value), 
 
816
    validate_options(Tail, [Opt | Acc]);
 
817
 
 
818
validate_options([{verbose, Value} = Opt| Tail], Acc) ->
 
819
    validate_verbose(Value), 
 
820
    validate_options(Tail, [Opt | Acc]);
 
821
 
 
822
validate_options([{_, _} = Opt| _], _Acc) ->
 
823
    {error, {not_an_option, Opt}}.
 
824
 
 
825
 
 
826
validate_proxy({{ProxyHost, ProxyPort}, NoProxy} = Proxy) 
 
827
  when is_list(ProxyHost) andalso 
 
828
       is_integer(ProxyPort) andalso 
 
829
       is_list(NoProxy) ->
 
830
    Proxy;
 
831
validate_proxy(BadProxy) ->
 
832
    bad_option(proxy, BadProxy).
 
833
 
 
834
validate_max_sessions(Value) when is_integer(Value) andalso (Value >= 0) ->
 
835
    Value;
 
836
validate_max_sessions(BadValue) ->
 
837
    bad_option(max_sessions, BadValue).
 
838
 
 
839
validate_keep_alive_timeout(Value) when is_integer(Value) andalso (Value >= 0) ->
 
840
    Value;
 
841
validate_keep_alive_timeout(infinity = Value) ->
 
842
    Value;
 
843
validate_keep_alive_timeout(BadValue) ->
 
844
    bad_option(keep_alive_timeout, BadValue).
 
845
 
 
846
validate_max_keep_alive_length(Value) when is_integer(Value) andalso (Value >= 0) ->
 
847
    Value;
 
848
validate_max_keep_alive_length(BadValue) ->
 
849
    bad_option(max_keep_alive_length, BadValue).
 
850
 
 
851
validate_pipeline_timeout(Value) when is_integer(Value) ->
 
852
    Value;
 
853
validate_pipeline_timeout(infinity = Value) ->
 
854
    Value;
 
855
validate_pipeline_timeout(BadValue) ->
 
856
    bad_option(pipeline_timeout, BadValue).
 
857
 
 
858
validate_max_pipeline_length(Value) when is_integer(Value) ->
 
859
    Value;
 
860
validate_max_pipeline_length(BadValue) ->
 
861
    bad_option(max_pipeline_length, BadValue).
 
862
 
 
863
validate_cookies(Value) 
 
864
  when ((Value =:= enabled)  orelse 
 
865
        (Value =:= disabled) orelse 
 
866
        (Value =:= verify)) ->
 
867
    Value;
 
868
validate_cookies(BadValue) ->
 
869
    bad_option(cookies, BadValue).
 
870
 
 
871
validate_ipv6(Value) when (Value =:= enabled) orelse (Value =:= disabled) ->
 
872
    case Value of
 
873
        enabled ->
 
874
            inet6fb4;
 
875
        disabled ->
 
876
            inet
 
877
    end;  
 
878
validate_ipv6(BadValue) ->
 
879
    bad_option(ipv6, BadValue).
 
880
 
 
881
validate_ipfamily(Value) 
 
882
  when (Value =:= inet) orelse (Value =:= inet6) orelse (Value =:= inet6fb4) ->
 
883
    Value;
 
884
validate_ipfamily(BadValue) ->
 
885
    bad_option(ipfamily, BadValue).
 
886
 
 
887
validate_ip(Value) 
 
888
  when is_tuple(Value) andalso ((size(Value) =:= 4) orelse (size(Value) =:= 8)) ->
 
889
    Value;
 
890
validate_ip(BadValue) ->
 
891
    bad_option(ip, BadValue).
 
892
    
 
893
validate_port(Value) when is_integer(Value) ->
 
894
    Value;
 
895
validate_port(BadValue) ->
 
896
    bad_option(port, BadValue).
 
897
 
 
898
validate_socket_opts(Value) when is_list(Value) ->
 
899
    Value;
 
900
validate_socket_opts(BadValue) ->
 
901
    bad_option(socket_opts, BadValue).
 
902
 
 
903
validate_verbose(Value) 
 
904
  when ((Value =:= false) orelse 
 
905
        (Value =:= verbose) orelse 
 
906
        (Value =:= debug) orelse 
 
907
        (Value =:= trace)) ->
 
908
    ok;
 
909
validate_verbose(BadValue) ->
 
910
    bad_option(verbose, BadValue).
 
911
 
 
912
bad_option(Option, BadValue) ->
 
913
    throw({error, {bad_option, Option, BadValue}}).
 
914
 
 
915
 
 
916
header_host(https, Host, 443 = _Port) ->
 
917
    Host;
 
918
header_host(http, Host, 80 = _Port) ->
 
919
    Host;
 
920
header_host(_Scheme, Host, Port) ->
 
921
    Host ++ ":" ++ integer_to_list(Port).
 
922
 
 
923
 
 
924
header_record(NewHeaders, Host, #http_options{version = Version}) ->
 
925
    header_record(NewHeaders, #http_request_h{}, Host, Version).
 
926
 
 
927
header_record([], RequestHeaders, Host, Version) ->
 
928
    validate_headers(RequestHeaders, Host, Version);
 
929
header_record([{"cache-control", Val} | Rest], RequestHeaders, Host, Version) ->
 
930
    header_record(Rest, RequestHeaders#http_request_h{'cache-control' = Val},
 
931
                  Host, Version);  
 
932
header_record([{"connection", Val} | Rest], RequestHeaders, Host, Version) ->
 
933
    header_record(Rest, RequestHeaders#http_request_h{connection = Val}, Host,
 
934
                 Version);
 
935
header_record([{"date", Val} | Rest], RequestHeaders, Host, Version) ->
 
936
    header_record(Rest, RequestHeaders#http_request_h{date = Val}, Host, 
 
937
                  Version);  
 
938
header_record([{"pragma", Val} | Rest], RequestHeaders, Host, Version) ->
 
939
    header_record(Rest, RequestHeaders#http_request_h{pragma = Val}, Host,
 
940
                  Version);  
 
941
header_record([{"trailer", Val} | Rest], RequestHeaders, Host, Version) ->
 
942
    header_record(Rest, RequestHeaders#http_request_h{trailer = Val}, Host,
 
943
                  Version);  
 
944
header_record([{"transfer-encoding", Val} | Rest], RequestHeaders, Host, 
 
945
              Version) ->
 
946
    header_record(Rest, 
 
947
                  RequestHeaders#http_request_h{'transfer-encoding' = Val},
 
948
                  Host, Version);  
 
949
header_record([{"upgrade", Val} | Rest], RequestHeaders, Host, Version) ->
 
950
    header_record(Rest, RequestHeaders#http_request_h{upgrade = Val}, Host,
 
951
                  Version);  
 
952
header_record([{"via", Val} | Rest], RequestHeaders, Host, Version) ->
 
953
    header_record(Rest, RequestHeaders#http_request_h{via = Val}, Host, 
 
954
                  Version);  
 
955
header_record([{"warning", Val} | Rest], RequestHeaders, Host, Version) ->
 
956
    header_record(Rest, RequestHeaders#http_request_h{warning = Val}, Host,
 
957
                  Version);  
 
958
header_record([{"accept", Val} | Rest], RequestHeaders, Host, Version) ->
 
959
    header_record(Rest, RequestHeaders#http_request_h{accept = Val}, Host,
 
960
                  Version);  
 
961
header_record([{"accept-charset", Val} | Rest], RequestHeaders, Host, Version) ->
 
962
    header_record(Rest, RequestHeaders#http_request_h{'accept-charset' = Val}, 
 
963
                  Host, Version);  
 
964
header_record([{"accept-encoding", Val} | Rest], RequestHeaders, Host, 
 
965
              Version) ->
 
966
    header_record(Rest, RequestHeaders#http_request_h{'accept-encoding' = Val},
 
967
                  Host, Version);  
 
968
header_record([{"accept-language", Val} | Rest], RequestHeaders, Host, 
 
969
              Version) ->
 
970
    header_record(Rest, RequestHeaders#http_request_h{'accept-language' = Val},
 
971
                  Host, Version);  
 
972
header_record([{"authorization", Val} | Rest], RequestHeaders, Host, Version) ->
 
973
    header_record(Rest, RequestHeaders#http_request_h{authorization = Val}, 
 
974
                  Host, Version);  
 
975
header_record([{"expect", Val} | Rest], RequestHeaders, Host, Version) ->
 
976
    header_record(Rest, RequestHeaders#http_request_h{expect = Val}, Host,
 
977
                  Version);
 
978
header_record([{"from", Val} | Rest], RequestHeaders, Host, Version) ->
 
979
    header_record(Rest, RequestHeaders#http_request_h{from = Val}, Host, 
 
980
                  Version);  
 
981
header_record([{"host", Val} | Rest], RequestHeaders, Host, Version) ->
 
982
    header_record(Rest, RequestHeaders#http_request_h{host = Val}, Host, 
 
983
                  Version);
 
984
header_record([{"if-match", Val} | Rest], RequestHeaders, Host, Version) ->
 
985
    header_record(Rest, RequestHeaders#http_request_h{'if-match' = Val},
 
986
                  Host, Version);  
 
987
header_record([{"if-modified-since", Val} | Rest], RequestHeaders, Host, 
 
988
              Version) ->
 
989
    header_record(Rest, 
 
990
                  RequestHeaders#http_request_h{'if-modified-since' = Val},
 
991
                  Host, Version);  
 
992
header_record([{"if-none-match", Val} | Rest], RequestHeaders, Host, Version) ->
 
993
    header_record(Rest, RequestHeaders#http_request_h{'if-none-match' = Val}, 
 
994
                  Host, Version);  
 
995
header_record([{"if-range", Val} | Rest], RequestHeaders, Host, Version) ->
 
996
    header_record(Rest, RequestHeaders#http_request_h{'if-range' = Val}, 
 
997
                  Host, Version);  
 
998
 
 
999
header_record([{"if-unmodified-since", Val} | Rest], RequestHeaders, Host, 
 
1000
              Version) ->
 
1001
    header_record(Rest, RequestHeaders#http_request_h{'if-unmodified-since' 
 
1002
                                                      = Val}, Host, Version);  
 
1003
header_record([{"max-forwards", Val} | Rest], RequestHeaders, Host, Version) ->
 
1004
    header_record(Rest, RequestHeaders#http_request_h{'max-forwards' = Val}, 
 
1005
                  Host, Version);  
 
1006
header_record([{"proxy-authorization", Val} | Rest], RequestHeaders, Host, 
 
1007
              Version) ->
 
1008
    header_record(Rest, RequestHeaders#http_request_h{'proxy-authorization' 
 
1009
                                                      = Val}, Host, Version);  
 
1010
header_record([{"range", Val} | Rest], RequestHeaders, Host, Version) ->
 
1011
    header_record(Rest, RequestHeaders#http_request_h{range = Val}, Host, 
 
1012
                  Version);  
 
1013
header_record([{"referer", Val} | Rest], RequestHeaders, Host, Version) ->
 
1014
    header_record(Rest, RequestHeaders#http_request_h{referer = Val}, Host, 
 
1015
                  Version);  
 
1016
header_record([{"te", Val} | Rest], RequestHeaders, Host, Version) ->
 
1017
    header_record(Rest, RequestHeaders#http_request_h{te = Val}, Host, 
 
1018
                  Version);  
 
1019
header_record([{"user-agent", Val} | Rest], RequestHeaders, Host, Version) ->
 
1020
    header_record(Rest, RequestHeaders#http_request_h{'user-agent' = Val}, 
 
1021
                  Host, Version);  
 
1022
header_record([{"allow", Val} | Rest], RequestHeaders, Host, Version) ->
 
1023
    header_record(Rest, RequestHeaders#http_request_h{allow = Val}, Host, 
 
1024
                  Version);  
 
1025
header_record([{"content-encoding", Val} | Rest], RequestHeaders, Host, 
 
1026
              Version) ->
 
1027
    header_record(Rest, 
 
1028
                  RequestHeaders#http_request_h{'content-encoding' = Val},
 
1029
                  Host, Version);  
 
1030
header_record([{"content-language", Val} | Rest], RequestHeaders, 
 
1031
              Host, Version) ->
 
1032
    header_record(Rest, 
 
1033
                  RequestHeaders#http_request_h{'content-language' = Val}, 
 
1034
                  Host, Version);  
 
1035
header_record([{"content-length", Val} | Rest], RequestHeaders, Host, Version) ->
 
1036
    header_record(Rest, RequestHeaders#http_request_h{'content-length' = Val},
 
1037
                  Host, Version);  
 
1038
header_record([{"content-location", Val} | Rest], RequestHeaders, 
 
1039
              Host, Version) ->
 
1040
    header_record(Rest, 
 
1041
                  RequestHeaders#http_request_h{'content-location' = Val},
 
1042
                  Host, Version);  
 
1043
header_record([{"content-md5", Val} | Rest], RequestHeaders, Host, Version) ->
 
1044
    header_record(Rest, RequestHeaders#http_request_h{'content-md5' = Val}, 
 
1045
                  Host, Version);  
 
1046
header_record([{"content-range", Val} | Rest], RequestHeaders, Host, Version) ->
 
1047
    header_record(Rest, RequestHeaders#http_request_h{'content-range' = Val},
 
1048
                  Host, Version);  
 
1049
header_record([{"content-type", Val} | Rest], RequestHeaders, Host, Version) ->
 
1050
    header_record(Rest, RequestHeaders#http_request_h{'content-type' = Val}, 
 
1051
                  Host, Version);  
 
1052
header_record([{"expires", Val} | Rest], RequestHeaders, Host, Version) ->
 
1053
    header_record(Rest, RequestHeaders#http_request_h{expires = Val}, Host, 
 
1054
                  Version);  
 
1055
header_record([{"last-modified", Val} | Rest], RequestHeaders, Host, Version) ->
 
1056
    header_record(Rest, RequestHeaders#http_request_h{'last-modified' = Val},
 
1057
                  Host, Version);  
 
1058
header_record([{Key, Val} | Rest], RequestHeaders, Host, Version) ->
 
1059
    header_record(Rest, RequestHeaders#http_request_h{
 
1060
                          other = [{Key, Val} |
 
1061
                                   RequestHeaders#http_request_h.other]}, 
 
1062
                  Host, Version).
 
1063
 
 
1064
validate_headers(RequestHeaders = #http_request_h{te = undefined}, Host, 
 
1065
                 "HTTP/1.1" = Version) ->
 
1066
    validate_headers(RequestHeaders#http_request_h{te = ""}, Host, 
 
1067
                     "HTTP/1.1" = Version);
 
1068
validate_headers(RequestHeaders = #http_request_h{host = undefined}, 
 
1069
                 Host, "HTTP/1.1" = Version) ->
 
1070
    validate_headers(RequestHeaders#http_request_h{host = Host}, Host, Version);
 
1071
validate_headers(RequestHeaders, _, _) ->
 
1072
    RequestHeaders.
 
1073
 
 
1074
 
 
1075
child_name2info(undefined) ->
 
1076
    {error, no_such_service};
 
1077
child_name2info(httpc_manager) ->
 
1078
    {ok, [{profile, default}]};
 
1079
child_name2info({httpc, Profile}) ->
 
1080
    {ok, [{profile, Profile}]}.
 
1081
 
 
1082
child_name(_, []) ->
 
1083
    undefined;
 
1084
child_name(Pid, [{Name, Pid} | _]) ->
 
1085
    Name;
 
1086
child_name(Pid, [_ | Children]) ->
 
1087
    child_name(Pid, Children).
 
1088
 
 
1089
%% d(F) ->
 
1090
%%    d(F, []).
 
1091
 
 
1092
%% d(F, A) -> 
 
1093
%%     d(get(dbg), F, A).
 
1094
 
 
1095
%% d(true, F, A) ->
 
1096
%%     io:format(user, "~w:~w:" ++ F ++ "~n", [self(), ?MODULE | A]);
 
1097
%% d(_, _, _) ->
 
1098
%%     ok.
 
1099