~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/ssl/test/old_ssl_peer_cert_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2003-2009. 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_peer_cert_SUITE).
 
22
 
 
23
-export([all/1,
 
24
         init_per_testcase/2,
 
25
         fin_per_testcase/2,
 
26
         config/1,
 
27
         finish/1,
 
28
         cinit_plain/1,
 
29
         cinit_both_verify/1,
 
30
         cinit_cnocert/1
 
31
         ]).
 
32
 
 
33
-import(ssl_test_MACHINE, [mk_ssl_cert_opts/1, test_one_listener/7,
 
34
                           test_server_only/6]).
 
35
-include("test_server.hrl").
 
36
-include("ssl_test_MACHINE.hrl").
 
37
 
 
38
 
 
39
init_per_testcase(_Case, Config) ->
 
40
    WatchDog = ssl_test_lib:timetrap(?DEFAULT_TIMEOUT),
 
41
    [{watchdog, WatchDog}| Config].
 
42
 
 
43
fin_per_testcase(_Case, Config) ->
 
44
    WatchDog = ?config(watchdog, Config),
 
45
    test_server:timetrap_cancel(WatchDog).
 
46
 
 
47
all(doc) ->
 
48
    "Test of ssl verification and peer certificate retrieval.";
 
49
all(suite) ->
 
50
    {conf,
 
51
     config,
 
52
     [cinit_plain,
 
53
      cinit_both_verify,
 
54
      cinit_cnocert],
 
55
     finish}.
 
56
 
 
57
config(doc) ->
 
58
    "Want to se what Config contains.";
 
59
config(suite) ->
 
60
    [];
 
61
config(Config) ->
 
62
    io:format("Config: ~p~n", [Config]),
 
63
 
 
64
    %% Check if SSL exists. If this case fails, all other cases are skipped
 
65
    case ssl:start() of
 
66
        ok -> ssl:stop();
 
67
        {error, {already_started, _}} -> ssl:stop();
 
68
        Error -> ?t:fail({failed_starting_ssl,Error})
 
69
    end,
 
70
    Config.
 
71
 
 
72
finish(doc) ->
 
73
    "This test case has no mission other than closing the conf case";
 
74
finish(suite) ->
 
75
    [];
 
76
finish(Config) ->
 
77
    Config.
 
78
 
 
79
cinit_plain(doc) ->
 
80
    "Server closes after accept, Client waits for close. Both have certs "
 
81
        "but both use the defaults for verify and depth, but still tries "
 
82
        "to retreive each others certificates.";
 
83
cinit_plain(suite) ->
 
84
    [];
 
85
cinit_plain(Config) when list(Config) ->
 
86
    process_flag(trap_exit, true),
 
87
    DataSize = 1000, LPort = 3456,
 
88
    Timeout = 40000, NConns = 1,
 
89
 
 
90
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
 
91
 
 
92
    ?line {ok, Host} = inet:gethostname(),
 
93
 
 
94
    LCmds = [{sockopts, [{backlog, NConns}]},
 
95
             {sslopts, SsslOpts},
 
96
             {listen, LPort}, 
 
97
             wait_sync,
 
98
             lclose],
 
99
    ACmds = [{timeout, Timeout}, 
 
100
             accept,
 
101
             nopeercert,
 
102
             {recv, DataSize},
 
103
             close],
 
104
    CCmds = [{timeout, Timeout}, 
 
105
             {sslopts, CsslOpts},
 
106
             {connect, {Host, LPort}},
 
107
             peercert,
 
108
             {send, DataSize},
 
109
             await_close],
 
110
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, 
 
111
                            ?MODULE, Config).
 
112
 
 
113
cinit_both_verify(doc) ->
 
114
    "Server closes after accept, Client waits for close. Both have certs "
 
115
        "and both verify each other.";
 
116
cinit_both_verify(suite) ->
 
117
    [];
 
118
cinit_both_verify(Config) when list(Config) ->
 
119
    process_flag(trap_exit, true),
 
120
    DataSize = 1000, LPort = 3456,
 
121
    Timeout = 40000, NConns = 1,
 
122
 
 
123
    ?line {ok, {CsslOpts0, SsslOpts0}} = mk_ssl_cert_opts(Config),
 
124
    ?line CsslOpts = [{verify, 2}, {depth, 2} | CsslOpts0],
 
125
    ?line SsslOpts = [{verify, 2}, {depth, 3} | SsslOpts0],
 
126
 
 
127
    ?line {ok, Host} = inet:gethostname(),
 
128
 
 
129
    LCmds = [{sockopts, [{backlog, NConns}]},
 
130
             {sslopts, SsslOpts},
 
131
             {listen, LPort}, 
 
132
             wait_sync,
 
133
             lclose],
 
134
    ACmds = [{timeout, Timeout}, 
 
135
             accept,
 
136
             peercert,
 
137
             {recv, DataSize},
 
138
             close],
 
139
    CCmds = [{timeout, Timeout}, 
 
140
             {sslopts, CsslOpts},
 
141
             {connect, {Host, LPort}},
 
142
             peercert,
 
143
             {send, DataSize},
 
144
             await_close],
 
145
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, 
 
146
                            ?MODULE, Config).
 
147
 
 
148
cinit_cnocert(doc) ->
 
149
    "Client has no cert. Nor the client, nor the server is verifying its "
 
150
        "peer. Server closes, client waits for close.";
 
151
cinit_cnocert(suite) ->
 
152
    [];
 
153
cinit_cnocert(Config) when list(Config) ->
 
154
    process_flag(trap_exit, true),
 
155
    DataSize = 1000, LPort = 3457,
 
156
    Timeout = 40000, NConns = 1,
 
157
 
 
158
    ?line {ok, {_, SsslOpts0}} = mk_ssl_cert_opts(Config),
 
159
    ?line SsslOpts = [{verify, 0}, {depth, 2} | SsslOpts0],
 
160
 
 
161
    ?line {ok, Host} = inet:gethostname(),
 
162
 
 
163
    LCmds = [{sockopts, [{backlog, NConns}]},
 
164
             {sslopts, SsslOpts},
 
165
             {listen, LPort}, 
 
166
             wait_sync,
 
167
             lclose],
 
168
    ACmds = [{timeout, Timeout}, 
 
169
             accept,
 
170
             {recv, DataSize},
 
171
             close],
 
172
    CCmds = [{timeout, Timeout}, 
 
173
             {connect, {Host, LPort}},
 
174
             peercert,
 
175
             {send, DataSize},
 
176
             await_close],
 
177
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout,
 
178
                            ?MODULE, Config).
 
179
 
 
180