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

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_frag_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 1999-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_frag_test).
 
22
-author('hakan@erix.ericsson.se').
 
23
-include("mnesia_test_lib.hrl").
 
24
 
 
25
-compile([export_all]).
 
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
-define(match_dist(ExpectedRes, Expr),
 
34
        case ?match(ExpectedRes, Expr) of
 
35
            
 
36
        mnesia_test_lib:error(Format, Args,?FILE,?LINE)).
 
37
 
 
38
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
39
 
 
40
all() -> 
 
41
    [{group, light}, {group, medium}].
 
42
 
 
43
groups() -> 
 
44
    [{light, [], [{group, nice}, {group, evil}]},
 
45
     {medium, [], [consistency]},
 
46
     {nice, [],
 
47
      [nice_single, nice_multi, nice_access, iter_access]},
 
48
     {evil, [],
 
49
      [evil_create, evil_delete, evil_change, evil_combine,
 
50
       evil_loop, evil_delete_db_node]}].
 
51
 
 
52
init_per_group(_GroupName, Config) ->
 
53
    Config.
 
54
 
 
55
end_per_group(_GroupName, Config) ->
 
56
    Config.
 
57
 
 
58
 
 
59
 
 
60
 
 
61
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
62
 
 
63
 
 
64
nice_single(suite) -> [];
 
65
nice_single(Config) when is_list(Config) ->
 
66
    [Node1, Node2] = Nodes = ?acquire_nodes(2, Config),
 
67
 
 
68
    %% Create a table with 2 fragments and 12 records
 
69
    Tab = nice_frag,
 
70
    Props = [{n_fragments, 2}, {node_pool, [Node1]}],
 
71
    ?match({atomic, ok}, mnesia:create_table(Tab, [{frag_properties, Props}])),
 
72
    Records = [{Tab, N, -N} || N <- lists:seq(1, 12)],
 
73
    [frag_write(Tab, R)  || R <- Records],
 
74
    ?match([{Node1, 2}], frag_dist(Tab)),
 
75
    ?match([8, 4], frag_rec_dist(Tab)),
 
76
 
 
77
    %% Adding a new node to pool should not affect distribution
 
78
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_node, Node2})),
 
79
    Dist =  frag_dist(Tab), 
 
80
    ?match([{Node2, 0}, {Node1, 2}], Dist), 
 
81
    ?match([8, 4], frag_rec_dist(Tab)),
 
82
 
 
83
    %% Add new fragment hopefully on the new node
 
84
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, Dist})),
 
85
    Dist2 =  frag_dist(Tab), 
 
86
    ?match([{Node2, 1}, {Node1, 2}], Dist2), 
 
87
    ?match([3, 4, 5], frag_rec_dist(Tab)),
 
88
    
 
89
    %% Add new fragment hopefully on the new node
 
90
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, Dist2})),
 
91
    Dist3 =  frag_dist(Tab), 
 
92
    ?match([{Node1, 2}, {Node2, 2}], Dist3), 
 
93
    ?match([3, 2, 5, 2], frag_rec_dist(Tab)),
 
94
 
 
95
    %% Add new fragment hopefully on the new node
 
96
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, Dist3})),
 
97
    Dist4 =  frag_dist(Tab), 
 
98
    ?match([{Node2, 2}, {Node1, 3}], Dist4), 
 
99
    ?match([_, _, _, _, _], frag_rec_dist(Tab)),
 
100
 
 
101
    %% Dropping a node in pool should not affect distribution
 
102
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {del_node, Node1})),
 
103
    ?match([{Node2, 2}, {Node1, 3}], frag_dist(Tab)),
 
104
    ?match([_, _, _, _, _], frag_rec_dist(Tab)),
 
105
 
 
106
    %% Dropping a fragment
 
107
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
108
    Dist5 =  frag_dist(Tab), 
 
109
    ?match([{Node2, 2}, {Node1, 2}], Dist5), 
 
110
    ?match([3, 2, 5, 2], frag_rec_dist(Tab)),
 
111
    
 
112
    %% Add new fragment hopefully on the new node
 
113
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, Dist5})),
 
114
    Dist6 =  frag_dist(Tab), 
 
115
    ?match([{Node2, 3}, {Node1, 2}], Dist6), 
 
116
    ?match([_, _, _, _, _], frag_rec_dist(Tab)),
 
117
 
 
118
    %% Dropping all fragments but one
 
119
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
120
    ?match([3, 2, 5, 2], frag_rec_dist(Tab)),
 
121
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
122
    ?match([3, 4, 5], frag_rec_dist(Tab)),
 
123
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
124
    ?match([8, 4], frag_rec_dist(Tab)),
 
125
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
126
    ?match([{Node2, 0}, {Node1, 1}], frag_dist(Tab)), 
 
127
    ?match([12], frag_rec_dist(Tab)),
 
128
             
 
129
    %% Defragmenting the table clears frag_properties
 
130
    ?match(Len when Len > 0,
 
131
                    length(mnesia:table_info(Tab, frag_properties))),
 
132
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, deactivate)),
 
133
    ?match(0, length(mnesia:table_info(Tab, frag_properties))),
 
134
 
 
135
    %% Making the table fragmented again
 
136
    Props2 = [{n_fragments, 1}],
 
137
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {activate, Props2})),
 
138
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, frag_dist(Tab)})),
 
139
    Dist7 = frag_dist(Tab),
 
140
    ?match([{Node1, 1}, {Node2, 1}], Dist7),
 
141
    ?match([8, 4], frag_rec_dist(Tab)),
 
142
 
 
143
    %% Deleting the fragmented table
 
144
    ?match({atomic, ok}, mnesia:delete_table(Tab)),
 
145
    ?match(false, lists:member(Tab, mnesia:system_info(tables))),
 
146
             
 
147
    ?verify_mnesia(Nodes, []).
 
148
 
 
149
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
150
 
 
151
nice_multi(doc) ->
 
152
    ["Extending the nice case with one more node, ",
 
153
     "one more replica and a foreign key"];
 
154
nice_multi(suite) -> [];
 
155
nice_multi(Config) when is_list(Config) ->
 
156
    [Node1, Node2, Node3] = Nodes = ?acquire_nodes(3, Config),
 
157
 
 
158
    %% Create a table with 2 fragments and 8 records
 
