File 0743-Fix-filelib-wildcard-1-2-for-patterns-containing-.-a.patch of Package erlang

From 72f704c7b83643bec889eabe3f9fe378639bb06e Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 19 Aug 2019 15:45:46 +0200
Subject: [PATCH] Fix filelib:wildcard/1,2 for patterns containing ".." and/or
 "@"

`..` was broken and only worked when it was used in the beginning
of the pattern before any wildcard characters. For example:

    1> filelib:wildcard("erts/..").
    ["erts/.."]

Using `..` preceded by wildcard characters would not work:

    1> filelib:wildcard("*/..").
    []

`@` is not a wildcard character but is used internally in `filelib` as
an escape character and was not handled as other literal
characters. That could lead to performance degradation as it disabled
an optimization of the matching of the literal prefix of a pattern. It
would also cause the following example to fail:

    1> filelib:wildcard("@/..").
    []

This commit corrects the handling `..` and also makes sure that the
use of `@` in a pattern does not degrade performance.

https://bugs.erlang.org/browse/ERL-1029
---
 lib/stdlib/src/filelib.erl        | 32 +++++++++++++++++++++++++++-----
 lib/stdlib/test/filelib_SUITE.erl | 34 ++++++++++++++++++++++++++++++++++
 2 files changed, 61 insertions(+), 5 deletions(-)

diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index de839be5cf..d1a5a4dc35 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -281,6 +281,14 @@ do_wildcard_2([], _, Result, _Mod) ->
 
 do_wildcard_3(Base, [[double_star]|Rest], Result, Mod) ->
     do_double_star(".", [Base], Rest, Result, Mod, true);
+do_wildcard_3(Base, [".."|Rest], Result, Mod) ->
+    case do_is_dir(Base, Mod) of
+        true ->
+            Matches = [filename:join(Base, "..")],
+            do_wildcard_2(Matches, Rest, Result, Mod);
+        false ->
+            Result
+    end;
 do_wildcard_3(Base0, [Pattern|Rest], Result, Mod) ->
     case do_list_dir(Base0, Mod) of
 	{ok, Files} ->
@@ -387,15 +395,29 @@ compile_wildcard(Pattern0, Cwd0) ->
     end.
 
 compile_wildcard_2([Part|Rest], Root) ->
-    case compile_part(Part) of
-	Part ->
-	    compile_wildcard_2(Rest, compile_join(Root, Part));
-	Pattern ->
-	    compile_wildcard_3(Rest, [Pattern,Root])
+    Pattern = compile_part(Part),
+    case is_literal_pattern(Pattern) of
+        true ->
+            %% Add this literal pattern to the literal pattern prefix.
+            %% This is an optimization to avoid listing all files of
+            %% a directory only to discard all but one. For example,
+            %% without this optimizaton, there would be three
+            %% redundant directory listings when executing this
+            %% wildcard: "./lib/compiler/ebin/*.beam"
+            compile_wildcard_2(Rest, compile_join(Root, Pattern));
+        false ->
+            %% This is the end of the literal prefix. Compile the
+            %% rest of the pattern.
+            compile_wildcard_3(Rest, [Pattern,Root])
     end;
 compile_wildcard_2([], {root,PrefixLen,Root}) ->
     {{exists,Root},PrefixLen}.
 
+is_literal_pattern([H|T]) ->
+    is_integer(H) andalso is_literal_pattern(T);
+is_literal_pattern([]) ->
+    true.
+
 compile_wildcard_3([Part|Rest], Result) ->
     compile_wildcard_3(Rest, [compile_part(Part)|Result]);
 compile_wildcard_3([], Result) ->
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 7403d52881..527d083eaa 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -79,9 +79,11 @@ wildcard_one(Config) when is_list(Config) ->
     do_wildcard_1(Dir,
 		  fun(Wc) ->
 			  L = filelib:wildcard(Wc),
+			  L = filelib:wildcard(disable_prefix_opt(Wc)),
 			  L = filelib:wildcard(Wc, erl_prim_loader),
 			  L = filelib:wildcard(Wc, "."),
 			  L = filelib:wildcard(Wc, Dir),
+			  L = filelib:wildcard(disable_prefix_opt(Wc), Dir),
 			  L = filelib:wildcard(Wc, Dir++"/.")
 		  end),
     file:set_cwd(OldCwd),
@@ -119,6 +121,14 @@ wcc(Wc, Error) ->
     {'EXIT',{{badpattern,Error},
 	     [{filelib,wildcard,2,_}|_]}} = (catch filelib:wildcard(Wc, ".")).
 
+disable_prefix_opt([C|Wc]) when $a =< C, C =< $z; C =:= $@ ->
+    %% There is an optimization for patterns that have a literal prefix
+    %% (such as "lib/compiler/ebin/*"). Test that we'll get the same result
+    %% if we disable that optimization.
+    [$[, C, $] | Wc];
+disable_prefix_opt(Wc) ->
+    Wc.
+
 do_wildcard_1(Dir, Wcf0) ->
     do_wildcard_2(Dir, Wcf0),
     Wcf = fun(Wc0) ->
@@ -300,6 +310,30 @@ do_wildcard_10(Dir, Wcf) ->
     %% Cleanup.
     del(Files),
     [ok = file:del_dir(D) || D <- lists:reverse(Dirs)],
+    wildcard_11(Dir, Wcf).
+
+%% ERL-ERL-1029/OTP-15987: Fix problems with "@/.." and ".." in general.
+wildcard_11(Dir, Wcf) ->
+    Dirs0 = ["@","@dir","dir@"],
+    Dirs = [filename:join(Dir, D) || D <- Dirs0],
+    _ = [ok = file:make_dir(D) || D <- Dirs],
+    Files0 = ["@a","b@","x","y","z"],
+    Files = mkfiles(Files0, Dir),
+
+    ["@","@a","@dir","b@","dir@","x","y","z"] = Wcf("*"),
+    ["@"] = Wcf("@"),
+    ["@","@a","@dir"] = Wcf("@*"),
+    ["@/..","@dir/.."] = Wcf("@*/.."),
+    ["@/../@","@/../@a","@/../@dir",
+     "@dir/../@","@dir/../@a","@dir/../@dir"] = Wcf("@*/../@*"),
+
+    %% Non-directories followed by "/.." should not match any files.
+    [] = Wcf("@a/.."),
+    [] = Wcf("x/.."),
+
+    %% Cleanup.
+    del(Files),
+    [ok = file:del_dir(D) || D <- Dirs],
     ok.
 
 
-- 
2.16.4

openSUSE Build Service is sponsored by