File 2931-Change-Reserved-to-unmodified-HTTP-header-field.patch of Package erlang

From e7cd437733489a882f0e7f278a1a854bee7b6e6b Mon Sep 17 00:00:00 2001
From: Matyas Markovics <matyas@scrapinghub.com>
Date: Sun, 24 Nov 2019 13:44:48 +0100
Subject: [PATCH 1/4] Change Reserved to unmodified HTTP header-field

Propagate unmodified header fields in the previously Reserved and
undefined 4th element of the http_header tuple.

*Why do we need this new feature?*

While Section 4.2 of RFC 2616 for HTTP/1.1 states
that Field names are case-insensitive, some non-compliant
web services may rely on peculiar casing of Field names.
Such web-services cannot be accessed through a Proxy-server,
that is implemented in Erlang/OTP, certainly not over HTTPS.

Despite the RFC, even the IANA lists a number of permanently
registered headers in all-caps or mixed-cased format,
e.g.: ALPN, HTTP2-Settings, WWW-Authenticate, etc.
This leads to confusion and to service implementations,
that only accept headers formatted the same way.
A production issue was experienced using the common, drafted,
but not yet standard header: DNT.

There are a number of HTTP servers implemented in Erlang
that could be used in a Proxy implementation. However,
there is none that would respect header-casing.
* cowboy, httpd - their header parser lower-cases the fields
* yaws - emulators' internal HTTP header parsing via ssl/inet
* mochiweb, elli - both use erlang:decode_packet/3

As a side note: An HTTPS-Proxy requires CONNECT method support.
Therefor cowboy is not a real option despite its popularity.

With this proposal yaws, mochiweb and elli could all be patched
to respect casing of header fields and propagate the original
header format to the application level modules.
The DNT header issue was experienced using a patched mochiweb.

*Risks or uncertain artifacts?*

These changes are minimalistic and backward compatible,
given application developers respected the documentation.
All above mentioned http servers do so, they ignore the 4th
element of http_header tuple. It was verified in the master
branches of the project repositories.

*How did you solve it?*

The proposal is that packet_parser.c should also propagate
unmodified fields to both inet_drv.c and erl_bif_port.c,
where these would be put in the 4th place of the http_header
tuple. Its recognised, that this element was Reserved
for future and/or internal use. Hopefully you'd agree, that
sending the original header fields is a productive use-case
to free up the reservation.

Adding a new httph_cs option, cs for case-sensitive, was also
considered. I got the impression thought, that these these
packet decoders exit for compatibility reasons only and
the OTP-Team is not keen on adding new options.
---
 erts/emulator/beam/erl_bif_port.c          | 14 ++++++---
 erts/emulator/beam/packet_parser.c         |  4 ++-
 erts/emulator/beam/packet_parser.h         |  6 ++--
 erts/emulator/drivers/common/inet_drv.c    | 12 ++++---
 erts/emulator/test/decode_packet_SUITE.erl | 50 +++++++++++++++---------------
 erts/preloaded/src/erlang.erl              |  2 +-
 lib/ssl/test/ssl_packet_SUITE.erl          | 12 +++----
 7 files changed, 55 insertions(+), 45 deletions(-)

diff --git a/erts/emulator/beam/erl_bif_port.c b/erts/emulator/beam/erl_bif_port.c
index 17e09f835b..cf633b2f01 100644
--- a/erts/emulator/beam/erl_bif_port.c
+++ b/erts/emulator/beam/erl_bif_port.c
@@ -1228,22 +1228,25 @@ static int http_request_erl(void* arg, const http_atom_t* meth,
 }
 
 static int
