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

« back to all changes in this revision

Viewing changes to lib/common_test/src/ct.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 2003-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2003-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
63
63
         log/1, log/2, log/3,
64
64
         print/1, print/2, print/3,
65
65
         pal/1, pal/2, pal/3,
66
 
         fail/1, comment/1,
 
66
         capture_start/0, capture_stop/0, capture_get/0, capture_get/1,
 
67
         fail/1, fail/2, comment/1, comment/2,
67
68
         testcases/2, userdata/2, userdata/3,
68
 
         timetrap/1, sleep/1]).
 
69
         timetrap/1, get_timetrap_info/0, sleep/1]).
69
70
 
70
71
%% New API for manipulating with config handlers
71
72
-export([add_config/2, remove_config/2]).
108
109
%%%   Cases = atom() | [atom()]
109
110
%%%   Result = [TestResult] | {error,Reason}
110
111
%%%
111
 
%%% @doc Run the given testcase(s).
 
112
%%% @doc Run the given test case(s).
112
113
%%%
113
114
%%% <p>Requires that <code>ct:install/1</code> has been run first.</p>
114
115
%%%
121
122
%%%-----------------------------------------------------------------
122
123
%%% @spec run(TestDir,Suite) -> Result
123
124
%%%
124
 
%%% @doc Run all testcases in the given suite.
 
125
%%% @doc Run all test cases in the given suite.
125
126
%%% @see run/3.
126
127
run(TestDir,Suite) ->
127
128
    ct_run:run(TestDir,Suite).
130
131
%%% @spec run(TestDirs) -> Result
131
132
%%%   TestDirs = TestDir | [TestDir]
132
133
%%%
133
 
%%% @doc Run all testcases in all suites in the given directories.
 
134
%%% @doc Run all test cases in all suites in the given directories.
134
135
%%% @see run/3.
135
136
run(TestDirs) ->
136
137
    ct_run:run(TestDirs).
148
149
%%%               {auto_compile,Bool} | {multiply_timetraps,M} | {scale_timetraps,Bool} |
149
150
%%%               {repeat,N} | {duration,DurTime} | {until,StopTime} |
150
151
%%%               {force_stop,Bool} | {decrypt,DecryptKeyOrFile} |
151
 
%%%               {refresh_logs,LogDir} | {basic_html,Bool}
 
152
%%%               {refresh_logs,LogDir} | {logopts,LogOpts} | {basic_html,Bool} | 
 
153
%%%               {ct_hooks, CTHs} | {enable_builtin_hooks,Bool}
152
154
%%%   TestDirs = [string()] | string()
153
 
%%%   Suites = [string()] | string()
 
155
%%%   Suites = [string()] | [atom()] | string() | atom()
154
156
%%%   Cases = [atom()] | atom()
155
157
%%%   Groups = [atom()] | atom()
156
158
%%%   TestSpecs = [string()] | string()
176
178
%%%   DecryptKeyOrFile = {key,DecryptKey} | {file,DecryptFile}
177
179
%%%   DecryptKey = string()
178
180
%%%   DecryptFile = string()
 
181
%%%   LogOpts = [LogOpt]
 
182
%%%   LogOpt = no_nl | no_src
 
183
%%%   CTHs = [CTHModule | {CTHModule, CTHInitArgs}]
 
184
%%%   CTHModule = atom()
 
185
%%%   CTHInitArgs = term()
179
186
%%%   Result = [TestResult] | {error,Reason}
180
187
%%% @doc Run tests as specified by the combination of options in <code>Opts</code>.
181
188
%%% The options are the same as those used with the
434
441
%%%      Format = string()
435
442
%%%      Args = list()
436
443
%%%
437
 
%%% @doc Printout from a testcase to the log. 
 
444
%%% @doc Printout from a test case to the log file. 
438
445
%%%
439
 
%%% <p>This function is meant for printing stuff directly from a
440
 
