File 0399-inets-httpd-dir-listing-fix.patch of Package erlang

From 68df92876d53121d05d195b39bc4ea37198eacea Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Fri, 7 May 2021 14:44:56 +0200
Subject: [PATCH] inets: httpd dir listing fix

Before this change httpd was generating HTML dir listing with corrupted hrefs (GH-4677).
Closes #4677.
---
 lib/inets/src/http_server/mod_dir.erl | 21 +++++++++------------
 lib/inets/test/httpd_SUITE.erl        | 20 +++++++++++++++++++-
 lib/inets/test/httpd_test_lib.erl     | 17 ++++++++++++++++-
 3 files changed, 44 insertions(+), 14 deletions(-)

diff --git a/lib/inets/src/http_server/mod_dir.erl b/lib/inets/src/http_server/mod_dir.erl
index 1d2d44fc82..d81c6cc4c3 100644
--- a/lib/inets/src/http_server/mod_dir.erl
+++ b/lib/inets/src/http_server/mod_dir.erl
@@ -135,7 +135,7 @@ format(Path,RequestURI) ->
     io_lib:format("<IMG SRC=\"~s\" ALT=\"[~s]\">"
 		  " <A HREF=\"~s\">Parent directory</A>      "
 		  " ~2.2.0w-~s-~w ~2.2.0w:~2.2.0w        -\n",
-		  [icon(back),"DIR",get_href(RequestURI),Day,
+		  [icon(back),"DIR",percent_encode(RequestURI),Day,
 		   httpd_util:month(Month),Year,Hour,Minute]).
 
 %% body
@@ -159,7 +159,7 @@ format(Path,RequestURI,ConfigDB,InitEntry) ->
 				  "<A HREF=\"~s\">~-21.s..</A>"
 				  "~*.*c~2.2.0w-~s-~w ~2.2.0w:~2.2.0w"
 				  "        -\n", [icon(folder),"DIR",
-						  get_href(RequestURI++"/"++InitEntry++"/"),
+						  RequestURI ++ "/" ++ percent_encode(InitEntry) ++ "/",
 						  Entry, 23-21, 23-21, $ ,
 						  Day, httpd_util:month(Month),
 						  Year,Hour,Minute]);
