diff options
author | Patrik Nyblom <[email protected]> | 2010-12-03 15:38:14 +0100 |
---|---|---|
committer | Patrik Nyblom <[email protected]> | 2010-12-03 15:38:14 +0100 |
commit | 73b53fe24ebc595a81c4ee023bcfef5a71e59db4 (patch) | |
tree | ed75b935318dbef275d62ab141a5f59b5b36bce0 /lib/stdlib/src/filename.erl | |
parent | 52b0fbbc4daa4e22fcad6fe39dd8f8cec8bb8d1b (diff) | |
parent | 159d79b6657e5bb4f3accb6a0d74b74f06da4ba2 (diff) | |
download | otp-73b53fe24ebc595a81c4ee023bcfef5a71e59db4.tar.gz otp-73b53fe24ebc595a81c4ee023bcfef5a71e59db4.tar.bz2 otp-73b53fe24ebc595a81c4ee023bcfef5a71e59db4.zip |
Merge branch 'pan/unicode-filenames/OTP-8887' into dev
* pan/unicode-filenames/OTP-8887: (27 commits)
Test and correct filelib and filename
Add documentation to erlang.xml and slight correction to unicode_usage.xml
Add section about Unicode file names to stdlib users guide
Correct bug in file_name_SUITE making it fail on Unix instead of Windows7
Add documentation about raw filenames and Unicode file name translation mode
Make filelib not crash on re codepoints beyond 255 in re when filename is raw
Mend on_load_embedded testcase which did not handle windows links
Correct testcase regarding windows versions supporting soft links.
Teach filelib to use re in unicode mode when filenames are not raw
Treat soft links on Windows correctly in file_name_SUITE
Adapt new soft and hard link routines on Windos to Unicode
Corrected testcases broken by unicode filenames
Update preloaded prim_file
Teach prim_file not to accept atoms and not to throw exceptions
Adapt inet_drv to Visual Studio 2008
Teach spawn_executable about Unicode
Convert filenames read on MacOSX to canonical form
Teach file to accept codepoints beyond 255.
Add testcases
Correct shell utilities to handle unicode and possibly binaries
...
Diffstat (limited to 'lib/stdlib/src/filename.erl')
-rw-r--r-- | lib/stdlib/src/filename.erl | 424 |
1 files changed, 278 insertions, 146 deletions
diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl index 01c06e4596..e38b8957f2 100644 --- a/lib/stdlib/src/filename.erl +++ b/lib/stdlib/src/filename.erl @@ -41,6 +41,9 @@ -include_lib("kernel/include/file.hrl"). +-define(IS_DRIVELETTER(Letter),(((Letter >= $A) andalso (Letter =< $Z)) orelse + ((Letter >= $a) andalso (Letter =< $z)))). + %% Converts a relative filename to an absolute filename %% or the filename itself if it already is an absolute filename %% Note that no attempt is made to create the most beatiful @@ -57,12 +60,18 @@ %% (for Unix) : absname("/") -> "/" %% (for WIN32): absname("/") -> "D:/" --spec absname(file:name()) -> string(). + +-spec absname(file:name()) -> file:filename(). absname(Name) -> {ok, Cwd} = file:get_cwd(), absname(Name, Cwd). --spec absname(file:name(), string()) -> string(). +-spec absname(file:name(), file:filename()) -> file:filename(). +absname(Name, AbsBase) when is_binary(Name), is_list(AbsBase) -> + absname(Name,filename_string_to_binary(AbsBase)); +absname(Name, AbsBase) when is_list(Name), is_binary(AbsBase) -> + absname(filename_string_to_binary(Name),AbsBase); + absname(Name, AbsBase) -> case pathtype(Name) of relative -> @@ -77,6 +86,20 @@ absname(Name, AbsBase) -> %% Handles volumerelative names (on Windows only). +absname_vr([<<"/">>|Rest1], [Volume|_], _AbsBase) -> + %% Absolute path on current drive. + join([Volume|Rest1]); +absname_vr([<<X, $:>>|Rest1], [<<X,_/binary>>|_], AbsBase) -> + %% Relative to current directory on current drive. + absname(join(Rest1), AbsBase); +absname_vr([<<X, $:>>|Name], _, _AbsBase) -> + %% Relative to current directory on another drive. + Dcwd = + case file:get_cwd([X, $:]) of + {ok, Dir} -> filename_string_to_binary(Dir); + {error, _} -> <<X, $:, $/>> + end, + absname(join(Name), Dcwd); absname_vr(["/"|Rest1], [Volume|_], _AbsBase) -> %% Absolute path on current drive. join([Volume|Rest1]); @@ -92,41 +115,13 @@ absname_vr([[X, $:]|Name], _, _AbsBase) -> end, absname(join(Name), Dcwd). -%% Joins a relative filename to an absolute base. For VxWorks the -%% resulting name is fixed to minimize the length by collapsing -%% ".." directories. -%% For other systems this is just a join/2, but assumes that +%% Joins a relative filename to an absolute base. +%% This is just a join/2, but assumes that %% AbsBase must be absolute and Name must be relative. --spec absname_join(string(), file:name()) -> string(). +-spec absname_join(file:filename(), file:name()) -> file:filename(). absname_join(AbsBase, Name) -> - case major_os_type() of - vxworks -> - absname_pretty(AbsBase, split(Name), lists:reverse(split(AbsBase))); - _Else -> - join(AbsBase, flatten(Name)) - end. - -%% Handles absolute filenames for VxWorks - these are 'pretty-printed', -%% since a C function call chdir("/erlang/lib/../bin") really sets -%% cwd to '/erlang/lib/../bin' which also works, but the long term -%% effect is potentially not so good ... -%% -%% absname_pretty("../bin", "/erlang/lib") -> "/erlang/bin" -%% absname_pretty("../../../..", "/erlang") -> "/erlang" - -absname_pretty(Abspath, Relpath, []) -> - %% AbsBase _must_ begin with a vxworks device name - {device, _Rest, Dev} = vxworks_first(Abspath), - absname_pretty(Abspath, Relpath, [lists:reverse(Dev)]); -absname_pretty(_Abspath, [], AbsBase) -> - join(lists:reverse(AbsBase)); -absname_pretty(Abspath, [[$.]|Rest], AbsBase) -> - absname_pretty(Abspath, Rest, AbsBase); -absname_pretty(Abspath, [[$.,$.]|Rest], [_|AbsRest]) -> - absname_pretty(Abspath, Rest, AbsRest); -absname_pretty(Abspath, [First|Rest], AbsBase) -> - absname_pretty(Abspath, Rest, [First|AbsBase]). + join(AbsBase, flatten(Name)). %% Returns the part of the filename after the last directory separator, %% or the filename itself if it has no separators. @@ -136,12 +131,36 @@ absname_pretty(Abspath, [First|Rest], AbsBase) -> %% basename("/usr/foo/") -> "foo" (trailing slashes ignored) %% basename("/") -> [] --spec basename(file:name()) -> string(). +-spec basename(file:name()) -> file:filename(). +basename(Name) when is_binary(Name) -> + case os:type() of + {win32,_} -> + win_basenameb(Name); + _ -> + basenameb(Name,[<<"/">>]) + end; + basename(Name0) -> Name = flatten(Name0), {DirSep2, DrvSep} = separators(), basename1(skip_prefix(Name, DrvSep), [], DirSep2). +win_basenameb(<<Letter,$:,Rest/binary>>) when ?IS_DRIVELETTER(Letter) -> + basenameb(Rest,[<<"/">>,<<"\\">>]); +win_basenameb(O) -> + basenameb(O,[<<"/">>,<<"\\">>]). +basenameb(Bin,Sep) -> + Parts = [ X || X <- binary:split(Bin,Sep,[global]), + X =/= <<>> ], + if + Parts =:= [] -> + <<>>; + true -> + lists:last(Parts) + end. + + + basename1([$/|[]], Tail, DirSep2) -> basename1([], Tail, DirSep2); basename1([$/|Rest], _Tail, DirSep2) -> @@ -155,26 +174,11 @@ basename1([Char|Rest], Tail, DirSep2) when is_integer(Char) -> basename1([], Tail, _DirSep2) -> lists:reverse(Tail). -skip_prefix(Name, false) -> % No prefix for unix, but for VxWorks. - case major_os_type() of - vxworks -> - case vxworks_first(Name) of - {device, Rest, _Device} -> - Rest; - {not_device, _Rest, _First} -> - Name - end; - _Else -> - Name - end; -skip_prefix(Name, DrvSep) -> - skip_prefix1(Name, DrvSep). - -skip_prefix1([L, DrvSep|Name], DrvSep) when is_integer(L) -> +skip_prefix(Name, false) -> Name; -skip_prefix1([L], _) when is_integer(L) -> - [L]; -skip_prefix1(Name, _) -> +skip_prefix([L, DrvSep|Name], DrvSep) when ?IS_DRIVELETTER(L) -> + Name; +skip_prefix(Name, _) -> Name. %% Returns the last component of the filename, with the given @@ -190,7 +194,29 @@ skip_prefix1(Name, _) -> %% rootname(basename("xxx.jam")) -> "xxx" %% rootname(basename("xxx.erl")) -> "xxx" --spec basename(file:name(), file:name()) -> string(). +-spec basename(file:name(), file:name()) -> file:filename(). +basename(Name, Ext) when is_binary(Name), is_list(Ext) -> + basename(Name,filename_string_to_binary(Ext)); +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 -> + StartLen = LAll - Pos - LE, + case Name of + <<_:StartLen/binary,Part:Pos/binary,Ext/binary>> -> + Part; + _Other -> + BName + end + end; + basename(Name0, Ext0) -> Name = flatten(Name0), Ext = flatten(Ext0), @@ -204,7 +230,7 @@ basename([$/|[]], Ext, Tail, DrvSep2) -> basename([], Ext, Tail, DrvSep2); basename([$/|Rest], Ext, _Tail, DrvSep2) -> basename(Rest, Ext, [], DrvSep2); -basename([$\\|Rest], Ext, Tail, DirSep2) when is_integer(DirSep2) -> +basename([DirSep2|Rest], Ext, Tail, DirSep2) when is_integer(DirSep2) -> basename([$/|Rest], Ext, Tail, DirSep2); basename([Char|Rest], Ext, Tail, DrvSep2) when is_integer(Char) -> basename(Rest, Ext, [Char|Tail], DrvSep2); @@ -216,21 +242,43 @@ basename([], _Ext, Tail, _DrvSep2) -> %% Example: dirname("/usr/src/kalle.erl") -> "/usr/src", %% dirname("kalle.erl") -> "." --spec dirname(file:name()) -> string(). +-spec dirname(file:name()) -> file:filename(). +dirname(Name) when is_binary(Name) -> + {Dsep,Drivesep} = separators(), + SList = case Dsep of + Sep when is_integer(Sep) -> + [ <<Sep>> ]; + _ -> + [] + end, + {XPart0,Dirs} = case Drivesep of + X when is_integer(X) -> + case Name of + <<DL,X,Rest/binary>> when ?IS_DRIVELETTER(DL) -> + {<<DL,X>>,Rest}; + _ -> + {<<>>,Name} + end; + _ -> + {<<>>,Name} + end, + Parts0 = binary:split(Dirs,[<<"/">>|SList],[global]), + %% Fairly short lists of parts, OK to reverse twice... + Parts = case Parts0 of + [] -> []; + _ -> lists:reverse(fstrip(tl(lists:reverse(Parts0)))) + end, + XPart = case {Parts,XPart0} of + {[],<<>>} -> + <<".">>; + _ -> + XPart0 + end, + dirjoin(Parts,XPart,<<"/">>); + dirname(Name0) -> Name = flatten(Name0), - case os:type() of - vxworks -> - {Devicep, Restname, FirstComp} = vxworks_first(Name), - case Devicep of - device -> - dirname(Restname, FirstComp, [], separators()); - _ -> - dirname(Name, [], [], separators()) - end; - _ -> - dirname(Name, [], [], separators()) - end. + dirname(Name, [], [], separators()). dirname([[_|_]=List|Rest], Dir, File, Seps) -> dirname(List++Rest, Dir, File, Seps); @@ -258,6 +306,26 @@ dirname([], [DrvSep,Dl], File, {_,DrvSep}) -> end; dirname([], Dir, _, _) -> lists:reverse(Dir). + +%% Compatibility with lists variant, remove trailing slashes +fstrip([<<>>,X|Y]) -> + fstrip([X|Y]); +fstrip(A) -> + A. + + +dirjoin([<<>>|T],Acc,Sep) -> + dirjoin1(T,<<Acc/binary,"/">>,Sep); +dirjoin(A,B,C) -> + dirjoin1(A,B,C). + +dirjoin1([],Acc,_) -> + Acc; +dirjoin1([One],Acc,_) -> + <<Acc/binary,One/binary>>; +dirjoin1([H|T],Acc,Sep) -> + dirjoin(T,<<Acc/binary,H/binary,Sep/binary>>,Sep). + %% Given a filename string, returns the file extension, %% including the period. Returns an empty list if there @@ -268,7 +336,31 @@ dirname([], Dir, _, _) -> %% %% On Windows: fn:dirname("\\usr\\src/kalle.erl") -> "/usr/src" --spec extension(file:name()) -> string(). +-spec extension(file:name()) -> file:filename(). +extension(Name) when is_binary(Name) -> + {Dsep,_} = separators(), + SList = case Dsep of + Sep when is_integer(Sep) -> + [ <<Sep>> ]; + _ -> + [] + end, + case binary:matches(Name,[<<".">>]) of + nomatch -> % Bug in binary workaround :( + <<>>; + [] -> + <<>>; + List -> + {Pos,_} = lists:last(List), + <<_:Pos/binary,Part/binary>> = Name, + case binary:match(Part,[<<"/">>|SList]) of + nomatch -> + Part; + _ -> + <<>> + end + end; + extension(Name0) -> Name = flatten(Name0), extension(Name, [], major_os_type()). @@ -281,8 +373,6 @@ extension([$/|Rest], _Result, OsType) -> extension(Rest, [], OsType); extension([$\\|Rest], _Result, win32) -> extension(Rest, [], win32); -extension([$\\|Rest], _Result, vxworks) -> - extension(Rest, [], vxworks); extension([Char|Rest], Result, OsType) when is_integer(Char) -> extension(Rest, [Char|Result], OsType); extension([], Result, _OsType) -> @@ -290,23 +380,36 @@ extension([], Result, _OsType) -> %% Joins a list of filenames with directory separators. --spec join([string()]) -> string(). +-spec join([file:filename()]) -> file:filename(). join([Name1, Name2|Rest]) -> join([join(Name1, Name2)|Rest]); join([Name]) when is_list(Name) -> join1(Name, [], [], major_os_type()); +join([Name]) when is_binary(Name) -> + join1b(Name, <<>>, [], major_os_type()); join([Name]) when is_atom(Name) -> join([atom_to_list(Name)]). %% Joins two filenames with directory separators. --spec join(string(), string()) -> string(). +-spec join(file:filename(), file:filename()) -> file:filename(). join(Name1, Name2) when is_list(Name1), is_list(Name2) -> OsType = major_os_type(), case pathtype(Name2) of relative -> join1(Name1, Name2, [], OsType); _Other -> join1(Name2, [], [], OsType) end; +join(Name1, Name2) when is_binary(Name1), is_list(Name2) -> + join(Name1,filename_string_to_binary(Name2)); +join(Name1, Name2) when is_list(Name1), is_binary(Name2) -> + join(filename_string_to_binary(Name1),Name2); +join(Name1, Name2) when is_binary(Name1), is_binary(Name2) -> + OsType = major_os_type(), + case pathtype(Name2) of + relative -> join1b(Name1, Name2, [], OsType); + _Other -> join1b(Name2, <<>>, [], OsType) + end; + join(Name1, Name2) when is_atom(Name1) -> join(atom_to_list(Name1), Name2); join(Name1, Name2) when is_atom(Name2) -> @@ -321,8 +424,6 @@ when is_integer(UcLetter), UcLetter >= $A, UcLetter =< $Z -> join1(Rest, RelativeName, [$:, UcLetter+$a-$A], win32); join1([$\\|Rest], RelativeName, Result, win32) -> join1([$/|Rest], RelativeName, Result, win32); -join1([$\\|Rest], RelativeName, Result, vxworks) -> - join1([$/|Rest], RelativeName, Result, vxworks); join1([$/|Rest], RelativeName, [$., $/|Result], OsType) -> join1(Rest, RelativeName, [$/|Result], OsType); join1([$/|Rest], RelativeName, [$/|Result], OsType) -> @@ -344,6 +445,26 @@ join1([Char|Rest], RelativeName, Result, OsType) when is_integer(Char) -> join1([Atom|Rest], RelativeName, Result, OsType) when is_atom(Atom) -> join1(atom_to_list(Atom)++Rest, RelativeName, Result, OsType). +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/binary>>, RelativeName, Result, win32); +join1b(<<$/,Rest/binary>>, RelativeName, [$., $/|Result], OsType) -> + join1b(Rest, RelativeName, [$/|Result], OsType); +join1b(<<$/,Rest/binary>>, RelativeName, [$/|Result], OsType) -> + join1b(Rest, RelativeName, [$/|Result], OsType); +join1b(<<>>, <<>>, Result, OsType) -> + list_to_binary(maybe_remove_dirsep(Result, OsType)); +join1b(<<>>, RelativeName, [$:|Rest], win32) -> + join1b(RelativeName, <<>>, [$:|Rest], win32); +join1b(<<>>, RelativeName, [$/|Result], OsType) -> + join1b(RelativeName, <<>>, [$/|Result], OsType); +join1b(<<>>, RelativeName, Result, OsType) -> + join1b(RelativeName, <<>>, [$/|Result], OsType); +join1b(<<Char,Rest/binary>>, RelativeName, Result, OsType) when is_integer(Char) -> + join1b(Rest, RelativeName, [Char|Result], OsType). + maybe_remove_dirsep([$/, $:, Letter], win32) -> [Letter, $:, $/]; maybe_remove_dirsep([$/], _) -> @@ -357,7 +478,7 @@ maybe_remove_dirsep(Name, _) -> %% a given base directory, which is is assumed to be normalised %% by a previous call to join/{1,2}. --spec append(string(), file:name()) -> string(). +-spec append(file:filename(), file:name()) -> file:filename(). append(Dir, Name) -> Dir ++ [$/|Name]. @@ -376,19 +497,14 @@ append(Dir, Name) -> -spec pathtype(file:name()) -> 'absolute' | 'relative' | 'volumerelative'. pathtype(Atom) when is_atom(Atom) -> pathtype(atom_to_list(Atom)); -pathtype(Name) when is_list(Name) -> +pathtype(Name) when is_list(Name) or is_binary(Name) -> case os:type() of {unix, _} -> unix_pathtype(Name); - {win32, _} -> win32_pathtype(Name); - vxworks -> case vxworks_first(Name) of - {device, _Rest, _Dev} -> - absolute; - _ -> - relative - end; - {ose,_} -> unix_pathtype(Name) + {win32, _} -> win32_pathtype(Name) end. +unix_pathtype(<<$/,_/binary>>) -> + absolute; unix_pathtype([$/|_]) -> absolute; unix_pathtype([List|Rest]) when is_list(List) -> @@ -404,6 +520,15 @@ win32_pathtype([Atom|Rest]) when is_atom(Atom) -> win32_pathtype(atom_to_list(Atom)++Rest); win32_pathtype([Char, List|Rest]) when is_list(List) -> win32_pathtype([Char|List++Rest]); +win32_pathtype(<<$/, $/, _/binary>>) -> absolute; +win32_pathtype(<<$\\, $/, _/binary>>) -> absolute; +win32_pathtype(<<$/, $\\, _/binary>>) -> absolute; +win32_pathtype(<<$\\, $\\, _/binary>>) -> absolute; +win32_pathtype(<<$/, _/binary>>) -> volumerelative; +win32_pathtype(<<$\\, _/binary>>) -> volumerelative; +win32_pathtype(<<_Letter, $:, $/, _/binary>>) -> absolute; +win32_pathtype(<<_Letter, $:, $\\, _/binary>>) -> absolute; +win32_pathtype(<<_Letter, $:, _/binary>>) -> volumerelative; win32_pathtype([$/, $/|_]) -> absolute; win32_pathtype([$\\, $/|_]) -> absolute; win32_pathtype([$/, $\\|_]) -> absolute; @@ -422,7 +547,9 @@ win32_pathtype(_) -> relative. %% Examples: rootname("/jam.src/kalle") -> "/jam.src/kalle" %% rootname("/jam.src/foo.erl") -> "/jam.src/foo" --spec rootname(file:name()) -> string(). +-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()). @@ -431,8 +558,6 @@ rootname([$/|Rest], Root, Ext, OsType) -> rootname(Rest, [$/]++Ext++Root, [], OsType); rootname([$\\|Rest], Root, Ext, win32) -> rootname(Rest, [$/]++Ext++Root, [], win32); -rootname([$\\|Rest], Root, Ext, vxworks) -> - rootname(Rest, [$/]++Ext++Root, [], vxworks); rootname([$.|Rest], Root, [], OsType) -> rootname(Rest, Root, ".", OsType); rootname([$.|Rest], Root, Ext, OsType) -> @@ -451,7 +576,13 @@ rootname([], Root, _Ext, _OsType) -> %% Examples: rootname("/jam.src/kalle.jam", ".erl") -> "/jam.src/kalle.jam" %% rootname("/jam.src/foo.erl", ".erl") -> "/jam.src/foo" --spec rootname(file:name(), file:name()) -> string(). +-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), @@ -471,27 +602,55 @@ rootname2([Char|Rest], Ext, Result) when is_integer(Char) -> %% split("foo/bar") -> ["foo", "bar"] %% split("a:\\msdev\\include") -> ["a:/", "msdev", "include"] --spec split(file:name()) -> [string()]. +-spec split(file:name()) -> [file:filename()]. +split(Name) when is_binary(Name) -> + case os:type() of + {win32, _} -> win32_splitb(Name); + _ -> unix_splitb(Name) + end; + split(Name0) -> Name = flatten(Name0), case os:type() of - {unix, _} -> unix_split(Name); {win32, _} -> win32_split(Name); - vxworks -> vxworks_split(Name); - {ose,_} -> unix_split(Name) + _ -> unix_split(Name) end. -%% If a VxWorks filename starts with '[/\].*[^/\]' '[/\].*:' or '.*:' -%% that part of the filename is considered a device. -%% The rest of the name is interpreted exactly as for win32. -%% XXX - dirty solution to make filename:split([]) return the same thing on -%% VxWorks as on unix and win32. -vxworks_split([]) -> - []; -vxworks_split(L) -> - {_Devicep, Rest, FirstComp} = vxworks_first(L), - split(Rest, [], [lists:reverse(FirstComp)], win32). +unix_splitb(Name) -> + L = binary:split(Name,[<<"/">>],[global]), + LL = case L of + [<<>>|Rest] -> + [<<"/">>|Rest]; + _ -> + L + end, + [ X || X <- LL, X =/= <<>>]. + + +fix_driveletter(Letter0) -> + if + Letter0 >= $A, Letter0 =< $Z -> + Letter0+$a-$A; + true -> + Letter0 + end. +win32_splitb(<<Letter0,$:, Slash, Rest/binary>>) when (((Slash =:= $\\) orelse (Slash =:= $/)) andalso + ?IS_DRIVELETTER(Letter0)) -> + Letter = fix_driveletter(Letter0), + L = binary:split(Rest,[<<"/">>,<<"\\">>],[global]), + [<<Letter,$:,$/>> | [ X || X <- L, X =/= <<>> ]]; +win32_splitb(<<Letter0,$:,Rest/binary>>) when ?IS_DRIVELETTER(Letter0) -> + Letter = fix_driveletter(Letter0), + L = binary:split(Rest,[<<"/">>,<<"\\">>],[global]), + [<<Letter,$:>> | [ X || X <- L, X =/= <<>> ]]; +win32_splitb(<<Slash,Rest/binary>>) when ((Slash =:= $\\) orelse (Slash =:= $/)) -> + L = binary:split(Rest,[<<"/">>,<<"\\">>],[global]), + [<<$/>> | [ X || X <- L, X =/= <<>> ]]; +win32_splitb(Name) -> + L = binary:split(Name,[<<"/">>,<<"\\">>],[global]), + [ X || X <- L, X =/= <<>> ]. + unix_split(Name) -> split(Name, [], unix). @@ -502,8 +661,6 @@ win32_split([X, $\\|Rest]) when is_integer(X) -> win32_split([X, $/|Rest]); win32_split([X, Y, $\\|Rest]) when is_integer(X), is_integer(Y) -> win32_split([X, Y, $/|Rest]); -win32_split([$/, $/|Rest]) -> - split(Rest, [], [[$/, $/]]); win32_split([UcLetter, $:|Rest]) when UcLetter >= $A, UcLetter =< $Z -> win32_split([UcLetter+$a-$A, $:|Rest]); win32_split([Letter, $:, $/|Rest]) -> @@ -540,7 +697,7 @@ split([], Comp, Components, OsType) -> %% will be converted to backslashes. On all platforms, the %% name will be normalized as done by join/1. --spec nativename(string()) -> string(). +-spec nativename(file:filename()) -> file:filename(). nativename(Name0) -> Name = join([Name0]), %Normalize. case os:type() of @@ -557,13 +714,12 @@ win32_nativename([]) -> separators() -> case os:type() of - {unix, _} -> {false, false}; {win32, _} -> {$\\, $:}; - vxworks -> {$\\, false}; - {ose,_} -> {false, false} + _ -> {false, false} end. + %% find_src(Module) -- %% find_src(Module, Rules) -- %% @@ -733,45 +889,12 @@ major_os_type() -> OsT -> OsT end. -%% Need to take care of the first pathname component separately -%% due to VxWorks less than good device naming rules. -%% (i.e. this is VxWorks specific ...) -%% The following four all starts with device names -%% elrond:/foo -> elrond: -%% elrond:\\foo.bar -> elrond: -%% /DISK1:foo -> /DISK1: -%% /usr/include -> /usr -%% This one doesn't: -%% foo/bar - -vxworks_first([]) -> - {not_device, [], []}; -vxworks_first([$/|T]) -> - vxworks_first2(device, T, [$/]); -vxworks_first([$\\|T]) -> - vxworks_first2(device, T, [$/]); -vxworks_first([H|T]) when is_list(H) -> - vxworks_first(H++T); -vxworks_first([H|T]) -> - vxworks_first2(not_device, T, [H]). - -vxworks_first2(Devicep, [], FirstComp) -> - {Devicep, [], FirstComp}; -vxworks_first2(Devicep, [$/|T], FirstComp) -> - {Devicep, [$/|T], FirstComp}; -vxworks_first2(Devicep, [$\\|T], FirstComp) -> - {Devicep, [$/|T], FirstComp}; -vxworks_first2(_Devicep, [$:|T], FirstComp)-> - {device, T, [$:|FirstComp]}; -vxworks_first2(Devicep, [H|T], FirstComp) when is_list(H) -> - vxworks_first2(Devicep, H++T, FirstComp); -vxworks_first2(Devicep, [H|T], FirstComp) -> - vxworks_first2(Devicep, T, [H|FirstComp]). - %% flatten(List) %% Flatten a list, also accepting atoms. --spec flatten(file:name()) -> string(). +-spec flatten(file:name()) -> file:filename(). +flatten(Bin) when is_binary(Bin) -> + Bin; flatten(List) -> do_flatten(List, []). @@ -785,3 +908,12 @@ do_flatten([], Tail) -> Tail; do_flatten(Atom, Tail) when is_atom(Atom) -> atom_to_list(Atom) ++ flatten(Tail). + +filename_string_to_binary(List) -> + case unicode:characters_to_binary(flatten(List),unicode,file:native_name_encoding()) of + {error,_,_} -> + erlang:error(badarg); + Bin when is_binary(Bin) -> + Bin + end. + |