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

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_config_test.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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 1997-2010. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
%%
 
21
-module(mnesia_config_test).
 
22
-author('hakan@erix.ericsson.se').
 
23
 
 
24
-include("mnesia_test_lib.hrl").
 
25
 
 
26
-record(test_table,{i,a1,a2,a3}).
 
27
-record(test_table2,{i, b}).
 
28
 
 
29
-export([
 
30
        all/0,groups/0,init_per_group/2,end_per_group/2,
 
31
         access_module/1,
 
32
         auto_repair/1,
 
33
         backup_module/1,
 
34
         debug/1,
 
35
         dir/1,
 
36
         dump_log_load_regulation/1,
 
37
        
 
38
         dump_log_update_in_place/1,
 
39
         embedded_mnemosyne/1,
 
40
         event_module/1,
 
41
         ignore_fallback_at_startup/1,
 
42
         inconsistent_database/1,
 
43
         max_wait_for_decision/1,
 
44
         send_compressed/1,
 
45
 
 
46
         app_test/1,
 
47
        
 
48
         schema_merge/1,
 
49
         unknown_config/1,
 
50
 
 
51
         dump_log_time_threshold/1,
 
52
         dump_log_write_threshold/1,
 
53
         
 
54
         start_one_disc_full_then_one_disc_less/1,
 
55
         start_first_one_disc_less_then_one_disc_full/1,
 
56
         start_first_one_disc_less_then_two_more_disc_less/1,
 
57
         schema_location_and_extra_db_nodes_combinations/1,
 
58
         table_load_to_disc_less_nodes/1,
 
59
        
 
60
         dynamic_basic/1,
 
61
         dynamic_ext/1,
 
62
         dynamic_bad/1,
 
63
 
 
64
         init_per_testcase/2,
 
65
         end_per_testcase/2,
 
66
         c_nodes/0
 
67
        ]).
 
68
 
 
69
-export([check_logs/1]).
 
70
 
 
71
-define(init(N, Config),
 
72
        mnesia_test_lib:prepare_test_case([{init_test_case, [mnesia]},
 
73
                                           delete_schema,
 
74
                                           {reload_appls, [mnesia]}],
 
75
                                          N, Config, ?FILE, ?LINE)).
 
76
-define(acquire(N, Config),
 
77
        mnesia_test_lib:prepare_test_case([{init_test_case, [mnesia]},
 
78
                                           delete_schema,
 
79
                                           {reload_appls, [mnesia]},
 
80
                                           create_schema,
 
81
                                           {start_appls, [mnesia]}],
 
82
                                          N, Config, ?FILE, ?LINE)).
 
83
-define(acquire_schema(N, Config),
 
84
        mnesia_test_lib:prepare_test_case([{init_test_case, [mnesia]},
 
85
                                            delete_schema,
 
86
                                            {reload_appls, [mnesia]},
 
87
                                            create_schema],
 
88
                                          N, Config, ?FILE, ?LINE)).
 
89
-define(cleanup(N, Config),
 
90
        mnesia_test_lib:prepare_test_case([{reload_appls, [mnesia]}],
 
91
                                          N, Config, ?FILE, ?LINE)).
 
92
-define(trans(Fun),
 
93
        ?match({atomic, ok}, mnesia:transaction(Fun))).
 
94
 
 
95
init_per_testcase(Func, Conf) ->
 
96
    mnesia_test_lib:init_per_testcase(Func, Conf).
 
97
 
 
98
end_per_testcase(Func, Conf) ->
 
99
    mnesia_test_lib:end_per_testcase(Func, Conf).
 
100
 
 
101
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
102
 
 
103
 
 
104
all() -> 
 
105
    [access_module, auto_repair, backup_module, debug, dir,
 
106
     dump_log_load_regulation, {group, dump_log_thresholds},
 
107
     dump_log_update_in_place, embedded_mnemosyne,
 
108
     event_module, ignore_fallback_at_startup,
 
109
     inconsistent_database, max_wait_for_decision,
 
110
     send_compressed, app_test, {group, schema_config},
 
111
     unknown_config].
 
112
 
 
113
groups() -> 
 
114
    [{dump_log_thresholds, [],
 
115
      [dump_log_time_threshold, dump_log_write_threshold]},
 
116
     {schema_config, [],
 
117
      [start_one_disc_full_then_one_disc_less,
 
118
       start_first_one_disc_less_then_one_disc_full,
 
119
       start_first_one_disc_less_then_two_more_disc_less,
 
120
       schema_location_and_extra_db_nodes_combinations,
 
121
       table_load_to_disc_less_nodes, schema_merge,
 
122
       {group, dynamic_connect}]},
 
123
     {dynamic_connect, [],
 
124
      [dynamic_basic, dynamic_ext, dynamic_bad]}].
 
125
 
 
126
init_per_group(_GroupName, Config) ->
 
127
    Config.
 
128
 
 
129
end_per_group(_GroupName, Config) ->
 
130
    Config.
 
131
 
 
132
 
 
133
 
 
134
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
135
 
 
136
access_module(doc) ->
 
137
    ["Replace the activity access module with another module and ",
 
138
     "use it to read and write to some alternate table storage"];
 
139
access_module(suite) -> [];
 
140
access_module(Config) when is_list(Config) ->
 
141
    Nodes = ?acquire_schema(1, Config),
 
142
    ?match(ok, mnesia:start([{access_module, mnesia_frag}])),
 
143
 
 
144
    ?match(mnesia_frag, mnesia:system_info(access_module)),
 
145
 
 
146
    access_tab(ram_copies, Nodes),
 
147
    case mnesia_test_lib:diskless(Config) of
 
148
        true -> skip;
 
149
        false -> 
 
150
            access_tab(disc_copies, Nodes)
 
151
                ,  access_tab(disc_only_copies, Nodes)
 
152
    end,
 
153
 
 
154
    ?verify_mnesia(Nodes, []),
 
155
    ?cleanup(1, Config).
 
156
 
 
157
access_tab(Storage, Nodes) ->
 
158
    Tab = list_to_atom(lists:concat([access_tab_, Storage])),
 
159
    RecName = some_access,
 
160
    Attr = val,
 
161
    TabDef = [{Storage, Nodes},
 
162
              {type, bag},
 
163
              {index, [Attr]},
 
164
              {record_name, RecName}],
 
165
    ?match({atomic,ok}, mnesia:create_table(Tab, TabDef)),
 
166
 
 
167
    Activity = fun(Kind) ->
 
168
                       A = [Kind, Tab, RecName, Attr, Nodes],
 
169
                       io:format("kind: ~w, storage: ~w~n", [Kind, Storage]),
 
170
                       mnesia:activity(Kind, fun do_access/5, A)
 
171
               end,
 
172
    ModActivity = fun(Kind, M) ->
 
173
                          io:format("kind: ~w, storage: ~w. module: ~w~n",
 
174
                                    [Kind, Storage, M]),
 
175
                          A = [Kind, Tab, RecName, Attr, Nodes],
 
176
                          mnesia:activity(Kind, fun do_access/5, A, M)
 
177
               end,
 
178
    ?match(ok, Activity(transaction)),
 
179
    ?match(ok, Activity({transaction, 47})),
 
180
    ?match(ok, ModActivity(transaction, mnesia)),
 
181
    ?match(ok, ModActivity(transaction, mnesia_frag)),
 
182
    
 
183
    ?match(ok, Activity(async_dirty)),
 
184
    ?match(ok, Activity(sync_dirty)),
 
185
    case Storage of
 
186
        ram_copies ->
 
187
            ?match(ok, Activity(ets));
 
188
        _ ->
 
189
            ignore
 
190
    end.
 
191
 
 
192
do_access(Kind, Tab, RecName, Attr, Nodes) ->
 
193
    Tens = lists:sort([{RecName, 1, 10}, {RecName, 3, 10}]),
 
194
    {OptNodes, OptTens} = 
 
195
        case Kind of
 
196
            transaction -> {Nodes, Tens};
 
197
            {transaction, _} -> {Nodes, Tens};
 
198
            async_dirty -> {[], Tens};
 
199
            sync_dirty -> {[], Tens};
 
200
            ets -> {[], []}
 
201
        end,
 
202
    ?match(RecName, mnesia:table_info(Tab, record_name)),
 
203
    
 
204
    ?match(ok, mnesia:write(Tab, {RecName, 1, 10}, write)),
 
205
    ?match(ok, mnesia:write(Tab, {RecName, 2, 20}, sticky_write)),
 
206
    ?match(ok, mnesia:write(Tab, {RecName, 2, 21}, sticky_write)),
 
207
    ?match(ok, mnesia:write(Tab, {RecName, 2, 22}, write)),
 
208
    ?match(ok, mnesia:write(Tab, {RecName, 3, 10}, write)),
 
209
 
 
210
    Twos = [{RecName, 2, 20}, {RecName, 2, 21}, {RecName, 2, 22}],
 
211
    ?match(Twos, lists:sort(mnesia:read(Tab, 2, read))),
 
212
    
 
213
    ?match(ok, mnesia:delete_object(Tab, {RecName, 2, 21}, sticky_write)),
 
214
 
 
215
    TenPat = {RecName, '_', 10},
 
216
    ?match(Tens, lists:sort(mnesia:match_object(Tab, TenPat, read))),
 
217
    ?match(OptTens, lists:sort(mnesia:index_match_object(Tab, TenPat, Attr, read) )),
 
