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

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_schema_recovery_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 1998-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_schema_recovery_test).
 
22
-author('hakan@erix.ericsson.se').
 
23
-compile([export_all]).
 
24
-include("mnesia_test_lib.hrl").
 
25
 
 
26
init_per_testcase(Func, Conf) ->
 
27
    mnesia_test_lib:init_per_testcase(Func, Conf).
 
28
 
 
29
end_per_testcase(Func, Conf) ->
 
30
    mnesia_test_lib:end_per_testcase(Func, Conf).
 
31
 
 
32
-define(receive_messages(Msgs), receive_messages(Msgs, ?FILE, ?LINE)).
 
33
 
 
34
% First Some debug logging 
 
35
-define(dgb, true).
 
36
-ifdef(dgb).
 
37
-define(dl(X, Y), ?verbose("**TRACING: " ++ X ++ "**~n", Y)).
 
38
-else. 
 
39
-define(dl(X, Y), ok).
 
40
-endif.
 
41
 
 
42
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
43
 
 
44
all() -> 
 
45
    [{group, interrupted_before_log_dump},
 
46
     {group, interrupted_after_log_dump}].
 
47
 
 
48
groups() -> 
 
49
    [{interrupted_before_log_dump, [],
 
50
      [interrupted_before_create_ram,
 
51
       interrupted_before_create_disc,
 
52
       interrupted_before_create_disc_only,
 
53
       interrupted_before_create_nostore,
 
54
       interrupted_before_delete_ram,
 
55
       interrupted_before_delete_disc,
 
56
       interrupted_before_delete_disc_only,
 
57
       interrupted_before_add_ram, interrupted_before_add_disc,
 
58
       interrupted_before_add_disc_only,
 
59
       interrupted_before_add_kill_copier,
 
60
       interrupted_before_move_ram,
 
61
       interrupted_before_move_disc,
 
62
       interrupted_before_move_disc_only,
 
63
       interrupted_before_move_kill_copier,
 
64
       interrupted_before_delcopy_ram,
 
65
       interrupted_before_delcopy_disc,
 
66
       interrupted_before_delcopy_disc_only,
 
67
       interrupted_before_delcopy_kill_copier,
 
68
       interrupted_before_addindex_ram,
 
69
       interrupted_before_addindex_disc,
 
70
       interrupted_before_addindex_disc_only,
 
71
       interrupted_before_delindex_ram,
 
72
       interrupted_before_delindex_disc,
 
73
       interrupted_before_delindex_disc_only,
 
74
       interrupted_before_change_type_ram2disc,
 
75
       interrupted_before_change_type_ram2disc_only,
 
76
       interrupted_before_change_type_disc2ram,
 
77
       interrupted_before_change_type_disc2disc_only,
 
78
       interrupted_before_change_type_disc_only2ram,
 
79
       interrupted_before_change_type_disc_only2disc,
 
80
       interrupted_before_change_type_other_node,
 
81
       interrupted_before_change_schema_type]},
 
82
     {interrupted_after_log_dump, [],
 
83
      [interrupted_after_create_ram,
 
84
       interrupted_after_create_disc,
 
85
       interrupted_after_create_disc_only,
 
86
       interrupted_after_create_nostore,
 
87
       interrupted_after_delete_ram,
 
88
       interrupted_after_delete_disc,
 
89
       interrupted_after_delete_disc_only,
 
90
       interrupted_after_add_ram, interrupted_after_add_disc,
 
91
       interrupted_after_add_disc_only,
 
92
       interrupted_after_add_kill_copier,
 
93
       interrupted_after_move_ram, interrupted_after_move_disc,
 
94
       interrupted_after_move_disc_only,
 
95
       interrupted_after_move_kill_copier,
 
96
       interrupted_after_delcopy_ram,
 
97
       interrupted_after_delcopy_disc,
 
98
       interrupted_after_delcopy_disc_only,
 
99
       interrupted_after_delcopy_kill_copier,
 
100
       interrupted_after_addindex_ram,
 
101
       interrupted_after_addindex_disc,
 
102
       interrupted_after_addindex_disc_only,
 
103
       interrupted_after_delindex_ram,
 
104
       interrupted_after_delindex_disc,
 
105
       interrupted_after_delindex_disc_only,
 
106
       interrupted_after_change_type_ram2disc,
 
107
       interrupted_after_change_type_ram2disc_only,
 
108
       interrupted_after_change_type_disc2ram,
 
109
       interrupted_after_change_type_disc2disc_only,
 
110
       interrupted_after_change_type_disc_only2ram,
 
111
       interrupted_after_change_type_disc_only2disc,
 
112
       interrupted_after_change_type_other_node,
 
113
       interrupted_after_change_schema_type]}].
 
114
 
 
115
init_per_group(_GroupName, Config) ->
 
116
    Config.
 
117
 
 
118
end_per_group(_GroupName, Config) ->
 
119
    Config.
 
120
 
 
121
interrupted_before_create_ram(suite) -> [];
 
122
interrupted_before_create_ram(Config) when is_list(Config) ->
 
123
    KillAt = {mnesia_dumper, dump_schema_op},
 
124
    interrupted_create(Config, ram_copies, all, KillAt).
 
125
 
 
126
interrupted_before_create_disc(suite) -> [];
 
127
interrupted_before_create_disc(Config) when is_list(Config) ->
 
128
    KillAt = {mnesia_dumper, dump_schema_op},
 
129
    interrupted_create(Config, disc_copies, all, KillAt).
 
130
 
 
131
interrupted_before_create_disc_only(suite) -> [];
 
132
interrupted_before_create_disc_only(Config) when is_list(Config) ->
 
133
    KillAt = {mnesia_dumper, dump_schema_op},
 
134
    interrupted_create(Config, disc_only_copies, all, KillAt).
 
135
 
 
136
interrupted_before_create_nostore(suite) -> [];
 
