File 3402-inets-remove-support-of-http-0.9-for-httpd.patch of Package erlang

From 485d9efcead14efc2c7c3cec4844d6574d495dda Mon Sep 17 00:00:00 2001
From: Ao Song <andy@erlang.org>
Date: Thu, 30 Jul 2020 10:02:47 +0200
Subject: [PATCH] inets: remove support of http 0.9 for httpd

Change-Id: I1c495613545fbf09569e3687770cb8fbf6455512
---
 lib/inets/doc/src/httpd.xml                   |  2 +-
 lib/inets/src/http_server/httpd_request.erl   | 29 +++++------
 .../src/http_server/httpd_request_handler.erl | 20 ++++---
 lib/inets/src/http_server/httpd_response.erl  |  7 +--
 lib/inets/src/http_server/mod_get.erl         |  2 +-
 lib/inets/test/http_format_SUITE.erl          | 13 ++---
 lib/inets/test/httpc_proxy_SUITE.erl          | 15 ++----
 lib/inets/test/httpd_SUITE.erl                | 52 ++++---------------
 lib/inets/test/httpd_basic_SUITE.erl          | 46 +++++++++-------
 lib/inets/test/httpd_mod_SUITE.erl            |  3 +-
 10 files changed, 78 insertions(+), 111 deletions(-)

diff --git a/lib/inets/doc/src/httpd.xml b/lib/inets/doc/src/httpd.xml
index 7d82463d12..0f84bb98d7 100644
--- a/lib/inets/doc/src/httpd.xml
+++ b/lib/inets/doc/src/httpd.xml
@@ -1029,7 +1029,7 @@ Transport: TLS
       </item>
       <tag><c>http_version</c></tag>
       <item><p>The <c>HTTP</c> version of the
-       request, that is, "HTTP/0.9", "HTTP/1.0", or "HTTP/1.1".</p>
+       request, that is, "HTTP/1.0", or "HTTP/1.1".</p>
       </item>
       <tag><c>request_line</c></tag>
       <item><p>The <c>Request-Line</c> as
diff --git a/lib/inets/src/http_server/httpd_request.erl b/lib/inets/src/http_server/httpd_request.erl
index 958b122255..d9b63ece35 100644
--- a/lib/inets/src/http_server/httpd_request.erl
+++ b/lib/inets/src/http_server/httpd_request.erl
@@ -29,7 +29,8 @@
 	 whole_body/2, 
 	 validate/3, 
 	 update_mod_data/5,
-	 body_data/2
+	 body_data/2,
+	 default_version/0
 	]).
 
 %% Callback API - used for example if the header/body is received a
@@ -91,10 +92,6 @@ body_data(Headers, Body) ->
 %%------------------------------------------------------------------------- 
 validate("HEAD", Uri, "HTTP/1." ++ _N) ->
     validate_uri(Uri);
-validate("GET", Uri, []) -> %% Simple HTTP/0.9 
-    validate_uri(Uri);
-validate("GET", Uri, "HTTP/0.9") ->
-    validate_uri(Uri);
 validate("GET", Uri, "HTTP/1." ++ _N) ->
     validate_uri(Uri);
 validate("PUT", Uri, "HTTP/1." ++ _N) ->
@@ -146,23 +143,22 @@ parse_method(_, _, _, Max, _, _) ->
     %% We do not know the version of the client as it comes after the
     %% method send the lowest version in the response so that the client
     %% will be able to handle it.
-    {error, {size_error, Max, 413, "Method unreasonably long"}, lowest_version()}.
+    {error, {size_error, Max, 413, "Method unreasonably long"}, default_version()}.
 
-parse_uri(_, _, Current, MaxURI, _, _) 
+parse_uri(_, _, Current, MaxURI, _, _)
   when (Current > MaxURI) andalso (MaxURI =/= nolimit) -> 
     %% We do not know the version of the client as it comes after the
     %% uri send the lowest version in the response so that the client
     %% will be able to handle it.
