File 2363-erts-kernel-Add-native-coverage-support.patch of Package erlang

From 141a287d2cd293c0d0a4f94edfb3852f5e110ca3 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 31 Jul 2023 02:08:33 -0700
Subject: [PATCH 3/4] erts, kernel: Add native coverage support

This implementation was inspired by and partially based on
a previous implementation by Robin Morisset <rmorisset@meta.com>.

To get an idea of the exuction overhead for using various cover modes,
I compiled the entire compiler with the line_coverage option, and then
run the test case compilation_SUITE:self_compile/1 with different
configurations. I ran each test case several times on an 2017 Intel
iMac for each configuration and noted the shortest time for each:

* +JPcover false: 11.5 sec
* +JPcover line: 11.5 sec
* +JPcover line_counters: 12.4 sec

On an M1 MacBook Pro (AAarc64) and the times were the following:

* +JPcover false: 7.2 sec
* +JPcover line: 7.2 sec
* +JPcover line_counters: 8.0 sec

At least according to this benchmark, the overhead for the `line` mode
is negligible, while the overhead for `line_counters` mode is less
than 10 percent.
---
 erts/doc/src/erl_cmd.xml                    |  56 +++
 erts/emulator/Makefile.in                   |   3 +-
 erts/emulator/beam/atom.names               |   2 +
 erts/emulator/beam/beam_bif_load.c          |   1 +
 erts/emulator/beam/beam_code.h              |  12 +
 erts/emulator/beam/beam_common.c            |   3 +
 erts/emulator/beam/beam_file.c              |   4 +-
 erts/emulator/beam/beam_file.h              |   5 +
 erts/emulator/beam/beam_load.h              |   2 +
 erts/emulator/beam/bif.tab                  |  10 +
 erts/emulator/beam/emu/emu_load.c           |   4 +
 erts/emulator/beam/erl_alloc.types          |   1 +
 erts/emulator/beam/erl_bif_coverage.c       | 415 ++++++++++++++++++++
 erts/emulator/beam/erl_init.c               |  24 +-
 erts/emulator/beam/global.h                 |   8 +
 erts/emulator/beam/jit/arm/beam_asm.hpp     |   2 +
 erts/emulator/beam/jit/arm/instr_common.cpp |  31 ++
 erts/emulator/beam/jit/asm_load.c           | 123 ++++++
 erts/emulator/beam/jit/beam_asm.h           |   4 +
 erts/emulator/beam/jit/beam_jit_main.cpp    |   8 +
 erts/emulator/beam/jit/load.h               |   6 +
 erts/emulator/beam/jit/x86/beam_asm.hpp     |   2 +
 erts/emulator/beam/jit/x86/instr_common.cpp |  20 +
 lib/kernel/doc/src/code.xml                 | 207 ++++++++++
 lib/kernel/src/code.erl                     |  52 ++-
 lib/kernel/src/erl_kernel_errors.erl        |  77 ++++
 lib/kernel/test/Makefile                    |   1 +
 lib/kernel/test/code_coverage_SUITE.erl     | 273 +++++++++++++
 28 files changed, 1350 insertions(+), 6 deletions(-)
 create mode 100644 erts/emulator/beam/erl_bif_coverage.c
 create mode 100644 lib/kernel/test/code_coverage_SUITE.erl

diff --git a/erts/doc/src/erl_cmd.xml b/erts/doc/src/erl_cmd.xml
index 24a764b5ac..a11b423664 100644
--- a/erts/doc/src/erl_cmd.xml
+++ b/erts/doc/src/erl_cmd.xml
@@ -1035,6 +1035,62 @@ $ <input>erl \
           descriptor input events.
         </p>
       </item>
+      <tag><marker id="+JPcover"/><c>+JPcover true|false|function|function_counters|line|line_counters</c></tag>
+      <item>
+        <p>Since: OTP 27.0</p>
+        <p>Enables or disables support for coverage when running with
+        the JIT. Defaults to false.</p>
+        <taglist>
+          <tag><c>function</c></tag>
+          <item><p>All modules that are loaded will be instrumented to
+          keep track of which functions are executed. Information
+          about which functions that have been executed can be
+          retrieved by calling <seemfa
+          marker="kernel:code#get_coverage/2"><c>code:get_coverage(function, Module)</c></seemfa>.</p>
+	  </item>
+          <tag><c>function_counters</c></tag>
+          <item><p>All modules that are loaded will be instrumented to
+          count how many times each function is executed. Information
+          about how many times each function has been executed can be
+          retrieved by calling <seemfa
+          marker="kernel:code#get_coverage/2"><c>code:get_coverage(function,
+          Module)</c></seemfa>.</p>
+          </item>
+          <tag><c>line</c></tag>
+          <item><p>When modules that have been compiled with the
+          <seeerl
+          marker="compiler:compile#line_coverage"><c>line_coverage</c></seeerl>
+          option are loaded, they will be instrumented to keep track
+          of which lines have been executed. Information about which
+          lines have been executed can be retrieved by calling <seemfa
+          marker="kernel:code#get_coverage/2"><c>code:get_coverage(line,
+          Module)</c></seemfa>, and information about which functions
+          that have been executed can be retrieved by calling <seemfa
+          marker="kernel:code#get_coverage/2"><c>code:get_coverage(function,
+          Module)</c></seemfa>.</p>
+          </item>
+          <tag><c>line_counters</c></tag>
+          <item><p>When modules that have been compiled with the
+          <seeerl
+          marker="compiler:compile#line_coverage"><c>line_coverage</c></seeerl>
+          option are loaded, they will be instrumented to count the
+          number of times each line is executed. Information about how
+          many times each line has been executed can be retrieved by
+          calling <seemfa
+          marker="kernel:code#get_coverage/2"><c>code:get_coverage(line,
+          Module)</c></seemfa>, and information about which functions
+          that have been executed can be retrieved by calling <seemfa
+          marker="kernel:code#get_coverage/2"><c>code:get_coverage(function,
+          Module)</c></seemfa> (note that in this mode, counters for
+          the number of times each function has been executed
+          <strong>cannot</strong> be retrieved).</p>
+          </item>
+          <tag><c>true</c></tag>
+          <item><p>Same as <c>line_counters</c>.</p></item>
+          <tag><c>false</c></tag>
+          <item><p>Disables coverage.</p></item>
+        </taglist>
+      </item>
       <tag><marker id="+JPperf"/><c>+JPperf true|false|dump|map|fp|no_fp</c></tag>
       <item>
         <p>Enables or disables support for the <c>perf</c> profiler when
diff --git a/erts/emulator/Makefile.in b/erts/emulator/Makefile.in
index c0f0fc1cd4..e0cce0203f 100644
--- a/erts/emulator/Makefile.in
+++ b/erts/emulator/Makefile.in
@@ -1119,7 +1119,8 @@ RUN_OBJS += \
 	$(OBJDIR)/erl_global_literals.o \
 	$(OBJDIR)/beam_file.o \
 	$(OBJDIR)/beam_types.o \
-	$(OBJDIR)/erl_term_hashing.o
+	$(OBJDIR)/erl_term_hashing.o \
+	$(OBJDIR)/erl_bif_coverage.o
 
 LTTNG_OBJS = $(OBJDIR)/erlang_lttng.o
 
diff --git a/erts/emulator/beam/atom.names b/erts/emulator/beam/atom.names
index 06164e9f6a..a33589f1e7 100644
--- a/erts/emulator/beam/atom.names
+++ b/erts/emulator/beam/atom.names
@@ -313,6 +313,7 @@ atom format_cpu_topology
 atom free
 atom fullsweep_after
 atom function
+atom function_counters
 atom functions
 atom function_clause
 atom garbage_collect
@@ -397,6 +398,7 @@ atom ldflags
 atom Le='=<'
 atom lf
 atom line
+atom line_counters
 atom line_delimiter
 atom line_length
 atom linked_in_driver
diff --git a/erts/emulator/beam/beam_bif_load.c b/erts/emulator/beam/beam_bif_load.c
index a4fc8632c6..f0437ac3f1 100644
--- a/erts/emulator/beam/beam_bif_load.c
+++ b/erts/emulator/beam/beam_bif_load.c
@@ -2079,6 +2079,7 @@ BIF_RETTYPE erts_internal_purge_module_2(BIF_ALIST_2)
                               modp->old.code_hdr->are_nifs);
                 }
 
+                beam_load_purge_aux(modp->old.code_hdr);
 #ifndef BEAMASM
                 erts_free(ERTS_ALC_T_CODE, (void *) modp->old.code_hdr);
 #else
