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

« back to all changes in this revision

Viewing changes to lib/inets/src/http_client/httpc_handler.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2002-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2002-2010. All Rights Reserved.
 
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
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
%%
28
28
 
29
29
%%--------------------------------------------------------------------
30
30
%% Internal Application API
31
 
-export([start_link/3, send/2, cancel/2, stream/3, stream_next/1]).
 
31
-export([
 
32
         start_link/2, 
 
33
         connect_and_send/2, 
 
34
         send/2, 
 
35
         cancel/2, 
 
36
         stream/3, 
 
37
         stream_next/1,
 
38
         info/1
 
39
        ]).
32
40
 
33
41
%% gen_server callbacks
34
42
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
50
58
          mfa,                       % {Moduel, Function, Args}
51
59
          pipeline = queue:new(),    % queue() 
52
60
          keep_alive = queue:new(),  % queue() 
53
 
          status = new,   % new | pipeline | keep_alive | close | ssl_tunnel
 
61
          status,   % undefined | new | pipeline | keep_alive | close | ssl_tunnel
54
62
          canceled = [],             % [RequestId]
55
63
          max_header_size = nolimit, % nolimit | integer() 
56
64
          max_body_size = nolimit,   % nolimit | integer()
85
93
%% the reply or part of it has arrived.)
86
94
%%--------------------------------------------------------------------
87
95
%%--------------------------------------------------------------------
88
 
start_link(Request, Options, ProfileName) ->
89
 
    {ok, proc_lib:spawn_link(?MODULE, init, [[Request, Options, 
90
 
                                              ProfileName]])}.
 
96
 
 
97
start_link(Options, ProfileName) ->
 
98
    Args = [Options, ProfileName], 
 
99
    gen_server:start_link(?MODULE, Args, []).
 
100
 
 
101
connect_and_send(Request, HandlerPid) ->
 
102
    call({connect_and_send, Request}, HandlerPid).
91
103
 
92
104
 
93
105
%%--------------------------------------------------------------------
126
138
 
127
139
 
128
140
%%--------------------------------------------------------------------
 
141
%% Function: info(Pid) -> [{Key, Val}]
 
142
%%      Pid = pid() -  the pid of the http-request handler process.
 
143
%%
 
144
%% Description: 
 
145
%%     Returns various information related to this handler
 
146
%%     Used for debugging and testing
 
147
%%--------------------------------------------------------------------
 
148
info(Pid) ->
 
149
    call(info, Pid).
 
150
 
 
151
 
 
152
%%--------------------------------------------------------------------
129
153
%% Function: stream(BodyPart, Request, Code) -> _
130
154
%%      BodyPart = binary()
131
155
%%      Request = #request{}
138
162
%%--------------------------------------------------------------------
139
163
%% Request should not be streamed
140
164
stream(BodyPart, Request = #request{stream = none}, _) ->
141
 
    ?hcrt("stream - none", [{body_part, BodyPart}]),
 
165
    ?hcrt("stream - none", []),
142
166
    {BodyPart, Request};
143
167
 
144
168
%% Stream to caller
145
169
stream(BodyPart, Request = #request{stream = Self}, Code) 
146
170
  when ((Code =:= 200) orelse  (Code =:= 206)) andalso 
147
171
       ((Self =:= self) orelse (Self =:= {self, once})) ->
148
 
    ?hcrt("stream - self", [{stream, Self}, {code, Code}, {body_part, BodyPart}]),
 
172
    ?hcrt("stream - self", [{stream, Self}, {code, Code}]),
149
173
    httpc_response:send(Request#request.from, 
150
174
                        {Request#request.id, stream, BodyPart}),
151
175
    {<<>>, Request};
152
176
 
153
177
stream(BodyPart, Request = #request{stream = Self}, 404) 
154
178
  when (Self =:= self) orelse (Self =:= {self, once}) ->
155
 
    ?hcrt("stream - self with 404", [{stream, Self}, {body_part, BodyPart}]),
 
179
    ?hcrt("stream - self with 404", [{stream, Self}]),
156
180
    httpc_response:send(Request#request.from,
157
181
                       {Request#request.id, stream, BodyPart}),
158
182
    {<<>>, Request};
162
186
%% We keep this for backward compatibillity...
163
187
stream(BodyPart, Request = #request{stream = Filename}, Code)
164
188
  when ((Code =:= 200) orelse (Code =:= 206)) andalso is_list(Filename) -> 
165
 
    ?hcrt("stream - filename", [{stream, Filename}, {code, Code}, {body_part, BodyPart}]),
 
189
    ?hcrt("stream - filename", [{stream, Filename}, {code, Code}]),
166
190
    case file:open(Filename, [write, raw, append, delayed_write]) of
167
191
        {ok, Fd} ->
168
192
            ?hcrt("stream - file open ok", [{fd, Fd}]),
174
198
%% Stream to file
175
199
stream(BodyPart, Request = #request{stream = Fd}, Code)  
176
200
  when ((Code =:= 200) orelse (Code =:= 206)) -> 
177
 
    ?hcrt("stream to file", [{stream, Fd}, {code, Code}, {body_part, BodyPart}]),
 
201
    ?hcrt("stream to file", [{stream, Fd}, {code, Code}]),
178
202
    case file:write(Fd, BodyPart) of
179
203
        ok ->
180
204
            {<<>>, Request};
183
207
    end;
184
208
 
185
209
stream(BodyPart, Request,_) -> % only 200 and 206 responses can be streamed
186
 
    ?hcrt("stream - ignore", [{request, Request}, {body_part, BodyPart}]),
 
210
    ?hcrt("stream - ignore", [{request, Request}]),
187
211
    {BodyPart, Request}.
188
212
 
189
213
 
192
216
%%====================================================================
193
217
 
194
218
%%--------------------------------------------------------------------
195
 
%% Function: init([Request, Options, ProfileName]) -> {ok, State} | 
196
 
%%                       {ok, State, Timeout} | ignore |{stop, Reason}
 
219
%% Function: init([Options, ProfileName]) -> {ok, State} | 
 
220
%%                       {ok, State, Timeout} | ignore | {stop, Reason}
197
221
%%
198
 
%%      Request = #request{}
199
222
%%      Options =  #options{} 
200
223
%%      ProfileName = atom() - id of httpc manager process
201
224
%%
206
229
%% but we do not want that so errors will be handled by the process
207
230
%% sending an init_error message to itself.
208
231
%%--------------------------------------------------------------------
209
 
init([Request, Options, ProfileName]) ->
 
232
init([Options, ProfileName]) ->
 
233
    ?hcrv("init - starting", [{options, Options}, {profile, ProfileName}]),
210
234
    process_flag(trap_exit, true),
211
 
 
212
235
    handle_verbose(Options#options.verbose),
213
 
    Address = handle_proxy(Request#request.address, Options#options.proxy),
214
 
    {ok, State} =
215
 
        case {Address /= Request#request.address, Request#request.scheme} of
216
 
            {true, https} ->
217
 
                Error = https_through_proxy_is_not_currently_supported,
218
 
                self() ! {init_error, 
219
 
                          Error, httpc_response:error(Request, Error)},
220
 
                {ok, #state{request = Request, options = Options,
221
 
                            status = ssl_tunnel}};
222
 
            %% This is what we should do if and when ssl supports 
223
 
            %% "socket upgrading"
224
 
            %%send_ssl_tunnel_request(Address, Request,
225
 
            %%              #state{options = Options,
226
 
            %%             status = ssl_tunnel});
227
 
            {_, _} ->
228
 
                send_first_request(Address, Request, 
229
 
                                   #state{options = Options,
230
 
                                          profile_name = ProfileName})
231
 
        end,
232
 
    gen_server:enter_loop(?MODULE, [], State).
 
236
    State = #state{status       = undefined,
 
237
                   options      = Options, 
 
238
                   profile_name = ProfileName},
 
239
    ?hcrd("init - started", []),
 
240
    {ok, State}.
 
241
 
233
242
 
234
243
%%--------------------------------------------------------------------
235
244
%% Function: handle_call(Request, From, State) -> {reply, Reply, State} |
240
249
%%          {stop, Reason, State}            (terminate/2 is called)
241
250
%% Description: Handling call messages
242
251
%%--------------------------------------------------------------------
243
 
handle_call(Request, _, State = #state{session = Session =
244
 
                                       #tcp_session{socket = Socket,
245
 
                                                    type = pipeline},
246
 
                                       timers = Timers,
247
 
                                       options = Options,
248
 
                                       profile_name = ProfileName}) ->
249
 
    Address = handle_proxy(Request#request.address, Options#options.proxy),
 
252
 
 
253
 
 
254
%% This is the first request, the reason the proc was started
 
255
handle_call({connect_and_send, #request{address = Address0,
 
256
                                        scheme  = Scheme} = Request}, 
 
257
            _From, 
 
258
            #state{options = #options{proxy = Proxy}, 
 
259
                   status  = undefined,
 
260
                   session = undefined} = State) ->
 
261
    ?hcrv("connect and send", [{address0, Address0}, {proxy, Proxy}]),
 
262
    Address = handle_proxy(Address0, Proxy),
 
263
    if
 
264
        ((Address =/= Address0) andalso (Scheme  =:= https)) ->
 
265
            %% This is what we should do if and when ssl supports 
 
266
            %% "socket upgrading"
 
267
            %%send_ssl_tunnel_request(Address, Request,
 
268
            %%              #state{options = Options,
 
269
            %%             status = ssl_tunnel});
 
270
            Reason = {failed_connecting, 
 
271
                      https_through_proxy_is_not_currently_supported},
 
272
            %% Send a reply to the original caller
 
273
            ErrorResponse = httpc_response:error(Request, Reason), 
 
274
            httpc_response:send(Request#request.from, ErrorResponse),
 
275
            %% Reply to the manager
 
276
            ErrorReply    = {error, Reason},
 
277
            {stop, normal, ErrorReply, State};
 
278
        true ->
 
279
            case connect_and_send_first_request(Address, Request, State) of
 
280
                {ok, NewState} ->
 
281
                    {reply, ok, NewState};
 
282
                {stop, Error, NewState} ->
 
283
                    {stop, Error, Error, NewState}
 
284
            end
 
285
    end;
 
286
        
 
287
handle_call(#request{address = Addr} = Request, _, 
 
288
            #state{status  = Status,
 
289
                   session = #tcp_session{socket = Socket,
 
290
                                          type   = pipeline} = Session,
 
291
                   timers  = Timers,
 
292
                   options = #options{proxy = Proxy} = _Options, 
 
293
                   profile_name = ProfileName} = State) 
 
294
  when Status =/= undefined ->
 
295
 
 
296
    ?hcrv("new request on a pipeline session", 
 
297
          [{request, Request}, 
 
298
           {profile, ProfileName}, 
 
299
           {status,  Status}, 
 
300
           {timers,  Timers}]),
 
301
 
 
302
    Address = handle_proxy(Addr, Proxy),
250
303
 
251
304
    case httpc_request:send(Address, Request, Socket) of
252
305
        ok ->
 
306
 
 
307
            ?hcrd("request sent", []),
 
308
 
253
309
            %% Activate the request time out for the new request
254
 
            NewState = activate_request_timeout(State#state{request =
255
 
                                                             Request}),
256
 
 
257
 
            ClientClose = httpc_request:is_client_closing(
258
 
                            Request#request.headers),
 
310
            NewState = 
 
311
                activate_request_timeout(State#state{request = Request}),
 
312
 
 
313
            ClientClose = 
 
314
                httpc_request:is_client_closing(Request#request.headers),
 
315
 
259
316
            case State#state.request of
260
 
                #request{} -> %% Old request no yet finished
 
317
                #request{} -> %% Old request not yet finished
 
318
                    ?hcrd("old request still not finished", []),
261
319
                    %% Make sure to use the new value of timers in state
262
 
                    NewTimers = NewState#state.timers,
 
320
                    NewTimers   = NewState#state.timers,
263
321
                    NewPipeline = queue:in(Request, State#state.pipeline),
264
 
                    NewSession = 
 
322
                    NewSession  = 
265
323
                        Session#tcp_session{queue_length = 
266
324
                                            %% Queue + current
267
325
                                            queue:len(NewPipeline) + 1,
268
326
                                            client_close = ClientClose},
269
327
                    httpc_manager:insert_session(NewSession, ProfileName),
 
328
                    ?hcrd("session updated", []),
270
329
                    {reply, ok, State#state{pipeline = NewPipeline,
271
 
                                            session = NewSession,
272
 
                                            timers = NewTimers}};
 
330
                                            session  = NewSession,
 
331
                                            timers   = NewTimers}};
273
332
                undefined ->
274
 
                    %% Note: tcp-message reciving has already been
 
333
                    %% Note: tcp-message receiving has already been
275
334
                    %% activated by handle_pipeline/2. 
 
335
                    ?hcrd("no current request", []),
276
336
                    cancel_timer(Timers#timers.queue_timer, 
277
337
                                 timeout_queue),
278
338
                    NewSession = 
281
341
                    httpc_manager:insert_session(NewSession, ProfileName),
282
342
                    Relaxed = 
283
343
                        (Request#request.settings)#http_options.relaxed, 
284
 
                    {reply, ok, 
285
 
                     NewState#state{request = Request,
286
 
                                    session = NewSession,
287
 
                                    mfa = {httpc_response, parse,
288
 
                                           [State#state.max_header_size,
289
 
                                            Relaxed]},
290
 
                                    timers = 
291
 
                                    Timers#timers{queue_timer =
292
 
                                                  undefined}}}
 
344
                    MFA = {httpc_response, parse, 
 
345
                           [State#state.max_header_size, Relaxed]}, 
 
346
                    NewTimers = Timers#timers{queue_timer = undefined}, 
 
347
                    ?hcrd("session created", []),
 
348
                    {reply, ok, NewState#state{request = Request,
 
349
                                               session = NewSession,
 
350
                                               mfa     = MFA,
 
351
                                               timers  = NewTimers}}
293
352
            end;
294
353
        {error, Reason} ->
 
354
            ?hcri("failed sending request", [{reason, Reason}]),
295
355
            {reply, {pipeline_failed, Reason}, State}
296
356
    end;
297
357
 
298
 
handle_call(Request, _, #state{session = Session =
299
 
                               #tcp_session{type = keep_alive,
300
 
                                            socket = Socket},
301
 
                               timers = Timers,
302
 
                               options = Options,
303
 
                               profile_name = ProfileName} = State) ->
