File 0578-mnesia-Allow-ram-nodes-to-be-deleted-with-del_table_.patch of Package erlang
From f98d37c498bced1c975fb37ecae741e402d1c449 Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Wed, 10 Dec 2025 09:21:45 +0100
Subject: [PATCH 1/2] mnesia: Allow ram nodes to be deleted with del_table_copy
If a table was not loaded anywhere del_table_copy(schema, Node) was
not allowed to be run.
It tried to grab a table lock but couldn't since where_to_write was
not set.
---
lib/mnesia/src/mnesia_controller.erl | 1 +
lib/mnesia/src/mnesia_lib.erl | 4 +-
lib/mnesia/src/mnesia_schema.erl | 6 ++-
lib/mnesia/src/mnesia_tm.erl | 27 ++++++----
lib/mnesia/test/mnesia_evil_coverage_test.erl | 51 ++++++++++++++-----
lib/mnesia/test/mt | 23 +++++----
6 files changed, 76 insertions(+), 36 deletions(-)
diff --git a/lib/mnesia/src/mnesia_controller.erl b/lib/mnesia/src/mnesia_controller.erl
index 99f8ea9b46..2278b2c4f5 100644
--- a/lib/mnesia/src/mnesia_controller.erl
+++ b/lib/mnesia/src/mnesia_controller.erl
@@ -1808,6 +1808,7 @@ update_where_to_wlock(Tab) ->
%% This code is rpc:call'ed from the tab_copier process
%% when it has *not* released it's table lock
unannounce_add_table_copy(Tab, To) ->
+ verbose("unannounce_add_table_copy ~w ~w~n", [Tab,To]),
?CATCH(del_active_replica(Tab, To)),
try To = val({Tab , where_to_read}),
mnesia_lib:set_remote_where_to_read(Tab)
diff --git a/lib/mnesia/src/mnesia_lib.erl b/lib/mnesia/src/mnesia_lib.erl
index f96b64710d..48ef7a703f 100644
--- a/lib/mnesia/src/mnesia_lib.erl
+++ b/lib/mnesia/src/mnesia_lib.erl
@@ -904,12 +904,12 @@ vcore_elem({_Item, Info}) ->
show("~tp~n", [Info]).
fix_error(X) ->
- set(last_error, X), %% for debugabililty
+ set(last_error, X), %% for debugging
case X of
{aborted, Reason} -> Reason;
{abort, Reason} -> Reason;
Y when is_atom(Y) -> Y;
- {'EXIT', {_Reason, {Mod, _, _}}} when is_atom(Mod) ->
+ {_Reason, [{Mod, _, _}|_]} when is_atom(Mod) ->
save(X),
case atom_to_list(Mod) of
[$m, $n, $e|_] -> badarg;
diff --git a/lib/mnesia/src/mnesia_schema.erl b/lib/mnesia/src/mnesia_schema.erl
index 428d2da695..e9b484c453 100644
--- a/lib/mnesia/src/mnesia_schema.erl
+++ b/lib/mnesia/src/mnesia_schema.erl
@@ -1780,7 +1780,10 @@ remove_node_from_tabs([Tab|Rest], Node) ->
remove_node_from_tabs(Rest, Node)];
_Ns ->
Cs3 = verify_cstruct(Cs2),
- get_tid_ts_and_lock(Tab, write),
+ case ?catch_val({Tab, active_replicas}) of
+ [] -> ok;
+ _ -> get_tid_ts_and_lock(Tab, write)
+ end,
[{op, del_table_copy, ram_copies, Node, vsn_cs2list(Cs3)}|
remove_node_from_tabs(Rest, Node)]
end
@@ -2841,6 +2844,7 @@ undo_prepare_commit(Tid, Commit) ->
[] ->
ignore;
Ops ->
+ verbose("undo prepare: ~w:~n ~p~n", [Tid, Ops]),
%% Catch to allow failure mnesia_controller may not be started
?SAFE(mnesia_controller:release_schema_commit_lock()),
undo_prepare_ops(Tid, Ops)
diff --git a/lib/mnesia/src/mnesia_tm.erl b/lib/mnesia/src/mnesia_tm.erl
index 8e5e517bce..34d69e0ebd 100644
--- a/lib/mnesia/src/mnesia_tm.erl
+++ b/lib/mnesia/src/mnesia_tm.erl
@@ -873,7 +873,7 @@ execute_transaction(Fun, Args, Factor, Retries, Type) ->
?SAFE(unlink(whereis(?MODULE))),
{atomic, Value};
{do_abort, Reason} ->
- check_exit(Fun, Args, Factor, Retries, {aborted, Reason}, Type);
+ check_exit(Fun, Args, Factor, Retries, {aborted, Reason}, [], Type);
{nested_atomic, Value} ->
mnesia_lib:incr_counter(trans_commits),
{atomic, Value}
@@ -881,9 +881,11 @@ execute_transaction(Fun, Args, Factor, Retries, Type) ->
Reason = {aborted, {throw, Value}},
return_abort(Fun, Args, Reason);
error:Reason:ST ->
- check_exit(Fun, Args, Factor, Retries, {Reason,ST}, Type);
- _:Reason ->
- check_exit(Fun, Args, Factor, Retries, Reason, Type)
+ check_exit(Fun, Args, Factor, Retries, Reason, ST, Type);
+ exit:{aborted, _R} = Reason:ST ->
+ check_exit(Fun, Args, Factor, Retries, Reason, ST, Type);
+ _:Reason:ST ->
+ check_exit(Fun, Args, Factor, Retries, Reason, ST, Type)
end.
apply_fun(Fun, Args, Type) ->
@@ -899,7 +901,7 @@ apply_fun(Fun, Args, Type) ->
Abort
end.
-check_exit(Fun, Args, Factor, Retries, Reason, Type) ->
+check_exit(Fun, Args, Factor, Retries, Reason, ST, Type) ->
case Reason of
{aborted, C = #cyclic{}} ->
maybe_restart(Fun, Args, Factor, Retries, Type, C);
@@ -908,7 +910,7 @@ check_exit(Fun, Args, Factor, Retries, Reason, Type) ->
{aborted, {bad_commit, N}} ->
maybe_restart(Fun, Args, Factor, Retries, Type, {bad_commit, N});
_ ->
- return_abort(Fun, Args, Reason)
+ return_abort(Fun, Args, Reason, ST)
end.
maybe_restart(Fun, Args, Factor, Retries, Type, Why) ->
@@ -1010,10 +1012,12 @@ decr(infinity) -> infinity;
decr(X) when is_integer(X), X > 1 -> X - 1;
decr(_X) -> 0.
-return_abort(Fun, Args, Reason) ->
+
+return_abort(Fun, Args, Reason) ->
+ return_abort(Fun, Args, Reason, []).
+
+return_abort(Fun, Args, Reason, ST) ->
{_Mod, Tid, Ts} = get(mnesia_activity_state),
- dbg_out("Transaction ~p calling ~tp with ~tp failed: ~n ~tp~n",
- [Tid, Fun, Args, Reason]),
OldStore = Ts#tidstore.store,
Nodes = get_elements(nodes, OldStore),
intercept_friends(Tid, Ts),
@@ -1021,6 +1025,8 @@ return_abort(Fun, Args, Reason) ->
Level = Ts#tidstore.level,
if
Level == 1 ->
+ verbose("Transaction ~p calling ~tp with ~tp failed: ~n ~tp~n ~tp~n",
+ [Tid, Fun, Args, Reason, ST]),
mnesia_locker:async_release_tid(Nodes, Tid),
?SAFE(?MODULE ! {delete_transaction, Tid}),
erase(mnesia_activity_state),
@@ -1806,9 +1812,10 @@ commit_participant(Protocol, Coord, Tid, Bin, C0, DiscNs, _RamNs) ->
mnesia_schema:undo_prepare_commit(Tid, C0),
?eval_debug_fun({?MODULE, commit_participant, pre_commit_undo_prepare}, [{tid, Tid}])
end
- catch _:Reason ->
+ catch _:Reason:ST ->
?eval_debug_fun({?MODULE, commit_participant, vote_no},
[{tid, Tid}]),
+ verbose("~w:~w: VOTE_NO: ~w ~w~n",[?MODULE, ?LINE, Reason, ST]),
reply(Coord, {vote_no, Tid, Reason}),
mnesia_schema:undo_prepare_commit(Tid, C0)
end,
diff --git a/lib/mnesia/test/mnesia_evil_coverage_test.erl b/lib/mnesia/test/mnesia_evil_coverage_test.erl
index 763d9054b7..7c470f3c49 100644
--- a/lib/mnesia/test/mnesia_evil_coverage_test.erl
+++ b/lib/mnesia/test/mnesia_evil_coverage_test.erl
@@ -369,16 +369,17 @@ evil_delete_db_node(Config) when is_list(Config) ->
Tab = evil_delete_db_node,
?match({atomic, ok}, mnesia:create_table(Tab, [{disc_copies, AllNodes}])),
-
+ ?match({atomic, ok}, mnesia:create_table(foobar, [{ram_copies, [Node2, Node3]}])),
+
?match([], mnesia_test_lib:stop_mnesia([Node2, Node3])),
?match({atomic, ok}, mnesia:del_table_copy(schema, Node2)),
-
+
RemNodes = AllNodes -- [Node2],
-
+
?match(RemNodes, mnesia:system_info(db_nodes)),
?match(RemNodes, mnesia:table_info(Tab, disc_copies)),
-
+
?verify_mnesia([Node1], []).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -1438,20 +1439,44 @@ dump_log(N, Tester) when N > 0 ->
dump_log(_, Tester) ->
Tester ! finished.
-
-wait_for_tables(doc) ->
+wait_for_tables(doc) ->
["Intf. test of wait_for_tables, see also force_load_table"];
wait_for_tables(suite) -> [];
wait_for_tables(Config) when is_list(Config) ->
[Node1, Node2] = Nodes = ?acquire_nodes(2, Config),
- Tab = wf_tab,
- Schema = [{name, Tab}, {ram_copies, [Node1, Node2]}],
- ?match({atomic, ok}, mnesia:create_table(Schema)),
- ?match(ok, mnesia:wait_for_tables([wf_tab], infinity)),
+ Tabs = [list_to_atom("wf_tab_" ++ integer_to_list(N)) || N <- lists:seq(1, 500)],
+ Schema = [{ram_copies, [Node1, Node2]}],
+ [{atomic, ok} = mnesia:create_table(Tab, Schema) || Tab <- Tabs],
+ ?match(stopped,mnesia:stop()),
+
+ ?match(ok, mnesia:start()),
+ ?match(timeout, element(1, mnesia:wait_for_tables(Tabs, 0))),
+ Check = fun(Time) ->
+ {Waited, ok} = timer:tc(mnesia, wait_for_tables, [Tabs, Time]),
+ io:format("~w Waited: ~wms~n", [node(), Waited div 1000]),
+ Waited div 1_000_000 < Time
+ end,
+ ?match(true, Check(timer:seconds(5))),
?match(ok, mnesia:wait_for_tables([], timer:seconds(5))),
- ?match({timeout, [bad_tab]}, mnesia:wait_for_tables([bad_tab], timer:seconds(5))),
- ?match(ok, mnesia:wait_for_tables([wf_tab], 0)),
+ ?match({timeout, [bad_tab]}, mnesia:wait_for_tables([bad_tab], timer:seconds(1))),
+ ?match(ok, mnesia:wait_for_tables([wf_tab_1], 0)),
?match({error,_}, mnesia:wait_for_tables([wf_tab], -1)),
+
+ ?match(stopped, erpc:call(Node2, mnesia, stop, [])),
+ fun Wait () -> %% Sync node_down
+ case mnesia:table_info(schema, active_replicas) of
+ [Node1] -> ok;
+ _ ->
+ timer:sleep(100),
+ _ = mnesia_controller:get_info(1000),
+ Wait()
+ end
+ end (),
+ {ok, foo, _} = mnesia:activate_checkpoint([{name, foo}, {max, Tabs}, {ram_overrides_dump, true}]),
+ ?match(ok, erpc:call(Node2, mnesia, start, [])),
+ ?match(true, erpc:call(Node2, fun() -> Check(5000) end)),
+ ?match(ok, mnesia:deactivate_checkpoint(foo)),
+
?verify_mnesia(Nodes, []).
force_load_table(suite) -> [];
@@ -1467,7 +1492,7 @@ force_load_table(Config) when is_list(Config) ->
mnesia_test_lib:kill_mnesia([Node2]),
%% timer:sleep(timer:seconds(5)),
?match(ok, mnesia:start()),
- ?match({timeout, [Tab]}, mnesia:wait_for_tables([Tab], 5)),
+ ?match({timeout, [Tab]}, mnesia:wait_for_tables([Tab], 2)),
?match({'EXIT', _}, mnesia:dirty_read({Tab, 1})),
?match(yes, mnesia:force_load_table(Tab)),
?match([{Tab, 1, test_ok}], mnesia:dirty_read({Tab, 1})),
diff --git a/lib/mnesia/test/mt b/lib/mnesia/test/mt
index f8bfdf09e6..d05255805c 100755
--- a/lib/mnesia/test/mt
+++ b/lib/mnesia/test/mt
@@ -1,5 +1,12 @@
#! /bin/sh -f
-# ``Licensed under the Apache License, Version 2.0 (the "License");
+#
+# %CopyrightBegin%
+#
+# SPDX-License-Identifier: Apache-2.0
+#
+# Copyright Ericsson AB 1999-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
#
@@ -10,12 +17,8 @@
# 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.
-#
-# The Initial Developer of the Original Code is Ericsson Utvecklings AB.
-# Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
-# AB. All Rights Reserved.''
-#
-# $Id$
+#
+# %CopyrightEnd%
#
#
# Author: Hakan Mattsson <hakan@erix.ericsson.se>
@@ -30,9 +33,9 @@ p="-pa $top/examples -pa $top/ebin -pa $top/test -mnesia_test_verbose true"
log=test_log$$
latest=test_log_latest
args=${1+"$@"}
-erlcmd="erl -sname a $p $args -mnesia_test_timeout"
-erlcmd1="erl -sname a1 $p $args"
-erlcmd2="erl -sname a2 $p $args"
+erlcmd="erl -sname a@localhost $p $args -mnesia_test_timeout"
+erlcmd1="erl -sname a1@localhost $p $args"
+erlcmd2="erl -sname a2@localhost $p $args"
if test z"$MT_TERM" = z ; then
MT_TERM=xterm
--
2.51.0