File 2333-Add-filelib-find_file-2-3-and-filelib-find_source-1-.patch of Package erlang

From 57aaf7d0c7c75cfd8c6b55c21d977b695f460022 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <richardc@klarna.com>
Date: Wed, 18 Jan 2017 18:28:47 +0100
Subject: [PATCH 3/8] 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.
---
 lib/stdlib/doc/src/filelib.xml    |  54 ++++++++++++++++-
 lib/stdlib/src/filelib.erl        | 122 ++++++++++++++++++++++++++++++++++++++
 lib/stdlib/src/filename.erl       |  74 +++++------------------
 lib/stdlib/test/filelib_SUITE.erl |  55 ++++++++++++++++-
 4 files changed, 243 insertions(+), 62 deletions(-)

diff --git a/lib/stdlib/doc/src/filelib.xml b/lib/stdlib/doc/src/filelib.xml
index 7c6380ce2..ad73fc254 100644
--- a/lib/stdlib/doc/src/filelib.xml
+++ b/lib/stdlib/doc/src/filelib.xml
@@ -60,6 +60,12 @@
     <datatype>
       <name name="filename_all"/>
     </datatype>
+    <datatype>
+      <name name="find_file_rule"/>
+    </datatype>
+    <datatype>
+      <name name="find_source_rule"/>
+    </datatype>
   </datatypes>
 
   <funcs>
@@ -226,7 +232,51 @@ filelib:wildcard("lib/**/*.{erl,hrl}")</code>
           directory.</p>
       </desc>
     </func>
+
+    <func>
+      <name name="find_file" arity="2"/>
+      <name name="find_file" arity="3"/>
+      <fsummary>Find a file relative to a given directory.</fsummary>
+      <desc>
+        <p>Looks for a file of the given name by applying suffix rules to
+        the given directory path. For example, a rule <c>{"ebin", "src"}</c>
+        means that if the directory path ends with <c>"ebin"</c>, the
+        corresponding path ending in <c>"src"</c> should be searched.</p>
+        <p>If <c><anno>Rules</anno></c> is left out or is an empty list, the
+        default system rules are used. See also the Kernel application
+        parameter <seealso
+        marker="kernel:kernel_app#source_search_rules"><c>source_search_rules</c></seealso>.</p>
+      </desc>
+    </func>
+    <func>
+      <name name="find_source" arity="1"/>
+      <fsummary>Find the source file for a given object file.</fsummary>
+      <desc>
+        <p>Equivalent to <c>find_source(Base, Dir)</c>, where <c>Dir</c> is
+        <c>filename:dirname(<anno>FilePath</anno>)</c> and <c>Base</c> is
+        <c>filename:basename(<anno>FilePath</anno>)</c>.</p>
+      </desc>
+    </func>
+    <func>
+      <name name="find_source" arity="2"/>
+      <name name="find_source" arity="3"/>
+      <fsummary>Find a source file relative to a given directory.</fsummary>
+      <desc>
+        <p>Applies file extension specific rules to find the source file for
+        a given object file relative to the object directory. For example,
+        for a file with the extension <c>.beam</c>, the default rule is to
+        look for a file with a corresponding extension <c>.erl</c> by
+        replacing the suffix <c>"ebin"</c> of the object directory path with
+        <c>"src"</c>.
+        The file search is done through <seealso
+        marker="#find_file/3"><c>find_file/3</c></seealso>. The directory of
+        the object file is always tried before any other directory specified
+        by the rules.</p>
+        <p>If <c><anno>Rules</anno></c> is left out or is an empty list, the
+        default system rules are used. See also the Kernel application
+        parameter <seealso
+        marker="kernel:kernel_app#source_search_rules"><c>source_search_rules</c></seealso>.</p>
+      </desc>
+    </func>
   </funcs>
 </erlref>
-
-
diff --git a/lib/stdlib/src/filelib.erl b/lib/stdlib/src/filelib.erl
index 7029389e2..daa18da9a 100644
--- a/lib/stdlib/src/filelib.erl
+++ b/lib/stdlib/src/filelib.erl
@@ -24,6 +24,7 @@
 -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]).
+-export([find_file/2, find_file/3, find_source/1, find_source/2, find_source/3]).
 
 %% For debugging/testing.
 -export([compile_wildcard/1]).
@@ -517,3 +518,124 @@ eval_list_dir(Dir, erl_prim_loader) ->
     end;
 eval_list_dir(Dir, Mod) ->
     Mod:list_dir(Dir).
