File 1213-fix-6074.patch of Package erlang

From 436fc1f7d5504fc8fe081eb910971e7f5e746669 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Marko=20Min=C4=91ek?= <marko.mindek@invariant.hr>
Date: Sun, 19 Feb 2023 17:03:54 +0100
Subject: [PATCH 1/2] fix 6074

Fixed functionallity of re_write property.
Previous code coudn't work because there was "^"++FakeName line,
   but FakeName could be MatchPattern so this would fail.
I changed the behaviour to append "^" while storeing the re_write,
alias or script_alias proplist.

Also, I included one simple re_write property into test, to make sure
everything works correcty.
---
 lib/inets/src/http_server/mod_alias.erl | 23 ++++++++++++++---------
 lib/inets/test/httpd_SUITE.erl          |  3 ++-
 2 files changed, 16 insertions(+), 10 deletions(-)

diff --git a/lib/inets/src/http_server/mod_alias.erl b/lib/inets/src/http_server/mod_alias.erl
index e1264deb10..b310a7c909 100644
--- a/lib/inets/src/http_server/mod_alias.erl
+++ b/lib/inets/src/http_server/mod_alias.erl
@@ -123,8 +123,7 @@ real_name(ConfigDB, RequestURI, [{MP,Replacement}| _] = Aliases)
 real_name(ConfigDB, RequestURI,  [{_,_}|_] = Aliases) ->
     case longest_match(Aliases, RequestURI) of
 	{match, {FakeName, RealName}} ->
-	    ActualName = re:replace(RequestURI,
-				    "^" ++ FakeName, RealName, [{return,list}]),
+	    ActualName = re:replace(RequestURI, FakeName, RealName, [{return,list}]),
  	    {ShortPath, _AfterPath} = httpd_util:split_path(ActualName),
 	    {Path, AfterPath} =
 		httpd_util:split_path(default_index(ConfigDB, ActualName)),
@@ -137,7 +136,7 @@ longest_match(Aliases, RequestURI) ->
     longest_match(Aliases, RequestURI, _LongestNo = 0, _LongestAlias = undefined).
 
 longest_match([{FakeName, RealName} | Rest], RequestURI, LongestNo, LongestAlias) ->
-    case re:run(RequestURI, "^" ++ FakeName, [{capture, first}]) of
+    case re:run(RequestURI, FakeName, [{capture, first}]) of
 	{match, [{_, Length}]} ->
 	    if
 		Length > LongestNo ->
@@ -158,10 +157,10 @@ longest_match([], _RequestURI, _LongestNo, LongestAlias) ->
 real_script_name(_ConfigDB, _RequestURI, []) ->
     not_a_script;
 real_script_name(ConfigDB, RequestURI, [{FakeName,RealName} | Rest]) ->
-    case re:run(RequestURI, "^" ++ FakeName, [{capture, none}]) of
+    case re:run(RequestURI, FakeName, [{capture, none}]) of
 	match ->
 	    ActualName0 =
-		re:replace(RequestURI, "^" ++ FakeName, RealName,  [{return,list}]),
+		re:replace(RequestURI, FakeName, RealName,  [{return,list}]),
             ActualName = abs_script_path(ConfigDB, ActualName0),
 	    httpd_util:split_script_path(default_index(ConfigDB, ActualName));
 	nomatch ->
@@ -234,14 +233,17 @@ store({directory_index, Value} = Conf, _) when is_list(Value) ->
     end;
 store({directory_index, Value}, _) ->
     {error, {wrong_type, {directory_index, Value}}};
-store({alias, {Fake, Real}} = Conf, _)
+store({alias, {Fake, Real}}, _)
   when is_list(Fake), is_list(Real) ->
+    {ok, {alias,{"^"++Fake,Real}}};
+store({alias, {MP, _}} = Conf, _)
+  when element(1, MP) =:= re_pattern ->
     {ok, Conf};
 store({alias, Value}, _) ->
     {error, {wrong_type, {alias, Value}}};
 store({re_write, {Re, Replacement}} = Conf, _)
   when is_list(Re), is_list(Replacement) ->
-    case re:compile(Re) of
+    case re:compile("^"++Re) of
 	{ok, MP} ->
 	    {ok, {alias, {MP, Replacement}}};
 	{error,_} ->
@@ -249,14 +251,17 @@ store({re_write, {Re, Replacement}} = Conf, _)
     end;
 store({re_write, _} = Conf, _) ->
     {error, {wrong_type, Conf}};
-store({script_alias, {Fake, Real}} = Conf, _) 
+store({script_alias, {Fake, Real}}, _)
   when is_list(Fake), is_list(Real) ->
+    {ok, {script_alias,{"^"++Fake,Real}}};
+store({script_alias, {MP, _}} = Conf, _)
+  when element(1, MP) =:= re_pattern ->
     {ok, Conf};
 store({script_alias, Value}, _) ->
     {error, {wrong_type, {script_alias, Value}}};
 store({script_re_write, {Re, Replacement}} = Conf, _)
   when is_list(Re), is_list(Replacement) ->
-    case re:compile(Re) of
+    case re:compile("^"++Re) of
 	{ok, MP} ->
 	    {ok, {script_alias, {MP, Replacement}}};
 	{error,_} ->
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index df628257ec..0cd31427e0 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -1151,6 +1151,7 @@ alias() ->
 alias(Config) when is_list(Config) ->
     TestURIs200 = [
                    {"GET /pics/icon.sheet.gif ", 200, "image/gif"},
+                   {"GET /pictures/icon.sheet.gif ", 200, "image/gif"},
                    {"GET / ", 200, "text/html"},
                    {"GET /misc/ ", 200, "text/html"}
                   ],
@@ -2160,7 +2161,7 @@ config_template(Config, ServerRoot, ScriptPath, Modules) ->
      {mime_types, [{"html","text/html"},{"htm","text/html"}, {"shtml","text/html"},
 		   {"gif", "image/gif"}]},
      {alias, {"/icons/", filename:join(ServerRoot,"icons") ++ "/"}},
-     {alias, {"/pics/",  filename:join(ServerRoot,"icons") ++ "/"}},
+     {re_write, {"/pic(ture)?s/",  filename:join(ServerRoot,"icons") ++ "/"}},
      {script_alias, {"/cgi-bin/", ScriptPath}},
      {script_alias, {"/htbin/", ScriptPath}},
      {erl_script_alias, {"/cgi-bin/erl", Modules}}
-- 
2.35.3

openSUSE Build Service is sponsored by