-http_header_erl(void* arg, const http_atom_t* name, const char* name_ptr,
-                int name_len, const char* value_ptr, int value_len)
+http_header_erl(void* arg, const http_atom_t* name,
+		const char* name_ptr, int name_len,
+		const char* oname_ptr, int oname_len,
+		const char* value_ptr, int value_len)
 {
     struct packet_callback_args* pca = (struct packet_callback_args*) arg;    
-    Eterm bit_term, name_term, val_term;
+    Eterm bit_term, name_term, oname_term, val_term;
     Uint sz = 6;
     Eterm* hp;
 #ifdef DEBUG
     Eterm* hend;
 #endif
     
-    /* {http_header,Bit,Name,IValue,Value} */
+    /* {http_header,Bit,Name,Oname,Value} */
 
     if (name == NULL) {
 	http_bld_string(pca, NULL, &sz, name_ptr, name_len);
     }
+    http_bld_string(pca, NULL, &sz, oname_ptr, oname_len);
     http_bld_string(pca, NULL, &sz, value_ptr, value_len);
 
     hp = HAlloc(pca->p, sz);
@@ -1260,8 +1263,9 @@ http_header_erl(void* arg, const http_atom_t* name, const char* name_ptr,
 	name_term = http_bld_string(pca, &hp,NULL,name_ptr,name_len);
     }
 
+    oname_term = http_bld_string(pca, &hp, NULL, oname_ptr, oname_len);
     val_term = http_bld_string(pca, &hp, NULL, value_ptr, value_len);
-    pca->res = TUPLE5(hp, am_http_header, bit_term, name_term, am_undefined, val_term);
+    pca->res = TUPLE5(hp, am_http_header, bit_term, name_term, oname_term, val_term);
     ASSERT(hp+6==hend);
     return 1;
 }   
