Skip to content

Commit

Permalink
Merge pull request #1314 from ferd/cover_excl_mods
Browse files Browse the repository at this point in the history
Cover excl mods
  • Loading branch information
alisdair sullivan authored Aug 27, 2016
2 parents 8ee9cc8 + 4b0a072 commit 00b1053
Show file tree
Hide file tree
Showing 3 changed files with 59 additions and 13 deletions.
3 changes: 3 additions & 0 deletions rebar.config.sample
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,9 @@
%% is `false'
{cover_enabled, false}.

%% Modules to exclude from cover
{cover_excl_mods, []}.

%% Options to pass to cover provider
{cover_opts, [verbose]}.

Expand Down
39 changes: 28 additions & 11 deletions src/rebar_prv_cover.erl
Original file line number Diff line number Diff line change
Expand Up @@ -303,23 +303,44 @@ cover_compile(State, Dirs) ->
{ok, CoverPid} = start_cover(),
%% redirect cover output
true = redirect_cover_output(State, CoverPid),
ExclMods = rebar_state:get(State, cover_excl_mods, []),

lists:foreach(fun(Dir) ->
?DEBUG("cover compiling ~p", [Dir]),
case catch(cover:compile_beam_directory(Dir)) of
case file:list_dir(Dir) of
{ok, Files} ->
?DEBUG("cover compiling ~p", [Dir]),
[cover_compile_file(filename:join(Dir, File))
|| File <- Files,
filename:extension(File) == ".beam",
not is_ignored(Dir, File, ExclMods)],
ok;
{error, eacces} ->
?WARN("Directory ~p not readable, modules will not be included in coverage", [Dir]);
{error, enoent} ->
?WARN("Directory ~p not found", [Dir]);
{'EXIT', {Reason, _}} ->
?WARN("Cover compilation for directory ~p failed: ~p", [Dir, Reason]);
Results ->
%% print any warnings about modules that failed to cover compile
lists:foreach(fun print_cover_warnings/1, lists:flatten(Results))
{error, Reason} ->
?WARN("Directory ~p error ~p", [Dir, Reason])
end
end, Dirs),
rebar_utils:cleanup_code_path(rebar_state:code_paths(State, default)),
ok.

is_ignored(Dir, File, ExclMods) ->
Ignored = lists:any(fun(Excl) ->
File =:= atom_to_list(Excl) ++ ".beam"
end,
ExclMods),
Ignored andalso ?DEBUG("cover ignoring ~p ~p", [Dir, File]),
Ignored.

cover_compile_file(FileName) ->
case catch(cover:compile_beam(FileName)) of
{error, Reason} ->
?WARN("Cover compilation failed: ~p", [Reason]);
{ok, _} ->
ok
end.

app_dirs(Apps) ->
lists:foldl(fun app_ebin_dirs/2, [], Apps).

Expand Down Expand Up @@ -349,10 +370,6 @@ redirect_cover_output(State, CoverPid) ->
[append]),
group_leader(F, CoverPid).

print_cover_warnings({ok, _}) -> ok;
print_cover_warnings({error, Error}) ->
?WARN("Cover compilation failed: ~p", [Error]).

write_coverdata(State, Task) ->
DataDir = cover_dir(State),
ok = filelib:ensure_dir(filename:join([DataDir, "dummy.log"])),
Expand Down
30 changes: 28 additions & 2 deletions test/rebar_cover_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,8 @@
root_extra_src_dirs/1,
index_written/1,
flag_verbose/1,
config_verbose/1]).
config_verbose/1,
excl_mods/1]).

-include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl").
Expand All @@ -35,7 +36,8 @@ all() ->
basic_extra_src_dirs, release_extra_src_dirs,
root_extra_src_dirs,
index_written,
flag_verbose, config_verbose].
flag_verbose, config_verbose,
excl_mods].

flag_coverdata_written(Config) ->
AppDir = ?config(apps, Config),
Expand Down Expand Up @@ -206,3 +208,27 @@ config_verbose(Config) ->
{ok, [{app, Name}]}),

true = filelib:is_file(filename:join([AppDir, "_build", "test", "cover", "index.html"])).

excl_mods(Config) ->
AppDir = ?config(apps, Config),

Name1 = rebar_test_utils:create_random_name("relapp1_"),
Vsn1 = rebar_test_utils:create_random_vsn(),
rebar_test_utils:create_app(filename:join([AppDir, "apps", Name1]), Name1, Vsn1, [kernel, stdlib]),

Name2 = rebar_test_utils:create_random_name("relapp2_"),
Vsn2 = rebar_test_utils:create_random_vsn(),
rebar_test_utils:create_app(filename:join([AppDir, "apps", Name2]), Name2, Vsn2, [kernel, stdlib]),

Mod1 = list_to_atom(Name1),
Mod2 = list_to_atom(Name2),
RebarConfig = [{erl_opts, [{d, some_define}]},
{cover_excl_mods, [Mod2]}],

rebar_test_utils:run_and_check(Config,
RebarConfig,
["eunit", "--cover"],
{ok, [{app, Name1}, {app, Name2}]}),

{file, _} = cover:is_compiled(Mod1),
false = cover:is_compiled(Mod2).

0 comments on commit 00b1053

Please sign in to comment.