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

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_consistency_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_consistency_test).
 
22
-author('hakan@erix.ericsson.se').
 
23
-compile([export_all]).
 
24
 
 
25
-include("mnesia_test_lib.hrl").
 
26
 
 
27
init_per_testcase(Func, Conf) ->
 
28
    mnesia_test_lib:init_per_testcase(Func, Conf).
 
29
 
 
30
end_per_testcase(Func, Conf) ->
 
31
    mnesia_test_lib:end_per_testcase(Func, Conf).
 
32
 
 
33
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
34
all() -> 
 
35
    [{group, consistency_after_restart},
 
36
     {group, consistency_after_dump_tables},
 
37
     {group, consistency_after_add_replica},
 
38
     {group, consistency_after_del_replica},
 
39
     {group, consistency_after_move_replica},
 
40
     {group, consistency_after_transform_table},
 
41
     consistency_after_change_table_copy_type,
 
42
     {group, consistency_after_fallback},
 
43
     {group, consistency_after_restore},
 
44
     consistency_after_rename_of_node,
 
45
     {group, checkpoint_retainer_consistency},
 
46
     {group, backup_consistency}].
 
47
 
 
48
groups() -> 
 
49
    [{consistency_after_restart, [],
 
50
      [consistency_after_restart_1_ram,
 
51
       consistency_after_restart_1_disc,
 
52
       consistency_after_restart_1_disc_only,
 
53
       consistency_after_restart_2_ram,
 
54
       consistency_after_restart_2_disc,
 
55
       consistency_after_restart_2_disc_only]},
 
56
     {consistency_after_dump_tables, [],
 
57
      [consistency_after_dump_tables_1_ram,
 
58
       consistency_after_dump_tables_2_ram]},
 
59
     {consistency_after_add_replica, [],
 
60
      [consistency_after_add_replica_2_ram,
 
61
       consistency_after_add_replica_2_disc,
 
62
       consistency_after_add_replica_2_disc_only,
 
63
       consistency_after_add_replica_3_ram,
 
64
       consistency_after_add_replica_3_disc,
 
65
       consistency_after_add_replica_3_disc_only]},
 
66
     {consistency_after_del_replica, [],
 
67
      [consistency_after_del_replica_2_ram,
 
68
       consistency_after_del_replica_2_disc,
 
69
       consistency_after_del_replica_2_disc_only,
 
70
       consistency_after_del_replica_3_ram,
 
71
       consistency_after_del_replica_3_disc,
 
72
       consistency_after_del_replica_3_disc_only]},
 
73
     {consistency_after_move_replica, [],
 
74
      [consistency_after_move_replica_2_ram,
 
75
       consistency_after_move_replica_2_disc,
 
76
       consistency_after_move_replica_2_disc_only,
 
77
       consistency_after_move_replica_3_ram,
 
78
       consistency_after_move_replica_3_disc,
 
79
       consistency_after_move_replica_3_disc_only]},
 
80
     {consistency_after_transform_table, [],
 
81
      [consistency_after_transform_table_ram,
 
82
       consistency_after_transform_table_disc,
 
83
       consistency_after_transform_table_disc_only]},
 
84
     {consistency_after_fallback, [],
 
85
      [consistency_after_fallback_2_ram,
 
86
       consistency_after_fallback_2_disc,
 
87
       consistency_after_fallback_2_disc_only,
 
88
       consistency_after_fallback_3_ram,
 
89
       consistency_after_fallback_3_disc,
 
90
       consistency_after_fallback_3_disc_only]},
 
91
     {consistency_after_restore, [],
 
92
      [consistency_after_restore_clear_ram,
 
93
       consistency_after_restore_clear_disc,
 
94
       consistency_after_restore_clear_disc_only,
 
95
       consistency_after_restore_recreate_ram,
 
96
       consistency_after_restore_recreate_disc,
 
97
       consistency_after_restore_recreate_disc_only]},
 
98
     {checkpoint_retainer_consistency, [],
 
99
      [{group, updates_during_checkpoint_activation},
 
100
       {group, updates_during_checkpoint_iteration},
 
101
       {group, load_table_with_activated_checkpoint},
 
102
       {group,
 
103
        add_table_copy_to_table_with_activated_checkpoint}]},
 
104
     {updates_during_checkpoint_activation, [],
 
105
      [updates_during_checkpoint_activation_2_ram,
 
106
       updates_during_checkpoint_activation_2_disc,
 
107
       updates_during_checkpoint_activation_2_disc_only,
 
108
       updates_during_checkpoint_activation_3_ram,
 
109
       updates_during_checkpoint_activation_3_disc,
 
110
       updates_during_checkpoint_activation_3_disc_only]},
 
111
     {updates_during_checkpoint_iteration, [],
 
112
      [updates_during_checkpoint_iteration_2_ram,
 
113
       updates_during_checkpoint_iteration_2_disc,
 
114
       updates_during_checkpoint_iteration_2_disc_only]},
 
115
     {load_table_with_activated_checkpoint, [],
 
116
      [load_table_with_activated_checkpoint_ram,
 
117
       load_table_with_activated_checkpoint_disc,
 
118
       load_table_with_activated_checkpoint_disc_only]},
 
119
     {add_table_copy_to_table_with_activated_checkpoint, [],
 
120
      [add_table_copy_to_table_with_activated_checkpoint_ram,
 
121
       add_table_copy_to_table_with_activated_checkpoint_disc,
 
122
       add_table_copy_to_table_with_activated_checkpoint_disc_only]},
 
123
     {backup_consistency, [],
 
124
      [{group, interupted_install_fallback},
 
125
       {group, interupted_uninstall_fallback},
 
126
       {group, mnesia_down_during_backup_causes_switch},
 
127
       {group, mnesia_down_during_backup_causes_abort},
 
128
       {group, schema_transactions_during_backup}]},
 
129
     {interupted_install_fallback, [],
 
130
      [inst_fallback_process_dies, fatal_when_inconsistency]},
 
131
     {interupted_uninstall_fallback, [], [after_delete]},
 
132
     {mnesia_down_during_backup_causes_switch, [],
 
133
      [cause_switch_before, cause_switch_after]},
 
134
     {mnesia_down_during_backup_causes_abort, [],
 
135
      [cause_abort_before, cause_abort_after]},
 
136
     {schema_transactions_during_backup, [],
 
137
      [change_schema_before, change_schema_after]}].
 
138
 
 
139
init_per_group(_GroupName, Config) ->
 
140
    Config.
 
141
 
 
142
end_per_group(_GroupName, Config) ->
 
143
    Config.
 
144
 
 
145
 
 
146
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
147
%
 
148
%  stolen from mnesia_tpcb.erl:
 
149
 
 
150
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
151
%%% Account record, total size must be at least 100 bytes
 
152
 
 
153
-define(ACCOUNT_FILLER,
 
154
        {123456789012345678901234567890123456789012345678901234567890,
 
155
         123456789012345678901234567890123456789012345678901234567890,
 
156
         123456789012345678901234567890123456789012345678901234}).
 
157
 
 
158
-record(account,
 
159
       {
 
160
        id           = 0, %% Unique account id
 
161
        branch_id    = 0, %% Branch where the account is held
 
162
        balance      = 0, %% Account balance
 
163
        filler       = ?ACCOUNT_FILLER  %% Gap filler to ensure size >= 100 bytes
 
164
       }).
 
165
 
 
166
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
167
%%% Branch record, total size must be at least 100 bytes
 
168
 
 
169
-define(BRANCH_FILLER,
 
170
        {123456789012345678901234567890123456789012345678901234567890,
 
171
         123456789012345678901234567890123456789012345678901234567890,
 
172
         123456789012345678901234567890123456789012345678901234567890}).
 
173
 
 
174
 
 
175
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
176
%%% Teller record, total size must be at least 100 bytes
 
177
 
 
178
-define(TELLER_FILLER,
 
179
        {123456789012345678901234567890123456789012345678901234567890,
 
180
         123456789012345678901234567890123456789012345678901234567890,
 
181
         1234567890123456789012345678901234567890123456789012345678}).
 
182
 
 
183
 
 
184
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
185
%%% History record, total size must be at least 50 bytes
 
186
 
 
187
-define(HISTORY_FILLER, 1234567890).
 
188
 
 
189
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
190
-record(tab_config,
 
191
        {
 
192
         db_nodes = [node()],
 
193
         replica_nodes = [node()],
 
194
         replica_type = ram_copies,
 
195
         use_running_mnesia = false,
 
196
         n_branches = 1,
 
197
         n_tellers_per_branch = 10, %% Must be 10
 
198
         n_accounts_per_branch = 100000, %% Must be 100000
 
199
         branch_filler = ?BRANCH_FILLER,
 
200
         account_filler = ?ACCOUNT_FILLER,
 
201
         teller_filler = ?TELLER_FILLER
 
202
        }).
 
203
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
204
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
205
%
 
206
%  stolen from mnesia_tpcb.erl:
 
207
 
 
208
list2rec(List, Fields, DefaultTuple) ->
 
209
    [Name|Defaults] = tuple_to_list(DefaultTuple),
 
210
    List2 = list2rec(List, Fields, Defaults, []),
 
211
    list_to_tuple([Name] ++ List2).
 
212
 
 
213
list2rec(_List, [], [], Acc) ->
 
214
    Acc;
 
215
list2rec(List, [F|Fields], [D|Defaults], Acc) ->
 
216
    {Val, List2} =
 
217
        case lists:keysearch(F, 1, List) of
 
218
            false ->
 
219
                {D, List};
 
220
            {value, {F, NewVal}} ->
 
221
                {NewVal, lists:keydelete(F, 1, List)}
 
222
        end,
 
223
    list2rec(List2, Fields, Defaults, Acc ++ [Val]).
 
224
 
 
225
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
226
 
 
227
tpcb_config(ReplicaType, _NodeConfig, Nodes, NoDriverNodes) ->
 