159
    Tab = frag_master,
 
160
    Name = frag_rec,
 
161
    Type = case mnesia_test_lib:diskless(Config) of 
 
162
               true -> n_ram_copies;
 
163
               false -> n_disc_copies
 
164
           end,
 
165
    Props = [{n_fragments, 2},
 
166
             {Type, 2},
 
167
             {node_pool, [Node2, Node1]}],
 
168
    Def = [{frag_properties, Props},
 
169
           {attributes, [id, data]},
 
170
           {record_name, Name}],
 
171
    ?match({atomic, ok}, mnesia:create_table(Tab, Def)),
 
172
    [frag_write(Tab, {Name, Id, -Id})  || Id <- lists:seq(1, 8)],
 
173
    ?match([6, 2], frag_rec_dist(Tab)),
 
174
    ?match([{Node2, 2}, {Node1, 2}], frag_dist(Tab)),
 
175
    
 
176
    %% And connect another table to it, via a foreign key
 
177
    TabF = frag_slave,
 
178
    PropsF = [{foreign_key, {Tab, foreign_id}}],
 
179
    DefF = [{frag_properties, PropsF},
 
180
            {attributes, [id, foreign_id]}],
 
181
 
 
182
    ?match({atomic, ok}, mnesia:create_table(TabF, DefF)),
 
183
    [frag_write(TabF, {TabF, {Id}, Id})  || Id <- lists:seq(1, 16)],
 
184
    ?match([10, 6], frag_rec_dist(TabF)),
 
185
    ?match([{Node2, 2}, {Node1, 2}], frag_dist(TabF)),
 
186
 
 
187
    %% Adding a new node to pool should not affect distribution
 
188
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_node, Node3})),
 
189
    Dist =  frag_dist(Tab), 
 
190
    ?match([{Node3, 0}, {Node2, 2}, {Node1, 2}], Dist), 
 
191
    ?match([6, 2], frag_rec_dist(Tab)),
 
192
    DistF =  frag_dist(TabF), 
 
193
    ?match([{Node3, 0}, {Node2, 2}, {Node1, 2}], DistF), 
 
194
    ?match([10, 6], frag_rec_dist(TabF)),
 
195
 
 
196
    %% Add new fragment hopefully on the new node
 
197
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, Dist})),
 
198
    Dist2 =  frag_dist(Tab), 
 
199
    ?match([{Node3, 1},{Node1, 2},{Node2,3}], Dist2), 
 
200
    ?match([_, _, _], frag_rec_dist(Tab)),
 
201
    DistF2 =  frag_dist(TabF), 
 
202
    ?match([{Node3, 1},{Node1, 2},{Node2,3}], DistF2), 
 
203
    ?match([_, _, _], frag_rec_dist(TabF)),
 
204
    
 
205
    %% Add new fragment hopefully on the new node
 
206
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, Dist2})),
 
207
    Dist3 =  frag_dist(Tab), 
 
208
    ?match([{Node3, 2},{Node2,3},{Node1, 3}], Dist3), 
 
209
    ?match([3, 0, 3, 2], frag_rec_dist(Tab)),
 
210
    DistF3 =  frag_dist(TabF), 
 
211
    ?match([{Node3, 2},{Node2,3},{Node1, 3}], DistF3), 
 
212
    ?match([3, 3, 7, 3], frag_rec_dist(TabF)),
 
213
 
 
214
    %% Add new fragment hopefully on the new node
 
215
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, Dist3})),
 
216
    Dist4 =  frag_dist(Tab), 
 
217
    ?match([{Node1, 3}, {Node3, 3},{Node2, 4}], Dist4), 
 
218
    ?match([_, _, _, _, _], frag_rec_dist(Tab)),
 
219
    DistF4 =  frag_dist(TabF), 
 
220
    ?match([{Node1, 3}, {Node3, 3},{Node2, 4}], DistF4), 
 
221
    ?match([_, _, _, _, _], frag_rec_dist(TabF)),
 
222
 
 
223
    %% Dropping a node in pool should not affect distribution
 
224
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {del_node, Node1})),
 
225
    ?match([{Node3, 3},{Node2, 4}, {Node1, 3}], frag_dist(Tab)),
 
226
    ?match([_, _, _, _, _], frag_rec_dist(Tab)),
 
227
    ?match([{Node3, 3},{Node2, 4}, {Node1, 3}], frag_dist(TabF)),
 
228
    ?match([_, _, _, _, _], frag_rec_dist(TabF)),
 
229
 
 
230
    %% Dropping a fragment
 
231
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
232
    Dist5 =  frag_dist(Tab), 
 
233
    ?match([{Node3, 2},{Node2,3},{Node1, 3}], Dist5), 
 
234
    ?match([3, 0, 3, 2], frag_rec_dist(Tab)),
 
235
    DistF5 =  frag_dist(Tab), 
 
236
    ?match([{Node3, 2},{Node2,3},{Node1, 3}], DistF5), 
 
237
    ?match([3, 3, 7, 3], frag_rec_dist(TabF)),
 
238
    
 
239
    %% Add new fragment hopefully on the new node
 
240
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, Dist5})),
 
241
    Dist6 =  frag_dist(Tab), 
 
242
    ?match([{Node3, 3},{Node2, 4},{Node1, 3}], Dist6), 
 
243
    ?match([_, _, _, _, _], frag_rec_dist(Tab)),
 
244
    DistF6 =  frag_dist(TabF), 
 
245
    ?match([{Node3, 3},{Node2, 4},{Node1, 3}], DistF6), 
 
246
    ?match([_, _, _, _, _], frag_rec_dist(TabF)),
 
247
 
 
248
    %% Dropping all fragments but one
 
249
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
250
    ?match([3, 0, 3, 2], frag_rec_dist(Tab)),
 
251
    ?match([3, 3, 7, 3], frag_rec_dist(TabF)),
 
252
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
253
    ?match([_, _, _], frag_rec_dist(Tab)),
 
254
    ?match([_, _, _], frag_rec_dist(TabF)),
 
255
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
256
    ?match([6, 2], frag_rec_dist(Tab)),
 
257
    ?match([10, 6], frag_rec_dist(TabF)),
 
258
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, del_frag)),
 
