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

« back to all changes in this revision

Viewing changes to lib/ssl/test/ssl_session_cache_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/.2
 
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
-module(ssl_session_cache_SUITE).
 
23
 
 
24
%% Note: This directive should only be used in test suites.
 
25
-compile(export_all).
 
26
 
 
27
-include_lib("common_test/include/ct.hrl").
 
28
 
 
29
-define(SLEEP, 500).
 
30
-define(TIMEOUT, 60000).
 
31
-define(LONG_TIMEOUT, 600000).
 
32
-behaviour(ssl_session_cache_api).
 
33
 
 
34
%% For the session cache tests
 
35
-export([init/1, terminate/1, lookup/2, update/3,
 
36
         delete/2, foldl/3, select_session/2]).
 
37
 
 
38
%% Test server callback functions
 
39
%%--------------------------------------------------------------------
 
40
%% Function: init_per_suite(Config) -> Config
 
41
%% Config - [tuple()]
 
42
%%   A list of key/value pairs, holding the test case configuration.
 
43
%% Description: Initialization before the whole suite
 
44
%%
 
45
%% Note: This function is free to add any key/value pairs to the Config
 
46
%% variable, but should NOT alter/remove any existing entries.
 
47
%%--------------------------------------------------------------------
 
48
init_per_suite(Config0) ->
 
49
    Dog = ssl_test_lib:timetrap(?LONG_TIMEOUT *2),
 
50
    try crypto:start() of
 
51
        ok ->
 
52
            application:start(public_key),
 
53
            ssl:start(),
 
54
 
 
55
            %% make rsa certs using oppenssl
 
56
            Result =
 
57
                (catch make_certs:all(?config(data_dir, Config0),
 
58
                                      ?config(priv_dir, Config0))),
 
59
            test_server:format("Make certs  ~p~n", [Result]),
 
60
 
 
61
            Config1 = ssl_test_lib:make_dsa_cert(Config0),
 
62
            Config = ssl_test_lib:cert_options(Config1),
 
63
            [{watchdog, Dog} | Config]
 
64
    catch _:_ ->
 
65
            {skip, "Crypto did not start"}
 
66
    end.
 
67
 
 
68
%%--------------------------------------------------------------------
 
69
%% Function: end_per_suite(Config) -> _
 
70
%% Config - [tuple()]
 
71
%%   A list of key/value pairs, holding the test case configuration.
 
72
%% Description: Cleanup after the whole suite
 
73
%%--------------------------------------------------------------------
 
74
end_per_suite(_Config) ->
 
75
    ssl:stop(),
 
76
    application:stop(crypto).
 
77
 
 
78
%%--------------------------------------------------------------------
 
79
%% Function: init_per_testcase(TestCase, Config) -> Config
 
80
%% Case - atom()
 
81
%%   Name of the test case that is about to be run.
 
82
%% Config - [tuple()]
 
83
%%   A list of key/value pairs, holding the test case configuration.
 
84
%%
 
85
%% Description: Initialization before each test case
 
86
%%
 
87
%% Note: This function is free to add any key/value pairs to the Config
 
88
%% variable, but should NOT alter/remove any existing entries.
 
89
%% Description: Initialization before each test case
 
90
%%--------------------------------------------------------------------
 
91
init_per_testcase(session_cache_process_list, Config) ->
 
92
    init_customized_session_cache(list, Config);
 
93
 
 
94
init_per_testcase(session_cache_process_mnesia, Config) ->
 
95
    mnesia:start(),
 
96
    init_customized_session_cache(mnesia, Config);
 
97
 
 
98
init_per_testcase(_TestCase, Config0) ->
 
99
    Config = lists:keydelete(watchdog, 1, Config0),
 
100
    Dog = test_server:timetrap(?TIMEOUT),
 
101
   [{watchdog, Dog} | Config].
 
102
 
 
103
init_customized_session_cache(Type, Config0) ->
 
104
    Config = lists:keydelete(watchdog, 1, Config0),
 
105
    Dog = test_server:timetrap(?TIMEOUT),
 
106
    ssl:stop(),
 
107
    application:load(ssl),
 
108
    application:set_env(ssl, session_cb, ?MODULE),
 
