~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
5
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
99
99
         slave_start_link/0,
100
100
         slave_start_link/1,
101
101
         slave_sup/0,
102
 
        
 
102
 
103
103
         start_mnesia/1,
104
104
         start_mnesia/2,
105
105
         start_appls/2,
130
130
         doc/1,
131
131
         struct/1,
132
132
         init_per_testcase/2,
133
 
         fin_per_testcase/2,
134
 
         kill_tc/2      
 
133
         end_per_testcase/2,
 
134
         kill_tc/2
135
135
        ]).
136
136
 
137
137
-include("mnesia_test_lib.hrl").
144
144
    global:register_name(mnesia_global_logger, group_leader()),
145
145
    Config.
146
146
 
147
 
fin_per_testcase(_Func, Config) ->
 
147
end_per_testcase(_Func, Config) ->
148
148
    global:unregister_name(mnesia_global_logger),
149
149
    %% Nodes = select_nodes(all, Config, ?FILE, ?LINE),
150
150
    %% rpc:multicall(Nodes, mnesia, lkill, []),
187
187
                    ok
188
188
            end
189
189
    end.
190
 
    
 
190
 
191
191
-record('REASON', {file, line, desc}).
192
192
 
193
193
error(Format, Args, File, Line) ->
196
196
                     line = Line,
197
197
                     desc = Args},
198
198
    case global:whereis_name(mnesia_test_case_sup) of
199
 
        undefined -> 
 
199
        undefined ->
200
200
            ignore;
201
 
        Pid -> 
 
201
        Pid ->
202
202
            Pid ! Fail
203
203
%%          global:send(mnesia_test_case_sup, Fail),
204
204
    end,
217
217
default_config() ->
218
218
    [{nodes, default_nodes()}].
219
219
 
220
 
default_nodes() ->    
 
220
default_nodes() ->
221
221
    mk_nodes(3, []).
222
222
 
223
223
mk_nodes(0, Nodes) ->
231
231
 
232
232
mk_node(N, Name, Host) ->
233
233
    list_to_atom(lists:concat([Name ++ integer_to_list(N) ++ "@" ++ Host])).
234
 
    
 
234
 
235
235
slave_start_link() ->
236
236
    slave_start_link(node()).
237
237
 
247
247
 
248
248
slave_start_link(Host, Name, Retries) ->
249
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)),    
 
250
    Args = "-mnesia debug " ++ Debug ++
 
251
        " -pa " ++
 
252
        filename:dirname(code:which(?MODULE)) ++
 
253
        " -pa " ++
 
254
        filename:dirname(code:which(mnesia)),
255
255
    case starter(Host, Name, Args) of
256
256
        {ok, NewNode} ->
257
257
            ?match(pong, net_adm:ping(NewNode)),
264
264
            {ok, NewNode};
265
265
        {error, Reason} when Retries == 0->
266
266
            {error, Reason};
267
 
        {error, Reason} ->          