137
interrupted_before_create_nostore(Config) when is_list(Config) ->
 
138
    KillAt = {mnesia_dumper, dump_schema_op},
 
139
    interrupted_create(Config, ram_copies, one, KillAt).
 
140
 
 
141
interrupted_after_create_ram(suite) -> [];
 
142
interrupted_after_create_ram(Config) when is_list(Config) ->
 
143
    KillAt = {mnesia_dumper, post_dump},
 
144
    interrupted_create(Config, ram_copies, all, KillAt).
 
145
 
 
146
interrupted_after_create_disc(suite) -> [];
 
147
interrupted_after_create_disc(Config) when is_list(Config) ->
 
148
    KillAt = {mnesia_dumper, post_dump},
 
149
    interrupted_create(Config, disc_copies, all, KillAt).
 
150
 
 
151
interrupted_after_create_disc_only(suite) -> [];
 
152
interrupted_after_create_disc_only(Config) when is_list(Config) ->
 
153
    KillAt = {mnesia_dumper, post_dump},
 
154
    interrupted_create(Config, disc_only_copies, all, KillAt).
 
155
 
 
156
interrupted_after_create_nostore(suite) -> [];
 
157
interrupted_after_create_nostore(Config) when is_list(Config) ->
 
158
    KillAt = {mnesia_dumper, post_dump},
 
159
    interrupted_create(Config, ram_copies, one, KillAt).
 
160
 
 
161
%%% After dump don't need debug point
 
162
interrupted_create(Config, Type, _Where, {mnesia_dumper, post_dump}) ->
 
163
    [Node1] = Nodes = ?acquire_nodes(1, [{tc_timeout, timer:seconds(30)} | Config]),
 
164
    ?match({atomic, ok},mnesia:create_table(itrpt, [{Type, Nodes}])),
 
165
    ?match({atomic, ok},mnesia:create_table(test, [{disc_copies,[Node1]}])),
 
166
    ?match(ok, mnesia:dirty_write({itrpt, before, 1})),
 
167
    ?match(ok, mnesia:dirty_write({test, found_in_log, 1})),
 
168
    ?match(stopped, mnesia:stop()),
 
169
    ?match([], mnesia_test_lib:start_mnesia([Node1], [itrpt,test])),  
 
170
    %% Verify 
 
171
    ?match([{test, found_in_log, 1}], mnesia:dirty_read({test, found_in_log})),
 
172
    case Type of
 
173
        ram_copies ->         
 
174
            ?match([], mnesia:dirty_read({itrpt, before}));
 
175
        _ ->
 
176
            ?match([{itrpt, before, 1}], mnesia:dirty_read({itrpt, before}))
 
177
    end,
 
178
    ?verify_mnesia(Nodes, []);
 
179
interrupted_create(Config, Type, Where, KillAt) ->
 
180
    ?is_debug_compiled,
 
181
    [Node1, Node2] = Nodes = ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
182
    {success, [A]} = ?start_activities([Node2]),
 
183
    setup_dbgpoint(KillAt, Node2),
 
184
 
 
185
    if       %% CREATE TABLE
 
186
        Where == all ->    % tables on both nodes
 
187
            A ! fun() -> mnesia:create_table(itrpt, [{Type, Nodes}]) end;
 
188
        true ->            % no table on the killed node
 
189
            A ! fun() -> mnesia:create_table(itrpt, [{Type, [Node1]}]) end
 
190
    end,
 
191
    
 
192
    kill_at_debug(),
 
193
    ?match([], mnesia_test_lib:start_mnesia([Node2], [itrpt])),  
 
194
    %% Verify 
 
195
    ?match(ok, mnesia:dirty_write({itrpt, before, 1})),
 
196
    verify_tab(Node1, Node2),
 
197
    ?verify_mnesia(Nodes, []).
 
198
 
 
199
interrupted_before_delete_ram(suite) -> [];
 
200
interrupted_before_delete_ram(Config) when is_list(Config) ->
 
201
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
202
    interrupted_delete(Config, ram_copies, Debug_Point).
 
203
interrupted_before_delete_disc(suite) -> [];
 
204
interrupted_before_delete_disc(Config) when is_list(Config) ->
 
205
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
206
    interrupted_delete(Config, disc_copies, Debug_Point).
 
207
interrupted_before_delete_disc_only(suite) -> [];
 
208
interrupted_before_delete_disc_only(Config) when is_list(Config) ->
 
209
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
210
    interrupted_delete(Config, disc_only_copies, Debug_Point).
 
211
 
 
212
interrupted_after_delete_ram(suite) -> [];
 
213
interrupted_after_delete_ram(Config) when is_list(Config) ->
 
214
    Debug_Point = {mnesia_dumper, post_dump},    
 
215
    interrupted_delete(Config, ram_copies, Debug_Point).
 
216
interrupted_after_delete_disc(suite) -> [];
 
217
interrupted_after_delete_disc(Config) when is_list(Config) ->
 
218
    Debug_Point = {mnesia_dumper, post_dump},    
 
219
    interrupted_delete(Config, disc_copies, Debug_Point).
 
220
interrupted_after_delete_disc_only(suite) -> [];
 
221
interrupted_after_delete_disc_only(Config) when is_list(Config) ->
 
222
    Debug_Point = {mnesia_dumper, post_dump},    
 
223
    interrupted_delete(Config, disc_only_copies, Debug_Point).
 
224
 
 
225
interrupted_delete(Config, Type, KillAt) ->
 
226
    ?is_debug_compiled,
 
227
    [Node1, Node2] = Nodes = ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
228
    Tab = itrpt,
 
229
    ?match({atomic, ok}, mnesia:create_table(Tab, [{Type, [Node2]}])),
 
230
    ?match(ok, mnesia:dirty_write({Tab, before, 1})),
 
231
    {_Alive, Kill} = {Node1, Node2},
 
232
    {success, [A]} = ?start_activities([Kill]),
 