109
    application:set_env(ssl, session_cb_init_args, [Type]),
 
110
    ssl:start(),
 
111
    [{watchdog, Dog} | Config].
 
112
 
 
113
%%--------------------------------------------------------------------
 
114
%% Function: end_per_testcase(TestCase, Config) -> _
 
115
%% Case - atom()
 
116
%%   Name of the test case that is about to be run.
 
117
%% Config - [tuple()]
 
118
%%   A list of key/value pairs, holding the test case configuration.
 
119
%% Description: Cleanup after each test case
 
120
%%--------------------------------------------------------------------
 
121
end_per_testcase(session_cache_process_list, Config) ->
 
122
    application:unset_env(ssl, session_cb),
 
123
    end_per_testcase(default_action, Config);
 
124
end_per_testcase(session_cache_process_mnesia, Config) ->
 
125
    application:unset_env(ssl, session_cb),
 
126
    application:unset_env(ssl, session_cb_init_args),
 
127
    mnesia:kill(),
 
128
    ssl:stop(),
 
129
    ssl:start(),
 
130
    end_per_testcase(default_action, Config);
 
131
end_per_testcase(_TestCase, Config) ->
 
132
    Dog = ?config(watchdog, Config),
 
133
    case Dog of
 
134
        undefined ->
 
135
            ok;
 
136
        _ ->
 
137
            test_server:timetrap_cancel(Dog)
 
138
    end.
 
139
 
 
140
%%--------------------------------------------------------------------
 
141
%% Function: all(Clause) -> TestCases
 
142
%% Clause - atom() - suite | doc
 
143
%% TestCases - [Case]
 
144
%% Case - atom()
 
145
%%   Name of a test case.
 
146
%% Description: Returns a list of all test cases in this test suite
 
147
%%--------------------------------------------------------------------
 
148
suite() -> [{ct_hooks,[ts_install_cth]}].
 
149
 
 
150
all() -> 
 
151
    [session_cache_process_list,
 
152
     session_cache_process_mnesia].
 
153
 
 
154
groups() -> 
 
155
    [].
 
156
 
 
157
init_per_group(_GroupName, Config) ->
 
158
    Config.
 
159
 
 
160
end_per_group(_GroupName, Config) ->
 
161
    Config.
 
162
 
 
163
session_cache_process_list(doc) ->
 
164
    ["Test reuse of sessions (short handshake)"];
 
165
 
 
166
session_cache_process_list(suite) ->
 
167
    [];
 
168
session_cache_process_list(Config) when is_list(Config) ->
 
169
    session_cache_process(list,Config).
 
170
%%--------------------------------------------------------------------
 
171
session_cache_process_mnesia(doc) ->
 
172
    ["Test reuse of sessions (short handshake)"];
 
173
 
 
174
session_cache_process_mnesia(suite) ->
 
175
    [];
 
176
session_cache_process_mnesia(Config) when is_list(Config) ->
 
177
    session_cache_process(mnesia,Config).
 
178
 
 
179
 
 
180
%%--------------------------------------------------------------------
 
181
%%% Session cache API callbacks
 
182
%%--------------------------------------------------------------------
 
183
 
 
184
init([Type]) ->
 
185
    ets:new(ssl_test, [named_table, public, set]),
 
186
    ets:insert(ssl_test, {type, Type}),
 
187
    case Type of
 
188
        list ->
 
189
            spawn(fun() -> session_loop([]) end);
 
190
        mnesia ->
 
191
            mnesia:start(),
 
192
            {atomic,ok} = mnesia:create_table(sess_cache, []),
 
193
            sess_cache
 
194
    end.
 
195
 
 
196
session_cb() ->
 
197
    [{type, Type}] = ets:lookup(ssl_test, type),
 
198
    Type.
 
199
 
 
200
terminate(Cache) ->
 
201
    case session_cb() of
 
202
        list ->
 
203
            Cache ! terminate;
 
204
        mnesia ->
 
205
            catch {atomic,ok} =
 
206
                mnesia:delete_table(sess_cache)
 
207
    end.
 
208
 
 
209
lookup(Cache, Key) ->
 
210
    case session_cb() of
 
211
        list ->
 
212
            Cache ! {self(), lookup, Key},
 