259
    ?match([{Node3, 0}, {Node2, 1}, {Node1, 1}], frag_dist(Tab)), 
 
260
    ?match([8], frag_rec_dist(Tab)),
 
261
    ?match([{Node3, 0}, {Node2, 1}, {Node1, 1}], frag_dist(TabF)), 
 
262
    ?match([16], frag_rec_dist(TabF)),
 
263
             
 
264
    %% Defragmenting the tables clears frag_properties
 
265
    ?match(Len when Len > 0,
 
266
                    length(mnesia:table_info(TabF, frag_properties))),
 
267
    ?match({atomic, ok}, mnesia:change_table_frag(TabF, deactivate)),
 
268
    ?match(0, length(mnesia:table_info(TabF, frag_properties))),
 
269
    ?match(Len when Len > 0,
 
270
                    length(mnesia:table_info(Tab, frag_properties))),
 
271
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, deactivate)),
 
272
    ?match(0, length(mnesia:table_info(Tab, frag_properties))),
 
273
 
 
274
    %% Making the tables fragmented again
 
275
    Props2 = [{n_fragments, 1}, {node_pool, [Node1, Node2]}],
 
276
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {activate, Props2})),
 
277
    ?match({atomic, ok}, mnesia:delete_table(TabF)),
 
278
    ?match({atomic, ok}, mnesia:create_table(TabF, DefF)),
 
279
    [frag_write(TabF, {TabF, {Id}, Id})  || Id <- lists:seq(1, 16)],
 
280
    ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, frag_dist(Tab)})),
 
281
    ?match([{Node1, 2}, {Node2, 2}], frag_dist(Tab)),
 
282
    ?match([6, 2], frag_rec_dist(Tab)),
 
283
    ?match([{Node1, 2}, {Node2, 2}], frag_dist(TabF)),
 
284
    ?match([10, 6], frag_rec_dist(TabF)),
 
285
 
 
286
    %% Deleting the fragmented tables
 
287
    ?match({atomic, ok}, mnesia:delete_table(TabF)),
 
288
    ?match(false, lists:member(TabF, mnesia:system_info(tables))),
 
289
    ?match({atomic, ok}, mnesia:delete_table(Tab)),
 
290
    ?match(false, lists:member(Tab, mnesia:system_info(tables))),
 
291
             
 
292
    ?verify_mnesia(Nodes, []).
 
293
 
 
294
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
295
 
 
296
nice_access(doc) ->
 
297
    ["Cover entire callback interface"];
 
298
nice_access(suite) -> [];
 
299
nice_access(Config) when is_list(Config) ->
 
300
    Nodes = ?acquire_nodes(3, Config),
 
301
 
 
302
    Tab = frag_access,
 
303
    Pool = lists:sort(Nodes),
 
304
    Props = [{n_fragments, 20},
 
305
             {n_ram_copies, 2},
 
306
             {node_pool, Pool}],
 
307
    Def = [{frag_properties, Props},
 
308
           {type, ordered_set},
 
309
           {index, [val]}],
 
310
    ?match({atomic, ok}, mnesia:create_table(Tab, Def)),
 
311
    [frag_write(Tab, {Tab, Id, Id})  || Id <- lists:seq(1, 400)],
 
312
    
 
313
    %% And connect another table to it, via a foreign key
 
314
    TabF = frag_access_slave,
 
315
    PropsF = [{foreign_key, {Tab, val}}],
 
316
    DefF = [{frag_properties, PropsF},
 
317
            {index, [val]}],
 
318
    ?match({atomic, ok}, mnesia:create_table(TabF, DefF)),
 
319
    [frag_write(TabF, {TabF, Id, Id})  || Id <- lists:seq(1, 400)],
 
320
 
 
321
    ?match(done, mnesia:activity(transaction, fun do_access/3, [Tab, Tab, Pool], mnesia_frag)),
 
322
    ?match(done, mnesia:activity(transaction, fun do_access/3, [TabF, Tab, Pool], mnesia_frag)),
 
323
 
 
324
    ?verify_mnesia(Nodes, []).
 
325
 
 
326
do_access(Tab, Master, Pool) ->
 
327
    ?match(20, mnesia:table_info(Tab, n_fragments)),
 
328
    ?match(Pool, mnesia:table_info(Tab, node_pool)),
 
329
    ?match(2, mnesia:table_info(Tab, n_ram_copies)),
 
330
    ?match(0, mnesia:table_info(Tab, n_disc_copies)),
 
331
    ?match(0, mnesia:table_info(Tab, n_disc_only_copies)),
 
332
    ?match(20, length(mnesia:table_info(Tab, frag_names))),
 
333
    ?match(20, length(mnesia:table_info(Tab, frag_size))),
 
334
    ?match(20, length(mnesia:table_info(Tab, frag_memory))),
 
335
    PoolSize = length(Pool),
 
336
    ?match(PoolSize, length(mnesia:table_info(Tab, frag_dist))),
 
337
    ?match(400, mnesia:table_info(Tab, size)),
 
338
    ?match(I when is_integer(I), mnesia:table_info(Tab, memory)),
 
339
    ?match(Tab, mnesia:table_info(Tab, base_table)),
 
340
 
 
341
    Foreign = 
 
342
        if
 
343
            Master == Tab ->
 
344
                ?match(undefined, mnesia:table_info(Tab, foreign_key)),
 
345
                ?match([_], mnesia:table_info(Tab, foreigners)),
 
346
                ?match({'EXIT', {aborted, {combine_error, Tab, frag_properties, {foreign_key, undefined}}}},
 
347
                    mnesia:read({Tab, 5}, 5, read)),
 
348
                fun({T, _K}) -> T end;
 
349
            true ->
 
350
                ?match({Master, 3}, mnesia:table_info(Tab, foreign_key)),
 
351
                ?match([], mnesia:table_info(Tab, foreigners)),
 
352
                fun({T, K}) -> {T, K} end
 
353
        end,
 
354
 
 
355
    Attr = val,
 
356
    ?match(400, mnesia:table_info(Tab, size)),
 
357
    Count = fun(_, N) -> N + 1 end,
 
358
    ?match(400, mnesia:foldl(Count, 0, Tab)),
 
359
    ?match(400, mnesia:foldr(Count, 0, Tab)),
 
360
    ?match(ok, mnesia:write({Tab, [-1], 1})),
 
