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

« back to all changes in this revision

Viewing changes to lib/common_test/test/ct_config_info_SUITE.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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2009-2011. 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
%%% File: ct_config_info_SUITE
 
22
%%%
 
23
%%% Description: Test how Common Test handles info functions
 
24
%%% for the config functions.
 
25
%%%
 
26
%%%-------------------------------------------------------------------
 
27
-module(ct_config_info_SUITE).
 
28
 
 
29
-compile(export_all).
 
30
 
 
31
-include_lib("common_test/include/ct.hrl").
 
32
-include_lib("common_test/include/ct_event.hrl").
 
33
 
 
34
-define(eh, ct_test_support_eh).
 
35
 
 
36
%%--------------------------------------------------------------------
 
37
%% TEST SERVER CALLBACK FUNCTIONS
 
38
%%--------------------------------------------------------------------
 
39
 
 
40
%%--------------------------------------------------------------------
 
41
%% Description: Since Common Test starts another Test Server
 
42
%% instance, the tests need to be performed on a separate node (or
 
43
%% there will be clashes with logging processes etc).
 
44
%%--------------------------------------------------------------------
 
45
init_per_suite(Config) ->
 
46
    Config1 = ct_test_support:init_per_suite(Config),
 
47
    Config1.
 
48
 
 
49
end_per_suite(Config) ->
 
50
    ct_test_support:end_per_suite(Config).
 
51
 
 
52
init_per_testcase(TestCase, Config) ->
 
53
    ct_test_support:init_per_testcase(TestCase, Config).
 
54
 
 
55
end_per_testcase(TestCase, Config) ->
 
56
    ct_test_support:end_per_testcase(TestCase, Config).
 
57
 
 
58
suite() -> [{ct_hooks,[ts_install_cth]}].
 
59
 
 
60
all() -> 
 
61
    [
 
62
     config_info
 
63
    ].
 
64
 
 
65
%%--------------------------------------------------------------------
 
66
%% TEST CASES
 
67
%%--------------------------------------------------------------------
 
68
 
 
69
%%%-----------------------------------------------------------------
 
70
%%% 
 
71
config_info(Config) when is_list(Config) -> 
 
72
    DataDir = ?config(data_dir, Config),
 
73
    Suite = filename:join(DataDir, "config_info_1_SUITE"),
 
74
    {Opts,ERPid} = setup([{suite,Suite},
 
75
                          {label,config_info}], Config),
 
76
    ok = execute(config_info, Opts, ERPid, Config).
 
77
 
 
78
%%%-----------------------------------------------------------------
 
79
%%% HELP FUNCTIONS
 
80
%%%-----------------------------------------------------------------
 
81
 
 
82
setup(Test, Config) ->
 
83
    Opts0 = ct_test_support:get_opts(Config),
 
84
    Level = ?config(trace_level, Config),
 
85
    EvHArgs = [{cbm,ct_test_support},{trace_level,Level}],
 
86
    Opts = Opts0 ++ [{event_handler,{?eh,EvHArgs}}|Test],
 
87
    ERPid = ct_test_support:start_event_receiver(Config),
 
88
    {Opts,ERPid}.
 
89
 
 
90
execute(Name, Opts, ERPid, Config) ->
 
91
    ok = ct_test_support:run(Opts, Config),
 
92
    Events = ct_test_support:get_events(ERPid, Config),
 
93
 
 
94
    ct_test_support:log_events(Name, 
 
95
                               reformat(Events, ?eh),
 
96
                               ?config(priv_dir, Config),
 
97
                               Opts),
 
98
 
 
99
    TestEvents = events_to_check(Name),
 
100
    ct_test_support:verify_events(TestEvents, Events, Config).
 
101
 
 
102
reformat(Events, EH) ->
 
103
    ct_test_support:reformat(Events, EH).
 
104
 
 
105
%%%-----------------------------------------------------------------
 
106
%%% TEST EVENTS
 
107
%%%-----------------------------------------------------------------
 
108
events_to_check(Test) ->
 
109
    %% 2 tests (ct:run_test + script_start) is default
 
110
    events_to_check(Test, 2).
 
111
 
 
112
events_to_check(_, 0) ->
 
113
    [];
 
114
events_to_check(Test, N) ->
 
115
    test_events(Test) ++ events_to_check(Test, N-1).
 
116
 
 
117
 
 
118
test_events(config_info) ->
 
