~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/mnesia/mnesia_monitor.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

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