File 2501-Correct-coverage-for-functions-on-the-same-line.patch of Package erlang
From c8256ac1de3a22295c1b9da1ad33acf67119efe7 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 21 Feb 2024 08:02:06 +0100
Subject: [PATCH] Correct coverage for functions on the same line
This commit fixes the bug reported in #8159.
It also eliminates a weird behavior when there are multiple functions
on the same line. Consider this module:
-module(foo).
-export([bar/0, baz/0]).
bar() -> ok. baz() -> not_ok.
In Erlang/OTP 26, analysing on the line level would return two entries
for line 4:
1> cover:compile_module(foo).
{ok,foo}
2> foo:bar().
ok
3> cover:analyse(foo, coverage, line).
{ok,[{{foo,4},{1,0}},{{foo,4},{0,1}}]}
4> cover:analyse(foo, calls, line).
{ok,[{{foo,4},1},{{foo,4},0}]}
This has been changed to coalesce all information about each line to
a single entry in the resulting list:
1> cover:compile_module(foo).
{ok,foo}
2> foo:bar().
ok
3> cover:analyse(foo, coverage, line).
{ok,[{{foo,4},{1,0}}]}
4> cover:analyse(foo, calls, line).
{ok,[{{foo,4},1}]}
Closes #8159
---
erts/emulator/beam/beam_code.h | 1 +
erts/emulator/beam/emu/ops.tab | 2 +-
erts/emulator/beam/erl_bif_coverage.c | 65 +++++++++++++++++++
.../emulator/beam/jit/arm/beam_asm_module.cpp | 3 +-
erts/emulator/beam/jit/arm/ops.tab | 2 +-
erts/emulator/beam/jit/asm_load.c | 35 +++++++++-
erts/emulator/beam/jit/load.h | 2 +
.../emulator/beam/jit/x86/beam_asm_module.cpp | 3 +-
erts/emulator/beam/jit/x86/ops.tab | 2 +-
lib/compiler/src/beam_asm.erl | 6 +-
lib/compiler/src/beam_block.erl | 2 +-
lib/compiler/src/beam_disasm.erl | 4 +-
lib/compiler/src/beam_flatten.erl | 2 +-
lib/compiler/src/beam_ssa_codegen.erl | 4 +-
lib/compiler/src/beam_validator.erl | 2 +-
lib/compiler/src/genop.tab | 4 +-
lib/compiler/src/sys_coverage.erl | 11 +++-
lib/compiler/src/v3_core.erl | 6 +-
lib/kernel/src/code.erl | 7 +-
lib/kernel/test/code_coverage_SUITE.erl | 9 +++
lib/tools/src/cover.erl | 36 ++++++----
lib/tools/test/cover_SUITE.erl | 50 ++++++++++++--
22 files changed, 215 insertions(+), 43 deletions(-)
diff --git a/erts/emulator/beam/beam_code.h b/erts/emulator/beam/beam_code.h
index 0cb6896641..5b9c3524fc 100644
--- a/erts/emulator/beam/beam_code.h
+++ b/erts/emulator/beam/beam_code.h
@@ -96,6 +96,7 @@ typedef struct beam_code_header {
Uint coverage_mode;
void *coverage;
byte *line_coverage_valid;
+ Uint32 *loc_index_to_cover_id;
Uint line_coverage_len;
#endif
diff --git a/erts/emulator/beam/emu/ops.tab b/erts/emulator/beam/emu/ops.tab
index f607d47039..f807852697 100644
--- a/erts/emulator/beam/emu/ops.tab
+++ b/erts/emulator/beam/emu/ops.tab
@@ -95,7 +95,7 @@ move S X0=x==0 | line Loc => line Loc | move S X0
line n => _
line I
-executable_line Line => _
+executable_line Id Line => _
# For the JIT, the init_yregs/1 instruction allows generation of better code.
# For the BEAM interpreter, though, it will probably be more efficient to
diff --git a/erts/emulator/beam/erl_bif_coverage.c b/erts/emulator/beam/erl_bif_coverage.c
index ad5e487169..0ea8c075cf 100644
--- a/erts/emulator/beam/erl_bif_coverage.c
+++ b/erts/emulator/beam/erl_bif_coverage.c
@@ -30,6 +30,7 @@
#include "bif.h"
#include "beam_load.h"
#include "beam_file.h"
+#include "atom.h"
#include "jit/beam_asm.h"
@@ -339,6 +340,66 @@ get_line_coverage(Process* c_p, const BeamCodeHeader* hdr)
}
#endif
+#ifdef BEAMASM
+static BIF_RETTYPE
+get_cover_id_line(Process* c_p, const BeamCodeHeader* hdr)
+{
+ const BeamCodeLineTab *lt;
+ const unsigned *loc2id;
+ Eterm* hp;
+ Eterm* hend;
+ Eterm tmp;
+ Eterm res;
+ ssize_t i;
+ unsigned location;
+ Uint alloc_size;
+ byte coverage_mode;
+
+ coverage_mode = hdr->coverage_mode;
+
+ switch (coverage_mode) {
+ case ERTS_COV_LINE_COUNTERS:
+ break;
+ default:
+ BIF_ERROR(c_p, BADARG);
+ }
+
+ lt = hdr->line_table;
+ loc2id = hdr->loc_index_to_cover_id;
+
+ alloc_size = (3 + 2) * hdr->line_coverage_len;
+ hp = HAlloc(c_p, alloc_size);
+ hend = hp + alloc_size;
+ res = NIL;
+ for (i = hdr->line_coverage_len - 1; i >= 0; i--) {
+ Eterm coverage = am_error;
+ Uint* coverage_array = hdr->coverage;
+ unsigned cover_id;
+
+ if (!hdr->line_coverage_valid[i]) {
+ continue;
+ }
+ if (lt->loc_size == 2) {
+ location = lt->loc_tab.p2[i];
+ } else {
+ ASSERT(lt->loc_size == 4);
+ location = lt->loc_tab.p4[i];
+ }
+ if (location == LINE_INVALID_LOCATION) {
+ continue;
+ }
+ coverage = make_small(MIN(coverage_array[i], MAX_SMALL));
+ cover_id = loc2id[i];
+ tmp = TUPLE2(hp, make_small(cover_id), coverage);
+ hp += 3;
+ res = CONS(hp, tmp, res);
+ hp += 2;
+ }
+ HRelease(c_p, hend, hp);
+ return res;
+}
+#endif
+
BIF_RETTYPE
code_get_coverage_2(BIF_ALIST_2)
{
@@ -365,6 +426,10 @@ code_get_coverage_2(BIF_ALIST_2)
BIF_RET(get_function_coverage(BIF_P, hdr));
case am_line:
BIF_RET(get_line_coverage(BIF_P, hdr));
+ default:
+ if (ERTS_IS_ATOM_STR("cover_id_line", BIF_ARG_1)) {
+ BIF_RET(get_cover_id_line(BIF_P, hdr));
+ }
}
#endif
diff --git a/erts/emulator/beam/jit/arm/beam_asm_module.cpp b/erts/emulator/beam/jit/arm/beam_asm_module.cpp
index 207c676ce2..caec6c0eb8 100644
--- a/erts/emulator/beam/jit/arm/beam_asm_module.cpp
+++ b/erts/emulator/beam/jit/arm/beam_asm_module.cpp
@@ -451,7 +451,8 @@ void BeamModuleAssembler::emit_func_line(const ArgWord &Loc) {
void BeamModuleAssembler::emit_empty_func_line() {
}
-void BeamModuleAssembler::emit_executable_line(const ArgWord &Loc) {
+void BeamModuleAssembler::emit_executable_line(const ArgWord &Loc,
+ const ArgWord &Index) {
}
/*
diff --git a/erts/emulator/beam/jit/arm/ops.tab b/erts/emulator/beam/jit/arm/ops.tab
index 098e714853..e7fe144772 100644
--- a/erts/emulator/beam/jit/arm/ops.tab
+++ b/erts/emulator/beam/jit/arm/ops.tab
@@ -86,7 +86,7 @@ func_line I
line n => _
line I
-executable_line I
+executable_line I I
allocate t t
allocate_heap t I t
diff --git a/erts/emulator/beam/jit/asm_load.c b/erts/emulator/beam/jit/asm_load.c
index df34a74475..dd337a5d34 100644
--- a/erts/emulator/beam/jit/asm_load.c
+++ b/erts/emulator/beam/jit/asm_load.c
@@ -71,6 +71,7 @@ int beam_load_prepare_emit(LoaderState *stp) {
stp->coverage = hdr->coverage = NULL;
stp->line_coverage_valid = hdr->line_coverage_valid = NULL;
+ stp->loc_index_to_cover_id = hdr->loc_index_to_cover_id = NULL;
hdr->line_coverage_len = 0;
@@ -115,6 +116,16 @@ int beam_load_prepare_emit(LoaderState *stp) {
stp->line_coverage_valid =
erts_alloc(ERTS_ALC_T_CODE_COVERAGE, alloc_size);
sys_memset(stp->line_coverage_valid, 0, alloc_size);
+ if (hdr->coverage_mode == ERTS_COV_LINE_COUNTERS) {
+ stp->loc_index_to_cover_id =
+ erts_alloc(ERTS_ALC_T_CODE_COVERAGE,
+ alloc_size * sizeof(unsigned));
+#ifdef DEBUG
+ sys_memset(stp->loc_index_to_cover_id,
+ 0xff,
+ alloc_size * sizeof(unsigned));
+#endif
+ }
hdr->line_coverage_len = alloc_size;
break;
}
@@ -231,6 +242,11 @@ int beam_load_prepared_dtor(Binary *magic) {
hdr->line_coverage_valid = NULL;
}
+ if (hdr->loc_index_to_cover_id) {
+ erts_free(ERTS_ALC_T_CODE_COVERAGE, hdr->loc_index_to_cover_id);
+ hdr->loc_index_to_cover_id = NULL;
+ }
+
erts_free(ERTS_ALC_T_PREPARED_CODE, hdr);
stp->load_hdr = NULL;
}
@@ -270,6 +286,11 @@ int beam_load_prepared_dtor(Binary *magic) {
stp->line_coverage_valid = NULL;
}
+ if (stp->loc_index_to_cover_id) {
+ erts_free(ERTS_ALC_T_CODE_COVERAGE, stp->loc_index_to_cover_id);
+ stp->loc_index_to_cover_id = NULL;
+ }
+
if (stp->ba) {
beamasm_delete_assembler(stp->ba);
stp->ba = NULL;
@@ -655,7 +676,7 @@ int beam_load_emit_op(LoaderState *stp, BeamOp *tmp_op) {
goto load_error;
}
break;
- case op_executable_line_I: {
+ case op_executable_line_II: {
byte coverage_size = 0;
/* We'll save some memory by not inserting a line entry that
@@ -670,8 +691,13 @@ int beam_load_emit_op(LoaderState *stp, BeamOp *tmp_op) {
}
if (coverage_size) {
unsigned loc_index = stp->current_li - 1;
+ unsigned cover_id = tmp_op->a[1].val;
+
ASSERT(stp->beam.lines.item_count > 0);
stp->line_coverage_valid[loc_index] = 1;
+ if (stp->loc_index_to_cover_id) {
+ stp->loc_index_to_cover_id[loc_index] = cover_id;
+ }
beamasm_emit_coverage(stp->ba,
stp->coverage,
loc_index,
@@ -882,8 +908,10 @@ int beam_load_finish_emit(LoaderState *stp) {
/* Transfer ownership of the coverage tables to the prepared code. */
stp->load_hdr->coverage = stp->coverage;
stp->load_hdr->line_coverage_valid = stp->line_coverage_valid;
+ stp->load_hdr->loc_index_to_cover_id = stp->loc_index_to_cover_id;
stp->coverage = NULL;
stp->line_coverage_valid = NULL;
+ stp->loc_index_to_cover_id = NULL;
/* Move the code to its final location. */
beamasm_codegen(stp->ba,
@@ -1142,6 +1170,7 @@ void beam_load_finalize_code(LoaderState *stp,
stp->load_hdr->are_nifs = NULL;
stp->load_hdr->coverage = NULL;
stp->load_hdr->line_coverage_valid = NULL;
+ stp->load_hdr->loc_index_to_cover_id = NULL;
stp->executable_region = NULL;
stp->writable_region = NULL;
stp->code_hdr = NULL;
@@ -1155,4 +1184,8 @@ void beam_load_purge_aux(const BeamCodeHeader *hdr) {
if (hdr->line_coverage_valid) {
erts_free(ERTS_ALC_T_CODE_COVERAGE, hdr->line_coverage_valid);
}
+
+ if (hdr->loc_index_to_cover_id) {
+ erts_free(ERTS_ALC_T_CODE_COVERAGE, hdr->loc_index_to_cover_id);
+ }
}
diff --git a/erts/emulator/beam/jit/load.h b/erts/emulator/beam/jit/load.h
index 7b5d25f4d9..ad4ca1d255 100644
--- a/erts/emulator/beam/jit/load.h
+++ b/erts/emulator/beam/jit/load.h
@@ -87,6 +87,8 @@ struct LoaderState_ {
*/
void *coverage;
byte *line_coverage_valid;
+ unsigned int current_index;
+ unsigned int *loc_index_to_cover_id;
/* Translates lambda indexes to their literals, if any. Lambdas that lack
* a literal (for example if they have an environment) are represented by
diff --git a/erts/emulator/beam/jit/x86/beam_asm_module.cpp b/erts/emulator/beam/jit/x86/beam_asm_module.cpp
index 69a1eede2d..5ad3672c18 100644
--- a/erts/emulator/beam/jit/x86/beam_asm_module.cpp
+++ b/erts/emulator/beam/jit/x86/beam_asm_module.cpp
@@ -383,7 +383,8 @@ void BeamModuleAssembler::emit_func_line(const ArgWord &Loc) {
void BeamModuleAssembler::emit_empty_func_line() {
}
-void BeamModuleAssembler::emit_executable_line(const ArgWord &Loc) {
+void BeamModuleAssembler::emit_executable_line(const ArgWord &Loc,
+ const ArgWord &Index) {
}
/*
diff --git a/erts/emulator/beam/jit/x86/ops.tab b/erts/emulator/beam/jit/x86/ops.tab
index fbdd5c0b84..d73435be65 100644
--- a/erts/emulator/beam/jit/x86/ops.tab
+++ b/erts/emulator/beam/jit/x86/ops.tab
@@ -86,7 +86,7 @@ func_line I
line n => _
line I
-executable_line I
+executable_line I I
allocate t t
allocate_heap t I t
diff --git a/lib/compiler/src/beam_asm.erl b/lib/compiler/src/beam_asm.erl
index 18b03b1a56..23673eace9 100644
--- a/lib/compiler/src/beam_asm.erl
+++ b/lib/compiler/src/beam_asm.erl
@@ -365,9 +365,9 @@ make_op({'%',_}, Dict) ->
make_op({line=Op,Location}, Dict0) ->
{Index,Dict} = beam_dict:line(Location, Dict0, Op),
encode_op(line, [Index], Dict);
-make_op({executable_line=Op,Location}, Dict0) ->
- {Index,Dict} = beam_dict:line(Location, Dict0, Op),
- encode_op(executable_line, [Index], Dict);
+make_op({executable_line=Op,Location,Index}, Dict0) ->
+ {LocationIndex,Dict} = beam_dict:line(Location, Dict0, Op),
+ encode_op(executable_line, [LocationIndex,Index], Dict);
make_op({bif, Bif, {f,_}, [], Dest}, Dict) ->
%% BIFs without arguments cannot fail.
encode_op(bif0, [{extfunc, erlang, Bif, 0}, Dest], Dict);
diff --git a/lib/compiler/src/beam_block.erl b/lib/compiler/src/beam_block.erl
index dad21894d1..4ddc88874a 100644
--- a/lib/compiler/src/beam_block.erl
+++ b/lib/compiler/src/beam_block.erl
@@ -171,7 +171,7 @@ collect({put_map,{f,0},Op,S,D,R,{list,Puts}}) ->
{set,[D],[S|Puts],{alloc,R,{put_map,Op,{f,0}}}};
collect({fmove,S,D}) -> {set,[D],[S],fmove};
collect({fconv,S,D}) -> {set,[D],[S],fconv};
-collect({executable_line,Line}) -> {set,[],[],{executable_line,Line}};
+collect({executable_line,_,_}=Line) -> {set,[],[],Line};
collect(_) -> error.
%% embed_lines([Instruction]) -> [Instruction]
diff --git a/lib/compiler/src/beam_disasm.erl b/lib/compiler/src/beam_disasm.erl
index 69275b9471..7195b94160 100644
--- a/lib/compiler/src/beam_disasm.erl
+++ b/lib/compiler/src/beam_disasm.erl
@@ -1308,8 +1308,8 @@ resolve_inst({bs_match,[{Fail,Ctx,{z,1},{u,_},Args}]},_,_,_) ->
%% OTP 27.
%%
-resolve_inst({executable_line,[Index]},_,_,_) ->
- {line,resolve_arg(Index)};
+resolve_inst({executable_line,[Location,Index]},_,_,_) ->
+ {executable_line,resolve_arg(Location),resolve_arg(Index)};
%%
%% Catches instructions that are not yet handled.
diff --git a/lib/compiler/src/beam_flatten.erl b/lib/compiler/src/beam_flatten.erl
index 63d05b3782..a2011b8752 100644
--- a/lib/compiler/src/beam_flatten.erl
+++ b/lib/compiler/src/beam_flatten.erl
@@ -64,7 +64,7 @@ norm({set,[D],[S|Puts],{alloc,R,{put_map,Op,F}}}) ->
{put_map,F,Op,S,D,R,{list,Puts}};
norm({set,[],[],remove_message}) -> remove_message;
norm({set,[],[],{line,_}=Line}) -> Line;
-norm({set,[],[],{executable_line,_}=Line}) -> Line.
+norm({set,[],[],{executable_line,_,_}=Line}) -> Line.
norm_allocate({_Zero,nostack,Nh,[]}, Regs) ->
[{test_heap,Nh,Regs}];
diff --git a/lib/compiler/src/beam_ssa_codegen.erl b/lib/compiler/src/beam_ssa_codegen.erl
index 1209c9ec1f..e618bcf761 100644
--- a/lib/compiler/src/beam_ssa_codegen.erl
+++ b/lib/compiler/src/beam_ssa_codegen.erl
@@ -1819,9 +1819,9 @@ cg_instr(bs_get_tail, [Src], Dst, Set) ->
cg_instr(bs_get_position, [Ctx], Dst, Set) ->
Live = get_live(Set),
[{bs_get_position,Ctx,Dst,Live}];
-cg_instr(executable_line, [], _Dst, #cg_set{anno=Anno}) ->
+cg_instr(executable_line, [{integer,Index}], _Dst, #cg_set{anno=Anno}) ->
{line,Location} = line(Anno),
- [{executable_line,Location}];
+ [{executable_line,Location,Index}];
cg_instr(put_map, [{atom,assoc},SrcMap|Ss], Dst, Set) ->
Live = get_live(Set),
[{put_map_assoc,{f,0},SrcMap,Dst,Live,{list,Ss}}];
diff --git a/lib/compiler/src/beam_validator.erl b/lib/compiler/src/beam_validator.erl
index ad9a5b331a..3e5adbef26 100644
--- a/lib/compiler/src/beam_validator.erl
+++ b/lib/compiler/src/beam_validator.erl
@@ -373,7 +373,7 @@ vi({'%',_}, Vst) ->
Vst;
vi({line,_}, Vst) ->
Vst;
-vi({executable_line,_}, Vst) ->
+vi({executable_line,_,_}, Vst) ->
Vst;
vi(nif_start, Vst) ->
Vst;
diff --git a/lib/compiler/src/genop.tab b/lib/compiler/src/genop.tab
index 19202243c8..f9ac6e1b1d 100755
--- a/lib/compiler/src/genop.tab
+++ b/lib/compiler/src/genop.tab
@@ -692,6 +692,6 @@ BEAM_FORMAT_NUMBER=0
# OTP 27
-## @spec executable_line Location
+## @spec executable_line Location Index
## @doc Provide location for an executable line.
-183: executable_line/1
+183: executable_line/2
diff --git a/lib/compiler/src/sys_coverage.erl b/lib/compiler/src/sys_coverage.erl
index 5bf6982952..2c0539a37c 100644
--- a/lib/compiler/src/sys_coverage.erl
+++ b/lib/compiler/src/sys_coverage.erl
@@ -35,8 +35,15 @@
{'ok',[form()]}.
module(Forms0, _Opts) when is_list(Forms0) ->
- IndexFun = fun(_, _, _, _, _) -> 0 end,
- transform(Forms0, IndexFun).
+ put(executable_line_index, 1),
+ GetIndex = fun(_, _, _, _, _) ->
+ Index = get(executable_line_index),
+ put(executable_line_index, Index + 1),
+ Index
+ end,
+ Forms = transform(Forms0, GetIndex),
+ erase(executable_line_index),
+ Forms.
%% Undocumented helper function for the `cover` module.
-spec cover_transform([form()], index_fun()) ->
diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index 2b0fe93e4f..e0fdc16de3 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -977,10 +977,10 @@ expr({op,L,Op,L0,R0}, St0) ->
{#icall{anno=#a{anno=LineAnno}, %Must have an #a{}
module=#c_literal{anno=LineAnno,val=erlang},
name=#c_literal{anno=LineAnno,val=Op},args=As},Aps,St1};
-expr({executable_line,L,_}, St0) ->
- {#iprimop{anno=#a{anno=lineno_anno(L, St0)},
+expr({executable_line,Loc,Index}, St0) ->
+ {#iprimop{anno=#a{anno=lineno_anno(Loc, St0)},
name=#c_literal{val=executable_line},
- args=[]},[],St0};
+ args=[#c_literal{val=Index}]},[],St0};
expr({ssa_check_when,L,WantedResult,Args,Tag,Clauses}, St) ->
{#c_opaque{anno=full_anno(L, St),val={ssa_check_when,WantedResult,Tag,Args,Clauses}}, [], St}.
diff --git a/lib/kernel/doc/src/code.xml b/lib/kernel/doc/src/code.xml
index fde70e6887..fc861c625e 100644
--- a/lib/kernel/doc/src/code.xml
+++ b/lib/kernel/doc/src/code.xml
@@ -696,6 +696,7 @@ ok = code:finish_loading(Prepared),
giving the number of times that line was executed is returned.
</item>
</taglist>
+ <p>Level <c>cover_id_line</c> is used by the <c>m:cover</c> tool.</p>
<p>Failures:</p>
<taglist>
<tag><c>badarg</c></tag>
diff --git a/lib/kernel/src/code.erl b/lib/kernel/src/code.erl
index fde70e6887..fc861c625e 100644
--- a/lib/kernel/src/code.erl
+++ b/lib/kernel/src/code.erl
@@ -1235,13 +1235,14 @@ path_files([Path|Tail]) ->
end.
-spec get_coverage(Level, module()) -> Result when
- Level :: 'function' | 'line',
+ Level :: 'function' | 'line' | 'cover_id_line',
Result :: [{Entity, CoverageInfo}],
- Entity :: {Function, Arity} | Line,
+ Entity :: {Function, Arity} | Line | CoverId,
CoverageInfo :: Covered | Counter,
Function :: atom(),
Arity :: arity(),
Line :: non_neg_integer(),
+ CoverId :: pos_integer(),
Covered :: boolean(),
Counter :: non_neg_integer().
get_coverage(_Level, _Module) ->
diff --git a/lib/kernel/test/code_coverage_SUITE.erl b/lib/kernel/test/code_coverage_SUITE.erl
index 925c316ae2..85cbc8a224 100644
--- a/lib/kernel/test/code_coverage_SUITE.erl
+++ b/lib/kernel/test/code_coverage_SUITE.erl
@@ -113,6 +113,15 @@ do_get_coverage(PrivDir) ->
[{5,0},{8,0},{10,0},{13,1},{16,1},{18,5}]},
do_get_coverage(M, Beam, Run2, Result2),
+ %% Test cover_id_line used by cover.
+ _ = code:set_coverage_mode(line_counters),
+ {module,M} = code:load_binary(M, "", Beam),
+ line_counters = code:set_coverage_mode(none),
+ _ = M:fib(5),
+ [{1,0},{2,0},{3,0},{4,1},{5,1},{6,5}] =
+ code:get_coverage(cover_id_line, M),
+ unload(M),
+
%% Compile without line_coverage.
{ok,M,BeamFun} = compile:file(ErlFile, [report,binary]),
do_get_function_coverage(M, BeamFun, Run1, Result1),
diff --git a/lib/tools/src/cover.erl b/lib/tools/src/cover.erl
index cab14c54af..339070b819 100644
--- a/lib/tools/src/cover.erl
+++ b/lib/tools/src/cover.erl
@@ -2281,20 +2281,20 @@ standard_move(Mod) ->
end.
native_move(Mod) ->
- Coverage = maps:from_list(code:get_coverage(line, Mod)),
+ Coverage = maps:from_list(code:get_coverage(cover_id_line, Mod)),
_ = code:reset_coverage(Mod),
- fun({#bump{line=Line}=Key,_Index}) ->
- case Coverage of
- #{Line := false} ->
- {Key,0};
- #{Line := true} ->
- {Key,1};
- #{Line := N} when is_integer(N), N >= 0 ->
- {Key,N};
- #{} ->
- {Key,0}
- end
- end.
+ 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};
+ #{} ->
+ {Key,0}
+ end
+ end.
%% Reset counters (set counters to 0).
reset_counters(Mod) ->
@@ -2456,7 +2456,8 @@ do_analyse(Module, Analysis, line) ->
{{Module,L}, N}
end
end,
- lists:keysort(1, lists:map(Fun, Bumps));
+ L = lists:keysort(1, lists:map(Fun, Bumps)),
+ merge_dup_lines(L);
do_analyse(Module, Analysis, clause) ->
Pattern = {#bump{module=Module},'_'},
Bumps = lists:keysort(1,ets:match_object(?COLLECTION_TABLE, Pattern)),
@@ -2660,6 +2661,13 @@ do_analyse_to_file1(Module, OutFile, ErlFile, HTML) ->
merge_dup_lines(CovLines) ->
merge_dup_lines(CovLines, []).
+merge_dup_lines([{L, {N1, _N2}}|T], [{L, {NAcc1, _NAcc2}}|TAcc]) ->
+ case N1 + NAcc1 of
+ 0 ->
+ merge_dup_lines(T, [{L, {0, 1}}|TAcc]);
+ _ ->
+ merge_dup_lines(T, [{L, {1, 0}}|TAcc])
+ end;
merge_dup_lines([{L, N}|T], [{L, NAcc}|TAcc]) ->
merge_dup_lines(T, [{L, NAcc + N}|TAcc]);
merge_dup_lines([{L, N}|T], Acc) ->
diff --git a/lib/tools/test/cover_SUITE.erl b/lib/tools/test/cover_SUITE.erl
index 27f4333a88..489c35d24d 100644
--- a/lib/tools/test/cover_SUITE.erl
+++ b/lib/tools/test/cover_SUITE.erl
@@ -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],
+ eep49, gh_8159],
StartStop = [start, compile, analyse, misc, stop,
distribution, reconnect, die_and_reconnect,
dont_reconnect_after_stop, stop_node_after_disconnect,
@@ -1586,9 +1586,7 @@ otp_14817(Config) when is_list(Config) ->
ok = otp_14817:b(),
ok = otp_14817:c(),
ok = otp_14817:d(),
- {ok,[{{otp_14817,3},1},
- {{otp_14817,3},1},
- {{otp_14817,3},1},
+ {ok,[{{otp_14817,3},3},
{{otp_14817,4},1}]} =
cover:analyse(otp_14817, calls, line),
{ok, CovOut} = cover:analyse_to_file(otp_14817),
@@ -1949,6 +1947,49 @@ eep49(Config) ->
ok = file:delete(File),
ok.
+gh_8159(Config) ->
+ ok = file:set_cwd(proplists:get_value(priv_dir, Config)),
+
+ M = same_line,
+ File = atom_to_list(M) ++ ".erl",
+ Test = <<"-module(same_line).
+-export([aaa/0, bbb/0, ccc/0]).
+bbb() -> ok. aaa() -> not_ok. ccc() -> cool.
+">>,
+ ok = file:write_file(File, Test),
+ {ok, M} = cover:compile(File),
+ {ok,[{{M,aaa,0},0}, {{M,bbb,0},0}, {{M,ccc,0},0}]} = cover:analyse(M, calls, function),
+ {ok,[{{M,3},0}]} = cover:analyse(M, calls, line),
+ {ok,[{{M,3},{0,1}}]} = cover:analyse(M, coverage, line),
+
+ cool = M:ccc(),
+ {ok,[{{M,aaa,0},0}, {{M,bbb,0},0}, {{M,ccc,0},1}]} = cover:analyse(M, calls, function),
+ {ok,[{{M,3},1}]} = cover:analyse(M, calls, line),
+ {ok,[{{M,3},{1,0}}]} = cover:analyse(M, coverage, line),
+
+ not_ok = M:aaa(),
+ {ok,[{{M,aaa,0},1}, {{M,bbb,0},0}, {{M,ccc,0},1}]} = cover:analyse(M, calls, function),
+ {ok,[{{M,3},2}]} = cover:analyse(M, calls, line),
+ {ok,[{{M,3},{1,0}}]} = cover:analyse(M, coverage, line),
+
+ ok = M:bbb(),
+ {ok,[{{M,aaa,0},1}, {{M,bbb,0},1}, {{M,ccc,0},1}]} = cover:analyse(M, calls, function),
+ {ok,[{{M,3},3}]} = cover:analyse(M, calls, line),
+ {ok,[{{M,3},{1,0}}]} = cover:analyse(M, coverage, line),
+
+ not_ok = M:aaa(),
+ {ok,[{{M,aaa,0},2}, {{M,bbb,0},1}, {{M,ccc,0},1}]} = cover:analyse(M, calls, function),
+ {ok,[{{M,3},{1,0}}]} = cover:analyse(M, coverage, line),
+
+ cover:reset(),
+
+ not_ok = M:aaa(),
+ {ok,[{{M,3},1}]} = cover:analyse(M, calls, line),
+
+ ok = file:delete(File),
+
+ ok.
+
%%--Auxiliary------------------------------------------------------------
--
2.35.3