~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
143
143
%%--------------------------------------------------------------------
144
144
init([Request, Options]) ->
145
145
    process_flag(trap_exit, true),
 
146
    handle_verbose(Options#options.verbose),
146
147
    Address = handle_proxy(Request#request.address, Options#options.proxy),
147
148
    case {Address /= Request#request.address, Request#request.scheme} of
148
149
        {true, https} ->
173
174
                                       timers = Timers,
174
175
                                       options = Options}) ->
175
176
    Address = handle_proxy(Request#request.address, Options#options.proxy),
176
 
    http_util:verbose_output(Options#options.verbose,
177
 
                             Request,"Sending: "),
 
177
 
178
178
    case httpc_request:send(Address, Request, Socket) of
179
179
        ok ->
180
180
            %% Activate the request time out for the new request
186
186
            case State#state.request of
187
187
                #request{} -> %% Old request no yet finished
188
188
                    %% Make sure to use the new value of timers in state
189
 
                    Timers = NewState#state.timers,
 
189
                    NewTimers = NewState#state.timers,
190
190
                    NewPipeline = queue:in(Request, State#state.pipeline),
191
191
                    NewSession = 
192
192
                        Session#tcp_session{pipeline_length = 
196
196
                    httpc_manager:insert_session(NewSession),
197
197
                    {reply, ok, State#state{pipeline = NewPipeline,
198
198
                                            session = NewSession,
199
 
                                            timers = Timers}};
 
199
                                            timers = NewTimers}};
200
200
                undefined ->
201
201
                    %% Note: tcp-message reciving has already been
202
202
                    %% activated by handle_pipeline/2. Also
255
255
                                      stream = Stream} = Request, 
256
256
                   session = Session, status_line = StatusLine}) 
257
257
  when Proto == tcp; Proto == ssl; Proto == httpc_handler ->
258
 
    http_util:verbose_output((State#state.options)#options.verbose,
259
 
                             Data,"Received: "),
 
258
 
260
259
    case Module:Function([Data | Args]) of
261
260
        {ok, Result} ->
262
261
            handle_http_msg(Result, State); 
398
397
    SocketType = socket_type(Request),
399
398
    case http_transport:connect(SocketType, Address, Ipv6) of
400
399
        {ok, Socket} ->
401
 
            http_util:verbose_output((State#state.options)#options.verbose,
402
 
                                     Request,"Sending: "),
403
400
            case httpc_request:send(Address, Request, Socket) of
404
401
                ok ->
405
402
                    ClientClose = 
424
421
                    NewState = activate_request_timeout(TmpState),
425
422
                    {ok, NewState};
426
423
                {error, Reason} -> 
427
 
                    case State#state.status of
428
 
                        new -> % Called from init/1
429
 
                            self() ! {init_error, error_sending, 
430
 
                                      httpc_response:error(Request, Reason)},
431
 
                            {ok, State#state{request = Request,
432
 
                                             session = 
433
 
                                             #tcp_session{socket = Socket}}};
434
 
                        ssl_tunnel -> % Not called from init/1
435
 
                            NewState = 
436
 
                                answer_request(Request, 
437
 
                                               httpc_response:error(Request, 
438
 
                                                                    Reason),
439
 
                                               State),
440
 
                            {stop, normal, NewState}
441
 
                    end
442
 
            end;
443
 
        {error, Reason} ->
444
 
            case State#state.status of
445
 
                new -> % Called from init/1
446
 
                    self() ! {init_error, error_connecting, 
 
424
                    %% Commented out in wait of ssl support to avoid
 
425
                    %% dialyzer warning
 
426
                    %%case State#state.status of
 
427
                    %%  new -> % Called from init/1
 
428
                    self() ! {init_error, error_sending, 
447
429
                              httpc_response:error(Request, Reason)},
448
 
                    {ok, State#state{request = Request}};
449
 
                ssl_tunnel -> % Not called from init/1
450
 
                            NewState = 
451
 
                        answer_request(Request, 
452
 
                                       httpc_response:error(Request, 
453
 
                                                            Reason),
454
 
                                       State),
455
 
                    {stop, normal, NewState}
456
 
            end
 
430
                    {ok, State#state{request = Request,
 
431
                                     session = 
 
432
                                     #tcp_session{socket = Socket}}}
 
433
                    %%ssl_tunnel -> % Not called from init/1
 
434
                    %%  NewState = 
 
435
                    %%  answer_request(Request, 
 
436
                    %%httpc_response:error(Request, 
 
437
                    %%Reason),
 
438
                    %%                         State),
 
439
                    %%      {stop, normal, NewState}
 
440
                    %%    end
 
441
            end;
 
442
        {error, Reason} -> 
 
443
            %% Commented out in wait of ssl support to avoid
 
444
            %% dialyzer warning
 
445
            %% case State#state.status of
 
446
            %%  new -> % Called from init/1
 
447
            self() ! {init_error, error_connecting, 
 
448
                      httpc_response:error(Request, Reason)},
 
449
            {ok, State#state{request = Request}}
 
450
            %%  ssl_tunnel -> % Not called from init/1
 
451
            %%    NewState = 
 
452
            %%  answer_request(Request, 
 
453
            %%                 httpc_response:error(Request, 
 
454
            %%                                      Reason),
 
455
            %%                 State),
 
456
            %%    {stop, normal, NewState}
 
457
            %%end
457
458
    end.
458
459
 
459
460
handle_http_msg({Version, StatusCode, ReasonPharse, Headers, Body}, 
573
574
        continue -> 
574
575
            %% Send request body
575
576
            {_, RequestBody} = Request#request.content,
576
 
            http_util:verbose_output(Options#options.verbose,
577
 
                                     RequestBody,"Sending request body: "),
578
577
            http_transport:send(socket_type(Session#tcp_session.scheme), 
579
578
                                            Session#tcp_session.socket, 
580
579
                                RequestBody),
883
882
end_stream(_, _) ->
884
883
    ok.
885
884
 
 
885
handle_verbose(verbose) ->
 
886
    dbg:p(self(), [r]);
 
887
handle_verbose(debug) ->
 
888
    dbg:p(self(), [call]),
 
889
    dbg:tp(?MODULE, [{'_', [], [{return_trace}]}]);
 
890
handle_verbose(trace) ->
 
891
    dbg:p(self(), [call]),
 
892
    dbg:tpl(?MODULE, [{'_', [], [{return_trace}]}]);
 
893
handle_verbose(_) ->
 
894
    ok.    
 
895
 
886
896
%%% Normaly I do not comment out code, I throw it away. But this might
887
897
%%% actually be used on day if ssl is improved.
888
898
%% send_ssl_tunnel_request(Address, Request = #request{address = {Host, Port}},