diff --git a/erts/emulator/beam/beam_code.h b/erts/emulator/beam/beam_code.h
index 7e8d2c744b..dfe192b41e 100644
--- a/erts/emulator/beam/beam_code.h
+++ b/erts/emulator/beam/beam_code.h
@@ -87,6 +87,18 @@ typedef struct beam_code_header {
      */
     const BeamCodeLineTab *line_table;
 
+#ifdef BEAMASM
+
+    /*
+     * Coverage support.
+     */
+    Uint coverage_mode;
+    void *coverage;
+    byte *line_coverage_valid;
+    Uint line_coverage_len;
+
+#endif
+
     /*
      * Pointer to the module MD5 sum (16 bytes)
      */
diff --git a/erts/emulator/beam/beam_common.c b/erts/emulator/beam/beam_common.c
index f278ca7707..57d179f5d7 100644
--- a/erts/emulator/beam/beam_common.c
+++ b/erts/emulator/beam/beam_common.c
@@ -948,6 +948,9 @@ save_stacktrace(Process* c_p, ErtsCodePtr pc, Eterm* reg,
             break;
 
             /* Kernel */
+        case am_code:
+            format_module = am_erl_kernel_errors;
+            break;
         case am_os:
             format_module = am_erl_kernel_errors;
             break;
diff --git a/erts/emulator/beam/beam_file.c b/erts/emulator/beam/beam_file.c
index ede07f36ef..670a9994c0 100644
--- a/erts/emulator/beam/beam_file.c
+++ b/erts/emulator/beam/beam_file.c
@@ -453,8 +453,8 @@ static int parse_line_chunk(BeamFile *beam, IFF_Chunk *chunk) {
      * have to special-case it anywhere else. */
     name_count++;
 
-    /* Flags are unused at the moment. */
-    (void)flags;
+    /* Save flags. */
+    lines->flags = flags;
 
     /* Reserve space for the "undefined location" entry. */
     item_count++;
diff --git a/erts/emulator/beam/beam_file.h b/erts/emulator/beam/beam_file.h
index 7168ffc793..f32f9db267 100644
--- a/erts/emulator/beam/beam_file.h
+++ b/erts/emulator/beam/beam_file.h
@@ -124,6 +124,11 @@ typedef struct {
     BeamFile_LineEntry *items;
 } BeamFile_LineTable;
 
+enum beamfile_line_flags {
+    BEAMFILE_EXECUTABLE_LINE = 1, /* The executable_line instruction is used. */
+    BEAMFILE_FORCE_LINE_COUNTERS = 2 /* Force emission of line counters. */
+};
+
 typedef struct {
     struct erl_heap_fragment *heap_fragments;
     Eterm value;
diff --git a/erts/emulator/beam/beam_load.h b/erts/emulator/beam/beam_load.h
index 0afdace2d3..56f3c55f29 100644
--- a/erts/emulator/beam/beam_load.h
+++ b/erts/emulator/beam/beam_load.h
@@ -64,6 +64,8 @@ struct erl_module_instance;
 void beam_load_finalize_code(LoaderState *stp,
                              struct erl_module_instance* inst_p);
 
+void beam_load_purge_aux(const BeamCodeHeader *hdr);
+
 void beam_load_new_genop(LoaderState* stp);
 
 #ifndef BEAMASM
diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab
index 6d23430506..614e8357c8 100644
--- a/erts/emulator/beam/bif.tab
+++ b/erts/emulator/beam/bif.tab
@@ -783,3 +783,13 @@ bif erts_internal:list_to_integer/2
 ubif erlang:min/2
 ubif erlang:max/2
 bif erts_internal:term_to_string/2
+
+#
+# New in 27.
+#
+bif code:coverage_support/0
+bif code:get_coverage_mode/0
+bif code:get_coverage_mode/1
+bif code:get_coverage/2
+bif code:reset_coverage/1
+bif code:set_coverage_mode/1
diff --git a/erts/emulator/beam/emu/emu_load.c b/erts/emulator/beam/emu/emu_load.c
index 3821b797e6..16ec0aa4c4 100644
--- a/erts/emulator/beam/emu/emu_load.c
+++ b/erts/emulator/beam/emu/emu_load.c
@@ -1525,3 +1525,7 @@ int beam_load_emit_op(LoaderState *stp, BeamOp *tmp_op) {
 load_error:
     return 0;
 }
+
+void beam_load_purge_aux(const BeamCodeHeader *hdr)
+{
+}
diff --git a/erts/emulator/beam/erl_alloc.types b/erts/emulator/beam/erl_alloc.types
index 8d70441295..7dd79bacfb 100644
--- a/erts/emulator/beam/erl_alloc.types
+++ b/erts/emulator/beam/erl_alloc.types
@@ -308,6 +308,7 @@ type	SL_MPATHS	SHORT_LIVED	SYSTEM		sl_migration_paths
 
 type    DSIG_HNDL_NTFY  SHORT_LIVED     PROCESSES       dirty_signal_handler_notification
 type    SCHD_SIG_NTFY   SHORT_LIVED     PROCESSES       scheduled_signal_notify
+type	CODE_COVERAGE   STANDARD        SYSTEM          code_coverage
 
 #
 # Types used for special emulators
diff --git a/erts/emulator/beam/erl_bif_coverage.c b/erts/emulator/beam/erl_bif_coverage.c
new file mode 100644
index 0000000000..ad5e487169
--- /dev/null
+++ b/erts/emulator/beam/erl_bif_coverage.c
@@ -0,0 +1,415 @@
+/*
+ * %CopyrightBegin%
+ *
+ * Copyright Ericsson AB 2023. All Rights Reserved.
+ *
+ * Licensed under the Apache License, Version 2.0 (the "License");
+ * you may not use this file except in compliance with the License.
+ * You may obtain a copy of the License at
+ *
+ *     http://www.apache.org/licenses/LICENSE-2.0
+ *
+ * Unless required by applicable law or agreed to in writing, software
+ * distributed under the License is distributed on an "AS IS" BASIS,
+ * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+ * See the License for the specific language governing permissions and
+ * limitations under the License.
+ *
+ * %CopyrightEnd%
+ */
+
+#ifdef HAVE_CONFIG_H
+#  include "config.h"
+#endif
+
+#include "sys.h"
+#include "erl_vm.h"
+#include "global.h"
+#include "erl_process.h"
+#include "error.h"
+#include "bif.h"
+#include "beam_load.h"
+#include "beam_file.h"
+
+#include "jit/beam_asm.h"
+
+BIF_RETTYPE
+code_coverage_support_0(BIF_ALIST_0)
+{
+#ifdef BEAMASM
+    BIF_RET(am_true);
+#else
+    BIF_RET(am_false);
+#endif
+}
+
+BIF_RETTYPE
+code_set_coverage_mode_1(BIF_ALIST_1)
+{
+#ifdef BEAMASM
+    Eterm old_mode;
+
+    switch (erts_coverage_mode) {
+    case ERTS_COV_FUNCTION:
+        old_mode = am_function;
+        break;
+    case ERTS_COV_FUNCTION_COUNTERS:
+        old_mode = am_function_counters;
+        break;
+    case ERTS_COV_LINE:
+        old_mode = am_line;
+        break;
+    case ERTS_COV_LINE_COUNTERS:
+        old_mode = am_line_counters;
+        break;
+    case ERTS_COV_NONE:
+        old_mode = am_none;
+        break;
+    default:
+        ASSERT(0);
+        old_mode = am_none;
+        break;
+    }
+
+    switch (BIF_ARG_1) {
+    case am_none:
+        erts_coverage_mode = ERTS_COV_NONE;
+        BIF_RET(old_mode);
+    case am_function:
+        erts_coverage_mode = ERTS_COV_FUNCTION;
+        BIF_RET(old_mode);
+    case am_function_counters:
+        erts_coverage_mode = ERTS_COV_FUNCTION_COUNTERS;
+        BIF_RET(old_mode);
+    case am_line:
+        erts_coverage_mode = ERTS_COV_LINE;
+        BIF_RET(old_mode);
+    case am_line_counters:
+        erts_coverage_mode = ERTS_COV_LINE_COUNTERS;
+        BIF_RET(old_mode);
+    }
+#endif
+
+    BIF_ERROR(BIF_P, BADARG);
+}
+
+BIF_RETTYPE
+code_get_coverage_mode_0(BIF_ALIST_0)
+{
+#ifdef BEAMASM
+    switch (erts_coverage_mode) {
+    case ERTS_COV_FUNCTION:
+        BIF_RET(am_function);
+    case ERTS_COV_FUNCTION_COUNTERS:
+        BIF_RET(am_function_counters);
+    case ERTS_COV_LINE:
+        BIF_RET(am_line);
+    case ERTS_COV_LINE_COUNTERS:
+        BIF_RET(am_line_counters);
+    case ERTS_COV_NONE:
+        BIF_RET(am_none);
+    default:
+        ASSERT(0);
+    }
+#endif
+
+    BIF_ERROR(BIF_P, BADARG);
+}
+
+BIF_RETTYPE
+code_get_coverage_mode_1(BIF_ALIST_1)
+{
+#ifdef BEAMASM
+    ErtsCodeIndex code_ix;
+    Module* modp;
+    const BeamCodeHeader* hdr;
+
+    if (is_not_atom(BIF_ARG_1)) {
+        BIF_ERROR(BIF_P, BADARG);
+    }
+    code_ix = erts_active_code_ix();
+    modp = erts_get_module(BIF_ARG_1, code_ix);
+    if (modp == NULL) {
+        BIF_ERROR(BIF_P, BADARG);
+    }
+    hdr = modp->curr.code_hdr;
+    if (hdr == NULL) {
+        BIF_ERROR(BIF_P, BADARG);
+    }
+
+    switch (hdr->coverage_mode) {
+    case ERTS_COV_FUNCTION:
+        BIF_RET(am_function);
+    case ERTS_COV_FUNCTION_COUNTERS:
+        BIF_RET(am_function_counters);
+    case ERTS_COV_LINE:
+        BIF_RET(am_line);
+    case ERTS_COV_LINE_COUNTERS:
+        BIF_RET(am_line_counters);
+    case ERTS_COV_NONE:
+        BIF_RET(am_none);
+    default:
+        ASSERT(0);
+    }
+#endif
+
+    BIF_ERROR(BIF_P, BADARG);
+}
+
+#ifdef BEAMASM
+static BIF_RETTYPE
+get_function_coverage(Process* c_p, const BeamCodeHeader* hdr)
+{
+    Eterm* hp;
+    Eterm* hend;
+    Eterm res;
+    Eterm tmp;
+    ssize_t i;
+    Uint alloc_size;
+
+    switch (hdr->coverage_mode) {
+    case ERTS_COV_FUNCTION: {
+        byte* p = hdr->coverage;
+
+        res = NIL;
+        alloc_size = (3 + 3 + 2) * hdr->num_functions;
+        hp = HAlloc(c_p, alloc_size);
+        hend = hp + alloc_size;
+        for (i = (ssize_t)(hdr->num_functions - 1); i >= 0; i--) {
+            if (hdr->functions[i]->mfa.function == am_module_info &&
+                hdr->functions[i]->mfa.arity <= 1) {
+                /* For consistency with function coverage in line
+                 * counters mode, don't include module_info/0 and
+                 * module_info/1 in the list. */
+                continue;
+            }
+
+            tmp = TUPLE2(hp, hdr->functions[i]->mfa.function,
+                         make_small(hdr->functions[i]->mfa.arity));
+            hp += 3;
+            tmp = TUPLE2(hp, tmp, p[i] ? am_true : am_false);
+            hp += 3;
+            res = CONS(hp, tmp, res);
+            hp += 2;
+        }
+        HRelease(c_p, hend, hp);
+        return res;
+    }
+    case ERTS_COV_FUNCTION_COUNTERS: {
+        Uint* p = hdr->coverage;
+
+        res = NIL;
+        alloc_size = (3 + 3 + 2) * hdr->num_functions;
+        hp = HAlloc(c_p, alloc_size);
+        hend = hp + alloc_size;
+        for (i = (ssize_t)(hdr->num_functions - 1); i >= 0; i--) {
+            if (hdr->functions[i]->mfa.function == am_module_info &&
+                hdr->functions[i]->mfa.arity <= 1) {
+                /* For consistency with function coverage in line
+                 * counters mode, don't include module_info/0 and
+                 * module_info/1 in the list. */
+                continue;
+            }
+
+            tmp = TUPLE2(hp, hdr->functions[i]->mfa.function,
+                         make_small(hdr->functions[i]->mfa.arity));
+            hp += 3;
+            tmp = TUPLE2(hp, tmp, make_small(MIN(p[i], MAX_SMALL)));
+            hp += 3;
+            res = CONS(hp, tmp, res);
+            hp += 2;
+        }
+        HRelease(c_p, hend, hp);
+        return res;
+    }
+    case ERTS_COV_LINE:
+    case ERTS_COV_LINE_COUNTERS: {
+        const BeamCodeLineTab *lt = hdr->line_table;
+        Eterm covered;
+
+        res = NIL;
+        alloc_size = (3 + 3 + 2) * hdr->num_functions;
+        hp = HAlloc(c_p, alloc_size);
+        hend = hp + alloc_size;
+        for (i = (ssize_t)(hdr->num_functions - 1); i >= 0; i--) {
+            int index = lt->func_tab[i] - lt->func_tab[0];
+            int high = lt->func_tab[i+1] - lt->func_tab[0];
+
+            if (hdr->functions[i]->mfa.function == am_module_info &&
+                hdr->functions[i]->mfa.arity <= 1) {
+                /* There are no executable_line instruction in the
+                 * module_info/0 and module_info/1 functions, and
+                 * therefore they would never be shown to be covered
+                 * regardless of coverage mode.
+                 */
+                continue;
+            }
+
+            if (hdr->coverage_mode == ERTS_COV_LINE) {
+                for (const byte *p = hdr->coverage; index < high && !p[index]; ) {
+                    index++;
+                }
+            } else {
+                ASSERT(hdr->coverage_mode == ERTS_COV_LINE_COUNTERS);
+                for (const Uint *p = hdr->coverage; index < high && !p[index]; ) {
+                    index++;
+                }
+            }
+
+            covered = index < high ? am_true : am_false;
+
+            tmp = TUPLE2(hp, hdr->functions[i]->mfa.function,
+                         make_small(hdr->functions[i]->mfa.arity));
+            hp += 3;
+            tmp = TUPLE2(hp, tmp, covered);
+            hp += 3;
+            res = CONS(hp, tmp, res);
+            hp += 2;
+        }
+        HRelease(c_p, hend, hp);
+        return res;
+    }
+    case ERTS_COV_NONE:
+    default:
+        BIF_ERROR(c_p, BADARG);
+    }
+}
+#endif
+
+#ifdef BEAMASM
+static BIF_RETTYPE
+get_line_coverage(Process* c_p, const BeamCodeHeader* hdr)
+{
+    const BeamCodeLineTab *lt;
+    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:
+    case ERTS_COV_LINE_COUNTERS:
+        break;
+    default:
+        BIF_ERROR(c_p, BADARG);
+    }
+
+    lt = hdr->line_table;
+
+    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;
+        void* coverage_array = hdr->coverage;
+
+        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;
+        }
+        if (coverage_mode == ERTS_COV_LINE) {
+            byte* p = coverage_array;
+            coverage = p[i] ? am_true : am_false;
+        } else if (coverage_mode == ERTS_COV_LINE_COUNTERS) {
+            Uint* p = coverage_array;
+            coverage = make_small(MIN(p[i], MAX_SMALL));
+        }
+        tmp = TUPLE2(hp, make_small(LOC_LINE(location)), 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)
+{
+#ifdef BEAMASM
+    ErtsCodeIndex code_ix;
+    Module* modp;
+    const BeamCodeHeader* hdr;
+
+    if (is_not_atom(BIF_ARG_2)) {
+        BIF_ERROR(BIF_P, BADARG);
+    }
+    code_ix = erts_active_code_ix();
+    modp = erts_get_module(BIF_ARG_2, code_ix);
+    if (modp == NULL) {
+        BIF_ERROR(BIF_P, BADARG);
+    }
+    hdr = modp->curr.code_hdr;
+    if (hdr == NULL) {
+        BIF_ERROR(BIF_P, BADARG);
+    }
+
+    switch (BIF_ARG_1) {
+    case am_function:
+        BIF_RET(get_function_coverage(BIF_P, hdr));
+    case am_line:
+        BIF_RET(get_line_coverage(BIF_P, hdr));
+    }
+#endif
+
+    BIF_ERROR(BIF_P, BADARG);
+}
+
+BIF_RETTYPE
+code_reset_coverage_1(BIF_ALIST_1)
+{
+#ifndef BEAMASM
+    BIF_ERROR(BIF_P, BADARG);
+#else
+    ErtsCodeIndex code_ix;
+    Module* modp;
+    const BeamCodeHeader* hdr;
+
+    if (is_not_atom(BIF_ARG_1)) {
+        BIF_ERROR(BIF_P, BADARG);
+    }
+    code_ix = erts_active_code_ix();
+    modp = erts_get_module(BIF_ARG_1, code_ix);
+    if (modp == NULL) {
+        BIF_ERROR(BIF_P, BADARG);
+    }
+    hdr = modp->curr.code_hdr;
+    if (hdr == NULL) {
+        BIF_ERROR(BIF_P, BADARG);
+    }
+
+    switch (hdr->coverage_mode) {
+    case ERTS_COV_FUNCTION:
+        sys_memset(hdr->coverage, 0, hdr->num_functions);
+        break;
+    case ERTS_COV_FUNCTION_COUNTERS:
+        sys_memset(hdr->coverage, 0, hdr->num_functions * sizeof(Uint));
+        break;
+    case ERTS_COV_LINE:
+        sys_memset(hdr->coverage, 0, hdr->line_coverage_len);
+        break;
+    case ERTS_COV_LINE_COUNTERS:
+        sys_memset(hdr->coverage, 0, hdr->line_coverage_len * sizeof(Uint));
+        break;
+    default:
+        BIF_ERROR(BIF_P, BADARG);
+    }
+    BIF_RET(am_ok);
+#endif
+}
diff --git a/erts/emulator/beam/erl_init.c b/erts/emulator/beam/erl_init.c
index 5f42548ca2..04379a6fb0 100644
--- a/erts/emulator/beam/erl_init.c
+++ b/erts/emulator/beam/erl_init.c
@@ -199,6 +199,7 @@ int erts_no_crash_dump = 0;	/* Use -d to suppress crash dump. */
 int erts_no_line_info = 0;	/* -L: Don't load line information */
 
 #ifdef BEAMASM
+Uint erts_coverage_mode = ERTS_COV_NONE; /* -JPcover: Enable coverage */
 int erts_jit_asm_dump = 0;	/* -JDdump: Dump assembly code */
 #endif
 
@@ -652,6 +653,7 @@ void erts_usage(void)
 
 #ifdef BEAMASM
     erts_fprintf(stderr, "-JDdump bool   enable or disable dumping of generated assembly code for each module loaded\n");
+    erts_fprintf(stderr, "-JPcover true|false|line|line_counters|function|function_counters  enable or disable instrumentation for coverage\n");
     erts_fprintf(stderr, "-JPperf true|false|dump|map|fp|no_fp   enable or disable support for perf on Linux\n");
     erts_fprintf(stderr, "-JMsingle bool enable the use of single-mapped RWX memory for JIT:ed code\n");
     erts_fprintf(stderr, "\n");
@@ -1766,6 +1768,24 @@ erl_start(int argc, char **argv)
                 erts_fprintf(stderr, "+JPperf is not supported on this platform\n");
                 erts_usage();
 #endif
+                } else if (has_prefix("cover", sub_param)) {
+                    arg = get_arg(sub_param+5, argv[i + 1], &i);
+                    if (sys_strcmp(arg, "true") == 0) {
+                        erts_coverage_mode = ERTS_COV_LINE_COUNTERS;
+                    } else if (sys_strcmp(arg, "false") == 0) {
+                        erts_coverage_mode = ERTS_COV_NONE;
+                    } else if (sys_strcmp(arg, "function") == 0) {
+                        erts_coverage_mode = ERTS_COV_FUNCTION;
+                    } else if (sys_strcmp(arg, "function_counters") == 0) {
+                        erts_coverage_mode = ERTS_COV_FUNCTION_COUNTERS;
+                    } else if (sys_strcmp(arg, "line_coverage") == 0) {
+                        erts_coverage_mode = ERTS_COV_LINE;
+                    } else if (sys_strcmp(arg, "line_counters") == 0) {
+                        erts_coverage_mode = ERTS_COV_LINE_COUNTERS;
+                    } else {
+                        erts_fprintf(stderr, "bad +JPcover flag %s\n", arg);
+                        erts_usage();
+                    }
                 }
                 break;
             case 'M':
@@ -2252,7 +2272,7 @@ erl_start(int argc, char **argv)
 	    /* suggested stack size (Kilo Words) for threads in thread pool */
 	    arg = get_arg(argv[i]+2, argv[i+1], &i);
 	    erts_async_thread_suggested_stack_size = atoi(arg);
-	    
+
 	    if ((erts_async_thread_suggested_stack_size
 		 < ERTS_ASYNC_THREAD_MIN_STACK_SIZE)
 		|| (erts_async_thread_suggested_stack_size >
@@ -2516,7 +2536,7 @@ erl_start(int argc, char **argv)
 	    = (Process *) erts_ptab_pix2intptr_ddrb(&erts_proc,
 						    internal_pid_index(pid));
 	ASSERT(erts_code_purger && erts_code_purger->common.id == pid);
-	erts_proc_inc_refc(erts_code_purger); 
+	erts_proc_inc_refc(erts_code_purger);
 
 	pid = erl_system_process_otp(erts_init_process_id,
                                      "erts_literal_area_collector",
diff --git a/erts/emulator/beam/global.h b/erts/emulator/beam/global.h
index 7f8e54b949..de3eeaccad 100644
--- a/erts/emulator/beam/global.h
+++ b/erts/emulator/beam/global.h
@@ -1255,6 +1255,14 @@ extern Eterm erts_error_logger_warnings;
 extern int erts_initialized;
 extern int erts_compat_rel;
 
+#define ERTS_COV_NONE 0
+#define ERTS_COV_FUNCTION 1
+#define ERTS_COV_FUNCTION_COUNTERS 2
+#define ERTS_COV_LINE 3
+#define ERTS_COV_LINE_COUNTERS 4
+
+extern Uint erts_coverage_mode;
+
 #ifdef BEAMASM
 extern int erts_jit_asm_dump;
 #endif
diff --git a/erts/emulator/beam/jit/arm/beam_asm.hpp b/erts/emulator/beam/jit/arm/beam_asm.hpp
index 7ab52fb5c0..505c9c077c 100644
--- a/erts/emulator/beam/jit/arm/beam_asm.hpp
+++ b/erts/emulator/beam/jit/arm/beam_asm.hpp
@@ -1083,6 +1083,8 @@ public:
 
     bool emit(unsigned op, const Span<ArgVal> &args);
 
+    void emit_coverage(void *coverage, Uint index, Uint size);
+
     void codegen(JitAllocator *allocator,
                  const void **executable_ptr,
                  void **writable_ptr,
diff --git a/erts/emulator/beam/jit/arm/instr_common.cpp b/erts/emulator/beam/jit/arm/instr_common.cpp
index 050d7e5361..e722cb3b0a 100644
--- a/erts/emulator/beam/jit/arm/instr_common.cpp
+++ b/erts/emulator/beam/jit/arm/instr_common.cpp
@@ -2680,3 +2680,34 @@ void BeamModuleAssembler::emit_i_perf_counter() {
 void BeamModuleAssembler::emit_mark_unreachable() {
     mark_unreachable();
 }
+
+void BeamModuleAssembler::emit_coverage(void *coverage, Uint index, Uint size) {
+    Uint address = Uint(coverage) + index * size;
+    comment("coverage index = %d", index);
+
+    mov_imm(TMP1, address);
+    if (size == sizeof(Uint)) {
+        if (hasCpuFeature(CpuFeatures::ARM::kLSE)) {
+            mov_imm(TMP2, 1);
+            a.ldaddal(TMP2, TMP2, arm::Mem(TMP1));
+        } else {
+            Label again = a.newLabel();
+            a.bind(again);
+            {
+                a.ldaxr(TMP2, arm::Mem(TMP1));
+                a.add(TMP2, TMP2, imm(1));
+                a.stlxr(TMP2, TMP2, arm::Mem(TMP1));
+                a.cbnz(TMP2, again);
+            }
+        }
+    } else if (size == sizeof(byte)) {
+        if ((address & 0xff) != 0) {
+            a.strb(TMP1.w(), arm::Mem(TMP1));
+        } else {
+            mov_imm(TMP2, 1);
+            a.strb(TMP2.w(), arm::Mem(TMP1));
+        }
+    } else {
+        ASSERT(0);
+    }
+}
diff --git a/erts/emulator/beam/jit/asm_load.c b/erts/emulator/beam/jit/asm_load.c
index 93a5971a21..52299031c0 100644
--- a/erts/emulator/beam/jit/asm_load.c
+++ b/erts/emulator/beam/jit/asm_load.c
@@ -69,6 +69,57 @@ int beam_load_prepare_emit(LoaderState *stp) {
     hdr->md5_ptr = NULL;
     hdr->are_nifs = NULL;
 
+    stp->coverage = hdr->coverage = NULL;
+    stp->line_coverage_valid = hdr->line_coverage_valid = NULL;
+
+    hdr->line_coverage_len = 0;
+
+    if (stp->beam.lines.flags & BEAMFILE_FORCE_LINE_COUNTERS) {
+        hdr->coverage_mode = ERTS_COV_LINE_COUNTERS;
+    } else if ((stp->beam.lines.flags & BEAMFILE_EXECUTABLE_LINE) == 0 &&
+               (erts_coverage_mode == ERTS_COV_LINE ||
+                erts_coverage_mode == ERTS_COV_LINE_COUNTERS)) {
+        /* A line coverage mode is enabled, but there are no
+         * executable_line instructions in this module; therefore,
+         * turn off coverage for this module. */
+        hdr->coverage_mode = ERTS_COV_NONE;
+    } else {
+        /* Use the system default coverage mode for this module. */
+        hdr->coverage_mode = erts_coverage_mode;
+    }
+
+    switch (hdr->coverage_mode) {
+    case ERTS_COV_FUNCTION:
+    case ERTS_COV_FUNCTION_COUNTERS: {
+        size_t alloc_size = hdr->num_functions;
+        if (hdr->coverage_mode == ERTS_COV_FUNCTION_COUNTERS) {
+            alloc_size *= sizeof(Uint);
+        }
+        stp->coverage = erts_alloc(ERTS_ALC_T_CODE_COVERAGE, alloc_size);
+        sys_memset(stp->coverage, 0, alloc_size);
+        break;
+    }
+    case ERTS_COV_LINE:
+    case ERTS_COV_LINE_COUNTERS: {
+        size_t alloc_size = stp->beam.lines.instruction_count;
+        Uint coverage_size;
+
+        if (hdr->coverage_mode == ERTS_COV_LINE) {
+            coverage_size = sizeof(byte);
+        } else {
+            coverage_size = sizeof(Uint);
+        }
+        stp->coverage = erts_alloc(ERTS_ALC_T_CODE_COVERAGE,
+                                   alloc_size * coverage_size);
+        sys_memset(stp->coverage, 0, alloc_size * coverage_size);
+        stp->line_coverage_valid =
+                erts_alloc(ERTS_ALC_T_CODE_COVERAGE, alloc_size);
+        sys_memset(stp->line_coverage_valid, 0, alloc_size);
+        hdr->line_coverage_len = alloc_size;
+        break;
+    }
+    }
+
     stp->load_hdr = hdr;
 
     stp->labels = erts_alloc(ERTS_ALC_T_PREPARED_CODE,
@@ -201,6 +252,16 @@ int beam_load_prepared_dtor(Binary *magic) {
         stp->func_line = NULL;
     }
 
+    if (stp->coverage) {
+        erts_free(ERTS_ALC_T_CODE_COVERAGE, stp->coverage);
+        stp->coverage = NULL;
+    }
+
+    if (stp->line_coverage_valid) {
+        erts_free(ERTS_ALC_T_CODE_COVERAGE, stp->line_coverage_valid);
+        stp->line_coverage_valid = NULL;
+    }
+
     if (stp->ba) {
         beamasm_delete_assembler(stp->ba);
         stp->ba = NULL;
@@ -586,6 +647,30 @@ int beam_load_emit_op(LoaderState *stp, BeamOp *tmp_op) {
             goto load_error;
         }
         break;
+    case op_executable_line_I: {
+        byte coverage_size = 0;
+
+        /* We'll save some memory by not inserting a line entry that
+         * is equal to the previous one. */
+        if (add_line_entry(stp, tmp_op->a[0].val, 0)) {
+            goto load_error;
+        }
+        if (stp->load_hdr->coverage_mode == ERTS_COV_LINE) {
+            coverage_size = sizeof(byte);
+        } else if (stp->load_hdr->coverage_mode == ERTS_COV_LINE_COUNTERS) {
+            coverage_size = sizeof(Uint);
+        }
+        if (coverage_size) {
+            unsigned loc_index = stp->current_li - 1;
+            ASSERT(stp->beam.lines.item_count > 0);
+            stp->line_coverage_valid[loc_index] = 1;
+            beamasm_emit_coverage(stp->ba,
+                                  stp->coverage,
+                                  loc_index,
+                                  coverage_size);
+        }
+        break;
+    }
     case op_int_code_end:
         /* End of code found. */
         if (stp->function_number != stp->beam.code.function_count) {
@@ -598,6 +683,27 @@ int beam_load_emit_op(LoaderState *stp, BeamOp *tmp_op) {
         stp->function = THE_NON_VALUE;
         stp->genop = NULL;
         stp->specific_op = -1;
+
+        if (stp->load_hdr->coverage_mode == ERTS_COV_LINE ||
+            stp->load_hdr->coverage_mode == ERTS_COV_LINE_COUNTERS) {
+            stp->load_hdr->line_coverage_len = stp->current_li;
+        }
+        break;
+    case op_i_test_yield:
+        if (stp->load_hdr->coverage_mode == ERTS_COV_FUNCTION) {
+            ASSERT(stp->function_number != 0);
+            beamasm_emit_coverage(stp->ba,
+                                  stp->coverage,
+                                  stp->function_number - 1,
+                                  sizeof(byte));
+        } else if (stp->load_hdr->coverage_mode == ERTS_COV_FUNCTION_COUNTERS) {
+            ASSERT(stp->function_number != 0);
+            beamasm_emit_coverage(stp->ba,
+                                  stp->coverage,
+                                  stp->function_number - 1,
+                                  sizeof(Uint));
+        }
+        break;
     }
 
     return 1;
@@ -781,6 +887,13 @@ int beam_load_finish_emit(LoaderState *stp) {
     stp->code_hdr = code_hdr_ro;
     stp->loaded_size = module_size;
 
+    /* Transfer ownership of the coverage tables to the loaded code. */
+    code_hdr_rw->coverage = stp->coverage;
+    code_hdr_rw->line_coverage_valid = stp->line_coverage_valid;
+
+    stp->coverage = NULL;
+    stp->line_coverage_valid = NULL;
+
     /*
      * Place the literals in their own allocated heap (for fast range check)
      * and fix up all instructions that refer to it.
@@ -1025,3 +1138,13 @@ void beam_load_finalize_code(LoaderState *stp,
     stp->writable_region = NULL;
     stp->code_hdr = NULL;
 }
+
+void beam_load_purge_aux(const BeamCodeHeader *hdr) {
+    if (hdr->coverage) {
+        erts_free(ERTS_ALC_T_CODE_COVERAGE, hdr->coverage);
+    }
+
+    if (hdr->line_coverage_valid) {
+        erts_free(ERTS_ALC_T_CODE_COVERAGE, hdr->line_coverage_valid);
+    }
+}
diff --git a/erts/emulator/beam/jit/beam_asm.h b/erts/emulator/beam/jit/beam_asm.h
index a0d82f82e1..595d579aa8 100644
--- a/erts/emulator/beam/jit/beam_asm.h
+++ b/erts/emulator/beam/jit/beam_asm.h
@@ -65,6 +65,10 @@ void beamasm_purge_module(const void *executable_region,
                           size_t size);
 void beamasm_delete_assembler(void *ba);
 int beamasm_emit(void *ba, unsigned specific_op, BeamOp *op);
+void beamasm_emit_coverage(void *instance,
+                           void *coverage,
+                           Uint index,
+                           Uint size);
 ErtsCodePtr beamasm_get_code(void *ba, int label);
 ErtsCodePtr beamasm_get_lambda(void *ba, int index);
 const byte *beamasm_get_rodata(void *ba, char *label);
diff --git a/erts/emulator/beam/jit/beam_jit_main.cpp b/erts/emulator/beam/jit/beam_jit_main.cpp
index 40679e8be5..000b3c6c70 100644
--- a/erts/emulator/beam/jit/beam_jit_main.cpp
+++ b/erts/emulator/beam/jit/beam_jit_main.cpp
@@ -523,6 +523,14 @@ extern "C"
         return ba->emit(specific_op, args);
     }
 
+    void beamasm_emit_coverage(void *instance,
+                               void *coverage,
+                               Uint index,
+                               Uint size) {
+        BeamModuleAssembler *ba = static_cast<BeamModuleAssembler *>(instance);
+        ba->emit_coverage(coverage, index, size);
+    }
+
     void beamasm_emit_call_nif(const ErtsCodeInfo *info,
                                void *normal_fptr,
                                void *lib,
diff --git a/erts/emulator/beam/jit/load.h b/erts/emulator/beam/jit/load.h
index 3f259cfe7e..54fb2b9213 100644
--- a/erts/emulator/beam/jit/load.h
+++ b/erts/emulator/beam/jit/load.h
@@ -82,6 +82,12 @@ struct LoaderState_ {
     unsigned int current_li; /* Current line instruction */
     unsigned int *func_line; /* Mapping from function to first line instr */
 
+    /*
+     * Coverage tables used during loading.
+     */
+    void *coverage;
+    byte *line_coverage_valid;
+
     /* Translates lambda indexes to their literals, if any. Lambdas that lack
      * a literal (for example if they have an environment) are represented by
      * ERTS_SWORD_MAX. */
diff --git a/erts/emulator/beam/jit/x86/beam_asm.hpp b/erts/emulator/beam/jit/x86/beam_asm.hpp
index 648a4bbc73..3f6c96387a 100644
--- a/erts/emulator/beam/jit/x86/beam_asm.hpp
+++ b/erts/emulator/beam/jit/x86/beam_asm.hpp
@@ -1169,6 +1169,8 @@ public:
 
     bool emit(unsigned op, const Span<ArgVal> &args);
 
+    void emit_coverage(void *coverage, Uint index, Uint size);
+
     void codegen(JitAllocator *allocator,
                  const void **executable_ptr,
                  void **writable_ptr,
diff --git a/erts/emulator/beam/jit/x86/instr_common.cpp b/erts/emulator/beam/jit/x86/instr_common.cpp
index 4c555e326c..3e556ad00d 100644
--- a/erts/emulator/beam/jit/x86/instr_common.cpp
+++ b/erts/emulator/beam/jit/x86/instr_common.cpp
@@ -2700,3 +2700,23 @@ void BeamModuleAssembler::emit_i_perf_counter() {
     a.bind(next);
     a.mov(getXRef(0), RET);
 }
+
+void BeamModuleAssembler::emit_coverage(void *coverage, Uint index, Uint size) {
+    Uint address = Uint(coverage) + index * size;
+    comment("coverage index = %d", index);
+
+    mov_imm(RET, address);
+    if (size == sizeof(Uint)) {
+        a.lock().inc(x86::qword_ptr(RET));
+    } else if (size == sizeof(byte)) {
+        if ((address & 0xff) != 0) {
+            /* The size of this instruction is two bytes. */
+            a.mov(x86::byte_ptr(RET), RETb);
+        } else {
+            /* The size of this instruction is three bytes. */
+            a.mov(x86::byte_ptr(RET), imm(1));
+        }
+    } else {
+        ASSERT(0);
+    }
+}
diff --git a/lib/kernel/doc/src/code.xml b/lib/kernel/doc/src/code.xml
index 5a1bb44cef..bbd6e345dd 100644
--- a/lib/kernel/doc/src/code.xml
+++ b/lib/kernel/doc/src/code.xml
@@ -326,6 +326,9 @@ zip:create("mnesia-4.4.7.ez",
     <datatype>
       <name name="cache"/>
     </datatype>
+    <datatype>
+      <name name="coverage_mode"/>
+    </datatype>
     <datatype>
       <name name="load_error_rsn"/>
     </datatype>
@@ -539,6 +542,14 @@ ok = code:finish_loading(Prepared),
           <c>code:lib_dir(compiler)</c>.</p>
       </desc>
     </func>
+    <func>
+      <name name="coverage_support" arity="0" since="OTP 27.0"/>
+      <fsummary>Query whether the system supports coverage.</fsummary>
+      <desc>
+        <p>Returns <c>true</c> if the system supports coverage and <c>false</c>
+        otherwise.</p>
+      </desc>
+    </func>
     <func>
       <name name="del_path" arity="1" since=""/>
       <fsummary>Delete a directory from the code path.</fsummary>
@@ -637,6 +648,111 @@ ok = code:finish_loading(Prepared),
 	</taglist>
       </desc>
     </func>
+    <func>
+      <name name="get_coverage" arity="2" since="OTP 27.0"/>
+      <fsummary>Get coverage for a module.</fsummary>
+      <desc>
+        <p>If <anno>Level</anno> is <c>function</c>, returns line coverage
+        for the given module according to its coverage mode:</p>
+        <taglist>
+          <tag><c>function</c></tag>
+          <item>For each function in module <anno>Module</anno>, a
+          boolean indicating whether that function has been executed
+          at least once is returned.
+          </item>
+          <tag><c>function_counters</c></tag>
+          <item>For each function in module <anno>Module</anno>, an
+          integer giving the number of times that line has been
+          executed is returned.
+          </item>
+          <tag><c>line</c></tag>
+          <item>For each function in module <anno>Module</anno>, a
+          boolean indicating whether that function has been executed
+          at least once is returned.
+          </item>
+          <tag><c>line_counters</c></tag>
+          <item>For each function in module <anno>Module</anno>, a
+          boolean indicating whether that function has been executed
+          at least once is returned (note that in this mode, counters for
+	  the number of times each function has been executed <strong>cannot</strong>
+	  be retrieved).
+          </item>
+        </taglist>
+        <p>If <anno>Level</anno> is <c>line</c>, returns line coverage
+        for the given module according to its coverage mode:</p>
+        <taglist>
+          <tag><c>line</c></tag>
+          <item>For each executable line in the module, a boolean
+          indicating whether that line has been executed at least once
+          is returned.
+          </item>
+          <tag><c>line_counters</c></tag>
+          <item>For each executable line in the module, an integer
+          giving the number of times that line was executed is returned.
+          </item>
+        </taglist>
+        <p>Failures:</p>
+        <taglist>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Level</anno></c> is not <c>function</c> or <c>line</c>.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Module</anno></c> is not an atom.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Module</anno></c> does not refer to a loaded module.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Module</anno></c> was not loaded in another
+          coverage mode than <c>none</c>.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If <anno>Level</anno> is <c>line</c> and
+          <c><anno>Module</anno></c> has not been loaded with either
+          <c>line</c> or <c>line_counters</c> enabled.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If the runtime system does not support coverage.
+          </item>
+        </taglist>
+      </desc>
+    </func>
+    <func>
+      <name name="get_coverage_mode" arity="0" since="OTP 27.0"/>
+      <fsummary>Returns the current coverage mode.</fsummary>
+      <type name="coverage_mode"/>
+      <desc>
+        <p>Returns the current coverage mode as set by option
+        <seecom marker="erts:erl#+JPcover">+JPcover</seecom> for <c>erl</c> or
+        <seemfa marker="#set_coverage_mode/1">set_coverage_mode/1</seemfa>.
+        </p>
+        <p>Failure:</p>
+        <taglist>
+          <tag><c>badarg</c></tag>
+          <item>If the runtime system does not support coverage.
+          </item>
+        </taglist>
+      </desc>
+    </func>
+    <func>
+      <name name="get_coverage_mode" arity="1" since="OTP 27.0"/>
+      <fsummary>Get the coverage mode for a module.</fsummary>
+      <desc>
+        <p>Get coverage mode for the given module.</p>
+        <p>Failures:</p>
+        <taglist>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Module</anno></c> is not an atom.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Module</anno></c> does not refer to a loaded module.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If the runtime system does not support coverage.
+          </item>
+        </taglist>
+      </desc>
+    </func>
     <func>
       <name name="get_doc" arity="1" since="OTP 23.0"/>
       <fsummary>Gets the documentation for a module.</fsummary>
@@ -981,6 +1097,29 @@ rpc:call(Node, code, load_binary, [Module, Filename, Binary]),
 	</taglist>
       </desc>
     </func>
+    <func>
+      <name name="reset_coverage" arity="1" since="OTP 27.0"/>
+      <fsummary>Reset coverage for a module.</fsummary>
+      <desc>
+        <p>Reset coverage information for module <anno>Module</anno>.</p>
+        <p>Failures:</p>
+        <taglist>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Module</anno></c> is not an atom.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Module</anno></c> does not refer to a loaded module.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Module</anno></c> was not loaded with
+          coverage enabled.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If the runtime system does not support coverage.
+          </item>
+        </taglist>
+      </desc>
+    </func>
     <func>
       <name name="root_dir" arity="0" since=""/>
       <fsummary>Root directory of Erlang/OTP.</fsummary>
@@ -993,6 +1132,74 @@ rpc:call(Node, code, load_binary, [Module, Filename, Binary]),
 "/usr/local/otp"</pre>
       </desc>
     </func>
+    <func>
+      <name name="set_coverage_mode" arity="1" since="OTP 27.0"/>
+      <fsummary>Set default coverage mode.</fsummary>
+      <type name="coverage_mode"/>
+      <desc>
+        <p>Sets the coverage mode for modules that are subsequently
+        loaded, similar to option <seecom
+        marker="erts:erl#+JPcover">+JPcover</seecom> for <c>erl</c>:</p>
+        <taglist>
+          <tag><c>function</c></tag>
+          <item><p>All modules that are loaded will be instrumented to
+          keep track of which functions are executed. Information
+          about which functions that have been executed can be
+          retrieved by calling <seemfa
+          marker="#get_coverage/2"><c>get_coverage(function, Module)</c></seemfa>.</p>
+          </item>
+          <tag><c>function_counters</c></tag>
+          <item><p>All modules that are loaded will be instrumented to
+          count how many times each function is executed. Information
+          about how many times each function has been executed can be
+          retrieved by calling <seemfa
+          marker="#get_coverage/2"><c>get_coverage(function,
+          Module)</c></seemfa>.</p>
+          </item>
+          <tag><c>line</c></tag>
+          <item><p>When modules that have been compiled with the
+          <seeerl
+          marker="compiler:compile#line_coverage"><c>line_coverage</c></seeerl>
+          option are loaded, they will be instrumented to keep track
+          of which lines have been executed. Information about which
+          lines have been executed can be retrieved by calling <seemfa
+          marker="#get_coverage/2"><c>get_coverage(line,
+          Module)</c></seemfa>, and information about which functions
+          that have been executed can be retrieved by calling <seemfa
+          marker="#get_coverage/2"><c>get_coverage(function,
+          Module)</c></seemfa>.</p>
+          </item>
+          <tag><c>line_counters</c></tag>
+          <item><p>When modules that have been compiled with the
+          <seeerl
+          marker="compiler:compile#line_coverage"><c>line_coverage</c></seeerl>
+          option are loaded, they will be instrumented to count the
+          number of times each line is executed. Information about how
+          many times each line has been executed can be retrieved by
+          calling <seemfa
+          marker="#get_coverage/2"><c>get_coverage(line,
+          Module)</c></seemfa>, and information about which functions
+          that have been executed can be retrieved by calling <seemfa
+          marker="#get_coverage/2"><c>get_coverage(function,
+          Module)</c></seemfa> (note that in this mode, counters for
+	  the number of times each function has been executed <strong>cannot</strong>
+	  be retrieved).</p>
+          </item>
+          <tag><c>none</c></tag>
+          <item><p>Modules will be loaded without coverage instrumentation.</p></item>
+        </taglist>
+        <p>Returns the previous coverage mode.</p>
+        <p>Failures:</p>
+        <taglist>
+          <tag><c>badarg</c></tag>
+          <item>If <c><anno>Mode</anno></c> is not a valid coverage mode.
+          </item>
+          <tag><c>badarg</c></tag>
+          <item>If the runtime system does not support coverage.
+          </item>
+        </taglist>
+      </desc>
+    </func>
     <func>
       <name name="set_path" arity="1" since=""/>
       <name name="set_path" arity="2" since="OTP 26.0"/>
diff --git a/lib/kernel/src/code.erl b/lib/kernel/src/code.erl
index 0148d9c7aa..b54e105ac3 100644
--- a/lib/kernel/src/code.erl
+++ b/lib/kernel/src/code.erl
@@ -86,9 +86,19 @@
 -export_type([load_error_rsn/0, load_ret/0]).
 -export_type([prepared_code/0]).
 -export_type([module_status/0]).
-
 -include_lib("kernel/include/file.hrl").
 
+-export_type([coverage_mode/0]).
+-type coverage_mode() :: 'none' | 'function' | 'function_counters' |
+                         'line_coverage' | 'line_counters'.
+
+-export([coverage_support/0,
+         get_coverage/2,
+         get_coverage_mode/0,
+         get_coverage_mode/1,
+         reset_coverage/1,
+         set_coverage_mode/1]).
+
 %%----------------------------------------------------------------------------
 %% Some types for basic exported functions of this module
 %%----------------------------------------------------------------------------
@@ -1191,3 +1201,43 @@ path_files([Path|Tail]) ->
         _Error ->
             path_files(Tail)
     end.
+
+-spec get_coverage(Level, module()) -> Result when
+      Level :: 'function' | 'line',
+      Result :: [{Entity, CoverageInfo}],
+      Entity :: {Function, Arity} | Line,
+      CoverageInfo :: Covered | Counter,
+      Function :: atom(),
+      Arity :: arity(),
+      Line :: non_neg_integer(),
+      Covered :: boolean(),
+      Counter :: non_neg_integer().
+get_coverage(_Level, _Module) ->
+    erlang:nif_error(undefined).
+
+-spec get_coverage_mode() -> Mode when
+      Mode :: coverage_mode().
+get_coverage_mode() ->
+    erlang:nif_error(undefined).
+
+-spec get_coverage_mode(Module) -> Mode when
+      Module :: module(),
+      Mode :: coverage_mode().
+get_coverage_mode(_Module) ->
+    erlang:nif_error(undefined).
+
+-spec set_coverage_mode(Mode) -> OldMode when
+      Mode :: coverage_mode(),
+      OldMode :: coverage_mode().
+set_coverage_mode(_Mode) ->
+    erlang:nif_error(undefined).
+
+-spec reset_coverage(Module) -> 'ok' when
+      Module :: module().
+reset_coverage(_Module) ->
+    erlang:nif_error(undefined).
+
+-spec coverage_support() -> Supported when
+      Supported :: boolean().
+coverage_support() ->
+    erlang:nif_error(undefined).
diff --git a/lib/kernel/src/erl_kernel_errors.erl b/lib/kernel/src/erl_kernel_errors.erl
index ee5b77ad25..6db4c417ca 100644
--- a/lib/kernel/src/erl_kernel_errors.erl
+++ b/lib/kernel/src/erl_kernel_errors.erl
@@ -30,6 +30,8 @@ format_error(_Reason, [{M,F,As,Info}|_]) ->
     ErrorInfoMap = proplists:get_value(error_info, Info, #{}),
     Cause = maps:get(cause, ErrorInfoMap, none),
     Res = case M of
+              code ->
+                  format_code_error(F, As);
               erl_ddll ->
                   format_erl_ddll_error(F, As, Cause);
               os ->
@@ -39,6 +41,77 @@ format_error(_Reason, [{M,F,As,Info}|_]) ->
           end,
     format_error_map(Res, 1, #{}).
 
+format_code_error(get_coverage, [What,Module]) ->
+    coverage(
+      fun() ->
+              Error = case What of
+                          function -> [];
+                          line -> [];
+                          _ -> <<"must be one of: function or line">>
+                      end,
+              case Error of
+                  [] ->
+                      [[],if
+                              not is_atom(Module) ->
+                                  not_atom;
+                              true ->
+                                  case erlang:module_loaded(Module) of
+                                      false -> module_not_loaded;
+                                      true -> coverage_disabled
+                                  end
+                          end];
+                  _ ->
+                      [Error]
+              end
+      end);
+format_code_error(get_coverage_mode, [Module]) ->
+    coverage(
+      fun() ->
+              [if
+                   not is_atom(Module) ->
+                       not_atom;
+                   true ->
+                       case erlang:module_loaded(Module) of
+                           false -> module_not_loaded;
+                           true -> coverage_disabled
+                       end
+               end]
+      end);
+format_code_error(reset_coverage, [Module]) ->
+    coverage(
+      fun () ->
+              [if
+                   not is_atom(Module) ->
+                       not_atom;
+                   true ->
+                       case erlang:module_loaded(Module) of
+                           false -> module_not_loaded;
+                           true -> coverage_disabled
+                       end
+               end]
+      end);
+format_code_error(set_coverage_mode, [Mode]) ->
+    coverage(
+      fun () ->
+              [if
+                   not is_atom(Mode) ->
+                       not_atom;
+                   true ->
+                       <<"must be one of: none, function, function_counters, "
+                         "line, or line_counters">>
+               end]
+      end);
+format_code_error(_, _) ->
+    [].
+
+coverage(Fun) ->
+    case code:coverage_support() of
+        true ->
+            Fun();
+        false ->
+            [<<"this runtime system does not support coverage">>]
+    end.
+
 format_erl_ddll_error(_, _, _) ->
     [].
 
@@ -146,6 +219,8 @@ format_error_map([E|Es], ArgNum, Map) ->
 format_error_map([], _, Map) ->
     Map.
 
+expand_error(coverage_disabled) ->
+    <<"not loaded with coverage enabled">>;
 expand_error(eq_in_list) ->
     <<"\"=\" characters is not allowed in environment variable names">>;
 expand_error(zero_in_list) ->
@@ -158,6 +233,8 @@ expand_error(invalid_signal_option) ->
     <<"invalid signal handling option">>;
 expand_error(invalid_time_unit) ->
     <<"invalid time unit">>;
+expand_error(module_not_loaded) ->
+    <<"the atom does not refer to a loaded module">>;
 expand_error(not_atom) ->
     <<"not an atom">>;
 expand_error(not_charlist) ->
diff --git a/lib/kernel/test/Makefile b/lib/kernel/test/Makefile
index 4bd7e24f66..c00ae839d5 100644
--- a/lib/kernel/test/Makefile
+++ b/lib/kernel/test/Makefile
@@ -66,6 +66,7 @@ MODULES= \
 	block_select_dist \
 	code_SUITE \
 	code_b_test \
+	code_coverage_SUITE \
 	disk_log_SUITE \
 	erl_boot_server_SUITE \
 	erl_distribution_SUITE \
diff --git a/lib/kernel/test/code_coverage_SUITE.erl b/lib/kernel/test/code_coverage_SUITE.erl
new file mode 100644
index 0000000000..925c316ae2
--- /dev/null
+++ b/lib/kernel/test/code_coverage_SUITE.erl
@@ -0,0 +1,273 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2023. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(code_coverage_SUITE).
+
+-export([all/0, suite/0, init_per_suite/1, end_per_suite/1]).
+-export([toggle_modes/1,
+         get_coverage/1,
+         error_info/1]).
+
+-include_lib("common_test/include/ct.hrl").
+
+suite() ->
+    [{ct_hooks,[ts_install_cth]},
+     {timetrap, {minutes, 1}}].
+
+init_per_suite(Config) ->
+    case code:coverage_support() of
+        true ->
+            Config;
+        false ->
+            {skip, "This runtime system does not support coverage"}
+    end.
+
+end_per_suite(Config) ->
+    Config.
+
+all() ->
+    [toggle_modes,get_coverage,error_info].
+
+toggle_modes(_Config) ->
+    none = code:get_coverage_mode(?MODULE),
+    OldMode = code:get_coverage_mode(),
+    try
+        do_toggle_modes(OldMode)
+    after
+        code:set_coverage_mode(OldMode)
+    end.
+
+do_toggle_modes(CurrentMode) ->
+    Modes = [none,line,line_counters,function,function_counters],
+    Last = lists:last(Modes),
+    Last = do_toggle_modes_1(CurrentMode, Modes),
+    ok.
+
+do_toggle_modes_1(Current, [Mode|Modes]) ->
+    Current = code:set_coverage_mode(Mode),
+    none = code:get_coverage_mode(?MODULE),
+    do_toggle_modes_1(Mode, Modes);
+do_toggle_modes_1(Current, []) ->
+    Current.
+
+get_coverage(Config) ->
+    PrivDir = proplists:get_value(priv_dir, Config),
+    OldMode = code:get_coverage_mode(),
+
+    try
+        do_get_coverage(PrivDir)
+    after
+        code:set_coverage_mode(OldMode)
+    end.
+
+do_get_coverage(PrivDir) ->
+    M = get_coverage_test,
+    S = ~"""
+        -module(get_coverage_test).
+        -export([fact/1,fib/1]).
+
+        fact(N) when is_integer(N), N >= 0 ->   %4
+            fact(N, 1).                         %5
+
+        fact(0, P) ->
+            P;                                  %8
+        fact(N, P) ->
+            fact(N - 1, P * N).                 %10
+
+        fib(N) ->
+            fib(N, 0, 1).                       %13
+
+        fib(0, _, B) ->
+            B;                                  %16
+        fib(N, A, B) ->
+            fib(N - 1, B, A + B).               %18
+        """,
+
+    ErlFile = filename:join(PrivDir, atom_to_list(M) ++ ".erl"),
+    ok = file:write_file(ErlFile, S),
+    {ok,M,Beam} = compile:file(ErlFile, [report,binary,line_coverage]),
+
+    Run1 = fun() -> ok end,
+    Result1 = {[{{fact,1},0}, {{fact,2},0}, {{fib,1},0}, {{fib,3},0}],
+               [{5,0},{8,0},{10,0},{13,0},{16,0},{18,0}]},
+    do_get_coverage(M, Beam, Run1, Result1),
+
+    Run2 = fun() -> M:fib(5) end,
+    Result2 = {[{{fact,1},0}, {{fact,2},0}, {{fib,1},1}, {{fib,3},6}],
+               [{5,0},{8,0},{10,0},{13,1},{16,1},{18,5}]},
+    do_get_coverage(M, Beam, Run2, Result2),
+
+    %% Compile without line_coverage.
+    {ok,M,BeamFun} = compile:file(ErlFile, [report,binary]),
+    do_get_function_coverage(M, BeamFun, Run1, Result1),
+    do_ensure_no_line_coverage(M, BeamFun),
+
+    none = code:get_coverage_mode(?MODULE),
+
+    ok.
+
+do_get_coverage(M, Beam, RunFun, Result) ->
+    {FunctionResult,LineCoverage} = Result,
+    FunctionResultBool = [{F,N =/= 0} || {F,N} <- FunctionResult],
+
+    %% Test function coverage.
+
+    do_get_function_coverage(M, Beam, RunFun, Result),
+
+    %% Test line.
+
+    _ = code:set_coverage_mode(line),
+    {module,M} = code:load_binary(M, "", Beam),
+    _ = code:set_coverage_mode(none),
+    RunFun(),
+
+    line = code:get_coverage_mode(M),
+
+    LineCoverageBool = [{F,N =/= 0} || {F,N} <- LineCoverage],
+    FunctionResultBool = code:get_coverage(function, M),
+    LineCoverageBool = code:get_coverage(line, M),
+
+    LineCoverageBoolReset = [{F,false} || {F,_} <- LineCoverage],
+    code:reset_coverage(M),
+    LineCoverageBoolReset = code:get_coverage(line, M),
+
+    unload(M),
+
+    %% Test line_counters.
+
+    _ = code:set_coverage_mode(line_counters),
+    {module,M} = code:load_binary(M, "", Beam),
+    _ = code:set_coverage_mode(none),
+    RunFun(),
+
+    line_counters = code:get_coverage_mode(M),
+
+    FunctionResultBool = code:get_coverage(function, M),
+    LineCoverage = code:get_coverage(line, M),
+
+    LineCoverageZero = [{F,0} || {F,_} <- LineCoverage],
+    code:reset_coverage(M),
+    LineCoverageZero = code:get_coverage(line, M),
+
+    unload(M),
+
+    {'EXIT',{badarg,_}} = catch code:get_coverage(function, M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(line, M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage_mode(M),
+
+    ok.
+
+do_get_function_coverage(M, Beam, RunFun, Result) ->
+    {FunctionResult,_LineCoverage} = Result,
+    FunctionResultBool = [{F,N =/= 0} || {F,N} <- FunctionResult],
+    FunctionResultBoolReset = [{F,false} || {F,_} <- FunctionResult],
+    FunctionResultBoolZero = [{F,0} || {F,_} <- FunctionResult],
+
+    %% Test function mode.
+
+    _ = code:set_coverage_mode(function),
+    {module,M} = code:load_binary(M, "", Beam),
+    _ = code:set_coverage_mode(none),
+    RunFun(),
+
+    function = code:get_coverage_mode(M),
+
+    FunctionResultBool = code:get_coverage(function, M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(line, M),
+
+    code:reset_coverage(M),
+    FunctionResultBoolReset = code:get_coverage(function, M),
+
+    unload(M),
+
+    {'EXIT',{badarg,_}} = catch code:get_coverage_mode(M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(function, M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(line, M),
+
+    %% Test function_counters mode.
+
+    _ = code:set_coverage_mode(function_counters),
+    {module,M} = code:load_binary(M, "", Beam),
+    _ = code:set_coverage_mode(none),
+    RunFun(),
+
+    function_counters = code:get_coverage_mode(M),
+
+    FunctionResult = code:get_coverage(function, M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(line, M),
+
+    code:reset_coverage(M),
+    FunctionResultBoolZero = code:get_coverage(function, M),
+
+    unload(M),
+
+    {'EXIT',{badarg,_}} = catch code:get_coverage_mode(M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(function, M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(line, M),
+
+    ok.
+
+do_ensure_no_line_coverage(M, Beam) ->
+    %% Test line mode.
+    _ = code:set_coverage_mode(line),
+    {module,M} = code:load_binary(M, "", Beam),
+    _ = code:set_coverage_mode(none),
+    none = code:get_coverage_mode(M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(function, M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(line, M),
+
+    unload(M),
+
+    %% Test line counters mode.
+    _ = code:set_coverage_mode(line_counters),
+    {module,M} = code:load_binary(M, "", Beam),
+    _ = code:set_coverage_mode(none),
+    none = code:get_coverage_mode(M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(function, M),
+    {'EXIT',{badarg,_}} = catch code:get_coverage(line, M),
+
+    unload(M),
+
+    ok.
+
+unload(M) ->
+    true = code:delete(M),
+    _ = code:purge(M),
+    ok.
+
+error_info(_Config) ->
+    %% An atom referring that does not refer to a loaded module.
+    NotLoaded = not__a__loaded__module__I__hope,
+
+    L = [{get_coverage_mode, [42]},
+         {get_coverage_mode, [NotLoaded]},
+
+         {get_coverage, [line,42]},
+         {get_coverage, [line,NotLoaded]},
+         {get_coverage, [line,?MODULE]},
+         {get_coverage, [whatever,?MODULE]},
+
+         {reset_coverage, [42]},
+         {reset_coverage, [NotLoaded]},
+         {reset_coverage, [?MODULE]},
+
+         {set_coverage_mode, [42]},
+         {set_coverage_mode, [xyz]}],
+
+    error_info_lib:test_error_info(code, L, [snifs_only]).
-- 
2.35.3

openSUSE Build Service is sponsored by