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

« back to all changes in this revision

Viewing changes to lib/common_test/test/ct_misc_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 2010-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_misc_1_SUITE
 
22
%%%
 
23
%%% Description:
 
24
%%% Test misc things in Common Test suites.
 
25
%%%
 
26
%%% The suites used for the test are located in the data directory.
 
27
%%%-------------------------------------------------------------------
 
28
-module(ct_misc_1_SUITE).
 
29
 
 
30
-compile(export_all).
 
31
 
 
32
-include_lib("common_test/include/ct.hrl").
 
33
-include_lib("test_server/include/test_server_line.hrl").
 
34
-include_lib("common_test/include/ct_event.hrl").
 
35
 
 
36
-define(eh, ct_test_support_eh).
 
37
 
 
38
%%--------------------------------------------------------------------
 
39
%% TEST SERVER CALLBACK FUNCTIONS
 
40
%%--------------------------------------------------------------------
 
41
 
 
42
%%--------------------------------------------------------------------
 
43
%% Description: Since Common Test starts another Test Server
 
44
%% instance, the tests need to be performed on a separate node (or
 
45
%% there will be clashes with logging processes etc).
 
46
%%--------------------------------------------------------------------
 
47
init_per_suite(Config) ->
 
48
    Config1 = ct_test_support:init_per_suite(Config),
 
49
    Config1.
 
50
 
 
51
end_per_suite(Config) ->
 
52
    ct_test_support:end_per_suite(Config).
 
53
 
 
54
init_per_testcase(TestCase, Config) ->
 
55
    ct_test_support:init_per_testcase(TestCase, Config).
 
56
 
 
57
end_per_testcase(TestCase, Config) ->
 
58
    ct_test_support:end_per_testcase(TestCase, Config).
 
59
 
 
60
suite() -> [{ct_hooks,[ts_install_cth]}].
 
61
 
 
62
all() -> 
 
63
    [beam_me_up, {group,parse_table}].
 
64
 
 
65
groups() -> 
 
66
    [{parse_table,[parallel], 
 
67
      [parse_table_empty, parse_table_single,
 
68
       parse_table_multiline_row,
 
69
       parse_table_one_column_multiline,
 
70
       parse_table_one_column_simple]}].
 
71
 
 
72
init_per_group(_GroupName, Config) ->
 
73
        Config.
 
74
 
 
75
end_per_group(_GroupName, Config) ->
 
76
        Config.
 
77
 
 
78
%%--------------------------------------------------------------------
 
79
%% TEST CASES
 
80
%%--------------------------------------------------------------------
 
81
 
 
82
%%%-----------------------------------------------------------------
 
83
%%%
 
84
beam_me_up(Config) when is_list(Config) ->
 
85
    DataDir = ?config(data_dir, Config),
 
86
    CTNode = ?config(ct_node, Config),
 
87
 
 
88
    %% Path = rpc:call(CTNode, code, get_path, []),
 
89
    %% [_ | Parts] = lists:reverse(filename:split(DataDir)),
 
90
    %% TSDir = filename:join(lists:reverse(Parts)),
 
91
    %% true = rpc:call(CTNode, code, del_path, [TSDir]),
 
92
 
 
93
    Mods = [beam_1_SUITE, beam_2_SUITE],
 
94
    Suites = [atom_to_list(M) || M <- Mods],
 
95
    [{error,_} = rpc:call(CTNode, code, load_file, [M]) || M <- Mods],
 
96
 
 
97
    code:add_path(DataDir),
 
98
    CRes =
 
99
        [compile:file(filename:join(DataDir,F),
 
100
                      [verbose,report_errors,
 
101
                       report_warnings,binary]) || F <- Suites],
 
102
 
 
103
    [{module,_} = rpc:call(CTNode, code, load_binary,
 
104
                           [Mod, atom_to_list(Mod), Bin]) ||
 
105
        {ok,Mod,Bin} <- CRes],
 
106
 
 
107
    {Opts,ERPid} = setup([{suite,Suites},{auto_compile,false}], Config),
 
108
 
 
109
    ok = ct_test_support:run(ct, run_test, [Opts], Config),
 
110
    Events = ct_test_support:get_events(ERPid, Config),
 
111
 
 
112
    ct_test_support:log_events(beam_me_up,
 
113
                               reformat(Events, ?eh),
 
114
                               ?config(priv_dir, Config)),
 
115
 
 
116
    TestEvents = events_to_check(beam_me_up, 1),
 
117
    ok = ct_test_support:verify_events(TestEvents, Events, Config).
 
118
 
 
119
parse_table_empty(Config) when is_list(Config) ->
 
120
 
 
121
    String = ["+----+-------+---------+---------+----------+------+--------+",
 
122
              "| id | col11 | col2222 | col3333 | col4     | col5 | col6666 |",
 
123
              "+----+-------+---------+---------+----------+------+--------+",
 
124
              "+----+-------+---------+---------+----------+------+--------+",
 
125
              "Query Done: 0 records selected"],
 
126
 
 
127
    {{"id","col11","col2222","col3333","col4","col5","col6666"},[]} =
 
128
        ct:parse_table(String).
 
129
 
 
130
 
 
131
parse_table_single(Config) when is_list(Config) ->
 
132
 
 
133
    String = ["+------+--------+--------------+------------+------------------+---------+--------+---------+-----------+",
 
134
              "| id | col1 | col2 | col3 | col4 | col5 | col6 | col7 | col8 |",
 
135
"+------+--------+--------------+------------+------------------+---------+--------+---------+-----------+",
 
136
              "| 0 | 0 | -1407231560 | -256 | -1407231489 | 1500 | 1 | 1 | 1 |",
 
137
              "+------+--------+--------------+------------+------------------+---------+--------+---------+-----------+"
 
138
              "Query Done: 1 record selected"],
 
