~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_lib.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_lib.erl,v 1.3 2009/07/01 15:45:40 kostis Exp $
 
17
%%
 
18
%% This module contains all sorts of various which doesn't fit
 
19
%% anywhere else. Basically everything is exported.
 
20
 
 
21
-module(mnesia_lib).
 
22
 
 
23
-include("mnesia.hrl").
 
24
-include_lib("kernel/include/file.hrl").
 
25
 
 
26
-export([core_file/0]).
 
27
 
 
28
-export([
 
29
         active_tables/0,
 
30
         add/2,
 
31
         add_list/2,
 
32
         all_nodes/0,
 
33
%%       catch_val/1,
 
34
         cleanup_tmp_files/1,    
 
35
         copy_file/2,
 
36
         copy_holders/1,
 
37
         coredump/0,
 
38
         coredump/1,
 
39
         create_counter/1,
 
40
         cs_to_nodes/1,
 
41
         cs_to_storage_type/2,
 
42
         dets_to_ets/6,
 
43
         db_chunk/2,
 
44
         db_init_chunk/1,
 
45
         db_init_chunk/2,
 
46
         db_init_chunk/3,
 
47
         db_erase/2,
 
48
         db_erase/3,
 
49
         db_erase_tab/1,
 
50
         db_erase_tab/2,
 
51
         db_first/1,
 
52
         db_first/2,
 
53
         db_last/1,
 
54
         db_last/2,
 
55
         db_fixtable/3,
 
56
         db_get/2,
 
57
         db_get/3,
 
58
         db_match_erase/2,
 
59
         db_match_erase/3,
 
60
         db_match_object/2,
 
61
         db_match_object/3,
 
62
         db_next_key/2,
 
63
         db_next_key/3,
 
64
         db_prev_key/2,
 
65
         db_prev_key/3,
 
66
         db_put/2,
 
67
         db_put/3,
 
68
         db_select/2,    
 
69
         db_select/3,
 
70
         db_slot/2,
 
71
         db_slot/3,
 
72
         db_update_counter/3,
 
73
         db_update_counter/4,
 
74
         dbg_out/2,
 
75
         del/2,
 
76
         dets_sync_close/1,
 
77
         dets_sync_open/2,
 
78
         dets_sync_open/3,
 
79
         dir/0,
 
80
         dir/1,
 
81
         dir_info/0,
 
82
         dirty_rpc_error_tag/1,
 
83
         dist_coredump/0,
 
84
         disk_type/1,
 
85
         disk_type/2,    
 
86
         elems/2,
 
87
         ensure_loaded/1,
 
88
         error/2,
 
89
         error_desc/1,
 
90
         etype/1,
 
91
         exists/1,
 
92
         fatal/2,
 
93
         get_node_number/0,
 
94
         fix_error/1,
 
95
         important/2,
 
96
         incr_counter/1,
 
97
         incr_counter/2,
 
98
         intersect/2,
 
99
         is_running/0,
 
100
         is_running/1,
 
101
         is_running_remote/0,
 
102
         is_string/1,
 
103
         key_search_delete/3,
 
104
         key_search_all/3,
 
105
         last_error/0,
 
106
         local_active_tables/0,
 
107
         lock_table/1,
 
108
         mkcore/1,
 
109
         not_active_here/1,
 
110
         other_val/2,
 
111
         pad_name/3,
 
112
         random_time/2,
 
113
         read_counter/1,
 
114
         readable_indecies/1,
 
115
         remote_copy_holders/1,
 
116
         report_fatal/2,
 
117
         report_system_event/1,
 
118
         running_nodes/0,
 
119
         running_nodes/1,
 
120
         schema_cs_to_storage_type/2,
 
121
         search_delete/2,
 
122
         set/2,
 
123
         set_counter/2,
 
124
         set_local_content_whereabouts/1,
 
125
         set_remote_where_to_read/1,
 
126
         set_remote_where_to_read/2,
 
127
         show/1,
 
128
         show/2,
 
129
         sort_commit/1,
 
130
         storage_type_at_node/2,
 
131
         swap_tmp_files/1,
 
132
         tab2dat/1,
 
133
         tab2dmp/1,
 
134
         tab2tmp/1,
 
135
         tab2dcd/1,
 
136
         tab2dcl/1,
 
137
         to_list/1,
 
138
         union/2,
 
139
         uniq/1,
 
140
         unlock_table/1,
 
141
         unset/1,
 
142
         update_counter/2,
 
143
         val/1,
 
144
         vcore/0,
 
145
         vcore/1,
 
146
         verbose/2,
 
147
         view/0,
 
148
         view/1,
 
149
         view/2,
 
150
         warning/2,
 
151
 
 
152
         is_debug_compiled/0,
 
153
         activate_debug_fun/5,
 
154
         deactivate_debug_fun/3,
 
155
         eval_debug_fun/4,
 
156
         scratch_debug_fun/0
 
157
        ]).
 
158
 
 
159
 
 
160
search_delete(Obj, List) ->
 
161
    search_delete(Obj, List, [], none).
 
162
search_delete(Obj, [Obj|Tail], Ack, _Res) ->
 
163
    search_delete(Obj, Tail, Ack, Obj);
 
164
search_delete(Obj, [H|T], Ack, Res) ->
 
165
    search_delete(Obj, T, [H|Ack], Res);
 
166
search_delete(_, [], Ack, Res) ->
 
167
    {Res, Ack}.
 
168
 
 
169
key_search_delete(Key, Pos, TupleList) ->
 
170
    key_search_delete(Key, Pos, TupleList, none, []).
 
171
key_search_delete(Key, Pos, [H|T], _Obj, Ack) when element(Pos, H) == Key ->
 
172
    key_search_delete(Key, Pos, T, H, Ack);
 
173
key_search_delete(Key, Pos, [H|T], Obj, Ack) ->
 
174
    key_search_delete(Key, Pos, T, Obj, [H|Ack]);
 
175
key_search_delete(_, _, [], Obj, Ack) ->
 
176
    {Obj, Ack}.
 
177
 
 
178
key_search_all(Key, Pos, TupleList) -> 
 
179
    key_search_all(Key, Pos, TupleList, []).
 
180
key_search_all(Key, N, [H|T], Ack) when element(N, H) == Key ->
 
181
    key_search_all(Key, N, T, [H|Ack]);
 
182
key_search_all(Key, N, [_|T], Ack) ->
 
183
    key_search_all(Key, N, T, Ack);
 
184
key_search_all(_, _, [], Ack) -> Ack.
 
185
 
 
186
intersect(L1, L2) ->
 
187
    L2 -- (L2 -- L1).
 
188
 
 
189
elems(I, [H|T]) ->
 
190
    [element(I, H) | elems(I, T)];
 
191
elems(_, []) ->
 
192
    [].
 
193
 
 
194
%%  sort_commit see to that checkpoint info is always first in 
 
195
%%  commit_work structure the other info don't need to be sorted.
 
196
sort_commit(List) ->
 
197
    sort_commit2(List, []).
 
198
 
 
199
sort_commit2([{checkpoints, ChkpL}| Rest], Acc) ->
 
200
    [{checkpoints, ChkpL}| Rest] ++ Acc;
 
