Skip to content

Commit

Permalink
Merge pull request #8919 from bjorng/bjorn/tools/cover/GH-8867/OTP-19289
Browse files Browse the repository at this point in the history
cover: Fix lines wrongly reported as uncovered
  • Loading branch information
bjorng authored Oct 10, 2024
2 parents 241f57b + 60323db commit 24f9c93
Show file tree
Hide file tree
Showing 2 changed files with 44 additions and 6 deletions.
13 changes: 8 additions & 5 deletions lib/tools/src/cover.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2373,14 +2373,17 @@ native_move(Mod) ->
[]
end,
_ = catch code:reset_coverage(Mod),
Coverage = maps:from_list(Coverage0),

%% Note that `executable_line` line instructions can become
%% duplicated, making it necessary to consolidate all entries
%% having the same cover id.
S0 = sofs:relation(Coverage0, [{cover_id,count}]),
S1 = sofs:relation_to_family(S0),
S = sofs:to_external(S1),
Coverage = #{Id => lists:sum(Counts) || {Id,Counts} <- S},

fun({#bump{}=Key,Index}) ->
case Coverage of
#{Index := false} ->
{Key,0};
#{Index := true} ->
{Key,1};
#{Index := N} when is_integer(N), N >= 0 ->
{Key,N};
#{} ->
Expand Down
37 changes: 36 additions & 1 deletion lib/tools/test/cover_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ all() ->
analyse_no_beam, line_0, compile_beam_no_file,
compile_beam_missing_backend,
otp_13277, otp_13289, guard_in_lc, gh_4796,
eep49, gh_8159],
eep49, gh_8159, gh_8867],
StartStop = [start, compile, analyse, misc, stop,
distribution, distribution_export, reconnect, die_and_reconnect,
dont_reconnect_after_stop, stop_node_after_disconnect,
Expand Down Expand Up @@ -2015,6 +2015,41 @@ gh_8159(Config) ->

ok.

%% GH-8867: Certain guard expressions could cause `executable_line`
%% instructions to be duplicated, resulting in multiple entries for
%% each cover id. `cover` would only keep the last entry, resulting
%% in lost coverage.
gh_8867(Config) ->
ok = file:set_cwd(proplists:get_value(priv_dir, Config)),

M = ?FUNCTION_NAME,
File = atom_to_list(M) ++ ".erl",
Test = ~"""
-module(gh_8867).
-export([myfun/2]).
myfun(Arg1, <<"bar", _>>) when Arg1 == arg1 orelse Arg1 == arg2 ->
nil;
myfun(arg3, Arg2) ->
case lists:sum([10, 2]) of
12 ->
Res = Arg2,
Res
end.
""",
ok = file:write_file(File, Test),
{ok, M} = cover:compile(File),

~"foo" = M:myfun(arg3, ~"foo"),

{ok,[{{gh_8867,4},0},
{{gh_8867,6},1},
{{gh_8867,8},1},
{{gh_8867,9},1}]} = cover:analyse(M, calls, line),

cover:reset(),
ok = file:delete(File),

ok.

%%--Auxiliary------------------------------------------------------------

Expand Down

0 comments on commit 24f9c93

Please sign in to comment.