233
    
 
234
    setup_dbgpoint(KillAt, Kill),
 
235
    A ! fun() -> mnesia:delete_table(Tab) end,
 
236
    
 
237
    kill_at_debug(),
 
238
    ?match([], mnesia_test_lib:start_mnesia([Node2], [])),
 
239
    Bad = {badrpc, {'EXIT', {aborted,{no_exists, Tab, all}}}},
 
240
    ?match(Bad, rpc:call(Node1, mnesia, table_info, [Tab, all])),
 
241
    ?match(Bad, rpc:call(Node2, mnesia, table_info, [Tab, all])),
 
242
    ?verify_mnesia(Nodes, []).
 
243
 
 
244
interrupted_before_add_ram(suite) -> [];
 
245
interrupted_before_add_ram(Config) when is_list(Config) ->
 
246
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
247
    interrupted_add(Config, ram_copies, kill_reciever, Debug_Point).
 
248
interrupted_before_add_disc(suite) -> [];
 
249
interrupted_before_add_disc(Config) when is_list(Config) ->
 
250
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
251
    interrupted_add(Config, disc_copies, kill_reciever, Debug_Point).
 
252
interrupted_before_add_disc_only(suite) -> [];
 
253
interrupted_before_add_disc_only(Config) when is_list(Config) ->
 
254
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
255
    interrupted_add(Config, disc_only_copies, kill_reciever, Debug_Point).
 
256
interrupted_before_add_kill_copier(suite) -> [];
 
257
interrupted_before_add_kill_copier(Config) when is_list(Config) ->
 
258
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
259
    interrupted_add(Config, ram_copies, kill_copier, Debug_Point).
 
260
 
 
261
interrupted_after_add_ram(suite) -> [];
 
262
interrupted_after_add_ram(Config) when is_list(Config) ->
 
263
    Debug_Point = {mnesia_dumper, post_dump},    
 
264
    interrupted_add(Config, ram_copies, kill_reciever, Debug_Point).
 
265
interrupted_after_add_disc(suite) -> [];
 
266
interrupted_after_add_disc(Config) when is_list(Config) ->
 
267
    Debug_Point = {mnesia_dumper, post_dump},    
 
268
    interrupted_add(Config, disc_copies, kill_reciever, Debug_Point).
 
269
interrupted_after_add_disc_only(suite) -> [];
 
270
interrupted_after_add_disc_only(Config) when is_list(Config) ->
 
271
    Debug_Point = {mnesia_dumper, post_dump},    
 
272
    interrupted_add(Config, disc_only_copies, kill_reciever, Debug_Point).
 
273
interrupted_after_add_kill_copier(suite) -> [];
 
274
interrupted_after_add_kill_copier(Config) when is_list(Config) ->
 
275
    Debug_Point = {mnesia_dumper, post_dump},    
 
276
    interrupted_add(Config, ram_copies, kill_copier, Debug_Point).
 
277
 
 
278
%%% After dump don't need debug point
 
279
interrupted_add(Config, Type, _Where, {mnesia_dumper, post_dump}) ->
 
280
    [Node1, Node2] = Nodes =
 
281
        ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
282
    Tab = itrpt,
 
283
    ?match({atomic, ok}, mnesia:create_table(Tab, [{Type, [Node2]}, {local_content,true}])),
 
284
    ?match({atomic, ok},mnesia:create_table(test, [{disc_copies,[Node1]}])),
 
285
    ?match({atomic, ok}, mnesia:add_table_copy(Tab, Node1, Type)),
 
286
    ?match(ok, mnesia:dirty_write({itrpt, before, 1})),
 
287
    ?match(ok, mnesia:dirty_write({test, found_in_log, 1})),
 
288
    ?match(stopped, mnesia:stop()),
 
289
    ?match([], mnesia_test_lib:start_mnesia([Node1], [itrpt,test])),
 
290
    %% Verify 
 
291
    ?match([{test, found_in_log, 1}], mnesia:dirty_read({test, found_in_log})),
 
292
    case Type of
 
293
        ram_copies ->         
 
294
            ?match([], mnesia:dirty_read({itrpt, before}));
 
295
        _ ->
 
296
            ?match([{itrpt, before, 1}], mnesia:dirty_read({itrpt, before}))
 
297
    end,
 
298
    ?verify_mnesia(Nodes, []);
 
299
interrupted_add(Config, Type, Who, KillAt) ->
 
300
    ?is_debug_compiled,
 
301
    [Node1, Node2] = Nodes =
 
302
        ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
303
    {_Alive, Kill} = 
 
304
        if Who == kill_reciever -> 
 
305
                {Node1, Node2};
 
306
           true -> 
 
307
                {Node2, Node1}
 
308
        end,    
 
309
    {success, [A]} = ?start_activities([Kill]),
 
310
    Tab = itrpt,
 
311
    ?match({atomic, ok}, mnesia:create_table(Tab, [{Type, [Node1]}])),
 
312
    ?match(ok, mnesia:dirty_write({Tab, before, 1})),
 
313
    
 
314
    setup_dbgpoint(KillAt, Kill),
 
315
    
 
316
    A ! fun() -> mnesia:add_table_copy(Tab, Node2, Type) end,
 
317
    kill_at_debug(),
 
318
    ?match([], mnesia_test_lib:start_mnesia([Kill], [itrpt])),    
 
319
    verify_tab(Node1, Node2),
 
320
    ?verify_mnesia(Nodes, []).
 
321
 
 
322
interrupted_before_move_ram(suite) -> [];
 
323
interrupted_before_move_ram(Config) when is_list(Config) ->
 
324
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
325
    interrupted_move(Config, ram_copies, kill_reciever, Debug_Point).
 
326
interrupted_before_move_disc(suite) -> [];
 
327
interrupted_before_move_disc(Config) when is_list(Config) ->
 
328
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
329
    interrupted_move(Config, disc_copies, kill_reciever, Debug_Point).
 
