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

« back to all changes in this revision

Viewing changes to lib/ssl/test/old_ssl_active_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 1999-2010. 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
 
-module(old_ssl_active_SUITE).
22
 
 
23
 
-export([all/1,
24
 
         init_per_testcase/2,
25
 
         fin_per_testcase/2,
26
 
         config/1,
27
 
         finish/1,
28
 
         cinit_return_chkclose/1,
29
 
         sinit_return_chkclose/1,
30
 
         cinit_big_return_chkclose/1,
31
 
         sinit_big_return_chkclose/1,
32
 
         cinit_big_echo_chkclose/1,
33
 
         cinit_huge_echo_chkclose/1,
34
 
         sinit_big_echo_chkclose/1,
35
 
         cinit_few_echo_chkclose/1,
36
 
         cinit_many_echo_chkclose/1,
37
 
         cinit_cnocert/1
38
 
        ]).
39
 
 
40
 
-import(ssl_test_MACHINE, [mk_ssl_cert_opts/1, test_one_listener/7,
41
 
                           test_server_only/6]).
42
 
 
43
 
-include("test_server.hrl").
44
 
-include("ssl_test_MACHINE.hrl").
45
 
 
46
 
-define(MANYCONNS, ssl_test_MACHINE:many_conns()).
47
 
 
48
 
init_per_testcase(_Case, Config) ->
49
 
    WatchDog = ssl_test_lib:timetrap(?DEFAULT_TIMEOUT),
50
 
    [{watchdog, WatchDog}| Config].
51
 
 
52
 
fin_per_testcase(_Case, Config) ->
53
 
    WatchDog = ?config(watchdog, Config),
54
 
    test_server:timetrap_cancel(WatchDog).
55
 
 
56
 
all(doc) ->
57
 
    "Test of ssl.erl interface in active mode.";
58
 
all(suite) ->
59
 
    {conf, 
60
 
     config,
61
 
     [cinit_return_chkclose,
62
 
      sinit_return_chkclose,
63
 
      cinit_big_return_chkclose,
64
 
      sinit_big_return_chkclose,
65
 
      cinit_big_echo_chkclose,
66
 
      cinit_huge_echo_chkclose,
67
 
      sinit_big_echo_chkclose,
68
 
      cinit_few_echo_chkclose,
69
 
      cinit_many_echo_chkclose,
70
 
      cinit_cnocert],
71
 
     finish}.
72
 
 
73
 
config(doc) ->
74
 
    "Want to se what Config contains, and record the number of available "
75
 
        "file descriptors";
76
 
config(suite) ->
77
 
    [];
78
 
config(Config) ->
79
 
    io:format("Config: ~p~n", [Config]),
80
 
    case os:type() of
81
 
        {unix, _} ->
82
 
            ?line io:format("Max fd value: ~s", [os:cmd("ulimit -n")]);
83
 
        _ ->
84
 
            ok
85
 
    end, 
86
 
    %% XXX Also record: Erlang/SSL version, version of OpenSSL, 
87
 
    %% operating system, version of OTP, Erts, kernel and stdlib. 
88
 
 
89
 
    %% Check if SSL exists. If this case fails, all other cases are skipped
90
 
    crypto:start(),
91
 
    application:start(public_key),
92
 
    case ssl:start() of
93
 
        ok -> ssl:stop();
94
 
        {error, {already_started, _}} -> ssl:stop();
95
 
        Error -> ?t:fail({failed_starting_ssl,Error})
96
 
    end,
97
 
    Config.
98
 
 
99
 
finish(doc) ->
100
 
    "This test case has no mission other than closing the conf case";
101
 
finish(suite) ->
102
 
    [];
103
 
finish(Config) ->
104
 
    Config.
105
 
 
106
 
cinit_return_chkclose(doc) ->
107
 
    "Client sends 1000 bytes to server, that receives them, sends them "
108
 
        "back, and closes. Client waits for close. Both have certs.";
109
 
cinit_return_chkclose(suite) ->
110
 
    [];
111
 