-    {error, {size_error, MaxURI, 414, "URI unreasonably long"},lowest_version()};
+    {error, {size_error, MaxURI, 414, "URI unreasonably long"}, default_version()};
 parse_uri(<<>>, URI, Current, Max, Options, Result) ->
     {?MODULE, parse_uri, [URI, Current, Max, Options, Result]};
 parse_uri(<<?SP, Rest/binary>>, URI, _, _, Options, Result) -> 
     parse_version(Rest, [], 0, proplists:get_value(max_version, Options), Options, 
 		  [string:strip(lists:reverse(URI)) | Result]);
 %% Can happen if it is a simple HTTP/0.9 request e.i "GET /\r\n\r\n"
-parse_uri(<<?CR, _Rest/binary>> = Data, URI, _, _, Options, Result) ->
-    parse_version(Data, [], 0, proplists:get_value(max_version, Options), Options, 
-		  [string:strip(lists:reverse(URI)) | Result]);
+parse_uri(<<?CR, _Rest/binary>>, _, _, _, _, _) ->
+    {error, {version_error, 505, "HTTP Version not supported"}, default_version()};
 parse_uri(<<Octet, Rest/binary>>, URI, Current, Max, Options, Result) ->
     parse_uri(Rest, [Octet | URI], Current + 1, Max, Options, Result).
 
@@ -179,7 +175,7 @@ parse_version(<<?CR>> = Data, Version, Current, Max, Options, Result) ->
 parse_version(<<Octet, Rest/binary>>, Version, Current, Max, Options, Result)  when Current =< Max ->
     parse_version(Rest, [Octet | Version], Current + 1, Max, Options, Result);
 parse_version(_, _, _, Max,_,_) ->
-    {error, {size_error, Max, 413, "Version string unreasonably long"}, lowest_version()}.
+    {error, {size_error, Max, 413, "Version string unreasonably long"}, default_version()}.
 
 parse_headers(_, _, _, Current, Max, _, Result) 
   when Max =/= nolimit andalso Current > Max -> 
@@ -351,10 +347,9 @@ validate_version("HTTP/1.1") ->
     true;
 validate_version("HTTP/1.0") ->
     true;
-validate_version("HTTP/0.9") ->
-    true;
 validate_version(_) ->
     false.
+
 %%----------------------------------------------------------------------
 %% There are 3 possible forms of the request URI 
 %%
@@ -429,8 +424,10 @@ get_persistens(HTTPVersion,ParsedHeader,ConfigDB)->
 	    false
     end.
 
-lowest_version()->    
-    "HTTP/0.9".
+%% rfc2145, an HTTP server SHOULD send a response version equal to the highest
+%% version for which the server is at least conditionally compliant
+default_version()->
+    "HTTP/1.1".
 
 check_header({"content-length", Value}, Maxsizes) ->
     Max = proplists:get_value(max_content_length, Maxsizes),
diff --git a/lib/inets/src/http_server/httpd_request_handler.erl b/lib/inets/src/http_server/httpd_request_handler.erl
index 9c5544ff10..0e99e5d098 100644
--- a/lib/inets/src/http_server/httpd_request_handler.erl
+++ b/lib/inets/src/http_server/httpd_request_handler.erl
@@ -233,12 +233,18 @@ handle_info({Proto, Socket, Data},
 	{error, {size_error, MaxSize, ErrCode, ErrStr}, Version} ->
 	    NewModData =  ModData#mod{http_version = Version},
 	    httpd_response:send_status(NewModData, ErrCode, ErrStr, {max_size, MaxSize}),
-	    {stop, normal, State#state{response_sent = true, 
+	    {stop, normal, State#state{response_sent = true,
 				       mod = NewModData}};
-        
-        {http_chunk = Module, Function, Args} when ChunkState =/= undefined ->
-            NewState = handle_chunk(Module, Function, Args, State),
-            {noreply, NewState};
+
+    {error, {version_error, ErrCode, ErrStr}, Version} ->
+        NewModData =  ModData#mod{http_version = Version},
+	    httpd_response:send_status(NewModData, ErrCode, ErrStr),
+	    {stop, normal, State#state{response_sent = true,
+				                   mod = NewModData}};
+
+    {http_chunk = Module, Function, Args} when ChunkState =/= undefined ->
+        NewState = handle_chunk(Module, Function, Args, State),
+        {noreply, NewState};
 	NewMFA ->
         setopts(Socket, SockType, [{active, once}]),
 	    case NewDataSize of
