Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
* maint:
  Fix del_table_copy loading loop
  • Loading branch information
dgud committed Apr 25, 2024
2 parents e4344d2 + 019eff4 commit 940c1de
Show file tree
Hide file tree
Showing 3 changed files with 48 additions and 28 deletions.
29 changes: 18 additions & 11 deletions lib/mnesia/src/mnesia_controller.erl
Expand Up @@ -1122,6 +1122,10 @@ handle_cast({adopt_orphans, Node, Tabs}, State) ->
end, end,
noreply(State2); noreply(State2);


handle_cast({del_table_copy, Tab}, #state{late_loader_queue = LLQ0, loader_queue = LQ0} = State0) ->
noreply(State0#state{late_loader_queue = gb_trees:delete_any(Tab, LLQ0),
loader_queue = gb_trees:delete_any(Tab, LQ0)});

handle_cast(Msg, State) -> handle_cast(Msg, State) ->
error("~p got unexpected cast: ~tp~n", [?SERVER_NAME, Msg]), error("~p got unexpected cast: ~tp~n", [?SERVER_NAME, Msg]),
noreply(State). noreply(State).
Expand Down Expand Up @@ -1225,19 +1229,19 @@ handle_info(Done = #loader_done{worker_pid=WPid, table_name=Tab}, State0) ->
false -> false ->
ignore ignore
end, end,
case ?catch_val({Tab, active_replicas}) of
[_|_] -> % still available elsewhere case {?catch_val({Tab, storage_type}), val({Tab, active_replicas})} of
{unknown, _} -> %% Should not have a local copy anymore
State1#state{late_loader_queue=gb_trees:delete_any(Tab, LateQueue0)};
{_, [_|_]} -> % still available elsewhere
{value,{_,Worker}} = lists:keysearch(WPid,1,get_loaders(State0)), {value,{_,Worker}} = lists:keysearch(WPid,1,get_loaders(State0)),
add_loader(Tab,Worker,State1); add_loader(Tab,Worker,State1);
_ -> {ram_copies, []} ->
DelState = State1#state{late_loader_queue=gb_trees:delete_any(Tab, LateQueue0)}, DelState = State1#state{late_loader_queue=gb_trees:delete_any(Tab, LateQueue0)},
case ?catch_val({Tab, storage_type}) of cast({disc_load, Tab, ram_only}),
ram_copies -> DelState;
cast({disc_load, Tab, ram_only}), {_, []} -> %% Table deleted or not loaded anywhere
DelState; State1#state{late_loader_queue=gb_trees:delete_any(Tab, LateQueue0)}
_ ->
DelState
end
end end
end, end,
State3 = opt_start_worker(State2), State3 = opt_start_worker(State2),
Expand Down Expand Up @@ -1765,6 +1769,10 @@ del_active_replica(Tab, Node) ->
set(Var, mark_blocked_tab(Blocked, New)), % where_to_commit set(Var, mark_blocked_tab(Blocked, New)), % where_to_commit
mnesia_lib:del({Tab, active_replicas}, Node), mnesia_lib:del({Tab, active_replicas}, Node),
mnesia_lib:del({Tab, where_to_write}, Node), mnesia_lib:del({Tab, where_to_write}, Node),
case Node =:= node() of
true -> cast({del_table_copy, Tab});
false -> ok
end,
update_where_to_wlock(Tab). update_where_to_wlock(Tab).


change_table_access_mode(Cs) -> change_table_access_mode(Cs) ->
Expand Down Expand Up @@ -2099,7 +2107,6 @@ opt_start_loader(State = #state{loader_queue = LoaderQ}) ->
true -> true ->
opt_start_loader(State#state{loader_queue = Rest}); opt_start_loader(State#state{loader_queue = Rest});
false -> false ->
%% Start worker but keep him in the queue
Pid = load_and_reply(self(), Worker), Pid = load_and_reply(self(), Worker),
State#state{loader_pid=[{Pid,Worker}|get_loaders(State)], State#state{loader_pid=[{Pid,Worker}|get_loaders(State)],
loader_queue = Rest} loader_queue = Rest}
Expand Down
11 changes: 7 additions & 4 deletions lib/mnesia/src/mnesia_event.erl
Expand Up @@ -110,7 +110,7 @@ handle_any_event(Msg, State) ->
{ok, State}. {ok, State}.


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


Expand Down Expand Up @@ -161,9 +161,12 @@ handle_system_event({mnesia_overload, Details}, State) ->
report_warning("Mnesia is overloaded: ~tw~n", [Details]), report_warning("Mnesia is overloaded: ~tw~n", [Details]),
{ok, State}; {ok, State};


handle_system_event({mnesia_info, Format, Args}, State) -> handle_system_event({mnesia_info, Format, Args} = Event, State) ->
report_info(Format, Args), case put(last, Event) of
{ok, State}; Event -> ok;
_ -> report_info(Format, Args)
end,
{ok, State};


handle_system_event({mnesia_warning, Format, Args}, State) -> handle_system_event({mnesia_warning, Format, Args}, State) ->
report_warning(Format, Args), report_warning(Format, Args),
Expand Down
36 changes: 23 additions & 13 deletions lib/mnesia/src/mnesia_loader.erl
Expand Up @@ -48,7 +48,7 @@ val(Var) ->
disc_load_table(Tab, Reason, Cs) -> disc_load_table(Tab, Reason, Cs) ->
Storage = mnesia_lib:cs_to_storage_type(node(), Cs), Storage = mnesia_lib:cs_to_storage_type(node(), Cs),
Type = val({Tab, setorbag}), Type = val({Tab, setorbag}),
dbg_out("Getting table ~tp (~p) from disc: ~tp~n", dbg_out("Getting table ~0tp (~0p) from disc: ~0tp~n",
[Tab, Storage, Reason]), [Tab, Storage, Reason]),
?eval_debug_fun({?MODULE, do_get_disc_copy}, ?eval_debug_fun({?MODULE, do_get_disc_copy},
[{tab, Tab}, [{tab, Tab},
Expand All @@ -57,9 +57,9 @@ disc_load_table(Tab, Reason, Cs) ->
{type, Type}]), {type, Type}]),
do_get_disc_copy2(Tab, Reason, Storage, Type). do_get_disc_copy2(Tab, Reason, Storage, Type).


do_get_disc_copy2(Tab, _Reason, Storage, _Type) when Storage == unknown -> do_get_disc_copy2(Tab, Reason, Storage, _Type) when Storage == unknown ->
verbose("Local table copy of ~tp has recently been deleted, ignored.~n", verbose("Local table copy of ~0tp ~0p has recently been deleted, ignored.~n",
[Tab]), [Tab, Reason]),
{not_loaded, storage_unknown}; {not_loaded, storage_unknown};
do_get_disc_copy2(Tab, Reason, Storage, Type) when Storage == disc_copies -> do_get_disc_copy2(Tab, Reason, Storage, Type) when Storage == disc_copies ->
%% NOW we create the actual table %% NOW we create the actual table
Expand Down Expand Up @@ -207,14 +207,14 @@ try_net_load_table(Tab, Reason, Ns, Cs) ->
end, end,
do_get_network_copy(Tab, Reason, Ns, Storage, Cs). do_get_network_copy(Tab, Reason, Ns, Storage, Cs).


do_get_network_copy(Tab, _Reason, _Ns, unknown, _Cs) -> do_get_network_copy(Tab, Reason, _Ns, unknown, _Cs) ->
verbose("Local table copy of ~tp has recently been deleted, ignored.~n", [Tab]), verbose("Local table copy of ~0tp (~0p) has recently been deleted, ignored.~n", [Tab,Reason]),
{not_loaded, storage_unknown}; {not_loaded, storage_unknown};
do_get_network_copy(Tab, Reason, Ns, Storage, Cs) -> do_get_network_copy(Tab, Reason, Ns, Storage, Cs) ->
[Node | Tail] = Ns, [Node | Tail] = Ns,
case lists:member(Node,val({current, db_nodes})) of case lists:member(Node,val({current, db_nodes})) of
true -> true ->
dbg_out("Getting table ~tp (~p) from node ~p: ~tp~n", dbg_out("Getting table ~0tp (~0p) from node ~0p: ~0tp~n",
[Tab, Storage, Node, Reason]), [Tab, Storage, Node, Reason]),
?eval_debug_fun({?MODULE, do_get_network_copy}, ?eval_debug_fun({?MODULE, do_get_network_copy},
[{tab, Tab}, {reason, Reason}, [{tab, Tab}, {reason, Reason},
Expand Down Expand Up @@ -289,6 +289,14 @@ init_receiver(Node, Tab,Storage,Cs,Reason) ->
{atomic, {error,Result}} when {atomic, {error,Result}} when
element(1,Reason) == dumper -> element(1,Reason) == dumper ->
{error,Result}; {error,Result};
{atomic, {error,{mktab, _} = Reason}} ->
case val({Tab,where_to_read}) == node() of
true -> %% Already loaded
ok;
false ->
fatal("Cannot create table ~tp: ~tp~n",
[[Tab, Storage], Reason])
end;
{atomic, {error,Result}} -> {atomic, {error,Result}} ->
fatal("Cannot create table ~tp: ~tp~n", fatal("Cannot create table ~tp: ~tp~n",
[[Tab, Storage], Result]); [[Tab, Storage], Result]);
Expand Down Expand Up @@ -419,26 +427,28 @@ create_table(Tab, TabSize, Storage, Cs) ->
{ok, _} -> {ok, _} ->
mnesia_lib:unlock_table(Tab), mnesia_lib:unlock_table(Tab),
{Storage, Tab}; {Storage, Tab};
Else -> {error, Reason} ->
mnesia_lib:unlock_table(Tab), mnesia_lib:unlock_table(Tab),
Else {error, {mktab, Reason}}
end; end;
(Storage == ram_copies) or (Storage == disc_copies) -> (Storage == ram_copies) or (Storage == disc_copies) ->
EtsOpts = proplists:get_value(ets, StorageProps, []), EtsOpts = proplists:get_value(ets, StorageProps, []),
Args = [{keypos, 2}, public, named_table, Cs#cstruct.type | EtsOpts], Args = [{keypos, 2}, public, named_table, Cs#cstruct.type | EtsOpts],
case mnesia_monitor:unsafe_mktab(Tab, Args) of case mnesia_monitor:unsafe_mktab(Tab, Args) of
Tab -> Tab ->
{Storage, Tab}; {Storage, Tab};
Else -> {error, Reason} ->
Else {error, {mktab, Reason}}
end; end;
element(1, Storage) == ext -> element(1, Storage) == ext ->
{_, Alias, Mod} = Storage, {_, Alias, Mod} = Storage,
case mnesia_monitor:unsafe_create_external(Tab, Alias, Mod, Cs) of case mnesia_monitor:unsafe_create_external(Tab, Alias, Mod, Cs) of
ok -> ok ->
{Storage, Tab}; {Storage, Tab};
Else -> {error, Reason} ->
Else {error, {mktab, Reason}};
Reason ->
{error, {mktab, Reason}}
end end
end. end.


Expand Down

0 comments on commit 940c1de

Please sign in to comment.