diff --git a/erts/emulator/beam/packet_parser.c b/erts/emulator/beam/packet_parser.c
index c0937aa5f2..8f24725326 100644
--- a/erts/emulator/beam/packet_parser.c
+++ b/erts/emulator/beam/packet_parser.c
@@ -834,7 +834,9 @@ int packet_parse_http(const char* buf, int len, int* statep,
         while (n && SP(ptr)) {
             ptr++; n--;
         }
-        return pcb->http_header(arg, name, name_ptr, name_len,
+        return pcb->http_header(arg, name,
+                                name_ptr, name_len,
+                                buf, name_len,
                                 ptr, n);
     }
     return -1;
diff --git a/erts/emulator/beam/packet_parser.h b/erts/emulator/beam/packet_parser.h
index 358d650804..b05623efec 100644
--- a/erts/emulator/beam/packet_parser.h
+++ b/erts/emulator/beam/packet_parser.h
@@ -77,8 +77,10 @@ typedef int HttpResponseMessageFn(void* arg, int major, int minor, int status,
 typedef int HttpRequestMessageFn(void* arg, const http_atom_t* meth, const char* meth_ptr,
 				 int meth_len, const PacketHttpURI*, int major, int minor);
 typedef int HttpEohMessageFn(void *arg);
-typedef int HttpHeaderMessageFn(void* arg, const http_atom_t* name, const char* name_ptr,
-				int name_len, const char* value_ptr, int value_len);
+typedef int HttpHeaderMessageFn(void* arg, const http_atom_t* name,
+				const char* name_ptr, int name_len,
+				const char* oname_ptr, int oname_len,
+				const char* value_ptr, int value_len);
 typedef int HttpErrorMessageFn(void* arg, const char* buf, int len);
 typedef int SslTlsFn(void* arg, unsigned type, unsigned major, unsigned minor,
                      const char* data, int len, const char* prefix, int plen);
diff --git a/erts/emulator/drivers/common/inet_drv.c b/erts/emulator/drivers/common/inet_drv.c
index 66ff8d8450..b2ddba39ce 100644
--- a/erts/emulator/drivers/common/inet_drv.c
+++ b/erts/emulator/drivers/common/inet_drv.c
@@ -2574,8 +2574,10 @@ http_request_inetdrv(void* arg, const http_atom_t* meth, const char* meth_ptr,
 }
 
 static int
-http_header_inetdrv(void* arg, const http_atom_t* name, const char* name_ptr,
-		    int name_len, const char* value_ptr, int value_len)
+http_header_inetdrv(void* arg, const http_atom_t* name,
+		    const char* name_ptr, int name_len,
+		    const char* oname_ptr, int oname_len,
+		    const char* value_ptr, int value_len)
 {
     tcp_descriptor* desc = (tcp_descriptor*) arg;
     int i = 0;
@@ -2583,7 +2585,7 @@ http_header_inetdrv(void* arg, const http_atom_t* name, const char* name_ptr,
     ErlDrvTermData caller = ERL_DRV_NIL;
     
     if (desc->inet.active == INET_PASSIVE) {
-        /* {inet_async,S,Ref,{ok,{http_header,Bit,Name,IValue,Value}} */
+        /* {inet_async,S,Ref,{ok,{http_header,Bit,Name,Oname,Value}} */
         int req;
         int aid;
         
@@ -2596,7 +2598,7 @@ http_header_inetdrv(void* arg, const http_atom_t* name, const char* name_ptr,
         i = LOAD_ATOM(spec, i,  am_ok);
     }
     else {
-        /* {http, S, {http_header,Bit,Name,IValue,Value}} */
+        /* {http, S, {http_header,Bit,Name,Oname,Value}} */
         i = LOAD_ATOM(spec, i, am_http);
         i = LOAD_PORT(spec, i, desc->inet.dport);
     }
@@ -2610,7 +2612,7 @@ http_header_inetdrv(void* arg, const http_atom_t* name, const char* name_ptr,
       i = LOAD_INT(spec, i,  0);
       i = http_load_string(desc, spec, i, name_ptr, name_len);
     }
-    i = LOAD_ATOM(spec, i, am_undefined);
+    i = http_load_string(desc, spec, i, oname_ptr, oname_len);
     i = http_load_string(desc, spec, i, value_ptr, value_len);
     i = LOAD_TUPLE(spec, i, 5);
 
diff --git a/erts/emulator/test/decode_packet_SUITE.erl b/erts/emulator/test/decode_packet_SUITE.erl
index d0f46167e4..e5ee02cfba 100644
--- a/erts/emulator/test/decode_packet_SUITE.erl
+++ b/erts/emulator/test/decode_packet_SUITE.erl
@@ -301,8 +301,8 @@ http(Config) when is_list(Config) ->
                    StrA = list_to_atom(Str),
                    StrB = list_to_binary(Str),
                    Bin = <<StrB/binary,": ",ValB/binary,"\r\n",Rest/binary>>,
-                   {ok, {http_header,N,StrA,undefined,Val}, Rest} = decode_pkt(httph,Bin),
-                   {ok, {http_header,N,StrA,undefined,ValB}, Rest} = decode_pkt(httph_bin,Bin),
+                   {ok, {http_header,N,StrA,Str,Val}, Rest} = decode_pkt(httph,Bin),
+                   {ok, {http_header,N,StrA,StrB,ValB}, Rest} = decode_pkt(httph_bin,Bin),
                    N + 1
            end,
     lists:foldl(HdrF, 1, http_hdr_strings()),
@@ -373,28 +373,28 @@ http_request(Msg) ->
             {http_request, 'POST', {abs_path,  "/invalid/url"  }, {1,1}},
             {http_request, 'POST', {abs_path,<<"/invalid/url">>}, {1,1}}},
            {"Connection: close\r\n",
-            {http_header,2,'Connection',undefined,  "close"},
-            {http_header,2,'Connection',undefined,<<"close">>}},	 
+            {http_header,2,'Connection',  "Connection"  ,  "close"},
+            {http_header,2,'Connection',<<"Connection">>,<<"close">>}},
            {"User-Agent: perl post\r\n",
-            {http_header,24,'User-Agent',undefined,  "perl post"},
-            {http_header,24,'User-Agent',undefined,<<"perl post">>}},
+            {http_header,24,'User-Agent',  "User-Agent"  ,  "perl post"},
+            {http_header,24,'User-Agent',<<"User-Agent">>,<<"perl post">>}},
            {"Content-Length: 4\r\n",
-            {http_header,38,'Content-Length',undefined,  "4"},
-            {http_header,38,'Content-Length',undefined,<<"4">>}},
+            {http_header,38,'Content-Length',  "Content-Length"  ,  "4"},
+            {http_header,38,'Content-Length',<<"Content-Length">>,<<"4">>}},
            {"Content-Type: text/xml; charset=utf-8\r\n",
-            {http_header,42,'Content-Type',undefined,  "text/xml; charset=utf-8"},
-            {http_header,42,'Content-Type',undefined,<<"text/xml; charset=utf-8">>}},
+            {http_header,42,'Content-Type',  "Content-Type"  ,  "text/xml; charset=utf-8"},
+            {http_header,42,'Content-Type',<<"Content-Type">>,<<"text/xml; charset=utf-8">>}},
            {"Other-Field: with some text\r\n",
-            {http_header,0,  "Other-Field"  ,undefined,  "with some text"},
-            {http_header,0,<<"Other-Field">>,undefined,<<"with some text">>}},
+            {http_header,0,  "Other-Field"  ,  "Other-Field"  ,  "with some text"},
+            {http_header,0,<<"Other-Field">>,<<"Other-Field">>,<<"with some text">>}},
            {"Make-sure-a-LONG-HEaDer-fIeLd-is-fORMATTED-NicelY: with some text\r\n",
-            {http_header,0,  "Make-Sure-A-Long-Header-Field-Is-Formatted-Nicely"  ,undefined,  "with some text"},
-            {http_header,0,<<"Make-Sure-A-Long-Header-Field-Is-Formatted-Nicely">>,undefined,<<"with some text">>}},
+            {http_header,0,  "Make-Sure-A-Long-Header-Field-Is-Formatted-Nicely"  ,  "Make-sure-a-LONG-HEaDer-fIeLd-is-fORMATTED-NicelY"  ,  "with some text"},
+            {http_header,0,<<"Make-Sure-A-Long-Header-Field-Is-Formatted-Nicely">>,<<"Make-sure-a-LONG-HEaDer-fIeLd-is-fORMATTED-NicelY">>,<<"with some text">>}},
            {"Multi-Line: Once upon a time in a land far far away,\r\n"
             " there lived a princess imprisoned in the highest tower\r\n"
             " of the most haunted castle.\r\n",
-            {http_header,0,  "Multi-Line"  ,undefined,  "Once upon a time in a land far far away,\r\n there lived a princess imprisoned in the highest tower\r\n of the most haunted castle."},
-            {http_header,0,<<"Multi-Line">>,undefined,<<"Once upon a time in a land far far away,\r\n there lived a princess imprisoned in the highest tower\r\n of the most haunted castle.">>}},
+            {http_header,0,  "Multi-Line"  ,  "Multi-Line"  ,  "Once upon a time in a land far far away,\r\n there lived a princess imprisoned in the highest tower\r\n of the most haunted castle."},
+            {http_header,0,<<"Multi-Line">>,<<"Multi-Line">>,<<"Once upon a time in a land far far away,\r\n there lived a princess imprisoned in the highest tower\r\n of the most haunted castle.">>}},
            {"\r\n",
             http_eoh,
             http_eoh}],
