Skip to content

Commit 89f849f

Browse files
committed
Fix del_table_copy loading loop
When a local table copy was deleted but not yet loaded mnesia could try to load it in a loop, which later when a table copy was added again could result in a crash, since we don't have locks on the receiver anymore. Tables can be simultaneously loaded and added. Fixed by removing the table from the loader queue when it is determined that the local copy is removed. Also don't 'fatal' crash mnesia if table couldn't be loaded due to table already existing.
1 parent d17819b commit 89f849f

File tree

3 files changed

+48
-28
lines changed

3 files changed

+48
-28
lines changed

lib/mnesia/src/mnesia_controller.erl

Lines changed: 18 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1121,6 +1121,10 @@ handle_cast({adopt_orphans, Node, Tabs}, State) ->
11211121
end,
11221122
noreply(State2);
11231123

1124+
handle_cast({del_table_copy, Tab}, #state{late_loader_queue = LLQ0, loader_queue = LQ0} = State0) ->
1125+
noreply(State0#state{late_loader_queue = gb_trees:delete_any(Tab, LLQ0),
1126+
loader_queue = gb_trees:delete_any(Tab, LQ0)});
1127+
11241128
handle_cast(Msg, State) ->
11251129
error("~p got unexpected cast: ~tp~n", [?SERVER_NAME, Msg]),
11261130
noreply(State).
@@ -1224,19 +1228,19 @@ handle_info(Done = #loader_done{worker_pid=WPid, table_name=Tab}, State0) ->
12241228
false ->
12251229
ignore
12261230
end,
1227-
case ?catch_val({Tab, active_replicas}) of
1228-
[_|_] -> % still available elsewhere
1231+
1232+
case {?catch_val({Tab, storage_type}), val({Tab, active_replicas})} of
1233+
{unknown, _} -> %% Should not have a local copy anymore
1234+
State1#state{late_loader_queue=gb_trees:delete_any(Tab, LateQueue0)};
1235+
{_, [_|_]} -> % still available elsewhere
12291236
{value,{_,Worker}} = lists:keysearch(WPid,1,get_loaders(State0)),
12301237
add_loader(Tab,Worker,State1);
1231-
_ ->
1238+
{ram_copies, []} ->
12321239
DelState = State1#state{late_loader_queue=gb_trees:delete_any(Tab, LateQueue0)},
1233-
case ?catch_val({Tab, storage_type}) of
1234-
ram_copies ->
1235-
cast({disc_load, Tab, ram_only}),
1236-
DelState;
1237-
_ ->
1238-
DelState
1239-
end
1240+
cast({disc_load, Tab, ram_only}),
1241+
DelState;
1242+
{_, []} -> %% Table deleted or not loaded anywhere
1243+
State1#state{late_loader_queue=gb_trees:delete_any(Tab, LateQueue0)}
12401244
end
12411245
end,
12421246
State3 = opt_start_worker(State2),
@@ -1764,6 +1768,10 @@ del_active_replica(Tab, Node) ->
17641768
set(Var, mark_blocked_tab(Blocked, New)), % where_to_commit
17651769
mnesia_lib:del({Tab, active_replicas}, Node),
17661770
mnesia_lib:del({Tab, where_to_write}, Node),
1771+
case Node =:= node() of
1772+
true -> cast({del_table_copy, Tab});
1773+
false -> ok
1774+
end,
17671775
update_where_to_wlock(Tab).
17681776

17691777
change_table_access_mode(Cs) ->
@@ -2098,7 +2106,6 @@ opt_start_loader(State = #state{loader_queue = LoaderQ}) ->
20982106
true ->
20992107
opt_start_loader(State#state{loader_queue = Rest});
21002108
false ->
2101-
%% Start worker but keep him in the queue
21022109
Pid = load_and_reply(self(), Worker),
21032110
State#state{loader_pid=[{Pid,Worker}|get_loaders(State)],
21042111
loader_queue = Rest}

lib/mnesia/src/mnesia_event.erl

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -109,7 +109,7 @@ handle_any_event(Msg, State) ->
109109
{ok, State}.
110110

111111
handle_table_event({Oper, Record, TransId}, State) ->
112-
report_info("~p performed by ~p on record:~n\t~tp~n",
112+
report_info("~p performed by ~p on record:~n\t~0tp~n",
113113
[Oper, TransId, Record]),
114114
{ok, State}.
115115

@@ -160,9 +160,12 @@ handle_system_event({mnesia_overload, Details}, State) ->
160160
report_warning("Mnesia is overloaded: ~tw~n", [Details]),
161161
{ok, State};
162162

163-
handle_system_event({mnesia_info, Format, Args}, State) ->
164-
report_info(Format, Args),
165-
{ok, State};
163+
handle_system_event({mnesia_info, Format, Args} = Event, State) ->
164+
case put(last, Event) of
165+
Event -> ok;
166+
_ -> report_info(Format, Args)
167+
end,
168+
{ok, State};
166169

167170
handle_system_event({mnesia_warning, Format, Args}, State) ->
168171
report_warning(Format, Args),

lib/mnesia/src/mnesia_loader.erl

Lines changed: 23 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ val(Var) ->
4747
disc_load_table(Tab, Reason, Cs) ->
4848
Storage = mnesia_lib:cs_to_storage_type(node(), Cs),
4949
Type = val({Tab, setorbag}),
50-
dbg_out("Getting table ~tp (~p) from disc: ~tp~n",
50+
dbg_out("Getting table ~0tp (~0p) from disc: ~0tp~n",
5151
[Tab, Storage, Reason]),
5252
?eval_debug_fun({?MODULE, do_get_disc_copy},
5353
[{tab, Tab},
@@ -56,9 +56,9 @@ disc_load_table(Tab, Reason, Cs) ->
5656
{type, Type}]),
5757
do_get_disc_copy2(Tab, Reason, Storage, Type).
5858

59-
do_get_disc_copy2(Tab, _Reason, Storage, _Type) when Storage == unknown ->
60-
verbose("Local table copy of ~tp has recently been deleted, ignored.~n",
61-
[Tab]),
59+
do_get_disc_copy2(Tab, Reason, Storage, _Type) when Storage == unknown ->
60+
verbose("Local table copy of ~0tp ~0p has recently been deleted, ignored.~n",
61+
[Tab, Reason]),
6262
{not_loaded, storage_unknown};
6363
do_get_disc_copy2(Tab, Reason, Storage, Type) when Storage == disc_copies ->
6464
%% NOW we create the actual table
@@ -206,14 +206,14 @@ try_net_load_table(Tab, Reason, Ns, Cs) ->
206206
end,
207207
do_get_network_copy(Tab, Reason, Ns, Storage, Cs).
208208

209-
do_get_network_copy(Tab, _Reason, _Ns, unknown, _Cs) ->
210-
verbose("Local table copy of ~tp has recently been deleted, ignored.~n", [Tab]),
209+
do_get_network_copy(Tab, Reason, _Ns, unknown, _Cs) ->
210+
verbose("Local table copy of ~0tp (~0p) has recently been deleted, ignored.~n", [Tab,Reason]),
211211
{not_loaded, storage_unknown};
212212
do_get_network_copy(Tab, Reason, Ns, Storage, Cs) ->
213213
[Node | Tail] = Ns,
214214
case lists:member(Node,val({current, db_nodes})) of
215215
true ->
216-
dbg_out("Getting table ~tp (~p) from node ~p: ~tp~n",
216+
dbg_out("Getting table ~0tp (~0p) from node ~0p: ~0tp~n",
217217
[Tab, Storage, Node, Reason]),
218218
?eval_debug_fun({?MODULE, do_get_network_copy},
219219
[{tab, Tab}, {reason, Reason},
@@ -289,6 +289,14 @@ init_receiver(Node, Tab,Storage,Cs,Reason) ->
289289
{atomic, {error,Result}} when
290290
element(1,Reason) == dumper ->
291291
{error,Result};
292+
{atomic, {error,{mktab, _} = Reason}} ->
293+
case val({Tab,where_to_read}) == node() of
294+
true -> %% Already loaded
295+
ok;
296+
false ->
297+
fatal("Cannot create table ~tp: ~tp~n",
298+
[[Tab, Storage], Reason])
299+
end;
292300
{atomic, {error,Result}} ->
293301
fatal("Cannot create table ~tp: ~tp~n",
294302
[[Tab, Storage], Result]);
@@ -415,26 +423,28 @@ create_table(Tab, TabSize, Storage, Cs) ->
415423
{ok, _} ->
416424
mnesia_lib:unlock_table(Tab),
417425
{Storage, Tab};
418-
Else ->
426+
{error, Reason} ->
419427
mnesia_lib:unlock_table(Tab),
420-
Else
428+
{error, {mktab, Reason}}
421429
end;
422430
(Storage == ram_copies) or (Storage == disc_copies) ->
423431
EtsOpts = proplists:get_value(ets, StorageProps, []),
424432
Args = [{keypos, 2}, public, named_table, Cs#cstruct.type | EtsOpts],
425433
case mnesia_monitor:unsafe_mktab(Tab, Args) of
426434
Tab ->
427435
{Storage, Tab};
428-
Else ->
429-
Else
436+
{error, Reason} ->
437+
{error, {mktab, Reason}}
430438
end;
431439
element(1, Storage) == ext ->
432440
{_, Alias, Mod} = Storage,
433441
case mnesia_monitor:unsafe_create_external(Tab, Alias, Mod, Cs) of
434442
ok ->
435443
{Storage, Tab};
436-
Else ->
437-
Else
444+
{error, Reason} ->
445+
{error, {mktab, Reason}};
446+
Reason ->
447+
{error, {mktab, Reason}}
438448
end
439449
end.
440450

0 commit comments

Comments
 (0)