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

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_test_lib.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 1996-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
%%% Author: Hakan Mattsson  hakan@erix.ericsson.se
 
22
%%% Purpose: Test case support library
 
23
%%%
 
24
%%% This test suite may be run as a part of the Grand Test Suite
 
25
%%% of Erlang.  The Mnesia test suite is structured in a hierarchy.
 
26
%%% Each test case is implemented as an exported function with arity 1.
 
27
%%% Test case identifiers must have the following syntax: {Module, Function}.
 
28
%%%
 
29
%%% The driver of the test suite runs in two passes as follows:
 
30
%%% first the test case function is invoked with the atom 'suite' as
 
31
%%% single argument. The returned value is treated as a list of sub
 
32
%%% test cases. If the list of sub test cases is [] the test case
 
33
%%% function is invoked again, this time with a list of nodes as
 
34
%%% argument. If the list of sub test cases is not empty, the test
 
35
%%% case driver applies the algorithm recursively on each element
 
36
%%% in the list.
 
37
%%%
 
38
%%% All test cases are written in such a manner
 
39
%%% that they start to invoke ?acquire_nodes(X, Config)
 
40
%%% in order to prepare the test case execution. When that is
 
41
%%% done, the test machinery ensures that at least X number
 
42
%%% of nodes are connected to each other. If too few nodes was
 
43
%%% specified in the Config, the test case is skipped. If there
 
44
%%% was enough node names in the Config, X of them are selected
 
45
%%% and if some of them happens to be down they are restarted
 
46
%%% via the slave module. When all nodes are up and running a
 
47
%%% disk resident schema is created on all nodes and Mnesia is
 
48
%%% started a on all nodes. This means that all test cases may
 
49
%%% assume that Mnesia is up and running on all acquired nodes.
 
50
%%%
 
51
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
52
%%%
 
53
%%% doc(TestCases)
 
54
%%%
 
55
%%%    Generates a test spec from parts of the test case structure
 
56
%%%
 
57
%%% struct(TestCases)
 
58
%%%
 
59
%%%    Prints out the test case structure
 
60
%%%
 
61
%%% test(TestCases)
 
62
%%%
 
63
%%%    Run parts of the test suite. Uses test/2.
 
64
%%%    Reads Config from mnesia_test.config and starts them if neccessary.
 
65
%%%    Kills Mnesia and wipes out the Mnesia directories as a starter.
 
66
%%%
 
67
%%% test(TestCases, Config)
 
68
%%%
 
69
%%%    Run parts of the test suite on the given Nodes,
 
70
%%%    assuming that the nodes are up and running.
 
71
%%%    Kills Mnesia and wipes out the Mnesia directories as a starter.
 
72
%%%
 
73
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
74
 
 
75
-module(mnesia_test_lib).
 
76
-author('hakan@erix.ericsson.se').
 
77
-export([
 
78
         log/2,
 
79
         log/4,
 
80
         verbose/4,
 
81
         default_config/0,
 
82
         diskless/1,
 
83
         eval_test_case/3,
 
84
         test_driver/2,
 
85
         test_case_evaluator/3,
 
86
         activity_evaluator/1,
 
87
         flush/0,
 
88
         pick_msg/0,
 
89
         start_activities/1,
 
90
         start_transactions/1,
 
91
         start_transactions/2,
 
92
         start_sync_transactions/1,
 
93
         start_sync_transactions/2,
 
94
         sync_trans_tid_serial/1,
 
95
         prepare_test_case/5,
 
96
         select_nodes/4,
 
97
         init_nodes/3,
 
98
         error/4,
 
99
         slave_start_link/0,
 
100
         slave_start_link/1,
 
101
         slave_sup/0,
 
102
        
 
103
         start_mnesia/1,
 
104
         start_mnesia/2,
 
105
         start_appls/2,
 
106
         start_appls/3,
 
107
         start_wait/2,
 
108
         storage_type/2,
 
109
         stop_mnesia/1,
 
110
         stop_appls/2,
 
111
         sort/1,
 
112
         kill_mnesia/1,
 
113
         kill_appls/2,
 
114
         verify_mnesia/4,
 
115
         shutdown/0,
 
116
         verify_replica_location/5,
 
117
         lookup_config/2,
 
118
         sync_tables/2,
 
119
         remote_start/3,
 
120
         remote_stop/1,
 
121
         remote_kill/1,
 
122
 
 
123
         reload_appls/2,
 
124
 
 
125
         remote_activate_debug_fun/6,
 
126
         do_remote_activate_debug_fun/6,
 
127
 
 
128
         test/1,
 
129
         test/2,
 
130
         doc/1,
 
131
         struct/1,
 
132
         init_per_testcase/2,
 
133
         end_per_testcase/2,
 
134
         kill_tc/2      
 
135
        ]).
 
136
 
 
137
-include("mnesia_test_lib.hrl").
 
138
 
 
139
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
140
 
 
141
%% included for test server compatibility
 
142
%% assume that all test cases only takes Config as sole argument
 
143
init_per_testcase(_Func, Config) ->
 
144
    global:register_name(mnesia_global_logger, group_leader()),
 
145
    Config.
 
146
 
 
147
end_per_testcase(_Func, Config) ->
 
148
    global:unregister_name(mnesia_global_logger),
 
149
    %% Nodes = select_nodes(all, Config, ?FILE, ?LINE),
 
150
    %% rpc:multicall(Nodes, mnesia, lkill, []),
 
151
    Config.
 
152
 
 
153
%% Use ?log(Format, Args) as wrapper
 
154
log(Format, Args, LongFile, Line) ->
 
155
    File = filename:basename(LongFile),
 
156
    Format2 = lists:concat([File, "(", Line, ")", ": ", Format]),
 
157
    log(Format2, Args).
 
158
 
 
159
log(Format, Args) ->
 
160
    case global:whereis_name(mnesia_global_logger) of
 
161
        undefined ->
 
162
            io:format(user, Format, Args);
 
163
        Pid ->
 
164
            io:format(Pid, Format, Args)
 
165
    end.
 
166
 
 
167
verbose(Format, Args, File, Line) ->
 