361
    ?match(401, length(mnesia:match_object(Tab, {Tab, '_', '_'}, read))),
 
362
    ?match(401, length(mnesia:select(Tab, [{{Tab, '_', '$1'}, [], ['$1']}], read))),
 
363
 
 
364
    First = mnesia:select(Tab, [{{Tab, '_', '$1'}, [], ['$1']}], 10, read),
 
365
    TestCont = fun('$end_of_table', Total, _This) -> 
 
366
                       Total;
 
367
                  ({Res,Cont1}, Total, This) ->
 
368
                       Cont = mnesia:select(Cont1),
 
369
                       This(Cont, length(Res) + Total, This)
 
370
               end,
 
371
    ?match(401, TestCont(First, 0, TestCont)),
 
372
 
 
373
    %% OTP 
 
374
    [_, Frag2|_] = frag_names(Tab),
 
375
    Frag2key = mnesia:dirty_first(Frag2),
 
376
    ?match({[Frag2key],_},mnesia:select(Tab,[{{Tab,Frag2key,'$1'},[],['$1']}],100,read)),
 
377
 
 
378
    ?match([{Tab, [-1], 1}], mnesia:read(Foreign({Tab, 1}), [-1], read)),
 
379
    ?match(401, mnesia:foldl(Count, 0, Tab)),
 
380
    ?match(401, mnesia:foldr(Count, 0, Tab)),
 
381
    ?match(ok, mnesia:delete(Foreign({Tab, 2}), 2, write)),
 
382
    ?match([], mnesia:read(Foreign({Tab, 2}), 2, read)),
 
383
    ?match([{Tab, 3, 3}], mnesia:read(Foreign({Tab, 3}), 3, read)),
 
384
    ?match(400, mnesia:foldl(Count, 0, Tab)),
 
385
    ?match(400, mnesia:foldr(Count, 0, Tab)),
 
386
    ?match(ok, mnesia:delete_object({Tab, 3, 3})),
 
387
    ?match([], mnesia:read(Foreign({Tab, 3}), 3, read)),
 
388
    One = lists:sort([{Tab, 1, 1}, {Tab, [-1], 1}]),
 
389
    Pat = {Tab, '$1', 1},
 
390
    ?match(One, lists:sort(mnesia:match_object(Tab, Pat, read))),
 
391
    ?match([1,[-1]], lists:sort(mnesia:select(Tab, [{Pat, [], ['$1']}], read))),
 
392
    ?match([[[-1]]], lists:sort(mnesia:select(Tab, [{Pat, [{is_list, '$1'}], [['$1']]}], read))),
 
393
    ?match([[1, 100]], lists:sort(mnesia:select(Tab, [{Pat, [{is_integer, '$1'}], [['$1',100]]}], read))),
 
394
    ?match([1,[-1]], lists:sort(mnesia:select(Tab, [{Pat, [{is_list, '$1'}], ['$1']},{Pat, [{is_integer, '$1'}], ['$1']}], read))),
 
395
    ?match(One, lists:sort(mnesia:index_match_object(Tab, Pat, Attr, read) )),
 
396
    ?match(One, lists:sort(mnesia:index_read(Tab, 1, Attr))),
 
397
    Keys = mnesia:all_keys(Tab),
 
398
    ?match([-1], lists:max(Keys)),  %% OTP-3779
 
399
    ?match(399, length(Keys)),
 
400
    ?match(399, mnesia:foldl(Count, 0, Tab)),
 
401
    ?match(399, mnesia:foldr(Count, 0, Tab)),
 
402
 
 
403
    ?match(Pool, lists:sort(mnesia:lock({table, Tab}, write))),
 
404
 
 
405
    done.
 
406
 
 
407
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
408
 
 
409
iter_access(doc) ->
 
410
    ["Cover table iteration via callback interface"];
 
411
iter_access(suite) -> [];
 
412
iter_access(Config) when is_list(Config) ->
 
413
    Nodes = ?acquire_nodes(3, Config),
 
414
 
 
415
    Tab = frag_access,
 
416
    Pool = lists:sort(Nodes),
 
417
    Props = [{n_fragments, 20},
 
418
             {n_ram_copies, 2},
 
419
             {node_pool, Pool}],
 
420
    Def = [{frag_properties, Props},
 
421
           {type, ordered_set},
 
422
           {index, [val]}],
 
423
    ?match({atomic, ok}, mnesia:create_table(Tab, Def)),
 
424
    [frag_write(Tab, {Tab, Id, Id})  || Id <- lists:seq(1, 400)],
 
425
 
 
426
    FragNames = frag_names(Tab),
 
427
    RawRead = 
 
428
        fun(Frag) -> 
 
429
                Node = mnesia:table_info(Frag, where_to_read),
 
430
                {Frag, rpc:call(Node, ets, tab2list, [Frag])}
 
431
        end,
 
432
    
 
433
    ?match(done, mnesia:activity(transaction, fun nice_iter_access/3, [Tab, FragNames, RawRead], mnesia_frag)),
 
434
 
 
435
    FragNames = frag_names(Tab),
 
436
    [First, Second | _] = FragNames,
 
437
    [Last, LastButOne | _] = lists:reverse(FragNames),
 
438
 
 
439
    ?match({atomic, ok}, mnesia:clear_table(First)),
 
440
    ?match({atomic, ok}, mnesia:clear_table(Second)),
 
441
    ?match({atomic, ok}, mnesia:clear_table(lists:nth(8, FragNames))),
 
442
    ?match({atomic, ok}, mnesia:clear_table(lists:nth(9, FragNames))),
 
443
    ?match({atomic, ok}, mnesia:clear_table(lists:nth(10, FragNames))),
 
444
    ?match({atomic, ok}, mnesia:clear_table(lists:nth(11, FragNames))),
 
445
    ?match({atomic, ok}, mnesia:clear_table(LastButOne)),
 
446
    ?match({atomic, ok}, mnesia:clear_table(Last)),
 
447
 
 
448
    ?match(done, mnesia:activity(transaction, fun evil_iter_access/3, [Tab, FragNames, RawRead], mnesia_frag)),
 
449
    Size = fun(Table) -> mnesia:table_info(Table, size) end,
 