%%% testcase (i.e. not from within the CT framework) in the test
441
 
%%% log.</p>
 
446
%%% <p>This function is meant for printing a string directly from a
 
447
%%% test case to the test case log file.</p>
442
448
%%%
443
449
%%% <p>Default <code>Category</code> is <code>default</code> and
444
450
%%% default <code>Args</code> is <code>[]</code>.</p>
467
473
%%%      Format = string()
468
474
%%%      Args = list()
469
475
%%%
470
 
%%% @doc Printout from a testcase to the console. 
 
476
%%% @doc Printout from a test case to the console. 
471
477
%%%
472
 
%%% <p>This function is meant for printing stuff from a testcase on
473
 
%%% the console.</p>
 
478
%%% <p>This function is meant for printing a string from a test case
 
479
%%% to the console.</p>
474
480
%%%
475
481
%%% <p>Default <code>Category</code> is <code>default</code> and
476
482
%%% default <code>Args</code> is <code>[]</code>.</p>
502
508
%%%      Format = string()
503
509
%%%      Args = list()
504
510
%%%
505
 
%%% @doc Print and log from a testcase. 
 
511
%%% @doc Print and log from a test case. 
506
512
%%%
507
 
%%% <p>This function is meant for printing stuff from a testcase both
508
 
%%% in the log and on the console.</p>
 
513
%%% <p>This function is meant for printing a string from a test case,
 
514
%%% both to the test case log file and to the console.</p>
509
515
%%%
510
516
%%% <p>Default <code>Category</code> is <code>default</code> and
511
517
%%% default <code>Args</code> is <code>[]</code>.</p>
512
518
pal(Category,Format,Args) ->
513
519
    ct_logs:tc_pal(Category,Format,Args).
514
520
 
 
521
%%%-----------------------------------------------------------------
 
522
%%% @spec capture_start() -> ok
 
523
%%%
 
524
%%% @doc Start capturing all text strings printed to stdout during
 
525
%%% execution of the test case.
 
526
%%%
 
527
%%% @see capture_stop/0
 
528
%%% @see capture_get/1
 
529
capture_start() ->
 
530
    test_server:capture_start().
 
531
 
 
532
%%%-----------------------------------------------------------------
 
533
%%% @spec capture_stop() -> ok
 
534
%%%
 
535
%%% @doc Stop capturing text strings (a session started with
 
536
%%% <code>capture_start/0</code>).
 
537
%%%
 
538
%%% @see capture_start/0
 
539
%%% @see capture_get/1
 
540
capture_stop() ->
 
541
    test_server:capture_stop().
 
542
 
 
543
%%%-----------------------------------------------------------------
 
544
%%% @spec capture_get() -> ListOfStrings
 
545
%%%      ListOfStrings = [string()]
 
546
%%%
 
547
%%% @equiv capture_get([default])
 
548
capture_get() ->
 
549
    %% remove default log printouts (e.g. ct:log/2 printouts)
 
550
    capture_get([default]).
 
551
 
 
552
%%%-----------------------------------------------------------------
 
553
%%% @spec capture_get(ExclCategories) -> ListOfStrings
 
554
%%%      ExclCategories = [atom()]
 
555
%%%      ListOfStrings = [string()]
 
556
%%%
 
557
%%% @doc Return and purge the list of text strings buffered
 
558
%%% during the latest session of capturing printouts to stdout.
 
559
%%% With <code>ExclCategories</code> it's possible to specify
 
560
%%% log categories that should be ignored in <code>ListOfStrings</code>.
 
561
%%% If <code>ExclCategories = []</code>, no filtering takes place.
 
562
%%%
 
563
%%% @see capture_start/0
 
564
%%% @see capture_stop/0
 
565
%%% @see log/3
 
566
capture_get([ExclCat | ExclCategories]) ->
 
567
    Strs = test_server:capture_get(),
 