330
interrupted_before_move_disc_only(suite) -> [];
 
331
interrupted_before_move_disc_only(Config) when is_list(Config) ->
 
332
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
333
    interrupted_move(Config, disc_only_copies, kill_reciever, Debug_Point).
 
334
interrupted_before_move_kill_copier(suite) -> [];
 
335
interrupted_before_move_kill_copier(Config) when is_list(Config) ->
 
336
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
337
    interrupted_move(Config, ram_copies, kill_copier, Debug_Point).
 
338
 
 
339
interrupted_after_move_ram(suite) -> [];
 
340
interrupted_after_move_ram(Config) when is_list(Config) ->
 
341
    Debug_Point = {mnesia_dumper, post_dump},    
 
342
    interrupted_move(Config, ram_copies, kill_reciever, Debug_Point).
 
343
interrupted_after_move_disc(suite) -> [];
 
344
interrupted_after_move_disc(Config) when is_list(Config) ->
 
345
    Debug_Point = {mnesia_dumper, post_dump},    
 
346
    interrupted_move(Config, disc_copies, kill_reciever, Debug_Point).
 
347
interrupted_after_move_disc_only(suite) -> [];
 
348
interrupted_after_move_disc_only(Config) when is_list(Config) ->
 
349
    Debug_Point = {mnesia_dumper, post_dump},    
 
350
    interrupted_move(Config, disc_only_copies, kill_reciever, Debug_Point).
 
351
interrupted_after_move_kill_copier(suite) -> [];
 
352
interrupted_after_move_kill_copier(Config) when is_list(Config) ->
 
353
    Debug_Point = {mnesia_dumper, post_dump},    
 
354
    interrupted_move(Config, ram_copies, kill_copier, Debug_Point).
 
355
 
 
356
%%% After dump don't need debug point
 
357
interrupted_move(Config, Type, _Where, {mnesia_dumper, post_dump}) ->
 
358
    [Node1, Node2] = Nodes =
 
359
        ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
360
    Tab = itrpt,
 
361
    ?match({atomic, ok},mnesia:create_table(test, [{disc_copies,[Node1]}])),
 
362
    ?match({atomic, ok}, mnesia:create_table(Tab, [{Type, [Node1]}])),
 
363
    ?match(ok, mnesia:dirty_write({itrpt, before, 1})),
 
364
    ?match({atomic, ok}, mnesia:move_table_copy(Tab, Node1, Node2)),
 
365
    ?match(ok, mnesia:dirty_write({itrpt, aFter, 1})),
 
366
    ?match(ok, mnesia:dirty_write({test, found_in_log, 1})),
 
367
    ?match(stopped, mnesia:stop()),
 
368
    ?match([], mnesia_test_lib:start_mnesia([Node1], [itrpt,test])),
 
369
    %% Verify 
 
370
    ?match([{test, found_in_log, 1}], mnesia:dirty_read({test, found_in_log})),
 
371
    ?match([{itrpt, before, 1}], mnesia:dirty_read({itrpt, before})),
 
372
    ?match([{itrpt, aFter, 1}], mnesia:dirty_read({itrpt, aFter})),
 
373
    ?verify_mnesia(Nodes, []);
 
374
interrupted_move(Config, Type, Who, KillAt) ->
 
375
    ?is_debug_compiled,
 
376
    [Node1, Node2] = Nodes = 
 
377
        ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
378
    Tab = itrpt,
 
379
    ?match({atomic, ok}, mnesia:create_table(Tab, [{Type, [Node1]}])),
 
380
    ?match(ok, mnesia:dirty_write({Tab, before, 1})),
 
381
 
 
382
    {_Alive, Kill} = 
 
383
        if Who == kill_reciever -> 
 
384
                if Type == ram_copies -> 
 
385
                        {atomic, ok} = mnesia:dump_tables([Tab]);
 
386
                   true -> 
 
387
                        ignore
 
388
                end,
 
389
                {Node1, Node2};
 
390
           true -> 
 
391
                {Node2, Node1}
 
392
        end,
 
393
    
 
394
    {success, [A]} = ?start_activities([Kill]),
 
395
    
 
396
    setup_dbgpoint(KillAt, Kill),
 
397
    A ! fun() -> mnesia:move_table_copy(Tab, Node1, Node2) end,
 
398
    kill_at_debug(),
 
399
    ?match([], mnesia_test_lib:start_mnesia([Kill], [itrpt])),    
 
400
    verify_tab(Node1, Node2),
 
401
    ?verify_mnesia(Nodes, []).
 
402
 
 
403
interrupted_before_delcopy_ram(suite) -> [];
 
404
interrupted_before_delcopy_ram(Config) when is_list(Config) ->
 
405
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
406
    interrupted_delcopy(Config, ram_copies, kill_reciever, Debug_Point).
 
407
interrupted_before_delcopy_disc(suite) -> [];
 
408
interrupted_before_delcopy_disc(Config) when is_list(Config) ->
 
409
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
410
    interrupted_delcopy(Config, disc_copies, kill_reciever, Debug_Point).
 
411
interrupted_before_delcopy_disc_only(suite) -> [];
 
412
interrupted_before_delcopy_disc_only(Config) when is_list(Config) ->
 
413
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
414
    interrupted_delcopy(Config, disc_only_copies, kill_reciever, Debug_Point).
 
415
interrupted_before_delcopy_kill_copier(suite) -> [];
 
416
interrupted_before_delcopy_kill_copier(Config) when is_list(Config) ->
 
417
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
418
    interrupted_delcopy(Config, ram_copies, kill_copier, Debug_Point).
 
419
 
 
420
interrupted_after_delcopy_ram(suite) -> [];
 
421
interrupted_after_delcopy_ram(Config) when is_list(Config) ->
 
422
    Debug_Point = {mnesia_dumper, post_dump},    
 
423
    interrupted_delcopy(Config, ram_copies, kill_reciever, Debug_Point).
 
