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

« back to all changes in this revision

Viewing changes to lib/ic/test/erl_client_c_server_proto_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 2004-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
%%----------------------------------------------------------------------
 
22
%% Purpose : Test suite for erl-client/c-server
 
23
%%----------------------------------------------------------------------
 
24
 
 
25
 
 
26
-module(erl_client_c_server_proto_SUITE).
 
27
-include_lib("common_test/include/ct.hrl").
 
28
 
 
29
-export([init_per_testcase/2, end_per_testcase/2,all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, void_test/1,
 
30
         long_test/1, longlong_test/1, ushort_test/1, ulong_test/1,
 
31
         ulonglong_test/1, double_test/1, char_test/1, wchar_test/1,
 
32
         octet_test/1, bool_test/1, struct_test/1, struct2_test/1,
 
33
         seq1_test/1, seq2_test/1, seq3_test/1, seq4_test/1,
 
34
         seq5_test/1, array1_test/1, array2_test/1, enum_test/1,
 
35
         string1_test/1, string2_test/1, string3_test/1,
 
36
         string4_test/1, pid_test/1, port_test/1, ref_test/1,
 
37
         term_test/1, typedef_test/1, inline_sequence_test/1,
 
38
         term_sequence_test/1, term_struct_test/1, wstring1_test/1]).
 
39
 
 
40
-define(DEFAULT_TIMEOUT, 20000).
 
41
-define(PORT_TIMEOUT, 15000).
 
42
-define(CALL_TIMEOUT, 5000).
 
43
 
 
44
-define(C_SERVER_NODE_NAME, idl_c_server_test).
 
45
  
 
46
%% Add/remove code path and watchdog before/after each test case.
 
47
%%
 
48
init_per_testcase(_Case, Config) ->
 
49
    DataDir = ?config(data_dir, Config),
 
50
    code:add_patha(DataDir),
 
51
 
 
52
    %% Since other test suites use the module m_i, we have
 
53
    %% to make sure we are using the right m_i module.
 
54
    code:purge(m_i),
 
55
    code:load_file(m_i),
 
56
 
 
57
    WatchDog = test_server:timetrap(?DEFAULT_TIMEOUT),
 
58
    [{watchdog, WatchDog}| Config].
 
59
 
 
60
end_per_testcase(_Case, Config) ->
 
61
    DataDir = ?config(data_dir, Config),
 
62
    code:del_path(DataDir),
 
63
    WatchDog = ?config(watchdog, Config),
 
64
    test_server:timetrap_cancel(WatchDog).
 
65
 
 
66
suite() -> [{ct_hooks,[ts_install_cth]}].
 
67
 
 
68
all() -> 
 
69
[void_test, long_test, longlong_test, ushort_test,
 
70
 ulong_test, ulonglong_test, double_test, char_test,
 
71
 wchar_test, octet_test, bool_test, struct_test,
 
72
 struct2_test, seq1_test, seq2_test, seq3_test,
 
73
 seq4_test, seq5_test, array1_test, array2_test,
 
74
 enum_test, string1_test, string2_test, string3_test,
 
75
 string4_test, pid_test, port_test, ref_test, term_test,
 
76
 typedef_test, inline_sequence_test, term_sequence_test,
 
77
 term_struct_test, wstring1_test].
 
78
 
 
79
groups() -> 
 
80
    [].
 
81
 
 
82
init_per_suite(Config) ->
 
83
    Config.
 
84
 
 
85
end_per_suite(_Config) ->
 
86
    ok.
 
87
 
 
88
init_per_group(_GroupName, Config) ->
 
89
        Config.
 
90
 
 
91
end_per_group(_GroupName, Config) ->
 
92
        Config.
 
93
 
 
94
 
 
95
 
 
96
array1_test(doc) -> "";
 
97
array1_test(suite) -> [];
 
98
array1_test(Config) ->
 
99
    do_test(array1_test, Config). 
 
100
 
 
101
array2_test(doc) -> "";
 
102
array2_test(suite) -> [];
 
103
array2_test(Config) ->
 
104
    do_test(array2_test, Config).
 
105
 
 
106
bool_test(doc) -> "";
 
107
bool_test(suite) -> [];
 
108
bool_test(Config) ->
 
109
    do_test(bool_test, Config).
 
110
 
 
111
char_test(doc) -> "";
 
112
char_test(suite) -> [];
 
113
char_test(Config) ->
 
114
    do_test(char_test, Config).
 
115
 
 
116
double_test(doc) -> "";
 
117
double_test(suite) -> [];
 
118
double_test(Config) ->
 
119
    do_test(double_test, Config).
 
120
 
 
121
enum_test(doc) -> "";
 
122
enum_test(suite) -> [];
 
123
enum_test(Config) ->
 
124
    do_test(enum_test, Config).
 
125
 
 
126
inline_sequence_test(doc) -> "";
 
127
inline_sequence_test(suite) -> [];
 