304
 
       
305
 
    ClientClose = httpc_request:is_client_closing(Request#request.headers),
 
358
handle_call(#request{address = Addr} = Request, _, 
 
359
            #state{status  = Status,
 
360
                   session = #tcp_session{socket = Socket,
 
361
                                          type   = keep_alive} = Session,
 
362
                   timers  = Timers,
 
363
                   options = #options{proxy = Proxy} = _Options,
 
364
                   profile_name = ProfileName} = State) 
 
365
  when Status =/= undefined ->
306
366
    
307
 
    Address = handle_proxy(Request#request.address, 
308
 
                           Options#options.proxy),
 
367
    ?hcrv("new request on a keep-alive session", 
 
368
          [{request, Request}, 
 
369
           {profile, ProfileName}, 
 
370
           {status,  Status}]),
 
371
 
 
372
    Address = handle_proxy(Addr, Proxy),
309
373
    case httpc_request:send(Address, Request, Socket) of
310
374
        ok ->
 
375
 
 
376
            ?hcrd("request sent", []),
 
377
 
 
378
            %% Activate the request time out for the new request
311
379
            NewState = 
312
 
                activate_request_timeout(State#state{request =
313
 
                                                     Request}),
 
380
                activate_request_timeout(State#state{request = Request}),
 
381
 
 
382
            ClientClose = 
 
383
                httpc_request:is_client_closing(Request#request.headers),
314
384
 
315
385
            case State#state.request of
316
386
                #request{} -> %% Old request not yet finished
317
387
                    %% Make sure to use the new value of timers in state
318
 
                    NewTimers = NewState#state.timers,
 
388
                    ?hcrd("old request still not finished", []),
 
389
                    NewTimers    = NewState#state.timers,
319
390
                    NewKeepAlive = queue:in(Request, State#state.keep_alive),
320
 
                    NewSession = 
 
391
                    NewSession   = 
321
392
                        Session#tcp_session{queue_length = 
322
393
                                            %% Queue + current
323
394
                                            queue:len(NewKeepAlive) + 1,
324
395
                                            client_close = ClientClose},
325
396
                    httpc_manager:insert_session(NewSession, ProfileName),
 
397
                    ?hcrd("session updated", []),
326
398
                    {reply, ok, State#state{keep_alive = NewKeepAlive,
327
 
                                            session = NewSession,
328
 
                                            timers = NewTimers}};
 
399
                                            session    = NewSession,
 
400
                                            timers     = NewTimers}};
329
401
                undefined ->
330
402
                    %% Note: tcp-message reciving has already been
331
403
                    %% activated by handle_pipeline/2. 
 
404
                    ?hcrd("no current request", []),
332
405
                    cancel_timer(Timers#timers.queue_timer, 
333
406
                                 timeout_queue),
334
407
                    NewSession = 
337
410
                    httpc_manager:insert_session(NewSession, ProfileName),
338
411
                    Relaxed = 
339
412
                        (Request#request.settings)#http_options.relaxed,
340
 
                    {reply, ok, 
341
 
                     NewState#state{request = Request,
342
 
                                    session = NewSession, 
343
 
                                    mfa = {httpc_response, parse,
344
 
                                           [State#state.max_header_size,
345
 
                                            Relaxed]}}}
 
