Skip to content

Commit 07c979d

Browse files
committed
Merge branch 'michal/mnesia/fix-handling-node-name-as-atom-name/otp-19745' into maint
* michal/mnesia/fix-handling-node-name-as-atom-name/otp-19745: Test that node name can be used as table name in mnesia Avoid conflict between mnesia_down and master_nodes in mnesia_decision
2 parents 5fea6c4 + 0c8f423 commit 07c979d

File tree

2 files changed

+40
-12
lines changed

2 files changed

+40
-12
lines changed

lib/mnesia/src/mnesia_recover.erl

Lines changed: 18 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -223,15 +223,15 @@ note_decision(Tid, Outcome) ->
223223
?ets_insert(Tab, #transient_decision{tid = Tid, outcome = Outcome}).
224224

225225
note_up(Node, _Date, _Time) ->
226-
?ets_delete(mnesia_decision, Node).
226+
?ets_delete(mnesia_decision, {node, Node}).
227227

228228
note_down(Node, Date, Time) ->
229-
?ets_insert(mnesia_decision, {mnesia_down, Node, Date, Time}).
229+
?ets_insert(mnesia_decision, {mnesia_down, {node, Node}, Date, Time}).
230230

231231
note_master_nodes(Tab, []) ->
232-
?ets_delete(mnesia_decision, Tab);
232+
?ets_delete(mnesia_decision, {tab, Tab});
233233
note_master_nodes(Tab, Nodes) when is_list(Nodes) ->
234-
Master = {master_nodes, Tab, Nodes},
234+
Master = {master_nodes, {tab, Tab}, Nodes},
235235
?ets_insert(mnesia_decision, Master).
236236

237237
note_outcome(D) when D#decision.disc_nodes == [] ->
@@ -295,12 +295,12 @@ get_mnesia_downs() ->
295295
Tab = mnesia_decision,
296296
Pat = {mnesia_down, '_', '_', '_'},
297297
Downs = ?ets_match_object(Tab, Pat),
298-
[Node || {mnesia_down, Node, _Date, _Time} <- Downs].
298+
[Node || {mnesia_down, {node, Node}, _Date, _Time} <- Downs].
299299

300300
%% Check if we have got a mnesia_down from Node
301301
has_mnesia_down(Node) ->
302-
case ?ets_lookup(mnesia_decision, Node) of
303-
[{mnesia_down, Node, _Date, _Time}] ->
302+
case ?ets_lookup(mnesia_decision, {node, Node}) of
303+
[{mnesia_down, {node, Node}, _Date, _Time}] ->
304304
true;
305305
[] ->
306306
false
@@ -380,10 +380,10 @@ get_master_node_info() ->
380380

381381
get_master_node_tables() ->
382382
Masters = get_master_node_info(),
383-
[Tab || {master_nodes, Tab, _Nodes} <- Masters].
383+
[Tab || {master_nodes, {tab, Tab}, _Nodes} <- Masters].
384384

385385
get_master_nodes(Tab) ->
386-
try ?ets_lookup_element(mnesia_decision, Tab, 3)
386+
try ?ets_lookup_element(mnesia_decision, {tab, Tab}, 3)
387387
catch error:_ -> []
388388
end.
389389

@@ -532,7 +532,15 @@ confirm_decision_log_dump() ->
532532
dump_decision_tab() ->
533533
Tab = mnesia_decision,
534534
All = mnesia_lib:db_match_object(ram_copies,Tab, '_'),
535-
mnesia_log:save_decision_tab({decision_list, All}).
535+
Converted = lists:map(fun convert_decision_to_disk_format/1, All),
536+
mnesia_log:save_decision_tab({decision_list, Converted}).
537+
538+
convert_decision_to_disk_format({mnesia_down, {node, Node}, Date, Time}) ->
539+
{mnesia_down, Node, Date, Time};
540+
convert_decision_to_disk_format({master_nodes, {tab, Tab}, Nodes}) ->
541+
{master_nodes, Tab, Nodes};
542+
convert_decision_to_disk_format(Decision) ->
543+
Decision.
536544

537545
note_log_decisions([What | Tail], InitBy) ->
538546
note_log_decision(What, InitBy),

lib/mnesia/test/mnesia_recovery_test.erl

Lines changed: 22 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,8 @@
8787
after_corrupt_files_table_dat_head/1,
8888
after_corrupt_files_table_dat_tail/1,
8989
after_corrupt_files_schema_dat_head/1,
90-
after_corrupt_files_schema_dat_tail/1]).
90+
after_corrupt_files_schema_dat_tail/1,
91+
node_name_as_table_name/1]).
9192

9293
-export([reader/2, check/0, get_all_retainers/1,
9394
verify_data/2, verify_where2read/1,
@@ -122,7 +123,8 @@ all() ->
122123
coord_dies, {group, schema_trans}, {group, async_dirty},
123124
{group, sync_dirty}, {group, sym_trans},
124125
{group, asym_trans}, %% after_full_disc_partition,
125-
{group, after_corrupt_files}, disc_less, garb_decision
126+
{group, after_corrupt_files}, disc_less, garb_decision,
127+
node_name_as_table_name
126128
].
127129

128130
groups() ->
@@ -1725,3 +1727,21 @@ check_garb() ->
17251727
catch _:_ -> ok
17261728
end,
17271729
ok.
1730+
1731+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1732+
1733+
node_name_as_table_name(doc) ->
1734+
["Check node name can be used as table name."];
1735+
node_name_as_table_name(suite) ->
1736+
[];
1737+
node_name_as_table_name(Config) when is_list(Config) ->
1738+
[N1, N2] = All = ?acquire_nodes(2, Config),
1739+
Tab = N1,
1740+
1741+
?match({atomic, ok}, mnesia:create_table(Tab, [{ram_copies, [N1]}])),
1742+
1743+
?match([], mnesia_test_lib:kill_mnesia([N1])),
1744+
?match(ok, rpc:call(N1, mnesia, start, [[{extra_db_nodes, [N2]}]])),
1745+
?match(ok, rpc:call(N1, mnesia, wait_for_tables, [[Tab], 20000])),
1746+
1747+
?verify_mnesia(All, []).

0 commit comments

Comments
 (0)