168
    Arg = mnesia_test_verbose,
 
169
    case get(Arg) of
 
170
        false ->
 
171
            ok;
 
172
        true ->
 
173
            log(Format, Args, File, Line);
 
174
        undefined ->
 
175
            case init:get_argument(Arg) of
 
176
                {ok, List} when is_list(List) ->
 
177
                    case lists:last(List) of
 
178
                        ["true"] ->
 
179
                            put(Arg, true),
 
180
                            log(Format, Args, File, Line);
 
181
                        _ ->
 
182
                            put(Arg, false),
 
183
                            ok
 
184
                    end;
 
185
                _ ->
 
186
                    put(Arg, false),
 
187
                    ok
 
188
            end
 
189
    end.
 
190
    
 
191
-record('REASON', {file, line, desc}).
 
192
 
 
193
error(Format, Args, File, Line) ->
 
194
    global:send(mnesia_global_logger, {failed, File, Line}),
 
195
    Fail = #'REASON'{file = filename:basename(File),
 
196
                     line = Line,
 
197
                     desc = Args},
 
198
    case global:whereis_name(mnesia_test_case_sup) of
 
199
        undefined -> 
 
200
            ignore;
 
201
        Pid -> 
 
202
            Pid ! Fail
 
203
%%          global:send(mnesia_test_case_sup, Fail),
 
204
    end,
 
205
    log("<>ERROR<>~n" ++ Format, Args, File, Line).
 
206
 
 
207
storage_type(Default, Config) ->
 
208
    case diskless(Config) of
 
209
        true ->
 
210
            ram_copies;
 
211
        false ->
 
212
            Default
 
213
    end.
 
214
 
 
215
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
216
 
 
217
default_config() ->
 
218
    [{nodes, default_nodes()}].
 
219
 
 
220
default_nodes() ->    
 
221
    mk_nodes(3, []).
 
222
 
 
223
mk_nodes(0, Nodes) ->
 
224
    Nodes;
 
225
mk_nodes(N, []) ->
 
226
    mk_nodes(N - 1, [node()]);
 
227
mk_nodes(N, Nodes) when N > 0 ->
 
228
    Head = hd(Nodes),
 
229
    [Name, Host] = node_to_name_and_host(Head),
 
230
    Nodes ++ [mk_node(I, Name, Host) || I <- lists:seq(1, N)].
 
231
 
 
232
mk_node(N, Name, Host) ->
 
233
    list_to_atom(lists:concat([Name ++ integer_to_list(N) ++ "@" ++ Host])).
 
234
    
 
235
slave_start_link() ->
 
236
    slave_start_link(node()).
 
237
 
 
238
slave_start_link(Node) ->
 
239
    [Local, Host] = node_to_name_and_host(Node),
 
240
    {Mega, Sec, Micro} = erlang:now(),
 
241
    List = [Local, "_", Mega, "_", Sec, "_", Micro],
 
242
    Name = list_to_atom(lists:concat(List)),
 
243
    slave_start_link(list_to_atom(Host), Name).
 
244
 
 
245
slave_start_link(Host, Name) ->
 
246
    slave_start_link(Host, Name, 10).
 
247
 
 
248
slave_start_link(Host, Name, Retries) ->
 
249
    Debug = atom_to_list(mnesia:system_info(debug)),
 
250
    Args = "-mnesia debug " ++ Debug ++ 
 
251
        " -pa " ++
 
252
        filename:dirname(code:which(?MODULE)) ++ 
 
253
        " -pa " ++ 
 
254
        filename:dirname(code:which(mnesia)),    
 
255
    case starter(Host, Name, Args) of
 
256
        {ok, NewNode} ->
 
257
            ?match(pong, net_adm:ping(NewNode)),
 
258
            {ok, Cwd} = file:get_cwd(),
 
259
            Path = code:get_path(),
 
260
            ok = rpc:call(NewNode, file, set_cwd, [Cwd]),
 
261
            true = rpc:call(NewNode, code, set_path, [Path]),
 
262
            spawn_link(NewNode, ?MODULE, slave_sup, []),
 
263
            rpc:multicall([node() | nodes()], global, sync, []),
 
264
            {ok, NewNode};
 
265
        {error, Reason} when Retries == 0->
 
266
            {error, Reason};
 
267
        {error, Reason} ->          
 
268
            io:format("Could not start slavenode ~p ~p retrying~n", 
 
269
                      [{Host, Name, Args}, Reason]),
 
270
            timer:sleep(500),
 
271
            slave_start_link(Host, Name, Retries - 1)
 
272
    end.
 
273
 
 
274
starter(Host, Name, Args) ->
 
275
    case os:type() of
 
276
        vxworks ->
 
277
            X = test_server:start_node(Name, slave, [{args,Args}]),
 
278
            timer:sleep(5000),
 
279
            X;
 
280
        _ ->
 
281
            slave:start(Host, Name, Args)
 
282
    end.
 
283
 
 
284
slave_sup() ->
 
285
    process_flag(trap_exit, true),
 
286
    receive
 
287
        {'EXIT', _, _} -> 
 
288
            case os:type() of
 
289
                vxworks ->
 
290
                    erlang:halt();
 
291
                _  ->
 
292
                    ignore
 
293
            end
 
294
    end.
 
295
    
 
296
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
297
%% Index the test case structure
 
298
 
 
299
doc(TestCases) when is_list(TestCases) ->
 
300
    test(TestCases, suite),
 
301
    SuiteFname = "index.html",
 
302
    io:format("Generating HTML test specification to file: ~s~n",
 
303
              [SuiteFname]),
 
304
    {ok, Fd} = file:open(SuiteFname, [write]),
 
305
    io:format(Fd, "<TITLE>Test specification for ~p</TITLE>.~n", [TestCases]),
 
306
    io:format(Fd, "<H1>Test specification for ~p</H1>~n", [TestCases]),
 
307
    io:format(Fd, "Test cases which not are implemented yet are written in <B>bold face</B>.~n~n", []),
 
308
    
 
309
    io:format(Fd, "<BR><BR>~n", []),
 
310
    io:format(Fd, "~n<DL>~n", []),
 