128
inline_sequence_test(Config) ->
 
129
    do_test(inline_sequence_test, Config).
 
130
 
 
131
longlong_test(doc) -> "";
 
132
longlong_test(suite) -> [];
 
133
longlong_test(Config) ->
 
134
    do_test(longlong_test, Config).
 
135
 
 
136
long_test(doc) -> "";
 
137
long_test(suite) -> [];
 
138
long_test(Config) ->
 
139
    do_test(long_test, Config).
 
140
 
 
141
octet_test(doc) -> "";
 
142
octet_test(suite) -> [];
 
143
octet_test(Config) ->
 
144
    do_test(octet_test, Config).
 
145
 
 
146
pid_test(doc) -> "";
 
147
pid_test(suite) -> [];
 
148
pid_test(Config) ->
 
149
    do_test(pid_test, Config).
 
150
 
 
151
port_test(doc) -> "";
 
152
port_test(suite) -> [];
 
153
port_test(Config) ->
 
154
    do_test(port_test, Config).
 
155
 
 
156
ref_test(doc) -> "";
 
157
ref_test(suite) -> [];
 
158
ref_test(Config) ->
 
159
    do_test(ref_test, Config).
 
160
 
 
161
seq1_test(doc) -> "";
 
162
seq1_test(suite) -> [];
 
163
seq1_test(Config) ->
 
164
    do_test(seq1_test, Config).
 
165
 
 
166
seq2_test(doc) -> "";
 
167
seq2_test(suite) -> [];
 
168
seq2_test(Config) ->
 
169
    do_test(seq2_test, Config).
 
170
 
 
171
seq3_test(doc) -> "";
 
172
seq3_test(suite) -> [];
 
173
seq3_test(Config) ->
 
174
    do_test(seq3_test, Config).
 
175
 
 
176
seq4_test(doc) -> "";
 
177
seq4_test(suite) -> [];
 
178
seq4_test(Config) ->
 
179
    do_test(seq4_test, Config).
 
180
 
 
181
seq5_test(doc) -> "";
 
182
seq5_test(suite) -> [];
 
183
seq5_test(Config) ->
 
184
    do_test(seq5_test, Config).
 
185
 
 
186
string1_test(doc) -> "";
 
187
string1_test(suite) -> [];
 
188
string1_test(Config) ->
 
189
    do_test(string1_test, Config).
 
190
 
 
191
string2_test(doc) -> "";
 
192
string2_test(suite) -> [];
 
193
string2_test(Config) ->
 
194
    do_test(string2_test, Config).
 
195
 
 
196
string3_test(doc) -> "";
 
197
string3_test(suite) -> [];
 
198
string3_test(Config) ->
 
199
    do_test(string3_test, Config).
 
200
 
 
201
string4_test(doc) -> "";
 
202
string4_test(suite) -> [];
 
203
string4_test(Config) ->
 
204
    do_test(string4_test, Config).
 
205
 
 
206
struct2_test(doc) -> "";
 
207
struct2_test(suite) -> [];
 
208
struct2_test(Config) ->
 
209
    do_test(struct2_test, Config).
 
210
 
 
211
struct_test(doc) -> "";
 
212
struct_test(suite) -> [];
 
213
struct_test(Config) ->
 
214
    do_test(struct_test, Config).
 
215
 
 
216
term_sequence_test(doc) -> "";
 
217
term_sequence_test(suite) -> [];
 
218
term_sequence_test(Config) ->
 
219
    do_test(term_sequence_test, Config).
 
220
 
 
221
term_struct_test(doc) -> "";
 
222
term_struct_test(suite) -> [];
 
223
term_struct_test(Config) ->
 
224
    do_test(term_struct_test, Config).
 
225
 
 
226
term_test(doc) -> "";
 
227
term_test(suite) -> [];
 
228
term_test(Config) ->
 
229
    do_test(term_test, Config).
 
230
 
 
231
typedef_test(doc) -> "";
 
232
typedef_test(suite) -> [];
 
233
typedef_test(Config) ->
 
234
    do_test(typedef_test, Config).
 
235
 
 
236
ulonglong_test(doc) -> "";
 
237
ulonglong_test(suite) -> [];
 
238
ulonglong_test(Config) ->
 
239
    do_test(ulonglong_test, Config).
 
240
 
 
241
ulong_test(doc) -> "";
 
242
ulong_test(suite) -> [];
 
243
ulong_test(Config) ->
 
244
    do_test(ulong_test, Config).
 
245
 
 
246
ushort_test(doc) -> "";
 
247
ushort_test(suite) -> [];
 
248
ushort_test(Config) ->
 
249
    do_test(ushort_test, Config).
 
250
 
 
251
void_test(doc) -> "";
 
252
void_test(suite) -> [];
 
253
void_test(Config) ->
 
254
    do_test(void_test, Config).
 
255
 
 
256
wchar_test(doc) -> "";
 
257
wchar_test(suite) -> [];
 