268
 
            io:format("Could not start slavenode ~p ~p retrying~n", 
 
267
        {error, Reason} ->
 
268
            io:format("Could not start slavenode ~p ~p retrying~n",
269
269
                      [{Host, Name, Args}, Reason]),
270
270
            timer:sleep(500),
271
271
            slave_start_link(Host, Name, Retries - 1)
284
284
slave_sup() ->
285
285
    process_flag(trap_exit, true),
286
286
    receive
287
 
        {'EXIT', _, _} -> 
 
287
        {'EXIT', _, _} ->
288
288
            case os:type() of
289
289
                vxworks ->
290
290
                    erlang:halt();
292
292
                    ignore
293
293
            end
294
294
    end.
295
 
    
 
295
 
296
296
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
297
297
%% Index the test case structure
298
298
 
305
305
    io:format(Fd, "<TITLE>Test specification for ~p</TITLE>.~n", [TestCases]),
306
306
    io:format(Fd, "<H1>Test specification for ~p</H1>~n", [TestCases]),
307
307
    io:format(Fd, "Test cases which not are implemented yet are written in <B>bold face</B>.~n~n", []),
308
 
    
 
308
 
309
309
    io:format(Fd, "<BR><BR>~n", []),
310
310
    io:format(Fd, "~n<DL>~n", []),
311
311
    do_doc(Fd, TestCases, []),
349
349
 
350
350
print_doc(Fd, Mod, Fun, Head) ->
351
351
    case catch (apply(Mod, Fun, [doc])) of
352
 
        {'EXIT', _} -> 
 
352
        {'EXIT', _} ->
353
353
            io:format(Fd, "<DT>~s</DT>~n", [Head]);
354
354
        Doc when is_list(Doc) ->
355
355
            io:format(Fd, "<DT><U>~s</U><BR><DD>~n", [Head]),
413
413
    [L1|L2];
414
414
test_driver({Module, TestCases}, Config) when is_list(TestCases)->
415
415
    test_driver(default_module(Module, TestCases), Config);
416
 
test_driver({_, {Module, TestCase}}, Config) ->
417
 
    test_driver({Module, TestCase}, Config);
 
416
test_driver({Module, all}, Config) ->
 
417
    get_suite(Module, all, Config);
 
418
test_driver({Module, G={group, _}}, Config) ->
 
419
    get_suite(Module, G, Config);
 
420
test_driver({_, {group, Module, Group}}, Config) ->
 
421
    get_suite(Module, {group, Group}, Config);
 
422
 
418
423
test_driver({Module, TestCase}, Config) ->
419
424
    Sec = timer:seconds(1) * 1000,
420
 
    case get_suite(Module, TestCase) of
421
 
        [] when Config == suite ->
 
425
    case Config of
 
426
        suite ->
422
427
            {Module, TestCase, 'IMPL'};
423
 
        [] ->
 
428
        _ ->
424
429
            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"}}
 
430
            try timer:tc(?MODULE, eval_test_case, [Module, TestCase, Config]) of
 
431
                {T, Res} ->
 
432
                    log("Tested ~w in ~w sec~n", [TestCase, T div Sec]),
 
433
                    {T div Sec, Res}
 
434
            catch error:function_clause ->
 
435
                    log("<WARNING> Test case ~w NYI~n", [{Module, TestCase}]),
 
436
                    {0, {skip, {Module, TestCase}, "NYI"}}
 
437
            end
442
438
    end;
443
439
test_driver(TestCase, Config) ->
444
440
    DefaultModule = mnesia_SUITE,
449
445
default_module(DefaultModule, TestCases) when is_list(TestCases) ->
450
446
    Fun = fun(T) ->
451
447
                  case T of
 
448
                      {group, _} -> {true, {DefaultModule, T}};
452
449
                      {_, _} -> true;
453
450
                      T -> {true, {DefaultModule, T}}
454
451
                  end
455
452
          end,
456
453
    lists:zf(Fun, TestCases).
457
454
 
 
455
get_suite(Module, TestCase, Config) ->
 
456
    case get_suite(Module, TestCase) of
 
457
        Suite when is_list(Suite), Config == suite ->
 
458
            Res = test_driver(default_module(Module, Suite), Config),
 
459
            {{Module, TestCase}, Res};
 
460
        Suite when is_list(Suite) ->
 
461
            log("Expand test case ~w~n", [{Module, TestCase}]),
 
462
            Def = default_module(Module, Suite),
 
463
            {T, Res} = timer:tc(?MODULE, test_driver, [Def, Config]),
 
464
            Sec = timer:seconds(1) * 1000,
 
465
            {T div Sec, {{Module, TestCase}, Res}};
 
466
        'NYI' when Config == suite ->
 
467
            {Module, TestCase, 'NYI'};
 
468
        'NYI' ->
 
469
            log("<WARNING> Test case ~w NYI~n", [{Module, TestCase}]),
 
470
            {0, {skip, {Module, TestCase}, "NYI"}}
 
471
    end.
 
472
 
458
473
%% Returns a list (possibly empty) or the atom 'NYI'
459
 
get_suite(Mod, Fun) ->
460
 
    case catch (apply(Mod, Fun, [suite])) of
 
474
get_suite(Mod, {group, Suite}) ->
 
475
    try
 
476
        Groups = Mod:groups(),
 
477
        {_, _, TCList} = lists:keyfind(Suite, 1, Groups),
 
478
        TCList
 
479
    catch
 
480
        _:Reason ->
 
481
            io:format("Not implemented ~p ~p (~p ~p)~n",
 
482
                      [Mod,Suite,Reason, erlang:get_stacktrace()]),
 
483
            'NYI'
 
484
    end;
 
485
get_suite(Mod, all) ->
 
486
    case catch (apply(Mod, all, [])) of
461
487
        {'EXIT', _} -> 'NYI';
462
488
        List when is_list(List) -> List
463
 
    end.
 
489
    end;
 
490
get_suite(_Mod, _Fun) ->
 
491
    [].
464
492
 
465
493
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
466
494
 
483
511
    receive
484
512
        {'EXIT', Pid, {test_case_ok, _PidRes}} ->
485
513
            Errors = flush(),
486
 
            Res = 
 
514
            Res =
487
515
                case Errors of
488
516
                    [] -> ok;
489
517
                    Errors -> failed
492
520
        {'EXIT', Pid, {skipped, Reason}} ->
493
521
            log("<WARNING> Test case ~w skipped, because ~p~n",
494
522
                [{Mod, Fun}, Reason]),
495
 
            Mod:fin_per_testcase(Fun, Config),
 
523
            Mod:end_per_testcase(Fun, Config),
496
524
            {skip, {Mod, Fun}, Reason};
497
525
        {'EXIT', Pid, Reason} ->
498
526
            log("<>ERROR<> Eval process ~w exited, because ~p~n",
499
527
                [{Mod, Fun}, Reason]),
500
 
            Mod:fin_per_testcase(Fun, Config),
 
528
            Mod:end_per_testcase(Fun, Config),
501
529
            {crash, {Mod, Fun}, Reason}
502
530
    end.
503
531
 
504
532
test_case_evaluator(Mod, Fun, [Config]) ->
505
533
    NewConfig = Mod:init_per_testcase(Fun, Config),
506
 
    R = apply(Mod, Fun, [NewConfig]),
507
 
    Mod:fin_per_testcase(Fun, NewConfig),
508
 
    exit({test_case_ok, R}).
 
534
    try
 
535
        R = apply(Mod, Fun, [NewConfig]),
 
536
        Mod:end_per_testcase(Fun, NewConfig),
 
537
        exit({test_case_ok, R})
 
538
    catch error:function_clause ->
 
539
            exit({skipped, 'NYI'})
 
540
    end.
509
541
 
510
542
activity_evaluator(Coordinator) ->
511
543
    activity_evaluator_loop(Coordinator),
556
588
 
557
589
diskless(Config) ->
558
590
    case lists:keysearch(diskless, 1, Config) of
559
 
        {value, {diskless, true}} -> 
 
591
        {value, {diskless, true}} ->
560
592
            true;
561
593
        _Else ->
562
594
            false
602
634
 
603
635
select_nodes(N, Config, File, Line) ->
604
636
    prepare_test_case([], N, Config, File, Line).
605
 
    
 
637
 
606
638
prepare_test_case(Actions, N, Config, File, Line) ->
607
639
    NodeList1 = lookup_config(nodes, Config),
608
640
    NodeList2 = lookup_config(nodenames, Config), %% For testserver
634
666
        true ->
635
667
            skip;
636
668
        false ->
637
 
            Del = fun(Node) -> 
 
669
            Del = fun(Node) ->
638
670
                          case mnesia:delete_schema([Node]) of
639
671
                              ok -> ok;
640
 
                              {error, {"All nodes not running",_}} -> 
 
672
                              {error, {"All nodes not running",_}} ->
641
673
                                  ok;
642
674
                              Else ->
643
675
                                  ?log("Delete schema error ~p ~n", [Else])
648
680
    do_prepare(Actions, Selected, All, Config, File, Line);
649
681
do_prepare([create_schema | Actions], Selected, All, Config, File, Line) ->
650
682
    case diskless(Config) of
651
 
        true -> 
 
683
        true ->
652
684
            skip;
653
685
        _Else ->
654
686
            case mnesia:create_schema(Selected) of
673
705
    case init:get_argument(mnesia_test_timeout) of
674
706
        {ok, _ } -> ok;
675
707
        _ ->
676
 
            Time0 = 
 
708
            Time0 =
677
709
                case lookup_config(tc_timeout, Config) of
678
710
                    [] -> timer:minutes(5);
679
711
                    ConfigTime when is_integer(ConfigTime) -> ConfigTime
680
712
                end,
681
 
            Mul = try 
 
713
            Mul = try
682
714
                      test_server:timetrap_scale_factor()
683
715
                  catch _:_ -> 1 end,
684
716
            (catch test_server:timetrap(Mul*Time0 + 1000)),
686
718
    end.
687
719
 
688
720
kill_tc(Pid, Time) ->
689
 
    receive 
 
721
    receive
690
722
    after Time ->
691
723
            case process_info(Pid) of
692
724
                undefined ->  ok;
707
739
                    exit(Pid, kill)
708
740
            end
709
741
    end.
710
 
    
 
742
 
711
743
 
712
744
append_unique([], List) -> List;
713
 
append_unique([H|R], List) -> 
 
745
append_unique([H|R], List) ->
714
746
    case lists:member(H, List) of
715
747
        true -> append_unique(R, List);
716
748
        false -> [H | append_unique(R, List)]
719
751
pick_nodes(all, Nodes, File, Line) ->
720
752
    pick_nodes(length(Nodes), Nodes, File, Line);
721
753
pick_nodes(N, [H | T], File, Line) when N > 0 ->
722
 
    [H | pick_nodes(N - 1, T, File, Line)]; 
 
754
    [H | pick_nodes(N - 1, T, File, Line)];
723
755
pick_nodes(0, _Nodes, _File, _Line) ->
724
756
    [];
725
757
pick_nodes(N, [], File, Line) ->
726
758
    ?skip("Test case (~p(~p)) ignored: ~p nodes missing~n",
727
759
          [File, Line, N]).
728
 
   
 
760
 
729
761
init_nodes([Node | Nodes], File, Line) ->
730
762
    case net_adm:ping(Node) of
731
763
        pong ->
745
777
init_nodes([], _File, _Line) ->
746
778
    [].
747
779
 
748
 
%% Returns [Name, Host]    
 
780
%% Returns [Name, Host]
749
781
node_to_name_and_host(Node) ->
750
782
    string:tokens(atom_to_list(Node), [$@]).
751
783
 
761
793
 
762
794
start_appls(Appls, Nodes) ->
763
795
    start_appls(Appls, Nodes, [],  [schema]).
764
 
    
 
796
 
765
797
start_appls(Appls, Nodes, Config) ->
766
798
    start_appls(Appls, Nodes, Config, [schema]).
767
799
 
783
815
 
784
816
remote_start(mnesia, Config, Nodes) ->
785
817
    case diskless(Config) of
786
 
        true -> 
787
 
            application_controller:set_env(mnesia, 
788
 
                                           extra_db_nodes, 
 
818
        true ->
 
819
            application_controller:set_env(mnesia,
 
820
                                           extra_db_nodes,
789
821
                                           Nodes -- [node()]),
790
822
            application_controller:set_env(mnesia,
791
823
                                           schema_location,
798
830
    end,
799
831
    {node(), mnesia:start()};
800
832
remote_start(Appl, _Config, _Nodes) ->
801
 
    Res = 
 
833
    Res =
802
834
        case application:start(Appl) of
803
835
            {error, {already_started, Appl}} ->
804
836
                ok;
810
842
%% Start Mnesia on all given nodes and wait for specified
811
843
%% tables to be accessible on each node. The atom all means
812
844
%% that we should wait for all tables to be loaded
813
 
%% 
 
845
%%
814
846
%% Returns a list of error tuples {BadNode, mnesia, Reason}
815
847
start_mnesia(Nodes) ->
816
848
    start_appls([mnesia], Nodes).
817
849
start_mnesia(Nodes, Tabs) when is_list(Nodes) ->
818
850
    start_appls([mnesia], Nodes, [], Tabs).
819
 
    
 
851
 
820
852
%% Wait for the tables to be accessible from all nodes in the list
821
853
%% and that all nodes are aware of that the other nodes also ...
822
854
sync_tables(Nodes, Tabs) ->
892
924
        mnesia:table_info(Tab, ram_copies),
893
925
    Local = mnesia:table_info(Tab, local_content),
894
926
    case Copies -- Nodes of
895
 
        [] -> 
 
927
        [] ->
896
928
            verify_nodes(Tabs, 0);
897
929
        _Else when Local == true, Nodes /= [] ->
898
930
            verify_nodes(Tabs, 0);
899
931
        Else ->
900
 
            N2 = 
 
932
            N2 =
901
933
                if
902
 
                    N > 20 -> 
903
 
                        log("<>WARNING<> ~w Waiting for table: ~p on ~p ~n", 
 
934
                    N > 20 ->
 
935
                        log("<>WARNING<> ~w Waiting for table: ~p on ~p ~n",
904
936
                                 [node(), Tab, Else]),
905
937
                        0;
906
938
                    true -> N+1
907
 
                end,        
 
939
                end,
908
940
            timer:sleep(500),
909
941
            verify_nodes([Tab| Tabs], N2)
910
942
    end.
911
943
 
912
944
 
913
945
%% Nicely stop Mnesia on all given nodes
914
 
%% 
 
946
%%
915
947
%% Returns a list of error tuples {BadNode, Reason}
916
948
stop_mnesia(Nodes) when is_list(Nodes) ->
917
949
    stop_appls([mnesia], Nodes).
1015
1047
    Read = ignore_dead(DiscOnly ++ Ram ++ Disc, AliveNodes),
1016
1048
    This = node(),
1017
1049
 
1018
 
    timer:sleep(100), 
 
1050
    timer:sleep(100),
1019
1051
 
1020
1052
    S1 = ?match(AliveNodes, lists:sort(mnesia:system_info(running_db_nodes))),
1021
1053
    S2 = ?match(DiscOnly, lists:sort(mnesia:table_info(Tab, disc_only_copies))),
1048
1080
    timer:sleep(infinity).  % Dies whenever the test process dies !!
1049
1081
 
1050
1082
 
1051
 
sort(L) when is_list(L) -> 
 
1083
sort(L) when is_list(L) ->
1052
1084
    lists:sort(L);
1053
1085
sort({atomic, L}) when is_list(L) ->
1054
1086
    {atomic, lists:sort(L)};