228
    [{n_branches, 10},
 
229
     {n_drivers_per_node, 10},
 
230
     {replica_nodes, Nodes},
 
231
     {driver_nodes, Nodes -- NoDriverNodes},
 
232
     {use_running_mnesia, true},
 
233
     {report_interval, infinity},
 
234
     {n_accounts_per_branch, 100},
 
235
     {replica_type, ReplicaType},
 
236
     {reuse_history_id, true}].
 
237
 
 
238
%% Stolen from mnesia_tpcb:dist
 
239
tpcb_config_dist(ReplicaType, _NodeConfig, Nodes, _Config) ->
 
240
    [{db_nodes, Nodes},
 
241
     {driver_nodes, Nodes},
 
242
     {replica_nodes, Nodes},
 
243
     {n_drivers_per_node, 10},
 
244
     {n_branches, 1},
 
245
     {use_running_mnesia, true},
 
246
     {n_accounts_per_branch, 10},
 
247
     {replica_type, ReplicaType},
 
248
     {stop_after, timer:minutes(15)},
 
249
     {report_interval, timer:seconds(10)},
 
250
     {reuse_history_id, true}].
 
251
 
 
252
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
253
%
 
254
%  stolen from mnesia_recovery_test.erl:
 
255
 
 
256
receive_messages([]) -> [];
 
257
receive_messages(ListOfMsgs) ->
 
258
    receive 
 
259
        {Pid, Msg} ->     
 
260
            case lists:member(Msg, ListOfMsgs) of
 
261
                false -> 
 
262
                    ?warning("I (~p) have received unexpected msg~n ~p ~n",
 
263
                        [self(),{Pid, Msg}]),
 
264
                    receive_messages(ListOfMsgs);
 
265
                true -> 
 
266
                    ?verbose("I (~p) got msg ~p from ~p ~n", [self(),Msg, Pid]),
 
267
                    [{Pid, Msg} | receive_messages(ListOfMsgs -- [Msg])]
 
268
            end;
 
269
        Else -> ?warning("Recevied unexpected Msg~n ~p ~n", [Else])
 
270
    after timer:minutes(3) -> 
 
271
            ?error("Timeout in receive msgs while waiting for ~p~n", 
 
272
                   [ListOfMsgs])
 
273
    end.  
 
274
 
 
275
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
276
 
 
277
consistency_after_restart_1_ram(suite) -> [];
 
278
consistency_after_restart_1_ram(Config) when is_list(Config) ->
 
279
    consistency_after_restart(ram_copies, 2, Config).
 
280
 
 
281
consistency_after_restart_1_disc(suite) -> [];
 
282
consistency_after_restart_1_disc(Config) when is_list(Config) ->
 
283
    consistency_after_restart(disc_copies, 2, Config).
 
284
 
 
285
consistency_after_restart_1_disc_only(suite) -> [];
 
286
consistency_after_restart_1_disc_only(Config) when is_list(Config) ->
 
287
    consistency_after_restart(disc_only_copies, 2, Config).
 
288
 
 
289
consistency_after_restart_2_ram(suite) -> [];
 
290
consistency_after_restart_2_ram(Config) when is_list(Config) ->
 
291
    consistency_after_restart(ram_copies, 3, Config).
 
292
 
 
293
consistency_after_restart_2_disc(suite) -> [];
 
294
consistency_after_restart_2_disc(Config) when is_list(Config) ->
 
295
    consistency_after_restart(disc_copies, 3, Config).
 
296
 
 
297
consistency_after_restart_2_disc_only(suite) -> [];
 
298
consistency_after_restart_2_disc_only(Config) when is_list(Config) ->
 
299
    consistency_after_restart(disc_only_copies, 3, Config).
 
300
 
 
301
consistency_after_restart(ReplicaType, NodeConfig, Config) ->
 
302
    [Node1 | _] = Nodes = ?acquire_nodes(NodeConfig, Config),
 
303
    {success, [A]} = ?start_activities([Node1]),
 
304
    ?log("consistency_after_restart with ~p on ~p~n",
 
305
         [ReplicaType, Nodes]),
 
306
    TpcbConfig = tpcb_config(ReplicaType, NodeConfig, Nodes, [Node1]),
 
307
    mnesia_tpcb:init(TpcbConfig),
 
308
    A ! fun () -> mnesia_tpcb:run(TpcbConfig) end,
 
309
    timer:sleep(timer:seconds(10)),
 
310
    mnesia_test_lib:kill_mnesia([Node1]),
 
311
    %% Start and wait for tables to be loaded on all nodes
 
312
    timer:sleep(timer:seconds(3)),
 
313
    ?match([], mnesia_test_lib:start_mnesia(Nodes,[account,branch,teller, history])), 
 
314
    mnesia_tpcb:stop(),
 
315
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
316
    ?verify_mnesia(Nodes, []).
 
317
 
 
318
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
319
 
 
320
consistency_after_dump_tables_1_ram(suite) -> [];
 
321
consistency_after_dump_tables_1_ram(Config) when is_list(Config) ->
 
322
     consistency_after_dump_tables(ram_copies, 1, Config).
 
323
 
 
324
consistency_after_dump_tables_2_ram(suite) -> [];
 
325
consistency_after_dump_tables_2_ram(Config) when is_list(Config) ->
 
326
    consistency_after_dump_tables(ram_copies, 2, Config).
 
327
 
 
328
consistency_after_dump_tables(ReplicaType, NodeConfig, Config) ->
 
329
    [Node1 | _] = Nodes = ?acquire_nodes(NodeConfig, Config),
 
330
    {success, [A]} = ?start_activities([Node1]),
 
331
    ?log("consistency_after_dump_tables with ~p on ~p~n",
 
332
         [ReplicaType, Nodes]),
 
333
    TpcbConfig = tpcb_config(ReplicaType, NodeConfig, Nodes, []),
 
334
    mnesia_tpcb:init(TpcbConfig),
 
335
    A ! fun() -> mnesia_tpcb:run(TpcbConfig) end,
 
336
    timer:sleep(timer:seconds(10)),
 
337
    ?match({atomic, ok}, rpc:call(Node1, mnesia, dump_tables,
 
338
                        [[branch, teller, account, history]])),
 
339
    mnesia_tpcb:stop(),
 
340
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
341
 
 
342
    mnesia_test_lib:kill_mnesia(Nodes),
 
343
    timer:sleep(timer:seconds(1)),
 
344
    ?match([], mnesia_test_lib:start_mnesia(Nodes,[account, branch,
 
345
                                                   teller, history])),
 
346
    mnesia_tpcb:stop(),
 
347
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
348
    ?verify_mnesia(Nodes, []).
 
349
 
 
350
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
351
 
 
352
consistency_after_add_replica_2_ram(suite) -> [];
 
353
consistency_after_add_replica_2_ram(Config) when is_list(Config) ->
 
354
    consistency_after_add_replica(ram_copies, 2, Config).
 
355
 
 
356
consistency_after_add_replica_2_disc(suite) -> [];
 
357
consistency_after_add_replica_2_disc(Config) when is_list(Config) ->
 
358
    consistency_after_add_replica(disc_copies, 2, Config).
 
359
 
 
360
consistency_after_add_replica_2_disc_only(suite) -> [];
 
361
consistency_after_add_replica_2_disc_only(Config) when is_list(Config) ->
 
362
    consistency_after_add_replica(disc_only_copies, 2, Config).
 
363
 
 
364
consistency_after_add_replica_3_ram(suite) -> [];
 
365
consistency_after_add_replica_3_ram(Config) when is_list(Config) ->
 
366
    consistency_after_add_replica(ram_copies, 3, Config).
 
367
 
 
368
consistency_after_add_replica_3_disc(suite) -> [];
 
369
consistency_after_add_replica_3_disc(Config) when is_list(Config) ->
 
370
    consistency_after_add_replica(disc_copies, 3, Config).
 
371
 
 
372
consistency_after_add_replica_3_disc_only(suite) -> [];
 
373
consistency_after_add_replica_3_disc_only(Config) when is_list(Config) ->
 
374
    consistency_after_add_replica(disc_only_copies, 3, Config).
 
375
 
 
376
consistency_after_add_replica(ReplicaType, NodeConfig, Config) ->
 
377
    Nodes0 = ?acquire_nodes(NodeConfig, Config),
 
378
    AddNode = lists:last(Nodes0),
 
379
    Nodes = Nodes0 -- [AddNode],
 
380
    Node1 = hd(Nodes),
 
381
    {success, [A]} = ?start_activities([Node1]),
 
382
    ?log("consistency_after_add_replica with ~p on ~p~n",
 
383
         [ReplicaType, Nodes0]),
 
384
    TpcbConfig = tpcb_config(ReplicaType, NodeConfig, Nodes, []),
 
385
    mnesia_tpcb:init(TpcbConfig),
 
386
    A ! fun () -> mnesia_tpcb:run(TpcbConfig) end,
 
387
    timer:sleep(timer:seconds(10)),
 
388
    ?match({atomic, ok}, mnesia:add_table_copy(account, AddNode, ReplicaType)),
 
389
    mnesia_tpcb:stop(),
 
390
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
391
    ?verify_mnesia(Nodes0, []).
 
392
 
 
393
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
394
 
 
395
consistency_after_del_replica_2_ram(suite) -> [];
 
396
consistency_after_del_replica_2_ram(Config) when is_list(Config) ->
 
397
    consistency_after_del_replica(ram_copies, 2, Config).
 
398
 
 
399
consistency_after_del_replica_2_disc(suite) -> [];
 
400
consistency_after_del_replica_2_disc(Config) when is_list(Config) ->
 
401
    consistency_after_del_replica(disc_copies, 2, Config).
 
402
 
 
403
consistency_after_del_replica_2_disc_only(suite) -> [];
 
404
consistency_after_del_replica_2_disc_only(Config) when is_list(Config) ->
 