568
    CatsStr = [atom_to_list(ExclCat) | 
 
569
               [[$| | atom_to_list(EC)] || EC <- ExclCategories]],
 
570
    {ok,MP} = re:compile("<div class=\"(" ++ lists:flatten(CatsStr) ++ ")\">.*"),
 
571
    lists:flatmap(fun(Str) ->
 
572
                          case re:run(Str, MP) of
 
573
                              {match,_} -> [];
 
574
                              nomatch -> [Str]
 
575
                          end
 
576
                  end, Strs);
 
577
 
 
578
capture_get([]) ->
 
579
    test_server:capture_get().
515
580
 
516
581
%%%-----------------------------------------------------------------
517
582
%%% @spec fail(Reason) -> void()
522
587
fail(Reason) ->
523
588
    exit({test_case_failed,Reason}).
524
589
 
 
590
 
 
591
%%%-----------------------------------------------------------------
 
592
%%% @spec fail(Format, Args) -> void()
 
593
%%%      Format = string()
 
594
%%%      Args = list()
 
595
%%%
 
596
%%% @doc Terminate a test case with an error message specified
 
597
%%% by a format string and a list of values (used as arguments to
 
598
%%% <code>io_lib:format/2</code>).
 
599
fail(Format, Args) ->
 
600
    try io_lib:format(Format, Args) of
 
601
        Str ->
 
602
            exit({test_case_failed,lists:flatten(Str)})
 
603
    catch
 
604
        _:BadArgs ->
 
605
            exit({BadArgs,{?MODULE,fail,[Format,Args]}})
 
606
    end.
 
607
 
 
608
 
525
609
%%%-----------------------------------------------------------------
526
610
%%% @spec comment(Comment) -> void()
527
611
%%%      Comment = term()
528
612
%%%
529
 
%%% @doc Print the given <code>Comment</code> in the comment field of
 
613
%%% @doc Print the given <code>Comment</code> in the comment field in
530
614
%%% the table on the test suite result page.
531
615
%%%
532
616
%%% <p>If called several times, only the last comment is printed.
533
 
%%% <code>comment/1</code> is also overwritten by the return value
534
 
%%% <code>{comment,Comment}</code> or by the function
535
 
%%% <code>fail/1</code> (which prints <code>Reason</code> as a
536
 
%%% comment).</p>
 
617
%%% The test case return value <code>{comment,Comment}</code>
 
618
%%% overwrites the string set by this function.</p>
537
619
comment(Comment) when is_list(Comment) ->
538
620
    Formatted =
539
621
        case (catch io_lib:format("~s",[Comment])) of
547
629
    Formatted = io_lib:format("~p",[Comment]),
548
630
    send_html_comment(lists:flatten(Formatted)).
549
631
 
 
632
%%%-----------------------------------------------------------------
 
633
%%% @spec comment(Format, Args) -> void()
 
634
%%%      Format = string()
 
635
%%%      Args = list()
 
636
%%%
 
637
%%% @doc Print the formatted string in the comment field in
 
638
%%% the table on the test suite result page.
 
639
%%% 
 
640
%%% <p>The <code>Format</code> and <code>Args</code> arguments are
 
641
%%% used in call to <code>io_lib:format/2</code> in order to create
 
642
%%% the comment string. The behaviour of <code>comment/2</code> is
 
643
%%% otherwise the same as the <code>comment/1</code> function (see
 
644
%%% above for details).</p>
 
645
comment(Format, Args) when is_list(Format), is_list(Args) ->
 
646
    Formatted =
 
647
        case (catch io_lib:format(Format, Args)) of
 
648
            {'EXIT',Reason} ->  % bad args
 
649
                exit({Reason,{?MODULE,comment,[Format,Args]}});
 
650
            String ->
 
651
                lists:flatten(String)
 
652
        end,
 
653
    send_html_comment(Formatted).
 
654
 
