aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src
diff options
context:
space:
mode:
authorPatrik Nyblom <[email protected]>2010-12-03 13:16:21 +0100
committerPatrik Nyblom <[email protected]>2010-12-03 13:16:21 +0100
commit159d79b6657e5bb4f3accb6a0d74b74f06da4ba2 (patch)
tree2e86c92a66ab581e15c577f99bd8225144b6a05b /lib/stdlib/src
parent6ea8348174c62812057dd552d0890b2d9d4a3c16 (diff)
downloadotp-159d79b6657e5bb4f3accb6a0d74b74f06da4ba2.tar.gz
otp-159d79b6657e5bb4f3accb6a0d74b74f06da4ba2.tar.bz2
otp-159d79b6657e5bb4f3accb6a0d74b74f06da4ba2.zip
Test and correct filelib and filename
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r--lib/stdlib/src/filelib.erl28
-rw-r--r--lib/stdlib/src/filename.erl28
2 files changed, 41 insertions, 15 deletions
diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index 04147d40d1..c845b61204 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -47,14 +47,14 @@ wildcard(Pattern) when is_list(Pattern) ->
?HANDLE_ERROR(do_wildcard(Pattern, file)).
-spec wildcard(file:name(), file:name() | atom()) -> [file:filename()].
-wildcard(Pattern, Cwd) when is_list(Pattern), is_list(Cwd) ->
+wildcard(Pattern, Cwd) when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)) ->
?HANDLE_ERROR(do_wildcard(Pattern, Cwd, file));
wildcard(Pattern, Mod) when is_list(Pattern), is_atom(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), is_atom(Mod) ->
+ when is_list(Pattern), (is_list(Cwd) or is_binary(Cwd)), is_atom(Mod) ->
?HANDLE_ERROR(do_wildcard(Pattern, Cwd, Mod)).
-spec is_dir(file:name()) -> boolean().
@@ -118,7 +118,7 @@ do_wildcard_comp({compiled_wildcard,{exists,File}}, 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) ->
+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) ->
@@ -127,9 +127,18 @@ do_wildcard_comp({compiled_wildcard,{exists,File}}, Cwd, Mod) ->
_ -> []
end;
do_wildcard_comp({compiled_wildcard,[current|Rest]}, Cwd0, Mod) ->
- Cwd = filename:join([Cwd0]), %Slash away redundant slashes.
- PrefixLen = length(Cwd)+1,
- [lists:nthtail(PrefixLen, N) || N <- do_wildcard_1([Cwd], Rest, Mod)];
+ {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).
@@ -276,6 +285,13 @@ 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]);
+ false ->
+ wildcard_4(Pattern, Rest, Base, Result)
+ end;
wildcard_4(Pattern, [File|Rest], Base, Result) ->
case wildcard_5(Pattern, File) of
true ->
diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl
index 9ca4b808e1..e38b8957f2 100644
--- a/lib/stdlib/src/filename.erl
+++ b/lib/stdlib/src/filename.erl
@@ -151,10 +151,10 @@ win_basenameb(O) ->
basenameb(O,[<<"/">>,<<"\\">>]).
basenameb(Bin,Sep) ->
Parts = [ X || X <- binary:split(Bin,Sep,[global]),
- X =:= <<>> ],
+ X =/= <<>> ],
if
Parts =:= [] ->
- [];
+ <<>>;
true ->
lists:last(Parts)
end.
@@ -201,17 +201,19 @@ basename(Name, Ext) when is_list(Name), is_binary(Ext) ->
basename(filename_string_to_binary(Name),Ext);
basename(Name, Ext) when is_binary(Name), is_binary(Ext) ->
BName = basename(Name),
+ LAll = byte_size(Name),
LN = byte_size(BName),
LE = byte_size(Ext),
case LN - LE of
Neg when Neg < 0 ->
BName;
Pos ->
- case BName of
- <<Part:Pos/binary,Ext/binary>> ->
+ StartLen = LAll - Pos - LE,
+ case Name of
+ <<_:StartLen/binary,Part:Pos/binary,Ext/binary>> ->
Part;
- Other ->
- Other
+ _Other ->
+ BName
end
end;
@@ -447,7 +449,7 @@ join1b(<<UcLetter, $:, Rest/binary>>, RelativeName, [], win32)
when is_integer(UcLetter), UcLetter >= $A, UcLetter =< $Z ->
join1b(Rest, RelativeName, [$:, UcLetter+$a-$A], win32);
join1b(<<$\\,Rest/binary>>, RelativeName, Result, win32) ->
- join1b(<<$/,Rest>>, RelativeName, Result, win32);
+ join1b(<<$/,Rest/binary>>, RelativeName, Result, win32);
join1b(<<$/,Rest/binary>>, RelativeName, [$., $/|Result], OsType) ->
join1b(Rest, RelativeName, [$/|Result], OsType);
join1b(<<$/,Rest/binary>>, RelativeName, [$/|Result], OsType) ->
@@ -546,6 +548,8 @@ win32_pathtype(_) -> relative.
%% rootname("/jam.src/foo.erl") -> "/jam.src/foo"
-spec rootname(file:name()) -> file:filename().
+rootname(Name) when is_binary(Name) ->
+ list_to_binary(rootname(binary_to_list(Name))); % No need to handle unicode, . is < 128
rootname(Name0) ->
Name = flatten(Name0),
rootname(Name, [], [], major_os_type()).
@@ -573,6 +577,12 @@ rootname([], Root, _Ext, _OsType) ->
%% rootname("/jam.src/foo.erl", ".erl") -> "/jam.src/foo"
-spec rootname(file:name(), file:name()) -> file:filename().
+rootname(Name, Ext) when is_binary(Name), is_binary(Ext) ->
+ list_to_binary(rootname(binary_to_list(Name),binary_to_list(Ext)));
+rootname(Name, Ext) when is_binary(Name) ->
+ rootname(Name,filename_string_to_binary(Ext));
+rootname(Name, Ext) when is_binary(Ext) ->
+ rootname(filename_string_to_binary(Name),Ext);
rootname(Name0, Ext0) ->
Name = flatten(Name0),
Ext = flatten(Ext0),
@@ -639,7 +649,7 @@ win32_splitb(<<Slash,Rest/binary>>) when ((Slash =:= $\\) orelse (Slash =:= $/))
[<<$/>> | [ X || X <- L, X =/= <<>> ]];
win32_splitb(Name) ->
L = binary:split(Name,[<<"/">>,<<"\\">>],[global]),
- [<<$/>> | [ X || X <- L, X =/= <<>> ]].
+ [ X || X <- L, X =/= <<>> ].
unix_split(Name) ->
@@ -900,7 +910,7 @@ do_flatten(Atom, Tail) when is_atom(Atom) ->
atom_to_list(Atom) ++ flatten(Tail).
filename_string_to_binary(List) ->
- case unicode:characters_to_binary(List,unicode,file:native_name_encoding()) of
+ case unicode:characters_to_binary(flatten(List),unicode,file:native_name_encoding()) of
{error,_,_} ->
erlang:error(badarg);
Bin when is_binary(Bin) ->