311
    do_doc(Fd, TestCases, []),
 
312
    io:format(Fd, "</DL>~n", []),
 
313
    file:close(Fd);
 
314
doc(TestCases) ->
 
315
    doc([TestCases]).
 
316
 
 
317
do_doc(Fd, [H | T], List) ->
 
318
    case H of
 
319
        {Module, TestCase} when is_atom(Module), is_atom(TestCase) ->
 
320
            do_doc(Fd, Module, TestCase, List);
 
321
        TestCase when is_atom(TestCase), List == [] ->
 
322
            do_doc(Fd, mnesia_SUITE, TestCase, List);
 
323
        TestCase when is_atom(TestCase) ->
 
324
            do_doc(Fd, hd(List), TestCase, List)
 
325
    end,
 
326
    do_doc(Fd, T, List);
 
327
do_doc(_, [], _) ->
 
328
    ok.
 
329
 
 
330
do_doc(Fd, Module, TestCase, List) ->
 
331
    case get_suite(Module, TestCase) of
 
332
        [] ->
 
333
            %% Implemented leaf test case
 
334
            Head = ?flat_format("<A HREF=~p.html#~p_1>{~p, ~p}</A>}",
 
335
                                [Module, TestCase, Module, TestCase]),
 
336
            print_doc(Fd, Module, TestCase, Head);
 
337
        Suite when is_list(Suite) ->
 
338
            %% Test suite
 
339
            Head = ?flat_format("{~p, ~p}", [Module, TestCase]),
 
340
            print_doc(Fd, Module, TestCase, Head),
 
341
            io:format(Fd, "~n<DL>~n", []),
 
342
            do_doc(Fd, Suite, [Module | List]),
 
343
            io:format(Fd, "</DL>~n", []);
 
344
        'NYI' ->
 
345
            %% Not yet implemented
 
346
            Head = ?flat_format("<B>{~p, ~p}</B>", [Module, TestCase]),
 
347
            print_doc(Fd, Module, TestCase, Head)
 
348
    end.
 
349
 
 
350
print_doc(Fd, Mod, Fun, Head) ->
 
351
    case catch (apply(Mod, Fun, [doc])) of
 
352
        {'EXIT', _} -> 
 
353
            io:format(Fd, "<DT>~s</DT>~n", [Head]);
 
354
        Doc when is_list(Doc) ->
 
355
            io:format(Fd, "<DT><U>~s</U><BR><DD>~n", [Head]),
 
356
            print_rows(Fd, Doc),
 
357
            io:format(Fd, "</DD><BR><BR>~n", [])
 
358
    end.
 
359
 
 
360
print_rows(_Fd, []) ->
 
361
    ok;
 
362
print_rows(Fd, [H | T]) when is_list(H) ->
 
363
    io:format(Fd, "~s~n", [H]),
 
364
    print_rows(Fd, T);
 
365
print_rows(Fd, [H | T]) when is_integer(H) ->
 
366
    io:format(Fd, "~s~n", [[H | T]]).
 
367
 
 
368
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
369
%% Show the test case structure
 
370
 
 
371
struct(TestCases) ->
 
372
    T = test(TestCases, suite),
 
373
    struct(T, "").
 
374
 
 
375
struct({Module, TestCase}, Indentation)
 
376
        when is_atom(Module), is_atom(TestCase) ->
 
377
    log("~s{~p, ~p} ...~n", [Indentation, Module, TestCase]);
 
378
struct({Module, TestCase, Other}, Indentation)
 
379
        when is_atom(Module), is_atom(TestCase) ->
 
380
    log("~s{~p, ~p} ~p~n", [Indentation, Module, TestCase, Other]);
 
381
struct([], _) ->
 
382
    ok;
 
383
struct([TestCase | TestCases], Indentation) ->
 
384
    struct(TestCase, Indentation),
 
385
    struct(TestCases, Indentation);
 
386
struct({TestCase, []}, Indentation) ->
 
387
    struct(TestCase, Indentation);
 
388
struct({TestCase, SubTestCases}, Indentation) when is_list(SubTestCases) ->
 
389
    struct(TestCase, Indentation),
 
390
    struct(SubTestCases, Indentation ++ "  ").
 
391
 
 
392
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
393
%% Execute the test cases
 
394
 
 
395
test(TestCases) ->
 
396
    test(TestCases, []).
 
397
 
 
398
test(TestCases, suite) when is_list(TestCases) ->
 
399
    test_driver(TestCases, suite);
 
400
test(TestCases, Config) when is_list(TestCases) ->
 
401
    D1 = lists:duplicate(10, $=),
 
402
    D2 =  lists:duplicate(10, $ ),
 
403
    log("~n~s TEST CASES: ~p~n ~sCONFIG: ~p~n~n", [D1, TestCases, D2, Config]),
 
404
    test_driver(TestCases, Config);
 
405
test(TestCase, Config) ->
 
406
    test([TestCase], Config).
 
407
 
 
408
test_driver([], _Config) ->
 
409
    [];
 
410
test_driver([T|TestCases], Config) ->
 
411
    L1 = test_driver(T, Config),
 
412
    L2 = test_driver(TestCases, Config),
 
413
    [L1|L2];
 
414
test_driver({Module, TestCases}, Config) when is_list(TestCases)->
 
415
    test_driver(default_module(Module, TestCases), Config);
 
416
test_driver({_, {Module, TestCase}}, Config) ->
 
417
    test_driver({Module, TestCase}, Config);
 
418
test_driver({Module, TestCase}, Config) ->
 
419
    Sec = timer:seconds(1) * 1000,
 
420
    case get_suite(Module, TestCase) of
 
421
        [] when Config == suite ->
 
422
            {Module, TestCase, 'IMPL'};
 
423
        [] ->
 
424
            log("Eval test case: ~w~n", [{Module, TestCase}]),
 
425
            {T, Res} =
 
426
                timer:tc(?MODULE, eval_test_case, [Module, TestCase, Config]),
 
427
            log("Tested ~w in ~w sec~n", [TestCase, T div Sec]),
 
428
            {T div Sec, Res};
 
429
        Suite when is_list(Suite), Config == suite ->
 