413
                    MFA = {httpc_response, parse,
 
414
                           [State#state.max_header_size, Relaxed]}, 
 
415
                    {reply, ok, NewState#state{request = Request,
 
416
                                               session = NewSession, 
 
417
                                               mfa     = MFA}}
346
418
            end;
347
 
        {error, Reason}    ->
 
419
 
 
420
        {error, Reason} ->
 
421
            ?hcri("failed sending request", [{reason, Reason}]),
348
422
            {reply, {request_failed, Reason}, State}
349
 
    end.
 
423
    end;
 
424
 
 
425
 
 
426
handle_call(info, _, State) ->
 
427
    Info = handler_info(State), 
 
428
    {reply, Info, State}.
 
429
 
350
430
 
351
431
%%--------------------------------------------------------------------
352
432
%% Function: handle_cast(Msg, State) -> {noreply, State} |
367
447
%% handle_keep_alive_queue/2 on the other hand will just skip the
368
448
%% request as if it was never issued as in this case the request will
369
449
%% not have been sent. 
370
 
handle_cast({cancel, RequestId}, State = #state{request = Request =
371
 
                                                #request{id = RequestId},
372
 
                                                profile_name = ProfileName}) ->
 
450
handle_cast({cancel, RequestId}, 
 
451
            #state{request      = #request{id = RequestId} = Request,
 
452
                   profile_name = ProfileName,
 
453
                   canceled     = Canceled} = State) ->
 
454
    ?hcrv("cancel current request", [{request_id, RequestId}, 
 
455
                                     {profile,    ProfileName},
 
456
                                     {canceled,   Canceled}]),
373
457
    httpc_manager:request_canceled(RequestId, ProfileName),
 
458
    ?hcrv("canceled", []),
374
459
    {stop, normal, 
375
 
     State#state{canceled = [RequestId | State#state.canceled],
376
 
                 request = Request#request{from = answer_sent}}};
377
 
handle_cast({cancel, RequestId}, State = #state{profile_name = ProfileName}) ->
 
460
     State#state{canceled = [RequestId | Canceled],
 
461
                 request  = Request#request{from = answer_sent}}};
 
462
handle_cast({cancel, RequestId}, 
 
463
            #state{profile_name = ProfileName,
 
464
                   canceled     = Canceled} = State) ->
 
465
    ?hcrv("cancel", [{request_id, RequestId}, 
 
466
                     {profile, ProfileName},
 
467
                     {canceled,   Canceled}]),
378
468
    httpc_manager:request_canceled(RequestId, ProfileName),
379
 
    {noreply, State#state{canceled = [RequestId | State#state.canceled]}};
 
469
    ?hcrv("canceled", []),
 
470
    {noreply, State#state{canceled = [RequestId | Canceled]}};
 
471
 
380
472
handle_cast(stream_next, #state{session = Session} = State) ->
381
 
    http_transport:setopts(socket_type(Session#tcp_session.scheme), 
382
 
                           Session#tcp_session.socket, [{active, once}]), 
 
473
    activate_once(Session), 
383
474
    {noreply, State#state{once = once}}.
384
475
 
385
476
 
390
481
%% Description: Handling all non call/cast messages
391
482
%%--------------------------------------------------------------------
392
483
handle_info({Proto, _Socket, Data}, 
393
 
            #state{mfa = {Module, Function, Args} = MFA, 
 
484
            #state{mfa = {Module, Function, Args}, 
394
485
                   request = #request{method = Method, 
395
486
                                      stream = Stream} = Request, 
396
487
                   session = Session, 
399
490
       (Proto =:= ssl) orelse 
400
491
       (Proto =:= httpc_handler) ->
401
492
 
402
 
    ?hcri("received data", [{proto, Proto}, {data, Data}, {mfa, MFA}, {method, Method}, {stream, Stream}, {session, Session}, {status_line, StatusLine}]),
 
493
    ?hcri("received data", [{proto,       Proto}, 
 
494
                            {module,      Module}, 
 
495
                            {function,    Function}, 
 
496
                            {method,      Method}, 
 
497
                            {stream,      Stream}, 
 
498
                            {session,     Session}, 
 
499
                            {status_line, StatusLine}]),
403
500
 
404
501
    FinalResult = 
405
502
        try Module:Function([Data | Args]) of
406
503
            {ok, Result} ->
407
 
                ?hcrd("data processed - ok", [{result, Result}]),
 
504
                ?hcrd("data processed - ok", []),
408
505
                handle_http_msg(Result, State); 
409
506
            {_, whole_body, _} when Method =:= head ->
410
507
                ?hcrd("data processed - whole body", []),
411
508
                handle_response(State#state{body = <<>>}); 
412
509
            {Module, whole_body, [Body, Length]} ->
413
 
                ?hcrd("data processed - whole body", [{module, Module}, {body, Body}, {length, Length}]),
 
510
                ?hcrd("data processed - whole body", [{length, Length}]),
414
511
                {_, Code, _} = StatusLine,
415
512
                {NewBody, NewRequest} = stream(Body, Request, Code),
416
513
                %% When we stream we will not keep the already
417
514
                %% streamed data, that would be a waste of memory.
418
 
                NewLength = case Stream of
419
 
                                none ->   
420
 
                                    Length;
421
 
                                _ ->
422
 
                                    Length - size(Body)                     
423
 
                            end,
 
515
                NewLength = 
 
516
                    case Stream of
 
517
                        none ->   
 
518
                            Length;
 
519
                        _ ->
 
520
                            Length - size(Body)                     
 
521
                    end,
424
522
                
425
523
                NewState = next_body_chunk(State),
426
 
                
427
 
                {noreply, NewState#state{mfa = {Module, whole_body, 
428
 
                                                [NewBody, NewLength]},
 
524
                NewMFA   = {Module, whole_body, [NewBody, NewLength]}, 
 
525
                {noreply, NewState#state{mfa     = NewMFA,
429
526
                                         request = NewRequest}};
430
527
            NewMFA ->
431
 
                ?hcrd("data processed", [{new_mfa, NewMFA}]),
432
 
                http_transport:setopts(socket_type(Session#tcp_session.scheme), 
433
 
                                       Session#tcp_session.socket, 
434
 
                                       [{active, once}]),
 
528
                ?hcrd("data processed - new mfa", []),
 
529
                activate_once(Session),
435
530
                {noreply, State#state{mfa = NewMFA}}
436
531
        catch
437
 
            exit:_ ->
438
 
                ClientErrMsg = httpc_response:error(Request, 
439
 
                                                    {could_not_parse_as_http, 
440
 
                                                     Data}),
441
 
                NewState = answer_request(Request, ClientErrMsg, State),
 
532
            exit:_Exit ->
 
533
                ?hcrd("data processing exit", [{exit, _Exit}]),
 
534
                ClientReason = {could_not_parse_as_http, Data}, 
 
535
                ClientErrMsg = httpc_response:error(Request, ClientReason),
 
536
                NewState     = answer_request(Request, ClientErrMsg, State),
442
537
                {stop, normal, NewState};
443
 
              error:_ ->    
444
 
                ClientErrMsg = httpc_response:error(Request, 
445
 
                                                    {could_not_parse_as_http, 
446
 
                                                     Data}),
447
 
                NewState = answer_request(Request, ClientErrMsg, State),   
 
538
            error:_Error ->    
 
539
                ?hcrd("data processing error", [{error, _Error}]),
 
540
                ClientReason = {could_not_parse_as_http, Data}, 
 
541
                ClientErrMsg = httpc_response:error(Request, ClientReason),
 
542
                NewState     = answer_request(Request, ClientErrMsg, State),   
448
543
                {stop, normal, NewState}
449
544
        
450
545
        end,
451
 
    ?hcri("data processed", [{result, FinalResult}]),
 
546
    ?hcri("data processed", []),
452
547
    FinalResult;
453
548
 
454
549
 
455
550
handle_info({Proto, Socket, Data}, 
456
 
            #state{mfa     = MFA, 
457
 
                   request = Request, 
458
 
                   session = Session, 
459
 
                   status  = Status,
 
551
            #state{mfa          = MFA, 
 
552
                   request      = Request, 
 
553
                   session      = Session, 
 
554
                   status       = Status,
460
555
                   status_line  = StatusLine, 
461
556
                   profile_name = Profile} = State) 
462
557
  when (Proto =:= tcp) orelse 
474
569
                             "~n", 
475
570
                             [Proto, Socket, Data, MFA, 
476
571
                              Request, Session, Status, StatusLine, Profile]),
 
572
 
477
573
    {noreply, State};
478
574
 
479
575
 
513
609
handle_info({timeout, RequestId}, 
514
610
            #state{request  = #request{id = RequestId} = Request,
515
611
                   canceled = Canceled} = State) ->
 
612
    ?hcri("timeout of current request", [{id, RequestId}]),
516
613
    httpc_response:send(Request#request.from, 
517
 
                       httpc_response:error(Request,timeout)),
 
614
                        httpc_response:error(Request, timeout)),
 
615
    ?hcrv("response (timeout) sent - now terminate", []),
518
616
    {stop, normal, 
519
617
     State#state{request  = Request#request{from = answer_sent},
520
618
                 canceled = [RequestId | Canceled]}};
521
619
 
522
620
handle_info({timeout, RequestId}, #state{canceled = Canceled} = State) ->
 
621
    ?hcri("timeout", [{id, RequestId}]),
523
622
    Filter = 
524
623
        fun(#request{id = Id, from = From} = Request) when Id =:= RequestId ->
 
624
                ?hcrv("found request", [{id, Id}, {from, From}]),
525
625
                %% Notify the owner
526
626
                Response = httpc_response:error(Request, timeout), 
527
627
                httpc_response:send(From, Response),
 
628
                ?hcrv("response (timeout) sent", []),
528
629
                [Request#request{from = answer_sent}];
529
630
           (_) ->
530
631
                true
531
632
        end,
532
633
    case State#state.status of
533
634
        pipeline ->
 
635
            ?hcrd("pipeline", []),
534
636
            Pipeline = queue:filter(Filter, State#state.pipeline),
535
637
            {noreply, State#state{canceled = [RequestId | Canceled],
536
638
                                  pipeline = Pipeline}};
537
639
        keep_alive ->
 
640
            ?hcrd("keep_alive", []),
538
641
            KeepAlive = queue:filter(Filter, State#state.keep_alive),
539
642
            {noreply, State#state{canceled   = [RequestId | Canceled],
540
643
                                  keep_alive = KeepAlive}}
577
680
 
578
681
%% Init error sending, no session information has been setup but
579
682
%% there is a socket that needs closing.
580
 
terminate(normal, #state{request = Request,
581
 
                         session = #tcp_session{id = undefined,
582
 
                                                socket = Socket}}) ->  
 
683
terminate(normal, 
 
684
          #state{request = Request,
 
685
                 session = #tcp_session{id     = undefined,
 
686
                                        socket = Socket}}) ->  
583
687
    http_transport:close(socket_type(Request), Socket);
584
688
 
585
689
%% Socket closed remotely
590
694
                 request = Request,
591
695
                 timers  = Timers,
592
696
                 pipeline = Pipeline}) ->  
 
697
    ?hcrt("terminate(normal) - remote close", 
 
698
          [{id, Id}, {profile, ProfileName}]),
 
699
 
593
700
    %% Clobber session
594
701
    (catch httpc_manager:delete_session(Id, ProfileName)),
595
702
 
605
712
    %% And, just in case, close our side (**really** overkill)
606
713
    http_transport:close(socket_type(Request), Socket);
607
714
 
608
 
terminate(_, State = #state{session      = Session, 
609
 
                            request      = undefined,
610
 
                            profile_name = ProfileName,
611
 
                            timers       = Timers,
612
 
                            pipeline     = Pipeline,
613
 
                            keep_alive   = KeepAlive}) -> 
