File 0432-inets-Robust-handling-of-204-304-1xx-responses.patch of Package erlang

From 0dceb1347440c8ff5ec0f572d2fd6bee782374a2 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?P=C3=A9ter=20Dimitrov?= <peterdmv@erlang.org>
Date: Thu, 23 Aug 2018 14:37:30 +0200
Subject: [PATCH 1/2] inets: Robust handling of 204, 304, 1xx responses

All 1xx (informational), 204 (no content), and 304 (not modified)
responses MUST NOT include a message-body, and thus are always
terminated by the first empty line after the header fields.
This implies that chunked encoding MUST NOT be used for these
status codes.

This commit updates the client to gracefully handle responses from
faulty server implementations that can send chunked encoded 204,
304 or 1xx responses.

Change-Id: I2dd502e28b3c6e121640083118fa5c3e479f5194
---
 lib/inets/src/http_client/httpc_handler.erl | 18 +++++++---
 lib/inets/test/httpc_SUITE.erl              | 56 ++++++++++++++++++++++++++++-
 2 files changed, 69 insertions(+), 5 deletions(-)

diff --git a/lib/inets/src/http_client/httpc_handler.erl b/lib/inets/src/http_client/httpc_handler.erl
index 26e4f4e699..1a2ce277bf 100644
--- a/lib/inets/src/http_client/httpc_handler.erl
+++ b/lib/inets/src/http_client/httpc_handler.erl
@@ -980,13 +980,23 @@ handle_http_body(_, #state{status = {ssl_tunnel, Request},
     NewState     = answer_request(Request, ClientErrMsg, State),
     {stop, normal, NewState};
 
-handle_http_body(<<>>, #state{status_line = {_,304, _}} = State) ->
+%% All 1xx (informational), 204 (no content), and 304 (not modified)
+%% responses MUST NOT include a message-body, and thus are always
+%% terminated by the first empty line after the header fields.
+%% This implies that chunked encoding MUST NOT be used for these
+%% status codes.
+handle_http_body(<<>>, #state{headers = Headers,
+                              status_line = {_,StatusCode, _}} = State)
+  when Headers#http_response_h.'transfer-encoding' =/= "chunked" andalso
+       (StatusCode =:= 204 orelse                       %% No Content
+        StatusCode =:= 304 orelse                       %% Not Modified
+        100 =< StatusCode andalso StatusCode =< 199) -> %% Informational
     handle_response(State#state{body = <<>>});
 
-handle_http_body(<<>>, #state{status_line = {_,204, _}} = State) ->
-    handle_response(State#state{body = <<>>});
 
-handle_http_body(<<>>, #state{request = #request{method = head}} = State) ->
+handle_http_body(<<>>, #state{headers = Headers,
+                              request = #request{method = head}} = State)
+  when Headers#http_response_h.'transfer-encoding' =/= "chunked" ->
     handle_response(State#state{body = <<>>});
 
 handle_http_body(Body, #state{headers       = Headers, 
diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl
index d723fd0460..f3898e1b74 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -135,7 +135,8 @@ misc() ->
     [
      server_does_not_exist,
      timeout_memory_leak,
-     wait_for_whole_response
+     wait_for_whole_response,
+     post_204_chunked
     ].
 
 %%--------------------------------------------------------------------
@@ -1177,6 +1178,59 @@ wait_for_whole_response(Config) when is_list(Config) ->
      RespSeqNumServer ! shutdown,
      ReqSeqNumServer ! shutdown.
 
+%%--------------------------------------------------------------------
+post_204_chunked() ->
+    [{doc,"Test that chunked encoded 204 responses do not freeze the http client"}].
+post_204_chunked(_Config) ->
+    Msg = "HTTP/1.1 204 No Content\r\n" ++
+        "Date: Thu, 23 Aug 2018 13:36:29 GMT\r\n" ++
+        "Content-Type: text/html\r\n" ++
+        "Server: inets/6.5.2.3\r\n" ++
+        "Cache-Control: no-cache\r\n" ++
+        "Pragma: no-cache\r\n" ++
+        "Expires: Fri, 24 Aug 2018 07:49:35 GMT\r\n" ++
+        "Transfer-Encoding: chunked\r\n" ++
+        "\r\n",
+    Chunk = "0\r\n\r\n",
+
+    {ok, ListenSocket} = gen_tcp:listen(0, [{active,once}, binary]),
+    {ok,{_,Port}} = inet:sockname(ListenSocket),
+    spawn(fun () -> custom_server(Msg, Chunk, ListenSocket) end),
+
+    {ok,Host} = inet:gethostname(),
+    End = "/cgi-bin/erl/httpd_example:post_204",
+    URL = ?URL_START ++ Host ++ ":" ++ integer_to_list(Port) ++ End,
+    {ok, _} = httpc:request(post, {URL, [], "text/html", []}, [], []),
+    timer:sleep(500),
+    %% Second request times out in the faulty case.
+    {ok, _} = httpc:request(post, {URL, [], "text/html", []}, [], []).
+
+custom_server(Msg, Chunk, ListenSocket) ->
+    {ok, Accept} = gen_tcp:accept(ListenSocket),
+    receive_packet(),
+    send_response(Msg, Chunk, Accept),
+    custom_server_loop(Msg, Chunk, Accept).
+
+custom_server_loop(Msg, Chunk, Accept) ->
+    receive_packet(),
+    send_response(Msg, Chunk, Accept),
+    custom_server_loop(Msg, Chunk, Accept).
+
+send_response(Msg, Chunk, Socket) ->
+    inet:setopts(Socket, [{active, once}]),
+    gen_tcp:send(Socket, Msg),
+    timer:sleep(250),
+    gen_tcp:send(Socket, Chunk).
+
+receive_packet() ->
+    receive
+        {tcp, _, Msg} ->
+            ct:log("Message received: ~p", [Msg])
+    after
+        1000 ->
+            ct:fail("Timeout: did not recive packet")
+    end.
+
 %%--------------------------------------------------------------------
 %% Internal Functions ------------------------------------------------
 %%--------------------------------------------------------------------
-- 
2.16.4

openSUSE Build Service is sponsored by