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

« back to all changes in this revision

Viewing changes to lib/common_test/test/ct_test_server_if_1_SUITE.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 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_test_server_if_SUITE
 
22
%%%
 
23
%%% Description: 
 
24
%%% Test the test_server -> framework interface.
 
25
%%%
 
26
%%% The suites used for the test are located in the data directory.
 
27
%%%-------------------------------------------------------------------
 
28
-module(ct_test_server_if_1_SUITE).
 
29
 
 
30
-compile(export_all).
 
31
 
 
32
-include_lib("common_test/include/ct.hrl").
 
33
-include_lib("common_test/include/ct_event.hrl").
 
34
 
 
35
-define(eh, ct_test_support_eh).
 
36
 
 
37
%%--------------------------------------------------------------------
 
38
%% TEST SERVER CALLBACK FUNCTIONS
 
39
%%--------------------------------------------------------------------
 
40
 
 
41
%%--------------------------------------------------------------------
 
42
%% Description: Since Common Test starts another Test Server
 
43
%% instance, the tests need to be performed on a separate node (or
 
44
%% there will be clashes with logging processes etc).
 
45
%%--------------------------------------------------------------------
 
46
init_per_suite(Config) ->
 
47
    Config1 = ct_test_support:init_per_suite(Config),
 
48
    Config1.
 
49
 
 
50
end_per_suite(Config) ->
 
51
    ct_test_support:end_per_suite(Config).
 
52
 
 
53
init_per_testcase(TestCase, Config) ->
 
54
    ct_test_support:init_per_testcase(TestCase, Config).
 
55
 
 
56
end_per_testcase(TestCase, Config) ->
 
57
    ct_test_support:end_per_testcase(TestCase, Config).
 
58
 
 
59
suite() -> [{ct_hooks,[ts_install_cth]}].
 
60
 
 
61
all() -> 
 
62
    [ts_if_1].
 
63
 
 
64
groups() -> 
 
65
    [].
 
66
 
 
67
init_per_group(_GroupName, Config) ->
 
68
        Config.
 
69
 
 
70
end_per_group(_GroupName, Config) ->
 
71
        Config.
 
72
 
 
73
     
 
74
 
 
75
%%--------------------------------------------------------------------
 
76
%% TEST CASES
 
77
%%--------------------------------------------------------------------
 
78
 
 
79
%%%-----------------------------------------------------------------
 
80
%%% 
 
81
ts_if_1(Config) when is_list(Config) -> 
 
82
    DataDir = ?config(data_dir, Config),
 
83
    PrivDir = ?config(priv_dir, Config),
 
84
    TODir = filename:join(DataDir, "test_server_if"),
 
85
    Level = ?config(trace_level, Config),
 
86
    TestSpec = [
 
87
                {event_handler,?eh,[{cbm,ct_test_support},{trace_level,Level}]},
 
88
                {suites,TODir,[ts_if_1_SUITE,ts_if_2_SUITE,ts_if_3_SUITE,
 
89
                               ts_if_4_SUITE,ts_if_5_SUITE,ts_if_6_SUITE,
 
90
                               ts_if_7_SUITE,ts_if_8_SUITE]},
 
91
                {skip_suites,TODir,[skipped_by_spec_1_SUITE],"should be skipped"},
 
92
                {skip_cases,TODir,skipped_by_spec_2_SUITE,[tc1],"should be skipped"}
 
93
               ],
 
94
 
 
95
    TestSpecName = ct_test_support:write_testspec(TestSpec, PrivDir, "ts_if_1_spec"),
 
96
    {Opts,ERPid} = setup({spec,TestSpecName}, Config),
 
97
    ok = ct_test_support:run(Opts, Config),
 
98
    Events = ct_test_support:get_events(ERPid, Config),
 
99
 
 
100
    ct_test_support:log_events(ts_if_1, 
 
101
                               reformat(Events, ?eh), 
 
102
                               PrivDir),
 
103
 
 
104
    TestEvents = events_to_check(ts_if_1),
 
105
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
106
        
 
107
 
 
108
%%%-----------------------------------------------------------------
 