cinit_return_chkclose(Config) when list(Config) ->
112
 
    process_flag(trap_exit, true),
113
 
    DataSize = 1000, LPort = 3456,
114
 
    Timeout = 40000, NConns = 1,
115
 
 
116
 
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
117
 
    ?line {ok, Host} = inet:gethostname(),
118
 
 
119
 
    LCmds = [{sockopts, [{backlog, NConns}]},
120
 
             {sslopts, SsslOpts},
121
 
             {listen, LPort}, 
122
 
             wait_sync,
123
 
             lclose],
124
 
    ACmds = [{timeout, Timeout}, 
125
 
             accept,
126
 
             {recv, DataSize}, {send, DataSize}, 
127
 
             close],
128
 
    CCmds = [{timeout, Timeout}, 
129
 
             {sslopts, CsslOpts},
130
 
             {connect, {Host, LPort}},
131
 
             {send, DataSize}, {recv, DataSize}, 
132
 
             await_close],
133
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, ?MODULE, 
134
 
                            Config).
135
 
 
136
 
sinit_return_chkclose(doc) ->
137
 
    "Server sends 1000 bytes to client, that receives them, sends them "
138
 
        "back, and closes. Server waits for close. Both have certs.";
139
 
sinit_return_chkclose(suite) ->
140
 
    [];
141
 
sinit_return_chkclose(Config) when list(Config) ->
142
 
    process_flag(trap_exit, true),
143
 
    DataSize = 1000, LPort = 3456,
144
 
    Timeout = 40000, NConns = 1,
145
 
 
146
 
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
147
 
    ?line {ok, Host} = inet:gethostname(),
148
 
 
149
 
    LCmds = [{sockopts, [{backlog, NConns}]},
150
 
             {sslopts, [{ssl_imp, old}|SsslOpts]},
151
 
             {listen, LPort}, 
152
 
             wait_sync,
153
 
             lclose],
154
 
    ACmds = [{timeout, Timeout}, 
155
 
             accept,
156
 
             {send, DataSize}, {recv, DataSize},
157
 
             await_close],
158
 
    CCmds = [{timeout, Timeout}, 
159
 
             {sslopts, [{ssl_imp, old}|CsslOpts]},
160
 
             {connect, {Host, LPort}},
161
 
             {recv, DataSize}, {send, DataSize}, 
162
 
             close],
163
 
 
164
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, ?MODULE, 
165
 
                            Config).
166
 
 
167
 
cinit_big_return_chkclose(doc) ->
168
 
    "Client sends 50000 bytes to server, that receives them, sends them "
169
 
        "back, and closes. Client waits for close. Both have certs.";
170
 
cinit_big_return_chkclose(suite) ->
171
 
    [];
172
 
cinit_big_return_chkclose(Config) when list(Config) ->
173
 
    process_flag(trap_exit, true),
174
 
    DataSize = 50000, LPort = 3456,
175
 
    Timeout = 40000, NConns = 1,
176
 
 
177
 
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
178
 
    ?line {ok, Host} = inet:gethostname(),
179
 
 
180
 
    LCmds = [{sockopts, [{backlog, NConns}]},
181
 
             {sslopts, SsslOpts},
182
 
             {listen, LPort}, 
183
 
             wait_sync,
184
 
             lclose],
185
 
    ACmds = [{timeout, Timeout}, 
186
 
             accept,
187
 
             {recv, DataSize}, {send, DataSize}, 
188
 
             close],
189
 
    CCmds = [{timeout, Timeout}, 
190
 
             {sslopts, CsslOpts},
191
 
             {connect, {Host, LPort}},
192
 
             {send, DataSize}, {recv, DataSize}, 
193
 
             await_close],
194
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, ?MODULE, 
195
 
                            Config).
196
 
 
197
 
sinit_big_return_chkclose(doc) ->
198
 
    "Server sends 50000 bytes to client, that receives them, sends them "
199
 
        "back, and closes. Server waits for close. Both have certs.";
200
 
sinit_big_return_chkclose(suite) ->
201
 
    [];