450
    ?match(true, 0 < mnesia:activity(transaction, Size, [Tab], mnesia_frag)),
 
451
    ?match({atomic, ok}, mnesia:activity(ets, fun() -> mnesia:clear_table(Tab) end, mnesia_frag)),
 
452
    ?match(0, mnesia:activity(transaction, Size, [Tab], mnesia_frag)),
 
453
    
 
454
    ?verify_mnesia(Nodes, []).
 
455
 
 
456
nice_iter_access(Tab, FragNames, RawRead) ->
 
457
    RawData = ?ignore(lists:map(RawRead, FragNames)),
 
458
    Keys = [K || {_, Recs} <- RawData, {_, K, _} <- Recs],
 
459
    ExpectedFirst = hd(Keys),
 
460
    ?match(ExpectedFirst, mnesia:first(Tab)),
 
461
    ExpectedLast = lists:last(Keys),
 
462
    ?match(ExpectedLast, mnesia:last(Tab)),
 
463
    
 
464
    ExpectedAllPrev = ['$end_of_table' | lists:reverse(tl(lists:reverse(Keys)))],
 
465
    ?match(ExpectedAllPrev, lists:map(fun(K) -> mnesia:prev(Tab, K) end, Keys)),
 
466
    
 
467
    ExpectedAllNext = tl(Keys) ++ ['$end_of_table'],
 
468
    ?match(ExpectedAllNext, lists:map(fun(K) -> mnesia:next(Tab, K) end, Keys)),
 
469
 
 
470
    done.
 
471
 
 
472
evil_iter_access(Tab, FragNames, RawRead) ->
 
473
    RawData = ?ignore(lists:map(RawRead, FragNames)),
 
474
    Keys = [K || {_, Recs} <- RawData, {_, K, _} <- Recs],
 
475
    ExpectedFirst = hd(Keys),
 
476
    ?match(ExpectedFirst, mnesia:first(Tab)),
 
477
    ExpectedLast = lists:last(Keys),
 
478
    ?match(ExpectedLast, mnesia:last(Tab)),
 
479
    
 
480
    ExpectedAllPrev = ['$end_of_table' | lists:reverse(tl(lists:reverse(Keys)))],
 
481
    ?match(ExpectedAllPrev, lists:map(fun(K) -> mnesia:prev(Tab, K) end, Keys)),
 
482
    
 
483
    ExpectedAllNext = tl(Keys) ++ ['$end_of_table'],
 
484
    ?match(ExpectedAllNext, lists:map(fun(K) -> mnesia:next(Tab, K) end, Keys)),
 
485
 
 
486
    done.
 
487
 
 
488
 
 
489
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
490
 
 
491
consistency(doc) ->
 
492
    ["Add and delete fragments during TPC-B"];
 
493
consistency(suite) -> [];
 
494
consistency(Config) when is_list(Config) ->
 
495
    ?skip("Not yet implemented (NYI).~n", []),
 
496
    Nodes = ?acquire_nodes(2, Config),
 
497
    ?verify_mnesia(Nodes, []).
 
498
 
 
499
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
500
 
 
501
 
 
502
evil_create(suite) -> [];
 
503
evil_create(Config) when is_list(Config) ->
 
504
    [Node1, _Node2] = Nodes = ?acquire_nodes(2, Config),
 
505
    
 
506
    Create = fun(T, D, P) -> mnesia:create_table(T, [{frag_properties, P}| D]) end,
 
507
    
 
508
    Tab = evil_create,
 
509
    %% Props in general
 
510
    ?match({aborted, {badarg, Tab, {frag_properties, no_list}}},
 
511
           Create(Tab, [], no_list)),
 
512
    ?match({aborted, {badarg,Tab , [no_tuple]}},
 
513
           Create(Tab, [], [no_tuple])),
 
514
    ?match({aborted,{badarg, Tab, bad_key}},
 
515
           Create(Tab, [], [{bad_key, 7}])),
 
516
 
 
517
    %% n_fragments
 
518
    ?match({aborted,{badarg, Tab, [{n_fragments}]}},
 
519
           Create(Tab, [], [{n_fragments}])),
 
520
    ?match({aborted,{badarg, Tab, [{n_fragments, 1, 1}]}},
 
521
           Create(Tab, [], [{n_fragments, 1, 1}])),
 
522
    ?match({aborted, {bad_type,Tab, {n_fragments, a}}},
 
523
           Create(Tab, [], [{n_fragments, a}])),
 
524
    ?match({aborted, {bad_type, Tab, {n_fragments, 0}}},
 
525
           Create(Tab, [], [{n_fragments, 0}])),
 
526
 
 
527
    %% *_copies
 
528
    ?match({aborted, {bad_type, Tab, {n_ram_copies, -1}}},
 
529
           Create(Tab, [], [{n_ram_copies, -1}, {n_fragments, 1}])),
 
530
    ?match({aborted, {bad_type, Tab, {n_disc_copies, -1}}},
 
531
           Create(Tab, [], [{n_disc_copies, -1}, {n_fragments, 1}])),
 
532
    ?match({aborted, {bad_type, Tab, {n_disc_only_copies, -1}}},
 
533
           Create(Tab, [], [{n_disc_only_copies, -1}, {n_fragments, 1}])),
 
534
 
 
535
    %% node_pool
 
536
    ?match({aborted, {bad_type, Tab, {node_pool, 0}}},
 
537
           Create(Tab, [], [{node_pool, 0}])),
 
538
    ?match({aborted, {combine_error, Tab, "Too few nodes in node_pool"}},
 
539
           Create(Tab, [], [{n_ram_copies, 2}, {node_pool, [Node1]}])),
 
540
 
 
541
    %% foreign_key
 
542
    ?match({aborted, {bad_type, Tab, {foreign_key, bad_key}}},
 
543
           Create(Tab, [], [{foreign_key, bad_key}])), 
 
544
    ?match({aborted,{bad_type, Tab, {foreign_key, {bad_key}}}}, 
 
545
           Create(Tab, [], [{foreign_key, {bad_key}}])), 
 
546
    ?match({aborted, {no_exists, {bad_tab, frag_properties}}},
 
547
           Create(Tab, [], [{foreign_key, {bad_tab, val}}])), 
 
548
    ?match({aborted, {combine_error, Tab, {Tab, val}}},
 
549
           Create(Tab, [], [{foreign_key, {Tab, val}}])),
 
