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

« back to all changes in this revision

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

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 2002-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2002-2011. All Rights Reserved.
5
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
29
29
         start_link/3, 
30
30
         request/2, 
31
31
         cancel_request/2,
32
 
         request_canceled/2, 
 
32
         request_canceled/3,
33
33
         request_done/2, 
34
34
         retry_request/2, 
35
35
         redirect_request/2,
37
37
         delete_session/2, 
38
38
         set_options/2, 
39
39
         store_cookies/3,
40
 
         which_cookies/1, which_cookies/2, 
 
40
         which_cookies/1, which_cookies/2, which_cookies/3, 
41
41
         reset_cookies/1, 
42
42
         session_type/1,
43
43
         info/1
52
52
          cancel = [],   % [{RequestId, HandlerPid, ClientPid}]  
53
53
          handler_db,    % ets() - Entry: #handler_info{}
54
54
          cookie_db,     % cookie_db()
55
 
          session_db,    % ets() - Entry:  #tcp_session{}
 
55
          session_db,    % ets() - Entry:  #session{}
56
56
          profile_name,  % atom()
57
57
          options = #options{}
58
58
         }).
66
66
          state    % State of the handler: initiating | started | operational | canceled
67
67
         }).
68
68
 
 
69
-define(DELAY, 500).
69
70
 
70
71
%%====================================================================
71
72
%% Internal Application API
158
159
%% be called by the httpc handler process.
159
160
%%--------------------------------------------------------------------
160
161
 
161
 
request_canceled(RequestId, ProfileName) ->
 
162
request_canceled(RequestId, ProfileName, From) ->
 
163
    gen_server:reply(From, ok),
162
164
    cast(ProfileName, {request_canceled, RequestId}).
163
165
 
164
166
 
176
178
 
177
179
%%--------------------------------------------------------------------
178
180
%% Function: insert_session(Session, ProfileName) -> _
179
 
%%      Session - #tcp_session{}
 
181
%%      Session - #session{}
180
182
%%      ProfileName - atom()
181
183
%%
182
184
%% Description: Inserts session information into the httpc manager
254
256
 
255
257
 
256
258
%%--------------------------------------------------------------------
257
 
%% Function: which_cookies(Url, ProfileName) -> [cookie()]
 
259
%% Function: which_cookies(ProfileName)               -> [cookie()]
 
260
%%           which_cookies(Url, ProfileName)          -> [cookie()]
 
261
%%           which_cookies(Url, Options, ProfileName) -> [cookie()]
258
262
%%
259
263
%%      Url = string()
 
264
%%      Options = [option()]
260
265
%%      ProfileName = atom()
 
266
%%      option() = {ipv6_host_with_brackets, boolean()}
261
267
%%
262
268
%% Description: Retrieves the cookies that would be sent when 
263
269
%% requesting <Url>.
264
270
%%--------------------------------------------------------------------
265
271
 
266
 
which_cookies(ProfileName) ->
 
272
which_cookies(ProfileName) when is_atom(ProfileName) ->
267
273
    call(ProfileName, which_cookies).
268
 
which_cookies(Url, ProfileName) ->
269
 
    call(ProfileName, {which_cookies, Url}).
 
274
 
 
275
which_cookies(Url, ProfileName) 
 
276
  when is_list(Url) andalso is_atom(ProfileName) ->
 
277
    which_cookies(Url, [], ProfileName).
 
278
 
 
279
which_cookies(Url, Options, ProfileName) 
 
280
  when is_list(Url) andalso is_list(Options) andalso is_atom(ProfileName) ->
 
281
    call(ProfileName, {which_cookies, Url, Options}).
270
282
 
271
283
 
272
284
%%--------------------------------------------------------------------
355
367
%%          {stop, Reason, State}            (terminate/2 is called)
356
368
%% Description: Handling call messages
357
369
%%--------------------------------------------------------------------
358
 
handle_call({request, Request}, _From, State) ->
359
 
    ?hcrv("request", [{request, Request}]),
 
370
handle_call({request, Request}, _, State) ->
 
371
    ?hcri("request", [{request, Request}]),
360
372
    case (catch handle_request(Request, State)) of
361
 
        {ok, ReqId, NewState} ->
362
 
            {reply, {ok, ReqId}, NewState};
363
 
        
 
373
        {reply, Msg, NewState} ->
 
374
            {reply, Msg, NewState};
364
375
        Error ->
365
 
            NewError = {error, {failed_process_request, Error}}, 
