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

« back to all changes in this revision

Viewing changes to lib/ssl/test/old_ssl_verify_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_verify_SUITE).
22
 
 
23
 
-export([all/1,
24
 
         init_per_testcase/2,
25
 
         fin_per_testcase/2,
26
 
         config/1,
27
 
         finish/1,
28
 
         cinit_both_verify/1,
29
 
         cinit_cnocert/1
30
 
         ]).
31
 
 
32
 
-import(ssl_test_MACHINE, [mk_ssl_cert_opts/1, test_one_listener/7,
33
 
                           test_server_only/6]).
34
 
-include("test_server.hrl").
35
 
-include("ssl_test_MACHINE.hrl").
36
 
 
37
 
 
38
 
init_per_testcase(_Case, Config) ->
39
 
    WatchDog = ssl_test_lib:timetrap(?DEFAULT_TIMEOUT),
40
 
    [{watchdog, WatchDog}| Config].
41
 
 
42
 
fin_per_testcase(_Case, Config) ->
43
 
    WatchDog = ?config(watchdog, Config),
44
 
    test_server:timetrap_cancel(WatchDog).
45
 
 
46
 
all(doc) ->
47
 
    "Test of ssl.erl interface in active mode.";
48
 
all(suite) ->
49
 
    {conf,
50
 
     config,
51
 
     [cinit_both_verify,
52
 
      cinit_cnocert],
53
 
     finish}.
54
 
 
55
 
config(doc) ->
56
 
    "Want to se what Config contains.";
57
 
config(suite) ->
58
 
    [];
59
 
config(Config) ->
60
 
    io:format("Config: ~p~n", [Config]),
61
 
 
62
 
    %% Check if SSL exists. If this case fails, all other cases are skipped
63
 
    crypto:start(),
64
 
    application:start(public_key),
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_both_verify(doc) ->
80
 
    "Server closes after accept, Client waits for close. Both have certs "
81
 
        "and both verify each other.";
82
 
cinit_both_verify(suite) ->
83
 
    [];
84
 
cinit_both_verify(Config) when list(Config) ->
85
 
    process_flag(trap_exit, true),
86
 
    DataSize = 1000, LPort = 3456,
87
 
    Timeout = 40000, NConns = 1,
88
 
 
89
 
    ?line {ok, {CsslOpts0, SsslOpts0}} = mk_ssl_cert_opts(Config),
90
 
    ?line CsslOpts = [{verify, 2}, {depth, 2} | CsslOpts0],
91
 
    ?line SsslOpts = [{verify, 2}, {depth, 3} | SsslOpts0],
92
 
 
93
 
    ?line {ok, Host} = inet:gethostname(),
94
 
 
95
 
    LCmds = [{sockopts, [{backlog, NConns}]},
96
 
             {sslopts, SsslOpts},
97
 
             {listen, LPort}, 
98
 
             wait_sync,
99
 
             lclose],
100
 
    ACmds = [{timeout, Timeout}, 
101
 
             accept,
102
 
             {recv, DataSize},
103
 
             close],
104
 
    CCmds = [{timeout, Timeout}, 
105
 
             {sslopts, CsslOpts},
106
 
             {connect, {Host, LPort}},
107
 
             {send, DataSize},
108
 
             await_close],
109
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout, 
110
 
                            ?MODULE, Config).
111
 
 
112
 
cinit_cnocert(doc) ->
113
 
    "Client has no cert. Nor the client, nor the server is verifying its "
114
 
        "peer. Server closes, client waits for close.";
115
 
cinit_cnocert(suite) ->
116
 
    [];
117
 
cinit_cnocert(Config) when list(Config) ->
118
 
    process_flag(trap_exit, true),
119
 
    DataSize = 1000, LPort = 3457,
120
 
    Timeout = 40000, NConns = 1,
121
 
 
122
 
    ?line {ok, {_, SsslOpts0}} = mk_ssl_cert_opts(Config),
123
 
    ?line SsslOpts = [{verify, 0}, {depth, 2} | SsslOpts0],
124
 
 
125
 
    ?line {ok, Host} = inet:gethostname(),
126
 
 
127
 
    LCmds = [{sockopts, [{backlog, NConns}]},
128
 
             {sslopts, SsslOpts},
129
 
             {listen, LPort}, 
130
 
             wait_sync,
131
 
             lclose],
132
 
    ACmds = [{timeout, Timeout}, 
133
 
             accept,
134
 
             {recv, DataSize},
135
 
             close],
136
 
    CCmds = [{timeout, Timeout}, 
137
 
             {connect, {Host, LPort}},
138
 
             {send, DataSize},
139
 
             await_close],
140
 
    ?line test_one_listener(NConns, LCmds, ACmds, CCmds, Timeout,
141
 
                            ?MODULE, Config).
142
 
 
143