430
            Res = test_driver(default_module(Module, Suite), Config),
 
431
            {{Module, TestCase}, Res};
 
432
        Suite when is_list(Suite) ->
 
433
            log("Expand test case ~w~n", [{Module, TestCase}]),
 
434
            Def = default_module(Module, Suite),
 
435
            {T, Res} = timer:tc(?MODULE, test_driver, [Def, Config]),
 
436
            {T div Sec, {{Module, TestCase}, Res}};
 
437
        'NYI' when Config == suite ->
 
438
            {Module, TestCase, 'NYI'};
 
439
        'NYI' ->
 
440
            log("<WARNING> Test case ~w NYI~n", [{Module, TestCase}]),
 
441
            {0, {skip, {Module, TestCase}, "NYI"}}
 
442
    end;
 
443
test_driver(TestCase, Config) ->
 
444
    DefaultModule = mnesia_SUITE,
 
445
    log("<>WARNING<> Missing module in test case identifier. "
 
446
        "{~w, ~w} assumed~n", [DefaultModule, TestCase]),
 
447
    test_driver({DefaultModule, TestCase}, Config).
 
448
 
 
449
default_module(DefaultModule, TestCases) when is_list(TestCases) ->
 
450
    Fun = fun(T) ->
 
451
                  case T of
 
452
                      {_, _} -> true;
 
453
                      T -> {true, {DefaultModule, T}}
 
454
                  end
 
455
          end,
 
456
    lists:zf(Fun, TestCases).
 
457
 
 
458
%% Returns a list (possibly empty) or the atom 'NYI'
 
459
get_suite(Mod, Fun) ->
 
460
    case catch (apply(Mod, Fun, [suite])) of
 
461
        {'EXIT', _} -> 'NYI';
 
462
        List when is_list(List) -> List
 
463
    end.
 
464
 
 
465
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
466
 
 
467
eval_test_case(Mod, Fun, Config) ->
 
468
    flush(),
 
469
    global:register_name(mnesia_test_case_sup, self()),
 
470
    Flag = process_flag(trap_exit, true),
 
471
    Pid = spawn_link(?MODULE, test_case_evaluator, [Mod, Fun, [Config]]),
 
472
    R = wait_for_evaluator(Pid, Mod, Fun, Config),
 
473
    global:unregister_name(mnesia_test_case_sup),
 
474
    process_flag(trap_exit, Flag),
 
475
    R.
 
476
 
 
477
flush() ->
 
478
    receive Msg -> [Msg | flush()]
 
479
    after 0 -> []
 
480
    end.
 
481
 
 
482
wait_for_evaluator(Pid, Mod, Fun, Config) ->
 
483
    receive
 
484
        {'EXIT', Pid, {test_case_ok, _PidRes}} ->
 
485
            Errors = flush(),
 
486
            Res = 
 
487
                case Errors of
 
488
                    [] -> ok;
 
489
                    Errors -> failed
 
490
                end,
 
491
            {Res, {Mod, Fun}, Errors};
 
492
        {'EXIT', Pid, {skipped, Reason}} ->
 
493
            log("<WARNING> Test case ~w skipped, because ~p~n",
 
494
                [{Mod, Fun}, Reason]),
 
495
            Mod:end_per_testcase(Fun, Config),
 
496
            {skip, {Mod, Fun}, Reason};
 
497
        {'EXIT', Pid, Reason} ->
 
498
            log("<>ERROR<> Eval process ~w exited, because ~p~n",
 
499
                [{Mod, Fun}, Reason]),
 
500
            Mod:end_per_testcase(Fun, Config),
 
501
            {crash, {Mod, Fun}, Reason}
 
502
    end.
 
503
 
 
504
test_case_evaluator(Mod, Fun, [Config]) ->
 
505
    NewConfig = Mod:init_per_testcase(Fun, Config),
 
506
    R = apply(Mod, Fun, [NewConfig]),
 
507
    Mod:end_per_testcase(Fun, NewConfig),
 
508
    exit({test_case_ok, R}).
 
509
 
 
510
activity_evaluator(Coordinator) ->
 
511
    activity_evaluator_loop(Coordinator),
 
512
    exit(normal).
 
513
 
 
514
activity_evaluator_loop(Coordinator) ->
 
515
    receive
 
516
        begin_trans ->
 
517
            transaction(Coordinator, 0);
 
518
        {begin_trans, MaxRetries} ->
 
519
            transaction(Coordinator, MaxRetries);
 
520
        end_trans ->
 
521
            end_trans;
 
522
        Fun when is_function(Fun) ->
 
523
            Coordinator ! {self(), Fun()},
 
524
            activity_evaluator_loop(Coordinator);
 
525
%       {'EXIT', Coordinator, Reason} ->
 
526
%           Reason;
 
527
        ExitExpr ->
 
528
%           ?error("activity_evaluator_loop ~p ~p: exit(~p)~n}", [Coordinator, self(), ExitExpr]),
 
529
            exit(ExitExpr)
 
530
    end.
 
531
 
 
532
transaction(Coordinator, MaxRetries) ->
 
533
    Fun = fun() ->
 
534
                  Coordinator ! {self(), begin_trans},
 
535
                  activity_evaluator_loop(Coordinator)
 
536
          end,
 
537
    Coordinator ! {self(), mnesia:transaction(Fun, MaxRetries)},
 
538
    activity_evaluator_loop(Coordinator).
 
539
 
 
540
pick_msg() ->
 
541
    receive
 
542
        Message -> Message
 
543
    after 4000 -> timeout
 
544
    end.
 
545
 
 
546
start_activities(Nodes) ->
 
547
    Fun = fun(N) -> spawn_link(N, ?MODULE, activity_evaluator, [self()]) end,
 
548
    Pids = mapl(Fun, Nodes),
 
549
    {success, Pids}.
 
550
 
 
551
mapl(Fun, [H|T]) ->
 
552
    Res = Fun(H),
 
553
    [Res|mapl(Fun, T)];
 
554
mapl(_Fun, []) ->
 
555
    [].
 
556
 
 
557
diskless(Config) ->
 
558
    case lists:keysearch(diskless, 1, Config) of
 