366
 
            {reply, NewError, State}
 
376
            {stop, Error, httpc_response:error(Request, Error), State}
367
377
    end;
368
 
        
369
 
handle_call({cancel_request, RequestId}, From, 
370
 
            #state{handler_db = HandlerDb} = State) ->
371
 
    ?hcrv("cancel_request", [{request_id, RequestId}]),
 
378
 
 
379
handle_call({cancel_request, RequestId}, From, State) ->
 
380
    ?hcri("cancel_request", [{request_id, RequestId}]),
372
381
    case ets:lookup(State#state.handler_db, RequestId) of
373
382
        [] ->
374
 
            ?hcrd("nothing to cancel", []),
375
 
            Reply = ok, %% Nothing to cancel
376
 
            {reply, Reply, State};
377
 
 
378
 
        [#handler_info{handler = Pid}] when is_pid(Pid) ->
379
 
            ?hcrd("found operational handler for this request", 
380
 
                  [{handler, Pid}]),
381
 
            httpc_handler:cancel(RequestId, Pid),
382
 
            {noreply, State#state{cancel = 
383
 
                                  [{RequestId, Pid, From} | 
384
 
                                   State#state.cancel]}};
385
 
 
386
 
        [#handler_info{starter = Pid, state = HandlerState}] 
387
 
        when is_pid(Pid) ->
388
 
            ?hcri("found *initiating* handler for this request", 
389
 
                  [{starter, Pid}, {state, HandlerState}]),
390
 
            ets:update_element(HandlerDb, RequestId, 
391
 
                               {#handler_info.state, canceled}),
392
 
            {noreply, State#state{cancel = 
393
 
                                  [{RequestId, Pid, From} | 
 
383
            %% The request has allready compleated make sure
 
384
            %% it is deliverd to the client process queue so
 
385
            %% it can be thrown away by httpc:cancel_request
 
386
            %% This delay is hopfully a temporary workaround.
 
387
            %% Note that it will not not delay the manager,
 
388
            %% only the client that called httpc:cancel_request
 
389
            timer:apply_after(?DELAY, gen_server, reply, [From, ok]),
 
390
            {noreply, State};
 
391
        [{_, Pid, _}] ->
 
392
            httpc_handler:cancel(RequestId, Pid, From),
 
393
            {noreply, State#state{cancel = 
 
394
                                  [{RequestId, Pid, From} |
394
395
                                   State#state.cancel]}}
395
 
 
396
396
    end;
397
397
 
398
398
handle_call(reset_cookies, _, #state{cookie_db = CookieDb} = State) ->
405
405
    CookieHeaders = httpc_cookie:which_cookies(CookieDb),
406
406
    {reply, CookieHeaders, State};
407
407
 
408
 
handle_call({which_cookies, Url}, _, #state{cookie_db = CookieDb} = State) ->
409
 
    ?hcrv("which cookies", [{url, Url}]),
410
 
    case http_uri:parse(Url) of
411
 
        {Scheme, _, Host, Port, Path, _} ->
 
408
handle_call({which_cookies, Url, Options}, _, 
 
409
            #state{cookie_db = CookieDb} = State) ->
 
410
    ?hcrv("which cookies", [{url, Url}, {options, Options}]),
 
411
    case http_uri:parse(Url, Options) of
 
412
        {ok, {Scheme, _, Host, Port, Path, _}} ->
412
413
            CookieHeaders = 
413
414
                httpc_cookie:header(CookieDb, Scheme, {Host, Port}, Path),
414
415
            {reply, CookieHeaders, State};
415
 
        Msg ->
416
 
            {reply, Msg, State}
 
416
        {error, _} = ERROR ->
 
417
            {reply, ERROR, State}
417
418
    end;
418
419
 
419
420
handle_call(info, _, State) ->
437
438
%%--------------------------------------------------------------------
438
439
handle_cast({retry_or_redirect_request, {Time, Request}}, 
439
440
            #state{profile_name = ProfileName} = State) ->
440
 
    ?hcrv("retry or redirect request", [{time, Time}, {request, Request}]),
441
 
    case timer:apply_after(Time, ?MODULE, retry_request, 
442
 
                           [Request, ProfileName]) of
443
 
        {ok, _} ->
444
 
            {noreply, State};
445
 
        {error, Reason} ->
446
 
            error_report(ProfileName, 
447
 
                         "failed scheduling retry/redirect request"
448
 
                         "~n   Time:    ~p"
449
 
                         "~n   Request: ~p"
450
 
                         "~n   Reason:  ~p", [Time, Request, Reason]),
451
 
            {noreply, State}
452
 
    end;
 
441
    {ok, _} = timer:apply_after(Time, ?MODULE, retry_request, [Request, ProfileName]),
 
442
    {noreply, State};
453
443
 
454
 
handle_cast({retry_or_redirect_request, Request}, 
455
 
            #state{profile_name = Profile, 
456
 
                   handler_db   = HandlerDb} = State) ->
457
 
    ?hcrv("retry or redirect request", [{request, Request}]),
 
444
handle_cast({retry_or_redirect_request, Request}, State) ->
458
445
    case (catch handle_request(Request, State)) of
459
 
        {ok, _, NewState} ->
 
446
        {reply, {ok, _}, NewState} ->
460
447
            {noreply, NewState};
461
 
 
462
448
        Error  ->
463
 
            ReqId = Request#request.id, 
464
 
            error_report(Profile, 
465
 
                         "failed to retry or redirect request ~p"
466
 
                         "~n   Error: ~p", [ReqId, Error]),
467
 
            case ets:lookup(HandlerDb, ReqId) of
468
 
                [#handler_info{from = From}] -> 
469
 
                    Error2 = httpc_response:error(Request, Error), 
470
 
                    httpc_response:send(From, Error2),
471
 
                    ok;
472
 
                
473
 
                _ ->
474
 
                    ok
475
 
            end,
476
 
            {noreply, State}
 
449
            httpc_response:error(Request, Error),
 
450
            {stop, Error, State}
477
451
    end;
478
452
 
479
453
handle_cast({request_canceled, RequestId}, State) ->
482
456
    case lists:keysearch(RequestId, 1, State#state.cancel) of
483
457
        {value, Entry = {RequestId, _, From}} ->
484
458
            ?hcrt("found in cancel", [{from, From}]),
485
 
            gen_server:reply(From, ok),
486
459
            {noreply, 
487
460
             State#state{cancel = lists:delete(Entry, State#state.cancel)}};
488
461
        Else ->
539
512
                 "recived unknown message"
540
513
                 "~n   Msg: ~p", [Msg]),
541
514
    {noreply, State}.
542
 
 
543
 
 
544
515
            
545
516
%%--------------------------------------------------------------------
546
517
%% Function: handle_info(Info, State) -> {noreply, State} |
548
519
%%          {stop, Reason, State}            (terminate/2 is called)
549
520
%% Description: Handling all non call/cast messages
550
521
%%---------------------------------------------------------
551
 
 
552
 
handle_info({started, StarterPid, ReqId, HandlerPid}, State) ->
553
 
    handle_started(StarterPid, ReqId, HandlerPid, State),
554
 
    {noreply, State};
555
 
 
556
 
handle_info({connect_and_send, StarterPid, ReqId, HandlerPid, Res}, State) ->
557
 
    handle_connect_and_send(StarterPid, ReqId, HandlerPid, Res, State),
558
 
    {noreply, State};
559
 
 
560
 
handle_info({failed_starting_handler, StarterPid, ReqId, Res}, State) ->
561
 
    handle_failed_starting_handler(StarterPid, ReqId, Res, State),
562
 
    {noreply, State};
563
 
 
564
 
handle_info({'EXIT', Pid, Reason}, #state{handler_db = HandlerDb} = State) ->
565
 
    maybe_handle_terminating_starter(Pid, Reason, HandlerDb), 
566
 
    {noreply, State};
567
 
 
 
522
handle_info({'EXIT', _, _}, State) ->
 
523
    %% Handled in DOWN
 
524
    {noreply, State};
568
525
handle_info({'DOWN', _, _, Pid, _}, State) ->
569
 
    
570
 
    %% 
571
 
    %% Normally this should have been cleaned up already
572
 
    %% (when receiving {request_done, PequestId}), but
573
 
    %% just in case there is a glitch, cleanup anyway.
574
 
    %% 
575
 
 
576
 
    Pattern = #handler_info{handler = Pid, _ = '_'}, 
577
 
    ets:match_delete(State#state.handler_db, Pattern),
 
526
    ets:match_delete(State#state.handler_db, {'_', Pid, '_'}),
578
527
 
579
528
    %% If there where any canceled request, handled by the
580
529
    %% the process that now has terminated, the
581
530
    %% cancelation can be viewed as sucessfull!
582
 
    NewCanceledList = 
583
 
        lists:foldl(fun({_, HandlerPid, From} = Entry, Acc)  ->
 
531
    NewCanceldList =
 
532
        lists:foldl(fun(Entry = {_, HandlerPid, From}, Acc)  ->
584
533
                            case HandlerPid of
585
534
                                Pid ->
586
535
                                    gen_server:reply(From, ok),
589
538
                                    Acc
590
539
                            end 
591
540
                    end, State#state.cancel, State#state.cancel),
592
 
    {noreply, State#state{cancel = NewCanceledList}};    
593
 
 
594
 
handle_info(Info, #state{profile_name = ProfileName} = State) ->
595
 
    error_report(ProfileName, 
596
 
                 "received unknown info"
597
 
                 "~n   Info: ~p", [Info]),
 
541
    {noreply, State#state{cancel = NewCanceldList}};
 
542
handle_info(Info, State) ->
 
543
    Report = io_lib:format("Unknown message in "
 
544
                           "httpc_manager:handle_info ~p~n", [Info]),
 
545
    error_logger:error_report(Report),
598
546
    {noreply, State}. 
599
547
 
600
 
 
601
548
%%--------------------------------------------------------------------
602
549
%% Function: terminate(Reason, State) -> _  (ignored by gen_server)
603
550
%% Description: Shutdown the httpc_handler
655
602
                    {Pid, State} <- Handlers2],
656
603
    Handlers3.
657
604
 
658
 
 
659
 
%% 
660
 
%% The request handler process is started asynchronously by a 
661
 
%% "starter process". When the handler has sucessfully been started,
662
 
%% this message (started) is sent.
663
 
%% 
664
 
 
665
 
handle_started(StarterPid, ReqId, HandlerPid, 
666
 
                        #state{profile_name = Profile, 
667
 
                               handler_db   = HandlerDb}) ->
668
 
    case ets:lookup(HandlerDb, ReqId) of
669
 
        [#handler_info{state = initiating} = HandlerInfo] ->
670
 
            ?hcri("received started ack for initiating handler", []),
671
 
            %% As a last resort, make sure we know when it exits,
672
 
            %% in case it forgets to notify us.
673
 
            %% We dont need to know the ref id?
674
 
            erlang:monitor(process, HandlerPid),
675
 
            HandlerInfo2 = HandlerInfo#handler_info{handler = HandlerPid,
676
 
                                                    state   = started}, 
677
 
            ets:insert(HandlerDb, HandlerInfo2),
678
 
            ok;
679
 
 
680
 
        [#handler_info{state = State}] ->
681
 
            error_report(Profile, 
682
 
                         "unexpected (started) message for handler (~p) in state "
683
 
                         "~p regarding request ~p - ignoring", [HandlerPid, State, ReqId]),
684
 
            ?hcri("received unexpected started message", [{state, State}]),
685
 
            ok;
686
 
 
687
 
        [] ->
688
 
            error_report(Profile, 
689
 
                         "unknown handler ~p (~p) started for request ~w - canceling",
690
 
                         [HandlerPid, StarterPid, ReqId]),
691
 
            httpc_handler:cancel(ReqId, HandlerPid)
692
 
    end.
693
 
 
694
 
 
695
 
%% 
696
 
%% The request handler process is started asynchronously by a 
697
 
%% "starter process". When that process terminates it sends 
698
 
%% one of two messages. These ara handled by the two functions
699
 
%% below.
700
 
%% 
701
 
 
702
 
handle_connect_and_send(_StarterPid, ReqId, HandlerPid, Result, 
703
 
                        #state{profile_name = Profile, 
704
 
                               handler_db   = HandlerDb}) ->
705
 
    case ets:lookup(HandlerDb, ReqId) of
706
 
        [#handler_info{state = started} = HandlerInfo] when Result =:= ok ->
707
 
            ?hcri("received connect-and-send ack for started handler", []),
708
 
            HandlerInfo2 = HandlerInfo#handler_info{starter = undefined, 
709
 
                                                    handler = HandlerPid,
710
 
                                                    state   = operational}, 
711
 
            ets:insert(HandlerDb, HandlerInfo2),
712
 
            ok;
713
 
 
714
 
        [#handler_info{state = canceled} = HandlerInfo] when Result =:= ok ->
715
 
            ?hcri("received connect-and-send ack for canceled handler", []),
716
 
            httpc_handler:cancel(ReqId, HandlerPid),
717
 
            HandlerInfo2 = HandlerInfo#handler_info{starter = undefined, 
718
 
                                                    handler = HandlerPid}, 
719
 
            ets:insert(HandlerDb, HandlerInfo2),
720
 
            ok;
721
 
 
722
 
        [#handler_info{state = State}] when Result =/= ok ->
723
 
            error_report(Profile, 
724
 
                         "handler (~p, ~w) failed to connect and/or "
725
 
                         "send request ~p"
726
 
                         "~n   Result: ~p", 
727
 
                         [HandlerPid, State, ReqId, Result]),
728
 
            ?hcri("received connect-and-send error", 
729
 
                  [{result, Result}, {state, State}]),
730
 
            %% We don't need to send a response to the original caller
731
 
            %% because the handler already sent one in its terminate
732
 
            %% function.
733
 
            ets:delete(HandlerDb, ReqId), 
734
 
            ok;
735
 
 
736
 
        [] ->
737
 
            ?hcri("handler successfully started "
738
 
                  "for unknown request => canceling",
739
 
                  [{profile, Profile}, 
740
 
                   {handler, HandlerPid}, 
741
 
                   {request, ReqId}]),
742
 
            httpc_handler:cancel(ReqId, HandlerPid)
743
 
    end.
744
 
 
745
 
 
746
 
handle_failed_starting_handler(_StarterPid, ReqId, Error, 
747
 
                               #state{profile_name = Profile, 
748
 
                                      handler_db = HandlerDb}) ->
749
 
    case ets:lookup(HandlerDb, ReqId) of
750
 
        [#handler_info{state = canceled}] ->
751
 
            error_report(Profile, 
752
 
                         "failed starting handler for request ~p"
753
 
                         "~n   Error: ~p", [ReqId, Error]),
754
 
            request_canceled(Profile, ReqId), % Fake signal from handler
755
 
            ets:delete(HandlerDb, ReqId), 
756
 
            ok;
757
 
 
758
 
        [#handler_info{from = From}] ->
759
 
            error_report(Profile, 
760
 
                         "failed starting handler for request ~p"
761
 
                         "~n   Error: ~p", [ReqId, Error]),
762
 
            Reason2 = 
763
 
                case Error of
764
 
                    {error, Reason} ->
765
 
                        {failed_connecting, Reason};
766
 
                    _ ->
767
 
                        {failed_connecting, Error}
768
 
                end,
769
 
            DummyReq = #request{id = ReqId}, 
770
 
            httpc_response:send(From, httpc_response:error(DummyReq, Reason2)),
771
 
            ets:delete(HandlerDb, ReqId), 
772
 
            ok;
773
 
 
774
 
        [] ->
775
 
            error_report(Profile, 
776
 
                         "failed starting handler for unknown request ~p"
777
 
                         "~n   Error: ~p", [ReqId, Error]),
778
 
            ok
779
 
    end.
780
 
 
781
 
 
782
 
maybe_handle_terminating_starter(MeybeStarterPid, Reason, HandlerDb) ->
783
 
    Pattern = #handler_info{starter = MeybeStarterPid, _ = '_'}, 
784
 
    case ets:match_object(HandlerDb, Pattern) of
785
 
        [#handler_info{id = ReqId, from = From, state = initiating}] ->
786
 
            %% The starter process crashed before it could start the 
787
 
            %% the handler process, therefor we need to answer the 
788
 
            %% original caller.
789
 
            ?hcri("starter process crashed bfore starting handler", 
790
 
                  [{starter, MeybeStarterPid}, {reason, Reason}]),
791
 
            Reason2 = 
792
 
                case Reason of
793
 
                    {error, Error} ->
794
 
                        {failed_connecting, Error};
795
 
                    _ ->
796
 
                        {failed_connecting, Reason}
797
 
                end,
798
 
            DummyReq = #request{id = ReqId}, 
799
 
            httpc_response:send(From, httpc_response:error(DummyReq, Reason2)),
800
 
            ets:delete(HandlerDb, ReqId),
801
 
            ok;
802
 
 
803
 
        [#handler_info{state = State} = HandlerInfo] ->
804
 
            %% The starter process crashed after the handler was started. 
805
 
            %% The handler will answer to the original caller.
806
 
            ?hcri("starter process crashed after starting handler", 
807
 
                  [{starter, MeybeStarterPid}, {reason, Reason}, {state, State}]),
808
 
            HandlerInfo2 = HandlerInfo#handler_info{starter = undefined}, 
809
 
            ets:insert(HandlerDb, HandlerInfo2),
810
 
            ok;
811
 
 
812
 
        _ ->
813
 
            ok
814
 
    end.
815
 
 
816
 
 
817
 
%% -----
818
 
%% Act as an HTTP/0.9 client that does not know anything
819
 
%% about persistent connections
820
 
handle_request(#request{settings = 
821
 
                        #http_options{version = "HTTP/0.9"}} = Request0, 
822
 
               State) ->
823
 
    Request1 = handle_cookies(generate_request_id(Request0), State),
824
 
    Hdrs0    = Request1#request.headers, 
825
 
    Hdrs1    = Hdrs0#http_request_h{connection = undefined},
826
 
    Request2 = Request1#request{headers = Hdrs1}, 
827
 
    create_handler_starter(Request2, State),
828
 
    {ok, Request2#request.id, State};
829
 
 
830
 
%% -----
831
 
%% Act as an HTTP/1.0 client that does not 
832
 
%% use persistent connections
833
 
handle_request(#request{settings = 
834
 
                        #http_options{version = "HTTP/1.0"}} = Request0, 
835
 
               State) ->
836
 
    Request1 = handle_cookies(generate_request_id(Request0), State),
837
 
    Hdrs0    = Request1#request.headers, 
838
 
    Hdrs1    = Hdrs0#http_request_h{connection = "close"},
839
 
    Request2 = Request1#request{headers = Hdrs1}, 
840
 
    create_handler_starter(Request2, State),
841
 
    {ok, Request2#request.id, State};
842
 
 
843
 
 
844
 
%% -----
845
 
handle_request(#request{method  = Method,
846
 
                        address = Address,
847
 
                        scheme  = Scheme} = Request0, 
848
 
               #state{options = Opts} = State) ->
849
 
    Request1    = handle_cookies(generate_request_id(Request0), State),
850
 
    SessionType = session_type(Opts),
851
 
    case select_session(Method, Address, Scheme, SessionType, State) of
 
605
handle_request(#request{settings = 
 
606
                        #http_options{version = "HTTP/0.9"}} = Request,
 
607
               State) ->
 
608
    %% Act as an HTTP/0.9 client that does not know anything
 
609
    %% about persistent connections
 
610
 
 
611
    NewRequest = handle_cookies(generate_request_id(Request), State),
 
612
    NewHeaders =
 
613
        (NewRequest#request.headers)#http_request_h{connection
 
614
                                                    = undefined},
 
615
    start_handler(NewRequest#request{headers = NewHeaders}, State),
 
616
    {reply, {ok, NewRequest#request.id}, State};
 
617
 
 
618
handle_request(#request{settings = 
 
619
                        #http_options{version = "HTTP/1.0"}} = Request,
 
620
               State) ->
 
621
    %% Act as an HTTP/1.0 client that does not
 
622
    %% use persistent connections
 
623
 
 
624
    NewRequest = handle_cookies(generate_request_id(Request), State),
 
625
    NewHeaders =
 
626
        (NewRequest#request.headers)#http_request_h{connection
 
627
                                                    = "close"},
 
628
    start_handler(NewRequest#request{headers = NewHeaders}, State),
 
629
    {reply, {ok, NewRequest#request.id}, State};
 
630
 
 
631
handle_request(Request, State = #state{options = Options}) ->
 
632
 
 
633
    NewRequest = handle_cookies(generate_request_id(Request), State),
 
634
    SessionType = session_type(Options),
 
635
    case select_session(Request#request.method,
 
636
                        Request#request.address,
 
637
                        Request#request.scheme, SessionType, State) of
852
638
        {ok, HandlerPid} ->
853
 
            pipeline_or_keep_alive(Request1, HandlerPid, State);
 
639
            pipeline_or_keep_alive(NewRequest, HandlerPid, State);
854
640
        no_connection ->
855
 
            create_handler_starter(Request1, State);
856
 
        {no_session, OpenSessions} 
857
 
        when OpenSessions < Opts#options.max_sessions ->
858
 
            create_handler_starter(Request1, State);
 
641
            start_handler(NewRequest, State);
 
642
        {no_session,  OpenSessions} when OpenSessions
 
643
        < Options#options.max_sessions ->
 
644
            start_handler(NewRequest, State);
859
645
        {no_session, _} ->
860
646
            %% Do not start any more persistent connections
861
647
            %% towards this server.
862
 
            Hdrs0    = Request1#request.headers, 
863
 
            Hdrs1    = Hdrs0#http_request_h{connection = "close"},
864
 
            Request2 = Request1#request{headers = Hdrs1}, 
865
 
            create_handler_starter(Request2, State)
 
648
            NewHeaders =
 
649
                (NewRequest#request.headers)#http_request_h{connection
 
650
                                                            = "close"},
 
651
            start_handler(NewRequest#request{headers = NewHeaders}, State)
866
652
    end,
867
 
    {ok, Request1#request.id, State}.
 
653
    {reply, {ok, NewRequest#request.id}, State}.
 
654
 
 
655
 
 
656
start_handler(Request, State) ->
 
657
    {ok, Pid} =
 
658
        case is_inets_manager() of
 
659
            true ->
 
660
                httpc_handler_sup:start_child([whereis(httpc_handler_sup),
 
661
                                               Request, State#state.options,
 
662
                                               State#state.profile_name]);
 
663
            false ->
 
664
                httpc_handler:start_link(self(), Request, State#state.options,
 
665
                                         State#state.profile_name)
 
666
        end,
 
667
    ets:insert(State#state.handler_db, {Request#request.id,
 
668
                                        Pid, Request#request.from}),
 
669
    erlang:monitor(process, Pid).
868
670
 
869
671
 
870
672
select_session(Method, HostPort, Scheme, SessionType, 
871
673
               #state{options = #options{max_pipeline_length   = MaxPipe,
872
674
                                         max_keep_alive_length = MaxKeepAlive},
873
675
                      session_db = SessionDb}) ->
874
 
    ?hcrd("select session", [{session_type,          SessionType}, 
875
 
                             {max_pipeline_length,   MaxPipe}, 
 
676
    ?hcrd("select session", [{session_type,          SessionType},
 
677
                             {max_pipeline_length,   MaxPipe},
876
678
                             {max_keep_alive_length, MaxKeepAlive}]),
877
679
    case httpc_request:is_idempotent(Method) orelse 
878
680
        (SessionType =:= keep_alive) of
879
681
        true ->
880
682
            %% Look for handlers connecting to this host (HostPort)
881
 
            %% tcp_session with record name field (tcp_session) and 
 
683
            %% session with record name field (session) and 
882
684
            %% socket fields ignored. The fields id (part of: HostPort), 
883
685
            %% client_close, scheme and type specified. 
884
686
            %% The fields id (part of: HandlerPid) and queue_length
918
720
            ?hcrd("select session - found one", [{handler, HandlerPid}]),
919
721
            {ok, HandlerPid}
920
722
    end.
921
 
            
922
 
pipeline_or_keep_alive(#request{id = Id} = Request, HandlerPid, State) ->
923
 
    ?hcrd("pipeline of keep-alive", [{id, Id}, {handler, HandlerPid}]),
 
723
 
 
724
pipeline_or_keep_alive(Request, HandlerPid, State) ->
924
725
    case (catch httpc_handler:send(Request, HandlerPid)) of
925
726
        ok ->
926
 
            ?hcrd("pipeline or keep-alive - successfully sent", []),
927
 
            Entry = #handler_info{id      = Id,
928
 
                                  handler = HandlerPid,
929
 
                                  state   = operational},
930
 
            ets:insert(State#state.handler_db, Entry); 
931
 
                
932
 
        _  -> %% timeout pipelining failed 
933
 
            ?hcrd("pipeline or keep-alive - failed sending -> "
934
 
                  "start a new handler", []),
935
 
            create_handler_starter(Request, State)
 
727
            ets:insert(State#state.handler_db, {Request#request.id,
 
728
                                                HandlerPid,
 
729
                                                Request#request.from});
 
730
        _  -> %timeout pipelining failed
 
731
            start_handler(Request, State)
936
732
    end.
937
733
 
938
 
 
939
 
create_handler_starter(#request{socket_opts = SocketOpts} = Request, 
940
 
                       #state{options = Options} = State) 
941
 
  when is_list(SocketOpts) ->
942
 
    %% The user provided us with (override) socket options
943
 
    ?hcrt("create handler starter", [{socket_opts, SocketOpts}, {options, Options}]),
944
 
    Options2 = Options#options{socket_opts = SocketOpts}, 
945
 
    create_handler_starter(Request#request{socket_opts = undefined}, 
946
 
                           State#state{options = Options2});
947
 
 
948
 
create_handler_starter(#request{id          = Id, 
949
 
                                from        = From} = Request, 
950
 
                       #state{profile_name = ProfileName,
951
 
                              options      = Options,
952
 
                              handler_db   = HandlerDb} = _State) ->
953
 
    ?hcrv("create handler starter", [{id, Id}, {profile, ProfileName}]),
954
 
    IsInetsManager = is_inets_manager(), 
955
 
    ManagerPid = self(), 
956
 
    StarterFun = 
957
 
        fun() ->
958
 
                ?hcrd("handler starter - start", 
959
 
                      [{id,            Id}, 
960
 
                       {profile,       ProfileName}, 
961
 
                       {inets_manager, IsInetsManager}]),
962
 
                Result1 = 
963
 
                    case IsInetsManager of
964
 
                        true ->
965
 
                            httpc_handler_sup:start_child(Options, 
966
 
                                                          ProfileName);
967
 
                        false ->
968
 
                            httpc_handler:start_link(Options, 
969
 
                                                     ProfileName)
970
 
                    end,
971
 
                ?hcrd("handler starter - maybe connect and send", 
972
 
                      [{id, Id}, {profile, ProfileName}, {result, Result1}]),
973
 
                case Result1 of
974
 
                    {ok, HandlerPid} ->
975
 
                        StartedMessage = 
976
 
                            {started, self(), Id, HandlerPid}, 
977
 
                        ManagerPid ! StartedMessage, 
978
 
                        Result2 = httpc_handler:connect_and_send(Request, 
979
 
                                                                 HandlerPid),
980
 
                        ?hcrd("handler starter - connected and sent", 
981
 
                              [{id, Id}, {profile, ProfileName}, 
982
 
                               {handler, HandlerPid}, {result, Result2}]),
983
 
                        ConnAndSendMessage = 
984
 
                            {connect_and_send, 
985
 
                             self(), Id, HandlerPid, Result2}, 
986
 
                        ManagerPid ! ConnAndSendMessage;
987
 
                     {error, Reason} ->
988
 
                        StartFailureMessage = 
989
 
                            {failed_starting_handler, self(), Id, Reason}, 
990
 
                        ManagerPid ! StartFailureMessage;
991
 
                     _ ->
992
 
                        StartFailureMessage = 
993
 
                            {failed_starting_handler, self(), Id, Result1}, 
994
 
                        ManagerPid ! StartFailureMessage
995
 
                end
996
 
        end,
997
 
    Starter = erlang:spawn_link(StarterFun),
998
 
    ?hcrd("create handler starter - started", [{id, Id}, {starter, Starter}]),
999
 
    Entry = #handler_info{id      = Id,
1000
 
                          starter = Starter, 
1001
 
                          from    = From, 
1002
 
                          state   = initiating},
1003
 
    ets:insert(HandlerDb, Entry),
1004
 
    ok.
1005
 
                
1006
 
        
1007
734
is_inets_manager() ->
1008
735
    case get('$ancestors') of
1009
736
        [httpc_profile_sup | _] ->
1045
772
    ok = httpc_cookie:insert(CookieDb, Cookie),
1046
773
    do_store_cookies(Cookies, State).
1047
774
 
1048
 
 
1049
 
 
1050
775
session_db_name(ProfileName) ->
1051
776
    make_db_name(ProfileName, "__session_db").
1052
777
 
1074
799
   gen_server:cast(ProfileName, Msg).
1075
800
 
1076
801
 
1077
 
 
1078
802
get_proxy(Opts, #options{proxy = Default}) ->
1079
803
    proplists:get_value(proxy, Opts, Default).
1080
804
 
1133
857
handle_verbose(_) ->
1134
858
    ok.  
1135
859
 
1136
 
 
1137
860
error_report(Profile, F, A) ->
1138
861
    Report = io_lib:format("HTTPC-MANAGER<~p> " ++ F ++ "~n", [Profile | A]), 
1139
862
    error_logger:error_report(Report).
1140
 
 
1141
 
 
1142
 
%% d(F) ->
1143
 
%%    d(F, []).
1144
 
 
1145
 
%% d(F, A) -> 
1146
 
%%     d(get(dbg), F, A).
1147
 
 
1148
 
%% d(true, F, A) ->
1149
 
%%     io:format(user, "~w:~w:" ++ F ++ "~n", [self(), ?MODULE | A]);
1150
 
%% d(_, _, _) ->
1151
 
%%     ok.
1152