File 6661-Replace-slave-with-peer-in-mnesia-use-peer-start-ins.patch of Package erlang

From 44762f1ae46bc15c806f76ee0b65f7ac5a3decaf Mon Sep 17 00:00:00 2001
From: Dmytro Lytovchenko <dima.lytovchenko@ericsson.com>
Date: Mon, 25 Aug 2025 15:15:47 +0200
Subject: [PATCH] Replace 'slave' with 'peer' in mnesia, use peer:start instead
 of slave:start Copyright headers in README files

---
 lib/mnesia/examples/bench/README    | 26 ++++++++++++++++++++---
 lib/mnesia/examples/bench/bench.erl | 32 ++++++++++++++---------------
 lib/mnesia/test/README              | 22 +++++++++++++++++++-
 3 files changed, 60 insertions(+), 20 deletions(-)

diff --git a/lib/mnesia/examples/bench/README b/lib/mnesia/examples/bench/README
index 52225c5f7d..0469050e27 100644
--- a/lib/mnesia/examples/bench/README
+++ b/lib/mnesia/examples/bench/README
@@ -1,3 +1,23 @@
+> %CopyrightBegin%
+>
+> SPDX-License-Identifier: Apache-2.0
+>
+> Copyright Ericsson AB 2001-2025. 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%
+
 Author  : Hakan Mattsson <hakan@cslab.ericsson.se>
 Created : 21 Jun 2001 by Hakan Mattsson <hakan@cslab.ericsson.se>
 
@@ -85,10 +105,10 @@ the invocation of
 
 is equivalent with:
 
-   SlaveNodes = bench:start_all(Args).
+   Peers = bench:start_all(Args).
    bench:populate(Args).
    bench:generate(Args).
-   bench:stop_slave_nodes(SlaveNodes).
+   bench:stop_peer_nodes(Peers).
 
 In case you cannot get the automatic start of remote Erlang nodes to
 work (implied by bench:start_all/1) , you may need to manually start
@@ -202,7 +222,7 @@ always_try_nearest_node
   (fragmented) tables were distributed over all nodes. In
   such a system the transactions should be evenly distributed
   over all nodes. When this option is set to true it is possible
-  to make fair measurements of master/slave configurations, when
+  to make fair measurements of master/peer configurations, when
   all transactions are performed on on one node. Default is false.
 
 cookie
diff --git a/lib/mnesia/examples/bench/bench.erl b/lib/mnesia/examples/bench/bench.erl
index edaea93c0d..f4ef9f56a9 100644
--- a/lib/mnesia/examples/bench/bench.erl
+++ b/lib/mnesia/examples/bench/bench.erl
@@ -39,7 +39,7 @@
 	 
 	 args_to_config/1, verify_config/2,
 	 start/0, start/1,
-	 stop_slave_nodes/1,
+	 stop_peer_nodes/1,
 	 bind_schedulers/0
         ]).
 
@@ -71,10 +71,10 @@ run() ->
 
 run(Args) ->
     C = args_to_config(Args),
-    SlaveNodes = start_all(C),
+    PeerNodes = start_all(C),
     bench_populate:start(C),
     Result = bench_generate:start(C),
-    stop_slave_nodes(SlaveNodes),
+    stop_peer_nodes(PeerNodes),
     Result.
 
 %% Start Mnesia on the local node
@@ -139,7 +139,7 @@ start_all(Args) ->
     erlang:set_cookie(node(), C#config.cookie),
     ?d("Starting Erlang nodes...~n", []),
     ?d("~n", []),
-   SlaveNodes = do_start_all(Nodes, [], C#config.cookie),
+    PeerNodes = do_start_all(Nodes, [], C#config.cookie),
     Extra = [{extra_db_nodes, Nodes}],
     ?d("~n", []),
     ?d("Starting Mnesia...", []),
@@ -148,7 +148,7 @@ start_all(Args) ->
 	    case [R || R <- Replies, R /= ok] of
 		[] ->
 		    io:format(" ok~n", []),
-		    SlaveNodes;
+                    PeerNodes;
 		Bad ->
 		    io:format(" FAILED: ~p~n", [Bad]),
 		    exit({mnesia_start, Bad})
@@ -163,7 +163,7 @@ do_start_all([Node | Nodes], Acc, Cookie) when is_atom(Node) ->
 	[Name, Host] ->
 	    Arg = lists:concat(["-setcookie ", Cookie]),
 	    ?d("    ~s", [left(Node)]),
-	    case slave:start_link(Host, Name, Arg) of
+            case peer:start_link(#{host => Host, name => Name, args => Arg}) of
 		{ok, Node} ->
 		    load_modules(Node),
 		    rpc:call(Node, ?MODULE, bind_schedulers, []),
@@ -175,14 +175,14 @@ do_start_all([Node | Nodes], Acc, Cookie) when is_atom(Node) ->
 		    do_start_all(Nodes, Acc, Cookie);
 		{error, Reason} ->
 		    io:format(" FAILED:~p~n", [Reason]),
-		    stop_slave_nodes(Acc),
-		    exit({slave_start_failed, Reason})
+		    stop_peer_nodes(Acc),
+                    exit({peer_node_start_failed, Reason})
 	    end;
 	_ ->
 	    ?d("    ~s FAILED: "
 	       "Not valid as node name. Must be 'name@host'.~n",
 	       [left(Node)]),
-	    stop_slave_nodes(Acc),
+	    stop_peer_nodes(Acc),
 	    exit({bad_node_name, Node})
     end;
 do_start_all([], StartedNodes, _Cookie) ->
@@ -200,20 +200,20 @@ load_modules(Node) ->
 	end,
     lists:foreach(Fun, [bench, bench_generate, bench_populate, bench_trans]).
 
-stop_slave_nodes([]) ->
+stop_peer_nodes([]) ->
     ok;
-stop_slave_nodes(Nodes) ->
+stop_peer_nodes(Nodes) ->
     ?d("~n", []),
     ?d("Stopping Erlang nodes...~n", []),
     ?d("~n", []),
-    do_stop_slave_nodes(Nodes).
+    do_stop_peer_nodes(Nodes).
 
-do_stop_slave_nodes([Node | Nodes]) ->
+do_stop_peer_nodes([Node | Nodes]) ->
     ?d("    ~s", [left(Node)]),
-    Res = slave:stop(Node),
+    Res = peer:stop(Node),
     io:format(" ~p~n", [Res]),
-    do_stop_slave_nodes(Nodes);
-do_stop_slave_nodes([]) ->
+    do_stop_peer_nodes(Nodes);
+do_stop_peer_nodes([]) ->
     ok.
 	    
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/mnesia/test/README b/lib/mnesia/test/README
index ee4220689b..8f9ed9b945 100644
--- a/lib/mnesia/test/README
+++ b/lib/mnesia/test/README
@@ -1,3 +1,23 @@
+> %CopyrightBegin%
+>
+> SPDX-License-Identifier: Apache-2.0
+>
+> Copyright Ericsson AB 2010-2025. 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%
+
 This directory contains the test suite of Mnesia.
 Compile it with "erl -make".
 
@@ -66,7 +86,7 @@ in the debugger. This demands a little bit of preparations:
   - Start the necessary number of nodes (normally 3).
     This may either be done by running the mt script or
     by starting the main node and then invoke mt:start_nodes()
-    to start the extra nodes with slave.
+    to start the extra nodes with `peer`.
 
   - Ensure that the nodes are connected. The easiest way to do
     this is by invoking mt:ping().
-- 
2.51.0

openSUSE Build Service is sponsored by