201
sort_commit2([H | R], Acc) ->
 
202
    sort_commit2(R, [H | Acc]);
 
203
sort_commit2([], Acc) -> Acc.
 
204
    
 
205
is_string([H|T]) ->
 
206
    if
 
207
        0 =< H, H < 256, integer(H)  -> is_string(T);
 
208
        true -> false
 
209
    end;
 
210
is_string([]) -> true.
 
211
 
 
212
%%%
 
213
 
 
214
union([H|L1], L2) ->
 
215
    case lists:member(H, L2) of
 
216
        true -> union(L1, L2);
 
217
        false -> [H | union(L1, L2)]
 
218
    end;
 
219
union([], L2) -> L2.
 
220
 
 
221
uniq([]) ->
 
222
    [];
 
223
uniq(List) ->
 
224
    [H|T] = lists:sort(List),
 
225
    uniq1(H, T, []).
 
226
 
 
227
uniq1(H, [H|R], Ack) ->
 
228
    uniq1(H, R, Ack);
 
229
uniq1(Old, [H|R], Ack) ->
 
230
    uniq1(H, R, [Old|Ack]);
 
231
uniq1(Old, [], Ack) ->
 
232
    [Old| Ack].
 
233
 
 
234
to_list(X) when list(X) -> X;
 
235
to_list(X) -> atom_to_list(X).
 
236
 
 
237
all_nodes() ->
 
238
    Ns = mnesia:system_info(db_nodes) ++
 
239
        mnesia:system_info(extra_db_nodes),
 
240
    mnesia_lib:uniq(Ns).
 
241
 
 
242
running_nodes() ->
 
243
    running_nodes(all_nodes()).
 
244
 
 
245
running_nodes(Ns) ->
 
246
    {Replies, _BadNs} = rpc:multicall(Ns, ?MODULE, is_running_remote, []),
 
247
    [N || {GoodState, N} <- Replies, GoodState == true].
 
248
 
 
249
is_running_remote() ->
 
250
    IsRunning = is_running(),
 
251
    {IsRunning == yes, node()}.
 
252
 
 
253
is_running(Node) when atom(Node) ->
 
254
    case rpc:call(Node, ?MODULE, is_running, []) of
 
255
        {badrpc, _} -> no;
 
256
        X -> X
 
257
    end.
 
258
 
 
259
is_running() ->
 
260
    case ?catch_val(mnesia_status) of
 
261
        {'EXIT', _} -> no;
 
262
        running -> yes;
 
263
        starting -> starting;
 
264
        stopping -> stopping
 
265
    end.
 
266
 
 
267
show(X) ->
 
268
    show(X, []).
 
269
show(F, A) ->
 
270
    io:format(user, F, A).
 
271
 
 
272
 
 
273
pad_name([Char | Chars], Len, Tail) ->
 
274
    [Char | pad_name(Chars, Len - 1, Tail)];
 
275
pad_name([], Len, Tail) when Len =< 0 ->
 
276
    Tail;
 
277
pad_name([], Len, Tail) ->
 
278
    [$ | pad_name([], Len - 1, Tail)].
 
279
    
 
280
%% Some utility functions .....
 
281
active_here(Tab) ->
 
282
    case val({Tab, where_to_read}) of
 
283
        Node when Node == node() -> true;
 
284
        _ -> false
 
285
    end.
 
286
 
 
287
not_active_here(Tab) ->
 
288
    not active_here(Tab).
 
289
 
 
290
exists(Fname) ->
 
291
    case file:open(Fname, [raw,read]) of
 
292
        {ok, F} ->file:close(F), true;
 
293
        _ -> false
 
294
    end.
 
295
 
 
296
dir() -> mnesia_monitor:get_env(dir).
 
297
 
 
298
dir(Fname) ->
 
299
    filename:join([dir(), to_list(Fname)]).
 
300
 
 
301
tab2dat(Tab) ->  %% DETS files 
 
302
    dir(lists:concat([Tab, ".DAT"])).
 
303
 
 
304
tab2tmp(Tab) ->
 
305
    dir(lists:concat([Tab, ".TMP"])).
 
306
 
 
307
tab2dmp(Tab) ->  %% Dumped ets tables
 
308
    dir(lists:concat([Tab, ".DMP"])).
 
309
 
 
310
tab2dcd(Tab) ->  %% Disc copies data
 
311
    dir(lists:concat([Tab, ".DCD"])).
 
312
 
 
313
tab2dcl(Tab) ->  %% Disc copies log
 
314
    dir(lists:concat([Tab, ".DCL"])).
 
315
 
 
316
storage_type_at_node(Node, Tab) ->
 
317
    search_key(Node, [{disc_copies, val({Tab, disc_copies})},
 
318
                      {ram_copies, val({Tab, ram_copies})},
 
319
                      {disc_only_copies, val({Tab, disc_only_copies})}]).
 
320
 
 
321
cs_to_storage_type(Node, Cs) ->
 
