File 3582-inets-fix-html-encoding-issue.patch of Package erlang

From 5f83a9d719afac0718bff524df6654c9fc94aad5 Mon Sep 17 00:00:00 2001
From: Ao Song <andy@erlang.org>
Date: Mon, 21 Sep 2020 09:53:28 +0200
Subject: [PATCH] inets, fix html encoding issue

Change-Id: I5c10d9ea5a4b23aa38fc6ededf72fdb6967f5cb2
---
 lib/inets/src/http_server/mod_alias.erl |  5 ++
 lib/inets/src/http_server/mod_dir.erl   | 69 ++++++++++++++++++++-----
 2 files changed, 61 insertions(+), 13 deletions(-)

diff --git a/lib/inets/src/http_server/mod_alias.erl b/lib/inets/src/http_server/mod_alias.erl
index 0d1681f6ed..35da39c53c 100644
--- a/lib/inets/src/http_server/mod_alias.erl
+++ b/lib/inets/src/http_server/mod_alias.erl
@@ -198,6 +198,7 @@ append_index(RealName, [Index | Rest]) ->
 %% path
 
 path(Data, ConfigDB, RequestURI) ->
+	InitPath =
     case proplists:get_value(real_name, Data) of
 	undefined ->
 	    DocumentRoot = which_document_root(ConfigDB), 
@@ -206,6 +207,10 @@ path(Data, ConfigDB, RequestURI) ->
 	    Path;
 	{Path, _AfterPath} ->
 	    Path
+    end,
+	case uri_string:percent_decode(InitPath) of
+		{error, _} -> InitPath;
+		P -> P
     end.
 
 %%
diff --git a/lib/inets/src/http_server/mod_dir.erl b/lib/inets/src/http_server/mod_dir.erl
index ad2ee1d994..3d287c4b18 100644
--- a/lib/inets/src/http_server/mod_dir.erl
+++ b/lib/inets/src/http_server/mod_dir.erl
@@ -100,6 +100,17 @@ dir(Path,RequestURI,ConfigDB) ->
 			 file:format_error(Reason))}
     end.
 
+encode_html_entity(FileName) ->
+	Enc = fun($&) -> "&amp;";
+	         ($<) -> "&lt;";
+			 ($>) -> "&gt;";
+			 ($") -> "&quot;";
+			 ($') -> "&#x27;";
+			 ($/) -> "&#x2F;";
+			 (C)  -> C
+		  end,
+	unicode:characters_to_list([Enc(C) || C <- FileName]).
+
 %% header
 
 header(Path,RequestURI) ->
@@ -124,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",RequestURI,Day,
+		  [icon(back),"DIR",get_href(RequestURI),Day,
 		   httpd_util:month(Month),Year,Hour,Minute]).
 
 %% body
@@ -135,8 +146,9 @@ body(Path, RequestURI, ConfigDB, [Entry | Rest]) ->
     [format(Path, RequestURI, ConfigDB, Entry)|
      body(Path, RequestURI, ConfigDB, Rest)].
 
-format(Path,RequestURI,ConfigDB,Entry) ->
-    case file:read_file_info(Path++"/"++Entry) of
+format(Path,RequestURI,ConfigDB,InitEntry) ->
+	Entry = encode_html_entity(InitEntry),
+    case file:read_file_info(Path++"/"++InitEntry) of
 	{ok,FileInfo} when FileInfo#file_info.type == directory ->
 	    {{Year, Month, Day},{Hour, Minute, _Second}} = 
 		FileInfo#file_info.mtime,
@@ -145,18 +157,18 @@ format(Path,RequestURI,ConfigDB,Entry) ->
 		EntryLength > 21 ->
 		    io_lib:format("<IMG SRC=\"~s\" ALT=\"[~s]\"> "
 				  "<A HREF=\"~s\">~-21.s..</A>"
-				  "~2.2.0w-~s-~w ~2.2.0w:~2.2.0w"
+				  "~*.*c~2.2.0w-~s-~w ~2.2.0w:~2.2.0w"
 				  "        -\n", [icon(folder),"DIR",
-						  RequestURI++"/"++Entry++"/",
-						  Entry,
+						  get_href(RequestURI++"/"++InitEntry++"/"),
+						  Entry, 23-21, 23-21, $ ,
 						  Day, httpd_util:month(Month),
 						  Year,Hour,Minute]);
 		true ->
 		    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",RequestURI ++ "/" ++
-				   Entry ++ "/",Entry,
+				  [icon(folder),"DIR",get_href(RequestURI ++ "/" ++
+				   InitEntry ++ "/"),Entry,
 				   23-EntryLength,23-EntryLength,$ ,Day,
 				   httpd_util:month(Month),Year,Hour,Minute])
 	    end;
@@ -169,10 +181,10 @@ format(Path,RequestURI,ConfigDB,Entry) ->
 	    if
 		EntryLength > 21 ->
 		    io_lib:format("<IMG SRC=\"~s\" ALT=\"[~s]\">"
-				  " <A HREF=\"~s\">~-21.s..</A>~2.2.0"
+				  " <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, RequestURI 
-				   ++"/"++Entry, Entry,Day,
+				  [icon(Suffix, MimeType), Suffix, get_href(RequestURI 
+				   ++"/"++InitEntry), Entry, 23-21, 23-21, $ , Day,
 				   httpd_util:month(Month),Year,Hour,Minute,
 				   trunc(FileInfo#file_info.size/1024+1),
 				   MimeType]);
@@ -180,8 +192,8 @@ format(Path,RequestURI,ConfigDB,Entry) ->
 		    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, RequestURI
-				   ++ "/" ++ Entry, Entry, 23-EntryLength,
+				  [icon(Suffix, MimeType), Suffix, get_href(RequestURI
+				   ++ "/" ++ InitEntry), Entry, 23-EntryLength,
 				   23-EntryLength, $ ,Day,
 				   httpd_util:month(Month),Year,Hour,Minute,
 				   trunc(FileInfo#file_info.size/1024+1),
@@ -191,6 +203,37 @@ format(Path,RequestURI,ConfigDB,Entry) ->
 	    ""
     end.
 
+get_href(URI) ->
+	percent_encode(URI).
+
+percent_encode(URI) when is_list(URI) ->
+    Reserved = reserved(), 
+    lists:append([uri_encode(Char, Reserved) || Char <- URI]);
+percent_encode(URI) when is_binary(URI) ->
+    Reserved = reserved(),
+    << <<(uri_encode_binary(Char, Reserved))/binary>> || <<Char>> <= URI >>.
+
+reserved() ->
+    sets:from_list([$;, $:, $@, $&, $=, $+, $,, $/, $?,
+            $#, $[, $], $<, $>, $\", ${, $}, $|, %"
+			       $\\, $', $^, $%, $ ]).
+
+uri_encode(Char, Reserved) ->
+    case sets:is_element(Char, Reserved) of
+	true ->
+	    [ $% | http_util:integer_to_hexlist(Char)];
+	false ->
+	    [Char]
+    end.
+
+uri_encode_binary(Char, Reserved) ->
+    case sets:is_element(Char, Reserved) of
+        true ->
+            << $%, (integer_to_binary(Char, 16))/binary >>;
+        false ->
+            <<Char>>
+    end.
+
 %% footer
 
 footer(Path,FileList) ->
-- 
2.26.2

openSUSE Build Service is sponsored by