diff options
Diffstat (limited to 'lib/mnesia/src/mnesia_schema.erl')
-rw-r--r-- | lib/mnesia/src/mnesia_schema.erl | 505 |
1 files changed, 285 insertions, 220 deletions
diff --git a/lib/mnesia/src/mnesia_schema.erl b/lib/mnesia/src/mnesia_schema.erl index fef72ad39c..05be474aea 100644 --- a/lib/mnesia/src/mnesia_schema.erl +++ b/lib/mnesia/src/mnesia_schema.erl @@ -100,7 +100,7 @@ ]). %% Needed outside to be able to use/set table_properties -%% from user (not supported) +%% from user (not supported) -export([schema_transaction/1, insert_schema_ops/2, do_create_table/1, @@ -118,9 +118,9 @@ %% Here comes the init function which also resides in %% this module, it is called upon by the trans server %% at startup of the system -%% +%% %% We have a meta table which looks like -%% {table, schema, +%% {table, schema, %% {type, set}, %% {disc_copies, all}, %% {arity, 2} @@ -149,14 +149,14 @@ exit_on_error(GoodRes) -> val(Var) -> case ?catch_val(Var) of - {'EXIT', Reason} -> mnesia_lib:other_val(Var, Reason); - Value -> Value + {'EXIT', Reason} -> mnesia_lib:other_val(Var, Reason); + Value -> Value end. %% This function traverses all cstructs in the schema and %% sets all values in mnesia_gvar accordingly for each table/cstruct -set_schema('$end_of_table') -> +set_schema('$end_of_table') -> []; set_schema(Tab) -> do_set_schema(Tab), @@ -253,8 +253,8 @@ version() -> incr_version(Cs) -> {{Major, Minor}, _} = Cs#cstruct.version, Nodes = mnesia_lib:intersect(val({schema, disc_copies}), - mnesia_lib:cs_to_nodes(Cs)), - V = + mnesia_lib:cs_to_nodes(Cs)), + V = case Nodes -- val({Cs#cstruct.name, active_replicas}) of [] -> {Major + 1, 0}; % All replicas are active _ -> {Major, Minor + 1} % Some replicas are inactive @@ -359,7 +359,7 @@ delete_schema2() -> {error, Reason} -> {error, Reason} end. - + ensure_no_schema([H|T]) when is_atom(H) -> case rpc:call(H, ?MODULE, remote_read_schema, []) of {badrpc, Reason} -> @@ -407,7 +407,7 @@ opt_create_dir(UseDir, Dir) when UseDir == true-> check_can_write(Dir); false -> case file:make_dir(Dir) of - ok -> + ok -> verbose("Create Directory ~p~n", [Dir]), ok; {error, Reason} -> @@ -417,7 +417,7 @@ opt_create_dir(UseDir, Dir) when UseDir == true-> end; opt_create_dir(false, _) -> {error, {has_no_disc, node()}}. - + check_can_write(Dir) -> case file:read_file_info(Dir) of {ok, FI} when FI#file_info.type == directory, @@ -450,7 +450,7 @@ read_schema(Keep) -> read_schema(Keep, IgnoreFallback) -> lock_schema(), - Res = + Res = case mnesia:system_info(is_running) of yes -> {ok, ram, get_create_list(schema)}; @@ -477,7 +477,7 @@ read_disc_schema(Keep, IgnoreFallback) -> case mnesia_bup:fallback_exists() of true when IgnoreFallback == false, Running /= yes -> mnesia_bup:fallback_to_schema(); - _ -> + _ -> %% If we're running, we read the schema file even %% if fallback exists Dat = mnesia_lib:tab2dat(schema), @@ -499,7 +499,7 @@ read_disc_schema(Keep, IgnoreFallback) -> end. do_read_disc_schema(Fname, Keep) -> - T = + T = case Keep of false -> Args = [{keypos, 2}, public, set], @@ -523,7 +523,7 @@ do_read_disc_schema(Fname, Keep) -> get_initial_schema(SchemaStorage, Nodes) -> Cs = #cstruct{name = schema, record_name = schema, - attributes = [table, cstruct]}, + attributes = [table, cstruct]}, Cs2 = case SchemaStorage of ram_copies -> Cs#cstruct{ram_copies = Nodes}; @@ -532,7 +532,7 @@ get_initial_schema(SchemaStorage, Nodes) -> cs2list(Cs2). read_cstructs_from_disc() -> - %% Assumptions: + %% Assumptions: %% - local schema lock in global %% - use_dir is true %% - Mnesia is not running @@ -552,14 +552,14 @@ read_cstructs_from_disc() -> end, Cstructs = dets:traverse(Tab, Fun), dets:close(Tab), - {ok, Cstructs}; + {ok, Cstructs}; {error, Reason} -> {error, Reason} end; false -> {error, "No schema file exists"} end. - + %% We run a very special type of transactions when we %% we want to manipulate the schema. @@ -593,20 +593,20 @@ schema_transaction(Fun) -> %% This process may dump the transaction log, and should %% therefore not be run in an application process -%% +%% schema_coordinator(Client, _Fun, undefined) -> Res = {aborted, {node_not_running, node()}}, Client ! {transaction_done, Res, self()}, unlink(Client); - + schema_coordinator(Client, Fun, Controller) when is_pid(Controller) -> %% Do not trap exit in order to automatically die %% when the controller dies link(Controller), unlink(Client), - - %% Fulfull the transaction even if the client dies + + %% Fulfull the transaction even if the client dies Res = mnesia:transaction(Fun), Client ! {transaction_done, Res, self()}, unlink(Controller), % Avoids spurious exit message @@ -619,7 +619,7 @@ schema_coordinator(Client, Fun, Controller) when is_pid(Controller) -> insert_schema_ops({_Mod, _Tid, Ts}, SchemaIOps) -> do_insert_schema_ops(Ts#tidstore.store, SchemaIOps). - + do_insert_schema_ops(Store, [Head | Tail]) -> ?ets_insert(Store, Head), do_insert_schema_ops(Store, Tail); @@ -628,15 +628,56 @@ do_insert_schema_ops(_Store, []) -> cs2list(Cs) when is_record(Cs, cstruct) -> Tags = record_info(fields, cstruct), - rec2list(Tags, 2, Cs); + rec2list(Tags, Tags, 2, Cs); cs2list(CreateList) when is_list(CreateList) -> - CreateList. - -rec2list([Tag | Tags], Pos, Rec) -> + CreateList; +%% 4.4.19 +cs2list(Cs) when element(1, Cs) == cstruct, tuple_size(Cs) == 18 -> + Tags = [name,type,ram_copies,disc_copies,disc_only_copies, + load_order,access_mode,majority,index,snmp,local_content, + record_name,attributes,user_properties,frag_properties, + cookie,version], + rec2list(Tags, Tags, 2, Cs); +%% 4.4.18 and earlier +cs2list(Cs) when element(1, Cs) == cstruct, tuple_size(Cs) == 17 -> + Tags = [name,type,ram_copies,disc_copies,disc_only_copies, + load_order,access_mode,index,snmp,local_content, + record_name,attributes,user_properties,frag_properties, + cookie,version], + rec2list(Tags, Tags, 2, Cs). + +cs2list(false, Cs) -> + cs2list(Cs); +cs2list(ver4_4_18, Cs) -> + Orig = record_info(fields, cstruct), + Tags = [name,type,ram_copies,disc_copies,disc_only_copies, + load_order,access_mode,index,snmp,local_content, + record_name,attributes,user_properties,frag_properties, + cookie,version], + rec2list(Tags, Orig, 2, Cs); +cs2list(ver4_4_19, Cs) -> + Orig = record_info(fields, cstruct), + Tags = [name,type,ram_copies,disc_copies,disc_only_copies, + load_order,access_mode,majority,index,snmp,local_content, + record_name,attributes,user_properties,frag_properties, + cookie,version], + rec2list(Tags, Orig, 2, Cs). + +rec2list([Tag | Tags], [Tag | Orig], Pos, Rec) -> Val = element(Pos, Rec), - [{Tag, Val} | rec2list(Tags, Pos + 1, Rec)]; -rec2list([], _Pos, _Rec) -> - []. + [{Tag, Val} | rec2list(Tags, Orig, Pos + 1, Rec)]; +rec2list([], _, _Pos, _Rec) -> + []; +rec2list(Tags, [_|Orig], Pos, Rec) -> + rec2list(Tags, Orig, Pos+1, Rec). + +api_list2cs(List) when is_list(List) -> + Name = pick(unknown, name, List, must), + Keys = check_keys(Name, List, record_info(fields, cstruct)), + check_duplicates(Name, Keys), + list2cs(List); +api_list2cs(Other) -> + mnesia:abort({badarg, Other}). list2cs(List) when is_list(List) -> Name = pick(unknown, name, List, must), @@ -667,10 +708,7 @@ list2cs(List) when is_list(List) -> Frag = pick(Name, frag_properties, List, []), verify({alt, [nil, list]}, mnesia_lib:etype(Frag), - {badarg, Name, {frag_properties, Frag}}), - - Keys = check_keys(Name, List, record_info(fields, cstruct)), - check_duplicates(Name, Keys), + {badarg, Name, {frag_properties, Frag}}), #cstruct{name = Name, ram_copies = Rc, disc_copies = Dc, @@ -687,9 +725,7 @@ list2cs(List) when is_list(List) -> user_properties = lists:sort(UserProps), frag_properties = lists:sort(Frag), cookie = Cookie, - version = Version}; -list2cs(Other) -> - mnesia:abort({badarg, Other}). + version = Version}. pick(Tab, Key, List, Default) -> case lists:keysearch(Key, 1, List) of @@ -708,7 +744,7 @@ attr_tab_to_pos(_Tab, Pos) when is_integer(Pos) -> Pos; attr_tab_to_pos(Tab, Attr) -> attr_to_pos(Attr, val({Tab, attributes})). - + %% Convert attribute name to integer if neccessary attr_to_pos(Pos, _Attrs) when is_integer(Pos) -> Pos; @@ -723,7 +759,7 @@ attr_to_pos(Attr, [_ | Attrs], Pos) -> attr_to_pos(Attr, Attrs, Pos + 1); attr_to_pos(Attr, _, _) -> mnesia:abort({bad_type, Attr}). - + check_keys(Tab, [{Key, _Val} | Tail], Items) -> case lists:member(Key, Items) of true -> [Key | check_keys(Tab, Tail, Items)]; @@ -759,7 +795,7 @@ verify_cstruct(Cs) when is_record(Cs, cstruct) -> {bad_type, Tab, {type, Type}}), %% Currently ordered_set is not supported for disk_only_copies. - if + if Type == ordered_set, Cs#cstruct.disc_only_copies /= [] -> mnesia:abort({bad_type, Tab, {not_supported, Type, disc_only_copies}}); true -> @@ -776,10 +812,10 @@ verify_cstruct(Cs) when is_record(Cs, cstruct) -> Arity = length(Attrs) + 1, verify(true, Arity > 2, {bad_type, Tab, {attributes, Attrs}}), - + lists:foldl(fun(Attr,_Other) when Attr == snmp -> mnesia:abort({bad_type, Tab, {attributes, [Attr]}}); - (Attr,Other) -> + (Attr,Other) -> verify(atom, mnesia_lib:etype(Attr), {bad_type, Tab, {attributes, [Attr]}}), verify(false, lists:member(Attr, Other), @@ -792,7 +828,7 @@ verify_cstruct(Cs) when is_record(Cs, cstruct) -> Index = Cs#cstruct.index, verify({alt, [nil, list]}, mnesia_lib:etype(Index), {bad_type, Tab, {index, Index}}), - + IxFun = fun(Pos) -> verify(true, fun() -> @@ -807,7 +843,7 @@ verify_cstruct(Cs) when is_record(Cs, cstruct) -> {bad_type, Tab, {index, [Pos]}}) end, lists:foreach(IxFun, Index), - + LC = Cs#cstruct.local_content, verify({alt, [true, false]}, LC, {bad_type, Tab, {local_content, LC}}), @@ -834,7 +870,7 @@ verify_cstruct(Cs) when is_record(Cs, cstruct) -> lists:foreach(CheckProp, Cs#cstruct.user_properties), case Cs#cstruct.cookie of - {{MegaSecs, Secs, MicroSecs}, _Node} + {{MegaSecs, Secs, MicroSecs}, _Node} when is_integer(MegaSecs), is_integer(Secs), is_integer(MicroSecs), is_atom(node) -> ok; @@ -870,15 +906,15 @@ verify_nodes(Cs) -> end, verify(integer, mnesia_lib:etype(LoadOrder), {bad_type, Tab, {load_order, LoadOrder}}), - + Nodes = Ram ++ Disc ++ DiscOnly, verify(list, mnesia_lib:etype(Nodes), {combine_error, Tab, [{ram_copies, []}, {disc_copies, []}, {disc_only_copies, []}]}), verify(false, has_duplicates(Nodes), {combine_error, Tab, Nodes}), - AtomCheck = fun(N) -> verify(atom, mnesia_lib:etype(N), {bad_type, Tab, N}) end, + AtomCheck = fun(N) -> verify(atom, mnesia_lib:etype(N), {bad_type, Tab, N}) end, lists:foreach(AtomCheck, Nodes). - + verify(Expected, Fun, Error) when is_function(Fun) -> do_verify(Expected, catch Fun(), Error); verify(Expected, Actual, Error) -> @@ -909,7 +945,7 @@ ensure_active(Cs, What) -> W = {Tab, What}, ensure_non_empty(W), Nodes = mnesia_lib:intersect(val({schema, disc_copies}), - mnesia_lib:cs_to_nodes(Cs)), + mnesia_lib:cs_to_nodes(Cs)), case Nodes -- val(W) of [] -> ok; @@ -936,7 +972,7 @@ ensure_non_empty({Tab, Vhat}) -> ensure_not_active(Tab = schema, Node) -> Active = val({Tab, active_replicas}), - case lists:member(Node, Active) of + case lists:member(Node, Active) of false when Active =/= [] -> ok; false -> @@ -970,7 +1006,7 @@ create_table(TabDef) -> do_multi_create_table(TabDef) -> get_tid_ts_and_lock(schema, write), ensure_writable(schema), - Cs = list2cs(TabDef), + Cs = api_list2cs(TabDef), case Cs#cstruct.frag_properties of [] -> do_create_table(Cs); @@ -999,7 +1035,7 @@ unsafe_make_create_table(Cs) -> {_Mod, Tid, Ts} = get_tid_ts_and_lock(schema, none), verify_cstruct(Cs), Tab = Cs#cstruct.name, - + %% Check that we have all disc replica nodes running DiscNodes = Cs#cstruct.disc_copies ++ Cs#cstruct.disc_only_copies, RunningNodes = val({current, db_nodes}), @@ -1017,7 +1053,7 @@ unsafe_make_create_table(Cs) -> check_if_exists(Tab) -> TidTs = get_tid_ts_and_lock(schema, write), {_, _, Ts} = TidTs, - Store = Ts#tidstore.store, + Store = Ts#tidstore.store, ets:foldl( fun({op, create_table, [{name, T}|_]}, _Acc) when T==Tab -> true; @@ -1054,7 +1090,7 @@ make_delete_table(Tab, Mode) -> %% nodes etc. TidTs = get_tid_ts_and_lock(schema, write), {_, _, Ts} = TidTs, - Store = Ts#tidstore.store, + Store = Ts#tidstore.store, Deleted = ets:select_delete( Store, [{{op,'$1',[{name,Tab}|'_']}, [{'or', @@ -1077,9 +1113,9 @@ make_delete_table(Tab, Mode) -> [] -> [make_delete_table2(Tab)]; _Props -> - %% Check if it is a base table - mnesia_frag:lookup_frag_hash(Tab), - + %% Check if it is a base table + mnesia_frag:lookup_frag_hash(Tab), + %% Check for foreigners F = mnesia_frag:lookup_foreigners(Tab), verify([], F, {combine_error, @@ -1101,7 +1137,7 @@ make_delete_table2(Tab) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% Change fragmentation of a table - + change_table_frag(Tab, Change) -> schema_transaction(fun() -> do_change_table_frag(Tab, Change) end). @@ -1112,7 +1148,7 @@ do_change_table_frag(Tab, Change) when is_atom(Tab), Tab /= schema -> ok; do_change_table_frag(Tab, _Change) -> mnesia:abort({bad_type, Tab}). - + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% Clear a table @@ -1150,7 +1186,7 @@ make_add_table_copy(Tab, Node, Storage) -> verify(false, lists:member(Node, Ns), {already_exists, Tab, Node}), Cs2 = new_cs(Cs, Node, Storage, add), verify_cstruct(Cs2), - + %% Check storage and if node is running IsRunning = lists:member(Node, val({current, db_nodes})), if @@ -1177,21 +1213,21 @@ del_table_copy(Tab, Node) -> do_del_table_copy(Tab, Node) when is_atom(Node) -> TidTs = get_tid_ts_and_lock(schema, write), -%% get_tid_ts_and_lock(Tab, write), +%% get_tid_ts_and_lock(Tab, write), insert_schema_ops(TidTs, make_del_table_copy(Tab, Node)); do_del_table_copy(Tab, Node) -> mnesia:abort({badarg, Tab, Node}). - + make_del_table_copy(Tab, Node) -> ensure_writable(schema), Cs = incr_version(val({Tab, cstruct})), Storage = mnesia_lib:schema_cs_to_storage_type(Node, Cs), - Cs2 = new_cs(Cs, Node, Storage, del), + Cs2 = new_cs(Cs, Node, Storage, del), case mnesia_lib:cs_to_nodes(Cs2) of [] when Tab == schema -> mnesia:abort({combine_error, Tab, "Last replica"}); [] -> - ensure_active(Cs), + ensure_active(Cs), dbg_out("Last replica deleted in table ~p~n", [Tab]), make_delete_table(Tab, whole_table); _ when Tab == schema -> @@ -1210,14 +1246,14 @@ remove_node_from_tabs([], _Node) -> []; remove_node_from_tabs([schema|Rest], Node) -> remove_node_from_tabs(Rest, Node); -remove_node_from_tabs([Tab|Rest], Node) -> - {Cs, IsFragModified} = +remove_node_from_tabs([Tab|Rest], Node) -> + {Cs, IsFragModified} = mnesia_frag:remove_node(Node, incr_version(val({Tab, cstruct}))), case mnesia_lib:schema_cs_to_storage_type(Node, Cs) of unknown -> case IsFragModified of true -> - [{op, change_table_frag, {del_node, Node}, cs2list(Cs)} | + [{op, change_table_frag, {del_node, Node}, cs2list(Cs)} | remove_node_from_tabs(Rest, Node)]; false -> remove_node_from_tabs(Rest, Node) @@ -1246,7 +1282,7 @@ new_cs(Cs, Node, ram_copies, del) -> new_cs(Cs, Node, disc_copies, del) -> Cs#cstruct{disc_copies = lists:delete(Node , Cs#cstruct.disc_copies)}; new_cs(Cs, Node, disc_only_copies, del) -> - Cs#cstruct{disc_only_copies = + Cs#cstruct{disc_only_copies = lists:delete(Node , Cs#cstruct.disc_only_copies)}; new_cs(Cs, _Node, Storage, _Op) -> mnesia:abort({badarg, Cs#cstruct.name, Storage}). @@ -1278,7 +1314,7 @@ make_move_table(Tab, FromNode, ToNode) -> Running = val({current, db_nodes}), Storage = mnesia_lib:schema_cs_to_storage_type(FromNode, Cs), verify(true, lists:member(ToNode, Running), {not_active, schema, ToNode}), - + Cs2 = new_cs(Cs, ToNode, Storage, add), Cs3 = new_cs(Cs2, FromNode, Storage, del), verify_cstruct(Cs3), @@ -1306,7 +1342,7 @@ make_change_table_copy_type(Tab, Node, unknown) -> make_change_table_copy_type(Tab, Node, ToS) -> ensure_writable(schema), Cs = incr_version(val({Tab, cstruct})), - FromS = mnesia_lib:storage_type_at_node(Node, Tab), + FromS = mnesia_lib:storage_type_at_node(Node, Tab), case compare_storage_type(false, FromS, ToS) of {same, _} -> @@ -1320,12 +1356,12 @@ make_change_table_copy_type(Tab, Node, ToS) -> Cs2 = new_cs(Cs, Node, FromS, del), Cs3 = new_cs(Cs2, Node, ToS, add), verify_cstruct(Cs3), - + [{op, change_table_copy_type, Node, FromS, ToS, cs2list(Cs3)}]. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% change index functions .... -%% Pos is allready added by 1 in both of these functions +%% Pos is allready added by 1 in both of these functions add_table_index(Tab, Pos) -> schema_transaction(fun() -> do_add_table_index(Tab, Pos) end). @@ -1412,14 +1448,14 @@ make_del_snmp(Tab) -> [{op, del_snmp, cs2list(Cs2)}]. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%% +%% -transform_table(Tab, Fun, NewAttrs, NewRecName) - when is_function(Fun), is_list(NewAttrs), is_atom(NewRecName) -> +transform_table(Tab, Fun, NewAttrs, NewRecName) + when is_function(Fun), is_list(NewAttrs), is_atom(NewRecName) -> schema_transaction(fun() -> do_transform_table(Tab, Fun, NewAttrs, NewRecName) end); -transform_table(Tab, ignore, NewAttrs, NewRecName) - when is_list(NewAttrs), is_atom(NewRecName) -> +transform_table(Tab, ignore, NewAttrs, NewRecName) + when is_list(NewAttrs), is_atom(NewRecName) -> schema_transaction(fun() -> do_transform_table(Tab, ignore, NewAttrs, NewRecName) end); transform_table(Tab, Fun, NewAttrs, NewRecName) -> @@ -1438,7 +1474,7 @@ make_transform(Tab, Fun, NewAttrs, NewRecName) -> ensure_active(Cs), ensure_writable(Tab), case mnesia_lib:val({Tab, index}) of - [] -> + [] -> Cs2 = Cs#cstruct{attributes = NewAttrs, record_name = NewRecName}, verify_cstruct(Cs2), [{op, transform, Fun, cs2list(Cs2)}]; @@ -1464,7 +1500,7 @@ make_transform(Tab, Fun, NewAttrs, NewRecName) -> end. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%% +%% change_table_access_mode(Tab, Mode) -> schema_transaction(fun() -> do_change_table_access_mode(Tab, Mode) end). @@ -1598,9 +1634,9 @@ change_prop_in_existing_op(Tab, Prop, How, Store) -> false -> false end. - -update_existing_op([{op, Op, L = [{name,Tab}|_], _OldProp}|Ops], - Tab, Prop, How, Acc) when Op == write_property; + +update_existing_op([{op, Op, L = [{name,Tab}|_], _OldProp}|Ops], + Tab, Prop, How, Acc) when Op == write_property; Op == delete_property -> %% Apparently, mnesia_dumper doesn't care about OldProp here -- just L, %% so we will throw away OldProp (not that it matters...) and insert Prop. @@ -1625,7 +1661,7 @@ update_existing_op([], _, _, _, _) -> do_read_table_property(Tab, Key) -> TidTs = get_tid_ts_and_lock(schema, read), {_, _, Ts} = TidTs, - Store = Ts#tidstore.store, + Store = Ts#tidstore.store, Props = ets:foldl( fun({op, create_table, [{name, T}|Opts]}, _Acc) when T==Tab -> @@ -1689,7 +1725,7 @@ do_delete_table_property(Tab, PropKey) -> [Tab,PropKey]), %% this must be an existing table get_tid_ts_and_lock(Tab, none), - insert_schema_ops(TidTs, + insert_schema_ops(TidTs, make_delete_table_properties(Tab, [PropKey])) end. @@ -1711,17 +1747,17 @@ make_delete_table_properties(_Tab, [], _Cs) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% -%% Ensure that the transaction can be committed even +%% Ensure that the transaction can be committed even %% if the node crashes and Mnesia is restarted prepare_commit(Tid, Commit, WaitFor) -> case Commit#commit.schema_ops of [] -> {false, Commit, optional}; OrigOps -> - {Modified, Ops, DumperMode} = + {Modified, Ops, DumperMode} = prepare_ops(Tid, OrigOps, WaitFor, false, [], optional), InitBy = schema_prepare, - GoodRes = {Modified, + GoodRes = {Modified, Commit#commit{schema_ops = lists:reverse(Ops)}, DumperMode}, case DumperMode of @@ -1737,7 +1773,7 @@ prepare_commit(Tid, Commit, WaitFor) -> end end, case Ops of - [] -> + [] -> ignore; _ -> %% We need to grab a dumper lock here, the log may not @@ -1749,20 +1785,20 @@ prepare_commit(Tid, Commit, WaitFor) -> prepare_ops(Tid, [Op | Ops], WaitFor, Changed, Acc, DumperMode) -> case prepare_op(Tid, Op, WaitFor) of - {true, mandatory} -> + {true, mandatory} -> prepare_ops(Tid, Ops, WaitFor, Changed, [Op | Acc], mandatory); - {true, optional} -> + {true, optional} -> prepare_ops(Tid, Ops, WaitFor, Changed, [Op | Acc], DumperMode); - {true, Ops2, mandatory} -> + {true, Ops2, mandatory} -> prepare_ops(Tid, Ops, WaitFor, true, Ops2 ++ Acc, mandatory); - {true, Ops2, optional} -> + {true, Ops2, optional} -> prepare_ops(Tid, Ops, WaitFor, true, Ops2 ++ Acc, DumperMode); - {false, optional} -> + {false, optional} -> prepare_ops(Tid, Ops, WaitFor, true, Acc, DumperMode) end; prepare_ops(_Tid, [], _WaitFor, Changed, Acc, DumperMode) -> {Changed, Acc, DumperMode}. - + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% %% Prepare for commit %% returns true if Op should be included, i.e. unmodified @@ -1781,8 +1817,8 @@ prepare_op(_Tid, {op, rec, unknown, Rec}, _WaitFor) -> prepare_op(_Tid, {op, announce_im_running, Node, SchemaDef, Running, RemoteRunning}, _WaitFor) -> SchemaCs = list2cs(SchemaDef), - if - Node == node() -> %% Announce has already run on local node + if + Node == node() -> %% Announce has already run on local node ignore; %% from do_merge_schema true -> %% If a node has restarted it may still linger in db_nodes, @@ -1794,9 +1830,9 @@ prepare_op(_Tid, {op, announce_im_running, Node, SchemaDef, Running, RemoteRunni end, {false, optional}; -prepare_op(_Tid, {op, sync_trans}, {part, CoordPid}) -> +prepare_op(_Tid, {op, sync_trans}, {part, CoordPid}) -> CoordPid ! {sync_trans, self()}, - receive + receive {sync_trans, CoordPid} -> {false, optional}; {mnesia_down, _Node} = Else -> @@ -1807,7 +1843,7 @@ prepare_op(_Tid, {op, sync_trans}, {part, CoordPid}) -> mnesia:abort(Else) end; -prepare_op(_Tid, {op, sync_trans}, {coord, Nodes}) -> +prepare_op(_Tid, {op, sync_trans}, {coord, Nodes}) -> case receive_sync(Nodes, []) of {abort, Reason} -> mnesia_lib:verbose("sync_op terminated due to ~p~n", [Reason]), @@ -1838,7 +1874,7 @@ prepare_op(Tid, {op, create_table, TabDef}, _WaitFor) -> create_ram_table(Tab, Cs#cstruct.type), create_disc_table(Tab), insert_cstruct(Tid, Cs, false), - {true, optional}; + {true, optional}; disc_only_copies -> mnesia_lib:set({Tab, create_table},true), create_disc_only_table(Tab,Cs#cstruct.type), @@ -1857,15 +1893,15 @@ prepare_op(Tid, {op, add_table_copy, Storage, Node, TabDef}, _WaitFor) -> if Tab == schema -> {true, optional}; - + Node == node() -> - case mnesia_lib:val({schema, storage_type}) of - ram_copies when Storage /= ram_copies -> + case mnesia_lib:val({schema, storage_type}) of + ram_copies when Storage /= ram_copies -> Error = {combine_error, Tab, "has no disc", Node}, mnesia:abort(Error); _ -> ok - end, + end, %% Tables are created by mnesia_loader get_network code insert_cstruct(Tid, Cs, true), case mnesia_controller:get_network_copy(Tab, Cs) of @@ -1902,22 +1938,22 @@ prepare_op(Tid, {op, add_table_copy, Storage, Node, TabDef}, _WaitFor) -> prepare_op(Tid, {op, del_table_copy, _Storage, Node, TabDef}, _WaitFor) -> Cs = list2cs(TabDef), Tab = Cs#cstruct.name, - + if %% Schema table lock is always required to run a schema op. %% No need to look it. - node(Tid#tid.pid) == node(), Tab /= schema -> + node(Tid#tid.pid) == node(), Tab /= schema -> Self = self(), Pid = spawn_link(fun() -> lock_del_table(Tab, Node, Cs, Self) end), put(mnesia_lock, Pid), - receive - {Pid, updated} -> + receive + {Pid, updated} -> {true, optional}; {Pid, FailReason} -> mnesia:abort(FailReason); {'EXIT', Pid, Reason} -> mnesia:abort(Reason) - end; + end; true -> {true, optional} end; @@ -1928,12 +1964,12 @@ prepare_op(_Tid, {op, change_table_copy_type, N, FromS, ToS, TabDef}, _WaitFor) Tab = Cs#cstruct.name, NotActive = mnesia_lib:not_active_here(Tab), - - if + + if NotActive == true -> mnesia:abort({not_active, Tab, node()}); - - Tab == schema -> + + Tab == schema -> case {FromS, ToS} of {ram_copies, disc_copies} -> case mnesia:system_info(schema_location) of @@ -1943,7 +1979,7 @@ prepare_op(_Tid, {op, change_table_copy_type, N, FromS, ToS, TabDef}, _WaitFor) mnesia:abort({combine_error, Tab, node(), "schema_location must be opt_disc"}) end, - Dir = mnesia_lib:dir(), + Dir = mnesia_lib:dir(), case opt_create_dir(true, Dir) of ok -> purge_dir(Dir, []), @@ -1967,18 +2003,18 @@ prepare_op(_Tid, {op, change_table_copy_type, N, FromS, ToS, TabDef}, _WaitFor) _ -> mnesia:abort({combine_error, Tab, ToS}) end; - - FromS == ram_copies -> + + FromS == ram_copies -> case mnesia_monitor:use_dir() of - true -> + true -> Dat = mnesia_lib:tab2dcd(Tab), case mnesia_lib:exists(Dat) of true -> mnesia:abort({combine_error, Tab, node(), "Table dump exists"}); false -> - case ToS of - disc_copies -> + case ToS of + disc_copies -> mnesia_log:ets2dcd(Tab, dmp); disc_only_copies -> mnesia_dumper:raw_named_dump_table(Tab, dmp) @@ -1988,7 +2024,7 @@ prepare_op(_Tid, {op, change_table_copy_type, N, FromS, ToS, TabDef}, _WaitFor) false -> mnesia:abort({has_no_disc, node()}) end; - + FromS == disc_copies, ToS == disc_only_copies -> mnesia_dumper:raw_named_dump_table(Tab, dmp); FromS == disc_only_copies -> @@ -2020,7 +2056,7 @@ prepare_op(_Tid, {op, dump_table, unknown, TabDef}, _WaitFor) -> case lists:member(node(), Cs#cstruct.ram_copies) of true -> case mnesia_monitor:use_dir() of - true -> + true -> mnesia_log:ets2dcd(Tab, dmp), Size = mnesia:table_info(Tab, size), {true, [{op, dump_table, Size, TabDef}], optional}; @@ -2058,7 +2094,7 @@ prepare_op(_Tid, {op, transform, Fun, TabDef}, _WaitFor) -> mnesia_lib:db_fixtable(Storage, Tab, true), Key = mnesia_lib:db_first(Tab), Op = {op, transform, Fun, TabDef}, - case catch transform_objs(Fun, Tab, RecName, + case catch transform_objs(Fun, Tab, RecName, Key, NewArity, Storage, Type, [Op]) of {'EXIT', Reason} -> mnesia_lib:db_fixtable(Storage, Tab, false), @@ -2072,7 +2108,7 @@ prepare_op(_Tid, {op, transform, Fun, TabDef}, _WaitFor) -> prepare_op(_Tid, {op, merge_schema, TabDef}, _WaitFor) -> Cs = list2cs(TabDef), case verify_merge(Cs) of - ok -> + ok -> {true, optional}; Error -> verbose("Merge_Schema ~p failed on ~p: ~p~n", [_Tid,node(),Error]), @@ -2093,7 +2129,7 @@ create_ram_table(Tab, Type) -> create_disc_table(Tab) -> File = mnesia_lib:tab2dcd(Tab), file:delete(File), - FArg = [{file, File}, {name, {mnesia,create}}, + FArg = [{file, File}, {name, {mnesia,create}}, {repair, false}, {mode, read_write}], case mnesia_monitor:open_log(FArg) of {ok,Log} -> @@ -2124,7 +2160,7 @@ receive_sync([], Pids) -> receive_sync(Nodes, Pids) -> receive {sync_trans, Pid} -> - Node = node(Pid), + Node = node(Pid), receive_sync(lists:delete(Node, Nodes), [Pid | Pids]); Else -> {abort, Else} @@ -2140,16 +2176,16 @@ lock_del_table(Tab, Node, Cs, Father) -> false; ({badrpc, {'EXIT', {undef, _}}}) -> %% This will be the case we talks with elder nodes - %% than 3.8.2, they will set where_to_read without - %% getting a lock. + %% than 3.8.2, they will set where_to_read without + %% getting a lock. false; (_) -> true end, case lists:filter(Filter, Res) of - [] -> + [] -> Father ! {self(), updated}, - %% When transaction is commited the process dies + %% When transaction is commited the process dies %% and the lock is released. receive _ -> ok end; Err -> @@ -2166,7 +2202,7 @@ lock_del_table(Tab, Node, Cs, Father) -> exit(normal). set_where_to_read(Tab, Node, Cs) -> - case mnesia_lib:val({Tab, where_to_read}) of + case mnesia_lib:val({Tab, where_to_read}) of Node -> case Cs#cstruct.local_content of true -> @@ -2185,16 +2221,16 @@ transform_objs(_Fun, _Tab, _RT, '$end_of_table', _NewArity, _Storage, _Type, Acc transform_objs(Fun, Tab, RecName, Key, A, Storage, Type, Acc) -> Objs = mnesia_lib:db_get(Tab, Key), NextKey = mnesia_lib:db_next_key(Tab, Key), - Oid = {Tab, Key}, + Oid = {Tab, Key}, NewObjs = {Ws, Ds} = transform_obj(Tab, RecName, Key, Fun, Objs, A, Type, [], []), - if - NewObjs == {[], []} -> + if + NewObjs == {[], []} -> transform_objs(Fun, Tab, RecName, NextKey, A, Storage, Type, Acc); - Type == bag -> + Type == bag -> transform_objs(Fun, Tab, RecName, NextKey, A, Storage, Type, [{op, rec, Storage, {Oid, Ws, write}}, {op, rec, Storage, {Oid, [Oid], delete}} | Acc]); - Ds == [] -> + Ds == [] -> %% Type is set or ordered_set, no need to delete the record first transform_objs(Fun, Tab, RecName, NextKey, A, Storage, Type, [{op, rec, Storage, {Oid, Ws, write}} | Acc]); @@ -2215,15 +2251,15 @@ transform_obj(Tab, RecName, Key, Fun, [Obj|Rest], NewArity, Type, Ws, Ds) -> NewObj == Obj -> transform_obj(Tab, RecName, Key, Fun, Rest, NewArity, Type, Ws, Ds); RecName == element(1, NewObj), Key == element(2, NewObj) -> - transform_obj(Tab, RecName, Key, Fun, Rest, NewArity, + transform_obj(Tab, RecName, Key, Fun, Rest, NewArity, Type, [NewObj | Ws], Ds); - NewObj == delete -> - case Type of + NewObj == delete -> + case Type of bag -> %% Just don't write that object - transform_obj(Tab, RecName, Key, Fun, Rest, - NewArity, Type, Ws, Ds); + transform_obj(Tab, RecName, Key, Fun, Rest, + NewArity, Type, Ws, Ds); _ -> - transform_obj(Tab, RecName, Key, Fun, Rest, NewArity, + transform_obj(Tab, RecName, Key, Fun, Rest, NewArity, Type, Ws, [NewObj | Ds]) end; true -> @@ -2247,7 +2283,7 @@ undo_prepare_commit(Tid, Commit) -> %% Undo in reverse order undo_prepare_ops(Tid, [Op | Ops]) -> - case element(1, Op) of + case element(1, Op) of TheOp when TheOp /= op, TheOp /= restore_op -> undo_prepare_ops(Tid, Ops); _ -> @@ -2274,7 +2310,7 @@ undo_prepare_op(Tid, {op, create_table, TabDef}) -> mnesia_lib:unset({Tab, create_table}), delete_cstruct(Tid, Cs), case mnesia_lib:cs_to_storage_type(node(), Cs) of - unknown -> + unknown -> ok; ram_copies -> ram_delete_table(Tab, ram_copies); @@ -2289,7 +2325,7 @@ undo_prepare_op(Tid, {op, create_table, TabDef}) -> %% disc_delete_table(Tab, Storage), file:delete(Dat) end; - + undo_prepare_op(Tid, {op, add_table_copy, Storage, Node, TabDef}) -> Cs = list2cs(TabDef), Tab = Cs#cstruct.name, @@ -2314,21 +2350,21 @@ undo_prepare_op(Tid, {op, add_table_copy, Storage, Node, TabDef}) -> Cs2 = new_cs(Cs, Node, Storage, del), insert_cstruct(Tid, Cs2, true) % Don't care about the version end; - -undo_prepare_op(_Tid, {op, del_table_copy, _, Node, TabDef}) + +undo_prepare_op(_Tid, {op, del_table_copy, _, Node, TabDef}) when Node == node() -> Cs = list2cs(TabDef), Tab = Cs#cstruct.name, mnesia_lib:set({Tab, where_to_read}, Node); -undo_prepare_op(_Tid, {op, change_table_copy_type, N, FromS, ToS, TabDef}) +undo_prepare_op(_Tid, {op, change_table_copy_type, N, FromS, ToS, TabDef}) when N == node() -> Cs = list2cs(TabDef), Tab = Cs#cstruct.name, mnesia_checkpoint:tm_change_table_copy_type(Tab, ToS, FromS), Dmp = mnesia_lib:tab2dmp(Tab), - + case {FromS, ToS} of {ram_copies, disc_copies} when Tab == schema -> file:delete(Dmp), @@ -2382,9 +2418,9 @@ ram_delete_table(Tab, Storage) -> ignore; disc_only_copies -> ignore; - _Else -> + _Else -> %% delete possible index files and data ..... - %% Got to catch this since if no info has been set in the + %% Got to catch this since if no info has been set in the %% mnesia_gvar it will crash catch mnesia_index:del_transient(Tab, Storage), case ?catch_val({Tab, {index, snmp}}) of @@ -2454,7 +2490,7 @@ has_known_suffix(File, [Suffix | Tail], false) -> has_known_suffix(File, Tail, lists:suffix(Suffix, File)); has_known_suffix(_File, [], Bool) -> Bool. - + known_suffixes() -> real_suffixes() ++ tmp_suffixes(). real_suffixes() -> [".DAT", ".LOG", ".BUP", ".DCL", ".DCD"]. @@ -2477,11 +2513,11 @@ info2(Tab, [{frag_hash, _V} | Tail]) -> % Ignore frag_hash info2(Tab, [{P, V} | Tail]) -> io:format("~-20w -> ~p~n",[P,V]), info2(Tab, Tail); -info2(_, []) -> +info2(_, []) -> io:format("~n", []). get_table_properties(Tab) -> - case catch mnesia_lib:db_match_object(ram_copies, + case catch mnesia_lib:db_match_object(ram_copies, mnesia_gvar, {{Tab, '_'}, '_'}) of {'EXIT', _} -> mnesia:abort({no_exists, Tab, all}); @@ -2509,9 +2545,9 @@ get_table_properties(Tab) -> recs = error_recs }). -restore(Opaque) -> +restore(Opaque) -> restore(Opaque, [], mnesia_monitor:get_env(backup_module)). -restore(Opaque, Args) when is_list(Args) -> +restore(Opaque, Args) when is_list(Args) -> restore(Opaque, Args, mnesia_monitor:get_env(backup_module)); restore(_Opaque, BadArg) -> {aborted, {badarg, BadArg}}. @@ -2522,7 +2558,7 @@ restore(Opaque, Args, Module) when is_list(Args), is_atom(Module) -> case mnesia_bup:read_schema(R#r.module, Opaque) of {error, Reason} -> {aborted, Reason}; - BupSchema -> + BupSchema -> schema_transaction(fun() -> do_restore(R, BupSchema) end) end; {'EXIT', Reason} -> @@ -2556,8 +2592,8 @@ check_restore_arg({keep_tables, List}, R) when is_list(List) -> check_restore_arg({skip_tables, List}, R) when is_list(List) -> TableList = [{Tab, skip_tables} || Tab <- List], R#r{table_options = R#r.table_options ++ TableList}; -check_restore_arg({default_op, Op}, R) -> - case Op of +check_restore_arg({default_op, Op}, R) -> + case Op of clear_tables -> ok; recreate_tables -> ok; keep_tables -> ok; @@ -2588,12 +2624,12 @@ restore_items([Rec | Recs], Header, Schema, R) -> case lists:keysearch(Tab, 1, R#r.tables) of {value, {Tab, Where0, Snmp, RecName}} -> Where = case Where0 of - undefined -> + undefined -> val({Tab, where_to_commit}); _ -> Where0 end, - {Rest, NRecs} = restore_tab_items([Rec | Recs], Tab, + {Rest, NRecs} = restore_tab_items([Rec | Recs], Tab, RecName, Where, Snmp, R#r.recs, R#r.insert_op), restore_items(Rest, Header, Schema, R#r{recs = NRecs}); @@ -2601,12 +2637,12 @@ restore_items([Rec | Recs], Header, Schema, R) -> Rest = skip_tab_items(Recs, Tab), restore_items(Rest, Header, Schema, R) end; - + restore_items([], _Header, _Schema, R) -> R. restore_func(Tab, R) -> - case lists:keysearch(Tab, 1, R#r.table_options) of + case lists:keysearch(Tab, 1, R#r.table_options) of {value, {Tab, OP}} -> OP; false -> @@ -2618,24 +2654,24 @@ where_to_commit(Tab, CsList) -> Disc = [{N, disc_copies} || N <- pick(Tab, disc_copies, CsList, [])], DiscO = [{N, disc_only_copies} || N <- pick(Tab, disc_only_copies, CsList, [])], Ram ++ Disc ++ DiscO. - + %% Changes of the Meta info of schema itself is not allowed restore_schema([{schema, schema, _List} | Schema], R) -> restore_schema(Schema, R); restore_schema([{schema, Tab, List} | Schema], R) -> case restore_func(Tab, R) of - clear_tables -> + clear_tables -> do_clear_table(Tab), - Snmp = val({Tab, snmp}), - RecName = val({Tab, record_name}), + Snmp = val({Tab, snmp}), + RecName = val({Tab, record_name}), R2 = R#r{tables = [{Tab, undefined, Snmp, RecName} | R#r.tables]}, restore_schema(Schema, R2); - recreate_tables -> + recreate_tables -> case ?catch_val({Tab, cstruct}) of - {'EXIT', _} -> + {'EXIT', _} -> TidTs = {_Mod, Tid, Ts} = get(mnesia_activity_state), RunningNodes = val({current, db_nodes}), - Nodes = mnesia_lib:intersect(mnesia_lib:cs_to_nodes(list2cs(List)), + Nodes = mnesia_lib:intersect(mnesia_lib:cs_to_nodes(list2cs(List)), RunningNodes), mnesia_locker:wlock_no_exist(Tid, Ts#tidstore.store, Tab, Nodes), TidTs; @@ -2643,20 +2679,20 @@ restore_schema([{schema, Tab, List} | Schema], R) -> TidTs = get_tid_ts_and_lock(Tab, write) end, NC = {cookie, ?unique_cookie}, - List2 = lists:keyreplace(cookie, 1, List, NC), + List2 = lists:keyreplace(cookie, 1, List, NC), Where = where_to_commit(Tab, List2), Snmp = pick(Tab, snmp, List2, []), RecName = pick(Tab, record_name, List2, Tab), insert_schema_ops(TidTs, [{op, restore_recreate, List2}]), R2 = R#r{tables = [{Tab, Where, Snmp, RecName} | R#r.tables]}, restore_schema(Schema, R2); - keep_tables -> + keep_tables -> get_tid_ts_and_lock(Tab, write), Snmp = val({Tab, snmp}), - RecName = val({Tab, record_name}), + RecName = val({Tab, record_name}), R2 = R#r{tables = [{Tab, undefined, Snmp, RecName} | R#r.tables]}, restore_schema(Schema, R2); - skip_tables -> + skip_tables -> restore_schema(Schema, R) end; @@ -2667,7 +2703,7 @@ restore_schema([{schema, Tab} | Schema], R) -> restore_schema([], R) -> R. -restore_tab_items([Rec | Rest], Tab, RecName, Where, Snmp, Recs, Op) +restore_tab_items([Rec | Rest], Tab, RecName, Where, Snmp, Recs, Op) when element(1, Rec) == Tab -> NewRecs = Op(Rec, Recs, RecName, Where, Snmp), restore_tab_items(Rest, Tab, RecName, Where, Snmp, NewRecs, Op); @@ -2675,7 +2711,7 @@ restore_tab_items([Rec | Rest], Tab, RecName, Where, Snmp, Recs, Op) restore_tab_items(Rest, _Tab, _RecName, _Where, _Snmp, Recs, _Op) -> {Rest, Recs}. -skip_tab_items([Rec| Rest], Tab) +skip_tab_items([Rec| Rest], Tab) when element(1, Rec) == Tab -> skip_tab_items(Rest, Tab); skip_tab_items(Recs, _) -> @@ -2710,7 +2746,6 @@ merge_schema() -> merge_schema(UserFun) -> schema_transaction(fun() -> UserFun(fun(Arg) -> do_merge_schema(Arg) end) end). - do_merge_schema(LockTabs0) -> {_Mod, Tid, Ts} = get_tid_ts_and_lock(schema, write), LockTabs = [{T, tab_to_nodes(T)} || T <- LockTabs0], @@ -2732,14 +2767,14 @@ do_merge_schema(LockTabs0) -> [mnesia_locker:wlock_no_exist( Tid, Store, T, mnesia_lib:intersect(Ns, OtherNodes)) || {T,Ns} <- LockTabs], - case rpc:call(Node, mnesia_controller, get_cstructs, []) of + case fetch_cstructs(Node) of {cstructs, Cstructs, RemoteRunning1} -> LockedAlready = Running ++ [Node], {New, Old} = mnesia_recover:connect_nodes(RemoteRunning1), RemoteRunning = mnesia_lib:intersect(New ++ Old, RemoteRunning1), - if + if RemoteRunning /= RemoteRunning1 -> - mnesia_lib:error("Mnesia on ~p could not connect to node(s) ~p~n", + mnesia_lib:error("Mnesia on ~p could not connect to node(s) ~p~n", [node(), RemoteRunning1 -- RemoteRunning]), mnesia:abort({node_not_running, RemoteRunning1 -- RemoteRunning}); true -> ok @@ -2749,24 +2784,24 @@ do_merge_schema(LockTabs0) -> [mnesia_locker:wlock_no_exist(Tid, Store, T, mnesia_lib:intersect(Ns,NeedsLock)) || {T,Ns} <- LockTabs], - {value, SchemaCs} = - lists:keysearch(schema, #cstruct.name, Cstructs), + NeedsConversion = need_old_cstructs(NeedsLock ++ LockedAlready), + {value, SchemaCs} = lists:keysearch(schema, #cstruct.name, Cstructs), + SchemaDef = cs2list(NeedsConversion, SchemaCs), %% Announce that Node is running - A = [{op, announce_im_running, node(), - cs2list(SchemaCs), Running, RemoteRunning}], + A = [{op, announce_im_running, node(), SchemaDef, Running, RemoteRunning}], do_insert_schema_ops(Store, A), - + %% Introduce remote tables to local node - do_insert_schema_ops(Store, make_merge_schema(Node, Cstructs)), - + do_insert_schema_ops(Store, make_merge_schema(Node, NeedsConversion, Cstructs)), + %% Introduce local tables to remote nodes Tabs = val({schema, tables}), Ops = [{op, merge_schema, get_create_list(T)} || T <- Tabs, not lists:keymember(T, #cstruct.name, Cstructs)], do_insert_schema_ops(Store, Ops), - + %% Ensure that the txn will be committed on all nodes NewNodes = RemoteRunning -- Running, mnesia_lib:set(prepare_op, {announce_im_running,NewNodes}), @@ -2782,19 +2817,49 @@ do_merge_schema(LockTabs0) -> not_merged end. +fetch_cstructs(Node) -> + case mnesia_monitor:needs_protocol_conversion(Node) of + true -> + case rpc:call(Node, mnesia_controller, get_cstructs, []) of + {cstructs, Cs0, RR} -> + {cstructs, [list2cs(cs2list(Cs)) || Cs <- Cs0], RR}; + Err -> Err + end; + false -> + rpc:call(Node, mnesia_controller, get_remote_cstructs, []) + end. + +need_old_cstructs(Nodes) -> + Filter = fun(Node) -> not mnesia_monitor:needs_protocol_conversion(Node) end, + case lists:dropwhile(Filter, Nodes) of + [] -> false; + [Node|_] -> + case rpc:call(Node, mnesia_lib, val, [{schema,cstruct}]) of + #cstruct{} -> + %% mnesia_lib:warning("Mnesia on ~p do not need to convert cstruct (~p)~n", + %% [node(), Node]), + false; + {badrpc, _} -> + need_old_cstructs(lists:delete(Node,Nodes)); + Cs when element(1, Cs) == cstruct, tuple_size(Cs) == 17 -> + ver4_4_18; % Without majority + Cs when element(1, Cs) == cstruct, tuple_size(Cs) == 18 -> + ver4_4_19 % With majority + end + end. + tab_to_nodes(Tab) when is_atom(Tab) -> Cs = val({Tab, cstruct}), mnesia_lib:cs_to_nodes(Cs). -make_merge_schema(Node, [Cs | Cstructs]) -> - Ops = do_make_merge_schema(Node, Cs), - Ops ++ make_merge_schema(Node, Cstructs); -make_merge_schema(_Node, []) -> +make_merge_schema(Node, NeedsConv, [Cs | Cstructs]) -> + Ops = do_make_merge_schema(Node, NeedsConv, Cs), + Ops ++ make_merge_schema(Node, NeedsConv, Cstructs); +make_merge_schema(_Node, _, []) -> []. %% Merge definitions of schema table -do_make_merge_schema(Node, RemoteCs) - when RemoteCs#cstruct.name == schema -> +do_make_merge_schema(Node, NeedsConv, RemoteCs = #cstruct{name = schema}) -> Cs = val({schema, cstruct}), Masters = mnesia_recover:get_master_nodes(schema), HasRemoteMaster = lists:member(Node, Masters), @@ -2804,15 +2869,15 @@ do_make_merge_schema(Node, RemoteCs) StCsLocal = mnesia_lib:cs_to_storage_type(node(), Cs), StRcsLocal = mnesia_lib:cs_to_storage_type(node(), RemoteCs), StCsRemote = mnesia_lib:cs_to_storage_type(Node, Cs), - StRcsRemote = mnesia_lib:cs_to_storage_type(Node, RemoteCs), - + StRcsRemote = mnesia_lib:cs_to_storage_type(Node, RemoteCs), + if Cs#cstruct.cookie == RemoteCs#cstruct.cookie, Cs#cstruct.version == RemoteCs#cstruct.version -> %% Great, we have the same cookie and version %% and do not need to merge cstructs []; - + Cs#cstruct.cookie /= RemoteCs#cstruct.cookie, Cs#cstruct.disc_copies /= [], RemoteCs#cstruct.disc_copies /= [] -> @@ -2823,14 +2888,14 @@ do_make_merge_schema(Node, RemoteCs) HasRemoteMaster == false -> %% Choose local cstruct, %% since it's the master - [{op, merge_schema, cs2list(Cs)}]; + [{op, merge_schema, cs2list(NeedsConv, Cs)}]; HasRemoteMaster == true, HasLocalMaster == false -> %% Choose remote cstruct, %% since it's the master - [{op, merge_schema, cs2list(RemoteCs)}]; - + [{op, merge_schema, cs2list(NeedsConv, RemoteCs)}]; + true -> Str = io_lib:format("Incompatible schema cookies. " "Please, restart from old backup." @@ -2838,12 +2903,12 @@ do_make_merge_schema(Node, RemoteCs) [Node, cs2list(RemoteCs), node(), cs2list(Cs)]), throw(Str) end; - + StCsLocal /= StRcsLocal, StRcsLocal /= unknown, StCsLocal /= ram_copies -> Str = io_lib:format("Incompatible schema storage types (local). " "on ~w storage ~w, on ~w storage ~w~n", [node(), StCsLocal, Node, StRcsLocal]), - throw(Str); + throw(Str); StCsRemote /= StRcsRemote, StCsRemote /= unknown, StRcsRemote /= ram_copies -> Str = io_lib:format("Incompatible schema storage types (remote). " "on ~w cs ~w, on ~w rcs ~w~n", @@ -2854,27 +2919,27 @@ do_make_merge_schema(Node, RemoteCs) %% Choose local cstruct, %% since it involves disc nodes MergedCs = merge_cstructs(Cs, RemoteCs, Force), - [{op, merge_schema, cs2list(MergedCs)}]; - + [{op, merge_schema, cs2list(NeedsConv, MergedCs)}]; + RemoteCs#cstruct.disc_copies /= [] -> %% Choose remote cstruct, %% since it involves disc nodes MergedCs = merge_cstructs(RemoteCs, Cs, Force), - [{op, merge_schema, cs2list(MergedCs)}]; + [{op, merge_schema, cs2list(NeedsConv, MergedCs)}]; Cs > RemoteCs -> %% Choose remote cstruct MergedCs = merge_cstructs(RemoteCs, Cs, Force), - [{op, merge_schema, cs2list(MergedCs)}]; - + [{op, merge_schema, cs2list(NeedsConv, MergedCs)}]; + true -> %% Choose local cstruct MergedCs = merge_cstructs(Cs, RemoteCs, Force), - [{op, merge_schema, cs2list(MergedCs)}] + [{op, merge_schema, cs2list(NeedsConv, MergedCs)}] end; %% Merge definitions of normal table -do_make_merge_schema(Node, RemoteCs) -> +do_make_merge_schema(Node, NeedsConv, RemoteCs = #cstruct{}) -> Tab = RemoteCs#cstruct.name, Masters = mnesia_recover:get_master_nodes(schema), HasRemoteMaster = lists:member(Node, Masters), @@ -2883,27 +2948,27 @@ do_make_merge_schema(Node, RemoteCs) -> case ?catch_val({Tab, cstruct}) of {'EXIT', _} -> %% A completely new table, created while Node was down - [{op, merge_schema, cs2list(RemoteCs)}]; + [{op, merge_schema, cs2list(NeedsConv, RemoteCs)}]; Cs when Cs#cstruct.cookie == RemoteCs#cstruct.cookie -> if Cs#cstruct.version == RemoteCs#cstruct.version -> %% We have exactly the same version of the %% table def []; - + Cs#cstruct.version > RemoteCs#cstruct.version -> %% Oops, we have different versions %% of the table def, lets merge them. %% The only changes that may have occurred %% is that new replicas may have been added. MergedCs = merge_cstructs(Cs, RemoteCs, Force), - [{op, merge_schema, cs2list(MergedCs)}]; - + [{op, merge_schema, cs2list(NeedsConv, MergedCs)}]; + Cs#cstruct.version < RemoteCs#cstruct.version -> %% Oops, we have different versions %% of the table def, lets merge them MergedCs = merge_cstructs(RemoteCs, Cs, Force), - [{op, merge_schema, cs2list(MergedCs)}] + [{op, merge_schema, cs2list(NeedsConv, MergedCs)}] end; Cs -> %% Different cookies, not possible to merge @@ -2912,14 +2977,14 @@ do_make_merge_schema(Node, RemoteCs) -> HasRemoteMaster == false -> %% Choose local cstruct, %% since it's the master - [{op, merge_schema, cs2list(Cs)}]; + [{op, merge_schema, cs2list(NeedsConv, Cs)}]; HasRemoteMaster == true, HasLocalMaster == false -> %% Choose remote cstruct, %% since it's the master - [{op, merge_schema, cs2list(RemoteCs)}]; - + [{op, merge_schema, cs2list(NeedsConv, RemoteCs)}]; + true -> Str = io_lib:format("Bad cookie in table definition" " ~w: ~w = ~w, ~w = ~w~n", @@ -2989,7 +3054,7 @@ compare_storage_type(true, One, Another) -> compare_storage_type(false, Another, One); compare_storage_type(false, _One, _Another) -> incompatible. - + change_storage_type(N, ram_copies, Cs) -> Nodes = [N | Cs#cstruct.ram_copies], Cs#cstruct{ram_copies = mnesia_lib:uniq(Nodes)}; @@ -3071,14 +3136,14 @@ verify_merge(RemoteCs) -> if StCsLocal == StRcsLocal -> ok; StCsLocal == unknown -> ok; - (StRcsLocal == unknown), (HasRemoteMaster == false) -> + (StRcsLocal == unknown), (HasRemoteMaster == false) -> {merge_error, Cs, RemoteCs}; %% Trust the merger true -> ok end end. -announce_im_running([N | Ns], SchemaCs) -> +announce_im_running([N | Ns], SchemaCs) -> {L1, L2} = mnesia_recover:connect_nodes([N]), case lists:member(N, L1) or lists:member(N, L2) of true -> @@ -3095,7 +3160,7 @@ announce_im_running([], _) -> unannounce_im_running([N | Ns]) -> mnesia_lib:del({current, db_nodes}, N), - mnesia_controller:del_active_replica(schema, N), + mnesia_controller:del_active_replica(schema, N), unannounce_im_running(Ns); unannounce_im_running([]) -> ok. |