559
        {value, {diskless, true}} -> 
 
560
            true;
 
561
        _Else ->
 
562
            false
 
563
    end.
 
564
 
 
565
 
 
566
start_transactions(Pids) ->
 
567
    Fun = fun(Pid) ->
 
568
                  Pid ! begin_trans,
 
569
                  ?match_receive({Pid, begin_trans})
 
570
          end,
 
571
    mapl(Fun, Pids).
 
572
 
 
573
start_sync_transactions(Pids) ->
 
574
    Nodes = [node(Pid) || Pid <- Pids],
 
575
    Fun = fun(Pid) ->
 
576
                  sync_trans_tid_serial(Nodes),
 
577
                  Pid ! begin_trans,
 
578
                  ?match_receive({Pid, begin_trans})
 
579
          end,
 
580
    mapl(Fun, Pids).
 
581
 
 
582
 
 
583
start_transactions(Pids, MaxRetries) ->
 
584
    Fun = fun(Pid) ->
 
585
                  Pid ! {begin_trans, MaxRetries},
 
586
                  ?match_receive({Pid, begin_trans})
 
587
          end,
 
588
    mapl(Fun, Pids).
 
589
 
 
590
start_sync_transactions(Pids, MaxRetries) ->
 
591
    Nodes = [node(Pid) || Pid <- Pids],
 
592
    Fun = fun(Pid) ->
 
593
                  sync_trans_tid_serial(Nodes),
 
594
                  Pid ! {begin_trans, MaxRetries},
 
595
                  ?match_receive({Pid, begin_trans})
 
596
          end,
 
597
    mapl(Fun, Pids).
 
598
 
 
599
sync_trans_tid_serial(Nodes) ->
 
600
    Fun = fun() -> mnesia:write_lock_table(schema) end,
 
601
    rpc:multicall(Nodes, mnesia, transaction, [Fun]).
 
602
 
 
603
select_nodes(N, Config, File, Line) ->
 
604
    prepare_test_case([], N, Config, File, Line).
 
605
    
 
606
prepare_test_case(Actions, N, Config, File, Line) ->
 
607
    NodeList1 = lookup_config(nodes, Config),
 
608
    NodeList2 = lookup_config(nodenames, Config), %% For testserver
 
609
    NodeList3 = append_unique(NodeList1, NodeList2),
 
610
    This = node(),
 
611
    All = [This | lists:delete(This, NodeList3)],
 
612
    Selected = pick_nodes(N, All, File, Line),
 
613
    case diskless(Config) of
 
614
        true ->
 
615
            ok;
 
616
        false ->
 
617
            rpc:multicall(Selected, application, set_env,[mnesia, schema_location, opt_disc])
 
618
    end,
 
619
    do_prepare(Actions, Selected, All, Config, File, Line).
 
620
 
 
621
do_prepare([], Selected, _All, _Config, _File, _Line) ->
 
622
    Selected;
 
623
do_prepare([{init_test_case, Appls} | Actions], Selected, All, Config, File, Line) ->
 
624
    set_kill_timer(Config),
 
625
    Started = init_nodes(Selected, File, Line),
 
626
    All2 = append_unique(Started, All),
 
627
    Alive = mnesia_lib:intersect(nodes() ++ [node()], All2),
 
628
    kill_appls(Appls, Alive),
 
629
    process_flag(trap_exit, true),
 
630
    do_prepare(Actions, Started, All2, Config, File, Line);
 
631
do_prepare([delete_schema | Actions], Selected, All, Config, File, Line) ->
 
632
    Alive = mnesia_lib:intersect(nodes() ++ [node()], All),
 
633
    case diskless(Config) of
 
634
        true ->
 
635
            skip;
 
636
        false ->
 
637
            Del = fun(Node) -> 
 
638
                          case mnesia:delete_schema([Node]) of
 
639
                              ok -> ok;
 
640
                              {error, {"All nodes not running",_}} -> 
 
641
                                  ok;
 
642
                              Else ->
 
643
                                  ?log("Delete schema error ~p ~n", [Else])
 
644
                          end
 
645
                  end,
 
646
            lists:foreach(Del, Alive)
 
647
    end,
 
648
    do_prepare(Actions, Selected, All, Config, File, Line);
 
649
do_prepare([create_schema | Actions], Selected, All, Config, File, Line) ->
 
650
    case diskless(Config) of
 
651
        true -> 
 
652
            skip;
 
653
        _Else ->
 
654
            case mnesia:create_schema(Selected) of
 
655
                ok ->
 
656
                    ignore;
 
657
                BadNodes ->
 
658
                    ?fatal("Cannot create Mnesia schema on ~p~n", [BadNodes])
 
659
            end
 
660
    end,
 
661
    do_prepare(Actions, Selected, All, Config, File, Line);
 
662
do_prepare([{start_appls, Appls} | Actions], Selected, All, Config, File, Line) ->
 
663
    case start_appls(Appls, Selected, Config) of
 
664
        [] -> ok;
 
665
        Bad -> ?fatal("Cannot start appls ~p: ~p~n", [Appls, Bad])
 
666
    end,
 
667
    do_prepare(Actions, Selected, All, Config, File, Line);
 
668
do_prepare([{reload_appls, Appls} | Actions], Selected, All, Config, File, Line) ->
 
669
    reload_appls(Appls, Selected),
 
670
    do_prepare(Actions, Selected, All, Config, File, Line).
 
671
 
 
672
set_kill_timer(Config) ->
 
673
    case init:get_argument(mnesia_test_timeout) of
 
674
        {ok, _ } -> ok;
 
675
        _ ->
 
676
            Time0 = 
 
677
                case lookup_config(tc_timeout, Config) of
 
678
                    [] -> timer:minutes(5);
 
679
                    ConfigTime when is_integer(ConfigTime) -> ConfigTime
 
680
                end,
 
681
            Mul = try 
 
682
                      test_server:timetrap_scale_factor()
 
683
                  catch _:_ -> 1 end,
 
684
            (catch test_server:timetrap(Mul*Time0 + 1000)),
 
685
            spawn_link(?MODULE, kill_tc, [self(),Time0*Mul])
 
