File 0917-inets-Do-not-consider-file-errors-as-500-Internal-se.patch of Package erlang

From d2744503e5d62406053b31e01de02e7fa925d30d Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Wed, 29 Nov 2023 08:15:09 +0100
Subject: [PATCH 1/2] inets: Do not consider file errors as "500 - Internal
 server error"

---
 lib/inets/src/http_server/httpd_file.erl | 14 +++++----
 lib/inets/test/httpd_SUITE.erl           | 36 +++++++++++++++++-------
 2 files changed, 35 insertions(+), 15 deletions(-)

diff --git a/lib/inets/src/http_server/httpd_file.erl b/lib/inets/src/http_server/httpd_file.erl
index e8af80cc64..f904f741c7 100644
--- a/lib/inets/src/http_server/httpd_file.erl
+++ b/lib/inets/src/http_server/httpd_file.erl
@@ -35,13 +35,17 @@ handle_error(enotdir, Op, ModData, Path) ->
 	         ": A component of the file name is not a directory");
 handle_error(eisdir, Op, ModData, Path) ->
     handle_error(403, Op, ModData, Path,
-	         ":Illegal operation expected a file not a directory");
+	         ": Illegal operation expected a file not a directory");
+handle_error(enametoolong, Op, ModData, Path) ->
+    handle_error(404, Op, ModData, Path,
+	         ": Filename too long");
 handle_error(emfile, Op, _ModData, Path) ->
-    handle_error(500, Op, none, Path, ": Too many open files");
+    handle_error(503, Op, none, Path, ": Too many open files");
 handle_error({enfile,_}, Op, _ModData, Path) ->
-    handle_error(500, Op, none, Path, ": File table overflow");
-handle_error(_Reason, Op, _ModData, Path) ->
-    handle_error(500, Op, none, Path, "").
+    handle_error(503, Op, none, Path, ": File table overflow");
+handle_error(Reason, Op, _ModData, Path) ->
+    ReasonStr = lists:flatten(io_lib:format("File error ~p", [Reason])),
+    handle_error(503, Op, none, Path, ReasonStr).
 	    
 handle_error(StatusCode, Op, none, Path, Reason) ->
     {StatusCode, none, ?NICE("Can't " ++ Op ++ " " ++ Path ++ Reason)};
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index 4a9f01baf1..4a965a194d 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -156,6 +156,7 @@ http_get() ->
      bad_dot_paths,
      %%actions, Add configuration so that this test mod_action
      esi, 
+     filename_too_long,
      bad_hex, 
      missing_CR,
      max_header,
@@ -895,8 +896,8 @@ chunked(Config) when is_list(Config) ->
 		      proplists:get_value(host, Config), proplists:get_value(node, Config)).
 %%-------------------------------------------------------------------------
 expect() ->   
-    ["Check that the server handles request with the expect header "
-     "field appropriate"].
+    [{doc, "Check that the server handles request with the expect header "
+      "field appropriate"}].
 expect(Config) when is_list(Config) ->
     httpd_1_1:expect(proplists:get_value(type, Config), proplists:get_value(port, Config), 
 		     proplists:get_value(host, Config), proplists:get_value(node, Config)).
@@ -1245,19 +1246,19 @@ trace(Config) when is_list(Config) ->
 	     proplists:get_value(host, Config), proplists:get_value(node, Config)).
 %%-------------------------------------------------------------------------
 light() ->
-    ["Test light load"].
+    [{doc, "Test light load"}].
 light(Config) when is_list(Config) ->
     httpd_load:load_test(proplists:get_value(type, Config), proplists:get_value(port, Config), proplists:get_value(host, Config), 
 			 proplists:get_value(node, Config), 10).
 %%-------------------------------------------------------------------------
 medium() ->
-    ["Test  medium load"].
+    [{doc, "Test  medium load"}].
 medium(Config) when is_list(Config) ->
     httpd_load:load_test(proplists:get_value(type, Config), proplists:get_value(port, Config), proplists:get_value(host, Config), 
 			 proplists:get_value(node, Config), 100).
 %%-------------------------------------------------------------------------
 heavy() ->
-    ["Test heavy load"].
+    [{doc, "Test heavy load"}].
 heavy(Config) when is_list(Config) ->
     httpd_load:load_test(proplists:get_value(type, Config), proplists:get_value(port, Config), proplists:get_value(host, Config), 
 			 proplists:get_value(node, Config),
@@ -1275,9 +1276,23 @@ content_length(Config) ->
 				       [{statuscode, 200},
 					{content_length, 274},
 					{version, Version}]).
+
+%-------------------------------------------------------------------------
+filename_too_long() ->
+    [{doc, "Tests what happens if supplied filename exceeds os-limit of filename characters."}].
+filename_too_long(Config) ->
+    Version = proplists:get_value(http_version, Config),
+    Host = proplists:get_value(host, Config),
+    TooLongFileName = lists:duplicate(257, $F),
+    ok = httpd_test_lib:verify_request(proplists:get_value(type, Config), Host,
+				       proplists:get_value(port, Config), proplists:get_value(node, Config),
+				       http_request("GET /" ++ TooLongFileName ++ " ", Version, Host),
+				       [{statuscode, 404},
+					{version, Version}]).
+
 %%-------------------------------------------------------------------------
 bad_hex() ->
-    ["Tests that a URI with a bad hexadecimal code is handled OTP-6003"].
+    [{doc, "Tests that a URI with a bad hexadecimal code is handled OTP-6003"}].
 bad_hex(Config) ->
     Version = proplists:get_value(http_version, Config),
     Host = proplists:get_value(host, Config),
@@ -1289,7 +1304,7 @@ bad_hex(Config) ->
 					{version, Version}]).
 %%-------------------------------------------------------------------------
 missing_CR() ->
-     ["Tests missing CR in delimiter OTP-7304"].
+     [{doc, "Tests missing CR in delimiter OTP-7304"}].
 missing_CR(Config) ->
     Version = proplists:get_value(http_version, Config),
     Host =  proplists:get_value(host, Config),
@@ -1318,6 +1333,7 @@ customize(Config) when is_list(Config) ->
 					{no_header, "Server"},
 					{version, Version}]).
 
+%%-------------------------------------------------------------------------
 add_default() ->
     [{doc, "Test adding default header with custom callback"}].
 
@@ -1338,7 +1354,7 @@ add_default(Config) when is_list(Config) ->
 
 %%-------------------------------------------------------------------------
 max_header() ->
-    ["Denial Of Service (DOS) attack, prevented by max_header"].
+    [{doc, "Denial Of Service (DOS) attack, prevented by max_header"}].
 max_header(Config) when is_list(Config) ->
     Version = proplists:get_value(http_version, Config),
     Host =  proplists:get_value(host, Config),
@@ -1352,7 +1368,7 @@ max_header(Config) when is_list(Config) ->
 
 %%-------------------------------------------------------------------------
 max_content_length() ->
-    ["Denial Of Service (DOS) attack, prevented by max_content_length"].
+    [{doc, "Denial Of Service (DOS) attack, prevented by max_content_length"}].
 max_content_length(Config) when is_list(Config) ->
     Version = proplists:get_value(http_version, Config),
     Host =  proplists:get_value(host, Config),
@@ -1361,7 +1377,7 @@ max_content_length(Config) when is_list(Config) ->
 
 %%-------------------------------------------------------------------------
 ignore_invalid_header() ->
-    ["RFC 7230 - 3.2.4 ... No whitespace is allowed between the header field-name and colon"].
+    [{doc, "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),
-- 
2.35.3

openSUSE Build Service is sponsored by