218
    ?match(OptTens, lists:sort(mnesia:index_read(Tab, 10, Attr))),
 
219
    Keys = [1, 2, 3],
 
220
    ?match(Keys, lists:sort(mnesia:all_keys(Tab))),
 
221
 
 
222
    First = mnesia:first(Tab),
 
223
    Mid   = mnesia:next(Tab, First),
 
224
    Last  = mnesia:next(Tab, Mid),
 
225
    ?match('$end_of_table', mnesia:next(Tab, Last)),
 
226
    ?match(Keys, lists:sort([First,Mid,Last])),
 
227
 
 
228
    %% For set and bag these last, prev works as first and next
 
229
    First2 = mnesia:last(Tab),
 
230
    Mid2   = mnesia:prev(Tab, First2),
 
231
    Last2  = mnesia:prev(Tab, Mid2),
 
232
    ?match('$end_of_table', mnesia:prev(Tab, Last2)),
 
233
    ?match(Keys, lists:sort([First2,Mid2,Last2])),
 
234
 
 
235
    ?match([ok, ok, ok], [mnesia:delete(Tab, K, write) || K <- Keys]),
 
236
    W = wild_pattern,
 
237
    ?match([], mnesia:match_object(Tab, mnesia:table_info(Tab, W), read)),
 
238
    ?log("Safe fixed ~p~n", [catch ets:info(Tab, safe_fixed)]),
 
239
    ?log("Fixed ~p ~n", [catch ets:info(Tab, fixed)]),
 
240
    
 
241
    ?match(OptNodes, mnesia:lock({global, some_lock_item, Nodes}, write)),
 
242
    ?match(OptNodes, mnesia:lock({global, some_lock_item, Nodes}, read)),
 
243
    ?match(OptNodes, mnesia:lock({table, Tab}, read)),
 
244
    ?match(OptNodes, mnesia:lock({table, Tab}, write)),
 
245
    
 
246
    ok.
 
247
 
 
248
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
249
auto_repair(doc) ->
 
250
    ["Try the auto_repair mechanism on the various disk_logs and dets files.",
 
251
     "",
 
252
     "The case tests both normal values of the parameter, and also",
 
253
     "one crazy value.",
 
254
     "The test of the real auto_repair functionality is made in the",
 
255
     "dets suite"
 
256
    ];
 
257
auto_repair(suite) -> [];
 
258
auto_repair(Config) when is_list(Config) ->
 
259
    ?init(1, Config),
 
260
    ?match(ok, mnesia:start()),                 % Check default true
 
261
    ?match(true, mnesia:system_info(auto_repair)),
 
262
    ?match(stopped, mnesia:stop()),
 
263
    ?match(ok, mnesia:start([{auto_repair, true}])),
 
264
    ?match(true, mnesia:system_info(auto_repair)),
 
265
    ?match(stopped, mnesia:stop()),
 
266
    ?match(ok, mnesia:start([{auto_repair, false}])),
 
267
    ?match(false, mnesia:system_info(auto_repair)),
 
268
    ?match(stopped, mnesia:stop()),
 
269
    ?match({error, {bad_type, auto_repair, your_mama}},
 
270
           mnesia:start([{auto_repair, your_mama}])),
 
271
     ?match(stopped, mnesia:stop()),
 
272
    ?cleanup(1, Config),
 
273
    ok.
 
274
 
 
275
 
 
276
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
277
 
 
278
backup_module(doc) ->
 
279
    ["Replace the backup module with another module and use it to",
 
280
     "read and write to an alternate backup media, e.g stored in",
 
281
     "the internal state of a simple process."];
 
282
backup_module(suite) -> [];
 
283
backup_module(Config) when is_list(Config) ->
 
284
    Nodes = ?acquire_schema(1, Config),
 
285
    ?match(ok, mnesia:start([{backup_module, mnesia_config_backup}])),
 
286
    ?match({atomic,ok},
 
287
           mnesia:create_table(test_table,
 
288
                               [{disc_copies, Nodes},
 
289
                                {attributes,
 
290
                                 record_info(fields,test_table)}])),
 
291
    
 
292
    ?match({atomic,ok},
 
293
           mnesia:create_table(test_table2,
 
294
                               [{disc_copies, Nodes},
 
295
                                {attributes,
 
296
                                 record_info(fields,test_table2)}])),
 
297
    %% Write in test table 
 
