File 2503-cover-Fix-lines-wrongly-reported-as-uncovered.patch of Package erlang

From 60323db3445e38a0de7f00c3b4013e2cae382c27 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 9 Oct 2024 06:09:40 +0200
Subject: [PATCH] cover: Fix lines wrongly reported as uncovered

Closes #8867
---
 lib/tools/src/cover.erl        | 13 +++++++-----
 lib/tools/test/cover_SUITE.erl | 37 +++++++++++++++++++++++++++++++++-
 2 files changed, 44 insertions(+), 6 deletions(-)

diff --git a/lib/tools/src/cover.erl b/lib/tools/src/cover.erl
index fc48997195..67b9841b20 100644
--- a/lib/tools/src/cover.erl
+++ b/lib/tools/src/cover.erl
@@ -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};
                 #{} ->
diff --git a/lib/tools/test/cover_SUITE.erl b/lib/tools/test/cover_SUITE.erl
index d9e77cd651..97cd9fb650 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, 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,
@@ -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------------------------------------------------------------
 
-- 
2.43.0

openSUSE Build Service is sponsored by