@@ -422,7 +428,9 @@ handle_http_msg({Method, Uri, Version, {RecordHeaders, Headers}, Body},
 				       400, URI, {malformed_syntax, URI}),
 	    {stop, normal, State#state{response_sent = true}};
 	{error, {bad_version, Ver}} ->
-	    httpd_response:send_status(ModData#mod{http_version = "HTTP/0.9"}, 400, Ver, {malformed_syntax, Ver}),
+	    httpd_response:send_status(
+            ModData#mod{http_version = httpd_request:default_version()},
+            400, Ver, {malformed_syntax, Ver}),
 	    {stop, normal, State#state{response_sent = true}}
     end;
 handle_http_msg(Body, State) ->
diff --git a/lib/inets/src/http_server/httpd_response.erl b/lib/inets/src/http_server/httpd_response.erl
index abbce5ac76..1066176e71 100644
--- a/lib/inets/src/http_server/httpd_response.erl
+++ b/lib/inets/src/http_server/httpd_response.erl
@@ -175,9 +175,6 @@ send_header(#mod{socket_type  = Type,
     Headers = create_header(ConfigDb, 
 			    lists:map(fun transform/1, KeyValueTupleHeaders)),
     NewVer = case {Ver, StatusCode} of
-		 {[], _} ->
-		     %% May be implicit!
-		     "HTTP/0.9";
 		 {unknown, 408} ->
 		     %% This will probably never happen! It means the
 		     %% server has timed out the request without
@@ -185,9 +182,9 @@ send_header(#mod{socket_type  = Type,
 		     %% lowest version so to ensure that the client
 		     %% will be able to handle it, probably the
 		     %% sensible thing to do!
-		     "HTTP/0.9";
+		     httpd_request:default_version();
 		 {undefined,_} ->
-		     "HTTP/1.0"; %% See rfc2145 2.3 last paragraph
+		     httpd_request:default_version(); %% See rfc2145 2.3 last paragraph
 		 _ ->
 		     Ver
 	     end,
diff --git a/lib/inets/src/http_server/mod_get.erl b/lib/inets/src/http_server/mod_get.erl
index 49e196ac07..706d868036 100644
--- a/lib/inets/src/http_server/mod_get.erl
+++ b/lib/inets/src/http_server/mod_get.erl
@@ -81,7 +81,7 @@ send_response(_Socket, _SocketType, Path, Info)->
 			       {content_length, Size}|LastModified];
 			  %% OTP-4935
 			 _ ->
-			     %% i.e http/1.0 and http/0.9
+			     %% i.e http/1.0
 			      [{content_type, MimeType},
 			       {content_length, Size}|LastModified]
 			  end,
diff --git a/lib/inets/test/http_format_SUITE.erl b/lib/inets/test/http_format_SUITE.erl
index 6492325701..2f5dc93c53 100644
--- a/lib/inets/test/http_format_SUITE.erl
+++ b/lib/inets/test/http_format_SUITE.erl
@@ -453,17 +453,14 @@ validate_request_line() ->
      " and protocol version."}].
 validate_request_line(Config) when is_list(Config) ->
 
-    %% HTTP/0.9 only has GET requests
-    {ok, "http://www.erlang/org"} = 
+    %% HTTP/0.9 not supported
+    {error, {bad_version, "HTTP/0.9"}} = 
 	httpd_request:validate("GET", "http://www.erlang/org", "HTTP/0.9"),
-    {error, {not_supported, 
-	     {"HEAD", "http://www.erlang/org", "HTTP/0.9"}}} =
+    {error, {bad_version, "HTTP/0.9"}} =
 	httpd_request:validate("HEAD", "http://www.erlang/org", "HTTP/0.9"),
-    {error, {not_supported, 
-	     {"TRACE", "http://www.erlang/org", "HTTP/0.9"}}} =
+    {error, {bad_version, "HTTP/0.9"}} =
 	httpd_request:validate("TRACE", "http://www.erlang/org", "HTTP/0.9"),
-    {error, {not_supported, 
-	     {"POST", "http://www.erlang/org", "HTTP/0.9"}}} =
+    {error, {bad_version, "HTTP/0.9"}} =
 	httpd_request:validate("POST", "http://www.erlang/org", "HTTP/0.9"),
 
     %% HTTP/1.* 
diff --git a/lib/inets/test/httpc_proxy_SUITE.erl b/lib/inets/test/httpc_proxy_SUITE.erl
index 3ee7981660..c6e110b0cc 100644
--- a/lib/inets/test/httpc_proxy_SUITE.erl
+++ b/lib/inets/test/httpc_proxy_SUITE.erl
@@ -377,26 +377,21 @@ http_stream(RequestId, Body) ->
 %%--------------------------------------------------------------------
 
 http_emulate_lower_versions(doc) ->
-    ["Perform requests as 0.9 and 1.0 clients."];
+    ["Perform requests as 1.0 and 1.1 clients."];
 http_emulate_lower_versions(Config) when is_list(Config) ->
     Method = get,
     URL = url("/index.html", Config),
     Request = {URL,[]},
     Opts = [],
 
-    HttpOpts1 = [{version,"HTTP/0.9"}],
-    {ok,[_|_]=B1} =
-	httpc:request(Method, Request, HttpOpts1, Opts),
-    inets_test_lib:check_body(B1),
-
-    HttpOpts2 = [{version,"HTTP/1.0"}],
+    HttpOpts1 = [{version,"HTTP/1.0"}],
     {ok,{{_,200,_},[_|_],[_|_]=B2}} =
-	httpc:request(Method, Request, HttpOpts2, Opts),
+	httpc:request(Method, Request, HttpOpts1, Opts),
     inets_test_lib:check_body(B2),
 
-    HttpOpts3 = [{version,"HTTP/1.1"}],
+    HttpOpts2 = [{version,"HTTP/1.1"}],
     {ok,{{_,200,_},[_|_],[_|_]=B3}} =
-	httpc:request(Method, Request, HttpOpts3, Opts),
+	httpc:request(Method, Request, HttpOpts2, Opts),
     inets_test_lib:check_body(B3),
 
     ok.
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index a745e2685d..be83aa2f81 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -110,22 +110,17 @@ groups() ->
      {reload, [], [non_disturbing_reconfiger_dies,
 		   disturbing_reconfiger_dies,
 		   non_disturbing_1_1, 
-		   non_disturbing_1_0, 
-		   non_disturbing_0_9,
-                   disturbing_1_1,
-                   disturbing_1_0, 
-                   disturbing_0_9,
+		   non_disturbing_1_0,
+           disturbing_1_1,
+           disturbing_1_0,
 		   reload_config_file
 		  ]},
      {post, [], [chunked_post, chunked_chunked_encoded_post, post_204]},
-     {basic_auth, [], [basic_auth_1_1, basic_auth_1_0, basic_auth_0_9, verify_href_1_1]},
-     {auth_api, [], [auth_api_1_1, auth_api_1_0, auth_api_0_9
-		    ]},
-     {auth_api_dets, [], [auth_api_1_1, auth_api_1_0, auth_api_0_9
-			 ]},
-     {auth_api_mnesia, [], [auth_api_1_1, auth_api_1_0, auth_api_0_9
-			   ]},
-     {security, [], [security_1_1, security_1_0]}, %% Skip 0.9 as causes timing issus in test code
+     {basic_auth, [], [basic_auth_1_1, basic_auth_1_0, verify_href_1_1]},
+     {auth_api, [], [auth_api_1_1, auth_api_1_0]},
+     {auth_api_dets, [], [auth_api_1_1, auth_api_1_0]},
+     {auth_api_mnesia, [], [auth_api_1_1, auth_api_1_0]},
+     {security, [], [security_1_1, security_1_0]},
      {logging, [], [disk_log_internal, disk_log_exists,
              disk_log_bad_size, disk_log_bad_file]},
      {http_1_1, [],
@@ -139,15 +134,13 @@ groups() ->
        esi_put, esi_patch, esi_post, esi_proagate, esi_atom_leak, esi_headers, cgi_bin_env]
       ++ http_head() ++ http_get() ++ load()},
      {http_1_0, [], [cgi_bin_env, host, cgi, trace] ++ http_head() ++ http_get() ++ load()},
-     {http_0_9, [], http_head() ++ http_get() ++ load()},
      {http_rel_path_script_alias, [], [cgi]},
      {not_sup, [], [put_not_sup]}
     ].
 
 basic_groups ()->
     [{group, http_1_1},
-     {group, http_1_0},
-     {group, http_0_9}
+     {group, http_1_0}
     ].
 
 http_head() ->