109
%%% HELP FUNCTIONS
 
110
%%%-----------------------------------------------------------------
 
111
 
 
112
setup(Test, Config) ->
 
113
    Opts0 = ct_test_support:get_opts(Config),
 
114
%    Level = ?config(trace_level, Config),
 
115
%    EvHArgs = [{cbm,ct_test_support},{trace_level,Level}],
 
116
%    Opts = Opts0 ++ [Test,{event_handler,{?eh,EvHArgs}}],
 
117
    Opts = [Test | Opts0],
 
118
    ERPid = ct_test_support:start_event_receiver(Config),
 
119
    {Opts,ERPid}.
 
120
 
 
121
reformat(Events, EH) ->
 
122
    ct_test_support:reformat(Events, EH).
 
123
%reformat(Events, _EH) ->
 
124
%    Events.
 
125
 
 
126
%%%-----------------------------------------------------------------
 
127
%%% TEST EVENTS
 
128
%%%-----------------------------------------------------------------
 
129
events_to_check(Test) ->
 
130
    %% 2 tests (ct:run_test + script_start) is default
 
131
    events_to_check(Test, 2).
 
132
 
 
133
events_to_check(_, 0) ->
 
134
    [];
 
135
events_to_check(Test, N) ->
 
136
    test_events(Test) ++ events_to_check(Test, N-1).
 
137
 
 
138
test_events(ts_if_1) ->
 