@@ -167,8 +167,8 @@ format(Path,RequestURI,ConfigDB,InitEntry) ->
 		    io_lib:format("<IMG SRC=\"~s\" ALT=\"[~s]\">"
 				  " <A HREF=\"~s\">~s</A>~*.*c~2.2.0"
 				  "w-~s-~w ~2.2.0w:~2.2.0w        -\n",
-				  [icon(folder),"DIR",get_href(RequestURI ++ "/" ++
-				   InitEntry ++ "/"),Entry,
+				  [icon(folder),"DIR",
+                                   RequestURI ++ "/" ++ percent_encode(InitEntry) ++ "/",Entry,
 				   23-EntryLength,23-EntryLength,$ ,Day,
 				   httpd_util:month(Month),Year,Hour,Minute])
 	    end;
@@ -183,8 +183,8 @@ format(Path,RequestURI,ConfigDB,InitEntry) ->
 		    io_lib:format("<IMG SRC=\"~s\" ALT=\"[~s]\">"
 				  " <A HREF=\"~s\">~-21.s..</A>~*.*c~2.2.0"
 				  "w-~s-~w ~2.2.0w:~2.2.0w~8wk  ~s\n",
-				  [icon(Suffix, MimeType), Suffix, get_href(RequestURI 
-				   ++"/"++InitEntry), Entry, 23-21, 23-21, $ , Day,
+				  [icon(Suffix, MimeType), Suffix,
+                                   RequestURI ++ "/" ++ percent_encode(InitEntry), Entry, 23-21, 23-21, $ , Day,
 				   httpd_util:month(Month),Year,Hour,Minute,
 				   trunc(FileInfo#file_info.size/1024+1),
 				   MimeType]);
@@ -192,8 +192,8 @@ format(Path,RequestURI,ConfigDB,InitEntry) ->
 		    io_lib:format("<IMG SRC=\"~s\" ALT=\"[~s]\"> "
 				  "<A HREF=\"~s\">~s</A>~*.*c~2.2.0w-~s-~w"
 				  " ~2.2.0w:~2.2.0w~8wk  ~s\n",
-				  [icon(Suffix, MimeType), Suffix, get_href(RequestURI
-				   ++ "/" ++ InitEntry), Entry, 23-EntryLength,
+				  [icon(Suffix, MimeType), Suffix,
+                                   RequestURI ++ "/" ++ percent_encode(InitEntry), Entry, 23-EntryLength,
 				   23-EntryLength, $ ,Day,
 				   httpd_util:month(Month),Year,Hour,Minute,
 				   trunc(FileInfo#file_info.size/1024+1),
@@ -203,11 +203,8 @@ format(Path,RequestURI,ConfigDB,InitEntry) ->
 	    ""
     end.
 
-get_href(URI) ->
-	percent_encode(URI).
-
 percent_encode(URI) when is_list(URI) ->
-    Reserved = reserved(), 
+    Reserved = reserved(),
     lists:append([uri_encode(Char, Reserved) || Char <- URI]);
 percent_encode(URI) when is_binary(URI) ->
     Reserved = reserved(),
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index 7c2a2f9075..9f82f09d6e 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -124,7 +124,7 @@ groups() ->
 		   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]},
+     {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
@@ -570,6 +570,24 @@ basic_auth(Config) ->
     %% Authentication still required!
     basic_auth_requiered(Config).
 
+verify_href_1_1(Config) when is_list(Config) ->
+    verify_href([{http_version, "HTTP/1.1"} | Config]).
+
+verify_href() ->
+    [{doc, "Test generated hrefs (related to GH-4677), check that hrefs for dir listing work"}].
+
+verify_href(Config) when is_list(Config) ->
+    Version = proplists:get_value(http_version, Config),
+    Host = proplists:get_value(host, Config),
+    Go = fun(Path, User, Password, Opts) ->
+                 ct:pal("Navigating to ~p", [Path]),
+                 auth_status(auth_request(Path, User, Password, Version, Host),
+                             Config, Opts)
+         end,
+    {ok, Hrefs} = Go("/open/", "Aladdin", "AladdinPassword", [{statuscode, 200}, {fetch_hrefs, true}]),
+    [ok = Go(H, "one", "onePassword", [{statuscode, 200}]) || H <- Hrefs],
+    ok.
+
 auth_api_1_1(Config) when is_list(Config) -> 
     auth_api([{http_version, "HTTP/1.1"} | Config]).
 
diff --git a/lib/inets/test/httpd_test_lib.erl b/lib/inets/test/httpd_test_lib.erl
index 31a9c72e9c..e2578b9d76 100644
--- a/lib/inets/test/httpd_test_lib.erl
+++ b/lib/inets/test/httpd_test_lib.erl
@@ -307,12 +307,27 @@ validate(RequestStr, #state{status_line = {Version, StatusCode, _},
 	    check_body(RequestStr, StatusCode, 
 		       Headers#http_response_h.'content-type',
 		       list_to_integer(Headers#http_response_h.'content-length'),
-		       Body)
+		       Body),
+            case proplists:get_bool(fetch_hrefs, Options) of
+                true ->
+                    {ok, fetch_hrefs(Body)};
+                _ ->
+                    ok
+            end
     end.
 
 %--------------------------------------------------------------------
 %% Internal functions
 %%------------------------------------------------------------------
+fetch_hrefs(Body) ->
+    {match, Matches} = re:run(Body, <<"HREF.*\"">>, [global]),
+    Parse = fun(B, S, L) ->
+                    Sliced = string:slice(B, S, L),
+                    HrefBin = lists:nth(2, re:split(Sliced, <<"\"">>)),
+                    binary:bin_to_list(HrefBin)
+            end,
+    [Parse(Body, Start, Length) || [{Start, Length}] <- Matches].
+
 check_version(Version, Options) ->
     case lists:keysearch(version, 1, Options) of
 	{value, {version, Version}} ->
-- 
2.26.2

openSUSE Build Service is sponsored by