+
+%% Getting the rules to use for file search
+
+keep_dir_search_rules(Rules) ->
+    [T || {_,_}=T <- Rules].
+
+keep_suffix_search_rules(Rules) ->
+    [T || {_,_,_}=T <- Rules].
+
+get_search_rules() ->
+    case application:get_env(kernel, source_search_rules) of
+        undefined -> default_search_rules();
+        {ok, []}  -> default_search_rules();
+        {ok, R} when is_list(R) -> R
+    end.
+
+default_search_rules() ->
+    [%% suffix-speficic rules for source search
+     {".beam", ".erl", erl_source_search_rules()},
+     {".erl", ".yrl", []},
+     {"", ".src", erl_source_search_rules()},
+     {".so", ".c", c_source_search_rules()},
+     {".o", ".c", c_source_search_rules()},
+     {"", ".c", c_source_search_rules()},
+     {"", ".in", basic_source_search_rules()},
+     %% plain old directory rules, backwards compatible
+     {"", ""},
+     {"ebin","src"},
+     {"ebin","esrc"}
+    ].
+
+basic_source_search_rules() ->
+    (erl_source_search_rules()
+     ++ c_source_search_rules()).
+
+erl_source_search_rules() ->
+    [{"ebin","src"}, {"ebin","esrc"}].
+
+c_source_search_rules() ->
+    [{"priv","c_src"}, {"priv","src"}, {"bin","c_src"}, {"bin","src"}, {"", "src"}].
+
+%% Looks for a file relative to a given directory
+
+-type find_file_rule() :: {ObjDirSuffix::string(), SrcDirSuffix::string()}.
+
+-spec find_file(filename(), filename()) ->
+        {ok, filename()} | {error, not_found}.
+find_file(Filename, Dir) ->
+    find_file(Filename, Dir, []).
+
+-spec find_file(filename(), filename(), [find_file_rule()]) ->
+        {ok, filename()} | {error, not_found}.
+find_file(Filename, Dir, []) ->
+    find_file(Filename, Dir, get_search_rules());
+find_file(Filename, Dir, Rules) ->
+    try_dir_rules(keep_dir_search_rules(Rules), Filename, Dir).
+
+%% Looks for a source file relative to the object file name and directory
+
+-type find_source_rule() :: {ObjExtension::string(), SrcExtension::string(),
+                             [find_file_rule()]}.
+
+-spec find_source(filename()) ->
+        {ok, filename()} | {error, not_found}.
+find_source(FilePath) ->
+    find_source(filename:basename(FilePath), filename:dirname(FilePath)).
+
+-spec find_source(filename(), filename()) ->
+        {ok, filename()} | {error, not_found}.
+find_source(Filename, Dir) ->
+    find_source(Filename, Dir, []).
+
+-spec find_source(filename(), filename(), [find_source_rule()]) ->
+        {ok, filename()} | {error, not_found}.
+find_source(Filename, Dir, []) ->
+    find_source(Filename, Dir, get_search_rules());
+find_source(Filename, Dir, Rules) ->
+    try_suffix_rules(keep_suffix_search_rules(Rules), Filename, Dir).
+
+try_suffix_rules(Rules, Filename, Dir) ->
+    Ext = filename:extension(Filename),
+    try_suffix_rules(Rules, filename:rootname(Filename, Ext), Dir, Ext).
+
+try_suffix_rules([{Ext,Src,Rules}|Rest], Root, Dir, Ext)
+  when is_list(Src), is_list(Rules) ->
+    case try_dir_rules(add_local_search(Rules), Root ++ Src, Dir) of
+        {ok, File} -> {ok, File};
+        _Other ->
+            try_suffix_rules(Rest, Root, Dir, Ext)
+    end;
+try_suffix_rules([_|Rest], Root, Dir, Ext) ->
+    try_suffix_rules(Rest, Root, Dir, Ext);
+try_suffix_rules([], _Root, _Dir, _Ext) ->
+    {error, not_found}.
+
+%% ensuring we check the directory of the object file before any other directory
+add_local_search(Rules) ->
+    Local = {"",""},
+    [Local] ++ lists:filter(fun (X) -> X =/= Local end, Rules).
+
+try_dir_rules([{From, To}|Rest], Filename, Dir)
+  when is_list(From), is_list(To) ->
+    case try_dir_rule(Dir, Filename, From, To) of
+	{ok, File} -> {ok, File};
+	error      -> try_dir_rules(Rest, Filename, Dir)
+    end;
+try_dir_rules([], _Filename, _Dir) ->
+    {error, not_found}.
+
+try_dir_rule(Dir, Filename, From, To) ->
+    case lists:suffix(From, Dir) of
+	true ->
+	    NewDir = lists:sublist(Dir, 1, length(Dir)-length(From))++To,
+	    Src = filename:join(NewDir, Filename),
+	    case is_regular(Src) of
+		true -> {ok, Src};
+		false -> error
+	    end;
+	false ->
+	    error
+    end.
diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl
index 51d5ca711..0ff22f876 100644
--- a/lib/stdlib/src/filename.erl
+++ b/lib/stdlib/src/filename.erl
@@ -34,9 +34,9 @@
 -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,