@@ -248,13 +241,6 @@ init_per_group(http_1_1, Config) ->
     [{http_version, "HTTP/1.1"} | Config];
 init_per_group(http_1_0, Config) ->
     [{http_version, "HTTP/1.0"} | Config];
-init_per_group(http_0_9, Config) ->
-    case {os:type(), os:version()} of
-	{{win32, _}, {5,1,2600}} ->
-	    {skip, "eaddrinuse XP problem"};
-	_ ->
-	    [{http_version, "HTTP/0.9"} | Config]
-    end;
 init_per_group(auth_api, Config) -> 
     [{auth_prefix, ""} | Config];
 init_per_group(auth_api_dets, Config) -> 
@@ -480,9 +466,6 @@ basic_auth_1_1(Config) when is_list(Config) ->
 basic_auth_1_0(Config) when is_list(Config) -> 
     basic_auth([{http_version, "HTTP/1.0"} | Config]).
 
-basic_auth_0_9(Config) when is_list(Config) -> 
-    basic_auth([{http_version, "HTTP/0.9"} | Config]).
-
 basic_auth() ->
     [{doc, "Test Basic authentication with WWW-Authenticate header"}].
 
@@ -521,9 +504,6 @@ auth_api_1_1(Config) when is_list(Config) ->
 auth_api_1_0(Config) when is_list(Config) -> 
     auth_api([{http_version, "HTTP/1.0"} | Config]).
 
