Skip to content

Commit fbb8263

Browse files
authored
Merge pull request #2904 from ariel-anieli/filelib-file-source
Replaced rebar_utils:find_source/3 by a call to filelib:find_source/3
2 parents 1ed6c2e + 7dadaf5 commit fbb8263

File tree

2 files changed

+2
-74
lines changed

2 files changed

+2
-74
lines changed

apps/rebar/rebar.config

+1-3
Original file line numberDiff line numberDiff line change
@@ -34,9 +34,7 @@
3434

3535
{overrides, [{add, relx, [{erl_opts, [{d, 'RLX_LOG', rebar_log}]}]}]}.
3636

37-
{erl_opts, [warnings_as_errors,
38-
{platform_define, "^(2[1-9])|(20\\\\.3)", filelib_find_source}
39-
]}.
37+
{erl_opts, [warnings_as_errors]}.
4038

4139
{edoc_opts, [preprocess]}.
4240

apps/rebar/src/rebar_utils.erl

+1-71
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@
2525
%% THE SOFTWARE.
2626
%% -------------------------------------------------------------------
2727
-module(rebar_utils).
28-
-deprecated({find_source, 3, "Instead, use filelib:find_source/3"}).
28+
2929
-export([sort_deps/1,
3030
droplast/1,
3131
filtermap/2,
@@ -1213,75 +1213,5 @@ version_pad([Major, Minor, Patch | _]) ->
12131213
{list_to_integer(Major), list_to_integer(Minor), list_to_integer(Patch)}.
12141214

12151215

1216-
-ifdef(filelib_find_source).
12171216
find_source(Filename, Dir, Rules) ->
12181217
filelib:find_source(Filename, Dir, Rules).
1219-
-else.
1220-
%% Looks for a file relative to a given directory
1221-
1222-
-type find_file_rule() :: {ObjDirSuffix::string(), SrcDirSuffix::string()}.
1223-
1224-
%% Looks for a source file relative to the object file name and directory
1225-
1226-
-type find_source_rule() :: {ObjExtension::string(), SrcExtension::string(),
1227-
[find_file_rule()]}.
1228-
1229-
keep_suffix_search_rules(Rules) ->
1230-
[T || {_,_,_}=T <- Rules].
1231-
1232-
-spec find_source(file:filename(), file:filename(), [find_source_rule()]) ->
1233-
{ok, file:filename()} | {error, not_found}.
1234-
find_source(Filename, Dir, Rules) ->
1235-
try_suffix_rules(keep_suffix_search_rules(Rules), Filename, Dir).
1236-
1237-
try_suffix_rules(Rules, Filename, Dir) ->
1238-
Ext = filename:extension(Filename),
1239-
try_suffix_rules(Rules, filename:rootname(Filename, Ext), Dir, Ext).
1240-
1241-
try_suffix_rules([{Ext,Src,Rules}|Rest], Root, Dir, Ext)
1242-
when is_list(Src), is_list(Rules) ->
1243-
case try_dir_rules(add_local_search(Rules), Root ++ Src, Dir) of
1244-
{ok, File} -> {ok, File};
1245-
_Other ->
1246-
try_suffix_rules(Rest, Root, Dir, Ext)
1247-
end;
1248-
try_suffix_rules([_|Rest], Root, Dir, Ext) ->
1249-
try_suffix_rules(Rest, Root, Dir, Ext);
1250-
try_suffix_rules([], _Root, _Dir, _Ext) ->
1251-
{error, not_found}.
1252-
1253-
%% ensuring we check the directory of the object file before any other directory
1254-
add_local_search(Rules) ->
1255-
Local = {"",""},
1256-
[Local] ++ lists:filter(fun (X) -> X =/= Local end, Rules).
1257-
1258-
try_dir_rules([{From, To}|Rest], Filename, Dir)
1259-
when is_list(From), is_list(To) ->
1260-
case try_dir_rule(Dir, Filename, From, To) of
1261-
{ok, File} -> {ok, File};
1262-
error -> try_dir_rules(Rest, Filename, Dir)
1263-
end;
1264-
try_dir_rules([], _Filename, _Dir) ->
1265-
{error, not_found}.
1266-
1267-
try_dir_rule(Dir, Filename, From, To) ->
1268-
case lists:suffix(From, Dir) of
1269-
true ->
1270-
NewDir = lists:sublist(Dir, 1, length(Dir)-length(From))++To,
1271-
Src = filename:join(NewDir, Filename),
1272-
case filelib:is_regular(Src) of
1273-
true -> {ok, Src};
1274-
false -> find_regular_file(filelib:wildcard(Src))
1275-
end;
1276-
false ->
1277-
error
1278-
end.
1279-
1280-
find_regular_file([]) ->
1281-
error;
1282-
find_regular_file([File|Files]) ->
1283-
case filelib:is_regular(File) of
1284-
true -> {ok, File};
1285-
false -> find_regular_file(Files)
1286-
end.
1287-
-endif.

0 commit comments

Comments
 (0)