File 0913-inets-httpd-now-ignores-invalid-headers-as-reported-.patch of Package erlang

From c06db0bedf49a9b40725745e73fa82e562612815 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 22 Nov 2019 10:12:21 +0100
Subject: [PATCH] inets: httpd now ignores invalid headers as reported by
 ERL-1053

That is it is not allowed to have space between the HTTP header filed
name and the colon in the header.
---
 lib/inets/src/http_lib/http_request.erl     |  9 ++++++++-
 lib/inets/src/http_server/httpd_example.erl | 13 +++++++++++--
 lib/inets/src/http_server/httpd_request.erl |  2 +-
 lib/inets/test/httpd_SUITE.erl              | 20 ++++++++++++++++++++
 4 files changed, 40 insertions(+), 4 deletions(-)

diff --git a/lib/inets/src/http_lib/http_request.erl b/lib/inets/src/http_lib/http_request.erl
index 2b1a0bd40f..c49402cc1f 100644
--- a/lib/inets/src/http_lib/http_request.erl
+++ b/lib/inets/src/http_lib/http_request.erl
@@ -28,7 +28,14 @@
 key_value(KeyValueStr) ->
     case lists:splitwith(fun($:) -> false; (_) -> true end, KeyValueStr) of
 	{Key, [$: | Value]} when Key =/= [] ->
-	    {http_util:to_lower(string:strip(Key)),  string:strip(Value)};
+            %% RFC 7230 - 3.2.4 ... No whitespace is allowed between the header field-name and colon. 
+            case string:strip(Key, right) of
+                Key ->
+                    {http_util:to_lower(string:strip(Key, left)),  string:strip(Value)};
+                 _ ->
+                    %% Ignore invalid header
+                    undefined
+            end;
 	{_, []} -> 
 	    undefined;
         _ ->
diff --git a/lib/inets/src/http_server/httpd_example.erl b/lib/inets/src/http_server/httpd_example.erl
index aaa7e428c2..3c25ca336f 100644
--- a/lib/inets/src/http_server/httpd_example.erl
+++ b/lib/inets/src/http_server/httpd_example.erl
@@ -22,7 +22,7 @@
 -export([print/1]).
 -export([get/2, put/2, post/2, yahoo/2, test1/2, get_bin/2, peer/2,new_status_and_location/2]).
 
--export([newformat/3, post_chunked/3, post_204/3]).
+-export([newformat/3, post_chunked/3, post_204/3, ignore_invalid_header/3]).
 %% These are used by the inets test-suite
 -export([delay/1, chunk_timeout/3, get_chunks/3]).
 
@@ -156,7 +156,16 @@ post_204(SessionID, _Env, _Input) ->
                     ["Status: 204 No Content" ++ "\r\n\r\n"]),
     mod_esi:deliver(SessionID, []).
 
-
+ignore_invalid_header(SessionID, Env, _Input) ->
+    case proplists:get_value(content_length, Env, undefined) of
+        undefined ->
+            mod_esi:deliver(SessionID,
+                            ["Status: 204 No Content" ++ "\r\n\r\n"]);
+        _ -> %% Invalid content_length header should have been ignored
+            mod_esi:deliver(SessionID,
+                            ["Status: 500 Internal Server Error" ++ "\r\n\r\n"])
+    end.            
+                         
 newformat(SessionID,_,_) ->
     mod_esi:deliver(SessionID, "Content-Type:text/html\r\n\r\n"),
     mod_esi:deliver(SessionID, top("new esi format test")),
diff --git a/lib/inets/src/http_server/httpd_request.erl b/lib/inets/src/http_server/httpd_request.erl
index 79566e3ac8..3df55c0f7a 100644
--- a/lib/inets/src/http_server/httpd_request.erl
+++ b/lib/inets/src/http_server/httpd_request.erl
@@ -207,7 +207,7 @@ parse_headers(<<?CR,?LF,?CR,?LF,Body/binary>>, Header, Headers, _, _,
 	      Options, Result) ->
     Customize = proplists:get_value(customize, Options),
     case http_request:key_value(lists:reverse(Header)) of
-	undefined -> %% Skip headers with missing :
+	undefined -> %% Skip invalid headers
 	    FinalHeaders = lists:filtermap(fun(H) ->
 						   httpd_custom:customize_headers(Customize, request_header, H)
 					   end,
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index 1d80d604b7..1289432f0d 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -168,6 +168,7 @@ http_get() ->
      missing_CR,
      max_header,
      max_content_length,
+     ignore_invalid_header,
      ipv6
     ].
 
@@ -1361,6 +1362,25 @@ max_content_length(Config) when is_list(Config) ->
     garbage_content_length(proplists:get_value(type, Config), proplists:get_value(port, Config), Host, 
 			   proplists:get_value(node, Config), Version).
 
+%%-------------------------------------------------------------------------
+ignore_invalid_header() ->
+    ["RFC 7230 - 3.2.4 ... No whitespace is allowed between the header field-name and colon"].
+ignore_invalid_header(Config) when is_list(Config) ->
+     Host =  proplists:get_value(host, Config),
+     Port =  proplists:get_value(port, Config),
+    {Url, Header, Opts} =
+        case proplists:get_value(type, Config) of
+            ip_comm ->
+                {"http://"  ++ Host ++  ":" ++ integer_to_list(Port) ++ "/cgi-bin/erl/httpd_example:ignore_invalid_header",
+                 [{"Host", "localhost"},{"Te", ""}, {"Content-Length ", "0"}], []};
+            ssl ->
+                Conf = proplists:get_value(client_config, proplists:get_value(ssl_conf, Config)),
+                {"https://"  ++ Host ++  ":" ++ integer_to_list(Port) ++ "/cgi-bin/erl/httpd_example:ignore_invalid_header",
+                 [{"Host", "localhost"},{"Te", ""}, {"Content-Length ", "0"}], [{ssl, Conf}]}
+        end,
+    {ok,{{_,204,_}, _, _}}
+        = httpc:request(get, {Url, Header}, [{timeout, 45000} | Opts], [{headers_as_is, true}]).
+
 %%-------------------------------------------------------------------------
 security_1_1(Config) when is_list(Config) -> 
     security([{http_version, "HTTP/1.1"} | Config]).
-- 
2.16.4

openSUSE Build Service is sponsored by