@@ -410,17 +410,17 @@ http_response(Msg) ->
             {http_response, {1,0}, 404,   "Object Not Found"},
             {http_response, {1,0}, 404, <<"Object Not Found">>}},
            {"Server: inets/4.7.16\r\n",
-            {http_header, 30, 'Server', undefined,   "inets/4.7.16"},
-            {http_header, 30, 'Server', undefined, <<"inets/4.7.16">>}},
+            {http_header, 30, 'Server',   "Server"  ,   "inets/4.7.16"},
+            {http_header, 30, 'Server', <<"Server">>, <<"inets/4.7.16">>}},
            {"Date: Fri, 04 Jul 2008 17:16:22 GMT\r\n",
-            {http_header, 3, 'Date', undefined,   "Fri, 04 Jul 2008 17:16:22 GMT"},
-            {http_header, 3, 'Date', undefined, <<"Fri, 04 Jul 2008 17:16:22 GMT">>}},
+            {http_header, 3, 'Date',   "Date"  ,   "Fri, 04 Jul 2008 17:16:22 GMT"},
+            {http_header, 3, 'Date', <<"Date">>, <<"Fri, 04 Jul 2008 17:16:22 GMT">>}},
            {"Content-Type: text/html\r\n",
-            {http_header, 42, 'Content-Type', undefined,   "text/html"},
-            {http_header, 42, 'Content-Type', undefined, <<"text/html">>}},
+            {http_header, 42, 'Content-Type',   "Content-Type"  ,   "text/html"},
+            {http_header, 42, 'Content-Type', <<"Content-Type">>, <<"text/html">>}},
            {"Content-Length: 207\r\n",
-            {http_header, 38, 'Content-Length', undefined,   "207"},
-            {http_header, 38, 'Content-Length', undefined, <<"207">>}},
+            {http_header, 38, 'Content-Length',   "Content-Length"  ,   "207"},
+            {http_header, 38, 'Content-Length', <<"Content-Length">>, <<"207">>}},
            {"\r\n",
             http_eoh,
             http_eoh}],
@@ -548,7 +548,7 @@ otp_8536_do(N) ->
     Bin = <<Hdr/binary, ": ", Data/binary, "\r\n\r\n">>,
 
     io:format("Bin='~p'\n",[Bin]),