-auth_api_0_9(Config) when is_list(Config) -> 
-    auth_api([{http_version, "HTTP/0.9"} | Config]).
-
 auth_api() ->
     [{doc, "Test mod_auth API"}].
 
@@ -1035,12 +1015,6 @@ alias_1_0() ->
 alias_1_0(Config) when is_list(Config) ->
     alias([{http_version, "HTTP/1.0"} | Config]).
 
-alias_0_9() ->
-    [{doc, "Test mod_alias"}].
-  
-alias_0_9(Config) when is_list(Config) ->
-    alias([{http_version, "HTTP/0.9"} | Config]).
-
 alias() ->
     [{doc, "Test mod_alias"}].
 
@@ -1467,9 +1441,6 @@ disturbing_1_1(Config) when is_list(Config) ->
 disturbing_1_0(Config) when is_list(Config) -> 
     disturbing([{http_version, "HTTP/1.0"} | Config]).
 
-disturbing_0_9(Config) when is_list(Config) -> 
-    disturbing([{http_version, "HTTP/0.9"} | Config]).
-
 disturbing(Config) when is_list(Config)->
     Server =  proplists:get_value(server_pid, Config),
     Version = proplists:get_value(http_version, Config),
@@ -1500,9 +1471,6 @@ non_disturbing_1_1(Config) when is_list(Config) ->
 non_disturbing_1_0(Config) when is_list(Config) -> 
     non_disturbing([{http_version, "HTTP/1.0"} | Config]).
 
-non_disturbing_0_9(Config) when is_list(Config) -> 
-    non_disturbing([{http_version, "HTTP/0.9"} | Config]).
-
 non_disturbing(Config) when is_list(Config)->
     Server =  proplists:get_value(server_pid, Config),
     Version = proplists:get_value(http_version, Config),