213
            receive {Cache, Res} -> Res end;
 
214
        mnesia ->
 
215
            case mnesia:transaction(fun() ->
 
216
                                            mnesia:read(sess_cache,
 
217
                                                        Key, read)
 
218
                                    end) of
 
219
                {atomic, [{sess_cache, Key, Value}]} ->
 
220
                    Value;
 
221
                _ ->
 
222
                    undefined
 
223
            end
 
224
        end.
 
225
 
 
226
update(Cache, Key, Value) ->
 
227
    case session_cb() of
 
228
        list ->
 
229
            Cache ! {update, Key, Value};
 
230
        mnesia ->
 
231
            {atomic, ok} =
 
232
                mnesia:transaction(fun() ->
 
233
                                           mnesia:write(sess_cache,
 
234
                                                        {sess_cache, Key, Value}, write)
 
235
                                   end)
 
236
    end.
 
237
 
 
238
delete(Cache, Key) ->
 
239
    case session_cb() of
 
240
        list ->
 
241
            Cache ! {delete, Key};
 
242
        mnesia ->
 
243
            {atomic, ok} =
 
244
                mnesia:transaction(fun() ->
 
245
                                           mnesia:delete(sess_cache, Key)
 
246
                                   end)
 
247
    end.
 
248
 
 
249
foldl(Fun, Acc, Cache) ->
 
250
    case session_cb() of
 
251
        list ->
 
252
            Cache ! {self(),foldl,Fun,Acc},
 
253
            receive {Cache, Res} -> Res end;
 
254
        mnesia ->
 
255
            Foldl = fun() ->
 
256
                            mnesia:foldl(Fun, Acc, sess_cache)
 
257
                    end,
 
258
            {atomic, Res} = mnesia:transaction(Foldl),
 
259
            Res
 
260
    end.
 
261
 
 
262
select_session(Cache, PartialKey) ->
 
263
    case session_cb() of
 
264
        list ->
 
265
            Cache ! {self(),select_session, PartialKey},
 
266
            receive
 
267
                {Cache, Res} ->
 
268
                    Res
 
269
            end;
 
270
        mnesia ->
 
271
            Sel = fun() ->
 
272
                          mnesia:select(Cache,
 
273
                                        [{{sess_cache,{PartialKey,'$1'}, '$2'},
 
274
                                          [],['$$']}])
 
275
                  end,
 
276
            {atomic, Res} = mnesia:transaction(Sel),
 
277
            Res
 
278
    end.
 
279
 
 
280
session_loop(Sess) ->
 
281
    receive
 
282
        terminate ->
 
283
            ok;
 
284
        {Pid, lookup, Key} ->
 
285
            case lists:keysearch(Key,1,Sess) of
 
286
                {value, {Key,Value}} ->
 
287
                    Pid ! {self(), Value};
 
288
                _ ->
 
289
                    Pid ! {self(), undefined}
 
290
            end,
 
291
            session_loop(Sess);
 
292
        {update, Key, Value} ->
 
293
            NewSess = [{Key,Value}| lists:keydelete(Key,1,Sess)],
 
294
            session_loop(NewSess);
 
295
        {delete, Key} ->
 
296
            session_loop(lists:keydelete(Key,1,Sess));
 
297
        {Pid,foldl,Fun,Acc} ->
 
298
            Res = lists:foldl(Fun, Acc,Sess),
 
299
            Pid ! {self(), Res},
 
300
            session_loop(Sess);
 
301
        {Pid,select_session,PKey} ->
 
302
            Sel = fun({{PKey0, Id},Session}, Acc) when PKey == PKey0 ->
 
303
                          [[Id, Session]|Acc];
 
304
                     (_,Acc) ->
 
305
                          Acc
 
306
                  end,
 
307
            Sessions = lists:foldl(Sel, [], Sess),
 
308
            Pid ! {self(), Sessions},
 
309
            session_loop(Sess)
 
310
    end.
 
311
 
 
312
%%--------------------------------------------------------------------
 
313
%%% Internal functions
 
314
%%--------------------------------------------------------------------
 
315
 
 
316
session_cache_process(_Type,Config) when is_list(Config) ->
 
317
    ssl_basic_SUITE:reuse_session(Config).