-    {ok,{http_header,0,Hdr2,undefined,Data2},<<"\r\n">>} = decode_pkt(httph_bin, Bin,  []),
+    {ok,{http_header,0,Hdr2,Hdr2,Data2},<<"\r\n">>} = decode_pkt(httph_bin, Bin,  []),
 
     %% Do something to trash the C-stack, how about another decode_packet:
     decode_pkt(httph_bin,<<Letters/binary, ": ", Data/binary, "\r\n\r\n">>, []),
diff --git a/erts/preloaded/src/erlang.erl b/erts/preloaded/src/erlang.erl
index 869982c262..15cd6ecbf4 100644
--- a/erts/preloaded/src/erlang.erl
+++ b/erts/preloaded/src/erlang.erl
@@ -630,7 +630,7 @@ date() ->
       HttpHeader :: {'http_header',
                      integer(),
                      HttpField,
-                     Reserved :: term(),
+                     Reserved :: HttpString,
                      Value :: HttpString},
       HttpError :: {'http_error', HttpString},
       HttpMethod :: 'OPTIONS' | 'GET' | 'HEAD' | 'POST' | 'PUT' | 'DELETE'
diff --git a/lib/ssl/test/ssl_packet_SUITE.erl b/lib/ssl/test/ssl_packet_SUITE.erl
index b79a51f02a..03e77dd863 100644
--- a/lib/ssl/test/ssl_packet_SUITE.erl
+++ b/lib/ssl/test/ssl_packet_SUITE.erl
@@ -1130,7 +1130,7 @@ server_send_trailer(Socket, Trailer)->
 client_http_decode_trailer_active(Socket) ->
     receive
 	{ssl, Socket,
-	 {http_header,36,'Content-Encoding',undefined,"gzip"}} ->
+	 {http_header,36,'Content-Encoding',"Content-Encoding","gzip"}} ->
 	    ok;
 	Other1 ->
 	    exit({?LINE, Other1})
@@ -1180,7 +1180,7 @@ packet_httph_bin_active(Config) when is_list(Config) ->
 client_http_decode_trailer_bin_active(Socket) ->
     receive
 	{ssl, Socket,
-	 {http_header,36,'Content-Encoding',undefined, <<"gzip">>}} ->
+	 {http_header,36,'Content-Encoding',<<"Content-Encoding">>, <<"gzip">>}} ->
 	    ok;
 	Other1 ->
 	    exit({?LINE, Other1})
@@ -1232,7 +1232,7 @@ client_http_decode_trailer_active_once(Socket) ->
     ssl:setopts(Socket, [{active, once}]),
     receive
 	{ssl, Socket,
-	 {http_header,36,'Content-Encoding',undefined,"gzip"}} ->
+	 {http_header,36,'Content-Encoding',"Content-Encoding","gzip"}} ->
 	    ok;
 	Other1 ->
 	    exit({?LINE, Other1})
@@ -1284,7 +1284,7 @@ client_http_decode_trailer_bin_active_once(Socket) ->
     ssl:setopts(Socket, [{active, once}]),
     receive
 	{ssl, Socket,
-	 {http_header,36,'Content-Encoding',undefined, <<"gzip">>}} ->
+	 {http_header,36,'Content-Encoding',<<"Content-Encoding">>, <<"gzip">>}} ->
 	    ok;
 	Other1 ->
 	    exit({?LINE, Other1})
@@ -1335,7 +1335,7 @@ packet_httph_passive(Config) when is_list(Config) ->
     ssl_test_lib:close(Client).
 
 client_http_decode_trailer_passive(Socket) ->
-    {ok,{http_header,36,'Content-Encoding',undefined,"gzip"}} = ssl:recv(Socket, 0),
+    {ok,{http_header,36,'Content-Encoding',"Content-Encoding","gzip"}} = ssl:recv(Socket, 0),
     {ok, http_eoh} = ssl:recv(Socket, 0),
     ok.
 
@@ -1375,7 +1375,7 @@ packet_httph_bin_passive(Config) when is_list(Config) ->
     ssl_test_lib:close(Client).
 
 client_http_decode_trailer_bin_passive(Socket) ->
-    {ok,{http_header,36,'Content-Encoding',undefined,<<"gzip">>}} = ssl:recv(Socket, 0),
+    {ok,{http_header,36,'Content-Encoding',<<"Content-Encoding">>,<<"gzip">>}} = ssl:recv(Socket, 0),
     {ok, http_eoh} = ssl:recv(Socket, 0),
     ok.
 
-- 
2.16.4

openSUSE Build Service is sponsored by