550
    ?match({atomic, ok},
 
551
           Create(Tab, [], [{n_fragments, 1}])),
 
552
           
 
553
    ?match({aborted, {already_exists, Tab}},
 
554
           Create(Tab, [], [{n_fragments, 1}])),
 
555
 
 
556
    Tab2 = evil_create2,
 
557
    ?match({aborted, {bad_type, no_attr}},
 
558
           Create(Tab2, [], [{foreign_key, {Tab, no_attr}}])),
 
559
    ?match({aborted, {combine_error, Tab2, _, _, _}},
 
560
           Create(Tab2, [], [{foreign_key, {Tab, val}},
 
561
                             {node_pool, [Node1]}])),
 
562
    ?match({aborted, {combine_error, Tab2, _, _, _}},
 
563
           Create(Tab2, [], [{foreign_key, {Tab, val}},
 
564
                             {n_fragments, 2}])),
 
565
    ?match({atomic, ok},
 
566
           Create(Tab2, [{attributes, [a, b, c]}], [{foreign_key, {Tab, c}}])),
 
567
    Tab3 = evil_create3,
 
568
    ?match({aborted, {combine_error, Tab3, _, _, _}},
 
569
           Create(Tab3, [{attributes, [a, b]}], [{foreign_key, {Tab2, b}}])),
 
570
    ?match({atomic, ok},
 
571
           Create(Tab3, [{attributes, [a, b]}], [{foreign_key, {Tab, b}}])),
 
572
    
 
573
    ?verify_mnesia(Nodes, []).
 
574
 
 
575
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
576
 
 
577
evil_delete(suite) -> [];
 
578
evil_delete(Config) when is_list(Config) ->
 
579
    ?skip("Not yet implemented (NYI).~n", []),
 
580
    Nodes = ?acquire_nodes(2, Config),
 
581
    ?verify_mnesia(Nodes, []).
 
582
 
 
583
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
584
 
 
585
evil_change(suite) -> [];
 
586
evil_change(Config) when is_list(Config) ->
 
587
    [N1,N2,_N3] = Nodes = ?acquire_nodes(3, Config),
 
588
    Create = fun(T, D, P) -> mnesia:create_table(T, [{frag_properties, P}| D]) end,
 
589
    Props1 = [{n_fragments, 2}, {node_pool, [N1]}],
 
590
    Tab1 = evil_change_ram,
 
591
    ?match({atomic, ok}, Create(Tab1, [], Props1)),
 
592
    
 
593
    ?match({atomic,ok}, mnesia:change_table_frag(Tab1, {add_frag, Nodes})),
 
594
    Dist10 =  frag_dist(Tab1), 
 
595
    ?match([{N1,3}], Dist10), 
 
596
    ?match({atomic, ok}, mnesia:change_table_frag(Tab1, {add_node, N2})),
 
597
    Dist11 =  frag_dist(Tab1),
 
598
    ?match([{N2,0},{N1,3}], Dist11),
 
599
    mnesia_test_lib:kill_mnesia([N2]),
 
600
    ?match({aborted,_}, mnesia:change_table_frag(Tab1, {add_frag, [N2,N1]})),
 
601
    ?verbose("~p~n",[frag_dist(Tab1)]),
 
602
    mnesia_test_lib:start_mnesia([N2]),
 
603
 
 
604
    Tab2 = evil_change_disc,
 
605
    ?match({atomic,ok}, Create(Tab2,[],[{n_disc_copies,1},{n_fragments,1},{node_pool,[N1,N2]}])),
 
606
    ?verbose("~p~n", [frag_dist(Tab2)]),
 
607
    ?match({atomic,ok}, mnesia:change_table_frag(Tab2, {add_frag, [N1,N2]})),
 
608
    _Dist20 =  frag_dist(Tab2), 
 
609
    mnesia_test_lib:kill_mnesia([N2]),
 
610
    ?match({atomic,ok}, mnesia:change_table_frag(Tab2, {add_frag, [N1,N2]})),
 
611
    ?match({aborted,_}, mnesia:change_table_frag(Tab2, {add_frag, [N2,N1]})),
 
612
 
 
613
    mnesia_test_lib:start_mnesia([N2]),
 
614
    ?verify_mnesia(Nodes, []).
 
615
 
 
616
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
617
 
 
618
evil_combine(doc) -> ["Bug in mnesia_4.1.5. and earlier"];
 
619
evil_combine(suite) -> [];
 
620
evil_combine(Config) when is_list(Config) ->
 
621
    [Node1] = Nodes = ?acquire_nodes(1, Config),
 
622
    ?match({atomic, ok},mnesia:create_table(tab1, [{disc_copies, [Node1]},
 
623
                                                   {frag_properties, [{n_fragments, 2},
 
624
                                                                      {node_pool, [Node1]},
 
625
                                                                      {n_disc_copies, 1}]}])),
 
626
    ?match({atomic, ok},mnesia:create_table(tab2, [{disc_copies, [Node1]}])),
 
627
    mnesia:wait_for_tables([tab1, tab2], infinity),
 
628
 
 
629
    Add2 = fun() -> 
 
630
                   mnesia:transaction(fun() ->
 
631
                                              mnesia:write({tab2,1,1})
 
632
                                      end)
 
633
           end,
 
634
    Fun = fun() ->
 
635
                  Add2(),
 
636
                  mnesia:write({tab1,9,10})
 
637
          end,
 
638
    ?match(ok, mnesia:activity({transaction, 1}, Fun, [], mnesia_frag)),
 
639
    
 
640
    Read = fun(T, K) ->
 
641
                   mnesia:read(T, K, read)
 
642
           end,
 
643
    
 
644
    ?match([{tab1,9,10}],mnesia:activity(async_dirty, Read, [tab1, 9], mnesia_frag)),
 
645
    ?match([{tab2,1,1}],mnesia:activity(async_dirty, Read, [tab2, 1], mnesia_frag)),
 
646
    
 
647
    ?verify_mnesia(Nodes, []).
 
648
 
 
649
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
650
 
 
651
evil_loop(doc) -> ["Test select/[14]"];
 
652
evil_loop(suite) -> [];
 
653
evil_loop(Config) when is_list(Config) ->
 