424
interrupted_after_delcopy_disc(suite) -> [];
 
425
interrupted_after_delcopy_disc(Config) when is_list(Config) ->
 
426
    Debug_Point = {mnesia_dumper, post_dump},    
 
427
    interrupted_delcopy(Config, disc_copies, kill_reciever, Debug_Point).
 
428
interrupted_after_delcopy_disc_only(suite) -> [];
 
429
interrupted_after_delcopy_disc_only(Config) when is_list(Config) ->
 
430
    Debug_Point = {mnesia_dumper, post_dump},    
 
431
    interrupted_delcopy(Config, disc_only_copies, kill_reciever, Debug_Point).
 
432
interrupted_after_delcopy_kill_copier(suite) -> [];
 
433
interrupted_after_delcopy_kill_copier(Config) when is_list(Config) ->
 
434
    Debug_Point = {mnesia_dumper, post_dump},    
 
435
    interrupted_delcopy(Config, ram_copies, kill_copier, Debug_Point).
 
436
 
 
437
 
 
438
%%% After dump don't need debug point
 
439
interrupted_delcopy(Config, Type, _Where, {mnesia_dumper, post_dump}) ->
 
440
    [Node1, Node2] = Nodes =
 
441
        ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
442
    Tab = itrpt,
 
443
    ?match({atomic, ok},mnesia:create_table(test, [{disc_copies,[Node1]}])),
 
444
    ?match({atomic, ok}, mnesia:create_table(Tab, [{Type, [Node1,Node2]}])),
 
445
    ?match({atomic, ok}, mnesia:del_table_copy(Tab, Node1)),
 
446
    ?match(ok, mnesia:dirty_write({test, found_in_log, 1})),
 
447
    ?match(stopped, mnesia:stop()),
 
448
    ?match([], mnesia_test_lib:start_mnesia([Node1], [test])),
 
449
    %% Verify 
 
450
    ?match([{test, found_in_log, 1}], mnesia:dirty_read({test, found_in_log})),
 
451
    ?match([Node2], mnesia:table_info(itrpt,Type)),
 
452
    ?verify_mnesia(Nodes, []);
 
453
interrupted_delcopy(Config, Type, Who, KillAt) ->
 
454
    ?is_debug_compiled,
 
455
    [Node1, Node2] = Nodes = 
 
456
        ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
457
    Tab = itrpt,
 
458
    ?match({atomic, ok}, mnesia:create_table(Tab, [{Type, [Node1, Node2]}])),
 
459
    ?match(ok, mnesia:dirty_write({Tab, before, 1})),
 
460
 
 
461
    {_Alive, Kill} = 
 
462
        if Who == kill_reciever -> 
 
463
                {Node1, Node2};
 
464
           true -> 
 
465
                if 
 
466
                    Type == ram_copies -> 
 
467
                        {atomic, ok} = mnesia:dump_tables([Tab]);
 
468
                    true -> 
 
469
                        ignore
 
470
                end,
 
471
                {Node2, Node1}
 
472
        end,
 
473
 
 
474
    {success, [A]} = ?start_activities([Kill]),
 
475
    setup_dbgpoint(KillAt, Kill),
 
476
    A ! fun() -> mnesia:del_table_copy(Tab, Node2) end,
 
477
    kill_at_debug(),
 
478
    ?match([], mnesia_test_lib:start_mnesia([Kill], [itrpt])),    
 
479
    verify_tab(Node1, Node2),
 
480
    ?verify_mnesia(Nodes, []).
 
481
 
 
482
interrupted_before_addindex_ram(suite) -> [];
 
483
interrupted_before_addindex_ram(Config) when is_list(Config) ->
 
484
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
485
    interrupted_addindex(Config, ram_copies, Debug_Point).
 
486
interrupted_before_addindex_disc(suite) -> [];
 
487
interrupted_before_addindex_disc(Config) when is_list(Config) ->
 
488
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
489
    interrupted_addindex(Config, disc_copies, Debug_Point).
 
490
interrupted_before_addindex_disc_only(suite) -> [];
 
491
interrupted_before_addindex_disc_only(Config) when is_list(Config) ->
 
492
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
493
    interrupted_addindex(Config, disc_only_copies, Debug_Point).
 
494
 
 
495
interrupted_after_addindex_ram(suite) -> [];
 
496
interrupted_after_addindex_ram(Config) when is_list(Config) ->
 
497
    Debug_Point = {mnesia_dumper, post_dump},
 
498
    interrupted_addindex(Config, ram_copies, Debug_Point).
 
499
interrupted_after_addindex_disc(suite) -> [];
 
500
interrupted_after_addindex_disc(Config) when is_list(Config) ->
 
501
    Debug_Point = {mnesia_dumper, post_dump},    
 
502
    interrupted_addindex(Config, disc_copies, Debug_Point).
 
503
interrupted_after_addindex_disc_only(suite) -> [];
 
504
interrupted_after_addindex_disc_only(Config) when is_list(Config) ->
 
505
    Debug_Point = {mnesia_dumper, post_dump},    
 
506
    interrupted_addindex(Config, disc_only_copies, Debug_Point).
 
507
 
 
508
 
 
509
%%% After dump don't need debug point
 
510
interrupted_addindex(Config, Type, {mnesia_dumper, post_dump}) ->
 
511
    [Node1] = Nodes = ?acquire_nodes(1, [{tc_timeout, timer:seconds(30)} | Config]),
 
512
    Tab = itrpt,
 
513
    ?match({atomic,ok},mnesia:create_table(Tab, [{Type, Nodes}])),
 
514
    ?match({atomic,ok},mnesia:create_table(test, [{disc_copies,[Node1]}])),
 
515
    ?match({atomic,ok}, mnesia:add_table_index(Tab, val)),
 
516
    ?match(ok, mnesia:dirty_write({itrpt, before, 1})),
 
