aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
authorBjörn Gustavsson <[email protected]>2013-02-14 12:05:01 +0100
committerBjörn Gustavsson <[email protected]>2013-02-14 12:05:01 +0100
commit856f165d08b03a85a96389c4795e8b1b019e30f3 (patch)
tree472ddeb664aa4eae2c8ec3424fcc6a160c490f0b /lib/stdlib/src
parent9905024a8b7d9a26f7fdf6640ab391c5cb8f6780 (diff)
parent5abcc77292e59a951e5a53c1641081f973d25c90 (diff)
downloadotp-856f165d08b03a85a96389c4795e8b1b019e30f3.tar.gz
otp-856f165d08b03a85a96389c4795e8b1b019e30f3.tar.bz2
otp-856f165d08b03a85a96389c4795e8b1b019e30f3.zip
Merge branch 'bjorn/stdlib/filelib-wildcard/OTP-10812'
* bjorn/stdlib/filelib-wildcard/OTP-10812: Remove special case handling "-" at the beginning of a charset Optimize character sets using gb_sets Clean up and simplify the inner matching loop Only sort the result list once, just before returning Replace filename:join/2 with '++' Rethink the filelib:wildcard() functions Don't redefine error/1 Don't allow binaries as the Cwd argument for filelib:wildcard() Don't handle binaries from file:list_dir/1 Strengthen test suite
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/filelib.erl224
1 files changed, 98 insertions, 126 deletions
diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index 318f3b87b8..7df72a93e5 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -19,16 +19,14 @@
-module(filelib).
%% File utilities.
-
-%% Avoid warning for local function error/1 clashing with autoimported BIF.
--compile({no_auto_import,[error/1]}).
--export([wildcard/1, wildcard/2, is_dir/1, is_file/1, is_regular/1,
- compile_wildcard/1]).
+-export([wildcard/1, wildcard/2, is_dir/1, is_file/1, is_regular/1]).
-export([fold_files/5, last_modified/1, file_size/1, ensure_dir/1]).
-
-export([wildcard/3, is_dir/2, is_file/2, is_regular/2]).
-export([fold_files/6, last_modified/2, file_size/2]).
+%% For debugging/testing.
+-export([compile_wildcard/1]).
+
-include_lib("kernel/include/file.hrl").
-define(HANDLE_ERROR(Expr),
@@ -37,7 +35,7 @@
catch
error:{badpattern,_}=UnUsUalVaRiAbLeNaMe ->
%% Get the stack backtrace correct.
- erlang:error(UnUsUalVaRiAbLeNaMe)
+ error(UnUsUalVaRiAbLeNaMe)
end).
-type filename() :: file:name().
@@ -48,19 +46,19 @@
-spec wildcard(Wildcard) -> [file:filename()] when
Wildcard :: filename() | dirname().
wildcard(Pattern) when is_list(Pattern) ->
- ?HANDLE_ERROR(do_wildcard(Pattern, file)).
+ ?HANDLE_ERROR(do_wildcard(Pattern, ".", file)).
-spec wildcard(Wildcard, Cwd) -> [file:filename()] when
Wildcard :: filename() | dirname(),
Cwd :: dirname().
-wildcard(Pattern, Cwd) when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)) ->
+wildcard(Pattern, Cwd) when is_list(Pattern), is_list(Cwd) ->
?HANDLE_ERROR(do_wildcard(Pattern, Cwd, file));
wildcard(Pattern, Mod) when is_list(Pattern), is_atom(Mod) ->
- ?HANDLE_ERROR(do_wildcard(Pattern, Mod)).
+ ?HANDLE_ERROR(do_wildcard(Pattern, ".", Mod)).
-spec wildcard(file:name(), file:name(), atom()) -> [file:filename()].
wildcard(Pattern, Cwd, Mod)
- when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)), is_atom(Mod) ->
+ when is_list(Pattern), is_list(Cwd), is_atom(Mod) ->
?HANDLE_ERROR(do_wildcard(Pattern, Cwd, Mod)).
-spec is_dir(Name) -> boolean() when
@@ -124,47 +122,6 @@ file_size(File, Mod) when is_atom(Mod) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-do_wildcard(Pattern, Mod) when is_list(Pattern) ->
- do_wildcard_comp(do_compile_wildcard(Pattern), Mod).
-
-do_wildcard_comp({compiled_wildcard,{exists,File}}, Mod) ->
- case eval_read_file_info(File, Mod) of
- {ok,_} -> [File];
- _ -> []
- end;
-do_wildcard_comp({compiled_wildcard,[cwd,Base|Rest]}, Mod) ->
- do_wildcard_1([Base], Rest, Mod);
-do_wildcard_comp({compiled_wildcard,[Base|Rest]}, Mod) ->
- do_wildcard_1([Base], Rest, Mod).
-
-do_wildcard(Pattern, Cwd, Mod) when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)) ->
- do_wildcard_comp(do_compile_wildcard(Pattern), Cwd, Mod).
-
-do_wildcard_comp({compiled_wildcard,{exists,File}}, Cwd, Mod) ->
- case eval_read_file_info(filename:absname(File, Cwd), Mod) of
- {ok,_} -> [File];
- _ -> []
- end;
-do_wildcard_comp({compiled_wildcard,[cwd|Rest0]}, Cwd0, Mod) ->
- case Rest0 of
- [current|Rest] -> ok;
- Rest -> ok
- end,
- {Cwd,PrefixLen} = case filename:join([Cwd0]) of
- Bin when is_binary(Bin) -> {Bin,byte_size(Bin)+1};
- Other -> {Other,length(Other)+1}
- end, %Slash away redundant slashes.
- [
- if
- is_binary(N) ->
- <<_:PrefixLen/binary,Res/binary>> = N,
- Res;
- true ->
- lists:nthtail(PrefixLen, N)
- end || N <- do_wildcard_1([Cwd], Rest, Mod)];
-do_wildcard_comp({compiled_wildcard,[Base|Rest]}, _Cwd, Mod) ->
- do_wildcard_1([Base], Rest, Mod).
-
do_is_dir(Dir, Mod) ->
case eval_read_file_info(Dir, Mod) of
{ok, #file_info{type=directory}} ->
@@ -293,8 +250,24 @@ ensure_dir(F) ->
%%% Pattern matching using a compiled wildcard.
%%%
-do_wildcard_1(Files, Pattern, Mod) ->
- do_wildcard_2(Files, Pattern, [], Mod).
+do_wildcard(Pattern, Cwd, Mod) ->
+ {Compiled,PrefixLen} = compile_wildcard(Pattern, Cwd),
+ Files0 = do_wildcard_1(Compiled, Mod),
+ Files = if
+ PrefixLen =:= 0 ->
+ Files0;
+ true ->
+ [lists:nthtail(PrefixLen, File) || File <- Files0]
+ end,
+ lists:sort(Files).
+
+do_wildcard_1({exists,File}, Mod) ->
+ case eval_read_file_info(File, Mod) of
+ {ok,_} -> [File];
+ _ -> []
+ end;
+do_wildcard_1([Base|Rest], Mod) ->
+ do_wildcard_2([Base], Rest, [], Mod).
do_wildcard_2([File|Rest], Pattern, Result, Mod) ->
do_wildcard_2(Rest, Pattern, do_wildcard_3(File, Pattern, Result, Mod), Mod);
@@ -302,12 +275,12 @@ do_wildcard_2([], _, Result, _Mod) ->
Result.
do_wildcard_3(Base, [[double_star]|Rest], Result, Mod) ->
- lists:sort(do_double_star(current, [Base], Rest, Result, Mod, true));
-do_wildcard_3(Base, [Pattern|Rest], Result, Mod) ->
- case do_list_dir(Base, Mod) of
- {ok, Files0} ->
- Files = lists:sort(Files0),
- Matches = wildcard_4(Pattern, Files, Base, []),
+ do_double_star(".", [Base], Rest, Result, Mod, true);
+do_wildcard_3(Base0, [Pattern|Rest], Result, Mod) ->
+ case do_list_dir(Base0, Mod) of
+ {ok, Files} ->
+ Base = prepare_base(Base0),
+ Matches = do_wildcard_4(Pattern, Base, Files),
do_wildcard_2(Matches, Rest, Result, Mod);
_ ->
Result
@@ -315,51 +288,50 @@ do_wildcard_3(Base, [Pattern|Rest], Result, Mod) ->
do_wildcard_3(Base, [], Result, _Mod) ->
[Base|Result].
-wildcard_4(Pattern, [File|Rest], Base, Result) when is_binary(File) ->
- case wildcard_5(Pattern, binary_to_list(File)) of
- true ->
- wildcard_4(Pattern, Rest, Base, [join(Base, File)|Result]);
+do_wildcard_4(Pattern, Base, Files) ->
+ case will_always_match(Pattern) of
false ->
- wildcard_4(Pattern, Rest, Base, Result)
- end;
-wildcard_4(Pattern, [File|Rest], Base, Result) ->
- case wildcard_5(Pattern, File) of
+ [Base++F || F <- Files, match_part(Pattern, F)];
true ->
- wildcard_4(Pattern, Rest, Base, [join(Base, File)|Result]);
- false ->
- wildcard_4(Pattern, Rest, Base, Result)
- end;
-wildcard_4(_Patt, [], _Base, Result) ->
- Result.
+ [Base++F || F <- Files]
+ end.
-wildcard_5([question|Rest1], [_|Rest2]) ->
- wildcard_5(Rest1, Rest2);
-wildcard_5([accept], _) ->
+match_part([question|Rest1], [_|Rest2]) ->
+ match_part(Rest1, Rest2);
+match_part([accept], _) ->
true;
-wildcard_5([double_star], _) ->
+match_part([double_star], _) ->
true;
-wildcard_5([star|Rest], File) ->
+match_part([star|Rest], File) ->
do_star(Rest, File);
-wildcard_5([{one_of, Ordset}|Rest], [C|File]) ->
- case ordsets:is_element(C, Ordset) of
- true -> wildcard_5(Rest, File);
- false -> false
- end;
-wildcard_5([{alt, Alts}], File) ->
+match_part([{one_of, Ordset}|Rest], [C|File]) ->
+ gb_sets:is_element(C, Ordset) andalso match_part(Rest, File);
+match_part([{alt, Alts}], File) ->
do_alt(Alts, File);
-wildcard_5([C|Rest1], [C|Rest2]) when is_integer(C) ->
- wildcard_5(Rest1, Rest2);
-wildcard_5([X|_], [Y|_]) when is_integer(X), is_integer(Y) ->
+match_part([C|Rest1], [C|Rest2]) when is_integer(C) ->
+ match_part(Rest1, Rest2);
+match_part([X|_], [Y|_]) when is_integer(X), is_integer(Y) ->
false;
-wildcard_5([], []) ->
+match_part([], []) ->
true;
-wildcard_5([], [_|_]) ->
+match_part([], [_|_]) ->
false;
-wildcard_5([_|_], []) ->
+match_part([_|_], []) ->
false.
+will_always_match([accept]) -> true;
+will_always_match(_) -> false.
+
+prepare_base(Base0) ->
+ Base1 = filename:join(Base0, "x"),
+ "x"++Base2 = lists:reverse(Base1),
+ lists:reverse(Base2).
+
do_double_star(Base, [H|T], Rest, Result, Mod, Root) ->
- Full = join(Base, H),
+ Full = case Root of
+ false -> filename:join(Base, H);
+ true -> H
+ end,
Result1 = case do_list_dir(Full, Mod) of
{ok, Files} ->
do_double_star(Full, Files, Rest, Result, Mod, false);
@@ -373,62 +345,64 @@ do_double_star(Base, [H|T], Rest, Result, Mod, Root) ->
do_double_star(_Base, [], _Rest, Result, _Mod, _Root) ->
Result.
-do_star(Pattern, [X|Rest]) ->
- case wildcard_5(Pattern, [X|Rest]) of
- true -> true;
- false -> do_star(Pattern, Rest)
- end;
+do_star(Pattern, [_|Rest]=File) ->
+ match_part(Pattern, File) orelse do_star(Pattern, Rest);
do_star(Pattern, []) ->
- wildcard_5(Pattern, []).
+ match_part(Pattern, []).
do_alt([Alt|Rest], File) ->
- case wildcard_5(Alt, File) of
- true -> true;
- false -> do_alt(Rest, File)
- end;
+ match_part(Alt, File) orelse do_alt(Rest, File);
do_alt([], _File) ->
false.
-do_list_dir(current, Mod) -> eval_list_dir(".", Mod);
do_list_dir(Dir, Mod) -> eval_list_dir(Dir, Mod).
-join(current, File) -> File;
-join(Base, File) -> filename:join(Base, File).
-
%%% Compiling a wildcard.
-compile_wildcard(Pattern) ->
- ?HANDLE_ERROR(do_compile_wildcard(Pattern)).
-
-do_compile_wildcard(Pattern) ->
- {compiled_wildcard,compile_wildcard_1(Pattern)}.
+%% Only for debugging.
+compile_wildcard(Pattern) when is_list(Pattern) ->
+ {compiled_wildcard,?HANDLE_ERROR(compile_wildcard(Pattern, "."))}.
-compile_wildcard_1(Pattern) ->
+compile_wildcard(Pattern, Cwd0) ->
[Root|Rest] = filename:split(Pattern),
case filename:pathtype(Root) of
relative ->
- case compile_wildcard_2([Root|Rest], current) of
- {exists,_}=Wc -> Wc;
- [_|_]=Wc -> [cwd|Wc]
- end;
+ Cwd = filename:join([Cwd0]),
+ compile_wildcard_2([Root|Rest], {cwd,Cwd});
_ ->
- compile_wildcard_2(Rest, [Root])
+ compile_wildcard_2(Rest, {root,0,Root})
end.
compile_wildcard_2([Part|Rest], Root) ->
case compile_part(Part) of
Part ->
- compile_wildcard_2(Rest, join(Root, Part));
+ compile_wildcard_2(Rest, compile_join(Root, Part));
Pattern ->
compile_wildcard_3(Rest, [Pattern,Root])
end;
-compile_wildcard_2([], Root) -> {exists,Root}.
+compile_wildcard_2([], {root,PrefixLen,Root}) ->
+ {{exists,Root},PrefixLen}.
compile_wildcard_3([Part|Rest], Result) ->
compile_wildcard_3(Rest, [compile_part(Part)|Result]);
compile_wildcard_3([], Result) ->
- lists:reverse(Result).
+ case lists:reverse(Result) of
+ [{root,PrefixLen,Root}|Compiled] ->
+ {[Root|Compiled],PrefixLen};
+ [{cwd,Root}|Compiled] ->
+ {[Root|Compiled],length(filename:join(Root, "x"))-1}
+ end.
+
+compile_join({cwd,"."}, File) ->
+ {root,0,File};
+compile_join({cwd,Cwd}, File0) ->
+ File = filename:join([File0]),
+ Root = filename:join(Cwd, File),
+ PrefixLen = length(Root) - length(File),
+ {root,PrefixLen,Root};
+compile_join({root,PrefixLen,Root}, File) ->
+ {root,PrefixLen,filename:join(Root, File)}.
compile_part(Part) ->
compile_part(Part, false, []).
@@ -437,7 +411,7 @@ compile_part_to_sep(Part) ->
compile_part(Part, true, []).
compile_part([], true, _) ->
- error(missing_delimiter);
+ badpattern(missing_delimiter);
compile_part([$,|Rest], true, Result) ->
{ok, $,, lists:reverse(Result), Rest};
compile_part([$}|Rest], true, Result) ->
@@ -473,8 +447,6 @@ compile_part([], _Upto, Result) ->
compile_charset([$]|Rest], Ordset) ->
compile_charset1(Rest, ordsets:add_element($], Ordset));
-compile_charset([$-|Rest], Ordset) ->
- compile_charset1(Rest, ordsets:add_element($-, Ordset));
compile_charset([], _Ordset) ->
error;
compile_charset(List, Ordset) ->
@@ -483,7 +455,7 @@ compile_charset(List, Ordset) ->
compile_charset1([Lower, $-, Upper|Rest], Ordset) when Lower =< Upper ->
compile_charset1(Rest, compile_range(Lower, Upper, Ordset));
compile_charset1([$]|Rest], Ordset) ->
- {ok, {one_of, Ordset}, Rest};
+ {ok, {one_of, gb_sets:from_ordset(Ordset)}, Rest};
compile_charset1([X|Rest], Ordset) ->
compile_charset1(Rest, ordsets:add_element(X, Ordset));
compile_charset1([], _Ordset) ->
@@ -509,8 +481,8 @@ compile_alt(Pattern, Result) ->
error
end.
-error(Reason) ->
- erlang:error({badpattern,Reason}).
+badpattern(Reason) ->
+ error({badpattern,Reason}).
eval_read_file_info(File, file) ->
file:read_file_info(File);