405
    consistency_after_del_replica(disc_only_copies, 2, Config).
 
406
 
 
407
consistency_after_del_replica_3_ram(suite) -> [];
 
408
consistency_after_del_replica_3_ram(Config) when is_list(Config) ->
 
409
    consistency_after_del_replica(ram_copies, 3, Config).
 
410
 
 
411
consistency_after_del_replica_3_disc(suite) -> [];
 
412
consistency_after_del_replica_3_disc(Config) when is_list(Config) ->
 
413
    consistency_after_del_replica(disc_copies, 3, Config).
 
414
 
 
415
consistency_after_del_replica_3_disc_only(suite) -> [];
 
416
consistency_after_del_replica_3_disc_only(Config) when is_list(Config) ->
 
417
    consistency_after_del_replica(disc_only_copies, 3, Config).
 
418
 
 
419
consistency_after_del_replica(ReplicaType, NodeConfig, Config) ->
 
420
    Nodes = ?acquire_nodes(NodeConfig, Config),
 
421
    Node1 = hd(Nodes),
 
422
    Node2 = lists:last(Nodes),
 
423
    {success, [A]} = ?start_activities([Node1]),
 
424
    ?log("consistency_after_del_replica with ~p on ~p~n",
 
425
         [ReplicaType, Nodes]),
 
426
    TpcbConfig = tpcb_config(ReplicaType, NodeConfig, Nodes, []),
 
427
    mnesia_tpcb:init(TpcbConfig),
 
428
    A ! fun () -> mnesia_tpcb:run(TpcbConfig) end,
 
429
    timer:sleep(timer:seconds(10)),
 
430
    ?match({atomic, ok}, mnesia:del_table_copy(account, Node2)),
 
431
    mnesia_tpcb:stop(),
 
432
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
433
    ?verify_mnesia(Nodes, []).
 
434
 
 
435
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
436
 
 
437
consistency_after_move_replica_2_ram(suite) -> [];
 
438
consistency_after_move_replica_2_ram(Config) when is_list(Config) ->
 
439
    consistency_after_move_replica(ram_copies, 2, Config).
 
440
 
 
441
consistency_after_move_replica_2_disc(suite) -> [];
 
442
consistency_after_move_replica_2_disc(Config) when is_list(Config) ->
 
443
    consistency_after_move_replica(disc_copies, 2, Config).
 
444
 
 
445
consistency_after_move_replica_2_disc_only(suite) -> [];
 
446
consistency_after_move_replica_2_disc_only(Config) when is_list(Config) ->
 
447
    consistency_after_move_replica(disc_only_copies, 2, Config).
 
448
 
 
449
consistency_after_move_replica_3_ram(suite) -> [];
 
450
consistency_after_move_replica_3_ram(Config) when is_list(Config) ->
 
451
    consistency_after_move_replica(ram_copies, 3, Config).
 
452
 
 
453
consistency_after_move_replica_3_disc(suite) -> [];
 
454
consistency_after_move_replica_3_disc(Config) when is_list(Config) ->
 
455
    consistency_after_move_replica(disc_copies, 3, Config).
 
456
 
 
457
consistency_after_move_replica_3_disc_only(suite) -> [];
 
458
consistency_after_move_replica_3_disc_only(Config) when is_list(Config) ->
 
459
    consistency_after_move_replica(disc_only_copies, 3, Config).
 
460
 
 
461
consistency_after_move_replica(ReplicaType, NodeConfig, Config) ->
 
462
    Nodes = ?acquire_nodes(NodeConfig, Config ++ [{tc_timeout, timer:minutes(10)}]),
 
463
    Node1 = hd(Nodes),
 
464
    Node2 = lists:last(Nodes),
 
465
    {success, [A]} = ?start_activities([Node1]),
 
466
    ?log("consistency_after_move_replica with ~p on ~p~n",
 
467
         [ReplicaType, Nodes]),
 
468
    TpcbConfig = tpcb_config(ReplicaType, NodeConfig, Nodes -- [Node2], []),
 
469
    mnesia_tpcb:init(TpcbConfig),
 
470
    A ! fun () -> mnesia_tpcb:run(TpcbConfig) end,
 
471
    timer:sleep(timer:seconds(10)),
 
472
    ?match({atomic, ok}, mnesia:move_table_copy(account, Node1, Node2)),    
 
473
    ?log("First move completed from node ~p to ~p ~n", [Node1, Node2]),
 
474
    ?match({atomic, ok}, mnesia:move_table_copy(account, Node2, Node1)),
 
475
    mnesia_tpcb:stop(),
 
476
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
477
    ?verify_mnesia(Nodes, []).
 
478
 
 
479
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
480
 
 
481
 
 
482
consistency_after_transform_table_ram(suite) -> [];
 
483
consistency_after_transform_table_ram(Config) when is_list(Config) ->
 
484
    consistency_after_transform_table(ram_copies, Config).
 
485
 
 
486
consistency_after_transform_table_disc(suite) -> [];
 
487
consistency_after_transform_table_disc(Config) when is_list(Config) ->
 
488
    consistency_after_transform_table(disc_copies, Config).
 
489
 
 
490
consistency_after_transform_table_disc_only(suite) -> [];
 
491
consistency_after_transform_table_disc_only(Config) when is_list(Config) ->
 
492
    consistency_after_transform_table(disc_only_copies, Config).
 
493
 
 
494
consistency_after_transform_table(Type, Config) ->
 
495
    Nodes = [N1, N2,_N3] = ?acquire_nodes(3, Config),
 
496
 
 
497
    ?match({atomic, ok}, mnesia:create_table(tab1, [{index, [3]}, {Type, [N1]}])),
 
498
    ?match({atomic, ok}, mnesia:create_table(tab2, [{index, [3]}, {Type, [N1,N2]}])),
 
499
    ?match({atomic, ok}, mnesia:create_table(tab3, [{index, [3]}, {Type, Nodes}])),
 
500
    ?match({atomic, ok}, mnesia:create_table(empty, [{index, [3]},{Type, Nodes}])),
 
501
    
 
502
    Tabs = lists:sort([tab1, tab2, tab3, empty]),
 
503
    
 
504
    [[mnesia:dirty_write({Tab, N, N}) || N <- lists:seq(1,10)] || 
 
505
        Tab <- Tabs -- [empty, tab4]],
 
506
    mnesia:dump_log(),
 
507
    
 
508
    Ok = lists:duplicate(4, {atomic, ok}),
 
509
    ?match(Ok, [mnesia:transform_table(Tab, fun({T, N, N}) ->  {T, N, N, ok} end,
 
510
        [k,a,n]) || Tab <- Tabs]),
 
511
    [?match([k,a,n], mnesia:table_info(Tab, attributes)) || Tab <- Tabs],
 
512
 
 
513
    Filter = fun(Tab) -> mnesia:foldl(fun(A, Acc) when size(A) == 3 -> [A|Acc];
 
514
                                         (A, Acc) when size(A) == 4 -> Acc
 
515
                                      end, [], Tab)
 
516
             end,    
 
517
        
 
518
    ?match([[],[],[],[]], [element(2,mnesia:transaction(Filter, [Tab])) || Tab <- Tabs]),
 
519
    
 
520
    mnesia_test_lib:kill_mnesia(Nodes),
 
521
    mnesia_test_lib:start_mnesia(Nodes, Tabs),
 
522
    
 
523
    ?match([Tabs, Tabs, Tabs], 
 
524
        [lists:sort(rpc:call(Node, mnesia,system_info, [tables]) -- [schema]) || Node <- Nodes]),
 
525
    
 
526
    ?match([[],[],[],[]], [element(2,mnesia:transaction(Filter, [Tab])) || Tab <- Tabs]),
 
527
    [?match([k,a,n], mnesia:table_info(Tab, attributes)) || Tab <- Tabs],
 
528
 
 
529
    ?verify_mnesia(Nodes, []).
 
530
 
 
531
 
 
532
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
533
consistency_after_change_table_copy_type(doc) ->
 
534
    ["Check that the database is consistent after change of copy type.",
 
535
     " While applications are updating the involved tables. "].
 
536
 
 
537
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
538
 
 
539
consistency_after_fallback_2_ram(suite) -> [];
 
540
consistency_after_fallback_2_ram(Config) when is_list(Config) ->
 
541
    consistency_after_fallback(ram_copies, 2, Config).
 
542
 
 
543
consistency_after_fallback_2_disc(suite) -> [];
 
544
consistency_after_fallback_2_disc(Config) when is_list(Config) ->
 
545
    consistency_after_fallback(disc_copies, 2, Config).
 
546
 
 
547
consistency_after_fallback_2_disc_only(suite) -> [];
 
548
consistency_after_fallback_2_disc_only(Config) when is_list(Config) ->
 
549
    consistency_after_fallback(disc_only_copies, 2, Config).
 
550
 
 
551
consistency_after_fallback_3_ram(suite) -> [];
 
552
consistency_after_fallback_3_ram(Config) when is_list(Config) ->
 
553
    consistency_after_fallback(ram_copies, 3, Config).
 
554
 
 
555
consistency_after_fallback_3_disc(suite) -> [];
 
556
consistency_after_fallback_3_disc(Config) when is_list(Config) ->
 
557
    consistency_after_fallback(disc_copies, 3, Config).
 
558
 
 
559
consistency_after_fallback_3_disc_only(suite) -> [];
 
560
consistency_after_fallback_3_disc_only(Config) when is_list(Config) ->
 
561
    consistency_after_fallback(disc_only_copies, 3, Config).
 
562
 
 
563
consistency_after_fallback(ReplicaType, NodeConfig, Config) ->
 
564
    %%?verbose("Starting consistency_after_fallback2 at ~p~n", [self()]),
 
565
    Delay = 5,
 
566
    Nodes = ?acquire_nodes(NodeConfig, [{tc_timeout, timer:minutes(10)} | Config]),
 
567
    Node1 = hd(Nodes),
 