686
    end.
 
687
 
 
688
kill_tc(Pid, Time) ->
 
689
    receive 
 
690
    after Time ->
 
691
            case process_info(Pid) of
 
692
                undefined ->  ok;
 
693
                _ ->
 
694
                    ?error("Watchdog in test case timed out "
 
695
                           "in ~p min~n", [Time div (1000*60)]),
 
696
                    Files = mnesia_lib:dist_coredump(),
 
697
                    ?log("Cores dumped to:~n ~p~n", [Files]),
 
698
                    %% Genarate erlang crashdumps.
 
699
                    %% GenDump = fun(Node) ->
 
700
                    %%                File = "CRASH_" ++ atom_to_list(Node) ++ ".dump",
 
701
                    %%                rpc:call(Node, os, putenv, ["ERL_CRASH_DUMP", File]),
 
702
                    %%                rpc:cast(Node, erlang, halt, ["RemoteTimeTrap"])
 
703
                    %%        end,
 
704
                    %% [GenDump(Node) || Node <- nodes()],
 
705
 
 
706
                    %% erlang:halt("DebugTimeTrap"),
 
707
                    exit(Pid, kill)
 
708
            end
 
709
    end.
 
710
    
 
711
 
 
712
append_unique([], List) -> List;
 
713
append_unique([H|R], List) -> 
 
714
    case lists:member(H, List) of
 
715
        true -> append_unique(R, List);
 
716
        false -> [H | append_unique(R, List)]
 
717
    end.
 
718
 
 
719
pick_nodes(all, Nodes, File, Line) ->
 
720
    pick_nodes(length(Nodes), Nodes, File, Line);
 
721
pick_nodes(N, [H | T], File, Line) when N > 0 ->
 
722
    [H | pick_nodes(N - 1, T, File, Line)]; 
 
723
pick_nodes(0, _Nodes, _File, _Line) ->
 
724
    [];
 
725
pick_nodes(N, [], File, Line) ->
 
726
    ?skip("Test case (~p(~p)) ignored: ~p nodes missing~n",
 
727
          [File, Line, N]).
 
728
   
 
729
init_nodes([Node | Nodes], File, Line) ->
 
730
    case net_adm:ping(Node) of
 
731
        pong ->
 
732
            [Node | init_nodes(Nodes, File, Line)];
 
733
        pang ->
 
734
            [Name, Host] = node_to_name_and_host(Node),
 
735
            case slave_start_link(Host, Name) of
 
736
                {ok, Node1} ->
 
737
                    Path = code:get_path(),
 
738
                    true = rpc:call(Node1, code, set_path, [Path]),
 
739
                    [Node1 | init_nodes(Nodes, File, Line)];
 
740
                Other ->
 
741
                    ?skip("Test case (~p(~p)) ignored: cannot start node ~p: ~p~n",
 
742
                          [File, Line, Node, Other])
 
743
            end
 
744
    end;
 
745
init_nodes([], _File, _Line) ->
 
746
    [].
 
747
 
 
748
%% Returns [Name, Host]    
 
749
node_to_name_and_host(Node) ->
 
750
    string:tokens(atom_to_list(Node), [$@]).
 
751
 
 
752
lookup_config(Key,Config) ->
 
753
    case lists:keysearch(Key,1,Config) of
 
754
        {value,{Key,Val}} ->
 
755
            Val;
 
756
        _ ->
 
757
            []
 
758
    end.
 
759
 
 
760
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
761
 
 
762
start_appls(Appls, Nodes) ->
 
763
    start_appls(Appls, Nodes, [],  [schema]).
 
764
    
 
765
start_appls(Appls, Nodes, Config) ->
 
766
    start_appls(Appls, Nodes, Config, [schema]).
 
767
 
 
768
start_appls([Appl | Appls], Nodes, Config, Tabs) ->
 
769
    {Started, BadStarters} =
 
770
        rpc:multicall(Nodes, ?MODULE, remote_start, [Appl, Config, Nodes]),
 
771
    BadS = [{Node, Appl, Res} || {Node, Res} <- Started, Res /= ok],
 
772
    BadN = [{BadNode, Appl, bad_start} || BadNode <- BadStarters],
 
773
    Bad = BadS ++ BadN,
 
774
    case Appl of
 
775
        mnesia when Bad == [] ->
 
776
            sync_tables(Nodes, Tabs);
 
777
        _ ->
 
778
            ignore
 
779
    end,
 
780
    Bad ++ start_appls(Appls, Nodes, Config, Tabs);
 
781
start_appls([], _Nodes, _Config, _Tabs) ->
 
782
    [].
 
783
 
 
784
remote_start(mnesia, Config, Nodes) ->
 
785
    case diskless(Config) of
 
786
        true -> 
 
787
            application_controller:set_env(mnesia, 
 
788
                                           extra_db_nodes, 
 
789
                                           Nodes -- [node()]),
 
790
            application_controller:set_env(mnesia,
 
791
                                           schema_location,
 
792
                                           ram);
 
793
        false ->
 
794
            application_controller:set_env(mnesia,
 
795
                                           schema_location,
 
796
                                           opt_disc),
 
797
            ignore
 
798
    end,
 
799
    {node(), mnesia:start()};
 
800
remote_start(Appl, _Config, _Nodes) ->
 
801
    Res = 
 
802
        case application:start(Appl) of
 
803
            {error, {already_started, Appl}} ->
 
804
                ok;
 
805
            Other ->
 
806
                Other
 
807
        end,
 
808
    {node(), Res}.
 
809
 
 
810
%% Start Mnesia on all given nodes and wait for specified
 
811
%% tables to be accessible on each node. The atom all means
 
812
%% that we should wait for all tables to be loaded
 
813
%% 
 
814
%% Returns a list of error tuples {BadNode, mnesia, Reason}
 
815
start_mnesia(Nodes) ->
 
816
    start_appls([mnesia], Nodes).
 
817
start_mnesia(Nodes, Tabs) when is_list(Nodes) ->
 
818
    start_appls([mnesia], Nodes, [], Tabs).
 
