Skip to content

Commit

Permalink
Abort if erl_first_files is not a list of strings
Browse files Browse the repository at this point in the history
 - resolves #1645
  • Loading branch information
Bryan Paxton committed Jun 8, 2018
1 parent 2c10bc9 commit d1fc937
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 3 deletions.
8 changes: 8 additions & 0 deletions src/rebar_erlc_compiler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -285,6 +285,7 @@ gather_src(Opts, BaseDirParts, [Dir|Rest], Srcs, CompileOpts) ->
%% files, so that yet to be compiled parse transformations are excluded from it.
erl_first_files(Opts, ErlOpts, Dir, NeededErlFiles) ->
ErlFirstFilesConf = rebar_opts:get(Opts, erl_first_files, []),
valid_erl_first_conf(ErlFirstFilesConf),
NeededSrcDirs = lists:usort(lists:map(fun filename:dirname/1, NeededErlFiles)),
%% NOTE: order of files here is important!
ErlFirstFiles =
Expand Down Expand Up @@ -796,3 +797,10 @@ dir_recursive(Opts, Dir, CompileOpts) when is_list(CompileOpts) ->
undefined -> rebar_dir:recursive(Opts, Dir);
Recursive -> Recursive
end.

valid_erl_first_conf(FileList) ->
case rebar_utils:is_list_of_strings(FileList) of
true -> true;
false -> ?ABORT("An invalid file list (~p) was provided as part of your erl_files_first directive",
[FileList])
end.
11 changes: 10 additions & 1 deletion src/rebar_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,8 @@
list_dir/1,
user_agent/0,
reread_config/1,
get_proxy_auth/0]).
get_proxy_auth/0,
is_list_of_strings/1]).


%% for internal use only
Expand Down Expand Up @@ -919,3 +920,11 @@ get_proxy_auth() ->
undefined -> [];
{ok, ProxyAuth} -> ProxyAuth
end.

-spec rebar_utils:is_list_of_strings(term()) -> boolean().
is_list_of_strings(List) when not is_list(hd(List)) ->
false;
is_list_of_strings(List) when is_list(hd(List)) ->
true;
is_list_of_strings(List) when is_list(List) ->
true.
11 changes: 9 additions & 2 deletions test/rebar_utils_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,8 @@
blacklisted_otp_version/1,
sh_does_not_miss_messages/1,
tup_merge/1,
proxy_auth/1]).
proxy_auth/1,
is_list_of_strings/1]).

-include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl").
Expand All @@ -48,7 +49,7 @@ all() ->
[{group, args_to_tasks},
sh_does_not_miss_messages,
tup_merge,
proxy_auth].
proxy_auth, is_list_of_strings].

groups() ->
[{args_to_tasks, [], [empty_arglist,
Expand Down Expand Up @@ -312,3 +313,9 @@ restore_proxy_env(ProxyEnvKey, false) ->
os:putenv(ProxyEnvKey, "");
restore_proxy_env(ProxyEnvKey, ProxySpec) ->
os:putenv(ProxyEnvKey, ProxySpec).

is_list_of_strings(_Config) ->
?assert(rebar_utils:is_list_of_strings(["foo"])),
?assert(rebar_utils:is_list_of_strings([])),
?assert(rebar_utils:is_list_of_strings("")),
?assert(rebar_utils:is_list_of_strings("foo") == false).

0 comments on commit d1fc937

Please sign in to comment.