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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

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