614
 
    catch httpc_manager:delete_session(Session#tcp_session.id,
615
 
                                       ProfileName),
 
715
terminate(_, #state{session      = #tcp_session{id     = Id,
 
716
                                                socket = Socket, 
 
717
                                                scheme = Scheme},
 
718
                    request      = undefined,
 
719
                    profile_name = ProfileName,
 
720
                    timers       = Timers,
 
721
                    pipeline     = Pipeline,
 
722
                    keep_alive   = KeepAlive} = State) -> 
 
723
    (catch httpc_manager:delete_session(Id, ProfileName)),
616
724
 
617
725
    maybe_retry_queue(Pipeline, State),
618
726
    maybe_retry_queue(KeepAlive, State),
619
727
 
620
728
    cancel_timer(Timers#timers.queue_timer, timeout_queue),
621
 
    Socket = Session#tcp_session.socket, 
622
 
    http_transport:close(socket_type(Session#tcp_session.scheme), Socket);
623
 
 
624
 
terminate(Reason, State = #state{request = Request}) -> 
 
729
    http_transport:close(socket_type(Scheme), Socket);
 
730
 
 
731
terminate(Reason, #state{request = undefined}) -> 
 
732
    ?hcrt("terminate", [{reason, Reason}]),
 
733
    ok;
 
734
 
 
735
terminate(Reason, #state{request = Request} = State) -> 
 
736
    ?hcrd("terminate", [{reason, Reason}, {request, Request}]),
625
737
    NewState = maybe_send_answer(Request, 
626
738
                                 httpc_response:error(Request, Reason), 
627
739
                                 State),
641
753
    answer_request(Request, Answer, State).
642
754
 
643
755
deliver_answers([]) ->
 
756
    ?hcrd("deliver answer done", []),
644
757
    ok;
645
 
deliver_answers([#request{from = From} = Request | Requests]) 
 
758
deliver_answers([#request{id = Id, from = From} = Request | Requests]) 
646
759
  when is_pid(From) ->
647
760
    Response = httpc_response:error(Request, socket_closed_remotely),
 
761
    ?hcrd("deliver answer", [{id, Id}, {from, From}, {response, Response}]),
648
762
    httpc_response:send(From, Response),
649
763
    deliver_answers(Requests);
650
 
deliver_answers([_|Requests]) ->
 
764
deliver_answers([Request|Requests]) ->
 
765
    ?hcrd("skip deliver answer", [{request, Request}]),
651
766
    deliver_answers(Requests).
652
767
 
653
768
 
691
806
                  end, List),
692
807
    queue:from_list(NewList).
693
808
    
694
 
%%--------------------------------------------------------------------
 
809
 
 
810
%%%--------------------------------------------------------------------
695
811
%%% Internal functions
696
 
%%--------------------------------------------------------------------
 
812
%%%--------------------------------------------------------------------
697
813
 
698
 
connect(SocketType, ToAddress, #options{ipfamily = IpFamily,
699
 
                                        ip       = FromAddress,
700
 
                                        port     = FromPort}, Timeout) ->
 
814
connect(SocketType, ToAddress, 
 
815
        #options{ipfamily    = IpFamily,
 
816
                 ip          = FromAddress,
 
817
                 port        = FromPort,
 
818
                 socket_opts = Opts0}, Timeout) ->
701
819
    Opts1 = 
702
820
        case FromPort of
703
821
            default ->
704
 
                [];
 
822
                Opts0;
705
823
            _ ->
706
 
                [{port, FromPort}]
 
824
                [{port, FromPort} | Opts0]
707
825
        end,
708
826
    Opts2 = 
709
827
        case FromAddress of
728
846
            http_transport:connect(SocketType, ToAddress, Opts3, Timeout)
729
847
    end.
730
848
                
731
 
    
732
 
send_first_request(Address, Request, #state{options = Options} = State) ->
 
849
connect_and_send_first_request(Address, 
 
850
                               #request{settings    = Settings,
 
851
                                        headers     = Headers,
 
852
                                        address     = OrigAddress,
 
853
                                        scheme      = Scheme} = Request, 
 
854
                               #state{options = Options} = State) ->
 
855
 
 
856
    ?hcrd("connect", 
 
857
          [{address, Address}, {request, Request}, {options, Options}]),
 
858
 
733
859
    SocketType  = socket_type(Request),
734
 
    ConnTimeout = (Request#request.settings)#http_options.connect_timeout,
735
 
    ?hcri("connect", 
736
 
          [{address, Address}, {request, Request}, {options, Options}]),
 
860
    ConnTimeout = Settings#http_options.connect_timeout,
737
861
    case connect(SocketType, Address, Options, ConnTimeout) of
738
862
        {ok, Socket} ->
739
 
            ?hcri("connected - now send first request", [{socket, Socket}]),
 
863
            ?hcrd("connected - now send first request", [{socket, Socket}]),
740
864
            case httpc_request:send(Address, Request, Socket) of
741
865
                ok ->
742
 
                    ?hcri("first request sent", []),
 
866
                    ?hcrd("first request sent", []),
743
867
                    ClientClose = 
744
 
                        httpc_request:is_client_closing(
745
 
                          Request#request.headers),
 
868
                        httpc_request:is_client_closing(Headers),
746
869
                    SessionType = httpc_manager:session_type(Options),
747
870
                    Session =
748
 
                        #tcp_session{id = {Request#request.address, self()},
749
 
                                     scheme = Request#request.scheme,
750
 
                                     socket = Socket,
 
871
                        #tcp_session{id           = {OrigAddress, self()},
 
872
                                     scheme       = Scheme,
 
873
                                     socket       = Socket,
751
874
                                     client_close = ClientClose,
752
 
                                     type = SessionType},
753
 
                    TmpState = State#state{request = Request, 
754
 
                                           session = Session, 
755
 
                                           mfa = init_mfa(Request, State),
756
 
                                           status_line = 
757
 
                                           init_status_line(Request),
758
 
                                           headers = undefined,
759
 
                                           body = undefined,
760
 
                                           status = new},
761
 
                    http_transport:setopts(SocketType, 
762
 
                                           Socket, [{active, once}]),
 
875
                                     type         = SessionType},
 
876
                    TmpState = 
 
877
                        State#state{request     = Request, 
 
878
                                    session     = Session, 
 
879
                                    mfa         = init_mfa(Request, State),
 
880
                                    status_line = init_status_line(Request),
 
881
                                    headers     = undefined,
 
882
                                    body        = undefined,
 
883
                                    status      = new},
 
884
                    ?hcrt("activate socket", []),
 
885
                    activate_once(Session),
763
886
                    NewState = activate_request_timeout(TmpState),
764
887
                    {ok, NewState};
765
888
 
766
 
                {error, Reason} ->                  
767
 
                    %% Commented out in wait of ssl support to avoid
768
 
                    %% dialyzer warning
769
 
                    %%case State#state.status of
770
 
                    %%  new -> % Called from init/1
771
 
                    self() ! {init_error, error_sending, 
772
 
                              httpc_response:error(Request, Reason)},
773
 
                    {ok, State#state{request = Request,
774
 
                                     session = 
775
 
                                     #tcp_session{socket = Socket}}}
776
 
                    %%ssl_tunnel -> % Not called from init/1
777
 
                    %%  NewState = 
778
 
                    %%  answer_request(Request, 
779
 
                    %%httpc_response:error(Request, 
780
 
                    %%Reason),
781
 
                    %%                         State),
782
 
                    %%      {stop, normal, NewState}
783
 
                    %%    end
 
889
                {error, Reason} -> 
 
890
                    ?hcrv("failed sending request", [{reason, Reason}]),
 
891
                    Error = {error, {send_failed, 
 
892
                                     httpc_response:error(Request, Reason)}},
 
893
                    {stop, Error, State#state{request = Request}}
784
894
            end;
785
895
 
786
 
        {error, Reason} ->          
787
 
            %% Commented out in wait of ssl support to avoid
788
 
            %% dialyzer warning
789
 
            %% case State#state.status of
790
 
            %%  new -> % Called from init/1
791
 
            self() ! {init_error, error_connecting, 
792
 
                      httpc_response:error(Request, Reason)},
793
 
            {ok, State#state{request = Request}}
794
 
            %%  ssl_tunnel -> % Not called from init/1
795
 
            %%    NewState = 
796
 
            %%  answer_request(Request, 
797
 
            %%                 httpc_response:error(Request, 
798
 
            %%                                      Reason),
799
 
            %%                 State),
800
 
            %%    {stop, normal, NewState}
801
 
            %%end
 
896
        {error, Reason} -> 
 
897
            ?hcri("connect failed", [{reason, Reason}]),
 
898
            Error = {error, {connect_failed, 
 
899
                             httpc_response:error(Request, Reason)}},
 
900
            {stop, Error, State#state{request = Request}}
802
901
    end.
803
902
 
 
903
 
 
904
handler_info(#state{request     = Request, 
 
905
                    session     = Session, 
 
906
                    status_line = _StatusLine, 
 
907
                    pipeline    = Pipeline, 
 
908
                    keep_alive  = KeepAlive, 
 
909
                    status      = Status,
 
910
                    canceled    = _Canceled, 
 
911
                    options     = _Options,
 
912
                    timers      = _Timers} = _State) ->
 
913
 
 
914
    ?hcrt("handler info", [{request,    Request},
 
915
                           {session,    Session}, 
 
916
                           {pipeline,   Pipeline}, 
 
917
                           {keep_alive, KeepAlive}, 
 
918
                           {status,     Status}]),
 
919
 
 
920
    %% Info about the current request
 
921
    RequestInfo = 
 
922
        case Request of
 
923
            undefined ->
 
924
                [];
 
925
            #request{id      = Id,
 
926
                     started = ReqStarted} ->
 
927
                [{id, Id}, {started, ReqStarted}]
 
928
        end,
 
929
 
 
930
    ?hcrt("handler info", [{request_info, RequestInfo}]),
 
931
 
 
932
    %% Info about the current session/socket
 
933
    SessionType = Session#tcp_session.type, 
 
934
    QueueLen    = case Session#tcp_session.type of
 
935
                      pipeline ->
 
936
                          queue:len(Pipeline);
 
937
                      keep_alive ->
 
938
                          queue:len(KeepAlive)
 
939
                  end,
 
940
    Socket      = Session#tcp_session.socket, 
 
941
    Scheme      = Session#tcp_session.scheme, 
 
942
    SocketType  = socket_type(Scheme),
 
943
 
 
944
    ?hcrt("handler info", [{session_type, SessionType}, 
 
945
                           {queue_length, QueueLen}, 
 
946
                           {scheme,       Scheme}, 
 
947
                           {socket_type,  SocketType}, 
 
948
                           {socket,       Socket}]),
 
949
 
 
950
    SocketOpts  = http_transport:getopts(SocketType, Socket), 
 
951
    SocketStats = http_transport:getstat(SocketType, Socket), 
 
952
 
 
953
    Remote = http_transport:peername(SocketType, Socket), 
 
954
    Local  = http_transport:sockname(SocketType, Socket), 
 
955
 
 
956
    ?hcrt("handler info", [{remote,       Remote}, 
 
957
                           {local,        Local}, 
 
958
                           {socket_opts,  SocketOpts}, 
 
959
                           {socket_stats, SocketStats}]),
 
960
 
 
961
    SocketInfo  = [{remote,       Remote}, 
 
962
                   {local,        Local}, 
 
963
                   {socket_opts,  SocketOpts},
 
964
                   {socket_stats, SocketStats}],
 
965
 
 
966
    SessionInfo = 
 
967
        [{type,         SessionType},
 
968
         {queue_length, QueueLen},
 
969
         {scheme,       Scheme}, 
 
970
         {socket_info,  SocketInfo}], 
 
971
                
 
972
    [{status,          Status}, 
 
973
     {current_request, RequestInfo},
 
974
     {session,         SessionInfo}].
 
975
 
 
976
 
 
977
 
804
978
handle_http_msg({Version, StatusCode, ReasonPharse, Headers, Body}, 
805
979
                State = #state{request = Request}) ->
806
 
    ?hcrt("handle_http_msg", [{body, Body}]),
 
980
    ?hcrt("handle_http_msg", [{headers, Headers}]),
807
981
    case Headers#http_response_h.'content-type' of
808
982
        "multipart/byteranges" ++ _Param ->
809
 
            exit(not_yet_implemented);
 
983
            exit({not_yet_implemented, multypart_byteranges});
810
984
        _ ->
811
 
            StatusLine = {Version, StatusCode, ReasonPharse}, 
 
985
            StatusLine       = {Version, StatusCode, ReasonPharse}, 
812
986
            {ok, NewRequest} = start_stream(StatusLine, Headers, Request), 
813
987
            handle_http_body(Body, 
814
988
                             State#state{request     = NewRequest,
815
989
                                         status_line = StatusLine, 
816
990
                                         headers     = Headers})
817
991
    end;
818
 
handle_http_msg({ChunkedHeaders, Body}, 
819
 
                State = #state{headers = Headers}) ->
820
 
    ?hcrt("handle_http_msg", [{chunked_headers, ChunkedHeaders}, {body, Body}]),
 
992
handle_http_msg({ChunkedHeaders, Body}, #state{headers = Headers} = State) ->
 
993
    ?hcrt("handle_http_msg", 
 
994
          [{chunked_headers, ChunkedHeaders}, {headers, Headers}]),
821
995
    NewHeaders = http_chunk:handle_headers(Headers, ChunkedHeaders),
822
996
    handle_response(State#state{headers = NewHeaders, body = Body});
823
 
handle_http_msg(Body, State = #state{status_line = {_,Code, _}}) ->
824
 
    ?hcrt("handle_http_msg", [{body, Body}, {code, Code}]),
825
 
    {NewBody, NewRequest}= stream(Body, State#state.request, Code),
 
997
handle_http_msg(Body, #state{status_line = {_,Code, _}} = State) ->
 
998
    ?hcrt("handle_http_msg", [{code, Code}]),
 
999
    {NewBody, NewRequest} = stream(Body, State#state.request, Code),
826
1000
    handle_response(State#state{body = NewBody, request = NewRequest}).
827
1001
 
828
1002
handle_http_body(<<>>, State = #state{status_line = {_,304, _}}) ->
837
1011
    ?hcrt("handle_http_body - head", []),
838
1012
    handle_response(State#state{body = <<>>});
839
1013
 
840
 
handle_http_body(Body, State = #state{headers = Headers, 
841
 
                                      max_body_size = MaxBodySize,
842
 
                                      status_line = {_,Code, _},
843
 
                                      request = Request}) ->
844
 
    ?hcrt("handle_http_body", [{body, Body}, {max_body_size, MaxBodySize}, {code, Code}]),
 
1014
handle_http_body(Body, #state{headers       = Headers, 
 
1015
                              max_body_size = MaxBodySize,
 
1016
                              status_line   = {_,Code, _},
 
1017
                              request       = Request} = State) ->
 
1018
    ?hcrt("handle_http_body", 
 
1019
          [{max_body_size, MaxBodySize}, {headers, Headers}, {code, Code}]),
845
1020
    TransferEnc = Headers#http_response_h.'transfer-encoding',
846
1021
    case case_insensitive_header(TransferEnc) of
847
1022
        "chunked" ->
850
1025
                                   State#state.max_header_size, 
851
1026
                                   {Code, Request}) of
852
1027
                {Module, Function, Args} ->
853
 
                    ?hcrt("handle_http_body - new mfa", [{module, Module}, {function, Function}, {args, Args}]),
 
1028
                    ?hcrt("handle_http_body - new mfa", 
 
1029
                          [{module,   Module}, 
 
1030
                           {function, Function}, 
 
1031
                           {args,     Args}]),
854
1032
                    NewState = next_body_chunk(State),
855
1033
                    {noreply, NewState#state{mfa = 
856
1034
                                             {Module, Function, Args}}};
857
1035
                {ok, {ChunkedHeaders, NewBody}} ->
858
 
                    ?hcrt("handle_http_body - nyew body", [{chunked_headers, ChunkedHeaders}, {new_body, NewBody}]),
 
1036
                    ?hcrt("handle_http_body - new body", 
 
1037
                          [{chunked_headers, ChunkedHeaders}, 
 
1038
                           {new_body,        NewBody}]),
859
1039
                    NewHeaders = http_chunk:handle_headers(Headers, 
860
1040
                                                           ChunkedHeaders),
861
1041
                    handle_response(State#state{headers = NewHeaders, 
872
1052
            ?hcrt("handle_http_body - other", []),
873
1053
            Length =
874
1054
                list_to_integer(Headers#http_response_h.'content-length'),
875
 
            case ((Length =< MaxBodySize) or (MaxBodySize == nolimit)) of
 
1055
            case ((Length =< MaxBodySize) orelse (MaxBodySize =:= nolimit)) of
876
1056
                true ->
877
1057
                    case httpc_response:whole_body(Body, Length) of
878
1058
                        {ok, Body} ->
879
 
                            {NewBody, NewRequest}= stream(Body, Request, Code),
880
 
                            handle_response(State#state{body = NewBody,
 
1059
                            {NewBody, NewRequest} = 
 
1060
                                stream(Body, Request, Code),
 
1061
                            handle_response(State#state{body    = NewBody,
881
1062
                                                        request = NewRequest});
882
1063
                        MFA ->
883
1064
                            NewState = next_body_chunk(State),   
893
1074
            end
894
1075
    end.
895
1076
 
896
 
%%% Normaly I do not comment out code, I throw it away. But this might
897
 
%%% actually be used on day if ssl is improved.
898
 
%% handle_response(State = #state{status = ssl_tunnel,
899
 
%%                             request = Request,
900
 
%%                             options = Options,
901
 
%%                             session = #tcp_session{socket = Socket,
902
 
%%                                                    scheme = Scheme},
903
 
%%                             status_line = {_, 200, _}}) ->
904
 
%%     %%% Insert code for upgrading the socket if and when ssl supports this.  
905
 
%%     Address = handle_proxy(Request#request.address, Options#options.proxy),   
906
 
%%     send_first_request(Address, Request, State);
907
 
%% handle_response(State = #state{status = ssl_tunnel,
908
 
%%                            request = Request}) ->
909
 
%%     NewState = answer_request(Request,
910
 
%%                            httpc_response:error(Request,
911
 
%%                                                 ssl_proxy_tunnel_failed),
912
 
%%                            State),
913
 
%%                     {stop, normal, NewState};
914
 
 
915
 
handle_response(State = #state{status = new}) ->
916
 
   handle_response(try_to_enable_pipeline_or_keep_alive(State));
917
 
 
918
 
handle_response(State = 
919
 
                #state{request      = Request,
 
1077
handle_response(#state{status = new} = State) ->
 
1078
    ?hcrd("handle response - status = new", []),
 
1079
    handle_response(try_to_enable_pipeline_or_keep_alive(State));
 
1080
 
 
1081
handle_response(#state{request      = Request,
920
1082
                       status       = Status,
921
1083
                       session      = Session, 
922
1084
                       status_line  = StatusLine,
923
1085
                       headers      = Headers, 
924
1086
                       body         = Body,
925
1087
                       options      = Options,
926
 
                       profile_name = ProfileName}) when Status =/= new ->
927
 
    ?hcrt("handle response", [{status, Status}, {session, Session}, {status_line, StatusLine}, {profile_name, ProfileName}]), 
 
1088
                       profile_name = ProfileName} = State) 
 
1089
  when Status =/= new ->
 
1090
    
 
1091
    ?hcrd("handle response", [{profile,     ProfileName},
 
1092
                              {status,      Status},
 
1093
                              {request,     Request},
 
1094
                              {session,     Session}, 
 
1095
                              {status_line, StatusLine}]),
 
1096
 
928
1097
    handle_cookies(Headers, Request, Options, ProfileName),
929
1098
    case httpc_response:result({StatusLine, Headers, Body}, Request) of
930
1099
        %% 100-continue
931
1100
        continue -> 
 
1101
            ?hcrd("handle response - continue", []),
932
1102
            %% Send request body
933
1103
            {_, RequestBody} = Request#request.content,
934
1104
            http_transport:send(socket_type(Session#tcp_session.scheme), 
935
1105
                                            Session#tcp_session.socket, 
936
1106
                                RequestBody),
937
1107
            %% Wait for next response
938
 
            http_transport:setopts(socket_type(Session#tcp_session.scheme), 
939
 
                                   Session#tcp_session.socket, 
940
 
                                   [{active, once}]),
 
1108
            activate_once(Session),
941
1109
            Relaxed = (Request#request.settings)#http_options.relaxed,
942
 
            {noreply, 
943
 
             State#state{mfa = {httpc_response, parse,
944
 
                                [State#state.max_header_size,
945
 
                                 Relaxed]},
946
 
                         status_line = undefined,
947
 
                         headers = undefined,
948
 
                         body = undefined
949
 
                        }};
 
1110
            MFA = {httpc_response, parse,
 
1111
                   [State#state.max_header_size, Relaxed]}, 
 
1112
            {noreply, State#state{mfa         = MFA,
 
1113
                                  status_line = undefined,
 
1114
                                  headers     = undefined,
 
1115
                                  body        = undefined}};
 
1116
 
950
1117
        %% Ignore unexpected 100-continue response and receive the
951
1118
        %% actual response that the server will send right away. 
952
1119
        {ignore, Data} -> 
 
1120
            ?hcrd("handle response - ignore", [{data, Data}]),
953
1121
            Relaxed = (Request#request.settings)#http_options.relaxed,
954
 
            NewState = State#state{mfa = 
955
 
                                   {httpc_response, parse,
956
 
                                    [State#state.max_header_size,
957
 
                                     Relaxed]},
 
1122
            MFA     = {httpc_response, parse,
 
1123
                       [State#state.max_header_size, Relaxed]}, 
 
1124
            NewState = State#state{mfa         = MFA, 
958
1125
                                   status_line = undefined,
959
 
                                   headers = undefined,
960
 
                                   body = undefined},
 
1126
                                   headers     = undefined,
 
1127
                                   body        = undefined},
961
1128
            handle_info({httpc_handler, dummy, Data}, NewState);
 
1129
 
962
1130
        %% On a redirect or retry the current request becomes 
963
1131
        %% obsolete and the manager will create a new request 
964
1132
        %% with the same id as the current.
965
1133
        {redirect, NewRequest, Data} ->
966
 
            ?hcrt("handle response - redirect", [{new_request, NewRequest}, {data, Data}]), 
 
1134
            ?hcrt("handle response - redirect", 
 
1135
                  [{new_request, NewRequest}, {data, Data}]), 
967
1136
            ok = httpc_manager:redirect_request(NewRequest, ProfileName),
968
1137
            handle_queue(State#state{request = undefined}, Data);
969
1138
        {retry, TimeNewRequest, Data} ->
970
 
            ?hcrt("handle response - retry", [{time_new_request, TimeNewRequest}, {data, Data}]), 
 
1139
            ?hcrt("handle response - retry", 
 
1140
                  [{time_new_request, TimeNewRequest}, {data, Data}]), 
971
1141
            ok = httpc_manager:retry_request(TimeNewRequest, ProfileName),
972
1142
            handle_queue(State#state{request = undefined}, Data);
973
1143
        {ok, Msg, Data} ->
974
 
            ?hcrt("handle response - result ok", [{msg, Msg}, {data, Data}]), 
 
1144
            ?hcrd("handle response - ok", []),
975
1145
            end_stream(StatusLine, Request),
976
1146
            NewState = answer_request(Request, Msg, State),
977
1147
            handle_queue(NewState, Data); 
978
1148
        {stop, Msg} ->
979
 
            ?hcrt("handle response - result stop", [{msg, Msg}]), 
 
1149
            ?hcrd("handle response - stop", [{msg, Msg}]),
980
1150
            end_stream(StatusLine, Request),
981
1151
            NewState = answer_request(Request, Msg, State),
982
1152
            {stop, normal, NewState}
990
1160
    ok;
991
1161
handle_cookies(Headers, Request, #options{cookies = enabled}, ProfileName) ->
992
1162
    {Host, _ } = Request#request.address,
993
 
    Cookies = http_cookie:cookies(Headers#http_response_h.other, 
 
1163
    Cookies = httpc_cookie:cookies(Headers#http_response_h.other, 
994
1164
                                  Request#request.path, Host),
995
1165
    httpc_manager:store_cookies(Cookies, Request#request.address,
996
1166
                                ProfileName).
997
1167
 
998
1168
%% This request could not be pipelined or used as sequential keept alive
999
1169
%% queue
1000
 
handle_queue(State = #state{status = close}, _) ->
 
1170
handle_queue(#state{status = close} = State, _) ->
1001
1171
    {stop, normal, State};
1002
1172
 
1003
 
handle_queue(State = #state{status = keep_alive}, Data) ->
 
1173
handle_queue(#state{status = keep_alive} = State, Data) ->
1004
1174
    handle_keep_alive_queue(State, Data);
1005
1175
 
1006
 
handle_queue(State = #state{status = pipeline}, Data) ->
 
1176
handle_queue(#state{status = pipeline} = State, Data) ->
1007
1177
    handle_pipeline(State, Data).
1008
1178
 
1009
 
handle_pipeline(State = 
1010
 
                #state{status = pipeline, session = Session,
 
1179
handle_pipeline(#state{status       = pipeline, 
 
1180
                       session      = Session,
1011
1181
                       profile_name = ProfileName,
1012
 
                       options = #options{pipeline_timeout = TimeOut}}, 
1013
 
                               Data) ->
 
1182
                       options      = #options{pipeline_timeout = TimeOut}} = 
 
1183
                State, 
 
1184
                Data) ->
 
1185
 
 
1186
    ?hcrd("handle pipeline", [{profile, ProfileName}, 
 
1187
                              {session, Session},
 
1188
                              {timeout, TimeOut}]),
 
1189
 
1014
1190
    case queue:out(State#state.pipeline) of
1015
1191
        {empty, _} ->
 
1192
            ?hcrd("epmty pipeline queue", []),
 
1193
            
1016
1194
            %% The server may choose too teminate an idle pipeline
1017
1195
            %% in this case we want to receive the close message
1018
1196
            %% at once and not when trying to pipeline the next
1019
1197
            %% request.
1020
 
            http_transport:setopts(socket_type(Session#tcp_session.scheme), 
1021
 
                                   Session#tcp_session.socket, 
1022
 
                                   [{active, once}]),
 
1198
            activate_once(Session), 
 
1199
 
1023
1200
            %% If a pipeline that has been idle for some time is not
1024
1201
            %% closed by the server, the client may want to close it.
1025
 
            NewState = activate_queue_timeout(TimeOut, State),
 
1202
            NewState   = activate_queue_timeout(TimeOut, State),
1026
1203
            NewSession = Session#tcp_session{queue_length = 0},
1027
1204
            httpc_manager:insert_session(NewSession, ProfileName),
1028
1205
            %% Note mfa will be initilized when a new request 
1029
1206
            %% arrives.
1030
1207
            {noreply, 
1031
 
             NewState#state{request = undefined, 
1032
 
                            mfa = undefined,
 
1208
             NewState#state{request     = undefined, 
 
1209
                            mfa         = undefined,
1033
1210
                            status_line = undefined,
1034
 
                            headers = undefined,
1035
 
                            body = undefined
1036
 
                           }
1037
 
            };
 
1211
                            headers     = undefined,
 
1212
                            body        = undefined}};
1038
1213
        {{value, NextRequest}, Pipeline} ->    
1039
1214
            case lists:member(NextRequest#request.id, 
1040
1215
                              State#state.canceled) of          
1041
1216
                true ->
 
1217
                    ?hcrv("next request had been cancelled", []),
1042
1218
                    %% See comment for handle_cast({cancel, RequestId})
1043
1219
                    {stop, normal, 
1044
1220
                     State#state{request = 
1045
1221
                                 NextRequest#request{from = answer_sent}}};
1046
1222
                false ->
 
1223
                    ?hcrv("next request", [{request, NextRequest}]),
1047
1224
                    NewSession = 
1048
1225
                        Session#tcp_session{queue_length =
1049
1226
                                            %% Queue + current
1051
1228
                    httpc_manager:insert_session(NewSession, ProfileName),
1052
1229
                    Relaxed = 
1053
1230
                        (NextRequest#request.settings)#http_options.relaxed,
 
1231
                    MFA = {httpc_response, 
 
1232
                           parse,
 
1233
                           [State#state.max_header_size, Relaxed]}, 
1054
1234
                    NewState = 
1055
 
                        State#state{pipeline = Pipeline,
1056
 
                                    request = NextRequest,
1057
 
                                    mfa = {httpc_response, parse,
1058
 
                                           [State#state.max_header_size,
1059
 
                                            Relaxed]},
 
1235
                        State#state{pipeline    = Pipeline,
 
1236
                                    request     = NextRequest,
 
1237
                                    mfa         = MFA,
1060
1238
                                    status_line = undefined,
1061
 
                                    headers = undefined,
1062
 
                                    body = undefined},
 
1239
                                    headers     = undefined,
 
1240
                                    body        = undefined},
1063
1241
                    case Data of
1064
1242
                        <<>> ->
1065
 
                            http_transport:setopts(
1066
 
                              socket_type(Session#tcp_session.scheme), 
1067
 
                              Session#tcp_session.socket, 
1068
 
                              [{active, once}]),
 
1243
                            activate_once(Session), 
1069
1244
                            {noreply, NewState};
1070
1245
                        _ ->
1071
1246
                            %% If we already received some bytes of
1076
1251
            end
1077
1252
    end.
1078
1253
 
1079
 
handle_keep_alive_queue(State = #state{status = keep_alive,
1080
 
                                       session = Session,
1081
 
                                       profile_name = ProfileName,
1082
 
                                       options = #options{keep_alive_timeout 
1083
 
                                                          = TimeOut}
1084
 
                                      }, 
1085
 
                        Data) ->
 
1254
handle_keep_alive_queue(
 
1255
  #state{status       = keep_alive,
 
1256
         session      = Session,
 
1257
         profile_name = ProfileName,
 
1258
         options      = #options{keep_alive_timeout = TimeOut}} = State, 
 
1259
  Data) ->
 
1260
 
 
1261
    ?hcrd("handle keep_alive", [{profile, ProfileName}, 
 
1262
                                {session, Session},
 
1263
                                {timeout, TimeOut}]),
 
1264
 
1086
1265
    case queue:out(State#state.keep_alive) of
1087
1266
        {empty, _} ->
 
1267
            ?hcrd("empty keep_alive queue", []),
1088
1268
            %% The server may choose too terminate an idle keep_alive session
1089
1269
            %% in this case we want to receive the close message
1090
1270
            %% at once and not when trying to send the next
1091
1271
            %% request.
1092
 
            http_transport:setopts(socket_type(Session#tcp_session.scheme), 
1093
 
                                   Session#tcp_session.socket, 
1094
 
                                   [{active, once}]),
 
1272
            activate_once(Session), 
1095
1273
            %% If a keep_alive session has been idle for some time is not
1096
1274
            %% closed by the server, the client may want to close it.
1097
1275
            NewState = activate_queue_timeout(TimeOut, State),
1111
1289
            case lists:member(NextRequest#request.id, 
1112
1290
                              State#state.canceled) of          
1113
1291
                true ->
1114
 
                    handle_keep_alive_queue(State#state{keep_alive = 
1115
 
                                                        KeepAlive}, Data);
 
1292
                    ?hcrv("next request has already been canceled", []),
 
1293
                    handle_keep_alive_queue(
 
1294
                      State#state{keep_alive = KeepAlive}, Data);
1116
1295
                false ->
 
1296
                    ?hcrv("next request", [{request, NextRequest}]),
1117
1297
                    Relaxed = 
1118
1298
                        (NextRequest#request.settings)#http_options.relaxed,
 
1299
                    MFA     = {httpc_response, parse, 
 
1300
                               [State#state.max_header_size, Relaxed]}, 
1119
1301
                    NewState =
1120
 
                        State#state{request = NextRequest,
1121
 
                                    keep_alive = KeepAlive,
1122
 
                                    mfa = {httpc_response, parse,
1123
 
                                           [State#state.max_header_size,
1124
 
                                            Relaxed]},
 
1302
                        State#state{request     = NextRequest,
 
1303
                                    keep_alive  = KeepAlive,
 
1304
                                    mfa         = MFA,
1125
1305
                                    status_line = undefined,
1126
 
                                    headers = undefined,
1127
 
                                    body = undefined},
 
1306
                                    headers     = undefined,
 
1307
                                    body        = undefined},
1128
1308
                    case Data of
1129
1309
                        <<>> ->
1130
 
                            http_transport:setopts(
1131
 
                              socket_type(Session#tcp_session.scheme), 
1132
 
                              Session#tcp_session.socket, [{active, once}]),
 
1310
                            activate_once(Session), 
1133
1311
                            {noreply, NewState};
1134
1312
                        _ ->
1135
1313
                            %% If we already received some bytes of
1140
1318
            end
1141
1319
    end.
1142
1320
 
1143
 
call(Msg, Pid, Timeout) ->
1144
 
    gen_server:call(Pid, Msg, Timeout).
1145
 
 
1146
 
cast(Msg, Pid) ->
1147
 
    gen_server:cast(Pid, Msg).
1148
1321
 
1149
1322
case_insensitive_header(Str) when is_list(Str) ->
1150
1323
    http_util:to_lower(Str);
1152
1325
case_insensitive_header(Str) ->
1153
1326
    Str.
1154
1327
 
1155
 
activate_request_timeout(State = #state{request = Request}) ->
1156
 
    Time = (Request#request.settings)#http_options.timeout,
1157
 
    case Time of
 
1328
activate_once(#tcp_session{scheme = Scheme, socket = Socket}) ->
 
1329
    SocketType = socket_type(Scheme),
 
1330
    http_transport:setopts(SocketType, Socket, [{active, once}]).
 
1331
 
 
1332
activate_request_timeout(
 
1333
  #state{request = #request{timer = undefined} = Request} = State) ->
 
1334
    Timeout = (Request#request.settings)#http_options.timeout,
 
1335
    case Timeout of
1158
1336
        infinity ->
1159
1337
            State;
1160
1338
        _ ->
1161
 
            Ref = erlang:send_after(Time, self(), 
1162
 
                                    {timeout, Request#request.id}),
1163
 
            State#state
1164
 
              {timers = 
1165
 
               #timers{request_timers = 
1166
 
                       [{Request#request.id, Ref}|
1167
 
                        (State#state.timers)#timers.request_timers]}}
1168
 
    end.
 
1339
            ReqId = Request#request.id, 
 
1340
            ?hcrt("activate request timer", 
 
1341
                  [{request_id,    ReqId}, 
 
1342
                   {time_consumed, t() - Request#request.started},
 
1343
                   {timeout,       Timeout}]),
 
1344
            Msg       = {timeout, ReqId}, 
 
1345
            Ref       = erlang:send_after(Timeout, self(), Msg), 
 
1346
            Request2  = Request#request{timer = Ref}, 
 
1347
            ReqTimers = [{Request#request.id, Ref} |
 
1348
                         (State#state.timers)#timers.request_timers],
 
1349
            Timers    = #timers{request_timers = ReqTimers}, 
 
1350
            State#state{request = Request2, timers = Timers}
 
1351
    end;
 
1352
 
 
1353
%% Timer is already running! This is the case for a redirect or retry
 
1354
activate_request_timeout(State) ->
 
1355
    State.
1169
1356
 
1170
1357
activate_queue_timeout(infinity, State) ->
1171
1358
    State;
1187
1374
is_keep_alive_enabled_server(_,_) ->
1188
1375
    false.
1189
1376
 
1190
 
is_keep_alive_connection(Headers, Session) ->
1191
 
    (not ((Session#tcp_session.client_close) or  
1192
 
          httpc_response:is_server_closing(Headers))).
 
1377
is_keep_alive_connection(Headers, #tcp_session{client_close = ClientClose}) ->
 
1378
    (not ((ClientClose) orelse httpc_response:is_server_closing(Headers))).
1193
1379
 
1194
 
try_to_enable_pipeline_or_keep_alive(State = 
1195
 
                                    #state{session = Session, 
1196
 
                                           request = #request{method = Method},
1197
 
                                           status_line = {Version, _, _},
1198
 
                                           headers = Headers,
1199
 
                                           profile_name = ProfileName}) ->
1200
 
    case (is_keep_alive_enabled_server(Version, Headers) andalso 
1201
 
          is_keep_alive_connection(Headers, Session)) of
 
1380
try_to_enable_pipeline_or_keep_alive(
 
1381
  #state{session      = Session, 
 
1382
         request      = #request{method = Method},
 
1383
         status_line  = {Version, _, _},
 
1384
         headers      = Headers,
 
1385
         profile_name = ProfileName} = State) ->
 
1386
    ?hcrd("try to enable pipeline or keep-alive", 
 
1387
          [{version, Version}, 
 
1388
           {headers, Headers}, 
 
1389
           {session, Session}]),
 
1390
    case is_keep_alive_enabled_server(Version, Headers) andalso 
 
1391
          is_keep_alive_connection(Headers, Session) of
1202
1392
        true ->
1203
1393
            case (is_pipeline_enabled_client(Session) andalso 
1204
1394
                  httpc_request:is_idempotent(Method)) of
1209
1399
                    httpc_manager:insert_session(Session, ProfileName),
1210
1400
                    %% Make sure type is keep_alive in session
1211
1401
                    %% as it in this case might be pipeline
1212
 
                    State#state{status = keep_alive,
1213
 
                                session = 
1214
 
                                Session#tcp_session{type = keep_alive}}
 
1402
                    NewSession = Session#tcp_session{type = keep_alive}, 
 
1403
                    State#state{status  = keep_alive,
 
1404
                                session = NewSession}
1215
1405
            end;
1216
1406
        false ->
1217
1407
            State#state{status = close}
1218
1408
    end.
1219
1409
 
1220
 
answer_request(Request, Msg, #state{timers = Timers} = State) ->    
 
1410
answer_request(Request, Msg, #state{timers = Timers} = State) -> 
 
1411
    ?hcrt("answer request", [{request, Request}]),
1221
1412
    httpc_response:send(Request#request.from, Msg),
1222
1413
    RequestTimers = Timers#timers.request_timers,
1223
1414
    TimerRef =
1253
1444
        case (catch httpc_manager:retry_request(Request, ProfileName)) of
1254
1445
            ok ->
1255
1446
                RequestTimers = Timers#timers.request_timers,
 
1447
                ReqId    = Request#request.id, 
1256
1448
                TimerRef =
1257
 
                    proplists:get_value(Request#request.id, RequestTimers, 
1258
 
                                         undefined),
1259
 
                cancel_timer(TimerRef, {timeout, Request#request.id}),
1260
 
                State#state{timers = Timers#timers{request_timers =
1261
 
                                          lists:delete({Request#request.id,
1262
 
                                                        TimerRef},
1263
 
                                                       RequestTimers)}};
 
1449
                    proplists:get_value(ReqId, RequestTimers, undefined),
 
1450
                cancel_timer(TimerRef, {timeout, ReqId}),
 
1451
                NewReqsTimers = lists:delete({ReqId, TimerRef}, RequestTimers),
 
1452
                NewTimers     = Timers#timers{request_timers = NewReqsTimers},
 
1453
                State#state{timers = NewTimers};
 
1454
 
1264
1455
            Error ->
1265
1456
                answer_request(Request#request.from,
1266
1457
                               httpc_response:error(Request, Error), State) 
1345
1536
socket_type(http) ->
1346
1537
    ip_comm;
1347
1538
socket_type(https) ->
1348
 
    {ssl, []}. %% Dummy value ok for ex setops that does not use this value
 
1539
    {ssl, []}. %% Dummy value ok for ex setopts that does not use this value
1349
1540
 
1350
 
start_stream({_Version, _Code, _ReasonPhrase}, _Headers, #request{stream = none} = Request) ->
 
1541
start_stream({_Version, _Code, _ReasonPhrase}, _Headers, 
 
1542
             #request{stream = none} = Request) ->
1351
1543
    ?hcrt("start stream - none", []), 
1352
1544
    {ok, Request};
1353
 
start_stream({_Version, Code, _ReasonPhrase}, Headers, #request{stream = self} = Request) 
 
1545
start_stream({_Version, Code, _ReasonPhrase}, Headers, 
 
1546
             #request{stream = self} = Request) 
1354
1547
  when (Code =:= 200) orelse (Code =:= 206) ->
1355
1548
    ?hcrt("start stream - self", [{code, Code}]), 
1356
1549
    Msg = httpc_response:stream_start(Headers, Request, ignore),
1363
1556
    Msg = httpc_response:stream_start(Headers, Request, self()),
1364
1557
    httpc_response:send(Request#request.from, Msg),
1365
1558
    {ok, Request};    
1366
 
start_stream({_Version, Code, _ReasonPhrase}, _Headers, #request{stream = Filename} = Request)
 
1559
start_stream({_Version, Code, _ReasonPhrase}, _Headers, 
 
1560
             #request{stream = Filename} = Request)
1367
1561
  when ((Code =:= 200) orelse (Code =:= 206)) andalso is_list(Filename) ->
1368
1562
    ?hcrt("start stream", [{code, Code}, {filename, Filename}]),
1369
1563
    case file:open(Filename, [write, raw, append, delayed_write]) of
1436
1630
handle_verbose(_) ->
1437
1631
    ok.    
1438
1632
 
 
1633
 
1439
1634
%%% Normaly I do not comment out code, I throw it away. But this might
1440
1635
%%% actually be used one day if ssl is improved.
1441
1636
%% send_ssl_tunnel_request(Address, Request = #request{address = {Host, Port}}, 
1497
1692
%% d(_, _, _) ->
1498
1693
%%     ok.
1499
1694
 
 
1695
 
 
1696
call(Msg, Pid) ->
 
1697
    Timeout = infinity,
 
1698
    call(Msg, Pid, Timeout).
 
1699
call(Msg, Pid, Timeout) ->
 
1700
    gen_server:call(Pid, Msg, Timeout).
 
1701
 
 
1702
cast(Msg, Pid) ->
 
1703
    gen_server:cast(Pid, Msg).
 
1704
 
 
1705
 
 
1706
%% to(To, Start) when is_integer(Start) andalso (Start >= 0) ->
 
1707
%%     http_util:timeout(To, Start);
 
1708
%% to(To, _Start) ->
 
1709
%%     http_util:timeout(To, t()).
 
1710
 
 
1711
t() ->
 
1712
    http_util:timestamp().