517
    ?match(ok, mnesia:dirty_write({test, found_in_log, 1})),
 
518
    ?match(stopped, mnesia:stop()),
 
519
    ?match([], mnesia_test_lib:start_mnesia([Node1], [itrpt,test])),  
 
520
    %% Verify 
 
521
    ?match([{test, found_in_log, 1}], mnesia:dirty_read({test, found_in_log})),
 
522
    case Type of
 
523
        ram_copies ->         
 
524
            ?match([], mnesia:dirty_index_read(itrpt, 1, val));
 
525
        _ ->
 
526
            ?match([{itrpt, before, 1}], mnesia:dirty_index_read(itrpt, 1, val))
 
527
    end,
 
528
    ?verify_mnesia(Nodes, []);
 
529
interrupted_addindex(Config, Type, KillAt) ->
 
530
    ?is_debug_compiled,
 
531
    [Node1, Node2] = Nodes = ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
532
    Tab = itrpt,
 
533
    ?match({atomic, ok}, mnesia:create_table(Tab, [{Type, [Node1]}])),
 
534
    ?match(ok, mnesia:dirty_write({Tab, before, 1})),
 
535
    {_Alive, Kill} = {Node1, Node2},
 
536
    {success, [A]} = ?start_activities([Kill]),
 
537
    
 
538
    setup_dbgpoint(KillAt, Kill),
 
539
    A ! fun() -> mnesia:add_table_index(Tab, val) end,
 
540
    kill_at_debug(),
 
541
    ?match([], mnesia_test_lib:start_mnesia([Node2], [])),
 
542
 
 
543
    verify_tab(Node1, Node2),
 
544
    ?match([{Tab, b, a}, {Tab, a, a}], 
 
545
           rpc:call(Node1, mnesia, dirty_index_read, [itrpt, a, val])),
 
546
    ?match([{Tab, b, a}, {Tab, a, a}], 
 
547
           rpc:call(Node2, mnesia, dirty_index_read, [itrpt, a, val])),
 
548
    ?verify_mnesia(Nodes, []).
 
549
 
 
550
interrupted_before_delindex_ram(suite) -> [];
 
551
interrupted_before_delindex_ram(Config) when is_list(Config) ->
 
552
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
553
    interrupted_delindex(Config, ram_copies, Debug_Point).
 
554
interrupted_before_delindex_disc(suite) -> [];
 
555
interrupted_before_delindex_disc(Config) when is_list(Config) ->
 
556
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
557
    interrupted_delindex(Config, disc_copies, Debug_Point).
 
558
interrupted_before_delindex_disc_only(suite) -> [];
 
559
interrupted_before_delindex_disc_only(Config) when is_list(Config) ->
 
560
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
561
    interrupted_delindex(Config, disc_only_copies, Debug_Point).
 
562
 
 
563
interrupted_after_delindex_ram(suite) -> [];
 
564
interrupted_after_delindex_ram(Config) when is_list(Config) ->
 
565
    Debug_Point = {mnesia_dumper, post_dump},    
 
566
    interrupted_delindex(Config, ram_copies, Debug_Point).
 
567
interrupted_after_delindex_disc(suite) -> [];
 
568
interrupted_after_delindex_disc(Config) when is_list(Config) ->
 
569
    Debug_Point = {mnesia_dumper, post_dump},    
 
570
    interrupted_delindex(Config, disc_copies, Debug_Point).
 
571
interrupted_after_delindex_disc_only(suite) -> [];
 
572
interrupted_after_delindex_disc_only(Config) when is_list(Config) ->
 
573
    Debug_Point = {mnesia_dumper, post_dump},    
 
574
    interrupted_delindex(Config, disc_only_copies, Debug_Point).
 
575
 
 
576
%%% After dump don't need debug point
 
577
interrupted_delindex(Config, Type, {mnesia_dumper, post_dump}) ->
 
578
    [Node1] = Nodes = ?acquire_nodes(1, [{tc_timeout, timer:seconds(30)} | Config]),
 
579
    Tab = itrpt,
 
580
    ?match({atomic,ok},mnesia:create_table(Tab, [{Type, Nodes},{index,[val]}])),
 
581
    ?match({atomic,ok},mnesia:create_table(test, [{disc_copies,[Node1]}])),
 
582
    ?match({atomic,ok}, mnesia:del_table_index(Tab, val)),
 
583
    ?match(ok, mnesia:dirty_write({itrpt, before, 1})),
 
584
    ?match(ok, mnesia:dirty_write({test, found_in_log, 1})),
 
585
    ?match(stopped, mnesia:stop()),
 
586
    ?match([], mnesia_test_lib:start_mnesia([Node1], [itrpt,test])),  
 
587
    %% Verify 
 
588
    ?match([{test, found_in_log, 1}], mnesia:dirty_read({test, found_in_log})),
 
589
    ?match({'EXIT',{aborted,{badarg,_}}}, mnesia:dirty_index_read(itrpt, 1, val)),
 
590
    ?verify_mnesia(Nodes, []);
 
591
 
 
592
interrupted_delindex(Config, Type, KillAt) ->
 
593
    ?is_debug_compiled,
 
594
    [Node1, Node2] = Nodes = ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
595
    Tab = itrpt,
 
596
    ?match({atomic, ok}, mnesia:create_table(Tab, [{index, [val]}, 
 
597
                                                   {Type, [Node1]}])),
 
598
    ?match(ok, mnesia:dirty_write({Tab, before, 1})),
 
599
    {_Alive, Kill} = {Node1, Node2},
 
600
    {success, [A]} = ?start_activities([Kill]),
 
601
    setup_dbgpoint(KillAt, Kill),
 
602
    A ! fun() -> mnesia:del_table_index(Tab, val) end,
 
603
    kill_at_debug(),
 
604
    ?match([], mnesia_test_lib:start_mnesia([Node2], [])),  
 
605
    verify_tab(Node1, Node2),
 