568
    %%?verbose("Mnesia info: ~p~n", [mnesia:info()]),
 
569
 
 
570
    {success, [A]} = ?start_activities([Node1]),
 
571
    ?log("consistency_after_fallback with ~p on ~p~n",
 
572
         [ReplicaType, Nodes]),
 
573
    TpcbConfig = tpcb_config(ReplicaType, NodeConfig, Nodes, []),
 
574
    mnesia_tpcb:init(TpcbConfig),
 
575
    A ! fun () -> mnesia_tpcb:run(TpcbConfig) end,
 
576
    timer:sleep(timer:seconds(Delay)),
 
577
    
 
578
    %% Make a backup
 
579
    ?verbose("Doing backup~n", []),
 
580
    ?match(ok, mnesia:backup(consistency_after_fallback2)),
 
581
    
 
582
    %% Install the backup as a fallback
 
583
    ?verbose("Doing fallback~n", []),
 
584
    ?match(ok, mnesia:install_fallback(consistency_after_fallback2)),
 
585
    timer:sleep(timer:seconds(Delay)),
 
586
 
 
587
    %% Stop tpcb
 
588
    ?verbose("Stopping TPC-B~n", []),
 
589
    mnesia_tpcb:stop(),    
 
590
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
591
    
 
592
    %% Stop and then start mnesia and check table consistency
 
593
    %%?verbose("Restarting Mnesia~n", []),
 
594
    mnesia_test_lib:kill_mnesia(Nodes),
 
595
    mnesia_test_lib:start_mnesia(Nodes,[account,branch,teller,history]),
 
596
    
 
597
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
598
    if 
 
599
        ReplicaType == ram_copies ->
 
600
            %% Test that change_table_copy work i.e. no account.dcd file exists.
 
601
            ?match({atomic, ok}, mnesia:change_table_copy_type(account, node(), disc_copies));
 
602
        true -> 
 
603
            ignore
 
604
    end,
 
605
    file:delete(consistency_after_fallback2),
 
606
    ?verify_mnesia(Nodes, []).
 
607
 
 
608
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
609
 
 
610
consistency_after_restore_clear_ram(suite) -> [];
 
611
consistency_after_restore_clear_ram(Config) when is_list(Config) ->
 
612
    consistency_after_restore(ram_copies, clear_tables, Config).
 
613
 
 
614
consistency_after_restore_clear_disc(suite) -> [];
 
615
consistency_after_restore_clear_disc(Config) when is_list(Config) ->
 
616
    consistency_after_restore(disc_copies, clear_tables, Config).
 
617
 
 
618
consistency_after_restore_clear_disc_only(suite) -> [];
 
619
consistency_after_restore_clear_disc_only(Config) when is_list(Config) ->
 
620
    consistency_after_restore(disc_only_copies, clear_tables, Config).
 
621
 
 
622
consistency_after_restore_recreate_ram(suite) -> [];
 
623
consistency_after_restore_recreate_ram(Config) when is_list(Config) ->
 
624
    consistency_after_restore(ram_copies, recreate_tables, Config).
 
625
 
 
626
consistency_after_restore_recreate_disc(suite) -> [];
 
627
consistency_after_restore_recreate_disc(Config) when is_list(Config) ->
 
628
    consistency_after_restore(disc_copies, recreate_tables, Config).
 
629
 
 
630
consistency_after_restore_recreate_disc_only(suite) -> [];
 
631
consistency_after_restore_recreate_disc_only(Config) when is_list(Config) ->
 
632
    consistency_after_restore(disc_only_copies, recreate_tables, Config).
 
633
 
 
634
consistency_after_restore(ReplicaType, Op, Config) ->
 
635
    Delay = 1,
 
636
    Nodes = ?acquire_nodes(3, [{tc_timeout, timer:minutes(10)} | Config]),
 
637
    [Node1, Node2, _Node3] = Nodes,
 
638
    File = "cons_backup_restore",
 
639
    
 
640
    ?log("consistency_after_restore with ~p on ~p~n",
 
641
         [ReplicaType, Nodes]),
 
642
    Tabs = [carA, carB, carC, carD],
 
643
    
 
644
    ?match({atomic, ok}, mnesia:create_table(carA, [{ReplicaType, Nodes}])),
 
645
    ?match({atomic, ok}, mnesia:create_table(carB, [{ReplicaType, Nodes -- [Node1]}])),
 
646
    ?match({atomic, ok}, mnesia:create_table(carC, [{ReplicaType, Nodes -- [Node2]}])),
 
647
    ?match({atomic, ok}, mnesia:create_table(carD, [{ReplicaType, [Node2]}])),
 
648
 
 
649
    NList = lists:seq(0, 20),
 
650
    [lists:foreach(fun(E) -> ok = mnesia:dirty_write({Tab, E, 1}) end, NList) ||
 
651
        Tab <- Tabs],
 
652
    
 
653
    {ok, Name, _} = mnesia:activate_checkpoint([{max, [schema | Tabs]}, 
 
654
                                                {ram_overrides_dump, true}]),
 
655
    ?verbose("Doing backup~n", []),
 
656
    ?match(ok, mnesia:backup_checkpoint(Name, File)),
 
657
    ?match(ok, mnesia:deactivate_checkpoint(Name)),
 
658
    
 
659
    [lists:foreach(fun(E) -> ok = mnesia:dirty_write({Tab, E, 2}) end, NList) ||
 
660
        Tab <- Tabs],
 
661
    
 
662
    Pids1 = [{'EXIT', spawn_link(?MODULE, change_tab, [self(), carA, Op]), ok} || _ <- lists:seq(1, 5)],
 
663
    Pids2 = [{'EXIT', spawn_link(?MODULE, change_tab, [self(), carB, Op]), ok} || _ <- lists:seq(1, 5)],
 
664
    Pids3 = [{'EXIT', spawn_link(?MODULE, change_tab, [self(), carC, Op]), ok} || _ <- lists:seq(1, 5)],
 
665
    Pids4 = [{'EXIT', spawn_link(?MODULE, change_tab, [self(), carD, Op]), ok} || _ <- lists:seq(1, 5)],
 
666
    
 
667
    AllPids = Pids1 ++ Pids2 ++ Pids3 ++ Pids4,
 
668
    
 
669
    Restore = fun(F, Args) ->
 
670
                      case mnesia:restore(F, Args) of
 
671
                          {atomic, List} -> lists:sort(List);
 
672
                          Else -> Else
 
673
                      end
 
674
              end,
 
675
    
 
676
    timer:sleep(timer:seconds(Delay)),  %% Let changers grab locks
 
677
    ?verbose("Doing restore~n", []),
 
678
    ?match(Tabs, Restore(File, [{default_op, Op}])),
 
679
 
 
680
    timer:sleep(timer:seconds(Delay)),  %% Let em die
 
681
 
 
682
    ?match_multi_receive(AllPids),
 
683
 
 
684
    case ?match(ok, restore_verify_tabs(Tabs)) of 
 
685
        {success, ok} -> 
 
686
            file:delete(File);
 
687
        _ -> 
 
688
            {T, M, S} = time(),
 
689
            File2 = ?flat_format("consistency_error~w~w~w.BUP", [T, M, S]),
 
690
            file:rename(File, File2)
 
691
    end,
 
692
    ?verify_mnesia(Nodes, []).
 
693
 
 
694
change_tab(Father, Tab, Test) ->
 
695
    Key = random:uniform(20),
 
696
    Update = fun() ->
 
697
                     case mnesia:read({Tab, Key}) of
 
698
                         [{Tab, Key, 1}] -> 
 
699
                             quit;
 
700
                         [{Tab, Key, _N}] ->                                   
 
701
                             mnesia:write({Tab, Key, 3})
 
702
                     end
 
703
             end,
 
704
    case mnesia:transaction(Update) of
 
705
        {atomic, quit} ->
 
706
            exit(ok);
 
707
        {aborted, {no_exists, Tab}} when Test == recreate_tables ->%% I'll allow this 
 
708
            change_tab(Father, Tab, Test);
 
709
        {atomic, ok} ->
 
710
            change_tab(Father, Tab, Test)
 
711
    end.
 
712
 
 
713
restore_verify_tabs([Tab | R]) ->
 
714
    ?match({atomic, ok}, 
 
715
           mnesia:transaction(fun() -> mnesia:foldl(fun({_, _, 1}, ok) -> 
 
716
                                                            ok;
 
717
                                                       (Else, Acc) ->
 
718
                                                            [Else|Acc]
 
719
                                                    end, ok, Tab) 
 
720
                              end)),
 
721
    restore_verify_tabs(R);
 
722
restore_verify_tabs([]) ->
 
723
    ok.
 
724
 
 
725
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
726
consistency_after_rename_of_node(doc) ->
 
727
    ["Skipped because it is an unimportant case."].
 
728
 
 
729
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
730
 
 
731
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
732
 
 
733
updates_during_checkpoint_activation_2_ram(suite) -> [];
 
734
updates_during_checkpoint_activation_2_ram(Config) when is_list(Config) ->
 
735
    updates_during_checkpoint_activation(ram_copies, 2, Config).
 
736
 
 
737
updates_during_checkpoint_activation_2_disc(suite) -> [];
 
738
updates_during_checkpoint_activation_2_disc(Config) when is_list(Config) ->
 
739
    updates_during_checkpoint_activation(disc_copies, 2, Config).
 
740
 
 
741
updates_during_checkpoint_activation_2_disc_only(suite) -> [];
 
742
updates_during_checkpoint_activation_2_disc_only(Config) when is_list(Config) ->
 
743
    updates_during_checkpoint_activation(disc_only_copies, 2, Config).
 
744
 
 
745
updates_during_checkpoint_activation_3_ram(suite) -> [];
 
746
updates_during_checkpoint_activation_3_ram(Config) when is_list(Config) ->
 
747
    updates_during_checkpoint_activation(ram_copies, 3, Config).
 