139
 
 
140
    {{"id","col1","col2","col3","col4","col5","col6","col7","col8"},
 
141
     [{"0","0","-1407231560","-256","-1407231489", "1500","1","1","1"}]} =
 
142
        ct:parse_table(String).
 
143
 
 
144
parse_table_multiline_row(Config) when is_list(Config) ->
 
145
    
 
146
    String = ["+------+--------+--------------+------------+------------------+---------+--------+---------+-----------+",
 
147
              "| id | col1 | col2 | col3 | col4 | col5 | col6 | col7 | col8 |",
 
148
"+------+--------+--------------+------------+------------------+---------+--------+---------+-----------+",
 
149
              "| 0 | 0 | Free test string",
 
150
              " on more lines",
 
151
              "than one",
 
152
              "| -256 | -1407231489 | 1500 | 1 | 1 | 1 |",
 
153
              "+------+--------+--------------+------------+------------------+---------+--------+---------+-----------+"
 
154
              "Query Done: 1 record selected"],
 
155
 
 
156
    {{"id","col1","col2","col3","col4","col5","col6","col7","col8"},
 
157
     [{"0","0","Free test string\n on more lines\nthan one\n",
 
158
       "-256","-1407231489", "1500","1","1","1"}]} =
 
159
        ct:parse_table(String).
 
160
 
 
161
parse_table_one_column_simple(Config) when is_list(Config) ->
 
162
 
 
163
    String = ["|test|","|test value|"],
 
164
 
 
165
    {{"test"},[{"test value"}]} = ct:parse_table(String).
 
166
 
 
167
parse_table_one_column_multiline(Config) when is_list(Config) ->
 
168
    String = ["|test|","|test","value|"],
 
169
 
 
170
    {{"test"},[{"test\nvalue"}]} = ct:parse_table(String).
 
171
        
 
172
%%%-----------------------------------------------------------------
 
173
%%% HELP FUNCTIONS
 
174
%%%-----------------------------------------------------------------
 
175
 
 
176
setup(Test, Config) ->
 
177
    Opts0 = ct_test_support:get_opts(Config),
 
178
    Level = ?config(trace_level, Config),
 
179
    EvHArgs = [{cbm,ct_test_support},{trace_level,Level}],
 
180
    Opts = Opts0 ++ [{event_handler,{?eh,EvHArgs}}|Test],
 
181
    ERPid = ct_test_support:start_event_receiver(Config),
 
182
    {Opts,ERPid}.
 
183
 
 
184
reformat(Events, EH) ->
 
185
    ct_test_support:reformat(Events, EH).
 
186
%reformat(Events, _EH) ->
 
187
%    Events.
 
188
 
 
189
%%%-----------------------------------------------------------------
 
190
%%% TEST EVENTS
 
191
%%%-----------------------------------------------------------------
 
192
events_to_check(Test) ->
 
193
    %% 2 tests (ct:run_test + script_start) is default
 
194
    events_to_check(Test, 2).
 
195
 
 
196
events_to_check(_, 0) ->
 
197
    [];
 
198
events_to_check(Test, N) ->
 
199
    test_events(Test) ++ events_to_check(Test, N-1).
 
200
 
 
201
test_events(beam_me_up) ->
 
202
    [
 
203
     {?eh,start_logging,{'DEF','RUNDIR'}},
 
204
     {?eh,test_start,{'DEF',{'START_TIME','LOGDIR'}}},
 
205
     {?eh,start_info,{2,2,4}},
 
206
     {?eh,tc_start,{beam_1_SUITE,init_per_suite}},
 
207
     {?eh,tc_done,{beam_1_SUITE,init_per_suite,ok}},
 
208
     {?eh,tc_start,{beam_1_SUITE,tc1}},
 
209
     {?eh,tc_done,{beam_1_SUITE,tc1,ok}},
 
210
     {?eh,test_stats,{1,0,{0,0}}},
 
211
     {?eh,tc_start,{beam_1_SUITE,tc2}},
 
212
     {?eh,tc_done,{beam_1_SUITE,tc2,{failed,{error,'tc2 failed'}}}},
 
213
     {?eh,test_stats,{1,1,{0,0}}},
 
214
     {?eh,tc_start,{beam_1_SUITE,end_per_suite}},
 
215
     {?eh,tc_done,{beam_1_SUITE,end_per_suite,ok}},
 
216
     {?eh,tc_start,{beam_2_SUITE,init_per_suite}},
 
217
     {?eh,tc_done,{beam_2_SUITE,init_per_suite,ok}},
 
218
     {?eh,tc_start,{beam_2_SUITE,tc1}},
 
219
     {?eh,tc_done,{beam_2_SUITE,tc1,ok}},
 
220
     {?eh,test_stats,{2,1,{0,0}}},
 
221
     {?eh,tc_start,{beam_2_SUITE,tc2}},
 
222
     {?eh,tc_done,{beam_2_SUITE,tc2,{failed,{error,'tc2 failed'}}}},
 
223
     {?eh,test_stats,{2,2,{0,0}}},
 
224
     {?eh,tc_start,{beam_2_SUITE,end_per_suite}},
 
225
     {?eh,tc_done,{beam_2_SUITE,end_per_suite,ok}},
 
226
     {?eh,test_done,{'DEF','STOP_TIME'}},
 
227
     {?eh,stop_logging,[]}
 
228
    ].