654
    [Node1,_Node2] = ?acquire_nodes(2, Config), 
 
655
    Tab1 = ss_oset,
 
656
    Tab2 = ss_set,
 
657
    Tab3 = ss_bag,
 
658
    Tabs = [Tab1, Tab2, Tab3],
 
659
    RecName = ss,
 
660
    ?match({atomic, ok},  mnesia:create_table([{name, Tab1}, 
 
661
                                               {ram_copies, [Node1]}, 
 
662
                                               {record_name, RecName},
 
663
                                               {type,  ordered_set}])),
 
664
    ?match({atomic, ok},  mnesia:create_table([{name, Tab2},
 
665
                                               {record_name, RecName},
 
666
                                               {ram_copies, [Node1]},
 
667
                                               {type,  set}])),
 
668
    ?match({atomic, ok},  mnesia:create_table([{name, Tab3},
 
669
                                               {record_name, RecName},
 
670
                                               {ram_copies, [Node1]}, 
 
671
                                               {type,  bag}])),
 
672
    Keys = [-3, -2] ++ lists:seq(1, 5, 2) ++ lists:seq(6, 10),
 
673
    Recs = [{RecName, K, K} || K <- Keys],
 
674
    [mnesia:dirty_write(Tab1, R) || R <- Recs],
 
675
    [mnesia:dirty_write(Tab2, R) || R <- Recs],
 
676
    [mnesia:dirty_write(Tab3, R) || R <- Recs],
 
677
 
 
678
    Activate = 
 
679
        fun(Tab) ->
 
680
                ?match({atomic, ok}, mnesia:change_table_frag(Tab, {activate, []})),
 
681
                Dist = frag_dist(Tab),
 
682
                ?match({atomic, ok}, mnesia:change_table_frag(Tab, {add_frag, Dist}))
 
683
        end,
 
684
 
 
685
    Activate(Tab1),
 
686
    Activate(Tab2),
 
687
    Activate(Tab3),
 
688
 
 
689
    Match  = fun(Tab) -> mnesia:match_object(Tab, {'_', '_', '_'}, write) end,
 
690
    Select = fun(Tab) -> mnesia:select(Tab, [{'_', [], ['$_']}]) end,
 
691
    Trans  = fun(Fun, Args) -> mnesia:activity(transaction, Fun, Args, mnesia_frag) end,
 
692
    LoopHelp = fun('$end_of_table',_) ->
 
693
                       [];
 
694
                  ({Res,Cont},Fun) -> 
 
695
                       Sel = mnesia:select(Cont),
 
696
                       Res ++ Fun(Sel, Fun)
 
697
               end,
 
698
    SelLoop = fun(Table) -> 
 
699
                      Sel = mnesia:select(Table, [{'_', [], ['$_']}], 1, read),
 
700
                      LoopHelp(Sel, LoopHelp)
 
701
              end,
 
702
 
 
703
    R1 = {RecName, 2, 2},
 
704
    R2 = {RecName, 4, 4},
 
705
    R3 = {RecName, 2, 3},
 
706
    R4 = {RecName, 3, 1},
 
707
    R5 = {RecName, 104, 104},
 
708
    W1 = fun(Tab,Search) ->
 
709
                 mnesia:write(Tab,R1,write),
 
710
                 mnesia:write(Tab,R2,write), 
 
711
                 Search(Tab)
 
712
         end,
 
713
    S1 = lists:sort([R1, R2| Recs]),
 
714
    ?match(S1, sort_res(Trans(W1, [Tab1, Select]))),
 
715
    ?match(S1, sort_res(Trans(W1, [Tab1, Match]))),
 
716
    ?match(S1, sort_res(Trans(W1, [Tab1, SelLoop]))),
 
717
    ?match(S1, sort_res(Trans(W1, [Tab2, Select]))),
 
718
    ?match(S1, sort_res(Trans(W1, [Tab2, SelLoop]))),
 
719
    ?match(S1, sort_res(Trans(W1, [Tab2, Match]))),
 
720
    ?match(S1, sort_res(Trans(W1, [Tab3, Select]))),
 
721
    ?match(S1, sort_res(Trans(W1, [Tab3, SelLoop]))),
 
722
    ?match(S1, sort_res(Trans(W1, [Tab3, Match]))),
 
723
    [mnesia:dirty_delete_object(Frag, R) || R <- [R1, R2], 
 
724
                                           Tab <- Tabs,
 
725
                                           Frag <- frag_names(Tab)],
 
726
 
 
727
    W2 = fun(Tab, Search) -> 
 
728
                 mnesia:write(Tab, R3, write),
 
729
                 mnesia:write(Tab, R1, write), 
 
730
                 Search(Tab)
 
731
         end,
 
732
    S2 = lists:sort([R1 | Recs]),
 
733
    S2Bag = lists:sort([R1, R3 | Recs]),
 
734
    io:format("S2 = ~p\n", [S2]),
 
735
    ?match(S2, sort_res(Trans(W2, [Tab1, Select]))),
 
736
    ?match(S2, sort_res(Trans(W2, [Tab1, SelLoop]))),
 
737
    ?match(S2, sort_res(Trans(W2, [Tab1, Match]))),
 
738
    ?match(S2, sort_res(Trans(W2, [Tab2, Select]))),
 
739
    ?match(S2, sort_res(Trans(W2, [Tab2, SelLoop]))),
 
740
    ?match(S2, sort_res(Trans(W2, [Tab2, Match]))),
 
741
    io:format("S2Bag = ~p\n", [S2Bag]),
 
742
    ?match(S2Bag, sort_res(Trans(W2, [Tab3, Select]))),
 
743
    ?match(S2Bag, sort_res(Trans(W2, [Tab3, SelLoop]))),
 
744
    ?match(S2Bag, sort_res(Trans(W2, [Tab3, Match]))),
 
745
 
 
746
    W3 = fun(Tab,Search) -> 
 
747
                 mnesia:write(Tab, R4, write),
 
748
                 mnesia:delete(Tab, element(2, R1), write), 
 
749
                 Search(Tab)
 
750
         end,
 
751
    S3Bag = lists:sort([R4 | lists:delete(R1, Recs)]),
 
752
    S3 = lists:delete({RecName, 3, 3}, S3Bag),
 