202
 
sinit_big_return_chkclose(Config) when list(Config) ->
203
 
    process_flag(trap_exit, true),
204
 
    DataSize = 50000, LPort = 3456,
205
 
    Timeout = 40000, NConns = 1,
206
 
 
207
 
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
208
 
    ?line {ok, Host} = inet:gethostname(),
209
 
 
210
 
    LCmds = [{sockopts, [{backlog, NConns}]},
211
 
             {sslopts, SsslOpts},
212
 
             {listen, LPort}, 
213
 
             wait_sync,
214
 
             lclose],
215
 
    ACmds = [{timeout, Timeout}, 
216
 
             accept,
217
 
             {send, DataSize}, {recv, DataSize}, 
218
 
             await_close],
219
 
    CCmds = [{timeout, Timeout}, 
220
 
             {sslopts, CsslOpts},
221
 
             {connect, {Host, LPort}},
222
 
             {recv, DataSize}, {send, DataSize}, 
223
 
             close],
224
 
 
225
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, ?MODULE, 
226
 
                            Config).
227
 
 
228
 
cinit_big_echo_chkclose(doc) ->
229
 
    "Client sends 50000 bytes to server, that echoes them back "
230
 
        "and closes. Client waits for close. Both have certs.";
231
 
cinit_big_echo_chkclose(suite) ->
232
 
    [];
233
 
cinit_big_echo_chkclose(Config) when list(Config) ->
234
 
    process_flag(trap_exit, true),
235
 
    DataSize = 50000, LPort = 3456,
236
 
    Timeout = 40000, NConns = 1,
237
 
 
238
 
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
239
 
    ?line {ok, Host} = inet:gethostname(),
240
 
 
241
 
    LCmds = [{sockopts, [{backlog, NConns}]},
242
 
             {sslopts, SsslOpts},
243
 
             {listen, LPort}, 
244
 
             wait_sync,
245
 
             lclose],
246
 
    ACmds = [{timeout, Timeout}, 
247
 
             accept,
248
 
             {echo, DataSize},
249
 
             close],
250
 
    CCmds = [{timeout, Timeout}, 
251
 
             {sslopts, CsslOpts},
252
 
             {connect, {Host, LPort}},
253
 
             {send, DataSize}, {recv, DataSize}, 
254
 
             await_close],
255
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, ?MODULE, 
256
 
                            Config).
257
 
 
258
 
cinit_huge_echo_chkclose(doc) ->
259
 
    "Client sends 500000 bytes to server, that echoes them back "
260
 
        "and closes. Client waits for close. Both have certs.";
261
 
cinit_huge_echo_chkclose(suite) ->
262
 
    [];
263
 
cinit_huge_echo_chkclose(Config) when list(Config) ->
264
 
    process_flag(trap_exit, true),
265
 
    DataSize = 500000, LPort = 3456,
266
 
    Timeout = 40000, NConns = 1,
267
 
 
268
 
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
269
 
    ?line {ok, Host} = inet:gethostname(),
270
 
 
271
 
    LCmds = [{sockopts, [{backlog, NConns}]},
272
 
             {sslopts, SsslOpts},
273
 
             {listen, LPort}, 
274
 
             wait_sync,
275
 
             lclose],
276
 
    ACmds = [{timeout, Timeout}, 
277
 
             accept,
278
 
             {echo, DataSize},
279
 
             close],
280
 
    CCmds = [{timeout, Timeout}, 
281
 
             {sslopts, CsslOpts},
282
 
             {connect, {Host, LPort}},
283
 
             {send, DataSize}, {recv, DataSize}, 
284
 
             await_close],
285
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, ?MODULE, 
286
 
                            Config).
287
 
 
288
 
sinit_big_echo_chkclose(doc) ->
289
 
    "Server sends 50000 bytes to client, that echoes them back "
290
 
        "and closes. Server waits for close. Both have certs.";
291
 
sinit_big_echo_chkclose(suite) ->
292
 
    [];
293
 
sinit_big_echo_chkclose(Config) when list(Config) ->
294
 
    process_flag(trap_exit, true),