298
    ?trans(fun() -> mnesia:write(#test_table{i=1}) end),
 
299
    ?trans(fun() -> mnesia:write(#test_table{i=2}) end),
 
300
    
 
301
    %% Write in test table 2
 
302
    ?trans(fun() -> mnesia:write(#test_table2{i=3}) end),
 
303
    ?trans(fun() -> mnesia:write(#test_table2{i=4}) end),
 
304
    mnesia_test_lib:sync_tables(Nodes, [test_table, test_table2]),
 
305
    
 
306
    File = whow,
 
307
    %% Now make a backup
 
308
    ?match(ok, mnesia:backup(File)),
 
309
 
 
310
    ?match(ok, mnesia:install_fallback(File)),
 
311
    
 
312
    %% Now add things
 
313
    ?trans(fun() -> mnesia:write(#test_table{i=2.5}) end),
 
314
    ?trans(fun() -> mnesia:write(#test_table2{i=3.5}) end),
 
315
 
 
316
    mnesia_test_lib:kill_mnesia(Nodes),
 
317
    receive after 2000 -> ok end,
 
318
    ?match([], mnesia_test_lib:start_mnesia(Nodes, [test_table, test_table2])),
 
319
 
 
320
    %% Now check newly started tables
 
321
    ?match({atomic, [1,2]}, 
 
322
           mnesia:transaction(fun() -> lists:sort(mnesia:all_keys(test_table)) end)),
 
323
    ?match({atomic, [3,4]}, 
 
324
           mnesia:transaction(fun() -> lists:sort(mnesia:all_keys(test_table2)) end)),
 
325
    
 
326
    file:delete(File),
 
327
    ?verify_mnesia(Nodes, []),
 
328
    ?cleanup(1, Config),
 
329
    ok.
 
330
 
 
331
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
332
debug(doc) ->
 
333
    ["Try out the four debug levels and ensure that the",
 
334
    "expected events are generated."];
 
335
debug(suite) -> [];
 
336
debug(Config) when is_list(Config) ->
 
337
    Nodes = ?init(1, Config),
 
338
    case application:get_env(mnesia,debug) of
 
339
        undefined ->
 
340
            ?match(none, mnesia:system_info(debug));
 
341
        {ok, false} ->
 
342
            ?match(none, mnesia:system_info(debug));
 
343
        {ok, true} ->
 
344
            ?match(debug, mnesia:system_info(debug));
 
345
        {ok, Env} ->
 
346
            ?match(Env, mnesia:system_info(debug))
 
347
    end,
 
348
 
 
349
    ?match(ok, mnesia:start([{debug, verbose}])),
 
350
    ?match(verbose, mnesia:system_info(debug)),
 
351
    mnesia_test_lib:kill_mnesia(Nodes),
 
352
    receive after 2000 -> ok end,
 
353
 
 
354
    ?match(ok, mnesia:start([{debug, debug}])),
 
355
    ?match(debug, mnesia:system_info(debug)),
 
356
    mnesia_test_lib:kill_mnesia(Nodes),
 
357
    receive after 2000 -> ok end,
 
358
 
 
359
    ?match(ok, mnesia:start([{debug, trace}])),
 
360
    ?match(trace, mnesia:system_info(debug)),
 
361
    mnesia_test_lib:kill_mnesia(Nodes),
 
362
    receive after 2000 -> ok end,
 
363
 
 
364
    ?match(ok, mnesia:start([{debug, true}])),
 
365
    ?match(debug, mnesia:system_info(debug)),
 
366
    mnesia_test_lib:kill_mnesia(Nodes),
 
367
    receive after 2000 -> ok end,
 
368
 
 
369
    ?match(ok, mnesia:start([{debug, false}])),
 
370
    ?match(none, mnesia:system_info(debug)),
 
371
 
 
372
    ?verify_mnesia(Nodes, []),
 
373
    ?cleanup(1, Config),
 
374
    ok.
 
375
 
 
376
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
377
dir(doc) ->
 
378
    ["Try to use alternate Mnesia directories"];
 
379
dir(suite) -> [];
 
380
dir(Config) when is_list(Config) ->
 
381
    Nodes = ?init(1, Config),
 
382
 
 
383
    ?match(ok, mnesia:start([{dir, tuff}])),
 
384
    Dir = filename:join([element(2, file:get_cwd()), "tuff"]),
 
385
    ?match(Dir, mnesia:system_info(directory)),
 
386
    mnesia_test_lib:kill_mnesia(Nodes),
 
387
 
 
388
    ?cleanup(1, Config),
 
389
    ok.
 
390
 
 
391
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
392
dump_log_update_in_place(doc) ->
 
393
    ["Change the update in place policy for the transaction log dumper."];
 
394
dump_log_update_in_place(suite) -> [];
 
395
dump_log_update_in_place(Config) when is_list(Config) ->
 
396
    Nodes = ?acquire(1, Config),
 
397
    ?match(true, mnesia:system_info(dump_log_update_in_place)),
 
398
    ?match({atomic,ok},
 
399
           mnesia:create_table(test_table,
 
400
                               [{disc_copies, Nodes},
 
401
                                {attributes,
 
402
                                 record_info(fields,test_table)}])),
 
403
    
 
404
    mnesia_test_lib:kill_mnesia(Nodes),
 
405
    receive after 2000 -> ok end,
 
406
    
 
407
    ?match(ok, mnesia:start([{dump_log_update_in_place, false}])),
 
408
    ?match(false, mnesia:system_info(dump_log_update_in_place)),
 
409
 
 
410
    mnesia_test_lib:sync_tables(Nodes, [schema, test_table]),
 
411
 
 
412
    %% Now provoke some log dumps
 
413
 
 
414
    L = lists:map(
 
415
          fun(Num) ->
 
416
                  %% Write something on one end ...
 
417
                  mnesia:transaction(
 
418
                    fun() ->
 
419
                            mnesia:write(#test_table{i=Num}) end
 
420
                   ) end,
 
421
          lists:seq(1, 110)),
 
422
    
 
423
    L2 = lists:duplicate(110, {atomic, ok}),
 
424
 
 
425
    %% If this fails then some of the 110 writes above failed
 
426
    ?match(true, L==L2),
 
427
    if  L==L2 -> ok;
 
428
        true -> 
 
429
            ?verbose("***** List1 len: ~p, List2 len: ~p~n",
 
430
                      [length(L), length(L2)]),
 
431
            ?verbose("L: ~p~nL2:~p~n", [L, L2])
 
432
    end,
 
433
    
 
434
    %% If we still can write, then Mnesia is probably alive
 
435
    ?trans(fun() -> mnesia:write(#test_table{i=115}) end),
 
436
    
 
437
    ?verify_mnesia(Nodes, []),
 
438
    ?cleanup(1, Config),
 
439
    ok.
 
440
 
 
441
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
442
 
 
443
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
444
dump_log_write_threshold(doc)->
 
445
    ["This test case must be rewritten.",
 
446
     "Dump logs are tested by doing transactions, then killing Mnesia and ",
 
447
     "then examining the table data files and see if they are correct.",
 
448
     "The test_table is used as a counter, test_table. is stepped once ",
 
449
     "for each transaction."];
 
450
dump_log_write_threshold(suite)->[];
 
451
dump_log_write_threshold(Config) when is_list(Config) ->
 
452
    [N1] = ?acquire_schema(1, Config),
 
453
 
 
454
    Threshold = 3,
 
455
    ?match(ok,mnesia:start([{dump_log_write_threshold, Threshold}])),
 
456
 
 
457
    ?match({atomic,ok},
 
458
           mnesia:create_table(test_table,
 
459
                               [{disc_copies, [N1]},
 
460
                                {attributes,
 
461
                                 record_info(fields,test_table)}])),
 
462
    ?match(dumped, mnesia:dump_log()),
 
463
    
 
464
    ?match(ok, do_trans(2)),                            % Shall not have dumped
 
465
    check_logs(0),
 
466
    
 
467
    ?match(ok, do_trans(Threshold - 2)),                        % Trigger a dump
 
468
    receive after 1000 -> ok end,
 
469
    check_logs(Threshold),
 
470
 
 
471
    
 
472
    ?match(ok, do_trans(Threshold - 1)),   
 
473
    ?match(dumped, mnesia:dump_log()),   %% This should trigger ets2dcd dump
 
474
    check_logs(0),                       %% and leave no dcl file
 
475
    
 
476
    ?match(stopped, mnesia:stop()),
 
477
 
 
478
    %% Check bad threshold value
 
479
    ?match({error,{bad_type,dump_log_write_threshold,0}},
 
480
           mnesia:start([{dump_log_write_threshold,0}])),
 
481
 
 
482
    ?verify_mnesia([], [N1]),
 
483
    ?cleanup(1, Config),
 
484
    ok.
 
485
 
 
486
 
 
487
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
488
dump_log_time_threshold(doc)->
 
489
    ["See doc on above."];
 
490
dump_log_time_threshold(suite)->[];
 
491
dump_log_time_threshold(Config) when is_list(Config) ->
 
492
    Nodes = ?acquire_schema(1, Config),
 
493
    Time = 4000,
 
494
 
 
495
    %% Check bad threshold value
 
496
    ?match({error,{bad_type,dump_log_time_threshold,0}},
 
497
           mnesia:start([{dump_log_time_threshold,0}])),
 
498
    
 
499
    
 
500
    ?match(ok,mnesia:start([{dump_log_write_threshold,100},
 
501
                            {dump_log_time_threshold, Time}])),
 
502
    
 
503
    ?match({atomic,ok},mnesia:create_table(test_table,
 
504
                                           [{disc_copies, Nodes},
 
505
                                            {attributes,
 
506
                                             record_info(fields,
 
507
                                                         test_table)}])),
 
508
    
 
509
    %% Check that nothing is dumped when within time threshold
 
510
    ?match(ok, do_trans(1)),
 
511
    check_logs(0),
 
512
    
 
513
    ?match(Time, mnesia:system_info(dump_log_time_threshold)),
 
514
 
 
515
    %% Check that things get dumped when time threshold exceeded
 
516
    ?match(ok, do_trans(5)),
 
517
    receive after Time+2000 -> ok end,
 
518
    check_logs(6),
 
519
    
 
520
    ?verify_mnesia([node()], []),
 
521
    ?cleanup(1, Config),
 
522
    ok.
 
523
 
 
524
%%%%%%%%
 
525
%% 
 
526
%% Help functions for dump log
 
527
 
 
528
%% Do a transaction N times
 
529
do_trans(0) -> ok;
 
530
do_trans(N) ->
 
531
    Fun = fun() ->
 
532
                  XX=incr(),
 
533
                  mnesia:write(#test_table{i=XX})
 
534
          end,
 
535
    {atomic, ok} = mnesia:transaction(Fun),
 
536
    do_trans(N-1).
 
537
 
 
538
%% An increasing number
 
539
incr() ->
 
540
    case get(bloody_counter) of
 
541
        undefined -> put(bloody_counter, 2), 1;
 
542
        Num -> put(bloody_counter, Num+1)
 
543
    end.
 
544
 
 
545
%%
 
546
%% Check that the correct number of transactions have been recorded.
 
547
%%-record(test_table,{i,a1,a2,a3}).
 
548
check_logs(N) ->    
 
549
    File = mnesia_lib:tab2dcl(test_table),    
 
550
    Args = [{file, File}, {name, testing}, {repair, true}, {mode, read_only}],
 
551
 
 
552
    if N == 0 ->
 
553
            ?match(false, mnesia_lib:exists(File));
 
554
       true ->
 
555
            ?match(true, mnesia_lib:exists(File)),
 
556
            ?match({ok, _Log}, disk_log:open(Args)),
 
557
            
 
558
            {Cont, Terms} = disk_log:chunk(testing, start),
 
559
            ?match(eof, disk_log:chunk(testing, Cont)),
 
560
            %%?verbose("N: ~p, L: ~p~n", [N, L]),
 
561
            disk_log:close(testing),
 
562
            
 
563
            %% Correct number of records in file
 
564
            ?match({N, N}, {N, length(Terms) -1 })  %% Ignore Header
 
565
    end.
 
566
 
 
567
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
568
 
 
569
dump_log_load_regulation(doc) ->
 
570
    ["Test the load regulation of the dumper"];
 
571
dump_log_load_regulation(suite) ->
 
572
    [];
 
573
dump_log_load_regulation(Config) when is_list(Config) ->
 
574
    Nodes = ?acquire_nodes(1, Config),
 
575
    Param = dump_log_load_regulation,
 
576
 
 
577
    %% Normal 
 
578
    NoReg = false,
 
579
    ?match(NoReg, mnesia:system_info(Param)),
 
580
    ?match([], mnesia_test_lib:stop_mnesia(Nodes)),
 
581
 
 
582
    %% Bad
 
583
    Bad = arne_anka,
 
584
    ?match({error, {bad_type, Param, Bad}},
 
585
           mnesia:start([{Param, Bad}])),
 
586
 
 
587
    %% Regulation activated
 
588
    Reg = true,
 
589
    ?match(ok,mnesia:start([{Param, Reg}])),
 
590
    ?match(Reg, mnesia:system_info(Param)),
 
591
 
 
592
    Args =
 
593
        [{db_nodes, Nodes},
 
594
         {driver_nodes, Nodes},
 
595
         {replica_nodes, Nodes},
 
596
         {n_drivers_per_node, 5},
 
597
         {n_branches, length(Nodes) * 10},
 
598
         {n_accounts_per_branch, 5},
 
599
         {replica_type, disc_copies},
 
600
         {stop_after, timer:seconds(30)},
 
601
         {report_interval, timer:seconds(10)},
 
602
         {use_running_mnesia, true},
 
603
         {reuse_history_id, true}],
 
604
    
 
605
    ?match({ok, _}, mnesia_tpcb:start(Args)),
 
606
    
 
607
    ?verify_mnesia(Nodes, []),
 
608
    ?cleanup(1, Config),
 
609
    ok.
 
610
 
 
611
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
612
 
 
613
embedded_mnemosyne(doc) ->
 
614
    ["Start Mnemosyne as an embedded part of Mnesia",
 
615
     "on some of the nodes"];
 
616
embedded_mnemosyne(suite) ->
 
617
    [];
 
618
embedded_mnemosyne(Config) when is_list(Config) ->
 
619
    Nodes = ?acquire_nodes(1, Config),
 
620
    Param = embedded_mnemosyne,
 
621
 
 
622
    %% Normal 
 
623
    NoMnem = false,
 
624
    ?match(NoMnem, mnesia:system_info(Param)),
 
625
    ?match(undefined, whereis(mnemosyne_catalog)),
 
626
    ?match([], mnesia_test_lib:stop_mnesia(Nodes)),
 
627
 
 
628
    %% Bad
 
629
    Bad = arne_anka,
 
630
    ?match({error, {bad_type, Param, Bad}},
 
631
           mnesia:start([{Param, Bad}])),
 
632
 
 
633
    case code:priv_dir(mnemosyne) of
 
634
        {error, _} -> %% No mnemosyne on later systems
 
635
            ok;
 
636
        _ ->
 
637
            %% Mnemosyne as embedded application
 
638
            Mnem = true,
 
639
            ?match(undefined, whereis(mnemosyne_catalog)),
 
640
            ?match(ok,mnesia:start([{Param, Mnem}])),
 
641
            ?match(Mnem, mnesia:system_info(Param)),
 
642
            ?match(Pid when is_pid(Pid), whereis(mnemosyne_catalog)),
 
643
            ?match([], mnesia_test_lib:stop_mnesia(Nodes)),
 
644
            ?match(undefined, whereis(mnemosyne_catalog))
 
645
    end,
 
646
    ?verify_mnesia([], Nodes),
 
647
    ?cleanup(1, Config),
 
648
    ok.
 
649
 
 
650
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
651
 
 
652
ignore_fallback_at_startup(doc) ->
 
653
    ["Start Mnesia without rollback of the database to the fallback. ",
 
654
     "Once Mnesia has been (re)started the installed fallback should",
 
655
     "be handled as a normal active fallback.",
 
656
     "Install a customized event module which disables the termination",
 
657
     "of Mnesia when mnesia_down occurrs with an active fallback."].
 
658
 
 
659
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
660
 
 
661
max_wait_for_decision(doc) ->
 
662
    ["Provoke Mnesia to make a forced decision of the outome",
 
663
     "of a heavy weight transaction."].
 
664
     
 
665
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
666
 
 
667
send_compressed(doc) -> [];
 
668
send_compressed(suite) -> [];
 
669
send_compressed(Config) ->
 
670
    [N1,N2] = Nodes = ?acquire_nodes(2, Config),
 
671
    ?match({atomic,ok}, mnesia:create_table(t0, [{ram_copies,[N1,N2]}])),
 
672
    ?match({atomic,ok}, mnesia:create_table(t1, [{disc_copies,[N1,N2]}])),
 
673
    ?match({atomic,ok}, mnesia:create_table(t2, [{disc_only_copies,[N1,N2]}])),
 
674
 
 
675
    Max = 1000,
 
676
    Create = fun(Tab) -> [mnesia:write({Tab, N, {N, "FILLER-123490878345asdasd"}})
 
677
                          || N <- lists:seq(1, Max)],
 
678
                         ok
 
679
             end,
 
680
    
 
681
    ?match([], mnesia_test_lib:kill_mnesia([N2])),
 
682
    
 
683
    ?match([], mnesia_test_lib:kill_mnesia([N1])),
 
684
    ?match(ok, mnesia:start([{send_compressed, 9}])),
 
685
    ?match(ok, mnesia:wait_for_tables([t0,t1,t2], 5000)),
 
686
 
 
687
    ?match({atomic, ok}, mnesia:transaction(Create, [t0])),
 
688
    ?match({atomic, ok}, mnesia:transaction(Create, [t1])),
 
689
    ?match({atomic, ok}, mnesia:transaction(Create, [t2])),
 
690
    
 
691
    ?match([], mnesia_test_lib:start_mnesia([N2], [t0,t1,t2])),
 
692
    
 
693
    Verify = fun(Tab) ->                     
 
694
                     [ [{Tab,N,{N,_}}] = mnesia:read(Tab, N) || N <- lists:seq(1, Max)],
 
695
                     ok
 
696
             end,
 
697
    ?match({atomic, ok}, rpc:call(N1, mnesia, transaction, [Verify, [t0]])),
 
698
    ?match({atomic, ok}, rpc:call(N1, mnesia, transaction, [Verify, [t1]])),
 
699
    ?match({atomic, ok}, rpc:call(N1, mnesia, transaction, [Verify, [t2]])),
 
700
    
 
701
    ?match({atomic, ok}, rpc:call(N2, mnesia, transaction, [Verify, [t0]])),
 
702
    ?match({atomic, ok}, rpc:call(N2, mnesia, transaction, [Verify, [t1]])),
 
703
    ?match({atomic, ok}, rpc:call(N2, mnesia, transaction, [Verify, [t2]])),
 
704
    
 
705
    ?verify_mnesia(Nodes, []),
 
706
    ?cleanup(1, Config),
 
707
    ok.
 
708
 
 
709
app_test(doc) -> [];
 
710
app_test(suite) -> [];
 
711
app_test(_Config) ->
 
712
    ?match(ok,test_server:app_test(mnesia)),
 
713
    ok.
 
714
 
 
715
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
716
 
 
717
event_module(doc) ->
 
718
    ["Replace the event module with another module and use it as",
 
719
     "receiver of the various system and table events. Provoke",
 
720
     "coverage of all kinds of events."];
 
721
event_module(suite) -> [];
 
722
event_module(Config) when is_list(Config) ->
 
723
    Filter = fun({mnesia_system_event,{mnesia_info, _, _}}) -> false;
 
724
                (_) -> true
 
725
             end,
 
726
    
 
727
    [_N1, N2]=Nodes=?acquire_schema(2, Config),
 
728
 
 
729
    Def = case mnesia_test_lib:diskless(Config) of 
 
730
              true -> [{event_module, mnesia_config_event},
 
731
                       {extra_db_nodes, Nodes}];
 
732
              false  ->
 
733
                  [{event_module, mnesia_config_event}]
 
734
          end,
 
735
 
 
736
    ?match({[ok, ok], []}, rpc:multicall(Nodes, mnesia, start, [Def])),
 
737
    receive after 1000 -> ok end,
 
738
    mnesia_event ! {get_log, self()},
 
739
    DebugLog1 = receive 
 
740
                    {log, L1} -> L1
 
741
                after 10000 -> [timeout]
 
742
                end,
 
743
    ?match([{mnesia_system_event,{mnesia_up,N2}}],
 
744
           lists:filter(Filter, DebugLog1)),
 
745
    mnesia_test_lib:kill_mnesia([N2]),
 
746
    receive after 2000 -> ok end,
 
747
 
 
748
    ?match({[ok], []}, rpc:multicall([N2], mnesia, start, [])),
 
749
 
 
750
    receive after 1000 -> ok end,
 
751
    mnesia_event ! {get_log, self()},
 
752
    DebugLog = receive 
 
753
                   {log, L} -> L
 
754
               after 10000 -> [timeout]
 
755
               end,
 
756
    ?match([{mnesia_system_event,{mnesia_up,N2}},
 
757
            {mnesia_system_event,{mnesia_down,N2}},
 
758
            {mnesia_system_event,{mnesia_up, N2}}],
 
759
           lists:filter(Filter, DebugLog)),
 
760
    ?verify_mnesia(Nodes, []),
 
761
    ?cleanup(1, Config),
 
762
    ok.
 
763
 
 
764
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
765
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
766
start_one_disc_full_then_one_disc_less(doc)->
 
767
    ["Start a disk node and then a disk less one. Distribute some",
 
768
     "tables between them."];
 
769
start_one_disc_full_then_one_disc_less(suite) -> [];
 
770
start_one_disc_full_then_one_disc_less(Config) when is_list(Config) ->
 
771
    [N1, N2] = ?init(2, Config),
 
772
    ?match(ok, mnesia:create_schema([N1])),
 
773
    ?match([], mnesia_test_lib:start_mnesia([N1])),
 
774
 
 
775
    ?match({atomic, ok}, mnesia:add_table_copy(schema, N2, ram_copies)),
 
776
 
 
777
    ?match(ok, rpc:call(N2, mnesia, start, [[{schema_location, ram},
 
778
                                             {extra_db_nodes, [N1]}]])),
 
779
    mnesia_test_lib:sync_tables([N1, N2], [schema]),
 
780
 
 
781
    %% Now create some tables
 
782
    ?match({atomic,ok},
 
783
           mnesia:create_table(test_table,
 
784
                               [{ram_copies, [N1, N2]},
 
785
                                {attributes,
 
786
                                 record_info(fields,test_table)}])),
 
787
    
 
788
    ?match({atomic,ok},
 
789
           rpc:call(
 
790
             N2, mnesia,create_table, [test_table2,
 
791
                                      [{ram_copies, [N1, N2]},
 
792
                                       {attributes,
 
793
                                        record_info(fields,test_table2)}]])),
 
794
 
 
795
    %% Write something on one end ...
 
796
    Rec = #test_table{i=55},
 
797
    ?match({atomic, ok},
 
798
           mnesia:transaction(fun() -> mnesia:write(Rec) end)),
 
799
    
 
800
    %% ... and read it in the other
 
801
    ?match({atomic, [Rec]},
 
802
           rpc:call(N2, mnesia, transaction, 
 
803
                    [fun() -> mnesia:read({test_table, 55}) end])),
 
804
    
 
805
    
 
806
    %% Then do the same but start at the other end
 
807
    Rec2 = #test_table2{i=155},
 
808
    ?match({atomic, ok},
 
809
           rpc:call(N2, mnesia, transaction, 
 
810
                    [fun() ->
 
811
                             mnesia:write(Rec2) end
 
812
                    ])),
 
813
    
 
814
    ?match({atomic, [Rec2]},
 
815
           mnesia:transaction(fun() -> mnesia:read({test_table2, 155}) end)),
 
816
    
 
817
    ?verify_mnesia([N1, N2], []),
 
818
    ?cleanup(2, Config),
 
819
    ok.
 
820
    
 
821
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
822
start_first_one_disc_less_then_one_disc_full(doc)->
 
823
    ["no_doc"];
 
824
start_first_one_disc_less_then_one_disc_full(suite) -> [];
 
825
start_first_one_disc_less_then_one_disc_full(Config) when is_list(Config) ->
 
826
    [N1, N2] = Nodes = ?init(2, Config),
 
827
    ?match(ok, mnesia:create_schema([N1])),
 
828
    ?match([], mnesia_test_lib:start_mnesia([N1])),
 
829
 
 
830
    ?match({atomic, ok}, mnesia:add_table_copy(schema, N2, ram_copies)),
 
831
    
 
832
    ?match(ok, rpc:call(N2, mnesia, start, [[{schema_location, ram},
 
833
                                             {extra_db_nodes, Nodes}]])),
 
834
 
 
835
    mnesia_test_lib:sync_tables([N1, N2], [schema]),
 
836
    
 
837
    mnesia_test_lib:kill_mnesia(Nodes),
 
838
    receive after 2000 -> ok end,
 
839
    ?match([], mnesia_test_lib:start_mnesia(Nodes)),
 
840
 
 
841
    mnesia_test_lib:sync_tables([N1, N2], [schema]),
 
842
    
 
843
    %% Now create some tables
 
844
    ?match({atomic,ok},
 
845
           rpc:call(
 
846
             N1, mnesia,create_table, [test_table,
 
847
                                       [%%{disc_copies, [node()]},
 
848
                                        {ram_copies, [N1, N2]},
 
849
                                        {attributes,
 
850
                                         record_info(fields,test_table)}]])),
 
851
    mnesia_test_lib:sync_tables([N1, N2], [test_table]),
 
852
 
 
853
    ?match({atomic,ok},
 
854
           rpc:call(
 
855
             N2, mnesia,create_table, [test_table2,
 
856
                                       [%%{disc_copies, [node()]},
 
857
                                        {ram_copies, [N1, N2]},
 
858
                                        {attributes,
 
859
                                         record_info(fields,test_table2)}]])),
 
860
    
 
861
    mnesia_test_lib:sync_tables([N1, N2], [test_table, test_table2]),
 
862
 
 
863
    %% Assure tables loaded
 
864
    ?match({[ok, ok], []},
 
865
           rpc:multicall([N1, N2], mnesia, wait_for_tables,
 
866
                         [[schema, test_table, test_table2], 10000])),
 
867
    
 
868
    %% Write something on one end ...
 
869
    Rec = #test_table{i=55},
 
870
    ?match({atomic, ok},
 
871
           rpc:call(N1, mnesia, transaction, 
 
872
                    [fun() -> mnesia:write(Rec) end])),
 
873
    
 
874
    %% ... and read it in the other
 
875
    ?match({atomic, [Rec]},
 
876
           rpc:call(N2, mnesia, transaction, 
 
877
                    [fun() -> mnesia:read({test_table, 55}) end])),
 
878
    
 
879
    %% Then do the same but start at the other end
 
880
    Rec2 = #test_table2{i=155},
 
881
    ?match({atomic, ok},
 
882
           rpc:call(N2, mnesia, transaction, 
 
883
                    [fun() ->
 
884
                             mnesia:write(Rec2) end
 
885
                    ])),
 
886
    
 
887
    ?match({atomic, [Rec2]},
 
888
           rpc:call(N1, mnesia, transaction, 
 
889
                    [fun() -> mnesia:read({test_table2, 155}) end])),
 
890
    
 
891
    ?verify_mnesia(Nodes, []),
 
892
    ?cleanup(1, Config),
 
893
    ok.
 
894
 
 
895
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
896
start_first_one_disc_less_then_two_more_disc_less(doc)->
 
897
    ["no doc"];
 
898
start_first_one_disc_less_then_two_more_disc_less(suite) -> [];
 
899
start_first_one_disc_less_then_two_more_disc_less(Config) when is_list(Config) ->
 
900
    Nodes = [N1, N2, N3] = ?init(3, Config),
 
901
 
 
902
    ?match(ok, rpc:call(N1, mnesia, start, [[{schema_location, ram}]])),
 
903
 
 
904
    %% Really should use test_lib:mnesia_start for these ones but ...
 
905
    ?match({atomic, ok}, 
 
906
           rpc:call(N1, mnesia,add_table_copy, [schema, N2, ram_copies])),
 
907
    ?match({atomic, ok}, 
 
908
           rpc:call(N1, mnesia,add_table_copy, [schema, N3, ram_copies])),
 
909
    
 
910
    ?match(ok, rpc:call(N2, mnesia, start, [[{schema_location, ram},
 
911
                                             {extra_db_nodes, [N1]}]])),
 
912
    ?match(ok, rpc:call(N3, mnesia, start, [[{schema_location, ram},
 
913
                                             {extra_db_nodes, [N1, N2]}]])),
 
914
 
 
915
    %% Now create some tables
 
916
    ?match({atomic,ok},
 
917
           rpc:call(
 
918
             N1, mnesia,create_table, [test_table,
 
919
                                      [%%{disc_copies, [node()]},
 
920
                                       {ram_copies, [N1, N2, N3]},
 
921
                                       {attributes,
 
922
                                        record_info(fields,test_table)}]])),
 
923
 
 
924
    %% Assure tables loaded
 
925
    ?match({[ok, ok, ok], []},
 
926
           rpc:multicall([N1, N2, N3], mnesia, wait_for_tables,
 
927
                         [[test_table], 1000])),
 
928
 
 
929
    %% Write something on one end ...
 
930
    ?match({atomic, ok},
 
931
           rpc:call(N1, mnesia, transaction, 
 
932
                    [fun() -> mnesia:write(#test_table{i=44}) end])),
 
933
 
 
934
    %% Force synchronicity
 
935
    ?match({atomic, ok},
 
936
           rpc:call(N1, mnesia, transaction, 
 
937
                    [fun() -> mnesia:write_lock_table(test_table) end])),
 
938
    
 
939
    %% ... and read it in the others
 
940
    ?match({[{atomic, [{test_table, 44, _, _, _}]},
 
941
             {atomic, [{test_table, 44, _, _, _}]}], []},
 
942
           rpc:multicall([N2, N3], mnesia, transaction, 
 
943
                         [fun() -> mnesia:read({test_table, 44}) end])),
 
944
    
 
945
    %% Then do the other way around
 
946
    ?match({atomic, ok},
 
947
           rpc:call(N3, mnesia, transaction, 
 
948
                    [fun() -> mnesia:write(#test_table{i=33}) end])),
 
949
    %% Force synchronicity
 
950
    ?match({atomic, ok},
 
951
           rpc:call(N3, mnesia, transaction, 
 
952
                    [fun() -> mnesia:write_lock_table(test_table) end])),
 
953
    
 
954
    ?match({[{atomic, [{test_table, 44, _, _, _}]},
 
955
             {atomic, [{test_table, 44, _, _, _}]}], []},
 
956
           rpc:multicall([N1, N2], mnesia, transaction, 
 
957
                         [fun() -> mnesia:read({test_table, 44}) end])),
 
958
 
 
959
    mnesia_test_lib:reload_appls([mnesia], Nodes),
 
960
    ok.
 
961
 
 
962
 
 
963
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
964
schema_location_and_extra_db_nodes_combinations(doc)->
 
965
    ["Test schema loaction and extra_db_nodes combinations."];
 
966
schema_location_and_extra_db_nodes_combinations(suite) -> [];
 
967
schema_location_and_extra_db_nodes_combinations(Config) when is_list(Config) ->
 
968
    [N1, N2] = Nodes = ?init(2, Config),
 
969
    ?match(ok, mnesia:create_schema([N1])),
 
970
    ?match([], mnesia_test_lib:start_mnesia([N1])),
 
971
    
 
972
    %% Really should use test_lib:mnesia_start for these ones but ...
 
973
    ?match({atomic, ok}, 
 
974
           rpc:call(N1, mnesia,add_table_copy, [schema, N2, ram_copies])),
 
975
    
 
976
    ?match(ok, rpc:call(N2, mnesia, start, [[{schema_location, ram},
 
977
                                             {extra_db_nodes, [N1]}]])),
 
978
    
 
979
    %% Assure tables loaded
 
980
    ?match({[ok, ok], []},
 
981
           rpc:multicall([N1, N2], mnesia, wait_for_tables,
 
982
                         [[schema], 10000])),
 
983
    
 
984
    ?verify_mnesia(Nodes, []),
 
985
    ?cleanup(2, Config),
 
986
    ok.
 
987
 
 
988
 
 
989
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
990
table_load_to_disc_less_nodes(doc)->
 
991
    ["Load tables to disc less nodes"];
 
992
table_load_to_disc_less_nodes(suite) -> [];
 
993
table_load_to_disc_less_nodes(Config) when is_list(Config) ->
 
994
    [N1, N2] = ?init(2, Config),
 
995
 
 
996
    ?match(ok, rpc:call(N1, mnesia, start, [[{schema_location, ram}]])),
 
997
 
 
998
    %% Really should use test_lib:mnesia_start for these ones but ...
 
999
    ?match({atomic, ok}, 
 
1000
           rpc:call(N1, mnesia,add_table_copy, [schema, N2, ram_copies])),
 
1001
    
 
1002
    ?match(ok, rpc:call(N2, mnesia, start, [[{schema_location, ram},
 
1003
                                             {extra_db_nodes, [N1]}]])),
 
1004
 
 
1005
    %% Now create some tables
 
1006
    ?match({atomic,ok},
 
1007
           rpc:call(
 
1008
             N1, mnesia,create_table, [test_table,
 
1009
                                      [%%{disc_copies, [node()]},
 
1010
                                       {ram_copies, [N1, N2]},
 
1011
                                       {attributes,
 
1012
                                        record_info(fields,test_table)}]])),
 
1013
 
 
1014
    %% Assure tables loaded
 
1015
    ?match({[ok, ok], []},
 
1016
           rpc:multicall([N1, N2], mnesia, wait_for_tables,
 
1017
                         [[test_table], 1000])),
 
1018
 
 
1019
    %% Write something on one end ...
 
1020
    ?match({atomic, ok},
 
1021
           rpc:call(N1, mnesia, transaction, 
 
1022
                    [fun() -> mnesia:write(#test_table{i=44}) end])),
 
1023
 
 
1024
    %% Force synchronicity
 
1025
    ?match({atomic, ok},
 
1026
           rpc:call(N1, mnesia, transaction, 
 
1027
                    [fun() -> mnesia:write_lock_table(test_table) end])),
 
1028
    
 
1029
    %% ... and read it in the others
 
1030
    ?match({atomic, [{test_table, 44, _, _, _}]},
 
1031
           rpc:call(N2, mnesia, transaction, 
 
1032
                    [fun() -> mnesia:read({test_table, 44}) end])),
 
1033
 
 
1034
    ?cleanup(2, Config),
 
1035
    ok.
 
1036
    
 
1037
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1038
schema_merge(doc) ->
 
1039
    ["Provoke various schema merge situations.",
 
1040
     "Perform various schema updates while some nodes are down,",
 
1041
     "stop the started nodes, start the stopped nodes and perform",
 
1042
     "schema updates. Now we have a situation were some of the table",
 
1043
     "definitions have been changed on two or more nodes independently",
 
1044
     "of each other and when Mnesia on the nodes tries to connect",
 
1045
     "to each other at restart the schema will be merged.",
 
1046
     "Do also try to provoke schema merge situations were the",
 
1047
     "schema cannot be merged."];
 
1048
 
 
1049
schema_merge(suite) -> [];
 
1050
 
 
1051
schema_merge(Config) when is_list(Config) ->
 
1052
    [N1, N2]=Nodes=?acquire(2,Config),
 
1053
    
 
1054
    mnesia_test_lib:kill_mnesia([N2]),    
 
1055
    receive after 1000 -> ok end,
 
1056
 
 
1057
    Storage = mnesia_test_lib:storage_type(disc_copies, Config),    
 
1058
    ?match({atomic,ok},
 
1059
           rpc:call(
 
1060
             N1, mnesia,create_table, 
 
1061
             [test_table,
 
1062
              [{Storage, [N1]},
 
1063
               {attributes,
 
1064
                record_info(fields,test_table)}]])),
 
1065
    
 
1066
    ?match({atomic, ok},
 
1067
           rpc:call(N1, mnesia, transaction, 
 
1068
                    [fun() -> mnesia:write(#test_table{i=44}) end])),
 
1069
 
 
1070
    mnesia_test_lib:kill_mnesia([N1]),
 
1071
    receive after 2000 -> ok end,
 
1072
    %% Can't use std start because it waits for schema
 
1073
    ?match(ok, rpc:call(N2, mnesia, start, [])),
 
1074
 
 
1075
    ?match({atomic,ok},
 
1076
           rpc:call(
 
1077
             N2, mnesia,create_table, 
 
1078
             [test_table2,
 
1079
              [{Storage, [N2]},
 
1080
               {attributes,
 
1081
                record_info(fields,test_table2)}]])),
 
1082
    
 
1083
    receive after 5000 -> ok end,
 
1084
 
 
1085
    ?match({atomic, ok},
 
1086
           rpc:call(N2, mnesia, transaction, 
 
1087
                    [fun() -> mnesia:write(#test_table2{i=33}) end])),
 
1088
    
 
1089
    %% Can't use std start because it waits for schema
 
1090
    ?match(ok, rpc:call(N1, mnesia, start, [])),
 
1091
 
 
1092
    %% Assure tables loaded
 
1093
    ?match({[ok, ok], []},
 
1094
           rpc:multicall([N1, N2], mnesia, wait_for_tables,
 
1095
                         [[schema, test_table, test_table2], 10000])),
 
1096
    
 
1097
    %% ... and read it in the others
 
1098
    ?match({[{atomic, [{test_table, 44, _, _, _}]},
 
1099
             {atomic, [{test_table, 44, _, _, _}]}], []},
 
1100
           rpc:multicall([N1, N2], mnesia, transaction, 
 
1101
                         [fun() -> mnesia:read({test_table, 44}) end])),
 
1102
    
 
1103
    ?match({[{atomic, [{test_table2, 33, _}]},
 
1104
             {atomic, [{test_table2, 33, _}]}], []},
 
1105
           rpc:multicall([N1, N2], mnesia, transaction, 
 
1106
                         [fun() -> mnesia:read({test_table2, 33}) end])),
 
1107
    
 
1108
    ?verify_mnesia(Nodes, []),
 
1109
    ?cleanup(2, Config),
 
1110
    ok.
 
1111
 
 
1112
 
 
1113
-define(connect(Nodes), mnesia:change_config(extra_db_nodes, Nodes)).
 
1114
-define(rpc_connect(From, Nodes), 
 
1115
        rpc:call(From, mnesia, change_config, [extra_db_nodes, Nodes])).
 
1116
 
 
1117
 
 
1118
sort({ok, NS}) ->
 
1119
    {ok, lists:sort(NS)};
 
1120
sort(Ns) when is_tuple(Ns) ->
 
1121
    Ns;
 
1122
sort(NS) when is_list(NS) -> 
 
1123
    lists:sort(NS).
 
1124
 
 
1125
 
 
1126
 
 
1127
 
 
1128
dynamic_basic(suite) -> [];
 
1129
dynamic_basic(Config) when is_list(Config) ->
 
1130
    Nodes = [N1, N2, N3] = ?acquire_nodes(3, Config),
 
1131
    SNs = lists:sort(Nodes),    
 
1132
 
 
1133
    ?match({atomic, ok}, mnesia:create_table(tab1, [{ram_copies, Nodes--[N1]}, {disc_copies, [N1]}])),
 
1134
    ?match({atomic, ok}, mnesia:create_table(tab2, [{disc_copies, Nodes}])),
 
1135
 
 
1136
    ?match({ok, SNs}, sort(?rpc_connect(N1, Nodes))),     %% What shall happen?
 
1137
    ?match({ok, []}, sort(?rpc_connect(N1, [nonode@nothosted]))),  %% What shall happen?
 
1138
    
 
1139
    ?match([], mnesia_test_lib:kill_mnesia([N2])),
 
1140
    ?match(ok, mnesia:delete_schema([N2])),
 
1141
 
 
1142
    ?match(ok, mnesia:dirty_write({tab1, 1, 1})),
 
1143
    ?match(ok, mnesia:dirty_write({tab2, 1, 1})),
 
1144
   
 
1145
    ?match(ok, rpc:call(N2, mnesia, start, [[{extra_db_nodes, [N1]}]])),
 
1146
    ?match(ok, rpc:call(N2, mnesia, wait_for_tables, [[tab1,tab2],5000])),
 
1147
    io:format("Here ~p ~n",[?LINE]), 
 
1148
    check_storage(N2, N1, [N3]),
 
1149
    ?match(SNs, sort(rpc:call(N1, mnesia, system_info, [running_db_nodes]))),
 
1150
    ?match(SNs, sort(rpc:call(N2, mnesia, system_info, [running_db_nodes]))),
 
1151
 
 
1152
    ?match([], mnesia_test_lib:kill_mnesia([N3])),
 
1153
    ?match(ok, mnesia:delete_schema([N3])),
 
1154
    
 
1155
    io:format("T1 ~p ~n",[rpc:call(N3,?MODULE,c_nodes,[])]),
 
1156
    ?match(ok, rpc:call(N3, mnesia, start, [])),
 
1157
    io:format("T2 ~p ~n",[rpc:call(N3,?MODULE,c_nodes,[])]),
 
1158
    timer:sleep(2000),
 
1159
    io:format("T3 ~p ~n",[rpc:call(N3,?MODULE,c_nodes,[])]),
 
1160
    ?match({ok, [N1]}, sort(?rpc_connect(N3, [N1]))),
 
1161
    io:format("T4 ~p ~n",[rpc:call(N3,?MODULE,c_nodes,[])]),
 
1162
    ?match(ok, rpc:call(N3, mnesia, wait_for_tables, [[tab1,tab2],5000])),
 
1163
    io:format("Here ~p ~n",[?LINE]), 
 
1164
    check_storage(N3, N1, [N2]),
 
1165
    ?match(SNs, sort(rpc:call(N1, mnesia, system_info, [running_db_nodes]))),
 
1166
    ?match(SNs, sort(rpc:call(N2, mnesia, system_info, [running_db_nodes]))),
 
1167
    
 
1168
    ?match([], mnesia_test_lib:kill_mnesia([N3])),
 
1169
    ?match(ok, mnesia:delete_schema([N3])),
 
1170
    
 
1171
    ?match(ok, rpc:call(N3, mnesia, start, [])),
 
1172
    ?match({ok, [N3]}, sort(?rpc_connect(N1, [N3]))),
 
1173
    ?match(ok, rpc:call(N3, mnesia, wait_for_tables, [[tab1,tab2],5000])),
 
1174
    io:format("Here ~p ~n",[?LINE]), 
 
1175
    check_storage(N3, N1, [N2]),
 
1176
    ?match(SNs, sort(rpc:call(N1, mnesia, system_info, [running_db_nodes]))),
 
1177
    ?match(SNs, sort(rpc:call(N2, mnesia, system_info, [running_db_nodes]))),
 
1178
 
 
1179
    mnesia_test_lib:kill_mnesia([N2]),
 
1180
    ?match(ok, mnesia:delete_schema([N2])),
 
1181
    ?match({atomic, ok}, mnesia:del_table_copy(schema, N2)),
 
1182
 
 
1183
    % Ok, we have now removed references to node N2 from the other nodes
 
1184
    % mnesia should come up now.
 
1185
    ?match({atomic, ok}, mnesia:add_table_copy(tab1, N2, ram_copies)),
 
1186
 
 
1187
    ?match(ok, rpc:call(N2, mnesia, start, [])),
 
1188
    ?match({ok, _}, sort(?rpc_connect(N2, [N3]))),
 
1189
    
 
1190
    ?match(SNs, sort(rpc:call(N1, mnesia, system_info, [running_db_nodes]))),
 
1191
    ?match(SNs, sort(rpc:call(N2, mnesia, system_info, [running_db_nodes]))),
 
1192
    ?match(SNs, sort(rpc:call(N3, mnesia, system_info, [running_db_nodes]))),
 
1193
 
 
1194
    ?match(ok, rpc:call(N2, mnesia, wait_for_tables, [[tab1], 1000])),
 
1195
    ?match([{tab1, 1, 1}], rpc:call(N2, mnesia, dirty_read, [tab1, 1])),
 
1196
       
 
1197
    mnesia_test_lib:kill_mnesia([N2]),
 
1198
 
 
1199
    %%% SYNC!!!
 
1200
    timer:sleep(1000),
 
1201
 
 
1202
    ?match([N3,N1], sort(rpc:call(N1, mnesia, system_info, [running_db_nodes]))),
 
1203
    ?match([N3,N1], sort(rpc:call(N3, mnesia, system_info, [running_db_nodes]))),
 
1204
    
 
1205
    ?match(ok, rpc:call(N2, mnesia, start, [])),
 
1206
    ?match({ok, _}, sort(?rpc_connect(N3, [N2]))),
 
1207
    
 
1208
    ?match(SNs, sort(rpc:call(N1, mnesia, system_info, [running_db_nodes]))),
 
1209
    ?match(SNs, sort(rpc:call(N2, mnesia, system_info, [running_db_nodes]))),
 
1210
    ?match(SNs, sort(rpc:call(N3, mnesia, system_info, [running_db_nodes]))),
 
1211
 
 
1212
    ?match(ok, rpc:call(N2, mnesia, wait_for_tables, [[tab1], 1000])),
 
1213
    ?match([{tab1, 1, 1}], rpc:call(N2, mnesia, dirty_read, [tab1, 1])),
 
1214
 
 
1215
    ?verify_mnesia(Nodes, []),
 
1216
%%    ?cleanup(3, Config).
 
1217
    ok.
 
1218
 
 
1219
c_nodes() ->                                                            
 
1220
    {mnesia_lib:val({current, db_nodes}),mnesia_lib:val(recover_nodes)}.
 
1221
 
 
1222
 
 
1223
dynamic_ext(suite) ->    [];
 
1224
dynamic_ext(Config) when is_list(Config) ->
 
1225
    Ns = [N1,N2] = ?acquire_nodes(2, Config),
 
1226
    SNs = lists:sort([N1,N2]),
 
1227
    
 
1228
    ?match({atomic, ok}, mnesia:create_table(tab0, [{disc_copies, [N1,N2]}])),
 
1229
    ?match({atomic, ok}, mnesia:create_table(tab1, [{ram_copies, [N2]}])),
 
1230
    ?match({atomic, ok}, mnesia:create_table(tab2, [{disc_copies, [N2]}])),
 
1231
    ?match({atomic, ok}, mnesia:create_table(tab3, [{disc_only_copies, [N2]}])),
 
1232
    
 
1233
    mnesia_test_lib:kill_mnesia([N2]),
 
1234
    ?match(ok, mnesia:delete_schema([N2])),
 
1235
    ?match(ok, rpc:call(N2, mnesia, start, [[{extra_db_nodes, [N1]}]])),
 
1236
    
 
1237
    ?match(SNs, sort(rpc:call(N1, mnesia, system_info, [running_db_nodes]))),
 
1238
    ?match(SNs, sort(rpc:call(N2, mnesia, system_info, [running_db_nodes]))),
 
1239
    
 
1240
    ?match(ok, rpc:call(N2, mnesia, wait_for_tables, [[tab0,tab1,tab2,tab3], 2000])),
 
1241
 
 
1242
    Check = fun({Tab,Storage}) ->
 
1243
                    ?match(Storage, rpc:call(N2, mnesia, table_info, [Tab, storage_type])),
 
1244
                    ?match([{N2,Storage}], 
 
1245
                           lists:sort(rpc:call(N2, mnesia, table_info, [Tab, where_to_commit])))
 
1246
            end,
 
1247
    [Check(Test) || Test <- [{tab1, ram_copies},{tab2, disc_copies},{tab3, disc_only_copies}]],
 
1248
    
 
1249
    T = now(),
 
1250
    ?match(ok, mnesia:dirty_write({tab0, 42, T})),
 
1251
    ?match(ok, mnesia:dirty_write({tab1, 42, T})),
 
1252
    ?match(ok, mnesia:dirty_write({tab2, 42, T})),
 
1253
    ?match(ok, mnesia:dirty_write({tab3, 42, T})),
 
1254
    
 
1255
    ?match(stopped, rpc:call(N2, mnesia, stop, [])),
 
1256
    ?match(ok, rpc:call(N2, mnesia, start, [])),
 
1257
    ?match(SNs, sort(rpc:call(N2, mnesia, system_info, [running_db_nodes]))),
 
1258
    ?match(ok, mnesia:wait_for_tables([tab0,tab1,tab2,tab3], 10000)),
 
1259
    ?match(ok, rpc:call(N2, mnesia, wait_for_tables, [[tab1,tab2,tab3], 100])),
 
1260
    ?match([], mnesia:dirty_read({tab1, 41})),
 
1261
    ?match([{tab2,42,T}], mnesia:dirty_read({tab2, 42})),
 
1262
    ?match([{tab3,42,T}], mnesia:dirty_read({tab3, 42})),
 
1263
 
 
1264
    mnesia_test_lib:kill_mnesia([N2]),
 
1265
    ?match(ok, mnesia:delete_schema([N2])),
 
1266
 
 
1267
    ?match(stopped, rpc:call(N1, mnesia, stop, [])),
 
1268
 
 
1269
    ?match(ok, rpc:call(N2, mnesia, start, [[{extra_db_nodes,[N1,N2]}]])),
 
1270
    ?match({timeout,[tab0]}, rpc:call(N2, mnesia, wait_for_tables, [[tab0], 500])),
 
1271
 
 
1272
    ?match(ok, rpc:call(N1, mnesia, start, [[{extra_db_nodes, [N1,N2]}]])),
 
1273
    ?match(ok, rpc:call(N1, mnesia, wait_for_tables, [[tab0], 1500])),
 
1274
    ?match(ok, rpc:call(N2, mnesia, wait_for_tables, [[tab0], 1500])),
 
1275
    ?match([{tab0,42,T}], mnesia:dirty_read({tab0, 42})),
 
1276
    ?match([{tab0,42,T}], rpc:call(N2, mnesia,dirty_read,[{tab0,42}])),
 
1277
 
 
1278
    ?match(stopped, rpc:call(N1, mnesia, stop, [])),
 
1279
    mnesia_test_lib:kill_mnesia([N2]),
 
1280
    ?match(ok, mnesia:delete_schema([N2])),
 
1281
    ?match(ok, rpc:call(N1, mnesia, start, [[{extra_db_nodes, [N1,N2]}]])),   
 
1282
    ?match({timeout,[tab0]}, rpc:call(N1, mnesia, wait_for_tables, [[tab0], 500])),
 
1283
 
 
1284
    ?match(ok, rpc:call(N2, mnesia, start, [[{extra_db_nodes,[N1,N2]}]])),
 
1285
    ?match(ok, rpc:call(N1, mnesia, wait_for_tables, [[tab0], 1500])),
 
1286
    ?match(ok, rpc:call(N2, mnesia, wait_for_tables, [[tab0], 1500])),
 
1287
    ?match([{tab0,42,T}], mnesia:dirty_read({tab0, 42})),
 
1288
    ?match([{tab0,42,T}], rpc:call(N2,mnesia,dirty_read,[{tab0,42}])),
 
1289
 
 
1290
    ?verify_mnesia(Ns, []),
 
1291
    ok.
 
1292
 
 
1293
check_storage(Me, Orig, Other) ->
 
1294
    io:format("Nodes ~p ~p ~p~n",[Me,Orig,Other]),
 
1295
    rpc:multicall(Other, sys, status, [mnesia_locker]),
 
1296
    rpc:call(Me, sys, status, [mnesia_locker]),
 
1297
    rpc:call(Orig, sys, status, [mnesia_locker]),
 
1298
    rpc:multicall(Other, sys, status, [mnesia_controller]),
 
1299
    rpc:call(Me, sys, status, [mnesia_controller]),
 
1300
    rpc:call(Orig, sys, status, [mnesia_controller]),
 
1301
    %% Verify disc_copies
 
1302
    W2C = lists:sort([{Node,disc_copies} || Node <- [Me,Orig|Other]]),
 
1303
    W2W = lists:sort([Me,Orig|Other]),
 
1304
    ?match(disc_copies, rpc:call(Orig, mnesia, table_info, [schema, storage_type])),
 
1305
    ?match(disc_copies, rpc:call(Me, mnesia, table_info, [schema, storage_type])),
 
1306
    ?match(W2C, lists:sort(rpc:call(Orig, mnesia, table_info, [schema, where_to_commit]))),
 
1307
    ?match(W2C, lists:sort(rpc:call(Me, mnesia, table_info, [schema, where_to_commit]))),
 
1308
    
 
1309
    ?match(disc_copies, rpc:call(Orig, mnesia, table_info, [tab2, storage_type])),
 
1310
    ?match(disc_copies, rpc:call(Me, mnesia, table_info, [tab2, storage_type])),    
 
1311
    ?match(W2W, lists:sort(rpc:call(Me, mnesia, table_info, [tab2, where_to_write]))),    
 
1312
    ?match(Me, rpc:call(Me, mnesia, table_info, [tab2, where_to_read])),    
 
1313
    
 
1314
    ?match(W2C, lists:sort(rpc:call(Orig, mnesia, table_info, [tab2, where_to_commit]))),
 
1315
    ?match(W2C, lists:sort(rpc:call(Me, mnesia, table_info, [tab2, where_to_commit]))),
 
1316
    
 
1317
    ?match([{tab1,1,1}], mnesia:dirty_read(tab1,1)),
 
1318
    ?match([{tab2,1,1}], mnesia:dirty_read(tab2,1)),
 
1319
    ?match([{tab1,1,1}], rpc:call(Me, mnesia, dirty_read, [tab1,1])),
 
1320
    ?match([{tab2,1,1}], rpc:call(Me, mnesia, dirty_read, [tab2,1])),
 
1321
 
 
1322
    ?match(true, rpc:call(Me, mnesia_monitor, use_dir, [])),
 
1323
    ?match(disc_copies, rpc:call(Me, mnesia_lib, val, [{schema, storage_type}])),
 
1324
    
 
1325
    mnesia_test_lib:kill_mnesia([Orig]),
 
1326
    mnesia_test_lib:kill_mnesia(Other),
 
1327
    T = now(),
 
1328
    ?match(ok, rpc:call(Me, mnesia, dirty_write, [{tab2, 42, T}])),
 
1329
    ?match(stopped, rpc:call(Me, mnesia, stop, [])),
 
1330
    ?match(ok, rpc:call(Me, mnesia, start, [])),   
 
1331
    ?match([], mnesia_test_lib:start_mnesia([Orig|Other], [tab1,tab2])),
 
1332
    ?match([{tab2,42,T}], rpc:call(Me, mnesia, dirty_read, [{tab2, 42}])),
 
1333
    ?match([{tab2,42,T}], rpc:call(Orig, mnesia, dirty_read, [{tab2, 42}])),
 
1334
    
 
1335
    ?match([{tab1,1,1}], mnesia:dirty_read(tab1,1)),
 
1336
    ?match([{tab2,1,1}], mnesia:dirty_read(tab2,1)),
 
1337
    ?match([{tab1,1,1}], rpc:call(Me, mnesia, dirty_read, [tab1,1])),
 
1338
    ?match([{tab2,1,1}], rpc:call(Me, mnesia, dirty_read, [tab2,1])),    
 
1339
    ok.
 
1340
    
 
1341
 
 
1342
dynamic_bad(suite) ->    [];
 
1343
dynamic_bad(Config) when is_list(Config) ->
 
1344
    Ns = [N1, N2, N3] = ?acquire_nodes(3, Config),
 
1345
    SNs = lists:sort([N2,N3]), 
 
1346
 
 
1347
    ?match({atomic, ok}, mnesia:change_table_copy_type(schema, N2, ram_copies)),
 
1348
    ?match({atomic, ok}, mnesia:change_table_copy_type(schema, N3, ram_copies)),
 
1349
    ?match({atomic, ok}, mnesia:create_table(tab1, [{ram_copies, Ns -- [N1]},
 
1350
                                                    {disc_copies, [N1]}])),
 
1351
    ?match(ok, mnesia:dirty_write({tab1, 1, 1})),
 
1352
    
 
1353
    mnesia_test_lib:kill_mnesia(Ns),
 
1354
    ?match({[ok, ok], []}, rpc:multicall(Ns -- [N1], mnesia, start, [])),
 
1355
    ?match({ok, [N2]}, ?rpc_connect(N3, [N2])),
 
1356
    ?match(SNs, sort(rpc:call(N2, mnesia, system_info, [running_db_nodes]))),
 
1357
    ?match(SNs, sort(rpc:call(N3, mnesia, system_info, [running_db_nodes]))),
 
1358
    ?match({badrpc, {'EXIT', {aborted, {no_exists, _, _}}}},
 
1359
           rpc:call(N2, mnesia, table_info, [tab1, where_to_read])),
 
1360
    
 
1361
    ?match(ok, mnesia:start()),
 
1362
    ?match(ok, rpc:call(N2, mnesia, wait_for_tables, [[tab1], 1000])),
 
1363
    ?match(N2, rpc:call(N2, mnesia, table_info, [tab1, where_to_read])), 
 
1364
    ?match([{tab1, 1, 1}], rpc:call(N2, mnesia, dirty_read, [tab1, 1])),
 
1365
    
 
1366
    mnesia_test_lib:kill_mnesia(Ns),
 
1367
    ?match({[ok, ok], []}, rpc:multicall(Ns -- [N1], mnesia, start, [])),
 
1368
    ?match({ok, [N2]}, ?rpc_connect(N3, [N2])),
 
1369
    % Make a merge conflict
 
1370
    ?match({atomic, ok}, rpc:call(N3, mnesia, create_table, [tab1, []])),
 
1371
    
 
1372
    io:format("We expect a mnesia crash here~n", []),
 
1373
    ?match({error,{_, _}}, mnesia:start()),
 
1374
 
 
1375
    ?verify_mnesia(Ns -- [N1], []),
 
1376
    ok.
 
1377
 
 
1378
 
 
1379
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1380
unknown_config(doc) ->
 
1381
    ["Try some unknown configuration parameters and see that expected",
 
1382
     "things happens."];
 
1383
unknown_config(suite)-> [];
 
1384
unknown_config(Config) when is_list(Config) ->
 
1385
    ?init(1, Config),
 
1386
    %% NOTE: case 1 & 2 below do not respond the same
 
1387
    ?match({error, Res} when element(1, Res) == bad_type,
 
1388
           mnesia:start([{undefined_config,[]}])),
 
1389
    %% Below does not work, but the "correct" behaviour would be to have
 
1390
    %% case 1 above to behave as the one below.
 
1391
 
 
1392
    %% in mnesia-1.3 {error,{bad_type,{[],undefined_config}}}
 
1393
    ?match({error, Res} when element(1, Res) == bad_type,
 
1394
           mnesia:start([{[],undefined_config}])),
 
1395
    ?cleanup(1, Config),
 
1396
    ok.
 
1397
 
 
1398
 
 
1399
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1400
inconsistent_database(doc) ->
 
1401
    ["Replace the event module with another module and use it as",
 
1402
     "receiver of the various system and table events. Provoke",
 
1403
     "coverage of all kinds of events."];
 
1404
inconsistent_database(suite) -> [];
 
1405
inconsistent_database(Config) when is_list(Config) ->
 
1406
    Nodes = mnesia_test_lib:prepare_test_case([{init_test_case, [mnesia]}], 
 
1407
                                              2, Config, ?FILE, ?LINE),
 
1408
    KillAfter = length(Nodes) * timer:minutes(5),
 
1409
    ?acquire_schema(2, Config ++ [{tc_timeout, KillAfter}]),
 
1410
 
 
1411
    Ok = [ok || _N <- Nodes],
 
1412
    StartArgs = [{event_module, mnesia_inconsistent_database_test}],
 
1413
    ?match({Ok, []}, rpc:multicall(Nodes, mnesia, start, [StartArgs])),
 
1414
    ?match([], mnesia_test_lib:kill_mnesia(Nodes)),
 
1415
    
 
1416
    ?match(ok, mnesia_meter:go(ram_copies, Nodes)),
 
1417
 
 
1418
    mnesia_test_lib:reload_appls([mnesia], Nodes),
 
1419
    ok.
 
1420