753
    ?match(S3, sort_res(Trans(W3, [Tab1, Select]))),
 
754
    ?match(S3, sort_res(Trans(W3, [Tab1, SelLoop]))),
 
755
    ?match(S3, sort_res(Trans(W3, [Tab1, Match]))),
 
756
    ?match(S3, sort_res(Trans(W3, [Tab2, SelLoop]))),
 
757
    ?match(S3, sort_res(Trans(W3, [Tab2, Select]))),
 
758
    ?match(S3, sort_res(Trans(W3, [Tab2, Match]))),
 
759
    ?match(S3Bag, sort_res(Trans(W3, [Tab3, Select]))),
 
760
    ?match(S3Bag, sort_res(Trans(W3, [Tab3, SelLoop]))),
 
761
    ?match(S3Bag, sort_res(Trans(W3, [Tab3, Match]))),
 
762
 
 
763
    W4 = fun(Tab,Search) -> 
 
764
                 mnesia:delete(Tab, -1, write),
 
765
                 mnesia:delete(Tab, 4 , write),
 
766
                 mnesia:delete(Tab, 17, write),
 
767
                 mnesia:delete_object(Tab, {RecName, -1, x}, write),
 
768
                 mnesia:delete_object(Tab, {RecName, 4, x}, write),
 
769
                 mnesia:delete_object(Tab, {RecName, 42, x}, write),
 
770
                 mnesia:delete_object(Tab, R2, write),
 
771
                 mnesia:write(Tab, R5, write),
 
772
                 Search(Tab)
 
773
         end,
 
774
    S4Bag = lists:sort([R5 | S3Bag]),
 
775
    S4    = lists:sort([R5 | S3]),
 
776
    ?match(S4, sort_res(Trans(W4, [Tab1, Select]))),
 
777
    ?match(S4, sort_res(Trans(W4, [Tab1, SelLoop]))),
 
778
    ?match(S4, sort_res(Trans(W4, [Tab1, Match]))),
 
779
    ?match(S4, sort_res(Trans(W4, [Tab2, Select]))),
 
780
    ?match(S4, sort_res(Trans(W4, [Tab2, SelLoop]))),
 
781
    ?match(S4, sort_res(Trans(W4, [Tab2, Match]))),
 
782
    ?match(S4Bag, sort_res(Trans(W4, [Tab3, Select]))),
 
783
    ?match(S4Bag, sort_res(Trans(W4, [Tab3, SelLoop]))),
 
784
    ?match(S4Bag, sort_res(Trans(W4, [Tab3, Match]))),
 
785
    [mnesia:dirty_delete_object(Tab, R) || R <- [{RecName, 3, 3}, R5], Tab <- Tabs],
 
786
 
 
787
    %% hmmm anything more??
 
788
    
 
789
    ?verify_mnesia([Node1], []).
 
790
 
 
791
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
792
 
 
793
evil_delete_db_node(doc) ->
 
794
    ["Delete db_node with a repicated table with foreign key"];
 
795
evil_delete_db_node(suite) -> [];
 
796
evil_delete_db_node(Config) when is_list(Config) ->
 
797
    Nodes = lists:sort(?acquire_nodes(2, Config)),
 
798
    Local = node(),
 
799
    Remote = hd(Nodes -- [Local]),
 
800
    
 
801
    Type = case mnesia_test_lib:diskless(Config) of 
 
802
               true  -> n_ram_copies;
 
803
               false -> n_disc_copies
 
804
           end,
 
805
    Tab = frag_master,
 
806
    ?match({atomic, ok}, mnesia:create_table(Tab, [{frag_properties, [{Type, 2}, {node_pool, Nodes}]}])),
 
807
    ExtraTab = frag_foreigner,
 
808
    ?match({atomic, ok}, mnesia:create_table(ExtraTab, [{frag_properties, [{foreign_key, {Tab, key}}, {node_pool, Nodes}]}])),
 
809
    
 
810
    GetPool = fun(T) -> 
 
811
                      case lists:keysearch(node_pool, 1, mnesia:table_info (T, frag_properties)) of
 
812
                          {value, {node_pool, N}} -> lists:sort(N);
 
813
                          false                   -> []
 
814
                      end
 
815
              end,
 
816
    ?match(Nodes, GetPool(Tab)),
 
817
    ?match(Nodes, GetPool(ExtraTab)),
 
818
 
 
819
 
 
820
    ?match(stopped, rpc:call(Remote, mnesia, stop, [])),
 
821
    ?match({atomic, ok}, mnesia:del_table_copy(schema, Remote)),
 
822
           
 
823
    ?match([Local], GetPool(Tab)),
 
824
    ?match([Local], GetPool(ExtraTab)),
 
825
     
 
826
    ?verify_mnesia([Local], []).
 
827
 
 
828
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
829
%% Misc convenient helpers
 
830
 
 
831
frag_write(Tab, Rec) ->
 
832
    Fun = fun() -> mnesia:write(Tab, Rec, write) end,
 
833
    mnesia:activity(sync_dirty, Fun, mnesia_frag).
 
834
 
 
835
frag_dist(Tab) ->
 
836
    Fun = fun() -> mnesia:table_info(Tab, frag_dist) end,
 
837
    mnesia:activity(sync_dirty, Fun, mnesia_frag).
 
838
 
 
839
frag_names(Tab) ->
 
840
    Fun = fun() -> mnesia:table_info(Tab, frag_names) end,
 
841
    mnesia:activity(sync_dirty, Fun, mnesia_frag).
 
842
 
 
843
frag_rec_dist(Tab) -> 
 
844
    Fun = fun() -> mnesia:table_info(Tab, frag_size) end,
 
845
    [Size || {_, Size} <- mnesia:activity(sync_dirty, Fun, mnesia_frag)].
 
846
 
 
847
table_size(Tab) ->
 
848
    Node = mnesia:table_info(Tab, where_to_read),
 
849
    rpc:call(Node, mnesia, table_info, [Tab, size]).
 
850
 
 
851
sort_res(List) when is_list(List) ->
 
852
    lists:sort(List);
 
853
sort_res(Else) ->
 
854
    Else.
 
855
 
 
856
rev_res(List) when is_list(List) ->
 
857
    lists:reverse(List);
 
858
rev_res(Else) ->
 
859
    Else.