119
    [
 
120
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
121
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
122
     {?eh,start_info,{1,1,6}},
 
123
     {?eh,tc_done,{config_info_1_SUITE,init_per_suite,ok}},
 
124
 
 
125
     [{?eh,tc_start,{config_info_1_SUITE,{init_per_group,g1,[]}}},
 
126
      {?eh,tc_done,{config_info_1_SUITE,
 
127
                    {init_per_group,unknown,[]},
 
128
                    {failed,{timetrap_timeout,350}}}},
 
129
      {?eh,tc_auto_skip,{config_info_1_SUITE,t11,
 
130
        {failed,{config_info_1_SUITE,init_per_group,{timetrap_timeout,350}}}}},
 
131
      {?eh,tc_auto_skip,{config_info_1_SUITE,end_per_group,
 
132
                         {failed,{config_info_1_SUITE,init_per_group,
 
133
                                  {timetrap_timeout,350}}}}}],
 
134
 
 
135
     [{?eh,tc_start,{config_info_1_SUITE,{init_per_group,g2,[]}}},
 
136
      {?eh,tc_done,{config_info_1_SUITE,{init_per_group,g2,[]},ok}},
 
137
      {?eh,tc_done,{config_info_1_SUITE,t21,ok}},
 
138
      {?eh,tc_start,{config_info_1_SUITE,{end_per_group,g2,[]}}},
 
139
      {?eh,tc_done,{config_info_1_SUITE,
 
140
                    {end_per_group,unknown,[]},
 
141
                    {failed,{timetrap_timeout,450}}}}],
 
142
     [{?eh,tc_start,{config_info_1_SUITE,{init_per_group,g3,[]}}},
 
143
      {?eh,tc_done,{config_info_1_SUITE,{init_per_group,g3,[]},ok}},
 
144
      [{?eh,tc_start,{config_info_1_SUITE,{init_per_group,g4,[]}}},
 
145
       {?eh,tc_done,{config_info_1_SUITE,
 
146
                     {init_per_group,unknown,[]},
 
147
                     {failed,{timetrap_timeout,400}}}},
 
148
       {?eh,tc_auto_skip,{config_info_1_SUITE,t41,
 
149
         {failed,{config_info_1_SUITE,init_per_group,
 
150
                  {timetrap_timeout,400}}}}},
 
151
       {?eh,tc_auto_skip,{config_info_1_SUITE,end_per_group,
 
152
         {failed,{config_info_1_SUITE,init_per_group,
 
153
                  {timetrap_timeout,400}}}}}],
 
154
      {?eh,tc_start,{config_info_1_SUITE,t31}},
 
155
      {?eh,tc_done,{config_info_1_SUITE,t31,
 
156
                    {skipped,{failed,{config_info_1_SUITE,init_per_testcase,
 
157
                                      {timetrap_timeout,250}}}}}},
 
158
      {?eh,tc_start,{config_info_1_SUITE,t32}},
 
159
      {?eh,tc_done,{config_info_1_SUITE,t32,
 
160
                    {failed,{config_info_1_SUITE,end_per_testcase,
 
161
                             {timetrap_timeout,250}}}}},
 
162
 
 
163
      [{?eh,tc_start,{config_info_1_SUITE,{init_per_group,g5,[]}}},
 
164
       {?eh,tc_done,{config_info_1_SUITE,{init_per_group,g5,[]},ok}},
 
165
       {?eh,tc_done,{config_info_1_SUITE,t51,ok}},
 
166
       {?eh,tc_start,{config_info_1_SUITE,{end_per_group,g5,[]}}},
 
167
       {?eh,tc_done,{config_info_1_SUITE,
 
168
                     {end_per_group,unknown,[]},
 
169
                     {failed,{timetrap_timeout,400}}}}],
 
170
      {?eh,tc_start,{config_info_1_SUITE,{end_per_group,g3,[]}}},
 
171
      {?eh,tc_done,{config_info_1_SUITE,{end_per_group,g3,[]},ok}}],
 
172
 
 
173
     {?eh,tc_start,{config_info_1_SUITE,end_per_suite}},
 
174
     {?eh,tc_done,{config_info_1_SUITE,end_per_suite,
 
175
                   {failed,{timetrap_timeout,300}}}},
 
176
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
177
     {?eh,stop_logging,[]}
 
178
    ].