550
655
send_html_comment(Comment) ->
551
656
    Html = "<font color=\"green\">" ++ Comment ++ "</font>",
552
657
    ct_util:set_testdata({comment,Html}),
600
705
%%%       Testcases = list()
601
706
%%%       Reason = term()
602
707
%%%
603
 
%%% @doc Returns all testcases in the specified suite.
 
708
%%% @doc Returns all test cases in the specified suite.
604
709
testcases(TestDir, Suite) ->
605
710
    case make_and_load(TestDir, Suite) of
606
711
        E = {error,_} ->
658
763
            get_userdata(Info, "suite/0")
659
764
    end.
660
765
 
661
 
get_userdata({'EXIT',{undef,_}}, Spec) ->
 
766
get_userdata({'EXIT',{Undef,_}}, Spec) when Undef == undef;
 
767
                                             Undef == function_clause ->
662
768
    {error,list_to_atom(Spec ++ " is not defined")};
663
769
get_userdata({'EXIT',Reason}, Spec) ->
664
770
    {error,{list_to_atom("error in " ++ Spec),Reason}};
674
780
    {error,list_to_atom(Spec ++ " must return a list")}.
675
781
   
676
782
%%%-----------------------------------------------------------------
677
 
%%% @spec userdata(TestDir, Suite, Case) -> TCUserData | {error,Reason}
 
783
%%% @spec userdata(TestDir, Suite, GroupOrCase) -> TCUserData | {error,Reason}
678
784
%%%       TestDir = string()
679
785
%%%       Suite = atom()
680
 
%%%       Case = atom()
 
786
%%%       GroupOrCase = {group,GroupName} | atom()
 
787
%%%       GroupName = atom()
681
788
%%%       TCUserData = [term()]
682
789
%%%       Reason = term()
683
790
%%%
684
791
%%% @doc Returns any data specified with the tag <code>userdata</code>
685
 
%%% in the list of tuples returned from <code>Suite:Case/0</code>.
686
 
userdata(TestDir, Suite, Case) ->
 
792
%%% in the list of tuples returned from <code>Suite:group(GroupName)</code>
 
793
%%% or <code>Suite:Case()</code>.
 
794
userdata(TestDir, Suite, {group,GroupName}) ->
 
795
    case make_and_load(TestDir, Suite) of
 
796
        E = {error,_} ->
 
797
            E;
 
798
        _ ->
 
799
            Info = (catch apply(Suite, group, [GroupName])),
 
800
            get_userdata(Info, "group("++atom_to_list(GroupName)++")")
 
801
    end;
 
802
 
 
803
userdata(TestDir, Suite, Case) when is_atom(Case) ->
687
804
    case make_and_load(TestDir, Suite) of
688
805
        E = {error,_} ->
689
806
            E;
857
974
%%%
858
975
%%% @doc <p>Use this function to set a new timetrap for the running test case.</p>
859
976
timetrap(Time) ->
 
977
    test_server:timetrap_cancel(),
860
978
    test_server:timetrap(Time).
861
979
 
862
980
%%%-----------------------------------------------------------------
 
981
%%% @spec get_timetrap_info() -> {Time,Scale}
 
982
%%%       Time = integer() | infinity
 
983
%%%       Scale = true | false
 
984
%%%
 
985
%%% @doc <p>Read info about the timetrap set for the current test case.
 
986
%%%      <c>Scale</c> indicates if Common Test will attempt to automatically
 
987
%%%      compensate timetraps for runtime delays introduced by e.g. tools like
 
988
%%%      cover.</p>
 
989
get_timetrap_info() ->
 
990
    test_server:get_timetrap_info().
 
991
 
 
992
%%%-----------------------------------------------------------------
863
993
%%% @spec sleep(Time) -> ok
864
994
%%%       Time = {hours,Hours} | {minutes,Mins} | {seconds,Secs} | Millisecs | infinity
865
995
%%%       Hours = integer()