606
    ?match({badrpc, _}, rpc:call(Node1, mnesia, dirty_index_read, [itrpt, a, val])),
 
607
    ?match({badrpc, _}, rpc:call(Node2, mnesia, dirty_index_read, [itrpt, a, val])),
 
608
    ?match([], rpc:call(Node1, mnesia, table_info, [Tab, index])),
 
609
    ?match([], rpc:call(Node2, mnesia, table_info, [Tab, index])),
 
610
    ?verify_mnesia(Nodes, []).
 
611
 
 
612
interrupted_before_change_type_ram2disc(suite) -> [];
 
613
interrupted_before_change_type_ram2disc(Config) when is_list(Config) ->
 
614
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
615
    interrupted_change_type(Config, ram_copies, disc_copies, changer, Debug_Point).
 
616
interrupted_before_change_type_ram2disc_only(suite) -> [];
 
617
interrupted_before_change_type_ram2disc_only(Config) when is_list(Config) ->
 
618
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
619
    interrupted_change_type(Config, ram_copies, disc_only_copies, changer, Debug_Point).    
 
620
interrupted_before_change_type_disc2ram(suite) -> [];
 
621
interrupted_before_change_type_disc2ram(Config) when is_list(Config) ->
 
622
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
623
    interrupted_change_type(Config, disc_copies, ram_copies, changer, Debug_Point).
 
624
interrupted_before_change_type_disc2disc_only(suite) -> [];
 
625
interrupted_before_change_type_disc2disc_only(Config) when is_list(Config) ->
 
626
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
627
    interrupted_change_type(Config, disc_copies, disc_only_copies, changer, Debug_Point).
 
628
interrupted_before_change_type_disc_only2ram(suite) -> [];
 
629
interrupted_before_change_type_disc_only2ram(Config) when is_list(Config) ->
 
630
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
631
    interrupted_change_type(Config, disc_only_copies, ram_copies, changer, Debug_Point).
 
632
interrupted_before_change_type_disc_only2disc(suite) -> [];
 
633
interrupted_before_change_type_disc_only2disc(Config) when is_list(Config) ->
 
634
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
635
    interrupted_change_type(Config, disc_only_copies, disc_copies, changer, Debug_Point).
 
636
interrupted_before_change_type_other_node(suite) -> [];
 
637
interrupted_before_change_type_other_node(Config) when is_list(Config) ->
 
638
    Debug_Point = {mnesia_dumper, dump_schema_op},    
 
639
    interrupted_change_type(Config, ram_copies, disc_copies, the_other_one, Debug_Point).
 
640
 
 
641
interrupted_after_change_type_ram2disc(suite) -> [];
 
642
interrupted_after_change_type_ram2disc(Config) when is_list(Config) ->
 
643
    Debug_Point = {mnesia_dumper, post_dump},    
 
644
    interrupted_change_type(Config, ram_copies, disc_copies, changer, Debug_Point).
 
645
interrupted_after_change_type_ram2disc_only(suite) -> [];
 
646
interrupted_after_change_type_ram2disc_only(Config) when is_list(Config) ->
 
647
    Debug_Point = {mnesia_dumper, post_dump},    
 
648
    interrupted_change_type(Config, ram_copies, disc_only_copies, changer, Debug_Point).    
 
649
interrupted_after_change_type_disc2ram(suite) -> [];
 
650
interrupted_after_change_type_disc2ram(Config) when is_list(Config) ->
 
651
    Debug_Point = {mnesia_dumper, post_dump},    
 
652
    interrupted_change_type(Config, disc_copies, ram_copies, changer, Debug_Point).
 
653
interrupted_after_change_type_disc2disc_only(suite) -> [];
 
654
interrupted_after_change_type_disc2disc_only(Config) when is_list(Config) ->
 
655
    Debug_Point = {mnesia_dumper, post_dump},    
 
656
    interrupted_change_type(Config, disc_copies, disc_only_copies, changer, Debug_Point).
 
657
interrupted_after_change_type_disc_only2ram(suite) -> [];
 
658
interrupted_after_change_type_disc_only2ram(Config) when is_list(Config) ->
 
659
    Debug_Point = {mnesia_dumper, post_dump},    
 
660
    interrupted_change_type(Config, disc_only_copies, ram_copies, changer, Debug_Point).
 
661
interrupted_after_change_type_disc_only2disc(suite) -> [];
 
662
interrupted_after_change_type_disc_only2disc(Config) when is_list(Config) ->
 
663
    Debug_Point = {mnesia_dumper, post_dump},    
 
664
    interrupted_change_type(Config, disc_only_copies, disc_copies, changer, Debug_Point).
 
665
interrupted_after_change_type_other_node(suite) -> [];
 
666
interrupted_after_change_type_other_node(Config) when is_list(Config) ->
 
667
    Debug_Point = {mnesia_dumper, post_dump},    
 
668
    interrupted_change_type(Config, ram_copies, disc_copies, the_other_one, Debug_Point).
 
669
 
 
670
interrupted_change_type(Config, FromType, ToType, Who, KillAt) ->
 
671
    ?is_debug_compiled,
 
672
    [Node1, Node2] = Nodes = ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
673
    Tab = itrpt,
 
674
    ?match({atomic, ok}, mnesia:create_table(Tab, [{FromType, [Node2, Node1]}])),
 
675
    ?match(ok, mnesia:dirty_write({Tab, before, 1})),
 
676
 
 
677
    {_Alive, Kill} = 
 
678
        if Who == changer -> {Node1, Node2};
 
679
           true ->           {Node2, Node1}
 
680
        end,
 
681
    
 
682
    {success, [A]} = ?start_activities([Kill]),
 
683
    setup_dbgpoint(KillAt, Kill),
 
684
    A ! fun() -> mnesia:change_table_copy_type(Tab, Node2, ToType) end,
 
685
    kill_at_debug(),
 