258
wchar_test(Config) ->
 
259
    do_test(wchar_test, Config).
 
260
 
 
261
wstring1_test(doc) -> "";
 
262
wstring1_test(suite) -> [];
 
263
wstring1_test(Config) ->
 
264
    do_test(wstring1_test, Config).
 
265
 
 
266
 
 
267
do_test(Case, Config) ->
 
268
    %% Trap exits
 
269
    process_flag(trap_exit, true),
 
270
    Node = atom_to_list(node()),
 
271
    [_NodeName, HostName] = string:tokens(Node, "@"),
 
272
    DataDir = ?config(data_dir, Config),
 
273
    %% io:format("~p: data directory: ~p~n", [?MODULE, DataDir]),
 
274
    Cookie = atom_to_list(erlang:get_cookie()),
 
275
    ServerNodeName = atom_to_list(?C_SERVER_NODE_NAME), 
 
276
    %% Start C-server node as a port program. We wait for the node
 
277
    %% to connect to us.
 
278
    Cmd = filename:join([DataDir, "c_server"]) ++
 
279
        " -this-node-name " ++ ServerNodeName ++ 
 
280
        " -peer-node " ++ Node ++
 
281
        " -cookie " ++ Cookie, 
 
282
    Port = open_port({spawn, Cmd}, [exit_status, eof, stderr_to_stdout]),
 
283
    ServerNode = list_to_atom(ServerNodeName ++ "@" ++ HostName),
 
284
    Res = case wait_for_hidden_node(ServerNode) of
 
285
              ok ->
 
286
                  %% Need a port for port_test and typedef_test
 
287
                  put(port_test_port, Port),
 
288
                  R = (catch erl_client:Case(ServerNode, ?CALL_TIMEOUT)),
 
289
                  case wait_for_completion(Port) of
 
290
                      {error, timeout} ->
 
291
                          kill_off_node(ServerNode);
 
292
                      _ ->
 
293
                          ok
 
294
                  end,
 
295
                  R;
 
296
              {error, timeout} ->
 
297
                  case wait_for_completion(Port) of
 
298
                      {error, timeout} ->
 
299
                          kill_off_node(ServerNode);
 
300
                      _ ->
 
301
                          ok
 
302
                  end,
 
303
                  {error, timeout}
 
304
          end,
 
305
    process_flag(trap_exit, false),
 
306
    true = Res.
 
307
 
 
308
 
 
309
%% Wait for eof *and* exit status, but return if exit status indicates
 
310
%% an error, or we have been waiting more than PORT_TIMEOUT seconds.
 
311
%%
 
312
wait_for_completion(Port) ->
 
313
    wait_for_completion(Port, 0).
 
314
 
 
315
wait_for_completion(Port, N) when N < 2 ->
 
316
    receive
 
317
        {Port, {data, Bytes}} ->
 
318
            %% Relay output
 
319
            io:format("~s", [Bytes]),
 
320
            wait_for_completion(Port, N);
 
321
        {Port, {exit_status, 0}} ->
 
322
            wait_for_completion(Port, N + 1);
 
323
        {Port, {exit_status, Status}} ->
 
324
            {error, Status};
 
325
        {Port, eof} ->
 
326
            wait_for_completion(Port, N + 1);
 
327
        {'EXIT', Port, Reason} ->
 
328
            io:format("Port exited with reason: ~w~n", [Reason]),
 
329
            wait_for_completion(Port, N);
 
330
        {'EXIT', From, Reason} ->
 
331
            io:format("Got unexpected exit: ~p~n", [{'EXIT', From, Reason}]),
 
332
            wait_for_completion(Port, N)
 
333
    after ?PORT_TIMEOUT ->
 
334
            {error, timeout}
 
335
    end;
 
336
wait_for_completion(_, _) ->
 
337
    ok.
 
338
            
 
339
wait_for_hidden_node(Node) ->
 
340
    Times = ?DEFAULT_TIMEOUT div 100,
 
341
    wait_for_hidden_node(Node, Times, 100).
 
342
 
 
343
wait_for_hidden_node(Node, Times, WaitTime) when Times > 0 ->
 
344
    io:format("Waiting for hidden node: ~p~n", [Node]), 
 
345
    case lists:member(Node, erlang:nodes(hidden)) of
 
346
        true ->
 
347
            ok;
 
348
        false ->
 
349
            delay(WaitTime),
 
350
            wait_for_hidden_node(Node, Times - 1, WaitTime)
 
351
    end;
 
352
wait_for_hidden_node(_Node, _, _WaitTime) ->
 
353
    {error, timeout}.
 
354
 
 
355
kill_off_node(Node) ->
 
356
    catch rpc:cast(Node, erlang, halt, [1]).
 
357
 
 
358
delay(Time) ->
 
359
    receive
 
360
        after Time ->
 
361
                ok
 
362
        end.
 
363
    
 
364
 
 
365
            
 
366