File 3034-peer-Move-cover-start-of-peers-to-be-earlier.patch of Package erlang

From d7f1801788c7c4af01498e991641d3c47125ba7f Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Wed, 18 May 2022 09:02:36 +0200
Subject: [PATCH 4/4] peer: Move cover:start of peers to be earlier

If we want cover reports of the startup of the system we
need to start coverage as early as possible. This commit
moves the coverage start from after kernel starts to when
user_sup starts within kernel.
---
 lib/common_test/src/test_server.erl |  1 -
 lib/stdlib/src/peer.erl             | 25 +++++++++++++++++++++++--
 2 files changed, 23 insertions(+), 3 deletions(-)

diff --git a/lib/common_test/src/test_server.erl b/lib/common_test/src/test_server.erl
index aba1078bd1..9d893847c2 100644
--- a/lib/common_test/src/test_server.erl
+++ b/lib/common_test/src/test_server.erl
@@ -2844,7 +2844,6 @@ start_peer(#{name := Name} = Opts, Module) ->
             Shutdown = binary_to_term(term_to_binary({10000, CoverMain})),
             case peer:start_link(Opts#{args => FullArgs, shutdown => Shutdown}) of
                 {ok, Peer, Node} ->
-                    do_cover_for_node(Node, start),
                     {ok, Peer, Node};
                 Other ->
                     Other
diff --git a/lib/stdlib/src/peer.erl b/lib/stdlib/src/peer.erl
index fa2cf53f23..5ec9eb4f0a 100644
--- a/lib/stdlib/src/peer.erl
+++ b/lib/stdlib/src/peer.erl
@@ -332,6 +332,25 @@ handle_call({call, M, F, A}, From,
     origin_to_peer(tcp, Socket, {call, Seq, M, F, A}),
     {noreply, State#peer_state{outstanding = Out#{Seq => From}, seq = Seq + 1}};
 
+handle_call({starting, Node}, _From, #peer_state{ options = Options } = State) ->
+    case maps:find(shutdown, Options) of
+        {ok, {Timeout, MainCoverNode}} when is_integer(Timeout),
+                                            is_atom(MainCoverNode) ->
+
+            %% The node was started using test_server:start_peer/2 with cover enabled
+            %% so we should start cover on the starting node.
+            Modules = erpc:call(MainCoverNode,cover,modules,[]),
+            erpc:call(
+              Node, fun() ->
+                            Sticky = [ begin code:unstick_mod(M), M end
+                                       || M <- Modules, code:is_sticky(M)],
+                            erpc:call(MainCoverNode, cover, start, [Node]),
+                            [code:stick_mod(M) || M <- Sticky]
+                    end);
+        _ ->
+            ok
+    end,
+    {reply, ok, State};
 handle_call(get_node, _From, #peer_state{node = Node} = State) ->
     {reply, Node, State};
 
@@ -531,8 +550,9 @@ verify_args(Options) ->
     [error({invalid_arg, Arg}) || Arg <- Args, not io_lib:char_list(Arg)],
     %% alternative connection must be requested for non-distributed node,
     %%  or a distributed node when origin is not alive
-    is_map_key(connection, Options) orelse
-                                      (is_map_key(name, Options) andalso erlang:is_alive()) orelse error(not_alive),
+    is_map_key(connection, Options)
+        orelse
+          (is_map_key(name, Options) andalso erlang:is_alive()) orelse error(not_alive),
     %% exec must be a string, or a tuple of string(), [string()]
     case maps:find(exec, Options) of
         {ok, {Exec, Strs}} ->
@@ -933,6 +953,7 @@ start() ->
                       notify_when_started(dist, OriginProcess),
                       origin_link(MRef, OriginProcess)
               end),
+            ok = gen_server:call(OriginProcess, {starting, node()}),
             case init:get_argument(peer_detached) of
                 {ok, _} ->
                     %% We are detached, so setup 'user' process, I/O redirection:
-- 
2.35.3

openSUSE Build Service is sponsored by