Skip to content

Commit 01b3e23

Browse files
committed
Replace 'slave' with 'follower' in mnesia, use peer:start instead of slave:start
1 parent a85c81d commit 01b3e23

File tree

3 files changed

+20
-20
lines changed

3 files changed

+20
-20
lines changed

lib/mnesia/examples/bench/README

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -85,10 +85,10 @@ the invocation of
8585

8686
is equivalent with:
8787

88-
SlaveNodes = bench:start_all(Args).
88+
Followers = bench:start_all(Args).
8989
bench:populate(Args).
9090
bench:generate(Args).
91-
bench:stop_slave_nodes(SlaveNodes).
91+
bench:stop_follower_nodes(Followers).
9292

9393
In case you cannot get the automatic start of remote Erlang nodes to
9494
work (implied by bench:start_all/1) , you may need to manually start
@@ -202,7 +202,7 @@ always_try_nearest_node
202202
(fragmented) tables were distributed over all nodes. In
203203
such a system the transactions should be evenly distributed
204204
over all nodes. When this option is set to true it is possible
205-
to make fair measurements of master/slave configurations, when
205+
to make fair measurements of master/follower configurations, when
206206
all transactions are performed on on one node. Default is false.
207207

208208
cookie

lib/mnesia/examples/bench/bench.erl

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@
3939

4040
args_to_config/1, verify_config/2,
4141
start/0, start/1,
42-
stop_slave_nodes/1,
42+
stop_follower_nodes/1,
4343
bind_schedulers/0
4444
]).
4545

@@ -71,10 +71,10 @@ run() ->
7171

7272
run(Args) ->
7373
C = args_to_config(Args),
74-
SlaveNodes = start_all(C),
74+
FollowerNodes = start_all(C),
7575
bench_populate:start(C),
7676
Result = bench_generate:start(C),
77-
stop_slave_nodes(SlaveNodes),
77+
stop_follower_nodes(FollowerNodes),
7878
Result.
7979

8080
%% Start Mnesia on the local node
@@ -139,7 +139,7 @@ start_all(Args) ->
139139
erlang:set_cookie(node(), C#config.cookie),
140140
?d("Starting Erlang nodes...~n", []),
141141
?d("~n", []),
142-
SlaveNodes = do_start_all(Nodes, [], C#config.cookie),
142+
FollowerNodes = do_start_all(Nodes, [], C#config.cookie),
143143
Extra = [{extra_db_nodes, Nodes}],
144144
?d("~n", []),
145145
?d("Starting Mnesia...", []),
@@ -148,7 +148,7 @@ start_all(Args) ->
148148
case [R || R <- Replies, R /= ok] of
149149
[] ->
150150
io:format(" ok~n", []),
151-
SlaveNodes;
151+
FollowerNodes;
152152
Bad ->
153153
io:format(" FAILED: ~p~n", [Bad]),
154154
exit({mnesia_start, Bad})
@@ -163,7 +163,7 @@ do_start_all([Node | Nodes], Acc, Cookie) when is_atom(Node) ->
163163
[Name, Host] ->
164164
Arg = lists:concat(["-setcookie ", Cookie]),
165165
?d(" ~s", [left(Node)]),
166-
case slave:start_link(Host, Name, Arg) of
166+
case peer:start(#{host => Host, name => Name, args => Arg, peer_down => crash}) of
167167
{ok, Node} ->
168168
load_modules(Node),
169169
rpc:call(Node, ?MODULE, bind_schedulers, []),
@@ -175,14 +175,14 @@ do_start_all([Node | Nodes], Acc, Cookie) when is_atom(Node) ->
175175
do_start_all(Nodes, Acc, Cookie);
176176
{error, Reason} ->
177177
io:format(" FAILED:~p~n", [Reason]),
178-
stop_slave_nodes(Acc),
179-
exit({slave_start_failed, Reason})
178+
stop_follower_nodes(Acc),
179+
exit({follower_start_failed, Reason})
180180
end;
181181
_ ->
182182
?d(" ~s FAILED: "
183183
"Not valid as node name. Must be 'name@host'.~n",
184184
[left(Node)]),
185-
stop_slave_nodes(Acc),
185+
stop_follower_nodes(Acc),
186186
exit({bad_node_name, Node})
187187
end;
188188
do_start_all([], StartedNodes, _Cookie) ->
@@ -200,20 +200,20 @@ load_modules(Node) ->
200200
end,
201201
lists:foreach(Fun, [bench, bench_generate, bench_populate, bench_trans]).
202202

203-
stop_slave_nodes([]) ->
203+
stop_follower_nodes([]) ->
204204
ok;
205-
stop_slave_nodes(Nodes) ->
205+
stop_follower_nodes(Nodes) ->
206206
?d("~n", []),
207207
?d("Stopping Erlang nodes...~n", []),
208208
?d("~n", []),
209-
do_stop_slave_nodes(Nodes).
209+
do_stop_follower_nodes(Nodes).
210210

211-
do_stop_slave_nodes([Node | Nodes]) ->
211+
do_stop_follower_nodes([Node | Nodes]) ->
212212
?d(" ~s", [left(Node)]),
213-
Res = slave:stop(Node),
213+
Res = peer:stop(Node),
214214
io:format(" ~p~n", [Res]),
215-
do_stop_slave_nodes(Nodes);
216-
do_stop_slave_nodes([]) ->
215+
do_stop_follower_nodes(Nodes);
216+
do_stop_follower_nodes([]) ->
217217
ok.
218218

219219
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

lib/mnesia/test/README

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ in the debugger. This demands a little bit of preparations:
6666
- Start the necessary number of nodes (normally 3).
6767
This may either be done by running the mt script or
6868
by starting the main node and then invoke mt:start_nodes()
69-
to start the extra nodes with slave.
69+
to start the extra nodes with `peer`.
7070

7171
- Ensure that the nodes are connected. The easiest way to do
7272
this is by invoking mt:ping().

0 commit comments

Comments
 (0)