File 0155-Fix-httpc-timeout-for-redirects.patch of Package erlang

From fb4c7f27d050a167335a4274327cf1f8d8cc9aba Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Johannes=20Wei=C3=9Fl?= <jargon@molb.org>
Date: Sun, 14 May 2017 23:35:37 +0200
Subject: [PATCH] Fix httpc timeout for redirects

Probably since 6153ba7 (OTP R13B04) the httpc timeout setting does not
work for redirects (when autoredirect is true). With this patch a new
timer is started for the new (redirected) requests. This means that a
simple redirected request could return after 2*timeout milliseconds.

This is the first part to fix https://bugs.erlang.org/browse/ERL-420
---
 lib/inets/src/http_client/httpc_handler.erl | 16 ++++++++++------
 lib/inets/test/httpc_SUITE.erl              | 19 +++++++++++++++++++
 2 files changed, 29 insertions(+), 6 deletions(-)

diff --git a/lib/inets/src/http_client/httpc_handler.erl b/lib/inets/src/http_client/httpc_handler.erl
index c99200777..89c17a867 100644
--- a/lib/inets/src/http_client/httpc_handler.erl
+++ b/lib/inets/src/http_client/httpc_handler.erl
@@ -1224,7 +1224,7 @@ close_socket(#session{socket = Socket, socket_type = SocketType}) ->
     http_transport:close(SocketType, Socket).
 
 activate_request_timeout(
-  #state{request = #request{timer = undefined} = Request} = State) ->
+  #state{request = #request{timer = OldRef} = Request} = State) ->
     Timeout = (Request#request.settings)#http_options.timeout,
     case Timeout of
 	infinity ->
@@ -1232,17 +1232,21 @@ activate_request_timeout(
 	_ ->
 	    ReqId = Request#request.id, 
 	    Msg       = {timeout, ReqId}, 
+	    case OldRef of
+		undefined ->
+		    ok;
+		_ ->
+		    %% Timer is already running! This is the case for a redirect or retry
+		    %% We need to restart the timer because the handler pid has changed
+		    cancel_timer(OldRef, Msg)
+	    end,
 	    Ref       = erlang:send_after(Timeout, self(), Msg), 
 	    Request2  = Request#request{timer = Ref}, 
 	    ReqTimers = [{Request#request.id, Ref} |
 			 (State#state.timers)#timers.request_timers],
 	    Timers    = #timers{request_timers = ReqTimers}, 
 	    State#state{request = Request2, timers = Timers}
-    end;
-
-%% Timer is already running! This is the case for a redirect or retry
-activate_request_timeout(State) ->
-    State.
+    end.
 
 activate_queue_timeout(infinity, State) ->
     State;
diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl
index fc7f01245..e6dcd2285 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -108,6 +108,7 @@ only_simulated() ->
      tolerate_missing_CR,
      userinfo,
      bad_response,
+     timeout_redirect,
      internal_server_error,
      invalid_http,
      invalid_chunk_size,
@@ -785,6 +786,14 @@ bad_response(Config) when is_list(Config) ->
     ct:print("Wrong Statusline: ~p~n", [Reason]).
 %%-------------------------------------------------------------------------
 
+timeout_redirect() ->
+    [{doc, "Test that timeout works for redirects, check ERL-420."}].
+timeout_redirect(Config) when is_list(Config) ->
+    URL = url(group_name(Config), "/redirect_to_missing_crlf.html", Config),
+    {error, timeout} = httpc:request(get, {URL, []}, [{timeout, 400}], []).
+
+%%-------------------------------------------------------------------------
+
 internal_server_error(doc) ->
     ["Test 50X codes"];
 internal_server_error(Config) when is_list(Config) ->
@@ -1915,6 +1924,16 @@ handle_uri(_,"/missing_crlf.html",_,_,_,_) ->
 	"Content-Length:32\r\n" ++
 	"<HTML><BODY>foobar</BODY></HTML>";
 
+handle_uri(_,"/redirect_to_missing_crlf.html",Port,_,Socket,_) ->
+    NewUri = url_start(Socket) ++
+	integer_to_list(Port) ++ "/missing_crlf.html",
+    Body = "<HTML><BODY><a href=" ++ NewUri ++
+	">New place</a></BODY></HTML>",
+    "HTTP/1.1 303 See Other \r\n" ++
+	"Location:" ++ NewUri ++  "\r\n" ++
+	"Content-Length:" ++ integer_to_list(length(Body))
+	++ "\r\n\r\n" ++ Body;
+
 handle_uri(_,"/wrong_statusline.html",_,_,_,_) ->
     "ok 200 HTTP/1.1\r\n\r\n" ++
 	"Content-Length:32\r\n\r\n" ++
-- 
2.13.0

openSUSE Build Service is sponsored by