+	 rootname/1, rootname/2, split/1, flatten/1, nativename/1,
          safe_relative_path/1]).
--export([find_src/1, find_src/2, flatten/1]).
+-export([find_src/1, find_src/2]). % deprecated
 -export([basedir/2, basedir/3]).
 
 %% Undocumented and unsupported exports.
@@ -750,8 +750,12 @@ separators() ->
 climb(T, [_|Acc]) ->
     safe_relative_path_1(T, Acc).
 
-
-
+%% 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).
 
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 4f8936edb..87fba815d 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -25,7 +25,8 @@
 	 init_per_testcase/2,end_per_testcase/2,
 	 wildcard_one/1,wildcard_two/1,wildcard_errors/1,
 	 fold_files/1,otp_5960/1,ensure_dir_eexist/1,ensure_dir_symlink/1,
-	 wildcard_symlink/1, is_file_symlink/1, file_props_symlink/1]).
+	 wildcard_symlink/1, is_file_symlink/1, file_props_symlink/1,
+         find_source/1]).
 
 -import(lists, [foreach/2]).
 
@@ -45,7 +46,8 @@ suite() ->
 all() -> 
     [wildcard_one, wildcard_two, wildcard_errors,
      fold_files, otp_5960, ensure_dir_eexist, ensure_dir_symlink,
-     wildcard_symlink, is_file_symlink, file_props_symlink].
+     wildcard_symlink, is_file_symlink, file_props_symlink,
+     find_source].
 
 groups() -> 
     [].
@@ -503,3 +505,52 @@ file_props_symlink(Config) ->
 	    FileSize = filelib:file_size(Alias, erl_prim_loader),
 	    FileSize = filelib:file_size(Alias, prim_file)
     end.
+
+find_source(Config) when is_list(Config) ->
+    BeamFile = code:which(lists),
+    BeamName = filename:basename(BeamFile),
+    BeamDir = filename:dirname(BeamFile),
+    SrcName = filename:basename(BeamFile, ".beam") ++ ".erl",
+
+    {ok, BeamFile} = filelib:find_file(BeamName, BeamDir),
+    {ok, BeamFile} = filelib:find_file(BeamName, BeamDir, []),
+    {ok, BeamFile} = filelib:find_file(BeamName, BeamDir, [{"",""},{"ebin","src"}]),
+    {error, not_found} = filelib:find_file(BeamName, BeamDir, [{"ebin","src"}]),
+
+    {ok, SrcFile} = filelib:find_file(SrcName, BeamDir),
+    {ok, SrcFile} = filelib:find_file(SrcName, BeamDir, []),
+    {ok, SrcFile} = filelib:find_file(SrcName, BeamDir, [{"foo","bar"},{"ebin","src"}]),
+    {error, not_found} = filelib:find_file(SrcName, BeamDir, [{"",""}]),
+
+    {ok, SrcFile} = filelib:find_source(BeamFile),
+    {ok, SrcFile} = filelib:find_source(BeamName, BeamDir),
+    {ok, SrcFile} = filelib:find_source(BeamName, BeamDir,
+                                         [{".erl",".yrl",[{"",""}]},
+                                          {".beam",".erl",[{"ebin","src"}]}]),
+    {error, not_found} = filelib:find_source(BeamName, BeamDir,
+                                              [{".erl",".yrl",[{"",""}]}]),
+
+    {ok, ParserErl} = filelib:find_source(code:which(erl_parse)),
+    {ok, ParserYrl} = filelib:find_source(ParserErl),
+    "lry." ++ _ = lists:reverse(ParserYrl),
+    {ok, ParserYrl} = filelib:find_source(ParserErl,
+                                           [{".beam",".erl",[{"ebin","src"}]},
+                                            {".erl",".yrl",[{"",""}]}]),
+
+    %% find_source automatically checks the local directory regardless of rules
+    {ok, ParserYrl} = filelib:find_source(ParserErl),
+    {ok, ParserYrl} = filelib:find_source(ParserErl,
+                                          [{".beam",".erl",[{"ebin","src"}]}]),
+
+    %% find_file does not check the local directory unless in the rules
+    ParserYrlName = filename:basename(ParserYrl),
+    ParserYrlDir = filename:dirname(ParserYrl),
+    {ok, ParserYrl} = filelib:find_file(ParserYrlName, ParserYrlDir,
+                                        [{"",""}]),
+    {error, not_found} = filelib:find_file(ParserYrlName, ParserYrlDir,
+                                           [{"ebin","src"}]),
+
+    %% local directory is in the default list for find_file
+    {ok, ParserYrl} = filelib:find_file(ParserYrlName, ParserYrlDir),
+    {ok, ParserYrl} = filelib:find_file(ParserYrlName, ParserYrlDir, []),
+    ok.
-- 
2.11.1

openSUSE Build Service is sponsored by