819
    
 
820
%% Wait for the tables to be accessible from all nodes in the list
 
821
%% and that all nodes are aware of that the other nodes also ...
 
822
sync_tables(Nodes, Tabs) ->
 
823
    Res = send_wait(Nodes, Tabs, []),
 
824
    if
 
825
        Res ==  [] ->
 
826
            mnesia:transaction(fun() -> mnesia:write_lock_table(schema) end),
 
827
            Res;
 
828
        true ->
 
829
            Res
 
830
    end.
 
831
 
 
832
send_wait([Node | Nodes], Tabs, Pids) ->
 
833
    Pid = spawn_link(Node, ?MODULE, start_wait, [self(), Tabs]),
 
834
    send_wait(Nodes, Tabs, [Pid | Pids]);
 
835
send_wait([], _Tabs, Pids) ->
 
836
    rec_wait(Pids, []).
 
837
 
 
838
rec_wait([Pid | Pids], BadRes) ->
 
839
    receive
 
840
        {'EXIT', Pid, R} ->
 
841
            rec_wait(Pids, [{node(Pid), bad_wait, R} | BadRes]);
 
842
        {Pid, ok} ->
 
843
            rec_wait(Pids, BadRes);
 
844
        {Pid, {error, R}} ->
 
845
            rec_wait(Pids, [{node(Pid), bad_wait, R} | BadRes])
 
846
    end;
 
847
rec_wait([], BadRes) ->
 
848
    BadRes.
 
849
 
 
850
start_wait(Coord, Tabs) ->
 
851
    process_flag(trap_exit, true),
 
852
    Mon = whereis(mnesia_monitor),
 
853
    case catch link(Mon) of
 
854
        {'EXIT', _} ->
 
855
            unlink(Coord),
 
856
            Coord ! {self(), {error, {node_not_running, node()}}};
 
857
        _ ->
 
858
            Res = start_wait_loop(Tabs),
 
859
            unlink(Mon),
 
860
            unlink(Coord),
 
861
            Coord ! {self(), Res}
 
862
    end.
 
863
 
 
864
start_wait_loop(Tabs) ->
 
865
    receive
 
866
        {'EXIT', Pid, Reason} ->
 
867
            {error, {start_wait, Pid, Reason}}
 
868
    after 0 ->
 
869
            case mnesia:wait_for_tables(Tabs, timer:seconds(30)) of
 
870
                ok ->
 
871
                    verify_nodes(Tabs);
 
872
                {timeout, BadTabs} ->
 
873
                    log("<>WARNING<> Wait for tables ~p: ~p~n", [node(), Tabs]),
 
874
                    start_wait_loop(BadTabs);
 
875
                {error, Reason} ->
 
876
                    {error, {start_wait, Reason}}
 
877
            end
 
878
    end.
 
879
 
 
880
verify_nodes(Tabs) ->
 
881
    verify_nodes(Tabs, 0).
 
882
 
 
883
verify_nodes([], _) ->
 
884
    ok;
 
885
 
 
886
verify_nodes([Tab| Tabs], N) ->
 
887
    ?match(X when is_atom(X), mnesia_lib:val({Tab, where_to_read})),
 
888
    Nodes = mnesia:table_info(Tab, where_to_write),
 
889
    Copies =
 
890
        mnesia:table_info(Tab, disc_copies) ++
 
891
        mnesia:table_info(Tab, disc_only_copies) ++
 
892
        mnesia:table_info(Tab, ram_copies),
 
893
    Local = mnesia:table_info(Tab, local_content),
 
894
    case Copies -- Nodes of
 
895
        [] -> 
 
896
            verify_nodes(Tabs, 0);
 
897
        _Else when Local == true, Nodes /= [] ->
 
898
            verify_nodes(Tabs, 0);
 
899
        Else ->
 
900
            N2 = 
 
901
                if
 
902
                    N > 20 -> 
 
903
                        log("<>WARNING<> ~w Waiting for table: ~p on ~p ~n", 
 
904
                                 [node(), Tab, Else]),
 
905
                        0;
 
906
                    true -> N+1
 
907
                end,        
 
908
            timer:sleep(500),
 
909
            verify_nodes([Tab| Tabs], N2)
 
910
    end.
 
911
 
 
912
 
 
913
%% Nicely stop Mnesia on all given nodes
 
914
%% 
 
915
%% Returns a list of error tuples {BadNode, Reason}
 
916
stop_mnesia(Nodes) when is_list(Nodes) ->
 
917
    stop_appls([mnesia], Nodes).
 
918
 
 
919
stop_appls([Appl | Appls], Nodes) when is_list(Nodes) ->
 
920
    {Stopped, BadNodes} = rpc:multicall(Nodes, ?MODULE, remote_stop, [Appl]),
 
921
    BadS =[{Node, Appl, Res} || {Node, Res} <- Stopped, Res /= stopped],
 
922
    BadN =[{BadNode, Appl, bad_node} || BadNode <- BadNodes],
 
923
    BadS ++ BadN ++ stop_appls(Appls, Nodes);
 
924
stop_appls([], _Nodes) ->
 
925
    [].
 
926
 
 
927
remote_stop(mnesia) ->
 
928
    {node(), mnesia:stop()};
 
929
remote_stop(Appl) ->
 
930
    {node(), application:stop(Appl)}.
 
931
 
 
932
remote_kill([Appl | Appls]) ->
 
933
    catch Appl:lkill(),
 
934
    application:stop(Appl),
 
935
    remote_kill(Appls);
 
936
remote_kill([]) ->
 
937
    ok.
 
938
 
 
939
%% Abruptly kill Mnesia on all given nodes
 
940
%% Returns []
 
941
kill_appls(Appls, Nodes) when is_list(Nodes) ->
 
942
    verbose("<>WARNING<> Intentionally killing ~p: ~w...~n",
 
943
            [Appls, Nodes], ?FILE, ?LINE),
 
944
    rpc:multicall(Nodes, ?MODULE, remote_kill, [Appls]),
 
945
    [].
 
946
 
 
947
kill_mnesia(Nodes) when is_list(Nodes) ->
 
948
    kill_appls([mnesia], Nodes).
 
