1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1996-2020. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20
21%%
22-module(mnesia_monitor).
23
24-behaviour(gen_server).
25
26%% Public exports
27-export([
28	 close_dets/1,
29	 close_log/1,
30	 detect_inconcistency/2,
31	 get_env/1,
32	 init/0,
33	 mktab/2,
34	 unsafe_mktab/2,
35         unsafe_create_external/4,
36	 mnesia_down/2,
37	 needs_protocol_conversion/1,
38	 negotiate_protocol/1,
39	 disconnect/1,
40	 open_dets/2,
41	 unsafe_open_dets/2,
42	 open_log/1,
43	 patch_env/2,
44	 protocol_version/0,
45	 reopen_log/3,
46	 set_env/2,
47	 start/0,
48	 start_proc/4,
49	 sync_log/1,
50	 terminate_proc/3,
51	 unsafe_close_dets/1,
52	 unsafe_close_log/1,
53	 use_dir/0,
54	 do_check_type/2
55	]).
56
57%% gen_server callbacks
58-export([
59	 init/1,
60	 handle_call/3,
61	 handle_cast/2,
62	 handle_info/2,
63	 terminate/2,
64	 code_change/3
65	]).
66
67%% Internal exports
68-export([
69	 call/1,
70	 cast/1,
71	 detect_partitioned_network/2,
72	 has_remote_mnesia_down/1,
73	 negotiate_protocol_impl/2
74	]).
75
76-compile({no_auto_import,[error/2]}).
77
78-import(mnesia_lib, [dbg_out/2, verbose/2, error/2, fatal/2, set/2]).
79
80-include("mnesia.hrl").
81
82-record(state, {supervisor, pending_negotiators = [],
83		going_down = [], tm_started = false, early_connects = [],
84		connecting, mq = [], remote_node_status = []}).
85
86-define(current_protocol_version,  {8,5}).
87
88-define(previous_protocol_version, {8,4}).
89
90start() ->
91    gen_server:start_link({local, ?MODULE}, ?MODULE,
92			  [self()], [{timeout, infinity}
93				     %% ,{debug, [trace]}
94				    ]).
95
96init() ->
97    call(init).
98
99mnesia_down(From, Node) ->
100    cast({mnesia_down, From, Node}).
101
102mktab(Tab, Args) ->
103    unsafe_call({mktab, Tab, Args}).
104unsafe_mktab(Tab, Args) ->
105    unsafe_call({unsafe_mktab, Tab, Args}).
106
107open_dets(Tab, Args) ->
108    unsafe_call({open_dets, Tab, Args}).
109unsafe_open_dets(Tab, Args) ->
110    unsafe_call({unsafe_open_dets, Tab, Args}).
111
112close_dets(Tab) ->
113    unsafe_call({close_dets, Tab}).
114
115unsafe_close_dets(Name) ->
116    unsafe_call({unsafe_close_dets, Name}).
117
118open_log(Args) ->
119    unsafe_call({open_log, Args}).
120
121reopen_log(Name, Fname, Head) ->
122    unsafe_call({reopen_log, Name, Fname, Head}).
123
124sync_log(Name) ->
125    unsafe_call({sync_log, Name}).
126
127close_log(Name) ->
128    unsafe_call({close_log, Name}).
129
130unsafe_close_log(Name) ->
131    unsafe_call({unsafe_close_log, Name}).
132
133unsafe_create_external(Tab, Alias, Mod, Cs) ->
134    unsafe_call({unsafe_create_external, Tab, Alias, Mod, Cs}).
135
136disconnect(Node) ->
137    cast({disconnect, Node}).
138
139%% Returns GoodNoodes
140%% Creates a link to each compatible monitor and
141%% protocol_version to agreed version upon success
142
143negotiate_protocol([]) -> [];
144negotiate_protocol(Nodes) ->
145    call({negotiate_protocol, Nodes}).
146
147negotiate_protocol_impl(Nodes, Requester) ->
148    Version    = mnesia:system_info(version),
149    Protocols  = acceptable_protocol_versions(),
150    MonitorPid = whereis(?MODULE),
151    Msg = {negotiate_protocol, MonitorPid, Version, Protocols},
152    {Replies, _BadNodes} = multicall(Nodes, Msg),
153    Res = check_protocol(Replies, Protocols),
154    ?MODULE ! {protocol_negotiated,Requester,Res},
155    unlink(whereis(?MODULE)),
156    ok.
157
158check_protocol([{Node, {accept, Mon, Version, Protocol}} | Tail], Protocols) ->
159    case lists:member(Protocol, Protocols) of
160	true ->
161	    case Protocol == protocol_version() of
162		true ->
163		    set({protocol, Node}, {Protocol, false});
164		false ->
165		    set({protocol, Node}, {Protocol, true})
166	    end,
167	    [node(Mon) | check_protocol(Tail, Protocols)];
168	false  ->
169	    verbose("Failed to connect with ~p. ~p protocols rejected. "
170		    "expected version = ~p, expected protocol = ~p~n",
171		    [Node, Protocols, Version, Protocol]),
172	    unlink(Mon), % Get rid of unnecessary link
173	    check_protocol(Tail, Protocols)
174    end;
175check_protocol([{Node, {reject, _Mon, Version, Protocol}} | Tail], Protocols) ->
176    verbose("Failed to connect with ~p. ~p protocols rejected. "
177	    "expected version = ~p, expected protocol = ~p~n",
178	    [Node, Protocols, Version, Protocol]),
179    check_protocol(Tail, Protocols);
180check_protocol([{error, _Reason} | Tail], Protocols) ->
181    dbg_out("~p connect failed error: ~tp~n", [?MODULE, _Reason]),
182    check_protocol(Tail, Protocols);
183check_protocol([{badrpc, _Reason} | Tail], Protocols) ->
184    dbg_out("~p connect failed badrpc: ~tp~n", [?MODULE, _Reason]),
185    check_protocol(Tail, Protocols);
186check_protocol([], [Protocol | _Protocols]) ->
187    set(protocol_version, Protocol),
188    [].
189
190protocol_version() ->
191    case ?catch_val(protocol_version) of
192	{'EXIT', _} -> ?current_protocol_version;
193	Version -> Version
194    end.
195
196%% A sorted list of acceptable protocols the
197%% preferred protocols are first in the list
198acceptable_protocol_versions() ->
199    [protocol_version(), ?previous_protocol_version, {8,3}].
200
201needs_protocol_conversion(Node) ->
202    case {?catch_val({protocol, Node}), protocol_version()} of
203	{{'EXIT', _}, _} ->
204	    false;
205	{{_, Bool}, ?current_protocol_version} ->
206	    Bool;
207	{{_, Bool}, _} ->
208	    not Bool
209    end.
210
211cast(Msg) ->
212    case whereis(?MODULE) of
213	undefined -> ok;
214	Pid ->  gen_server:cast(Pid, Msg)
215    end.
216
217unsafe_call(Msg) ->
218    case whereis(?MODULE) of
219	undefined -> {error, {node_not_running, node()}};
220	Pid -> gen_server:call(Pid, Msg, infinity)
221    end.
222
223call(Msg) ->
224    case whereis(?MODULE) of
225	undefined ->
226	    {error, {node_not_running, node()}};
227	Pid ->
228	    link(Pid),
229	    Res = gen_server:call(Pid, Msg, infinity),
230	    unlink(Pid),
231
232            %% We get an exit signal if server dies
233	    receive
234		{'EXIT', Pid, _Reason} ->
235		    {error, {node_not_running, node()}}
236	    after 0 ->
237		    Res
238	    end
239    end.
240
241multicall(Nodes, Msg) ->
242    rpc:multicall(Nodes, ?MODULE, call, [Msg]).
243
244start_proc(Who, Mod, Fun, Args) ->
245    Args2 = [Who, Mod, Fun, Args],
246    proc_lib:start_link(mnesia_sp, init_proc, Args2, infinity).
247
248terminate_proc(Who, R, State) when R /= shutdown, R /= killed ->
249    fatal("~p crashed: ~p state: ~tp~n", [Who, R, State]);
250
251terminate_proc(Who, Reason, _State) ->
252    mnesia_lib:verbose("~p terminated: ~tp~n", [Who, Reason]),
253    ok.
254
255%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
256%%% Callback functions from gen_server
257
258%%----------------------------------------------------------------------
259%% Func: init/1
260%% Returns: {ok, State}          |
261%%          {ok, State, Timeout} |
262%%          {stop, Reason}
263%%----------------------------------------------------------------------
264init([Parent]) ->
265    process_flag(trap_exit, true),
266    ?ets_new_table(mnesia_gvar, [set, public, named_table]),
267    ?ets_new_table(mnesia_stats, [set, public, named_table]),
268    set(subscribers, []),
269    set(activity_subscribers, []),
270    mnesia_lib:verbose("~p starting: ~p~n", [?MODULE, self()]),
271    Version = mnesia:system_info(version),
272    set(version, Version),
273    dbg_out("Version: ~p~n", [Version]),
274
275    try process_config_args(env()) of
276	ok ->
277	    mnesia_lib:set({'$$$_report', current_pos}, 0),
278	    Level = mnesia_lib:val(debug),
279	    mnesia_lib:verbose("Mnesia debug level set to ~p\n", [Level]),
280	    set(mnesia_status, starting), %%  set start status
281	    set({current, db_nodes}, [node()]),
282	    set(use_dir, use_dir()),
283	    mnesia_lib:create_counter(trans_aborts),
284	    mnesia_lib:create_counter(trans_commits),
285	    mnesia_lib:create_counter(trans_log_writes),
286	    Left = get_env(dump_log_write_threshold),
287	    mnesia_lib:set_counter(trans_log_writes_left, Left),
288	    mnesia_lib:create_counter(trans_log_writes_prev),
289	    mnesia_lib:create_counter(trans_restarts),
290	    mnesia_lib:create_counter(trans_failures),
291	    set(checkpoints, []),
292	    set(pending_checkpoints, []),
293	    set(pending_checkpoint_pids, []),
294
295	    {ok, #state{supervisor = Parent}}
296    catch _:Reason ->
297	    mnesia_lib:report_fatal("Bad configuration: ~tp~n", [Reason]),
298	    {stop, {bad_config, Reason}}
299    end.
300
301use_dir() ->
302    case ?catch_val(use_dir) of
303	{'EXIT', _} ->
304	    case get_env(schema_location) of
305		disc -> true;
306		opt_disc -> non_empty_dir();
307		ram -> false
308	    end;
309	Bool ->
310	    Bool
311    end.
312
313%% Returns true if the Mnesia directory contains
314%% important files
315non_empty_dir() ->
316    mnesia_lib:exists(mnesia_bup:fallback_bup()) or
317    mnesia_lib:exists(mnesia_lib:tab2dmp(schema)) or
318    mnesia_lib:exists(mnesia_lib:tab2dat(schema)).
319
320%%----------------------------------------------------------------------
321%% Func: handle_call/3
322%% Returns: {reply, Reply, State}          |
323%%          {reply, Reply, State, Timeout} |
324%%          {noreply, State}               |
325%%          {noreply, State, Timeout}      |
326%%          {stop, Reason, Reply, State}   | (terminate/2 is called)
327%%----------------------------------------------------------------------
328
329handle_call({mktab, Tab, Args}, _From, State) ->
330    try ?ets_new_table(Tab, Args) of
331	Reply ->
332	    {reply, Reply, State}
333    catch error:ExitReason ->
334	    Msg = "Cannot create ets table",
335	    Reason = {system_limit, Msg, Tab, Args, ExitReason},
336	    fatal("~tp~n", [Reason]),
337	    {noreply, State}
338    end;
339
340handle_call({unsafe_mktab, Tab, Args}, _From, State) ->
341    try ?ets_new_table(Tab, Args) of
342	Reply ->
343	    {reply, Reply, State}
344    catch error:ExitReason ->
345	    {reply, {error, ExitReason}, State}
346    end;
347
348handle_call({open_dets, Tab, Args}, _From, State) ->
349    case mnesia_lib:dets_sync_open(Tab, Args) of
350	{ok, Tab} ->
351	    {reply, {ok, Tab}, State};
352
353	{error, Reason} ->
354	    Msg = "Cannot open dets table",
355	    Error = {error, {Msg, Tab, Args, Reason}},
356	    fatal("~tp~n", [Error]),
357	    {noreply, State}
358    end;
359
360handle_call({unsafe_open_dets, Tab, Args}, _From, State) ->
361    case mnesia_lib:dets_sync_open(Tab, Args) of
362	{ok, Tab} ->
363	    {reply, {ok, Tab}, State};
364	{error, Reason} ->
365	    {reply, {error,Reason}, State}
366    end;
367
368handle_call({close_dets, Tab}, _From, State) ->
369    ok = mnesia_lib:dets_sync_close(Tab),
370    {reply, ok, State};
371
372handle_call({unsafe_close_dets, Tab}, _From, State) ->
373    mnesia_lib:dets_sync_close(Tab),
374    {reply, ok, State};
375
376handle_call({open_log, Args}, _From, State) ->
377    Res = disk_log:open([{notify, true}|Args]),
378    {reply, Res, State};
379
380handle_call({reopen_log, Name, Fname, Head}, _From, State) ->
381    case disk_log:reopen(Name, Fname, Head) of
382	ok ->
383	    {reply, ok, State};
384
385        {error, Reason} ->
386	    Msg = "Cannot rename disk_log file",
387            Error = {error, {Msg, Name, Fname, Head, Reason}},
388	    fatal("~tp~n", [Error]),
389 	    {noreply, State}
390    end;
391
392handle_call({sync_log, Name}, _From, State) ->
393    {reply, disk_log:sync(Name), State};
394
395handle_call({close_log, Name}, _From, State) ->
396    case disk_log:close(Name) of
397	ok ->
398	    {reply, ok, State};
399
400        {error, Reason} ->
401	    Msg = "Cannot close disk_log file",
402            Error = {error, {Msg, Name, Reason}},
403	    fatal("~tp~n", [Error]),
404	    {noreply, State}
405    end;
406
407handle_call({unsafe_close_log, Name}, _From, State) ->
408    _ = disk_log:close(Name),
409    {reply, ok, State};
410
411handle_call({unsafe_create_external, Tab, Alias, Mod, Cs}, _From, State) ->
412    case ?CATCH(Mod:create_table(Alias, Tab, mnesia_schema:cs2list(Cs))) of
413	{'EXIT', ExitReason} ->
414	    {reply, {error, ExitReason}, State};
415	Reply ->
416	    {reply, Reply, State}
417    end;
418
419handle_call({negotiate_protocol, Mon, _Version, _Protocols}, _From, State)
420  when State#state.tm_started == false ->
421    State2 =  State#state{early_connects = [node(Mon) | State#state.early_connects]},
422    {reply, {node(), {reject, self(), uninitialized, uninitialized}}, State2};
423
424%% From remote monitor..
425handle_call({negotiate_protocol, Mon, Version, Protocols}, From, State)
426  when node(Mon) /= node() ->
427    Protocol = protocol_version(),
428    MyVersion = mnesia:system_info(version),
429    case lists:member(Protocol, Protocols) of
430	true ->
431	    accept_protocol(Mon, MyVersion, Protocol, From, State);
432	false ->
433	    %% in this release we should be able to handle the previous
434	    %% protocol
435	    case hd(Protocols) of
436		?previous_protocol_version ->
437		    accept_protocol(Mon, MyVersion, ?previous_protocol_version, From, State);
438		_ ->
439		    verbose("Connection with ~p rejected. "
440			    "version = ~p, protocols = ~p, "
441			    "expected version = ~p, expected protocol = ~p~n",
442			    [node(Mon), Version, Protocols, MyVersion, Protocol]),
443		    {reply, {node(), {reject, self(), MyVersion, Protocol}}, State}
444	    end
445    end;
446
447%% Local request to negotiate with other monitors (nodes).
448handle_call({negotiate_protocol, Nodes}, From, State) ->
449    case mnesia_lib:intersect(State#state.going_down, Nodes) of
450	[] ->
451	    spawn_link(?MODULE, negotiate_protocol_impl, [Nodes, From]),
452	    {noreply, State#state{connecting={From,Nodes}}};
453	_ ->  %% Cannot connect now, still processing mnesia down
454	    {reply, busy, State}
455    end;
456
457handle_call(init, _From, State) ->
458    _ = net_kernel:monitor_nodes(true),
459    EarlyNodes = State#state.early_connects,
460    State2 = State#state{tm_started = true},
461    {reply, EarlyNodes, State2};
462
463handle_call(Msg, _From, State) ->
464    error("~p got unexpected call: ~tp~n", [?MODULE, Msg]),
465    {noreply, State}.
466
467accept_protocol(Mon, Version, Protocol, From, State) ->
468    Reply = {node(), {accept, self(), Version, Protocol}},
469    Node = node(Mon),
470    Pending0 = State#state.pending_negotiators,
471    Pending = lists:keydelete(Node, 1, Pending0),
472    case lists:member(Node, State#state.going_down) of
473	true ->
474	    %% Wait for the mnesia_down to be processed,
475	    %% before we reply
476	    P = Pending ++ [{Node, Mon, From, Reply}],
477	    {noreply, State#state{pending_negotiators = P}};
478	false ->
479	    %% No need for wait
480	    link(Mon),  %% link to remote Monitor
481	    case Protocol == protocol_version() of
482		true ->
483		    set({protocol, Node}, {Protocol, false});
484		false ->
485		    set({protocol, Node}, {Protocol, true})
486	    end,
487	    {reply, Reply, State#state{pending_negotiators = Pending}}
488    end.
489
490%%----------------------------------------------------------------------
491%% Func: handle_cast/2
492%% Returns: {noreply, State}          |
493%%          {noreply, State, Timeout} |
494%%          {stop, Reason, State}            (terminate/2 is called)
495%%----------------------------------------------------------------------
496
497handle_cast({mnesia_down, mnesia_controller, Node}, State) ->
498    mnesia_tm:mnesia_down(Node),
499    {noreply, State};
500
501handle_cast({mnesia_down, mnesia_tm, Node}, State) ->
502    Down = {mnesia_down, Node},
503    mnesia_lib:report_system_event(Down),
504    GoingDown = lists:delete(Node, State#state.going_down),
505    State2 = State#state{going_down = GoingDown},
506    Pending = State#state.pending_negotiators,
507    State3 = check_raise_conditon_nodeup(Node, State2),
508    case lists:keysearch(Node, 1, Pending) of
509	{value, {Node, Mon, ReplyTo, Reply}} ->
510	    %% Late reply to remote monitor
511	    link(Mon),  %% link to remote Monitor
512	    gen_server:reply(ReplyTo, Reply),
513	    P2 = lists:keydelete(Node, 1,Pending),
514	    State4 = State3#state{pending_negotiators = P2},
515	    process_q(State4);
516	false ->
517	    %% No pending remote monitors
518	    process_q(State3)
519    end;
520
521handle_cast({disconnect, Node}, State) ->
522    case rpc:call(Node, erlang, whereis, [?MODULE]) of
523	{badrpc, _} ->
524	    ignore;
525	undefined ->
526	    ignore;
527	RemoteMon when is_pid(RemoteMon) ->
528	    unlink(RemoteMon)
529    end,
530    {noreply, State};
531
532handle_cast({inconsistent_database, Context, Node}, State) ->
533    Msg = {inconsistent_database, Context, Node},
534    mnesia_lib:report_system_event(Msg),
535    {noreply, State};
536
537handle_cast(Msg, State) ->
538    error("~p got unexpected cast: ~tp~n", [?MODULE, Msg]),
539    {noreply, State}.
540
541%%----------------------------------------------------------------------
542%% Func: handle_info/2
543%% Returns: {noreply, State}          |
544%%          {noreply, State, Timeout} |
545%%          {stop, Reason, State}            (terminate/2 is called)
546%%----------------------------------------------------------------------
547
548handle_info({'EXIT', Pid, R}, State) when Pid == State#state.supervisor ->
549    dbg_out("~p was ~p by supervisor~n",[?MODULE, R]),
550    {stop, R, State};
551
552handle_info({'EXIT', Pid, fatal}, State) when node(Pid) == node() ->
553    dbg_out("~p got FATAL ERROR from: ~p~n",[?MODULE, Pid]),
554    %% This may hang supervisor if a shutdown happens at the same time as an fatal
555    %% is in progress
556    %% exit(State#state.supervisor, shutdown),
557    %% It is better to kill an innocent process
558    ?SAFE(exit(whereis(mnesia_locker), kill)),
559    {noreply, State};
560
561handle_info(Msg = {'EXIT',Pid,_}, State) ->
562    Node = node(Pid),
563    if
564	Node /= node(), State#state.connecting == undefined ->
565	    %% Remotly linked process died, assume that it was a mnesia_monitor
566	    mnesia_recover:mnesia_down(Node),
567	    mnesia_controller:mnesia_down(Node),
568	    {noreply, State#state{going_down = [Node | State#state.going_down]}};
569	Node /= node() ->
570	    {noreply, State#state{mq = State#state.mq ++ [{info, Msg}]}};
571	true ->
572	    %% We have probably got an exit signal from
573	    %% disk_log or dets
574	    Hint = "Hint: check that the disk still is writable",
575	    fatal("~p got unexpected info: ~tp; ~p~n",
576		  [?MODULE, Msg, Hint])
577    end;
578
579handle_info({protocol_negotiated, From,Res}, State) ->
580    From = element(1,State#state.connecting),
581    gen_server:reply(From, Res),
582    process_q(State#state{connecting = undefined});
583
584handle_info({check_nodeup, Node}, State) ->
585    State2 = check_mnesia_down(Node, State),
586    {noreply, State2};
587
588handle_info({nodeup, Node}, State) ->
589    State2 = remote_node_status(Node, up, State),
590    State3 = check_mnesia_down(Node, State2),
591    {noreply, State3};
592
593handle_info({nodedown, Node}, State) ->
594    State2 = remote_node_status(Node, down, State),
595    {noreply, State2};
596
597handle_info({disk_log, _Node, Log, Info}, State) ->
598    case Info of
599	{truncated, _No} ->
600	    ok;
601	_ ->
602	    mnesia_lib:important("Warning Log file ~tp error reason ~ts~n",
603				 [Log, disk_log:format_error(Info)])
604    end,
605    {noreply, State};
606
607handle_info(Msg, State) ->
608    error("~p got unexpected info (~tp): ~tp~n", [?MODULE, State, Msg]).
609
610process_q(State = #state{mq=[]}) -> {noreply,State};
611process_q(State = #state{mq=[{info,Msg}|R]}) ->
612    handle_info(Msg, State#state{mq=R});
613process_q(State = #state{mq=[{cast,Msg}|R]}) ->
614    handle_cast(Msg, State#state{mq=R});
615process_q(State = #state{mq=[{call,From,Msg}|R]}) ->
616    handle_call(Msg, From, State#state{mq=R}).
617
618%%----------------------------------------------------------------------
619%% Func: terminate/2
620%% Purpose: Shutdown the server
621%% Returns: any (ignored by gen_server)
622%%----------------------------------------------------------------------
623terminate(Reason, State) ->
624    terminate_proc(?MODULE, Reason, State).
625
626%%----------------------------------------------------------------------
627%% Func: code_change/3
628%% Purpose: Upgrade process when its code is to be changed
629%% Returns: {ok, NewState}
630%%----------------------------------------------------------------------
631
632
633code_change(_, {state, SUP, PN, GD, TMS, EC}, _) ->
634    {ok, #state{supervisor=SUP, pending_negotiators=PN,
635		going_down = GD, tm_started =TMS, early_connects = EC}};
636
637code_change(_OldVsn, State, _Extra) ->
638    {ok, State}.
639
640%%%----------------------------------------------------------------------
641%%% Internal functions
642%%%----------------------------------------------------------------------
643
644process_config_args([]) ->
645    ok;
646process_config_args([C|T]) ->
647    V = get_env(C),
648    dbg_out("Env ~p: ~p~n", [C, V]),
649    mnesia_lib:set(C, V),
650    process_config_args(T).
651
652set_env(E,Val) ->
653    mnesia_lib:set(E, check_type(E,Val)),
654    ok.
655
656get_env(E) ->
657    case ?catch_val(E) of
658	{'EXIT', _} ->
659	    case application:get_env(mnesia, E) of
660		{ok, Val} ->
661		    check_type(E, Val);
662		undefined ->
663		    check_type(E, default_env(E))
664	    end;
665	Val ->
666	    Val
667    end.
668
669env() ->
670    [
671     access_module,
672     allow_index_on_key,
673     auto_repair,
674     backup_module,
675     debug,
676     dir,
677     dump_disc_copies_at_startup,
678     dump_log_load_regulation,
679     dump_log_time_threshold,
680     dump_log_update_in_place,
681     dump_log_write_threshold,
682     event_module,
683     extra_db_nodes,
684     ignore_fallback_at_startup,
685     fallback_error_function,
686     fold_chunk_size,
687     max_wait_for_decision,
688     schema_location,
689     core_dir,
690     pid_sort_order,
691     no_table_loaders,
692     dc_dump_limit,
693     send_compressed,
694     max_transfer_size,
695     schema
696    ].
697
698default_env(access_module) ->
699    mnesia;
700default_env(auto_repair) ->
701    true;
702default_env(allow_index_on_key) ->
703    false;
704default_env(backup_module) ->
705    mnesia_backup;
706default_env(debug) ->
707    none;
708default_env(dir) ->
709    Name = lists:concat(["Mnesia.", node()]),
710    filename:absname(Name);
711default_env(dump_disc_copies_at_startup) ->
712    true;
713default_env(dump_log_load_regulation) ->
714    false;
715default_env(dump_log_time_threshold) ->
716    timer:minutes(3);
717default_env(dump_log_update_in_place) ->
718    true;
719default_env(dump_log_write_threshold) ->
720    1000;
721default_env(event_module) ->
722    mnesia_event;
723default_env(extra_db_nodes) ->
724    [];
725default_env(ignore_fallback_at_startup) ->
726    false;
727default_env(fallback_error_function) ->
728    {mnesia, lkill};
729default_env(fold_chunk_size) ->
730    100;
731default_env(max_wait_for_decision) ->
732    infinity;
733default_env(schema_location) ->
734    opt_disc;
735default_env(core_dir) ->
736    false;
737default_env(pid_sort_order) ->
738    false;
739default_env(no_table_loaders) ->
740    2;
741default_env(dc_dump_limit) ->
742    4;
743default_env(send_compressed) ->
744    0;
745default_env(max_transfer_size) ->
746    64000;
747default_env(schema) ->
748    [].
749
750check_type(Env, Val) ->
751    try do_check_type(Env, Val)
752    catch error:_ -> exit({bad_config, Env, Val})
753    end.
754
755do_check_type(access_module, A) when is_atom(A) -> A;
756do_check_type(allow_index_on_key, B) -> bool(B);
757do_check_type(auto_repair, B) -> bool(B);
758do_check_type(backup_module, B) when is_atom(B) -> B;
759do_check_type(debug, debug) -> debug;
760do_check_type(debug, false) -> none;
761do_check_type(debug, none) -> none;
762do_check_type(debug, trace) -> trace;
763do_check_type(debug, true) -> debug;
764do_check_type(debug, verbose) -> verbose;
765do_check_type(dir, V) -> filename:absname(V);
766do_check_type(dump_disc_copies_at_startup, B) -> bool(B);
767do_check_type(dump_log_load_regulation, B) -> bool(B);
768do_check_type(dump_log_time_threshold, I) when is_integer(I), I > 0 -> I;
769do_check_type(dump_log_update_in_place, B) -> bool(B);
770do_check_type(dump_log_write_threshold, I) when is_integer(I), I > 0 -> I;
771do_check_type(event_module, A) when is_atom(A) -> A;
772do_check_type(ignore_fallback_at_startup, B) -> bool(B);
773do_check_type(fallback_error_function, {Mod, Func})
774  when is_atom(Mod), is_atom(Func) -> {Mod, Func};
775do_check_type(extra_db_nodes, L) when is_list(L) ->
776    Fun = fun(N) when N == node() -> false;
777	     (A) when is_atom(A) -> true
778	  end,
779    lists:filter(Fun, L);
780do_check_type(fold_chunk_size, I) when is_integer(I), I > 0;
781				       I =:= infinity -> I;
782do_check_type(max_wait_for_decision, infinity) -> infinity;
783do_check_type(max_wait_for_decision, I) when is_integer(I), I > 0 -> I;
784do_check_type(schema_location, M) -> media(M);
785do_check_type(core_dir, "false") -> false;
786do_check_type(core_dir, false) -> false;
787do_check_type(core_dir, Dir) when is_list(Dir) -> Dir;
788do_check_type(pid_sort_order, r9b_plain) -> r9b_plain;
789do_check_type(pid_sort_order, "r9b_plain") -> r9b_plain;
790do_check_type(pid_sort_order, standard) -> standard;
791do_check_type(pid_sort_order, "standard") -> standard;
792do_check_type(pid_sort_order, _) -> false;
793do_check_type(no_table_loaders, N) when is_integer(N), N > 0 -> N;
794do_check_type(dc_dump_limit,N) when is_number(N), N > 0 -> N;
795do_check_type(send_compressed, L) when is_integer(L), L >= 0, L =< 9 -> L;
796do_check_type(max_transfer_size, N) when is_integer(N), N > 0 -> N;
797do_check_type(schema, L) when is_list(L) -> L.
798
799bool(true) -> true;
800bool(false) -> false.
801
802media(disc) -> disc;
803media(opt_disc) -> opt_disc;
804media(ram) -> ram.
805
806patch_env(Env, Val) ->
807    try do_check_type(Env, Val) of
808	NewVal ->
809	    application_controller:set_env(mnesia, Env, NewVal),
810	    NewVal
811    catch error:_ ->
812	    {error, {bad_type, Env, Val}}
813    end.
814
815detect_partitioned_network(Mon, Node) ->
816    detect_inconcistency([Node], running_partitioned_network),
817    unlink(Mon),
818    exit(normal).
819
820detect_inconcistency([], _Context) ->
821    ok;
822detect_inconcistency(Nodes, Context) ->
823    Downs = [N || N <- Nodes, mnesia_recover:has_mnesia_down(N)],
824    {Replies, _BadNodes} =
825	rpc:multicall(Downs, ?MODULE, has_remote_mnesia_down, [node()]),
826    report_inconsistency(Replies, Context, ok).
827
828has_remote_mnesia_down(Node) ->
829    HasDown = mnesia_recover:has_mnesia_down(Node),
830    Master  = mnesia_recover:get_master_nodes(schema),
831    if
832	HasDown == true, Master == [] ->
833	    {true, node()};
834	true ->
835	    {false, node()}
836    end.
837
838report_inconsistency([{true, Node} | Replies], Context, _Status) ->
839    %% Oops, Mnesia is already running on the
840    %% other node AND we both regard each
841    %% other as down. The database is
842    %% potentially inconsistent and we has to
843    %% do tell the applications about it, so
844    %% they may perform some clever recovery
845    %% action.
846    Msg = {inconsistent_database, Context, Node},
847    mnesia_lib:report_system_event(Msg),
848    report_inconsistency(Replies, Context, inconsistent_database);
849report_inconsistency([{false, _Node} | Replies], Context, Status) ->
850    report_inconsistency(Replies, Context, Status);
851report_inconsistency([{badrpc, _Reason} | Replies], Context, Status) ->
852    report_inconsistency(Replies, Context, Status);
853report_inconsistency([], _Context, Status) ->
854    Status.
855
856remote_node_status(Node, Status, State) ->
857    {ok, Nodes} = mnesia_schema:read_nodes(),
858    case lists:member(Node, Nodes) of
859	true ->
860	    update_node_status({Node, Status}, State);
861	_ ->
862	    State
863    end.
864
865update_node_status({Node, down}, State = #state{remote_node_status = RNodeS}) ->
866    RNodeS2 = lists:ukeymerge(1, [{Node, down}], RNodeS),
867    State#state{remote_node_status = RNodeS2};
868update_node_status({Node, up}, State = #state{remote_node_status = RNodeS}) ->
869    case lists:keyfind(Node, 1, RNodeS) of
870	{Node, down} ->
871	    RNodeS2 = lists:ukeymerge(1, [{Node, up}], RNodeS),
872	    State#state{remote_node_status = RNodeS2};
873	_ ->
874	    State
875    end.
876
877check_raise_conditon_nodeup(Node, State = #state{remote_node_status = RNodeS}) ->
878    case lists:keyfind(Node, 1, RNodeS) of
879	{Node, up} ->
880	    self() ! {check_nodeup, Node};
881	_ ->
882	    ignore
883    end,
884    State#state{remote_node_status = lists:keydelete(Node, 1, RNodeS)}.
885
886check_mnesia_down(Node, State = #state{remote_node_status = RNodeS}) ->
887    %% Check if the network has been partitioned
888    %% due to communication failure.
889
890    HasDown   = mnesia_recover:has_mnesia_down(Node),
891    ImRunning = mnesia_lib:is_running(),
892    if
893	%% If I'm not running the test will be made later.
894	HasDown == true, ImRunning == yes ->
895	    spawn_link(?MODULE, detect_partitioned_network, [self(), Node]),
896	    State#state{remote_node_status = lists:keydelete(Node, 1, RNodeS)};
897	true ->
898	    State
899    end.
900