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

« back to all changes in this revision

Viewing changes to lib/ssl/test/old_ssl_peer_cert_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 2003-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_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
 
    crypto:start(),
66
 
    application:start(public_key),
67
 
    case ssl:start() of
68
 
        ok -> ssl:stop();
69
 
        {error, {already_started, _}} -> ssl:stop();
70
 
        Error -> ?t:fail({failed_starting_ssl,Error})
71
 
    end,
72
 
    Config.
73
 
 
74
 
finish(doc) ->
75
 
    "This test case has no mission other than closing the conf case";
76
 
finish(suite) ->
77
 
    [];
78
 
finish(Config) ->
79
 
    Config.
80
 
 
81
 
cinit_plain(doc) ->
82
 
    "Server closes after accept, Client waits for close. Both have certs "
83
 
        "but both use the defaults for verify and depth, but still tries "
84
 
        "to retreive each others certificates.";
85
 
cinit_plain(suite) ->
86
 
    [];
87
 
cinit_plain(Config) when list(Config) ->
88
 
    process_flag(trap_exit, true),
89
 
    DataSize = 1000, LPort = 3456,
90
 
    Timeout = 40000, NConns = 1,
91
 
 
92
 
    ?line {ok, {CsslOpts, SsslOpts}} = mk_ssl_cert_opts(Config),
93
 
 
94
 
    ?line {ok, Host} = inet:gethostname(),
95
 
 
96
 
    LCmds = [{sockopts, [{backlog, NConns}]},
97
 
             {sslopts, SsslOpts},
98
 
             {listen, LPort}, 
99
 
             wait_sync,
100
 
             lclose],
101
 
    ACmds = [{timeout, Timeout}, 
102
 
             accept,
103
 
             nopeercert,
104
 
             {recv, DataSize},
105
 
             close],
106
 
    CCmds = [{timeout, Timeout}, 
107
 
             {sslopts, CsslOpts},
108
 
             {connect, {Host, LPort}},
109
 
             peercert,
110
 
             {send, DataSize},
111
 
             await_close],
112
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, 
113
 
                            ?MODULE, Config).
114
 
 
115
 
cinit_both_verify(doc) ->
116
 
    "Server closes after accept, Client waits for close. Both have certs "
117
 
        "and both verify each other.";
118
 
cinit_both_verify(suite) ->
119
 
    [];
120
 
cinit_both_verify(Config) when list(Config) ->
121
 
    process_flag(trap_exit, true),
122
 
    DataSize = 1000, LPort = 3456,
123
 
    Timeout = 40000, NConns = 1,
124
 
 
125
 
    ?line {ok, {CsslOpts0, SsslOpts0}} = mk_ssl_cert_opts(Config),
126
 
    ?line CsslOpts = [{verify, 2}, {depth, 2} | CsslOpts0],
127
 
    ?line SsslOpts = [{verify, 2}, {depth, 3} | SsslOpts0],
128
 
 
129
 
    ?line {ok, Host} = inet:gethostname(),
130
 
 
131
 
    LCmds = [{sockopts, [{backlog, NConns}]},
132
 
             {sslopts, SsslOpts},
133
 
             {listen, LPort}, 
134
 
             wait_sync,
135
 
             lclose],
136
 
    ACmds = [{timeout, Timeout}, 
137
 
             accept,
138
 
             peercert,
139
 
             {recv, DataSize},
140
 
             close],
141
 
    CCmds = [{timeout, Timeout}, 
142
 
             {sslopts, CsslOpts},
143
 
             {connect, {Host, LPort}},
144
 
             peercert,
145
 
             {send, DataSize},
146
 
             await_close],
147
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, 
148
 
                            ?MODULE, Config).
149
 
 
150
 
cinit_cnocert(doc) ->
151
 
    "Client has no cert. Nor the client, nor the server is verifying its "
152
 
        "peer. Server closes, client waits for close.";
153
 
cinit_cnocert(suite) ->
154
 
    [];
155
 
cinit_cnocert(Config) when list(Config) ->
156
 
    process_flag(trap_exit, true),
157
 
    DataSize = 1000, LPort = 3457,
158
 
    Timeout = 40000, NConns = 1,
159
 
 
160
 
    ?line {ok, {_, SsslOpts0}} = mk_ssl_cert_opts(Config),
161
 
    ?line SsslOpts = [{verify, 0}, {depth, 2} | SsslOpts0],
162
 
 
163
 
    ?line {ok, Host} = inet:gethostname(),
164
 
 
165
 
    LCmds = [{sockopts, [{backlog, NConns}]},
166
 
             {sslopts, SsslOpts},
167
 
             {listen, LPort}, 
168
 
             wait_sync,
169
 
             lclose],
170
 
    ACmds = [{timeout, Timeout}, 
171
 
             accept,
172
 
             {recv, DataSize},
173
 
             close],
174
 
    CCmds = [{timeout, Timeout}, 
175
 
             {connect, {Host, LPort}},
176
 
             peercert,
177
 
             {send, DataSize},
178
 
             await_close],
179
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout,
180
 
                            ?MODULE, Config).
181
 
 
182