949
 
 
950
reload_appls([Appl | Appls], Selected) ->
 
951
    kill_appls([Appl], Selected),
 
952
    timer:sleep(1000),
 
953
    Ok = {[ok || _N <- Selected], []},
 
954
    {Ok2temp, Empty} = rpc:multicall(Selected, application, unload, [Appl]),
 
955
    Conv = fun({error,{not_loaded,mnesia}}) -> ok; (Else) -> Else end,
 
956
    Ok2 = {lists:map(Conv, Ok2temp), Empty},
 
957
 
 
958
    Ok3 = rpc:multicall(Selected, application, load, [Appl]),
 
959
    if
 
960
        Ok /= Ok2 ->
 
961
            ?fatal("Cannot unload appl ~p: ~p~n", [Appl, Ok2]);
 
962
        Ok /= Ok3 ->
 
963
            ?fatal("Cannot load appl ~p: ~p~n", [Appl, Ok3]);
 
964
        true ->
 
965
            ok
 
966
    end,
 
967
    reload_appls(Appls, Selected);
 
968
reload_appls([], _Selected) ->
 
969
    ok.
 
970
 
 
971
shutdown() ->
 
972
    log("<>WARNING<> Intentionally shutting down all nodes... ~p~n",
 
973
         [nodes() ++ [node()]]),
 
974
    rpc:multicall(nodes(), erlang, halt, []),
 
975
    erlang:halt().
 
976
 
 
977
verify_mnesia(Ups, Downs, File, Line) when is_list(Ups), is_list(Downs) ->
 
978
    BadUps =
 
979
        [N || N <- Ups, rpc:call(N, mnesia, system_info, [is_running]) /= yes],
 
980
    BadDowns =
 
981
        [N || N <- Downs, rpc:call(N, mnesia, system_info, [is_running]) == yes],
 
982
    if
 
983
        BadUps == [] ->
 
984
            ignore;
 
985
        true ->
 
986
            error("Mnesia is not running as expected: ~p~n",
 
987
                  [BadUps], File, Line)
 
988
    end,
 
989
    if
 
990
        BadDowns == [] ->
 
991
            ignore;
 
992
        true ->
 
993
            error("Mnesia is not stopped as expected: ~p~n",
 
994
                  [BadDowns], File, Line)
 
995
    end,
 
996
    ok.
 
997
 
 
998
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
999
 
 
1000
verify_replica_location(Tab, [], [], [], _) ->
 
1001
    ?match({'EXIT', _}, mnesia:table_info(Tab, ram_copies)),
 
1002
    ?match({'EXIT', _}, mnesia:table_info(Tab, disc_copies)),
 
1003
    ?match({'EXIT', _}, mnesia:table_info(Tab, disc_only_copies)),
 
1004
    ?match({'EXIT', _}, mnesia:table_info(Tab, where_to_write)),
 
1005
    ?match({'EXIT', _}, mnesia:table_info(Tab, where_to_read)),
 
1006
    [];
 
1007
 
 
1008
verify_replica_location(Tab, DiscOnly0, Ram0, Disc0, AliveNodes0) ->
 
1009
%%    sync_tables(AliveNodes0, [Tab]),
 
1010
    AliveNodes = lists:sort(AliveNodes0),
 
1011
    DiscOnly = lists:sort(DiscOnly0),
 
1012
    Ram = lists:sort(Ram0),
 
1013
    Disc = lists:sort(Disc0),
 
1014
    Write = ignore_dead(DiscOnly ++ Ram ++ Disc, AliveNodes),
 
1015
    Read = ignore_dead(DiscOnly ++ Ram ++ Disc, AliveNodes),
 
1016
    This = node(),
 
1017
 
 
1018
    timer:sleep(100), 
 
1019
 
 
1020
    S1 = ?match(AliveNodes, lists:sort(mnesia:system_info(running_db_nodes))),
 
1021
    S2 = ?match(DiscOnly, lists:sort(mnesia:table_info(Tab, disc_only_copies))),
 
1022
    S3 = ?match(Ram, lists:sort(mnesia:table_info(Tab, ram_copies))),
 
1023
    S4 = ?match(Disc, lists:sort(mnesia:table_info(Tab, disc_copies))),
 
1024
    S5 = ?match(Write, lists:sort(mnesia:table_info(Tab, where_to_write))),
 
1025
    S6 = case lists:member(This, Read) of
 
1026
             true ->
 
1027
                 ?match(This, mnesia:table_info(Tab, where_to_read));
 
1028
             false ->
 
1029
                 ?match(true, lists:member(mnesia:table_info(Tab, where_to_read), Read))
 
1030
         end,
 
1031
    lists:filter(fun({success,_}) -> false; (_) -> true end, [S1,S2,S3,S4,S5,S6]).
 
1032
 
 
1033
ignore_dead(Nodes, AliveNodes) ->
 
1034
    Filter = fun(Node) -> lists:member(Node, AliveNodes) end,
 
1035
    lists:sort(lists:zf(Filter, Nodes)).
 
1036
 
 
1037
 
 
1038
remote_activate_debug_fun(N, I, F, C, File, Line) ->
 
1039
    Pid = spawn_link(N, ?MODULE, do_remote_activate_debug_fun, [self(), I, F, C, File, Line]),
 
1040
    receive
 
1041
        {activated, Pid} -> ok;
 
1042
        {'EXIT', Pid, Reason} -> {error, Reason}
 
1043
    end.
 
1044
 
 
1045
do_remote_activate_debug_fun(From, I, F, C, File, Line) ->
 
1046
    mnesia_lib:activate_debug_fun(I, F, C, File, Line),
 
1047
    From ! {activated, self()},
 
1048
    timer:sleep(infinity).  % Dies whenever the test process dies !!
 
1049
 
 
1050
 
 
1051
sort(L) when is_list(L) -> 
 
1052
    lists:sort(L);
 
1053
sort({atomic, L}) when is_list(L) ->
 
1054
    {atomic, lists:sort(L)};
 
1055
sort({ok, L}) when is_list(L) ->
 
1056
    {ok, lists:sort(L)};
 
1057
sort(W) ->
 
1058
    W.