File 4122-Remove-use-of-module-slave.patch of Package erlang

From 507f713c5ae48d01f8858d99a68346b40d1ac12d Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Thu, 22 Sep 2022 17:11:36 +0200
Subject: [PATCH 02/27] Remove use of module 'slave'

---
 lib/ssl/test/ssl_bench_SUITE.erl      |  6 ++-
 lib/ssl/test/ssl_bench_test_lib.erl   | 57 ++++++++++++++++++++++++++-
 lib/ssl/test/ssl_dist_bench_SUITE.erl |  4 +-
 3 files changed, 62 insertions(+), 5 deletions(-)

diff --git a/lib/ssl/test/ssl_bench_SUITE.erl b/lib/ssl/test/ssl_bench_SUITE.erl
index f78ac9c9cc..104c373d26 100644
--- a/lib/ssl/test/ssl_bench_SUITE.erl
+++ b/lib/ssl/test/ssl_bench_SUITE.erl
@@ -1,7 +1,7 @@
 %%%-------------------------------------------------------------------
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2014-2020. All Rights Reserved.
+%% Copyright Ericsson AB 2014-2022. 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.
@@ -104,7 +104,7 @@ end_per_testcase(_Func, _Conf) ->
 
 
 -define(COUNT, 400).
--define(TC(Cmd), tc(fun() -> Cmd end, ?MODULE, ?LINE)).
+%%-define(TC(Cmd), tc(fun() -> Cmd end, ?MODULE, ?LINE)).
 
 -define(FPROF_CLIENT, false).
 -define(FPROF_SERVER, false).
@@ -365,6 +365,7 @@ setup_server_init(Type, Tc, Loop, PC, Certs) ->
     unlink(Pid),
     Res.
 
+-ifdef(TC).
 tc(Fun, Mod, Line) ->
     case timer:tc(Fun) of
 	{_,{'EXIT',Reason}} ->
@@ -377,6 +378,7 @@ tc(Fun, Mod, Line) ->
 	    io:format("~p:~p: Time: ~p\n", [Mod, Line, T]),
 	    R
     end.
+-endif.
 
 start_profile(eprof, Procs) ->
     profiling = eprof:start_profiling(Procs),
diff --git a/lib/ssl/test/ssl_bench_test_lib.erl b/lib/ssl/test/ssl_bench_test_lib.erl
index 04cda889df..7e40ce721f 100644
--- a/lib/ssl/test/ssl_bench_test_lib.erl
+++ b/lib/ssl/test/ssl_bench_test_lib.erl
@@ -20,13 +20,59 @@
 -module(ssl_bench_test_lib).
 
 %% API
--export([setup/1]).
+-export([setup/1, cleanup/1]).
 
 %% Internal exports
 -export([setup_server/1]).
 
 -define(remote_host, "NETMARKS_REMOTE_HOST").
 
+setup(Name) ->
+    NameStr = atom_to_list(Name),
+    case os:getenv(?remote_host) of
+        false ->
+            {ok, Host} = inet:gethostname(),
+            Remote = false,
+            ok;
+        Host ->
+            Remote = true,
+            ok
+    end,
+    Node = list_to_atom(NameStr ++ "@" ++ Host),
+    case net_adm:ping(Node) of
+        pong ->
+            Node;
+        pang ->
+            Pa = filename:dirname(code:which(?MODULE)),
+            PeerOptions =
+                #{name => NameStr,
+                  host => Host,
+                  args => ["-pa", Pa]},
+            {ok, _Pid, Node} =
+                peer:start(
+                  case Remote of
+                      true ->
+                          Ssh = find_executable("ssh"),
+                          Erl = find_executable("erl"),
+                          PeerOptions#{exec => {Ssh, [Host, Erl]}};
+                      false ->
+                          PeerOptions
+                  end),
+            Path = code:get_path(),
+            true = erpc:call(Node, code, set_path, [Path]),
+            ok = erpc:call(Node, ?MODULE, setup_server, [node()]),
+            ct:pal("Client (~p) using ~ts~n",[node(), code:which(ssl)]),
+            (Node =:= node()) andalso restrict_schedulers(client),
+            Node
+    end.
+
+find_executable(Prog) ->
+    case os:find_executable(Prog) of
+        false -> Prog;
+        P     -> P
+    end.
+
+-ifdef(undefined).
 setup(Name) ->
     Host = case os:getenv(?remote_host) of
 	       false ->
@@ -61,6 +107,7 @@ setup(Name) ->
     ct:pal("Client (~p) using ~ts~n",[node(), code:which(ssl)]),
     (Node =:= node()) andalso restrict_schedulers(client),
     Node.
+-endif.
 
 setup_server(ClientNode) ->
     (ClientNode =:= node()) andalso restrict_schedulers(server),
@@ -73,3 +120,11 @@ restrict_schedulers(Type) ->
     Extra =  if (Type =:= server) -> -Extra0; true -> Extra0 end,
     Scheds = erlang:system_info(schedulers),
     erlang:system_flag(schedulers_online, (Scheds div 2) + Extra).
+
+cleanup(Node) ->
+    try erpc:call(Node, erlang, halt, [], 5000) of
+        Result ->
+            ct:fail({unexpected_return, Result})
+    catch error : {erpc,noconnection} ->
+            ok
+    end.
diff --git a/lib/ssl/test/ssl_dist_bench_SUITE.erl b/lib/ssl/test/ssl_dist_bench_SUITE.erl
index a7b6bba807..58fa00ff2f 100644
--- a/lib/ssl/test/ssl_dist_bench_SUITE.erl
+++ b/lib/ssl/test/ssl_dist_bench_SUITE.erl
@@ -1,7 +1,7 @@
 %%%-------------------------------------------------------------------
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2017-2021. All Rights Reserved.
+%% Copyright Ericsson AB 2017-2022. 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.
@@ -166,7 +166,7 @@ init_per_suite(Config) ->
 
 end_per_suite(Config) ->
     ServerNode = proplists:get_value(server_node, Config),
-    slave:stop(ServerNode).
+    ssl_bench_test_lib:cleanup(ServerNode).
 
 init_per_group(ssl, Config) ->
     [{ssl_dist, true}, {ssl_dist_prefix, "SSL"}|Config];
-- 
2.35.3

openSUSE Build Service is sponsored by