aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/filename.erl
diff options
context:
space:
mode:
authorRichard Carlsson <[email protected]>2017-01-18 18:28:47 +0100
committerRichard Carlsson <[email protected]>2017-02-04 16:43:54 +0100
commit57aaf7d0c7c75cfd8c6b55c21d977b695f460022 (patch)
treed9785888f7a4a710ba3557ad2ce9a43d9bee5750 /lib/stdlib/src/filename.erl
parent6fff0463013f87963be707b80664bc209a1c4c16 (diff)
downloadotp-57aaf7d0c7c75cfd8c6b55c21d977b695f460022.tar.gz
otp-57aaf7d0c7c75cfd8c6b55c21d977b695f460022.tar.bz2
otp-57aaf7d0c7c75cfd8c6b55c21d977b695f460022.zip
Add filelib:find_file/2/3 and filelib:find_source/1/2/3
This moves, extends and exports functionality that previously existed only internally in filename:find_src/1/2, adding the ability to automatically substitute file suffixes and use different rules for different suffixes.
Diffstat (limited to 'lib/stdlib/src/filename.erl')
-rw-r--r--lib/stdlib/src/filename.erl74
1 files changed, 16 insertions, 58 deletions
diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl
index 51d5ca711d..0ff22f876a 100644
--- a/lib/stdlib/src/filename.erl
+++ b/lib/stdlib/src/filename.erl
@@ -34,8 +34,8 @@
-export([absname/1, absname/2, absname_join/2,
basename/1, basename/2, dirname/1,
extension/1, join/1, join/2, pathtype/1,
- rootname/1, rootname/2, split/1, nativename/1]).
--export([find_src/1, find_src/2, flatten/1]).
+ rootname/1, rootname/2, split/1, flatten/1, nativename/1]).
+-export([find_src/1, find_src/2]). % deprecated
-export([basedir/2, basedir/3]).
%% Undocumented and unsupported exports.
@@ -750,8 +750,12 @@ separators() ->
_ -> {false, false}
end.
-
-
+%% NOTE: The find_src/1/2 functions are deprecated; they try to do too much
+%% at once and are not a good fit for this module. Parts of the code have
+%% been moved to filelib:find_file/2 instead. Only this part of this
+%% module is allowed to call the filelib module; such mutual dependency
+%% should otherwise be avoided! This code should eventually be removed.
+%%
%% find_src(Module) --
%% find_src(Module, Rules) --
%%
@@ -815,26 +819,27 @@ find_src(ModOrFile, Rules) when is_list(ModOrFile) ->
case code:which(Mod) of
Possibly_Rel_Path when is_list(Possibly_Rel_Path) ->
{ok, Cwd} = file:get_cwd(),
- Dir = dirname(make_abs_path(Cwd, Possibly_Rel_Path)),
- find_src_1(ModOrFile, Dir, Mod, Extension, Rules);
+ ObjPath = make_abs_path(Cwd, Possibly_Rel_Path),
+ find_src_1(ModOrFile, ObjPath, Mod, Extension, Rules);
Ecode when is_atom(Ecode) -> % Ecode :: ecode()
{error, {Ecode, Mod}}
end.
%% At this point, the Mod is known to be valid.
%% If the source name is not known, find it.
-find_src_1(ModOrFile, Dir, Mod, Extension, Rules) ->
+find_src_1(ModOrFile, ObjPath, Mod, Extension, Rules) ->
%% The documentation says this function must return the found path
%% without extension in all cases. Also, ModOrFile could be given with
%% or without extension. Hence the calls to rootname below.
ModOrFileRoot = rootname(ModOrFile, Extension),
- case readable_file(ModOrFileRoot++Extension) of
+ case filelib:is_regular(ModOrFileRoot++Extension) of
true ->
find_src_2(ModOrFileRoot, Mod);
false ->
- case get_source_file(Dir, atom_to_list(Mod)++Extension, Rules) of
- {ok, Src} ->
- find_src_2(rootname(Src, Extension), Mod);
+ SrcName = basename(ObjPath, code:objfile_extension()) ++ Extension,
+ case filelib:find_file(SrcName, dirname(ObjPath), Rules) of
+ {ok, SrcFile} ->
+ find_src_2(rootname(SrcFile, Extension), Mod);
Error ->
Error
end
@@ -879,53 +884,6 @@ filter_options(Base, [_|Rest], Result) ->
filter_options(_Base, [], Result) ->
Result.
-%% Gets the source file given the object directory.
-
-get_source_file(Dir, Filename, []) ->
- Rules =
- case application:get_env(kernel, source_search_rules) of
- undefined -> default_source_search_rules();
- {ok, []} -> default_source_search_rules();
- {ok, R} when is_list(R) -> R
- end,
- get_source_file(Dir, Filename, Rules);
-get_source_file(Dir, Filename, Rules) ->
- source_by_rules(Dir, Filename, Rules).
-
-default_source_search_rules() ->
- [{"", ""}, {"ebin", "src"}, {"ebin", "esrc"}].
-
-source_by_rules(Dir, Filename, [{From, To}|Rest]) ->
- case try_rule(Dir, Filename, From, To) of
- {ok, File} -> {ok, File};
- error -> source_by_rules(Dir, Filename, Rest)
- end;
-source_by_rules(_Dir, _Filename, []) ->
- {error, source_file_not_found}.
-
-try_rule(Dir, Filename, From, To) ->
- case lists:suffix(From, Dir) of
- true ->
- NewDir = lists:sublist(Dir, 1, length(Dir)-length(From))++To,
- Src = join(NewDir, Filename),
- case readable_file(Src) of
- true -> {ok, Src};
- false -> error
- end;
- false ->
- error
- end.
-
-readable_file(File) ->
- case file:read_file_info(File) of
- {ok, #file_info{type=regular, access=read}} ->
- true;
- {ok, #file_info{type=regular, access=read_write}} ->
- true;
- _Other ->
- false
- end.
-
make_abs_path(BasePath, Path) ->
join(BasePath, Path).