686
    ?match([], mnesia_test_lib:start_mnesia(Nodes, [itrpt])),        
 
687
    verify_tab(Node1, Node2),
 
688
    ?match(FromType, rpc:call(Node1, mnesia, table_info, [Tab, storage_type])),
 
689
    ?match(ToType, rpc:call(Node2, mnesia, table_info, [Tab, storage_type])),
 
690
    ?verify_mnesia(Nodes, []).
 
691
 
 
692
interrupted_before_change_schema_type(suite) ->     [];
 
693
interrupted_before_change_schema_type(Config) when is_list(Config) ->
 
694
    KillAt = {mnesia_dumper, dump_schema_op},
 
695
    interrupted_change_schema_type(Config, KillAt).
 
696
 
 
697
interrupted_after_change_schema_type(suite) ->     [];
 
698
interrupted_after_change_schema_type(Config) when is_list(Config) ->
 
699
    KillAt = {mnesia_dumper, post_dump},
 
700
    interrupted_change_schema_type(Config, KillAt).
 
701
 
 
702
-define(cleanup(N, Config),
 
703
        mnesia_test_lib:prepare_test_case([{reload_appls, [mnesia]}],
 
704
                                          N, Config, ?FILE, ?LINE)).
 
705
    
 
706
interrupted_change_schema_type(Config, KillAt) ->
 
707
    ?is_debug_compiled,
 
708
    [Node1, Node2] = Nodes = ?acquire_nodes(2, [{tc_timeout, timer:seconds(30)} | Config]),
 
709
 
 
710
    Tab = itrpt,
 
711
    ?match({atomic, ok}, mnesia:create_table(Tab, [{ram_copies, [Node2, Node1]}])),
 
712
    ?match(ok, mnesia:dirty_write({Tab, before, 1})),
 
713
    
 
714
    {success, [A]} = ?start_activities([Node2]),
 
715
    setup_dbgpoint(KillAt, Node2),      
 
716
    
 
717
    A ! fun() -> mnesia:change_table_copy_type(schema, Node2, ram_copies) end,
 
718
    kill_at_debug(),    
 
719
    ?match(ok, rpc:call(Node2, mnesia, start, [[{extra_db_nodes, [Node1, Node2]}]])),
 
720
    ?match(ok, rpc:call(Node2, mnesia, wait_for_tables, [[itrpt, schema], 2000])),
 
721
    ?match(disc_copies, rpc:call(Node1, mnesia, table_info, [schema, storage_type])),
 
722
    ?match(ram_copies, rpc:call(Node2, mnesia, table_info,  [schema, storage_type])),
 
723
    
 
724
    %% Go back to disc_copies !!    
 
725
    {success, [B]} = ?start_activities([Node2]),
 
726
    setup_dbgpoint(KillAt, Node2),      
 
727
    B ! fun() -> mnesia:change_table_copy_type(schema, Node2, disc_copies) end,
 
728
    kill_at_debug(),
 
729
 
 
730
    ?match(ok, rpc:call(Node2, mnesia, start, [[{extra_db_nodes, [Node1, Node2]}]])),
 
731
    ?match(ok, rpc:call(Node2, mnesia, wait_for_tables, [[itrpt, schema], 2000])),
 
732
    ?match(disc_copies, rpc:call(Node1, mnesia, table_info, [schema, storage_type])),
 
733
    ?match(disc_copies, rpc:call(Node2, mnesia, table_info,  [schema, storage_type])),
 
734
 
 
735
    ?verify_mnesia(Nodes, []),
 
736
    ?cleanup(2, Config).
 
737
 
 
738
%%% Helpers
 
739
verify_tab(Node1, Node2) ->
 
740
    ?match({atomic, ok}, 
 
741
           rpc:call(Node1, mnesia, transaction, [fun() -> mnesia:dirty_write({itrpt, a, a}) end])),
 
742
    ?match({atomic, ok},
 
743
           rpc:call(Node2, mnesia, transaction, [fun() -> mnesia:dirty_write({itrpt, b, a}) end])),
 
744
    ?match([{itrpt,a,a}], rpc:call(Node1, mnesia, dirty_read, [{itrpt, a}])), 
 
745
    ?match([{itrpt,a,a}], rpc:call(Node2, mnesia, dirty_read, [{itrpt, a}])),
 
746
    ?match([{itrpt,b,a}], rpc:call(Node1, mnesia, dirty_read, [{itrpt, b}])), 
 
747
    ?match([{itrpt,b,a}], rpc:call(Node2, mnesia, dirty_read, [{itrpt, b}])),
 
748
    ?match([{itrpt,before,1}], rpc:call(Node1, mnesia, dirty_read, [{itrpt, before}])),
 
749
    ?match([{itrpt,before,1}], rpc:call(Node2, mnesia, dirty_read, [{itrpt, before}])).
 
750
 
 
751
setup_dbgpoint(DbgPoint, Where) -> 
 
752
    Self = self(),
 
753
    TestFun = fun(_, [InitBy]) ->
 
754
                      case InitBy of
 
755
                          schema_prepare ->
 
756
                              ignore;
 
757
                          schema_begin ->
 
758
                              ignore;
 
759
                          _Other ->
 
760
                              ?deactivate_debug_fun(DbgPoint),
 
761
                              unlink(Self),
 
762
                              Self ! {fun_done, node()},
 
763
                              timer:sleep(infinity)
 
764
                      end
 
765
              end, 
 
766
    %% Kill when debug has been reached
 
767
    ?remote_activate_debug_fun(Where, DbgPoint, TestFun, []).
 
768
 
 
769
kill_at_debug() ->   
 
770
    %% Wait till it's killed
 
771
    receive 
 
772
        {fun_done, Node} -> 
 
773
            ?match([], mnesia_test_lib:kill_mnesia([Node]))
 
774
    after 
 
775
        timer:minutes(1) -> ?error("Timeout in kill_at_debug", [])
 
776
    end.
 
777