748
 
 
749
updates_during_checkpoint_activation_3_disc(suite) -> [];
 
750
updates_during_checkpoint_activation_3_disc(Config) when is_list(Config) ->
 
751
    updates_during_checkpoint_activation(disc_copies, 3, Config).
 
752
 
 
753
updates_during_checkpoint_activation_3_disc_only(suite) -> [];
 
754
updates_during_checkpoint_activation_3_disc_only(Config) when is_list(Config) ->
 
755
    updates_during_checkpoint_activation(disc_only_copies, 3, Config).
 
756
 
 
757
updates_during_checkpoint_activation(ReplicaType,NodeConfig,Config) ->
 
758
    %%?verbose("updates_during_checkpoint_activation2 at ~p~n", [self()]),
 
759
    Delay = 5,
 
760
    Nodes = ?acquire_nodes(NodeConfig, Config),
 
761
    Node1 = hd(Nodes),
 
762
    %%?verbose("Mnesia info: ~p~n", [mnesia:info()]),
 
763
 
 
764
    {success, [A]} = ?start_activities([Node1]),
 
765
    ?log("consistency_after_fallback with ~p on ~p~n",
 
766
         [ReplicaType, Nodes]),
 
767
    TpcbConfig = tpcb_config_dist(ReplicaType, NodeConfig, Nodes, Config),
 
768
    %%TpcbConfig = tpcb_config(ReplicaType, NodeConfig, Nodes),
 
769
    mnesia_tpcb:init(TpcbConfig),
 
770
    A ! fun () -> mnesia_tpcb:run(TpcbConfig) end,
 
771
    timer:sleep(timer:seconds(Delay)),
 
772
 
 
773
    {ok, CPName, _NodeList} =
 
774
        mnesia:activate_checkpoint([{max, mnesia:system_info(tables)}]),
 
775
    timer:sleep(timer:seconds(Delay)),
 
776
 
 
777
    %% Stop tpcb
 
778
    ?verbose("Stopping TPC-B~n", []),
 
779
    mnesia_tpcb:stop(),
 
780
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
781
    
 
782
    ?match(ok, mnesia:backup_checkpoint(CPName, 
 
783
                                        updates_during_checkpoint_activation2)),
 
784
    timer:sleep(timer:seconds(Delay)),
 
785
 
 
786
    ?match(ok, mnesia:install_fallback(updates_during_checkpoint_activation2)),
 
787
 
 
788
    %% Stop and then start mnesia and check table consistency
 
789
    %%?verbose("Restarting Mnesia~n", []),
 
790
    mnesia_test_lib:kill_mnesia(Nodes),
 
791
    file:delete(updates_during_checkpoint_activation2),
 
792
    mnesia_test_lib:start_mnesia(Nodes,[account,branch,teller, history]),
 
793
 
 
794
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
795
    ?verify_mnesia(Nodes, []).
 
796
 
 
797
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
798
 
 
799
updates_during_checkpoint_iteration_2_ram(suite) -> [];
 
800
updates_during_checkpoint_iteration_2_ram(Config) when is_list(Config) ->
 
801
    updates_during_checkpoint_iteration(ram_copies, 2, Config).
 
802
 
 
803
updates_during_checkpoint_iteration_2_disc(suite) -> [];
 
804
updates_during_checkpoint_iteration_2_disc(Config) when is_list(Config) ->
 
805
    updates_during_checkpoint_iteration(disc_copies, 2, Config).
 
806
 
 
807
updates_during_checkpoint_iteration_2_disc_only(suite) -> [];
 
808
updates_during_checkpoint_iteration_2_disc_only(Config) when is_list(Config) ->
 
809
    updates_during_checkpoint_iteration(disc_only_copies, 2, Config).
 
810
 
 
811
updates_during_checkpoint_iteration(ReplicaType,NodeConfig,Config) ->
 
812
   %?verbose("updates_during_checkpoint_iteration2 at ~p~n", [self()]),
 
813
    Delay = 5,
 
814
    Nodes = ?acquire_nodes(NodeConfig, Config),
 
815
    Node1 = hd(Nodes),
 
816
   %?verbose("Mnesia info: ~p~n", [mnesia:info()]),
 
817
    File = updates_during_checkpoint_iteration2,
 
818
    {success, [A]} = ?start_activities([Node1]),
 
819
    ?log("updates_during_checkpoint_iteration with ~p on ~p~n",
 
820
         [ReplicaType, Nodes]),
 
821
    TpcbConfig = tpcb_config_dist(ReplicaType, NodeConfig, Nodes, Config),
 
822
    %%TpcbConfig = tpcb_config(ReplicaType, NodeConfig, Nodes),
 