diff --git a/lib/inets/test/httpd_basic_SUITE.erl b/lib/inets/test/httpd_basic_SUITE.erl
index 1d3be6de57..041882aece 100644
--- a/lib/inets/test/httpd_basic_SUITE.erl
+++ b/lib/inets/test/httpd_basic_SUITE.erl
@@ -37,6 +37,7 @@ all() ->
     [uri_too_long_414, 
      header_too_long_413,
      entity_too_long,
+     http_0_9_not_supported,
      erl_script_nocache_opt,
      script_nocache,
      escaped_url_in_error_body,
@@ -163,14 +164,10 @@ uri_too_long_414(Config) when is_list(Config) ->
     ok = httpd_test_lib:verify_request(ip_comm, Address, Port, node(), 
  				       "GET /morethantenchars "
  				       "HTTP/1.1\r\n\r\n",
- 				       [{statuscode, 414},
-					%% Server will send lowest version
-					%% as it will not get to the 
-					%% client version
-					%% before aborting
- 				        {version, "HTTP/0.9"}]),    
+ 				       [{statuscode, 414},                            
+       			        {version, "HTTP/1.1"}]),
     inets:stop(httpd, Pid).
-    
+
 %%-------------------------------------------------------------------------
 header_too_long_413() ->
     [{doc,"Test that too long headers's get 413 HTTP code"}].
@@ -188,7 +185,24 @@ header_too_long_413(Config) when is_list(Config) ->
  				       [{statuscode, 413},
  				        {version, "HTTP/1.1"}]),
     inets:stop(httpd, Pid).
-   
+
+%%-------------------------------------------------------------------------
+
+http_0_9_not_supported() ->
+    [{doc, "Test that HTTP 0.9 is not supported"}].
+http_0_9_not_supported(Config) when is_list(Config) ->
+    HttpdConf =   proplists:get_value(httpd_conf, Config),
+    {ok, Pid} = inets:start(httpd, HttpdConf),
+    Info = httpd:info(Pid),
+    Port = proplists:get_value(port, Info),
+    Address = proplists:get_value(bind_address, Info),
+
+    ok = httpd_test_lib:verify_request(ip_comm, Address, Port, node(),
+     				       "GET /\r\n\r\n",
+     				       [{statuscode, 505},
+     				        {version, "HTTP/1.1"}]),
+    inets:stop(httpd, Pid).
+
 %%-------------------------------------------------------------------------
 
 entity_too_long() ->
@@ -205,22 +219,14 @@ entity_too_long(Config) when is_list(Config) ->
      				       "GET / " ++
 					   lists:duplicate(5, $A) ++ "\r\n\r\n",
      				       [{statuscode, 400},
-     					%% Server will send lowest version
-    					%% as it will not get to the 
-     					%% client version
-     					%% before aborting
-     				        {version, "HTTP/0.9"}]),
-    
+     				        {version, "HTTP/1.1"}]),
+
     %% Too long
     ok = httpd_test_lib:verify_request(ip_comm, Address, Port, node(), 
  				       "GET / " ++
 					   lists:duplicate(100, $A) ++ "\r\n\r\n",
  				       [{statuscode, 413},
-					%% Server will send lowest version
-					%% as it will not get to the 
-					%% client version
-					%% before aborting
- 				        {version, "HTTP/0.9"}]),
+ 				        {version, "HTTP/1.1"}]),
     %% Not so long but wrong
     ok = httpd_test_lib:verify_request(ip_comm, Address, Port, node(), 
 				       lists:duplicate(5, $A) ++ " / "
@@ -240,7 +246,7 @@ entity_too_long(Config) when is_list(Config) ->
 					%% as it will not get to the 
 					%% client version
 					%% before aborting
- 				        {version, "HTTP/0.9"}]),   
+ 				        {version, "HTTP/1.1"}]),   
     inets:stop(httpd, Pid).
     
 %%-------------------------------------------------------------------------
diff --git a/lib/inets/test/httpd_mod_SUITE.erl b/lib/inets/test/httpd_mod_SUITE.erl
index ebef7eea6c..87153323bd 100644
--- a/lib/inets/test/httpd_mod_SUITE.erl
+++ b/lib/inets/test/httpd_mod_SUITE.erl
@@ -45,10 +45,9 @@ all() ->
 groups() ->
     [
      {http, [], all_version_groups()},
-     {https, [], all_version_groups()}
+     {https, [], all_version_groups()},
      {http_1_1, [], []},
      {http_1_0, [], []},
-     {http_0_9, [], []},
      {mod_alias, [], []},
      {mod_actions, [], []},
      {mod_security, [], []},
-- 
2.26.2

openSUSE Build Service is sponsored by