295
 
    DataSize = 50000, LPort = 3456,
296
 
    Timeout = 40000, NConns = 1,
297
 
 
298
 
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
299
 
    ?line {ok, Host} = inet:gethostname(),
300
 
 
301
 
    LCmds = [{sockopts, [{backlog, NConns}]},
302
 
             {sslopts, SsslOpts},
303
 
             {listen, LPort}, 
304
 
             wait_sync,
305
 
             lclose],
306
 
    ACmds = [{timeout, Timeout}, 
307
 
             accept,
308
 
             {send, DataSize}, {recv, DataSize}, 
309
 
             await_close],
310
 
    CCmds = [{timeout, Timeout}, 
311
 
             {sslopts, CsslOpts},
312
 
             {connect, {Host, LPort}},
313
 
             {echo, DataSize},
314
 
             close],
315
 
 
316
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, ?MODULE, 
317
 
                            Config).
318
 
 
319
 
 
320
 
%% This case is repeated several times.
321
 
 
322
 
cinit_few_echo_chkclose(X) -> cinit_many_echo_chkclose(X, 7).
323
 
 
324
 
cinit_many_echo_chkclose(X) -> cinit_many_echo_chkclose(X, ?MANYCONNS).
325
 
 
326
 
cinit_many_echo_chkclose(doc, _NConns) ->
327
 
    "N client sends 10000 bytes to server, that echoes them back "
328
 
        "and closes. Clients wait for close. All have certs.";
329
 
cinit_many_echo_chkclose(suite, _NConns) ->
330
 
    [];
331
 
cinit_many_echo_chkclose(Config, NConns) when list(Config) ->
332
 
    process_flag(trap_exit, true),
333
 
    DataSize = 10000, LPort = 3456,
334
 
    Timeout = 80000,
335
 
 
336
 
    io:format("~w connections", [NConns]),
337
 
 
338
 
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
339
 
    ?line {ok, Host} = inet:gethostname(),
340
 
 
341
 
    LCmds = [{sockopts, [{backlog, NConns}]},
342
 
             {sslopts, SsslOpts},
343
 
             {listen, LPort}, 
344
 
             wait_sync,
345
 
             lclose],
346
 
    ACmds = [{timeout, Timeout}, 
347
 
             accept,
348
 
             {echo, DataSize},
349
 
             close],
350
 
    CCmds = [{timeout, Timeout}, 
351
 
             {sslopts, CsslOpts},
352
 
             {connect, {Host, LPort}},
353
 
             {send, DataSize}, {recv, DataSize}, 
354
 
             await_close],
355
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, ?MODULE, 
356
 
                            Config).
357
 
 
358
 
 
359
 
cinit_cnocert(doc) ->
360
 
    "Client sends 1000 bytes to server, that receives them, sends them "
361
 
        "back, and closes. Client waits for close. Client has no cert, "
362
 
        "but server has.";
363
 
cinit_cnocert(suite) ->
364
 
    [];
365
 
cinit_cnocert(Config) when list(Config) ->
366
 
    process_flag(trap_exit, true),
367
 
    DataSize = 1000, LPort = 3457,
368
 
    Timeout = 40000, NConns = 1,
369
 
 
370
 
    ?line {ok, {_CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
371
 
    ?line {ok, Host} = inet:gethostname(),
372
 
 
373
 
    LCmds = [{sockopts, [{backlog, NConns}]},
374
 
             {sslopts, SsslOpts},
375
 
             {listen, LPort}, 
376
 
             wait_sync,
377
 
             lclose],
378
 
    ACmds = [{timeout, Timeout}, 
379
 
             accept,
380
 
             {recv, DataSize}, {send, DataSize}, 
381
 
             close],
382
 
    CCmds = [{timeout, Timeout}, 
383
 
             {connect, {Host, LPort}},
384
 
             {send, DataSize}, {recv, DataSize}, 
385
 
             await_close],
386
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, ?MODULE, 
387
 
                            Config).
388
 
 
389