322
    search_key(Node, [{disc_copies, Cs#cstruct.disc_copies},
 
323
                      {ram_copies, Cs#cstruct.ram_copies},
 
324
                      {disc_only_copies, Cs#cstruct.disc_only_copies}]).
 
325
 
 
326
schema_cs_to_storage_type(Node, Cs) ->
 
327
    case cs_to_storage_type(Node, Cs) of
 
328
        unknown when Cs#cstruct.name == schema -> ram_copies;
 
329
        Other -> Other
 
330
    end.
 
331
 
 
332
 
 
333
search_key(Key, [{Val, List} | Tail]) ->
 
334
    case lists:member(Key, List) of
 
335
        true -> Val;
 
336
        false -> search_key(Key, Tail)
 
337
    end;
 
338
search_key(_Key, []) ->
 
339
    unknown.
 
340
 
 
341
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
342
%% ops, we've got some global variables here :-)
 
343
 
 
344
%% They are
 
345
%%
 
346
%%   {Tab, setorbag}, -> set | bag
 
347
%%   {Tab, storage_type}       -> disc_copies |ram_copies | unknown (**)
 
348
%%   {Tab, disc_copies}        -> node list  (from schema)
 
349
%%   {Tab, ram_copies}, -> node list  (from schema)
 
350
%%   {Tab, arity}, -> number
 
351
%%   {Tab, attributes}, -> atom list
 
352
%%   {Tab, wild_pattern}, -> record tuple with '_'s
 
353
%%   {Tab, {index, Pos}}       -> ets table
 
354
%%   {Tab, index}              -> integer list
 
355
%%   {Tab, cstruct}            -> cstruct  structure
 
356
%%
 
357
 
 
358
%%   The following fields are dynamic according to the
 
359
%%   the current node/table situation
 
360
 
 
361
%%   {Tab, where_to_write}      -> node list
 
362
%%   {Tab, where_to_read}       -> node | nowhere
 
363
%%
 
364
%%   {schema, tables}                    -> tab list
 
365
%%   {schema, local_tables}              -> tab list  (**)
 
366
%%
 
367
%%   {current, db_nodes}                  -> node list
 
368
%%
 
369
%%   dir                                  -> directory path (**)
 
370
%%   mnesia_status                        -> status | running | stopping (**)
 
371
%%   (**) ==   (Different on all nodes)
 
372
%%
 
373
 
 
374
val(Var) ->
 
375
    case ?catch_val(Var) of
 
376
        {'EXIT', _ReASoN_} -> mnesia_lib:other_val(Var, _ReASoN_); 
 
377
        _VaLuE_ -> _VaLuE_ 
 
378
    end.
 
379
 
 
380
set(Var, Val) ->
 
381
    ?ets_insert(mnesia_gvar, {Var, Val}).
 
382
 
 
383
unset(Var) ->
 
384
    ?ets_delete(mnesia_gvar, Var).
 
385
 
 
386
other_val(Var, Other) ->
 
387
    case Var of
 
388
        {_, where_to_read} -> nowhere;
 
389
        {_, where_to_write} -> [];
 
390
        {_, active_replicas} -> [];
 
391
        _ ->
 
392
            pr_other(Var, Other)
 
393
    end.
 
394
 
 
395
pr_other(Var, Other) ->
 
396
    Why = 
 
397
        case is_running() of
 
398
            no -> {node_not_running, node()};
 
399
            _ -> {no_exists, Var}
 
400
        end,
 
401
    verbose("~p (~p) val(mnesia_gvar, ~w) -> ~p ~p ~n",
 
402
            [self(), process_info(self(), registered_name),
 
403
             Var, Other, Why]),
 
404
    case Other of
 
405
        {badarg, [{ets, lookup_element, _}|_]} ->
 
406
            exit(Why);
 
407
        _ ->
 
408
            erlang:error(Why)
 
409
    end.
 
410
 
 
411
%% Some functions for list valued variables
 
412
add(Var, Val) ->
 
413
    L = val(Var),
 
414
    set(Var, [Val | lists:delete(Val, L)]).
 
415
 
 
416
add_list(Var, List) ->
 
417
    L = val(Var),
 
418
    set(Var, union(L, List)).
 
419
 
 
420
del(Var, Val) ->
 
421
    L = val(Var),
 
422
    set(Var, lists:delete(Val, L)).
 
423
 
 
424
%% This function is needed due to the fact
 
425
%% that the application_controller enters
 
426
%% a deadlock now and then. ac is implemented
 
427
%% as a rather naive server.
 
428
ensure_loaded(Appl) ->
 
429
    case application_controller:get_loaded(Appl) of
 
430
        {true, _} -> 
 
431
            ok;
 
432
        false ->
 
433
            case application:load(Appl) of
 
434
                ok ->
 
435
                    ok;
 
436
                {error, {already_loaded, Appl}} ->
 
437
                    ok;
 
438
                {error, Reason} ->
 
439
                    {error, {application_load_error, Reason}}
 
440
            end
 
441
    end.
 
442
 
 
443
local_active_tables() ->
 
444
    Tabs = val({schema, local_tables}),
 
445
    lists:zf(fun(Tab) -> active_here(Tab) end, Tabs).
 
446
 
 
447
active_tables() ->
 
448
    Tabs = val({schema, tables}),
 
449
    F = fun(Tab) ->
 
450
                case val({Tab, where_to_read}) of
 
451
                    nowhere -> false;
 
452
                    _ -> {true, Tab}
 
453
                end
 
454
        end,
 
455
    lists:zf(F, Tabs).
 
456
 
 
457
etype(X) when integer(X) -> integer;
 
458
etype([]) -> nil;
 
459
etype(X) when list(X) -> list;
 
460
etype(X) when tuple(X) -> tuple;
 
461
etype(X) when atom(X) -> atom;
 
462
etype(_) -> othertype.
 
463
 
 
464
remote_copy_holders(Cs) ->
 
465
    copy_holders(Cs) -- [node()].
 
466
 
 
467
copy_holders(Cs) when Cs#cstruct.local_content == false ->
 
468
    cs_to_nodes(Cs);
 
469
copy_holders(Cs) when Cs#cstruct.local_content == true ->
 
470
    case lists:member(node(), cs_to_nodes(Cs)) of
 
471
        true -> [node()];
 
472
        false -> []
 
473
    end.
 
474
 
 
475
 
 
476
set_remote_where_to_read(Tab) ->
 
477
    set_remote_where_to_read(Tab, []).
 
478
 
 
479
set_remote_where_to_read(Tab, Ignore) ->
 
480
    Active = val({Tab, active_replicas}),
 
481
    Valid = 
 
482
        case mnesia_recover:get_master_nodes(Tab) of
 
483
            [] ->  Active;
 
484
            Masters -> mnesia_lib:intersect(Masters, Active)
 
485
        end,    
 
486
    Available = mnesia_lib:intersect(val({current, db_nodes}), Valid -- Ignore),    
 
487
    DiscOnlyC = val({Tab, disc_only_copies}),
 
488
    Prefered  = Available -- DiscOnlyC,
 
489
    if
 
490
        Prefered /= [] ->
 
491
            set({Tab, where_to_read}, hd(Prefered));
 
492
        Available /= [] ->
 
493
            set({Tab, where_to_read}, hd(Available));
 
494
        true ->
 
495
            set({Tab, where_to_read}, nowhere)
 
496
    end.
 
497
 
 
498
%%% Local only
 
499
set_local_content_whereabouts(Tab) ->
 
500
    add({schema, local_tables}, Tab),
 
501
    add({Tab, active_replicas}, node()),
 
502
    set({Tab, where_to_write}, [node()]),
 
503
    set({Tab, where_to_read}, node()).
 
504
 
 
505
%%% counter routines
 
506
 
 
507
create_counter(Name) ->
 
508
    set_counter(Name, 0).
 
509
 
 
510
set_counter(Name, Val) ->
 
511
    ?ets_insert(mnesia_gvar, {Name, Val}).
 
512
 
 
513
incr_counter(Name) ->
 
514
    ?ets_update_counter(mnesia_gvar, Name, 1).
 
515
 
 
516
incr_counter(Name, I) ->
 
517
    ?ets_update_counter(mnesia_gvar, Name, I).
 
518
 
 
519
update_counter(Name, Val) ->
 
520
    ?ets_update_counter(mnesia_gvar, Name, Val).
 
521
 
 
522
read_counter(Name) ->
 
523
    ?ets_lookup_element(mnesia_gvar, Name, 2).
 
524
 
 
525
cs_to_nodes(Cs) ->
 
526
    Cs#cstruct.disc_only_copies ++
 
527
    Cs#cstruct.disc_copies ++
 
528
    Cs#cstruct.ram_copies.
 
529
 
 
530
dist_coredump() ->
 
531
    dist_coredump(all_nodes()).
 
532
dist_coredump(Ns) ->
 
533
    {Replies, _} = rpc:multicall(Ns, ?MODULE, coredump, []),
 
534
    Replies.
 
535
 
 
536
coredump() ->
 
537
    coredump({crashinfo, {"user initiated~n", []}}).
 
538
coredump(CrashInfo) ->
 
539
    Core = mkcore(CrashInfo),
 
540
    Out = core_file(),
 
541
    important("Writing Mnesia core to file: ~p...~p~n", [Out, CrashInfo]),
 
542
    file:write_file(Out, Core),
 
543
    Out.
 
544
 
 
545
core_file() ->
 
546
    Integers = tuple_to_list(date()) ++ tuple_to_list(time()),
 
547
    Fun = fun(I) when I < 10 -> ["_0", I];
 
548
             (I) -> ["_", I]
 
549
          end,
 
550
    List = lists:append([Fun(I) || I <- Integers]),
 
551
    filename:absname(lists:concat(["MnesiaCore.", node()] ++ List)).
 
552
 
 
553
mkcore(CrashInfo) ->
 
554
%   dbg_out("Making a Mnesia core dump...~p~n", [CrashInfo]),
 
555
    Nodes = [node() |nodes()],
 
556
    TidLocks = (catch ets:tab2list(mnesia_tid_locks)),
 
557
    Core = [
 
558
            CrashInfo,
 
559
            {time, {date(), time()}},
 
560
            {self, catch process_info(self())},
 
561
            {nodes, catch rpc:multicall(Nodes, ?MODULE, get_node_number, [])},
 
562
            {applications, catch lists:sort(application:loaded_applications())},
 
563
            {flags, catch init:get_arguments()},
 
564
            {code_path, catch code:get_path()},
 
565
            {code_loaded, catch lists:sort(code:all_loaded())},
 
566
            {etsinfo, catch ets_info(ets:all())},
 
567
 
 
568
            {version, catch mnesia:system_info(version)},
 
569
            {schema, catch ets:tab2list(schema)},
 
570
            {gvar, catch ets:tab2list(mnesia_gvar)},
 
571
            {master_nodes, catch mnesia_recover:get_master_node_info()},
 
572
 
 
573
            {processes, catch procs()},
 
574
            {relatives, catch relatives()},
 
575
            {workers, catch workers(mnesia_controller:get_workers(2000))},
 
576
            {locking_procs, catch locking_procs(TidLocks)},
 
577
 
 
578
            {held_locks, catch mnesia:system_info(held_locks)},
 
579
            {tid_locks, TidLocks},
 
580
            {lock_queue, catch mnesia:system_info(lock_queue)},
 
581
            {load_info, catch mnesia_controller:get_info(2000)},
 
582
            {trans_info, catch mnesia_tm:get_info(2000)},
 
583
                    
 
584
            {schema_file, catch file:read_file(tab2dat(schema))},
 
585
            {dir_info, catch dir_info()},
 
586
            {logfile, catch {ok, read_log_files()}}
 
587
           ],
 
588
    term_to_binary(Core).
 
589
 
 
590
procs() ->
 
591
    Fun = fun(P) -> {P, (catch lists:zf(fun proc_info/1, process_info(P)))} end,
 
592
    lists:map(Fun, processes()).
 
593
 
 
594
proc_info({registered_name, Val}) -> {true, Val};
 
595
proc_info({message_queue_len, Val}) -> {true, Val};
 
596
proc_info({status, Val}) -> {true, Val};
 
597
proc_info({current_function, Val}) -> {true, Val};
 
598
proc_info(_) -> false.
 
599
 
 
600
get_node_number() ->
 
601
    {node(), self()}.
 
602
 
 
603
read_log_files() ->
 
604
    [{F, catch file:read_file(F)} || F <- mnesia_log:log_files()].
 
605
 
 
606
dir_info() ->
 
607
    {ok, Cwd} = file:get_cwd(),
 
608
    Dir = dir(),
 
609
    [{cwd, Cwd, file:read_file_info(Cwd)},
 
610
     {mnesia_dir, Dir, file:read_file_info(Dir)}] ++
 
611
    case file:list_dir(Dir) of
 
612
        {ok, Files} ->
 
613
            [{mnesia_file, F, catch file:read_file_info(dir(F))} || F <- Files];
 
614
        Other ->
 
615
            [Other]
 
616
    end.
 
617
 
 
618
ets_info([H|T]) ->
 
619
    [{table, H, ets:info(H)} | ets_info(T)];
 
620
ets_info([]) -> [].
 
621
 
 
622
relatives() ->
 
623
    Info = fun(Name) ->
 
624
                   case whereis(Name) of
 
625
                       undefined -> false;
 
626
                       Pid -> {true, {Name, Pid, catch process_info(Pid)}}
 
627
                   end
 
628
           end,
 
629
    lists:zf(Info, mnesia:ms()).
 
630
 
 
631
workers({workers, Loader, Sender, Dumper}) ->
 
632
    Info = fun({Name, Pid}) ->
 
633
                   case Pid of
 
634
                       undefined -> false;
 
635
                       Pid -> {true, {Name, Pid, catch process_info(Pid)}}
 
636
                   end
 
637
           end,
 
638
    lists:zf(Info, [{loader, Loader}, {sender, Sender}, {dumper, Dumper}]).
 
639
 
 
640
locking_procs(LockList) when list(LockList) ->
 
641
    Tids = [element(1, Lock) || Lock <- LockList],
 
642
    UT = uniq(Tids),    
 
643
    Info = fun(Tid) ->
 
644
                   Pid = Tid#tid.pid,
 
645
                   case node(Pid) == node() of
 
646
                       true -> 
 
647
                           {true, {Pid, catch process_info(Pid)}};
 
648
                       _ ->
 
649
                           false
 
650
                   end
 
651
           end,
 
652
    lists:zf(Info, UT).
 
653
 
 
654
view() ->
 
655
    Bin = mkcore({crashinfo, {"view only~n", []}}),
 
656
    vcore(Bin).
 
657
 
 
658
%% Displays a Mnesia file on the tty. The file may be repaired.
 
659
view(File) ->
 
660
    case suffix([".DAT", ".RET", ".DMP", ".TMP"], File) of
 
661
        true ->
 
662
            view(File, dat);
 
663
        false ->
 
664
            case suffix([".LOG", ".BUP", ".ETS"], File) of
 
665
                true ->
 
666
                    view(File, log);
 
667
                false ->
 
668
                    case lists:prefix("MnesiaCore.", File) of
 
669
                        true ->
 
670
                            view(File, core);
 
671
                        false ->
 
672
                            {error, "Unknown file name"}
 
673
                    end
 
674
            end
 
675
    end.
 
676
 
 
677
view(File, dat) ->
 
678
    dets:view(File);
 
679
view(File, log) ->
 
680
    mnesia_log:view(File);
 
681
view(File, core) ->
 
682
    vcore(File).
 
683
 
 
684
suffix(Suffixes, File) ->
 
685
    Fun = fun(S) -> lists:suffix(S, File) end,
 
686
    lists:any(Fun, Suffixes).
 
687
 
 
688
%% View a core file
 
689
 
 
690
vcore() ->
 
691
    Prefix = lists:concat(["MnesiaCore.", node()]),
 
692
    Filter = fun(F) -> lists:prefix(Prefix, F) end,
 
693
    {ok, Cwd} = file:get_cwd(),
 
694
    case file:list_dir(Cwd) of
 
695
        {ok, Files}->
 
696
            CoreFiles = lists:sort(lists:zf(Filter, Files)),
 
697
            show("Mnesia core files: ~p~n", [CoreFiles]),
 
698
            vcore(lists:last(CoreFiles));
 
699
        Error ->
 
700
            Error
 
701
    end.
 
702
 
 
703
vcore(Bin) when binary(Bin) ->
 
704
    Core = binary_to_term(Bin),
 
705
    Fun = fun({Item, Info}) ->
 
706
                  show("***** ~p *****~n", [Item]),
 
707
                  case catch vcore_elem({Item, Info}) of
 
708
                      {'EXIT', Reason} ->
 
709
                          show("{'EXIT', ~p}~n", [Reason]);
 
710
                      _ -> ok
 
711
                  end
 
712
          end,
 
713
    lists:foreach(Fun, Core);
 
714
    
 
715
vcore(File) ->
 
716
    show("~n***** Mnesia core: ~p *****~n", [File]),
 
717
    case file:read_file(File) of
 
718
        {ok, Bin} ->
 
719
            vcore(Bin);
 
720
        _ ->
 
721
            nocore
 
722
    end.
 
723
 
 
724
vcore_elem({schema_file, {ok, B}}) ->
 
725
    Fname = "/tmp/schema.DAT",
 
726
    file:write_file(Fname, B),
 
727
    dets:view(Fname),
 
728
    file:delete(Fname);
 
729
 
 
730
vcore_elem({logfile, {ok, BinList}}) ->
 
731
    Fun = fun({F, Info}) ->
 
732
                  show("----- logfile: ~p -----~n", [F]),
 
733
                  case Info of
 
734
                      {ok, B} ->
 
735
                          Fname = "/tmp/mnesia_vcore_elem.TMP",
 
736
                          file:write_file(Fname, B),
 
737
                          mnesia_log:view(Fname),
 
738
                          file:delete(Fname);
 
739
                      _ ->
 
740
                          show("~p~n", [Info])
 
741
                  end
 
742
          end,
 
743
    lists:foreach(Fun, BinList);
 
744
 
 
745
vcore_elem({crashinfo, {Format, Args}}) ->
 
746
    show(Format, Args);
 
747
vcore_elem({gvar, L}) ->
 
748
    show("~p~n", [lists:sort(L)]);
 
749
vcore_elem({transactions, Info}) ->
 
750
    mnesia_tm:display_info(user, Info);
 
751
 
 
752
vcore_elem({_Item, Info}) ->
 
753
    show("~p~n", [Info]).
 
754
 
 
755
fix_error(X) ->
 
756
    set(last_error, X), %% for debugabililty
 
757
    case X of
 
758
        {aborted, Reason} -> Reason;
 
759
        {abort, Reason} -> Reason;
 
760
        Y when atom(Y) -> Y;
 
761
        {'EXIT', {_Reason, {Mod, _, _}}} when atom(Mod) ->
 
762
            save(X),
 
763
            case atom_to_list(Mod) of
 
764
                [$m, $n, $e|_] -> badarg;
 
765
                _ -> X
 
766
            end;
 
767
        _ -> X
 
768
    end.
 
769
 
 
770
last_error() ->
 
771
    val(last_error).
 
772
 
 
773
%% The following is a list of possible mnesia errors and what they
 
774
%% actually mean
 
775
 
 
776
error_desc(nested_transaction) -> "Nested transactions are not allowed";
 
777
error_desc(badarg) -> "Bad or invalid argument, possibly bad type";
 
778
error_desc(no_transaction) -> "Operation not allowed outside transactions";
 
779
error_desc(combine_error)  -> "Table options were ilegally combined";
 
780
error_desc(bad_index)  -> "Index already exists or was out of bounds";
 
781
error_desc(already_exists) -> "Some schema option we try to set is already on";
 
782
error_desc(index_exists)-> "Some ops can not  be performed on tabs with index";
 
783
error_desc(no_exists)-> "Tried to perform op on non-existing (non alive) item";
 
784
error_desc(system_limit) -> "Some system_limit was exhausted";
 
785
error_desc(mnesia_down) -> "A transaction involving objects at some remote "
 
786
                           "node which died while transaction was executing"
 
787
                           "*and* object(s) are no longer available elsewhere"
 
788
                           "in the network";
 
789
error_desc(not_a_db_node) -> "A node which is non existant in "
 
790
                              "the schema was mentioned";
 
791
error_desc(bad_type)            -> "Bad type on some provided arguments";
 
792
error_desc(node_not_running)    -> "Node not running";
 
793
error_desc(truncated_binary_file) -> "Truncated binary in file";
 
794
error_desc(active)     -> "Some delete ops require that "
 
795
                           "all active objects are removed";
 
796
error_desc(illegal) -> "Operation not supported on object";
 
797
error_desc({'EXIT', Reason}) ->
 
798
    error_desc(Reason);
 
799
error_desc({error, Reason}) ->
 
800
    error_desc(Reason);
 
801
error_desc({aborted, Reason}) ->
 
802
    error_desc(Reason);
 
803
error_desc(Reason) when tuple(Reason), size(Reason) > 0 ->
 
804
    setelement(1, Reason, error_desc(element(1, Reason)));
 
805
error_desc(Reason) ->
 
806
    Reason.
 
807
 
 
808
dirty_rpc_error_tag(Reason) ->
 
809
    case Reason of
 
810
        {'EXIT', _} -> badarg;
 
811
        no_variable -> badarg;
 
812
        _           -> no_exists
 
813
    end.
 
814
 
 
815
fatal(Format, Args) ->
 
816
    catch set(mnesia_status, stopping),
 
817
    Core = mkcore({crashinfo, {Format, Args}}),
 
818
    report_fatal(Format, Args, Core),
 
819
    timer:sleep(10000), % Enough to write the core dump to disc?
 
820
    mnesia:lkill(),
 
821
    exit(fatal).
 
822
 
 
823
report_fatal(Format, Args) ->
 
824
    report_fatal(Format, Args, nocore).
 
825
 
 
826
report_fatal(Format, Args, Core) ->
 
827
    report_system_event({mnesia_fatal, Format, Args, Core}),
 
828
    catch exit(whereis(mnesia_monitor), fatal).
 
829
 
 
830
%% We sleep longer and longer the more we try
 
831
%% Made some testing and came up with the following constants
 
832
random_time(Retries, _Counter0) ->    
 
833
%    UpperLimit = 2000,
 
834
%    MaxIntv = trunc(UpperLimit * (1-(4/((Retries*Retries)+4)))),
 
835
    UpperLimit = 500,
 
836
    Dup = Retries * Retries,
 
837
    MaxIntv = trunc(UpperLimit * (1-(50/((Dup)+50)))),
 
838
    
 
839
    case get(random_seed) of
 
840
        undefined ->
 
841
            {X, Y, Z} = erlang:now(), %% time()
 
842
            random:seed(X, Y, Z),
 
843
            Time = Dup + random:uniform(MaxIntv),
 
844
            %%      dbg_out("---random_test rs ~w max ~w val ~w---~n", [Retries, MaxIntv, Time]),
 
845
            Time;
 
846
        _ ->
 
847
            Time = Dup + random:uniform(MaxIntv),
 
848
            %%      dbg_out("---random_test rs ~w max ~w val ~w---~n", [Retries, MaxIntv, Time]),
 
849
            Time            
 
850
    end.
 
851
 
 
852
report_system_event(Event0) ->
 
853
    Event = {mnesia_system_event, Event0},
 
854
    report_system_event(catch_notify(Event), Event),
 
855
    case ?catch_val(subscribers) of
 
856
        {'EXIT', _} -> ignore;
 
857
        Pids -> lists:foreach(fun(Pid) -> Pid ! Event end, Pids)
 
858
    end,
 
859
    ok.
 
860
 
 
861
catch_notify(Event) ->
 
862
    case whereis(mnesia_event) of
 
863
        undefined ->
 
864
            {'EXIT', {badarg, {mnesia_event, Event}}};
 
865
        Pid ->
 
866
            gen_event:notify(Pid, Event)
 
867
    end.
 
868
 
 
869
report_system_event({'EXIT', Reason}, Event) ->
 
870
    Mod = mnesia_monitor:get_env(event_module),
 
871
    case mnesia_sup:start_event() of
 
872
        {ok, Pid} ->
 
873
            link(Pid),
 
874
            gen_event:call(mnesia_event, Mod, Event, infinity),
 
875
            unlink(Pid),
 
876
 
 
877
            %% We get an exit signal if server dies
 
878
            receive
 
879
                {'EXIT', Pid, _Reason} ->
 
880
                    {error, {node_not_running, node()}}
 
881
            after 0 ->
 
882
                    gen_event:stop(mnesia_event),
 
883
                    ok
 
884
            end;
 
885
 
 
886
        Error ->
 
887
            Msg = "Mnesia(~p): Cannot report event ~p: ~p (~p)~n",
 
888
            error_logger:format(Msg, [node(), Event, Reason, Error])
 
889
    end;
 
890
report_system_event(_Res, _Event) ->
 
891
    ignore.
 
892
 
 
893
%% important messages are reported regardless of debug level
 
894
important(Format, Args) ->
 
895
    save({Format, Args}),
 
896
    report_system_event({mnesia_info, Format, Args}).
 
897
 
 
898
%% Warning messages are reported regardless of debug level
 
899
warning(Format, Args) ->
 
900
    save({Format, Args}),
 
901
    report_system_event({mnesia_warning, Format, Args}).
 
902
 
 
903
%% error messages are reported regardless of debug level
 
904
error(Format, Args) ->
 
905
    save({Format, Args}),
 
906
    report_system_event({mnesia_error, Format, Args}).
 
907
 
 
908
%% verbose messages are reported if debug level == debug or verbose
 
909
verbose(Format, Args) ->
 
910
    case mnesia_monitor:get_env(debug) of
 
911
        none ->    save({Format, Args});
 
912
        verbose -> important(Format, Args);
 
913
        debug ->   important(Format, Args);
 
914
        trace ->   important(Format, Args)
 
915
    end.
 
916
 
 
917
%% debug message are display if debug level == 2
 
918
dbg_out(Format, Args) ->
 
919
    case mnesia_monitor:get_env(debug) of
 
920
        none ->    ignore;
 
921
        verbose -> save({Format, Args});
 
922
        _ ->  report_system_event({mnesia_info, Format, Args})
 
923
    end.
 
924
 
 
925
%% Keep the last 10 debug print outs
 
926
save(DbgInfo) ->
 
927
    catch save2(DbgInfo).
 
928
 
 
929
save2(DbgInfo) ->
 
930
    Key = {'$$$_report', current_pos},
 
931
    P =
 
932
        case ?ets_lookup_element(mnesia_gvar, Key, 2) of
 
933
            30 -> -1;
 
934
            I -> I
 
935
        end,
 
936
    set({'$$$_report', current_pos}, P+1),
 
937
    set({'$$$_report', P+1}, {date(), time(), DbgInfo}).
 
938
 
 
939
copy_file(From, To) ->
 
940
    case file:open(From, [raw, binary, read]) of
 
941
        {ok, F} ->
 
942
            case file:open(To, [raw, binary, write]) of
 
943
                {ok, T} ->
 
944
                    Res = copy_file_loop(F, T, 8000),
 
945
                    file:close(F),
 
946
                    file:close(T),
 
947
                    Res;
 
948
                {error, Reason} ->
 
949
                    {error, Reason}
 
950
            end;
 
951
        {error, Reason} ->
 
952
            {error, Reason}
 
953
    end.
 
954
 
 
955
copy_file_loop(F, T, ChunkSize) ->
 
956
    case file:read(F, ChunkSize) of
 
957
        {ok, {0, _}} ->
 
958
            ok;
 
959
        {ok, {_, Bin}} ->
 
960
            file:write(T, Bin),
 
961
            copy_file_loop(F, T, ChunkSize);
 
962
        {ok, Bin} ->
 
963
            file:write(T, Bin),
 
964
            copy_file_loop(F, T, ChunkSize);
 
965
        eof ->
 
966
            ok;
 
967
        {error, Reason} ->
 
968
            {error, Reason}
 
969
    end.
 
970
 
 
971
 
 
972
%%%%%%%%%%%%
 
973
%% versions of all the lowlevel db funcs that determine whether we
 
974
%% shall go to disc or ram to do the actual operation.
 
975
 
 
976
db_get(Tab, Key) ->
 
977
    db_get(val({Tab, storage_type}), Tab, Key).
 
978
db_get(ram_copies, Tab, Key) -> ?ets_lookup(Tab, Key);
 
979
db_get(disc_copies, Tab, Key) -> ?ets_lookup(Tab, Key);
 
980
db_get(disc_only_copies, Tab, Key) -> dets:lookup(Tab, Key).
 
981
 
 
982
db_init_chunk(Tab) ->
 
983
    db_init_chunk(val({Tab, storage_type}), Tab, 1000).
 
984
db_init_chunk(Tab, N) ->
 
985
    db_init_chunk(val({Tab, storage_type}), Tab, N).
 
986
 
 
987
db_init_chunk(disc_only_copies, Tab, N) ->
 
988
    dets:select(Tab, [{'_', [], ['$_']}], N);
 
989
db_init_chunk(_, Tab, N) ->
 
990
    ets:select(Tab, [{'_', [], ['$_']}], N).
 
991
 
 
992
db_chunk(disc_only_copies, State) ->
 
993
    dets:select(State);
 
994
db_chunk(_, State) ->
 
995
    ets:select(State).
 
996
 
 
997
db_put(Tab, Val) ->
 
998
    db_put(val({Tab, storage_type}), Tab, Val).
 
999
 
 
1000
db_put(ram_copies, Tab, Val) -> ?ets_insert(Tab, Val), ok;
 
1001
db_put(disc_copies, Tab, Val) -> ?ets_insert(Tab, Val), ok;
 
1002
db_put(disc_only_copies, Tab, Val) -> dets:insert(Tab, Val).
 
1003
 
 
1004
db_match_object(Tab, Pat) ->
 
1005
    db_match_object(val({Tab, storage_type}), Tab, Pat).
 
1006
db_match_object(Storage, Tab, Pat) ->
 
1007
    db_fixtable(Storage, Tab, true),
 
1008
    Res = catch_match_object(Storage, Tab, Pat),
 
1009
    db_fixtable(Storage, Tab, false),
 
1010
    case Res of
 
1011
        {'EXIT', Reason} -> exit(Reason);
 
1012
        _ -> Res
 
1013
    end.
 
1014
 
 
1015
catch_match_object(disc_only_copies, Tab, Pat) ->
 
1016
    catch dets:match_object(Tab, Pat);
 
1017
catch_match_object(_, Tab, Pat) ->
 
1018
    catch ets:match_object(Tab, Pat).
 
1019
 
 
1020
db_select(Tab, Pat) ->
 
1021
    db_select(val({Tab, storage_type}), Tab, Pat).
 
1022
 
 
1023
db_select(Storage, Tab, Pat) ->
 
1024
    db_fixtable(Storage, Tab, true),
 
1025
    Res = catch_select(Storage, Tab, Pat),
 
1026
    db_fixtable(Storage, Tab, false),
 
1027
    case Res of
 
1028
        {'EXIT', Reason} -> exit(Reason);
 
1029
        _ -> Res
 
1030
    end.
 
1031
 
 
1032
catch_select(disc_only_copies, Tab, Pat) ->
 
1033
    dets:select(Tab, Pat);
 
1034
catch_select(_, Tab, Pat) ->
 
1035
    ets:select(Tab, Pat).
 
1036
 
 
1037
db_fixtable(ets, Tab, Bool) ->
 
1038
    ets:safe_fixtable(Tab, Bool);
 
1039
db_fixtable(ram_copies, Tab, Bool) ->
 
1040
    ets:safe_fixtable(Tab, Bool);
 
1041
db_fixtable(disc_copies, Tab, Bool) ->
 
1042
    ets:safe_fixtable(Tab, Bool);
 
1043
db_fixtable(dets, Tab, Bool) ->
 
1044
    dets:safe_fixtable(Tab, Bool);
 
1045
db_fixtable(disc_only_copies, Tab, Bool) ->
 
1046
    dets:safe_fixtable(Tab, Bool).
 
1047
 
 
1048
db_erase(Tab, Key) ->
 
1049
    db_erase(val({Tab, storage_type}), Tab, Key).
 
1050
db_erase(ram_copies, Tab, Key) -> ?ets_delete(Tab, Key), ok;
 
1051
db_erase(disc_copies, Tab, Key) -> ?ets_delete(Tab, Key), ok;
 
1052
db_erase(disc_only_copies, Tab, Key) -> dets:delete(Tab, Key).
 
1053
 
 
1054
db_match_erase(Tab, Pat) ->
 
1055
    db_match_erase(val({Tab, storage_type}), Tab, Pat).
 
1056
db_match_erase(ram_copies, Tab, Pat) -> ?ets_match_delete(Tab, Pat), ok;
 
1057
db_match_erase(disc_copies, Tab, Pat) -> ?ets_match_delete(Tab, Pat), ok;
 
1058
db_match_erase(disc_only_copies, Tab, Pat) -> dets:match_delete(Tab, Pat).
 
1059
 
 
1060
db_first(Tab) ->
 
1061
    db_first(val({Tab, storage_type}), Tab).
 
1062
db_first(ram_copies, Tab) -> ?ets_first(Tab);
 
1063
db_first(disc_copies, Tab) -> ?ets_first(Tab);
 
1064
db_first(disc_only_copies, Tab) -> dets:first(Tab).
 
1065
 
 
1066
db_next_key(Tab, Key) ->
 
1067
    db_next_key(val({Tab, storage_type}), Tab, Key).
 
1068
db_next_key(ram_copies, Tab, Key) -> ?ets_next(Tab, Key);
 
1069
db_next_key(disc_copies, Tab, Key) -> ?ets_next(Tab, Key);
 
1070
db_next_key(disc_only_copies, Tab, Key) -> dets:next(Tab, Key).
 
1071
 
 
1072
db_last(Tab) ->
 
1073
    db_last(val({Tab, storage_type}), Tab).
 
1074
db_last(ram_copies, Tab) -> ?ets_last(Tab);
 
1075
db_last(disc_copies, Tab) -> ?ets_last(Tab);
 
1076
db_last(disc_only_copies, Tab) -> dets:first(Tab). %% Dets don't have order
 
1077
 
 
1078
db_prev_key(Tab, Key) ->
 
1079
    db_prev_key(val({Tab, storage_type}), Tab, Key).
 
1080
db_prev_key(ram_copies, Tab, Key) -> ?ets_prev(Tab, Key);
 
1081
db_prev_key(disc_copies, Tab, Key) -> ?ets_prev(Tab, Key);
 
1082
db_prev_key(disc_only_copies, Tab, Key) -> dets:next(Tab, Key). %% Dets don't have order
 
1083
 
 
1084
db_slot(Tab, Pos) ->
 
1085
    db_slot(val({Tab, storage_type}), Tab, Pos).
 
1086
db_slot(ram_copies, Tab, Pos) -> ?ets_slot(Tab, Pos);
 
1087
db_slot(disc_copies, Tab, Pos) -> ?ets_slot(Tab, Pos);
 
1088
db_slot(disc_only_copies, Tab, Pos) -> dets:slot(Tab, Pos).
 
1089
 
 
1090
db_update_counter(Tab, C, Val) ->
 
1091
    db_update_counter(val({Tab, storage_type}), Tab, C, Val).
 
1092
db_update_counter(ram_copies, Tab, C, Val) ->
 
1093
    ?ets_update_counter(Tab, C, Val);
 
1094
db_update_counter(disc_copies, Tab, C, Val) ->
 
1095
    ?ets_update_counter(Tab, C, Val);
 
1096
db_update_counter(disc_only_copies, Tab, C, Val) ->
 
1097
    dets:update_counter(Tab, C, Val).
 
1098
 
 
1099
db_erase_tab(Tab) ->
 
1100
    db_erase_tab(val({Tab, storage_type}), Tab).
 
1101
db_erase_tab(ram_copies, Tab) -> ?ets_delete_table(Tab);
 
1102
db_erase_tab(disc_copies, Tab) -> ?ets_delete_table(Tab);
 
1103
db_erase_tab(disc_only_copies, _Tab) -> ignore.
 
1104
 
 
1105
%% assuming that Tab is a valid ets-table
 
1106
dets_to_ets(Tabname, Tab, File, Type, Rep, Lock) ->
 
1107
    {Open, Close} = mkfuns(Lock),
 
1108
    case Open(Tabname, [{file, File}, {type, disk_type(Tab, Type)},
 
1109
                        {keypos, 2}, {repair, Rep}]) of
 
1110
        {ok, Tabname} ->
 
1111
            Res = dets:to_ets(Tabname, Tab),
 
1112
            Close(Tabname),
 
1113
            trav_ret(Res, Tab);
 
1114
        Other ->
 
1115
            Other
 
1116
    end.
 
1117
 
 
1118
trav_ret(Tabname, Tabname) -> loaded;
 
1119
trav_ret(Other, _Tabname) -> Other.
 
1120
 
 
1121
mkfuns(yes) ->
 
1122
    {fun(Tab, Args) -> dets_sync_open(Tab, Args) end,
 
1123
     fun(Tab) -> dets_sync_close(Tab) end};
 
1124
mkfuns(no) ->
 
1125
    {fun(Tab, Args) -> dets:open_file(Tab, Args) end,
 
1126
     fun(Tab) -> dets:close(Tab) end}.
 
1127
 
 
1128
disk_type(Tab) ->
 
1129
    disk_type(Tab, val({Tab, setorbag})).
 
1130
 
 
1131
disk_type(_Tab, ordered_set) ->
 
1132
    set;
 
1133
disk_type(_, Type) ->
 
1134
    Type.
 
1135
 
 
1136
dets_sync_open(Tab, Ref, File) ->
 
1137
    Args = [{file, File},
 
1138
            {keypos, 2},
 
1139
            {repair, mnesia_monitor:get_env(auto_repair)},
 
1140
            {type, disk_type(Tab)}],
 
1141
    dets_sync_open(Ref, Args).
 
1142
 
 
1143
lock_table(Tab) ->
 
1144
    global:set_lock({{mnesia_table_lock, Tab}, self()}, [node()], infinity).
 
1145
%    dbg_out("dets_sync_open: ~p ~p~n", [T, self()]),
 
1146
 
 
1147
unlock_table(Tab) ->
 
1148
    global:del_lock({{mnesia_table_lock, Tab}, self()}, [node()]).
 
1149
%    dbg_out("unlock_table: ~p ~p~n", [T, self()]),
 
1150
 
 
1151
dets_sync_open(Tab, Args) ->
 
1152
    lock_table(Tab),
 
1153
    case dets:open_file(Tab, Args) of
 
1154
        {ok, Tab} ->
 
1155
            {ok, Tab};
 
1156
        Other ->
 
1157
            dets_sync_close(Tab),
 
1158
            Other
 
1159
    end.
 
1160
 
 
1161
dets_sync_close(Tab) ->
 
1162
    catch dets:close(Tab),
 
1163
    unlock_table(Tab),
 
1164
    ok.
 
1165
 
 
1166
cleanup_tmp_files([Tab | Tabs]) ->
 
1167
    dets_sync_close(Tab),
 
1168
    file:delete(tab2tmp(Tab)),
 
1169
    cleanup_tmp_files(Tabs);
 
1170
cleanup_tmp_files([]) ->
 
1171
    ok.
 
1172
 
 
1173
%% Returns a list of bad tables
 
1174
swap_tmp_files([Tab | Tabs]) ->
 
1175
    dets_sync_close(Tab),
 
1176
    Tmp = tab2tmp(Tab),
 
1177
    Dat = tab2dat(Tab),
 
1178
    case file:rename(Tmp, Dat) of
 
1179
        ok ->
 
1180
            swap_tmp_files(Tabs);
 
1181
        _ -> 
 
1182
            file:delete(Tmp),
 
1183
            [Tab | swap_tmp_files(Tabs)]
 
1184
    end;
 
1185
swap_tmp_files([]) ->
 
1186
    [].
 
1187
 
 
1188
readable_indecies(Tab) ->
 
1189
    val({Tab, index}).
 
1190
 
 
1191
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1192
%% Managing conditional debug functions
 
1193
%%
 
1194
%% The main idea with the debug_fun's is to allow test programs
 
1195
%% to control the internal behaviour of Mnesia. This is needed
 
1196
%% to make the test programs independent of system load, swapping
 
1197
%% and other circumstances that may affect the behaviour of Mnesia.
 
1198
%%
 
1199
%% First should calls to ?eval_debug_fun be inserted at well
 
1200
%% defined places in Mnesia's code. E.g. in critical situations
 
1201
%% of startup, transaction commit, backups etc.
 
1202
%%
 
1203
%% Then compile Mnesia with the compiler option 'debug'.
 
1204
%%
 
1205
%% In test programs ?activate_debug_fun should be called
 
1206
%% in order to bind a fun to the debug identifier stated
 
1207
%% in the call to ?eval_debug_fun.
 
1208
%%
 
1209
%% If eval_debug_fun finds that the fun is activated it
 
1210
%% invokes the fun as NewContext = Fun(PreviousContext, EvalContext)
 
1211
%% and replaces the PreviousContext with the NewContext.
 
1212
%% The initial context of a debug_fun is given as argument to
 
1213
%% activate_debug_fun.
 
1214
 
 
1215
-define(DEBUG_TAB, mnesia_debug).
 
1216
-record(debug_info, {id, function, context, file, line}).
 
1217
 
 
1218
scratch_debug_fun() ->
 
1219
    dbg_out("scratch_debug_fun(): ~p~n", [?DEBUG_TAB]),
 
1220
    (catch ?ets_delete_table(?DEBUG_TAB)),
 
1221
    ?ets_new_table(?DEBUG_TAB, [set, public, named_table, {keypos, 2}]).
 
1222
 
 
1223
activate_debug_fun(FunId, Fun, InitialContext, File, Line) ->
 
1224
    Info = #debug_info{id = FunId,
 
1225
                       function = Fun,
 
1226
                       context = InitialContext,
 
1227
                       file = File,
 
1228
                       line = Line
 
1229
                      },
 
1230
    update_debug_info(Info).
 
1231
 
 
1232
update_debug_info(Info) ->
 
1233
    case catch ?ets_insert(?DEBUG_TAB, Info) of
 
1234
        {'EXIT', _} ->
 
1235
            scratch_debug_fun(),
 
1236
            ?ets_insert(?DEBUG_TAB, Info);
 
1237
        _ ->
 
1238
            ok
 
1239
    end,
 
1240
    dbg_out("update_debug_info(~p)~n", [Info]),
 
1241
    ok.
 
1242
 
 
1243
deactivate_debug_fun(FunId, _File, _Line) ->
 
1244
    catch ?ets_delete(?DEBUG_TAB, FunId),
 
1245
    ok.
 
1246
 
 
1247
eval_debug_fun(FunId, EvalContext, EvalFile, EvalLine) ->
 
1248
    case catch ?ets_lookup(?DEBUG_TAB, FunId) of
 
1249
        [] ->
 
1250
            ok;
 
1251
        [Info] ->
 
1252
            OldContext = Info#debug_info.context,
 
1253
            dbg_out("~s(~p): ~w "
 
1254
                    "activated in ~s(~p)~n  "
 
1255
                    "eval_debug_fun(~w, ~w)~n",
 
1256
                    [filename:basename(EvalFile), EvalLine, Info#debug_info.id,
 
1257
                     filename:basename(Info#debug_info.file), Info#debug_info.line,
 
1258
                     OldContext, EvalContext]),
 
1259
            Fun = Info#debug_info.function,
 
1260
            NewContext = Fun(OldContext, EvalContext),
 
1261
            
 
1262
            case catch ?ets_lookup(?DEBUG_TAB, FunId) of
 
1263
                [Info] when NewContext /= OldContext ->
 
1264
                    NewInfo = Info#debug_info{context = NewContext},
 
1265
                    update_debug_info(NewInfo);
 
1266
                _ ->
 
1267
                    ok
 
1268
            end;
 
1269
        {'EXIT', _} -> ok    
 
1270
    end.
 
1271
        
 
1272
-ifdef(debug).
 
1273
    is_debug_compiled() -> true.
 
1274
-else.
 
1275
    is_debug_compiled() -> false.
 
1276
-endif.   
 
1277
 
 
1278