139
    [
 
140
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
141
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
142
     {?eh,start_info,{10,6,26}},
 
143
     {?eh,tc_start,{ts_if_1_SUITE,init_per_suite}},
 
144
     {?eh,tc_done,{ts_if_1_SUITE,init_per_suite,ok}},
 
145
     {?eh,tc_start,{ts_if_1_SUITE,tc1}},
 
146
     {?eh,tc_done,{ts_if_1_SUITE,tc1,{skipped,
 
147
                                      {failed,
 
148
                                       {ts_if_1_SUITE,init_per_testcase,
 
149
                                        {timetrap_timeout,2000}}}}}},
 
150
     {?eh,test_stats,{0,0,{0,1}}},
 
151
     {?eh,tc_start,{ts_if_1_SUITE,tc2}},
 
152
     {?eh,tc_done,{ts_if_1_SUITE,tc2,
 
153
                   {failed,{ts_if_1_SUITE,end_per_testcase,{timetrap_timeout,2000}}}}},
 
154
     {?eh,test_stats,{1,0,{0,1}}},
 
155
     {?eh,tc_start,{ts_if_1_SUITE,tc3}},
 
156
     {?eh,tc_done,{ts_if_1_SUITE,tc3,{failed,{timetrap_timeout,2000}}}},
 
157
     {?eh,test_stats,{1,1,{0,1}}},
 
158
     {?eh,tc_start,{ts_if_1_SUITE,tc4}},
 
159
     {?eh,tc_done,{ts_if_1_SUITE,tc4,{failed,{error,failed_on_purpose}}}},
 
160
     {?eh,test_stats,{1,2,{0,1}}},
 
161
     {?eh,tc_done,{ts_if_1_SUITE,tc5,{skipped,{sequence_failed,seq1,tc4}}}},
 
162
     {?eh,test_stats,{1,2,{1,1}}},
 
163
 
 
164
     [{?eh,tc_start,{ts_if_1_SUITE,{init_per_group,seq2,[sequence]}}},
 
165
      {?eh,tc_done,{ts_if_1_SUITE,{init_per_group,seq2,[sequence]},ok}},
 
166
      {?eh,tc_start,{ts_if_1_SUITE,tc4}},
 
167
      {?eh,tc_done,{ts_if_1_SUITE,tc4,{failed,{error,failed_on_purpose}}}},
 
168
      {?eh,test_stats,{1,3,{1,1}}},
 
169
      {?eh,tc_auto_skip,{ts_if_1_SUITE,tc5,{failed,{ts_if_1_SUITE,tc4}}}},
 
170
      {?eh,test_stats,{1,3,{1,2}}},
 
171
      {?eh,tc_start,{ts_if_1_SUITE,{end_per_group,seq2,[sequence]}}},
 
172
      {?eh,tc_done,{ts_if_1_SUITE,{end_per_group,seq2,[sequence]},ok}}],
 
173
 
 
174
     {?eh,tc_start,{ts_if_1_SUITE,tc6}},
 
175
     {?eh,tc_done,{ts_if_1_SUITE,tc6,{skipped,{require_failed,{not_available,void}}}}},
 
176
     {?eh,test_stats,{1,3,{1,3}}},
 
177
     {?eh,tc_start,{ts_if_1_SUITE,tc7}},
 
178
     {?eh,tc_done,{ts_if_1_SUITE,tc7,ok}},
 
179
     {?eh,test_stats,{2,3,{1,3}}},
 
180
     {?eh,tc_start,{ts_if_1_SUITE,tc8}},
 
181
     {?eh,tc_done,{ts_if_1_SUITE,tc8,{skipped,"tc8 skipped"}}},
 
182
     {?eh,test_stats,{2,3,{2,3}}},
 
183
     {?eh,tc_start,{ts_if_1_SUITE,tc9}},
 
184
     {?eh,tc_done,{ts_if_1_SUITE,tc9,{skipped,'tc9 skipped'}}},
 
185
     {?eh,test_stats,{2,3,{3,3}}},
 
186
     {?eh,tc_start,{ts_if_1_SUITE,tc10}},
 
187
     {?eh,tc_done,{ts_if_1_SUITE,tc10,{failed,{error,{function_clause,'_'}}}}},
 
188
     {?eh,test_stats,{2,4,{3,3}}},
 
189
     {?eh,tc_start,{ts_if_1_SUITE,tc11}},
 
190
     {?eh,tc_done,{ts_if_1_SUITE,tc11,
 
191
                   {skipped,{failed,{ts_if_1_SUITE,init_per_testcase,bad_return}}}}},
 
192
     {?eh,test_stats,{2,4,{3,4}}},
 
193
 
 
194
     [{?eh,tc_start,{ts_if_1_SUITE,{init_per_group,g1,[]}}},
 
195
      {?eh,tc_done,{ts_if_1_SUITE,{init_per_group,g1,[]},{skipped,g1_got_skipped}}},
 
196
      {?eh,tc_auto_skip,{ts_if_1_SUITE,gtc1,g1_got_skipped}},
 
197
      {?eh,test_stats,{2,4,{3,5}}},
 
198
      {?eh,tc_auto_skip,{ts_if_1_SUITE,end_per_group,g1_got_skipped}}],
 
199
 
 
200
     {parallel,
 
201
      [{?eh,tc_start,{ts_if_1_SUITE,{init_per_group,g2,[parallel]}}},
 
202
       {?eh,tc_done,{ts_if_1_SUITE,{init_per_group,g2,[parallel]},ok}},
 
203
       [{?eh,tc_start,{ts_if_1_SUITE,{init_per_group,g3,[]}}},
 
204
        {?eh,tc_done,{ts_if_1_SUITE,{init_per_group,g3,[]},{skipped,g3_got_skipped}}},
 
205
        {?eh,tc_auto_skip,{ts_if_1_SUITE,gtc2,g3_got_skipped}},
 
206
        {?eh,test_stats,{2,4,{3,6}}},
 
207
        {?eh,tc_auto_skip,{ts_if_1_SUITE,end_per_group,g3_got_skipped}}],
 
208
       {?eh,tc_start,{ts_if_1_SUITE,{end_per_group,g2,[parallel]}}},
 
209
       {?eh,tc_done,{ts_if_1_SUITE,{end_per_group,g2,[parallel]},ok}}]},
 
210
 
 
211
     {?eh,tc_start,{ts_if_1_SUITE,tc12}},
 
212
     {?eh,tc_done,{ts_if_1_SUITE,tc12,{failed,{testcase_aborted,'stopping tc12'}}}},
 
213
     {?eh,test_stats,{2,5,{3,6}}},
 
214
     {?eh,tc_start,{ts_if_1_SUITE,tc13}},
 
215
     {?eh,tc_done,{ts_if_1_SUITE,tc13,ok}},
 
216
     {?eh,test_stats,{3,5,{3,6}}},
 
217
     {?eh,tc_start,{ts_if_1_SUITE,end_per_suite}},
 
218
     {?eh,tc_done,{ts_if_1_SUITE,end_per_suite,ok}},
 
219
 
 
220
     {?eh,tc_start,{ts_if_2_SUITE,init_per_suite}},
 
221
     {?eh,tc_done,{ts_if_2_SUITE,init_per_suite,
 
222
                   {failed,{error,{suite0_failed,{exited,suite0_goes_boom}}}}}},
 
223
     {?eh,tc_auto_skip,{ts_if_2_SUITE,my_test_case,
 
224
                        {failed,{error,{suite0_failed,{exited,suite0_goes_boom}}}}}},
 
225
     {?eh,test_stats,{3,5,{3,7}}},
 
226
     {?eh,tc_auto_skip,{ts_if_2_SUITE,end_per_suite,
 
227
                        {failed,{error,{suite0_failed,{exited,suite0_goes_boom}}}}}},
 
228
 
 
229
     {?eh,tc_start,{ct_framework,error_in_suite}},
 
230
     {?eh,test_stats,{3,6,{3,7}}},
 
231
 
 
232
     {?eh,tc_start,{ct_framework,error_in_suite}},
 
233
     {?eh,test_stats,{3,7,{3,7}}},
 
234
 
 
235
     {?eh,tc_start,{ts_if_5_SUITE,init_per_suite}},
 
236
     {?eh,tc_done,{ts_if_5_SUITE,init_per_suite,
 
237
                   {skipped,{require_failed_in_suite0,{not_available,undef_variable}}}}},
 
238
     {?eh,tc_auto_skip,{ts_if_5_SUITE,my_test_case,
 
239
                        {require_failed_in_suite0,{not_available,undef_variable}}}},
 
240
     {?eh,test_stats,{3,7,{3,8}}},
 
241
     {?eh,tc_auto_skip,{ts_if_5_SUITE,end_per_suite,
 
242
                        {require_failed_in_suite0,{not_available,undef_variable}}}},
 
243
 
 
244
     {?eh,tc_start,{ts_if_6_SUITE,tc1}},
 
245
     {?eh,tc_done,{ts_if_6_SUITE,tc1,{failed,{error,{suite0_failed,{exited,suite0_byebye}}}}}},
 
246
     {?eh,test_stats,{3,7,{4,8}}},
 
247
 
 
248
     {?eh,tc_start,{ts_if_7_SUITE,tc1}},
 
249
     {?eh,tc_done,{ts_if_7_SUITE,tc1,ok}},
 
250
     {?eh,test_stats,{4,7,{4,8}}},
 
251
 
 
252
     {?eh,tc_start,{ts_if_8_SUITE,tc1}},
 
253
     {?eh,tc_done,{ts_if_8_SUITE,tc1,{failed,{error,failed_on_purpose}}}},
 
254
     {?eh,test_stats,{4,8,{4,8}}},
 
255
 
 
256
     {?eh,tc_user_skip,{skipped_by_spec_1_SUITE,all,"should be skipped"}},
 
257
     {?eh,test_stats,{4,8,{5,8}}},
 
258
 
 
259
     {?eh,tc_start,{skipped_by_spec_2_SUITE,init_per_suite}},
 
260
     {?eh,tc_done,{skipped_by_spec_2_SUITE,init_per_suite,ok}},
 
261
     {?eh,tc_user_skip,{skipped_by_spec_2_SUITE,tc1,"should be skipped"}},
 
262
     {?eh,test_stats,{4,8,{6,8}}},
 
263
     {?eh,tc_start,{skipped_by_spec_2_SUITE,end_per_suite}},
 
264
     {?eh,tc_done,{skipped_by_spec_2_SUITE,end_per_suite,ok}},
 
265
 
 
266
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
267
     {?eh,stop_logging,[]}
 
268
    ].
 
269