~ubuntu-branches/ubuntu/lucid/erlang/lucid-proposed

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
29
29
%% API
30
30
-export([request/1, request/2, request/4, request/5,
31
31
         cancel_request/1, cancel_request/2,
 
32
         set_option/2, set_option/3,
32
33
         set_options/1, set_options/2,
33
34
         verify_cookies/2, verify_cookies/3, cookie_header/1, 
34
 
         cookie_header/2, stream_next/1]).
 
35
         cookie_header/2, stream_next/1,
 
36
         default_profile/0]).
35
37
 
36
38
%% Behavior callbacks
37
39
-export([start_standalone/1, start_service/1, 
40
42
-include("http_internal.hrl").
41
43
-include("httpc_internal.hrl").
42
44
 
 
45
-define(DEFAULT_PROFILE, default).
 
46
 
 
47
 
43
48
%%%=========================================================================
44
49
%%%  API
45
50
%%%=========================================================================
51
56
%%      Url - string() 
52
57
%% Description: Calls request/4 with default values.
53
58
%%--------------------------------------------------------------------------
 
59
 
54
60
request(Url) ->
55
 
    request(Url, default).
 
61
    request(Url, default_profile()).
56
62
 
57
63
request(Url, Profile) ->
58
64
    request(get, {Url, []}, [], [], Profile).
59
65
 
 
66
 
60
67
%%--------------------------------------------------------------------------
61
68
%% request(Method, Request, HTTPOptions, Options [, Profile]) ->
62
69
%%           {ok, {StatusLine, Headers, Body}} | {ok, {Status, Body}} |
94
101
%%--------------------------------------------------------------------------
95
102
 
96
103
request(Method, Request, HttpOptions, Options) ->
97
 
    request(Method, Request, HttpOptions, Options, default). 
 
104
    request(Method, Request, HttpOptions, Options, default_profile()). 
98
105
 
99
106
request(Method, {Url, Headers}, HTTPOptions, Options, Profile) 
100
 
  when Method==options;Method==get;Method==head;Method==delete;Method==trace ->
 
107
  when (Method =:= options) orelse 
 
108
       (Method =:= get) orelse 
 
109
       (Method =:= head) orelse 
 
110
       (Method =:= delete) orelse 
 
111
       (Method =:= trace) ->
101
112
    case http_uri:parse(Url) of
102
 
        {error,Reason} ->
103
 
            {error,Reason};
 
113
        {error, Reason} ->
 
114
            {error, Reason};
104
115
        ParsedUrl ->
105
116
            handle_request(Method, Url, {ParsedUrl, Headers, [], []}, 
106
117
                           HTTPOptions, Options, Profile)
107
118
    end;
108
119
     
109
120
request(Method, {Url,Headers,ContentType,Body}, HTTPOptions, Options, Profile) 
110
 
  when Method==post;Method==put ->
 
121
  when (Method =:= post) orelse (Method =:= put) ->
111
122
    case http_uri:parse(Url) of
112
 
        {error,Reason} ->
113
 
            {error,Reason};
 
123
        {error, Reason} ->
 
124
            {error, Reason};
114
125
        ParsedUrl ->
115
126
            handle_request(Method, Url, 
116
127
                           {ParsedUrl, Headers, ContentType, Body}, 
124
135
%% Description: Cancels a HTTP-request.
125
136
%%-------------------------------------------------------------------------
126
137
cancel_request(RequestId) ->
127
 
    cancel_request(RequestId, default).
 
138
    cancel_request(RequestId, default_profile()).
128
139
 
129
140
cancel_request(RequestId, Profile) ->
130
141
    ok = httpc_manager:cancel_request(RequestId, profile_name(Profile)), 
137
148
            ok
138
149
    end.
139
150
 
 
151
 
 
152
set_option(Key, Value) ->
 
153
    set_option(Key, Value, default_profile()).
 
154
 
 
155
set_option(Key, Value, Profile) ->
 
156
    set_options([{Key, Value}], Profile).
 
157
 
 
158
 
140
159
%%--------------------------------------------------------------------------
141
160
%% set_options(Options [, Profile]) -> ok | {error, Reason}
142
161
%%   Options - [Option]
143
162
%%   Profile - atom()
144
163
%%   Option - {proxy, {Proxy, NoProxy}} | {max_sessions, MaxSessions} | 
145
164
%%            {max_pipeline_length, MaxPipeline} | 
146
 
%%            {pipeline_timeout, PipelineTimeout} | {cookies, CookieMode}
147
 
%%            | {ipv6, Ipv6Mode}
 
165
%%            {pipeline_timeout, PipelineTimeout} | {cookies, CookieMode} | 
 
166
%%            {ipfamily, IpFamily}
148
167
%%   Proxy - {Host, Port}
149
168
%%   NoProxy - [Domain | HostName | IPAddress]   
150
169
%%   MaxSessions, MaxPipeline, PipelineTimeout = integer()   
151
170
%%   CookieMode - enabled | disabled | verify
152
 
%%   Ipv6Mode - enabled | disabled
 
171
%%   IpFamily - inet | inet6 | inet6fb4
153
172
%% Description: Informs the httpc_manager of the new settings. 
154
173
%%-------------------------------------------------------------------------
155
174
set_options(Options) ->
156
 
    set_options(Options, default).
 
175
    set_options(Options, default_profile()).
157
176
set_options(Options, Profile) ->
158
177
    case validate_options(Options) of
159
 
        ok ->
160
 
            try httpc_manager:set_options(Options, profile_name(Profile)) of
 
178
        {ok, Opts} ->
 
179
            try httpc_manager:set_options(Opts, profile_name(Profile)) of
161
180
                Result ->
162
181
                    Result
163
182
            catch
168
187
            {error, Reason}
169
188
    end.
170
189
 
 
190
 
171
191
%%--------------------------------------------------------------------------
172
192
%% verify_cookies(SetCookieHeaders, Url [, Profile]) -> ok | {error, reason} 
173
193
%%   
174
194
%%                                 
175
 
%% Description: Store the cookies from <SetCookieHeaders> in the cookie database
 
195
%% Description: Store the cookies from <SetCookieHeaders> 
 
196
%%              in the cookie database
176
197
%% for the profile <Profile>. This function shall be used when the option
177
198
%% cookie is set to verify. 
178
199
%%-------------------------------------------------------------------------
179
200
verify_cookies(SetCookieHeaders, Url) ->
180
 
    verify_cookies(SetCookieHeaders, Url, default).
 
201
    verify_cookies(SetCookieHeaders, Url, default_profile()).
181
202
 
182
203
verify_cookies(SetCookieHeaders, Url, Profile) ->
183
204
    {_, _, Host, Port, Path, _} = http_uri:parse(Url),
198
219
%% a request to <Url>.
199
220
%%-------------------------------------------------------------------------
200
221
cookie_header(Url) ->
201
 
    cookie_header(Url, default).
 
222
    cookie_header(Url, default_profile()).
202
223
 
203
224
cookie_header(Url, Profile) ->
204
225
    try httpc_manager:cookies(Url, profile_name(Profile)) of
253
274
            {error, service_not_available} 
254
275
    end.
255
276
 
 
277
 
256
278
%%%========================================================================
257
279
%%% Internal functions
258
280
%%%========================================================================
259
 
handle_request(Method, Url, {{Scheme, UserInfo, Host, Port, Path, Query},
260
 
                        Headers, ContentType, Body}, 
 
281
handle_request(Method, Url, 
 
282
               {{Scheme, UserInfo, Host, Port, Path, Query}, Headers, ContentType, Body}, 
261
283
               HTTPOptions, Options, Profile) ->
 
284
 
262
285
    HTTPRecordOptions = http_options(HTTPOptions, #http_options{}),
263
 
    
264
286
    Sync = proplists:get_value(sync, Options, true),
265
287
    NewHeaders = lists:map(fun({Key, Val}) -> 
266
288
                                   {http_util:to_lower(Key), Val} end,
275
297
            RecordHeaders = header_record(NewHeaders, #http_request_h{}, 
276
298
                                          Host, Version),
277
299
            Request = #request{from = self(),
278
 
                               scheme = Scheme, address = {Host,Port},
279
 
                               path = Path, pquery = Query, method = Method,
 
300
                               scheme = Scheme, 
 
301
                               address = {Host,Port},
 
302
                               path = Path, 
 
303
                               pquery = Query, 
 
304
                               method = Method,
280
305
                               headers = RecordHeaders, 
281
306
                               content = {ContentType,Body},
282
307
                               settings = 
283
308
                               HTTPRecordOptions#http_options{version = Version},
284
 
                               abs_uri = Url, userinfo = UserInfo, 
 
309
                               abs_uri = Url, 
 
310
                               userinfo = UserInfo, 
285
311
                               stream = Stream, 
286
 
                               headers_as_is = 
287
 
                               headers_as_is(Headers, Options)},
 
312
                               headers_as_is = headers_as_is(Headers, Options)},
288
313
            try httpc_manager:request(Request, profile_name(Profile)) of
289
314
                {ok, RequestId} ->
290
315
                    handle_answer(RequestId, Sync, Options);
348
373
http_options([], Acc) ->
349
374
    Acc;
350
375
http_options([{timeout, Val} | Settings], Acc) 
351
 
  when is_integer(Val), Val >= 0->
 
376
  when is_integer(Val) andalso (Val >= 0) ->
352
377
    http_options(Settings, Acc#http_options{timeout = Val});
353
378
http_options([{timeout, infinity} | Settings], Acc) ->
354
379
    http_options(Settings, Acc#http_options{timeout = infinity});
355
380
http_options([{autoredirect, Val} | Settings], Acc)   
356
 
  when Val == true; Val == false ->
 
381
  when (Val =:= true) orelse (Val =:= false) ->
357
382
    http_options(Settings, Acc#http_options{autoredirect = Val});
358
383
http_options([{ssl, Val} | Settings], Acc) ->
359
384
    http_options(Settings, Acc#http_options{ssl = Val});
360
385
http_options([{relaxed, Val} | Settings], Acc)
361
 
  when Val == true; Val == false ->
 
386
  when (Val =:= true) orelse (Val =:= false) ->
362
387
    http_options(Settings, Acc#http_options{relaxed = Val});
363
388
http_options([{proxy_auth, Val = {User, Passwd}} | Settings], Acc) 
364
 
  when is_list(User),
365
 
       is_list(Passwd) ->
 
389
  when is_list(User) andalso is_list(Passwd) ->
366
390
    http_options(Settings, Acc#http_options{proxy_auth = Val});
367
391
http_options([{version, Val} | Settings], Acc) 
368
 
  when is_atom(Val)->
 
392
  when is_atom(Val) ->
 
393
    http_options(Settings, Acc#http_options{version = atom_to_list(Val)});
 
394
http_options([{version, Val} | Settings], Acc) 
 
395
  when is_list(Val) ->
369
396
    http_options(Settings, Acc#http_options{version = Val});
370
397
http_options([Option | Settings], Acc) ->
371
398
    Report = io_lib:format("Invalid option ~p ignored ~n", [Option]),
372
399
    error_logger:info_report(Report),
373
400
    http_options(Settings, Acc).
374
401
 
375
 
validate_options([]) ->
 
402
 
 
403
validate_options(Options) ->
 
404
    (catch validate_options(Options, [])).
 
405
 
 
406
validate_options([], ValidateOptions) ->
 
407
    {ok, lists:reverse(ValidateOptions)};
 
408
 
 
409
validate_options([{proxy, Proxy} = Opt| Tail], Acc) ->
 
410
    validate_proxy(Proxy),
 
411
    validate_options(Tail, [Opt | Acc]);
 
412
 
 
413
validate_options([{max_sessions, Value} = Opt| Tail], Acc) ->
 
414
    validate_max_sessions(Value),
 
415
    validate_options(Tail, [Opt | Acc]);
 
416
 
 
417
validate_options([{keep_alive_timeout, Value} = Opt| Tail], Acc) ->
 
418
    validate_keep_alive_timeout(Value),
 
419
    validate_options(Tail, [Opt | Acc]);
 
420
 
 
421
validate_options([{max_keep_alive_length, Value} = Opt| Tail], Acc) ->
 
422
    validate_max_keep_alive_length(Value),
 
423
    validate_options(Tail, [Opt | Acc]);
 
424
 
 
425
validate_options([{pipeline_timeout, Value} = Opt| Tail], Acc) ->
 
426
    validate_pipeline_timeout(Value),
 
427
    validate_options(Tail, [Opt | Acc]);
 
428
 
 
429
validate_options([{max_pipeline_length, Value} = Opt| Tail], Acc) ->
 
430
    validate_max_pipeline_length(Value), 
 
431
    validate_options(Tail, [Opt | Acc]);
 
432
 
 
433
validate_options([{cookies, Value} = Opt| Tail], Acc) ->
 
434
    validate_cookies(Value),
 
435
    validate_options(Tail, [Opt | Acc]);
 
436
 
 
437
validate_options([{ipfamily, Value} = Opt| Tail], Acc) ->
 
438
    validate_ipfamily(Value), 
 
439
    validate_options(Tail, [Opt | Acc]);
 
440
 
 
441
%% For backward compatibillity
 
442
validate_options([{ipv6, Value}| Tail], Acc) ->
 
443
    NewValue = validate_ipv6(Value), 
 
444
    Opt = {ipfamily, NewValue},
 
445
    validate_options(Tail, [Opt | Acc]);
 
446
 
 
447
validate_options([{ip, Value} = Opt| Tail], Acc) ->
 
448
    validate_ip(Value),
 
449
    validate_options(Tail, [Opt | Acc]);
 
450
 
 
451
validate_options([{port, Value} = Opt| Tail], Acc) ->
 
452
    validate_port(Value), 
 
453
    validate_options(Tail, [Opt | Acc]);
 
454
 
 
455
validate_options([{verbose, Value} = Opt| Tail], Acc) ->
 
456
    validate_verbose(Value), 
 
457
    validate_options(Tail, [Opt | Acc]);
 
458
 
 
459
validate_options([{_, _} = Opt| _], _Acc) ->
 
460
    {error, {not_an_option, Opt}}.
 
461
 
 
462
 
 
463
validate_proxy({{ProxyHost, ProxyPort}, NoProxy} = Proxy) 
 
464
  when is_list(ProxyHost) andalso 
 
465
       is_integer(ProxyPort) andalso 
 
466
       is_list(NoProxy) ->
 
467
    Proxy;
 
468
validate_proxy(BadProxy) ->
 
469
    bad_option(proxy, BadProxy).
 
470
 
 
471
validate_max_sessions(Value) when is_integer(Value) andalso (Value >= 0) ->
 
472
    Value;
 
473
validate_max_sessions(BadValue) ->
 
474
    bad_option(max_sessions, BadValue).
 
475
 
 
476
validate_keep_alive_timeout(Value) when is_integer(Value) andalso (Value >= 0) ->
 
477
    Value;
 
478
validate_keep_alive_timeout(infinity = Value) ->
 
479
    Value;
 
480
validate_keep_alive_timeout(BadValue) ->
 
481
    bad_option(keep_alive_timeout, BadValue).
 
482
 
 
483
validate_max_keep_alive_length(Value) when is_integer(Value) andalso (Value >= 0) ->
 
484
    Value;
 
485
validate_max_keep_alive_length(BadValue) ->
 
486
    bad_option(max_keep_alive_length, BadValue).
 
487
 
 
488
validate_pipeline_timeout(Value) when is_integer(Value) ->
 
489
    Value;
 
490
validate_pipeline_timeout(infinity = Value) ->
 
491
    Value;
 
492
validate_pipeline_timeout(BadValue) ->
 
493
    bad_option(pipeline_timeout, BadValue).
 
494
 
 
495
validate_max_pipeline_length(Value) when is_integer(Value) ->
 
496
    Value;
 
497
validate_max_pipeline_length(BadValue) ->
 
498
    bad_option(max_pipeline_length, BadValue).
 
499
 
 
500
validate_cookies(Value) 
 
501
  when ((Value =:= enabled)  orelse 
 
502
        (Value =:= disabled) orelse 
 
503
        (Value =:= verify)) ->
 
504
    Value;
 
505
validate_cookies(BadValue) ->
 
506
    bad_option(cookies, BadValue).
 
507
 
 
508
validate_ipv6(Value) when (Value =:= enabled) orelse (Value =:= disabled) ->
 
509
    case Value of
 
510
        enabled ->
 
511
            inet6fb4;
 
512
        disabled ->
 
513
            inet
 
514
    end;  
 
515
validate_ipv6(BadValue) ->
 
516
    bad_option(ipv6, BadValue).
 
517
 
 
518
validate_ipfamily(Value) 
 
519
  when (Value =:= inet) orelse (Value =:= inet6) orelse (Value =:= inet6fb4) ->
 
520
    Value;
 
521
validate_ipfamily(BadValue) ->
 
522
    bad_option(ipfamily, BadValue).
 
523
 
 
524
validate_ip(Value) 
 
525
  when is_tuple(Value) andalso ((size(Value) =:= 4) orelse (size(Value) =:= 8)) ->
 
526
    Value;
 
527
validate_ip(BadValue) ->
 
528
    bad_option(ip, BadValue).
 
529
    
 
530
validate_port(Value) when is_integer(Value) ->
 
531
    Value;
 
532
validate_port(BadValue) ->
 
533
    bad_option(port, BadValue).
 
534
 
 
535
validate_verbose(Value) 
 
536
  when ((Value =:= false) orelse 
 
537
        (Value =:= verbose) orelse 
 
538
        (Value =:= debug) orelse 
 
539
        (Value =:= trace)) ->
376
540
    ok;
377
 
validate_options([{proxy, {{ProxyHost, ProxyPort}, NoProxy}}| Tail]) when
378
 
                 is_list(ProxyHost), is_integer(ProxyPort), 
379
 
                 is_list(NoProxy) ->
380
 
    validate_options(Tail);
381
 
validate_options([{pipeline_timeout, Value}| Tail]) when is_integer(Value) ->
382
 
    validate_options(Tail);
383
 
validate_options([{pipeline_timeout, infinity}| Tail]) ->
384
 
    validate_options(Tail);
385
 
validate_options([{keep_alive_timeout, Value}| Tail]) when is_integer(Value) ->
386
 
    validate_options(Tail);
387
 
validate_options([{keep_alive_timeout, infinity}| Tail]) ->
388
 
    validate_options(Tail);
389
 
validate_options([{max_pipeline_length, Value}| Tail]) 
390
 
  when is_integer(Value) ->
391
 
    validate_options(Tail);
392
 
validate_options([{max_pipeline_length, Value}| Tail]) 
393
 
  when is_integer(Value) ->
394
 
    validate_options(Tail);
395
 
validate_options([{max_sessions, Value}| Tail]) when is_integer(Value) ->
396
 
    validate_options(Tail);
397
 
validate_options([{cookies, Value}| Tail]) 
398
 
  when Value == enabled; Value == disabled; Value == verify ->
399
 
    validate_options(Tail);
400
 
validate_options([{ipv6, Value}| Tail]) 
401
 
  when Value == enabled; Value == disabled ->
402
 
    validate_options(Tail);
403
 
validate_options([{verbose, Value}| Tail]) when Value == false;
404
 
                                                Value == verbose;
405
 
                                                Value == debug;
406
 
                                                Value == trace ->
407
 
    validate_options(Tail);
408
 
validate_options([{_, _} = Opt| _]) ->
409
 
    {error, {not_an_option, Opt}}.
 
541
validate_verbose(BadValue) ->
 
542
    bad_option(verbose, BadValue).
 
543
 
 
544
bad_option(Option, BadValue) ->
 
545
    throw({error, {bad_option, Option, BadValue}}).
 
546
 
 
547
 
410
548
 
411
549
header_record([], RequestHeaders, Host, Version) ->
412
550
    validate_headers(RequestHeaders, Host, Version);
555
693
validate_headers(RequestHeaders, _, _) ->
556
694
    RequestHeaders.
557
695
 
558
 
profile_name(default) ->
 
696
 
 
697
default_profile() ->
 
698
    ?DEFAULT_PROFILE.
 
699
 
 
700
profile_name(?DEFAULT_PROFILE) ->
559
701
    httpc_manager;
560
702
profile_name(Pid) when is_pid(Pid) ->
561
703
    Pid;
576
718
child_name(Pid, [_ | Children]) ->
577
719
    child_name(Pid, Children).
578
720
 
 
721
%% d(F) ->
 
722
%%    d(F, []).
 
723
 
 
724
%% d(F, A) -> 
 
725
%%     d(get(dbg), F, A).
 
726
 
 
727
%% d(true, F, A) ->
 
728
%%     io:format(user, "~w:~w:" ++ F ++ "~n", [self(), ?MODULE | A]);
 
729
%% d(_, _, _) ->
 
730
%%     ok.
 
731