Skip to content

Commit

Permalink
cover: Gracefully handle failures to collect coverage data
Browse files Browse the repository at this point in the history
On platforms that support native coverage (introduced in
Erlang/OTP 27), the `cover` module did not properly handle failed
calls to `code:get_coverage/2`. The call to that function will fail
if the module in question has been reloaded or unloaded.

For example, if `cover:export/1` was called and a module had been
reloaded on a remote node (for example by `meck`), the
`cover:export/1` call would never return.

Because the current API for `cover` has no good way to report this
kind of error, we will fix the issue by logging the failed call using
the `logger` module and otherwise ignore the failure. That implies
that there will be no coverage information for modules that have been
reloaded. That is compatible with the behavior of `cover` prior to
Erlang/OTP 27.

Closes #8691
  • Loading branch information
bjorng committed Aug 23, 2024
1 parent f7ddb9c commit 426c582
Show file tree
Hide file tree
Showing 2 changed files with 51 additions and 3 deletions.
28 changes: 26 additions & 2 deletions lib/tools/src/cover.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2364,8 +2364,17 @@ standard_move(Mod) ->
end.

native_move(Mod) ->
Coverage = maps:from_list(code:get_coverage(cover_id_line, Mod)),
_ = code:reset_coverage(Mod),
Coverage0 =
try
code:get_coverage(cover_id_line, Mod)
catch
error:badarg ->
log_native_move_error(Mod),
[]
end,
_ = catch code:reset_coverage(Mod),
Coverage = maps:from_list(Coverage0),

fun({#bump{}=Key,Index}) ->
case Coverage of
#{Index := false} ->
Expand All @@ -2379,6 +2388,21 @@ native_move(Mod) ->
end
end.

log_native_move_error(Mod) ->
S = "Module ~tp: Failed to collect coverage information. "
"Has it been reloaded or unloaded?",
F = fun(#{node := Node}) ->
case Node of
nonode@nohost ->
{S,[Mod]};
_ ->
{"On node ~tp: " ++ S,[Node,Mod]}
end
end,
logger:warning(#{coverage_collection_failed => Mod,
node => node()},
#{report_cb => F}).

%% Reset counters (set counters to 0).
reset_counters(Mod) ->
case has_native_coverage() of
Expand Down
26 changes: 25 additions & 1 deletion lib/tools/test/cover_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ all() ->
otp_13277, otp_13289, guard_in_lc, gh_4796,
eep49, gh_8159],
StartStop = [start, compile, analyse, misc, stop,
distribution, reconnect, die_and_reconnect,
distribution, distribution_export, reconnect, die_and_reconnect,
dont_reconnect_after_stop, stop_node_after_disconnect,
export_import, otp_5031, otp_6115,
otp_8270, otp_10979_hanging_node, otp_14817,
Expand Down Expand Up @@ -539,6 +539,30 @@ distribution(Config) when is_list(Config) ->
peer:stop(P1),
peer:stop(P2).

%% GH-8661. An attempt to export cover data on a remote node could
%% hang if the module had been reloaded.
distribution_export(Config) when is_list(Config) ->
ct:timetrap({seconds, 30}),

DataDir = proplists:get_value(data_dir, Config),

ok = file:set_cwd(DataDir),

{ok,P1,N1} = ?CT_PEER(),

{ok,f} = cover:compile(f),
{ok,[_]} = cover:start([N1]),
ok = cover:export("f.coverdata"),

{ok,f} = compile:file(f, [debug_info]),
{module, f} = erpc:call(N1, code, load_file, [f]),

ok = cover:export("f.coverdata"),

%% Cleanup
peer:stop(P1),
ok.

%% Test that a lost node is reconnected
reconnect(Config) ->
DataDir = proplists:get_value(data_dir, Config),
Expand Down

0 comments on commit 426c582

Please sign in to comment.