823
    TpcbConfigRec = list2rec(TpcbConfig, 
 
824
                                         record_info(fields,tab_config),
 
825
                                         #tab_config{}),
 
826
    mnesia_tpcb:init(TpcbConfig),
 
827
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
828
 
 
829
    {ok, CPName, _NodeList} =
 
830
        mnesia:activate_checkpoint([{max, mnesia:system_info(tables)},
 
831
                                    {ram_overrides_dump,true}]),  
 
832
    A ! fun () -> mnesia:backup_checkpoint(CPName, File) end,
 
833
 
 
834
    do_changes_during_backup(TpcbConfigRec),
 
835
 
 
836
    ?match_receive({A,ok}),
 
837
 
 
838
    timer:sleep(timer:seconds(Delay)), 
 
839
    ?match(ok, mnesia:install_fallback(File)),
 
840
    timer:sleep(timer:seconds(Delay)),
 
841
 
 
842
    ?match({error,{"Bad balance",_,_}}, mnesia_tpcb:verify_tabs()),
 
843
 
 
844
    mnesia_test_lib:kill_mnesia(Nodes),
 
845
    mnesia_test_lib:start_mnesia(Nodes,[account,branch,teller, history]),
 
846
 
 
847
    ?match(ok, mnesia_tpcb:verify_tabs()),
 
848
 
 
849
    ?match(ok, file:delete(File)),
 
850
    ?verify_mnesia(Nodes, []).
 
851
 
 
852
do_changes_during_backup(TpcbConfig) ->
 
853
    loop_branches(TpcbConfig#tab_config.n_branches,
 
854
                  TpcbConfig#tab_config.n_accounts_per_branch).
 
855
 
 
856
loop_branches(N_br,N_acc) when N_br >= 1 ->
 
857
   loop_accounts(N_br,N_acc),
 
858
   loop_branches(N_br-1,N_acc);
 
859
loop_branches(_,_) -> done.
 
860
 
 
861
loop_accounts(N_br, N_acc) when N_acc >= 1 ->
 
862
    A = #account{id=N_acc, branch_id=N_br, balance = 4711},
 
863
    ok = mnesia:dirty_write(A),
 
864
    loop_accounts(N_br, N_acc-1);
 
865
 
 
866
loop_accounts(_,_) -> done.
 
867
 
 
868
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
869
 
 
870
load_table_with_activated_checkpoint_ram(suite) -> [];
 
871
load_table_with_activated_checkpoint_ram(Config) when is_list(Config) ->
 
872
    load_table_with_activated_checkpoint(ram_copies, Config).
 
873
 
 
874
load_table_with_activated_checkpoint_disc(suite) -> [];
 
875
load_table_with_activated_checkpoint_disc(Config) when is_list(Config) ->
 
876
    load_table_with_activated_checkpoint(disc_copies, Config).
 
877
 
 
878
load_table_with_activated_checkpoint_disc_only(suite) -> [];
 
879
load_table_with_activated_checkpoint_disc_only(Config) when is_list(Config) ->
 
880
    load_table_with_activated_checkpoint(disc_only_copies, Config).
 
881
 
 
882
load_table_with_activated_checkpoint(Type, Config) ->
 
883
    Nodes = ?acquire_nodes(2, Config),
 
884
    Node1 = hd(Nodes),
 
885
    Tab = load_test,
 
886
    Def = [{attributes, [key, value]},
 
887
           {Type, Nodes}],            %%  ??? important that RAM  ???
 
888
    
 
889
    ?match({atomic, ok}, mnesia:create_table(Tab, Def)),
 
890
    ?match(ok, mnesia:dirty_write({Tab, 1, 4711})),
 
891
    ?match(ok, mnesia:dirty_write({Tab, 2, 42})),
 
892
    ?match(ok, mnesia:dirty_write({Tab, 3, 256})),
 
893
    
 
894
    timer:sleep(timer:seconds(1)), 
 
895
    
 
896
    {ok, CPName, _NodeList} =
 
897
        mnesia:activate_checkpoint([{max, mnesia:system_info(tables)},
 
898
                                    {ram_overrides_dump,true}]),
 
899
    
 
900
    mnesia_test_lib:stop_mnesia([Node1]),    
 
901
    mnesia_test_lib:start_mnesia([Node1],[Tab]),      
 
902
    %%--- check, whether the checkpiont is attached to both replicas
 
903
    {success, [A,B]} = ?start_activities(Nodes),
 
904
    
 
905
    A ! fun () ->
 
906
                mnesia:table_info(Tab,checkpoints)
 
907
        end,
 
908
    ?match_receive({A,[CPName]}),
 
909
    
 
910
    B ! fun () ->
 
911
                mnesia:table_info(Tab,checkpoints)
 
912
        end,
 
913
    ?match_receive({B,[CPName]}),    
 
914
    
 
915
    %%--- check, whether both retainers are consistent    
 
916
    ?match(ok, mnesia:dirty_write({Tab, 1, 815})),       
 
917
    A ! fun () ->
 
918
                mnesia:backup_checkpoint(CPName, load_table_a)
 
919
        end,
 
920
    ?match_receive({A,ok}),
 
921
    B ! fun () ->
 
922
                mnesia:backup_checkpoint(CPName, load_table_b)
 
923
        end,
 
924
    ?match_receive({B,ok}),
 
925
    
 
926
    Mod = mnesia_backup, %% Assume local files
 
927
    List_a =  view(load_table_a, Mod),
 
928
    List_b =  view(load_table_b, Mod),
 
929
    
 
930
    ?match(List_a, List_b),
 
931
    
 
932
    ?match(ok,file:delete(load_table_a)),
 
933
    ?match(ok,file:delete(load_table_b)),
 
934
    ?verify_mnesia(Nodes, []).
 
935
 
 
936
view(Source, Mod) ->
 
937
    View = fun(Item, Acc) ->
 
938
                   ?verbose("tab - item : ~p ~n",[Item]),
 
939
                   case Item of
 
940
                       {schema, Tab, Cs} ->  %% Remove cookie information
 
941
                           NewCs = lists:keyreplace(cookie, 1, Cs,
 
942
                                                    {cookie, skip_cookie}),
 
943
                           Item2 = {schema, Tab, NewCs},
 
944
                           {[Item], [Item2|Acc]};
 
945
                       _ ->   
 
946
                           {[Item], [Item|Acc]}
 
947
                   end
 
948
           end,
 
949
    {ok,TabList} =  
 
950
        mnesia:traverse_backup(Source, Mod, dummy, read_only, View, []),
 
951
    lists:sort(TabList).
 
952
 
 
953
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
954
 
 
955
add_table_copy_to_table_with_activated_checkpoint_ram(suite) -> [];
 
956
add_table_copy_to_table_with_activated_checkpoint_ram(Config) when is_list(Config) ->
 
957
    add_table_copy_to_table_with_activated_checkpoint(ram_copies, Config).
 
958
 
 
959
add_table_copy_to_table_with_activated_checkpoint_disc(suite) -> [];
 
960
add_table_copy_to_table_with_activated_checkpoint_disc(Config) when is_list(Config) ->
 
961
    add_table_copy_to_table_with_activated_checkpoint(disc_copies, Config).
 
962
 
 
963
add_table_copy_to_table_with_activated_checkpoint_disc_only(suite) -> [];
 
964
add_table_copy_to_table_with_activated_checkpoint_disc_only(Config) when is_list(Config) ->
 
965
    add_table_copy_to_table_with_activated_checkpoint(disc_only_copies, Config).
 
966
 
 
967
add_table_copy_to_table_with_activated_checkpoint(Type,Config) -> 
 
968
    Nodes = ?acquire_nodes(2, Config),
 
969
                                                %?verbose("NODES = ~p ~n",[Nodes]),
 
970
    [Node1,Node2] = Nodes,
 
971
 
 
972
    Tab = add_test,
 
973
    Def = [{attributes, [key, value]},
 
974
           {Type, [Node1]}],            %%  ??? important that RAM  ???
 
975
 
 
976
    ?match({atomic, ok}, mnesia:create_table(Tab, Def)),
 
977
    ?match(ok, mnesia:dirty_write({Tab, 1, 4711})),
 
978
    ?match(ok, mnesia:dirty_write({Tab, 2, 42})),
 
979
    ?match(ok, mnesia:dirty_write({Tab, 3, 256})),
 
980
 
 
981
    {ok, CPName, _NodeList} =
 
982
        mnesia:activate_checkpoint([{max, mnesia:system_info(tables)},
 
983
                                    {ram_overrides_dump,true}]),
 
984
 
 
985
    ?match({atomic,ok},mnesia:add_table_copy(Tab,Node2,ram_copies)),
 
986
 
 
987
    %%--- check, whether the checkpiont is attached to both replicas
 
988
    {success, [A,B]} = ?start_activities(Nodes),
 
989
 
 
990
    A ! fun () ->
 
991
                mnesia:table_info(Tab,checkpoints)
 
992
        end,
 
993
    ?match_receive({A,[CPName]}),
 
994
 
 
995
    B ! fun () ->
 
996
                mnesia:table_info(Tab,checkpoints)
 
997
        end,
 
998
    ?match_receive({B,[CPName]}),
 
999
 
 
1000
    %%--- check, whether both retainers are consistent
 
1001
 
 
1002
    ?match(ok, mnesia:dirty_write({Tab, 1, 815})),
 
1003
    ?match(ok, mnesia:dirty_write({Tab, 2, 815})),
 
1004
 
 
1005
    A ! fun () ->
 
1006
                mnesia:backup_checkpoint(CPName, add_table_a)
 
1007
        end,
 
1008
    ?match_receive({A,ok}),
 
1009
    B ! fun () ->
 
1010
                mnesia:backup_checkpoint(CPName, add_table_b)
 
1011
        end,
 
1012
    ?match_receive({B,ok}),
 
1013
 
 
1014
    Mod = mnesia_backup, %% Assume local files
 
1015
 
 
1016
    List_a = view(add_table_a, Mod),
 
1017
    List_b = view(add_table_b, Mod),
 
1018
 
 
1019
    ?match(List_a, List_b),
 
1020
 
 
1021
    ?match(ok,file:delete(add_table_a)),
 
1022
    ?match(ok, file:delete(add_table_b)),
 
1023
    ?verify_mnesia(Nodes, []).
 
1024
 
 
1025
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1026
 
 
1027
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1028
 
 
1029
inst_fallback_process_dies(suite) -> 
 
1030
    [];
 
1031
inst_fallback_process_dies(Config) when is_list(Config) ->
 
1032
    ?is_debug_compiled,
 
1033
    
 
1034
    Nodes = ?acquire_nodes(3, Config ++ [{tc_timeout, timer:minutes(2)}]),
 
1035
    {success, [A,_B,_C]} = ?start_activities(Nodes),
 
1036
    
 
1037
    TestPid = self(),
 
1038
    DebugId = {mnesia_bup, fallback_receiver_loop, pre_swap},
 
1039
    DebugFun =
 
1040
        fun(PrevContext, _EvalContext) ->
 
1041
                ?verbose("fallback_receiver_loop -  pre_swap pid ~p  #~p~n",
 
1042
                     [self(),PrevContext]),
 
1043
                TestPid ! {self(),fallback_preswap},
 
1044
                case receive_messages([fallback_continue]) of
 
1045
                    [{TestPid,fallback_continue}] ->
 
1046
                        ?deactivate_debug_fun(DebugId),
 
1047
                        PrevContext+1
 
1048
                end
 
1049
        end,
 
1050
    ?activate_debug_fun(DebugId, DebugFun, 1),
 
1051
        
 
1052
    Tab = install_table,
 
1053
    Def = [{attributes, [key, value]}, {disc_copies, Nodes}], 
 
1054
    
 
1055
    ?match({atomic, ok}, mnesia:create_table(Tab, Def)),
 
1056
    
 
1057
    ?match(ok, mnesia:dirty_write({Tab, 1, 4711})),
 
1058
    ?match(ok, mnesia:dirty_write({Tab, 2, 42})),
 
1059
    ?match(ok, mnesia:dirty_write({Tab, 3, 256})),
 
1060
    
 
1061
    {ok, CPName, _NodeList} =
 
1062
        mnesia:activate_checkpoint([{max, mnesia:system_info(tables)},
 
1063
                                    {ram_overrides_dump,true}]),
 
1064
    
 
1065
    ?match(ok, mnesia:backup_checkpoint(CPName, install_backup)),
 
1066
    
 
1067
    A ! fun() -> mnesia:install_fallback(install_backup) end,    
 
1068
    [{AnsPid,fallback_preswap}] = receive_messages([fallback_preswap]),
 
1069
    exit(A, kill),
 
1070
    AnsPid ! {self(), fallback_continue},
 
1071
    ?match_receive({'EXIT', A, killed}), 
 
1072
    timer:sleep(2000),  %% Wait till fallback is installed everywhere
 
1073
 
 
1074
    mnesia_test_lib:kill_mnesia(Nodes),    
 
1075
    ?verbose("~n---->Mnesia is stopped everywhere<-----~n", []),
 
1076
    ?match([], mnesia_test_lib:start_mnesia(Nodes,[Tab])),
 
1077
    
 
1078
    check_data(Nodes, Tab),
 
1079
    ?match(ok, file:delete(install_backup)),
 
1080
    ?verify_mnesia(Nodes, []).
 
1081
 
 
1082
check_data([N1 | R], Tab) ->
 
1083
    ?match([{Tab, 1, 4711}], rpc:call(N1, mnesia, dirty_read, [{Tab, 1}])),
 
1084
    ?match([{Tab, 2, 42}],   rpc:call(N1, mnesia, dirty_read, [{Tab, 2}])),
 
1085
    ?match([{Tab, 3, 256}],  rpc:call(N1, mnesia, dirty_read, [{Tab, 3}])),
 
1086
    check_data(R, Tab);
 
1087
check_data([], _Tab) -> 
 
1088
    ok.
 
1089
 
 
1090
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1091
 
 
1092
fatal_when_inconsistency(suite) -> 
 
1093
    [];
 
1094
fatal_when_inconsistency(Config) when is_list(Config) ->
 
1095
    ?is_debug_compiled,
 
1096
    
 
1097
    [Node1, Node2, Node3] = Nodes = 
 
1098
        ?acquire_nodes(3, Config ++ [{tc_timeout, timer:minutes(2)}]),
 
1099
    {success, [A,_B,_C]} = ?start_activities(Nodes),
 
1100
    
 
1101
    TestPid = self(),
 
1102
    DebugId = {mnesia_bup, fallback_receiver_loop, pre_swap},
 
1103
    DebugFun =
 
1104
        fun(PrevContext, _EvalContext) ->
 
1105
                ?verbose("fallback_receiver_loop -  pre_swap pid ~p  #~p~n",
 
1106
                     [self(),PrevContext]),
 
1107
                TestPid ! {self(),fallback_preswap},
 
1108
                case receive_messages([fallback_continue])  of
 
1109
                    [{TestPid,fallback_continue}] ->
 
1110
                        ?deactivate_debug_fun(DebugId),
 
1111
                        PrevContext+1
 
1112
                end
 
1113
        end,
 
1114
    ?activate_debug_fun(DebugId, DebugFun, 1),
 
1115
        
 
1116
    Tab = install_table,
 
1117
    Def = [{attributes, [key, value]}, {disc_copies, Nodes}], 
 
1118
    
 
1119
    ?match({atomic, ok}, mnesia:create_table(Tab, Def)),
 
1120
    
 
1121
    ?match(ok, mnesia:dirty_write({Tab, 1, 4711})),
 
1122
    ?match(ok, mnesia:dirty_write({Tab, 2, 42})),
 
1123
    ?match(ok, mnesia:dirty_write({Tab, 3, 256})),
 
1124
    
 
1125
    {ok, CPName, _NodeList} =
 
1126
        mnesia:activate_checkpoint([{max, mnesia:system_info(tables)},
 
1127
                                    {ram_overrides_dump,true}]),
 
1128
    
 
1129
    ?match(ok, mnesia:backup_checkpoint(CPName, install_backup)),
 
1130
    ?match(ok, mnesia:dirty_write({Tab, 2, 42424242})),
 
1131
    
 
1132
    A ! fun() ->
 
1133
                mnesia:install_fallback(install_backup)
 
1134
        end,    
 
1135
 
 
1136
    [{AnsPid,fallback_preswap}] = receive_messages([fallback_preswap]),
 
1137
    exit(AnsPid, kill),  %% Kill install-fallback on local node will 
 
1138
    AnsPid ! {self(), fallback_continue},
 
1139
    ?deactivate_debug_fun(DebugId),
 
1140
        
 
1141
    ?match_receive({A,{error,{"Cannot install fallback",
 
1142
                              {'EXIT',AnsPid,killed}}}}),
 
1143
    mnesia_test_lib:kill_mnesia(Nodes),
 
1144
    ?verbose("EXPECTING FATAL from 2 nodes WITH CORE DUMP~n", []),
 
1145
    
 
1146
    ?match([], mnesia_test_lib:start_mnesia([Node1],[])),
 
1147
    is_running(Node1, yes),
 
1148
    ?match([{Node2, mnesia, _}], mnesia_test_lib:start_mnesia([Node2],[])),
 
1149
    is_running(Node2, no),
 
1150
    ?match([{Node3, mnesia, _}], mnesia_test_lib:start_mnesia([Node3],[])),
 
1151
    is_running(Node3, no),
 
1152
    mnesia_test_lib:kill_mnesia(Nodes),
 
1153
    
 
1154
    ?match(ok, mnesia:install_fallback(install_backup)),    
 
1155
    mnesia_test_lib:start_mnesia(Nodes,[Tab]),
 
1156
    
 
1157
    check_data(Nodes, Tab),
 
1158
    
 
1159
    ?match(ok,file:delete(install_backup)),
 
1160
    ?verify_mnesia(Nodes, []).
 
1161
 
 
1162
is_running(Node, Shouldbe) ->
 
1163
    timer:sleep(1000),
 
1164
    Running = rpc:call(Node, mnesia, system_info, [is_running]),
 
1165
    case Running of
 
1166
        Shouldbe -> ok;
 
1167
        _  -> is_running(Node, Shouldbe)
 
1168
    end.
 
1169
 
 
1170
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1171
 
 
1172
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1173
 
 
1174
after_delete(doc) ->
 
1175
    ["interrupt the uninstall after deletion of ",
 
1176
     "fallback files - there shall be no fallback"];
 
1177
after_delete(suite) -> [];
 
1178
after_delete(Config) when is_list(Config) ->
 
1179
        do_uninstall(Config, post_delete).
 
1180
 
 
1181
%%%%%%%%%%%%%%%%%%%%%%%%%
 
1182
 
 
1183
do_uninstall(Config,DebugPoint) ->
 
1184
    ?is_debug_compiled,
 
1185
    
 
1186
    Nodes = ?acquire_nodes(3, Config),
 
1187
    %%?verbose("NODES = ~p ~n",[Nodes]),
 
1188
    
 
1189
    {success, [P1,P2,P3]} = ?start_activities(Nodes),
 
1190
    
 
1191
    NP1 = node(P1),
 
1192
    NP2 = node(P2),
 
1193
    
 
1194
    {A,B,C} = case node() of
 
1195
                  NP1 ->
 
1196
                      %%?verbose("first case ~n"),
 
1197
                      {P3,P2,P1};
 
1198
                  NP2 ->
 
1199
                      %%?verbose("second case ~n"),
 
1200
                      {P3, P1, P2};
 
1201
                  _  ->
 
1202
                      { P1, P2, P3}
 
1203
              end,
 
1204
    
 
1205
    Node1 = node(A),
 
1206
    Node2 = node(B),
 
1207
    Node3 = node(C),
 
1208
    
 
1209
    ?verbose(" A   pid:~p  node:~p ~n",[A,Node1]),
 
1210
    ?verbose(" B   pid:~p  node:~p ~n",[B,Node2]),
 
1211
    ?verbose(" C   pid:~p  node:~p ~n",[C,Node3]),
 
1212
    
 
1213
    
 
1214
    TestPid = self(),
 
1215
    %%?verbose("TestPid : ~p~n",[TestPid]),
 
1216
    DebugId = {mnesia_bup, uninstall_fallback2, DebugPoint},
 
1217
    DebugFun = fun(PrevContext, _EvalContext) ->
 
1218
                       ?verbose("uninstall_fallback pid ~p  #~p~n"
 
1219
                                ,[self(),PrevContext]),
 
1220
                       TestPid ! {self(),uninstall_predelete},
 
1221
                       case receive_messages([uninstall_continue]) of
 
1222
                           [{TestPid,uninstall_continue}] ->
 
1223
                               ?deactivate_debug_fun(DebugId),
 
1224
                               %%?verbose("uninstall_fallback continues~n"),
 
1225
                               PrevContext+1
 
1226
                       end
 
1227
               end,
 
1228
    ?remote_activate_debug_fun(Node1,DebugId, DebugFun, 1),
 
1229
    
 
1230
    Tab = install_table,
 
1231
    Def = [{attributes, [key, value]},
 
1232
           {ram_copies, Nodes}],     %% necessary to test different types ???  
 
1233
    
 
1234
    ?match({atomic, ok}, mnesia:create_table(Tab, Def)),
 
1235
    
 
1236
    ?match(ok, mnesia:dirty_write({Tab, 1, 4711})),
 
1237
    ?match(ok, mnesia:dirty_write({Tab, 2, 42})),
 
1238
    ?match(ok, mnesia:dirty_write({Tab, 3, 256})),
 
1239
    
 
1240
    {ok, CPName, _NodeList} =
 
1241
        mnesia:activate_checkpoint([{max, mnesia:system_info(tables)},
 
1242
                                    {ram_overrides_dump,true}]),
 
1243
    
 
1244
    ?match(ok, mnesia:backup_checkpoint(CPName,install_backup)),
 
1245
    timer:sleep(timer:seconds(1)), 
 
1246
    
 
1247
    A ! fun () ->
 
1248
                mnesia:install_fallback(install_backup)
 
1249
        end,
 
1250
    ?match_receive({A,ok}),
 
1251
    
 
1252
    A ! fun () ->
 
1253
                mnesia:uninstall_fallback()
 
1254
        end,
 
1255
    %%
 
1256
    %%  catch the debug entry in mnesia and kill one Mnesia node
 
1257
    %%
 
1258
    
 
1259
    
 
1260
    [{AnsPid,uninstall_predelete}] = receive_messages([uninstall_predelete]),
 
1261
    
 
1262
    ?verbose("AnsPid : ~p~n",[AnsPid]),
 
1263
    
 
1264
    mnesia_test_lib:kill_mnesia([Node2]),
 
1265
    timer:sleep(timer:seconds(1)), 
 
1266
    
 
1267
    AnsPid ! {self(),uninstall_continue},
 
1268
    
 
1269
    ?match_receive({A,ok}),
 
1270
    
 
1271
    mnesia_test_lib:kill_mnesia(Nodes) ,
 
1272
    mnesia_test_lib:start_mnesia(Nodes,[Tab]),
 
1273
    
 
1274
    A ! fun () ->
 
1275
                R1 = mnesia:dirty_read({Tab,1}),
 
1276
                R2 = mnesia:dirty_read({Tab,2}),
 
1277
                R3 = mnesia:dirty_read({Tab,3}),
 
1278
                {R1,R2,R3}
 
1279
        end,    
 
1280
    ?match_receive({ A, {[],[],[]} }),
 
1281
    
 
1282
    B ! fun () ->
 
1283
                R1 = mnesia:dirty_read({Tab,1}),
 
1284
                R2 = mnesia:dirty_read({Tab,2}),
 
1285
                R3 = mnesia:dirty_read({Tab,3}),
 
1286
                {R1,R2,R3}
 
1287
        end,
 
1288
    ?match_receive({ B, {[],[],[]} }),
 
1289
    
 
1290
    C ! fun () ->
 
1291
                R1 = mnesia:dirty_read({Tab,1}),
 
1292
                R2 = mnesia:dirty_read({Tab,2}),
 
1293
                R3 = mnesia:dirty_read({Tab,3}),
 
1294
                {R1,R2,R3}
 
1295
        end,
 
1296
    ?match_receive({ C, {[],[],[]} }),
 
1297
    
 
1298
    ?match(ok,file:delete(install_backup)),
 
1299
    ?verify_mnesia(Nodes, []).
 
1300
 
 
1301
 
 
1302
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1303
 
 
1304
%%%%%%%%%%%%%%%
 
1305
 
 
1306
cause_switch_before(doc)  ->
 
1307
      ["interrupt the backup before iterating the retainer"];
 
1308
cause_switch_before(suite)  ->  [];
 
1309
cause_switch_before(Config) when is_list(Config) ->
 
1310
   do_something_during_backup(cause_switch,pre,Config).
 
1311
 
 
1312
%%%%%%%%%%%%%%%
 
1313
 
 
1314
cause_switch_after(doc)  ->
 
1315
      ["interrupt the backup after iterating the retainer"];
 
1316
cause_switch_after(suite)  ->  [];
 
1317
cause_switch_after(Config) when is_list(Config) ->
 
1318
   do_something_during_backup(cause_switch,post,Config).
 
1319
 
 
1320
 
 
1321
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1322
 
 
1323
%%%%%%%%%%%%%%%%%%
 
1324
 
 
1325
cause_abort_before(doc) ->
 
1326
      ["interrupt the backup before iterating the retainer"];
 
1327
 
 
1328
cause_abort_before(suite) ->  [];
 
1329
cause_abort_before(Config) when is_list(Config) ->
 
1330
   do_something_during_backup(cause_abort,pre,Config).
 
1331
 
 
1332
%%%%%%%%%%%%%%%%%%
 
1333
 
 
1334
cause_abort_after(doc) ->
 
1335
      ["interrupt the backup after iterating the retainer"];
 
1336
 
 
1337
cause_abort_after(suite) ->  [];
 
1338
cause_abort_after(Config) when is_list(Config) ->
 
1339
   do_something_during_backup(cause_abort,post,Config).
 
1340
 
 
1341
 
 
1342
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1343
 
 
1344
%%%%%%%%%%%%%
 
1345
 
 
1346
change_schema_before(doc) ->
 
1347
      ["interrupt the backup before iterating the retainer"];
 
1348
change_schema_before(suite) -> [];
 
1349
change_schema_before(Config) when is_list(Config) ->
 
1350
   do_something_during_backup(change_schema,pre,Config).
 
1351
 
 
1352
%%%%%%%%%%%%%%%%
 
1353
 
 
1354
change_schema_after(doc) ->
 
1355
      ["interrupt the backup after iterating the retainer"];
 
1356
change_schema_after(suite) -> [];
 
1357
change_schema_after(Config) when is_list(Config) ->
 
1358
   do_something_during_backup(change_schema,post,Config).
 
1359
 
 
1360
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1361
 
 
1362
do_something_during_backup(Action,DebugPoint,Config) ->
 
1363
    ?is_debug_compiled,
 
1364
    
 
1365
    Nodes = ?acquire_nodes(3, Config),
 
1366
    
 
1367
    {success, [A,B,C]} = ?start_activities(Nodes),
 
1368
    
 
1369
    Node1 = node(A),
 
1370
    Node2 = node(B),
 
1371
    Node3 = node(C),
 
1372
    
 
1373
    TestPid = self(),
 
1374
    %%?verbose("TestPid : ~p~n",[TestPid]),
 
1375
    
 
1376
    Tab = interrupt_table,
 
1377
    Bak = interrupt_backup,
 
1378
    Def = [{attributes, [key, value]},
 
1379
           {ram_copies, [Node2,Node3]}],  
 
1380
    %% necessary to test different types ???  
 
1381
    
 
1382
    ?match({atomic, ok}, mnesia:create_table(Tab, Def)),
 
1383
    
 
1384
    
 
1385
    
 
1386
    DebugId = {mnesia_log, tab_copier, DebugPoint},
 
1387
    DebugFun = fun(PrevContext, EvalContext) ->
 
1388
                       ?verbose("interrupt backup  pid ~p  #~p ~n context ~p ~n"
 
1389
                            ,[self(),PrevContext,EvalContext]),
 
1390
                       TestPid ! {self(),interrupt_backup_pre},
 
1391
                       global:set_lock({{lock_for_backup, Tab}, self()},
 
1392
                                       Nodes,
 
1393
                                       infinity),
 
1394
                                       
 
1395
                       %%?verbose("interrupt backup - continues ~n"),
 
1396
                       ?deactivate_debug_fun(DebugId),
 
1397
                       PrevContext+1
 
1398
               end,
 
1399
    ?remote_activate_debug_fun(Node1,DebugId, DebugFun, 1),
 
1400
    
 
1401
    ?match(ok, mnesia:dirty_write({Tab, 1, 4711})),
 
1402
    ?match(ok, mnesia:dirty_write({Tab, 2, 42})),
 
1403
    ?match(ok, mnesia:dirty_write({Tab, 3, 256})),
 
1404
    
 
1405
    {ok, CPName, _NodeList} =
 
1406
        mnesia:activate_checkpoint([{max, mnesia:system_info(tables)},
 
1407
                                    {ram_overrides_dump,true}]),
 
1408
    
 
1409
    A ! fun () ->
 
1410
                %%?verbose("node: ~p pid: ~p ~n",[node(),self()]),
 
1411
                mnesia:table_info(Tab,where_to_read)
 
1412
        end,
 
1413
 
 
1414
    ReadNode_a = receive { A, ReadNode_a_tmp } -> ReadNode_a_tmp end,
 
1415
    ?verbose("ReadNode ~p ~n",[ReadNode_a]),
 
1416
    
 
1417
    global:set_lock({{lock_for_backup, Tab}, self()}, Nodes, infinity),
 
1418
    
 
1419
    A ! fun () ->    %% A shall perform the backup, so the test proc is
 
1420
                %% able to do further actions in between
 
1421
                mnesia:backup_checkpoint(CPName, Bak)
 
1422
        end,
 
1423
    
 
1424
    %% catch the debug function of mnesia, stop the backup process 
 
1425
    %% kill the node ReadNode_a and continue the backup process
 
1426
    %% As there is a second replica of the table, the backup shall continue
 
1427
 
 
1428
    case receive_messages([interrupt_backup_pre]) of
 
1429
        [{_AnsPid,interrupt_backup_pre}] -> ok
 
1430
    end,
 
1431
    
 
1432
    case Action of
 
1433
        cause_switch ->
 
1434
            mnesia_test_lib:kill_mnesia([ReadNode_a]),
 
1435
            timer:sleep(timer:seconds(1));
 
1436
        cause_abort ->
 
1437
            mnesia_test_lib:kill_mnesia([Node2,Node3]),
 
1438
            timer:sleep(timer:seconds(1));
 
1439
        change_schema ->
 
1440
            Tab2 = second_interrupt_table,
 
1441
            Def2 = [{attributes, [key, value]},
 
1442
                    {ram_copies, Nodes}],  
 
1443
            
 
1444
            ?match({atomic, ok}, mnesia:create_table(Tab2, Def2))
 
1445
    end,
 
1446
    
 
1447
    %%    AnsPid ! {self(),interrupt_backup_continue},
 
1448
    global:del_lock({{lock_for_backup, Tab}, self()}, Nodes),
 
1449
    
 
1450
    case Action of
 
1451
        cause_abort -> 
 
1452
            
 
1453
            %% answer of A when finishing the backup
 
1454
            ?match_receive({A,{error, _}}), 
 
1455
            
 
1456
            ?match({error,{"Cannot install fallback",_}},
 
1457
                   mnesia:install_fallback(Bak)); 
 
1458
        _ ->      %% cause_switch, change_schema
 
1459
            
 
1460
            ?match_receive({A,ok}), %% answer of A when finishing the backup
 
1461
            
 
1462
            %% send a fun to that node where mnesia is still running
 
1463
            WritePid = case ReadNode_a of
 
1464
                           Node2 -> C; %%   node(C) == Node3
 
1465
                           Node3 -> B
 
1466
                       end,
 
1467
            WritePid ! fun () ->
 
1468
                               ?match(ok, mnesia:dirty_write({Tab, 1, 815})),
 
1469
                               ?match(ok, mnesia:dirty_write({Tab, 2, 816})),
 
1470
                               ok
 
1471
                       end,
 
1472
            ?match_receive({ WritePid, ok }),  
 
1473
            ?match(ok, mnesia:install_fallback(Bak))
 
1474
    end,        
 
1475
    
 
1476
    %% Stop and then start mnesia and check table consistency
 
1477
    %%?verbose("Restarting Mnesia~n", []),
 
1478
    mnesia_test_lib:kill_mnesia(Nodes),
 
1479
    mnesia_test_lib:start_mnesia(Nodes,[Tab]),
 
1480
    
 
1481
    case Action of
 
1482
        cause_switch ->
 
1483
            %% the backup should exist
 
1484
            cross_check_tables([A,B,C],Tab,{[{Tab,1,4711}],
 
1485
                                            [{Tab,2,42}],
 
1486
                                            [{Tab,3,256}] }),
 
1487
            ?match(ok,file:delete(Bak));
 
1488
        cause_abort ->
 
1489
            %% the backup should  NOT exist
 
1490
            cross_check_tables([A,B,C],Tab,{[],[],[]}),
 
1491
            %% file does not exist 
 
1492
            ?match({error, _},file:delete(Bak)); 
 
1493
        change_schema ->
 
1494
            %% the backup should exist
 
1495
            cross_check_tables([A,B,C],Tab,{[{Tab,1,4711}],
 
1496
                                            [{Tab,2,42}],
 
1497
                                            [{Tab,3,256}] }),
 
1498
            ?match(ok,file:delete(Bak))
 
1499
    end,
 
1500
    ?verify_mnesia(Nodes, []).
 
1501
 
 
1502
%% check the contents of the table
 
1503
cross_check_tables([],_tab,_elements) -> ok;
 
1504
cross_check_tables([Pid|Rest],Tab,{Val1,Val2,Val3}) ->
 
1505
    Pid ! fun () ->
 
1506
              R1 = mnesia:dirty_read({Tab,1}),
 
1507
              R2 = mnesia:dirty_read({Tab,2}),
 
1508
              R3 = mnesia:dirty_read({Tab,3}),
 
1509
              {R1,R2,R3}
 
1510
            end,
 
1511
    ?match_receive({ Pid, {Val1, Val2, Val3 } }),
 
1512
    cross_check_tables(Rest,Tab,{Val1,Val2,Val3} ).