~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/public_key/test/public_key_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%<copyright>
 
2
%% <year>2008-2008</year>
 
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
 
4
%%</copyright>
 
5
%%<legalnotice>
 
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
%% The Initial Developer of the Original Code is Ericsson AB.
 
18
%%</legalnotice>
 
19
%%
 
20
-module(public_key_SUITE).
 
21
 
 
22
%% Note: This directive should only be used in test suites.
 
23
-compile(export_all).
 
24
 
 
25
-include("test_server.hrl").
 
26
-include("test_server_line.hrl").
 
27
-include("public_key.hrl").
 
28
 
 
29
-define(TIMEOUT, 120000). % 2 min
 
30
 
 
31
%% Test server callback functions
 
32
%%--------------------------------------------------------------------
 
33
%% Function: init_per_suite(Config) -> Config
 
34
%% Config - [tuple()]
 
35
%%   A list of key/value pairs, holding the test case configuration.
 
36
%% Description: Initialization before the whole suite
 
37
%%
 
38
%% Note: This function is free to add any key/value pairs to the Config
 
39
%% variable, but should NOT alter/remove any existing entries.
 
40
%%--------------------------------------------------------------------
 
41
init_per_suite(Config) ->
 
42
    crypto:start(),
 
43
    Config.
 
44
 
 
45
%%--------------------------------------------------------------------
 
46
%% Function: end_per_suite(Config) -> _
 
47
%% Config - [tuple()]
 
48
%%   A list of key/value pairs, holding the test case configuration.
 
49
%% Description: Cleanup after the whole suite
 
50
%%--------------------------------------------------------------------
 
51
end_per_suite(_Config) ->
 
52
    crypto:stop().
 
53
 
 
54
%%--------------------------------------------------------------------
 
55
%% Function: init_per_testcase(TestCase, Config) -> Config
 
56
%% Case - atom()
 
57
%%   Name of the test case that is about to be run.
 
58
%% Config - [tuple()]
 
59
%%   A list of key/value pairs, holding the test case configuration.
 
60
%%
 
61
%% Description: Initialization before each test case
 
62
%%
 
63
%% Note: This function is free to add any key/value pairs to the Config
 
64
%% variable, but should NOT alter/remove any existing entries.
 
65
%% Description: Initialization before each test case
 
66
%%--------------------------------------------------------------------
 
67
init_per_testcase(_TestCase, Config0) ->
 
68
    Config = lists:keydelete(watchdog, 1, Config0),
 
69
    Dog = test_server:timetrap(?TIMEOUT),
 
70
    [{watchdog, Dog} | Config].
 
71
 
 
72
%%--------------------------------------------------------------------
 
73
%% Function: end_per_testcase(TestCase, Config) -> _
 
74
%% Case - atom()
 
75
%%   Name of the test case that is about to be run.
 
76
%% Config - [tuple()]
 
77
%%   A list of key/value pairs, holding the test case configuration.
 
78
%% Description: Cleanup after each test case
 
79
%%--------------------------------------------------------------------
 
80
end_per_testcase(_TestCase, Config) ->
 
81
    Dog = ?config(watchdog, Config),
 
82
    case Dog of 
 
83
        undefined ->
 
84
            ok;
 
85
        _ ->
 
86
            test_server:timetrap_cancel(Dog)
 
87
    end.
 
88
 
 
89
%%--------------------------------------------------------------------
 
90
%% Function: all(Clause) -> TestCases
 
91
%% Clause - atom() - suite | doc
 
92
%% TestCases - [Case] 
 
93
%% Case - atom()
 
94
%%   Name of a test case.
 
95
%% Description: Returns a list of all test cases in this test suite
 
96
%%--------------------------------------------------------------------
 
97
all(doc) -> 
 
98
    ["Test the public_key rsa functionality"];
 
99
 
 
100
all(suite) -> 
 
101
    [pem_to_der, 
 
102
     decode_private_key
 
103
%%    encrypt_decrypt, 
 
104
%%     rsa_verify
 
105
%%      dsa_verify_sign,
 
106
%%      pkix_encode_decode,
 
107
%%      pkix_verify_sign, 
 
108
%%      pkix_path_validation
 
109
    ].
 
110
 
 
111
%% Test cases starts here.
 
112
%%--------------------------------------------------------------------
 
113
 
 
114
pem_to_der(doc) -> 
 
115
    ["Check that supported PEM files are decoded into the expected entry type"];
 
116
pem_to_der(suite) -> 
 
117
    [];
 
118
pem_to_der(Config) when is_list(Config) -> 
 
119
    Datadir = ?config(data_dir, Config),
 
120
    {ok,[{dsa_private_key, _, not_encrypted}]} = 
 
121
        public_key:pem_to_der(filename:join(Datadir, "dsa.pem")), 
 
122
    {ok,[{rsa_private_key, _, _}]} = 
 
123
        public_key:pem_to_der(filename:join(Datadir, "client_key.pem")),
 
124
    {ok,[{rsa_private_key, _, _}]} = 
 
125
        public_key:pem_to_der(filename:join(Datadir, "rsa.pem")),
 
126
    {ok,[{rsa_private_key, _, _}]} = 
 
127
        public_key:pem_to_der(filename:join(Datadir, "rsa.pem"), "abcd1234"),
 
128
    {ok,[{dh_params, _, _}]} = 
 
129
        public_key:pem_to_der(filename:join(Datadir, "dh.pem")),
 
130
    {ok,[{cert, _, not_encrypted}]} = 
 
131
        public_key:pem_to_der(filename:join(Datadir, "client_cert.pem")),
 
132
    {ok,[{cert_req, _, _}]} = 
 
133
        public_key:pem_to_der(filename:join(Datadir, "req.pem")),
 
134
    {ok,[{cert, _, _}, {cert, _, _}]} = 
 
135
        public_key:pem_to_der(filename:join(Datadir, "cacerts.pem")),
 
136
    ok.
 
137
%%--------------------------------------------------------------------
 
138
decode_private_key(doc) -> 
 
139
    ["Check that private keys are decode to the expected key type."];
 
140
decode_private_key(suite) -> 
 
141
    [];
 
142
decode_private_key(Config) when is_list(Config) -> 
 
143
    Datadir = ?config(data_dir, Config),
 
144
    {ok,[DsaKey = {dsa_private_key, _DsaKey, _}]} = 
 
145
        public_key:pem_to_der(filename:join(Datadir, "dsa.pem")), 
 
146
    {ok,[RsaKey = {rsa_private_key, _RsaKey,_}]} = 
 
147
        public_key:pem_to_der(filename:join(Datadir, "client_key.pem")),
 
148
    {ok,[ProtectedRsaKey1 = {rsa_private_key, _ProtectedRsaKey1,_}]} = 
 
149
        public_key:pem_to_der(filename:join(Datadir, "rsa.pem"), "abcd1234"),
 
150
    {ok,[ProtectedRsaKey2 = {rsa_private_key, _ProtectedRsaKey2,_}]} = 
 
151
        public_key:pem_to_der(filename:join(Datadir, "rsa.pem")),
 
152
 
 
153
    {ok, #'DSAPrivateKey'{}} = public_key:decode_private_key(DsaKey),
 
154
    {ok, #'RSAPrivateKey'{}} = public_key:decode_private_key(RsaKey),
 
155
    {ok, #'RSAPrivateKey'{}} = public_key:decode_private_key(ProtectedRsaKey1),
 
156
    {ok, #'RSAPrivateKey'{}} = public_key:decode_private_key(ProtectedRsaKey2, "abcd1234"),
 
157
    ok.
 
158
%%--------------------------------------------------------------------
 
159
encrypt_decrypt(doc) -> 
 
160
    [""];
 
161
encrypt_decrypt(suite) -> 
 
162
    [];
 
163
encrypt_decrypt(Config) when is_list(Config) -> 
 
164
    RSAPrivateKey = #'RSAPrivateKey'{publicExponent = 17,       
 
165
                                     modulus = 3233,
 
166
                                     privateExponent = 2753,
 
167
                                     prime1 = 61,
 
168
                                     prime2 = 53,
 
169
                                     version = 'two-prime'},
 
170
    Msg = <<0,123>>,   
 
171
    {ok, Encrypted} = public_key:encrypt(Msg, RSAPrivateKey, [{block_type, 2}]),
 
172
    test_server:format("Expected 855, Encrypted  ~p ~n", [Encrypted]),
 
173
    ok.
 
174
    
 
175
 
 
176
 
 
177
 
 
178
 
 
179
 
 
180
 
 
181
 
 
182
 
 
183
%%     Datadir = ?config(data_dir, Config),
 
184
%%      {ok,[{rsa_private_key, EncKey}]} = 
 
185
%%      public_key:pem_to_der(filename:join(Datadir, "server_key.pem")), 
 
186
%%     {ok, Key} = public_key:decode_private_key(EncKey, rsa),
 
187
%%     RSAPublicKey = #'RSAPublicKey'{publicExponent =
 
188
%%                                 Key#'RSAPrivateKey'.publicExponent,
 
189
%%                                 modulus = Key#'RSAPrivateKey'.modulus},
 
190
%%     {ok, Msg} = file:read_file(filename:join(Datadir, "msg.txt")),
 
191
%%     Hash = crypto:sha(Msg),
 
192
%%     {ok, Encrypted} = public_key:encrypt(Hash, Key, [{block_type, 2}]),
 
193
%%     test_server:format("Encrypted ~p", [Encrypted]),
 
194
%%     {ok, Decrypted} = public_key:decrypt(Encrypted, 
 
195
%%                                       RSAPublicKey, [{block_type, 1}]),
 
196
%%     test_server:format("Encrypted ~p", [Decrypted]),
 
197
%%     true = Encrypted == Decrypted. 
 
198
    
 
199
%%--------------------------------------------------------------------
 
200
rsa_verify(doc) -> 
 
201
    ["Cheks that we can verify an rsa signature."];
 
202
rsa_verify(suite) -> 
 
203
    [];
 
204
rsa_verify(Config) when is_list(Config) -> 
 
205
    Datadir = ?config(data_dir, Config),
 
206
    
 
207
    {ok,[{cert, DerCert}]} = 
 
208
        public_key:pem_to_der(filename:join(Datadir, "server_cert.pem")),
 
209
    
 
210
    {ok, OTPCert} = public_key:pkix_decode_cert(DerCert, otp),
 
211
    
 
212
    {0, Signature} = OTPCert#'Certificate'.signature,
 
213
    TBSCert =  OTPCert#'Certificate'.tbsCertificate,
 
214
 
 
215
    #'TBSCertificate'{subjectPublicKeyInfo = Info} = TBSCert,
 
216
    
 
217
    #'SubjectPublicKeyInfo'{subjectPublicKey = RSAPublicKey} = Info,
 
218
    
 
219
    EncTBSCert = encoded_tbs_cert(DerCert),
 
220
    Digest = crypto:sha(EncTBSCert),
 
221
 
 
222
    public_key:verify_signature(Digest, Signature, RSAPublicKey).
 
223
 
 
224
 
 
225
%% Signature is generated in the following way (in datadir):
 
226
%% openssl dgst -sha1 -binary -out rsa_signature -sign server_key.pem msg.txt
 
227
%%{ok, Signature} = file:read_file(filename:join(Datadir, "rsa_signature")),
 
228
%%{ok, Signature} = file:read_file(filename:join(Datadir, "rsa_signature")),
 
229
%% {ok, Msg} = file:read_file(filename:join(Datadir, "msg.txt")),
 
230
%% Digest = crypto:sha(Msg),
 
231
%% {ok,[{rsa_private_key, EncKey}]} = 
 
232
%%      public_key:pem_to_der(filename:join(Datadir, "server_key.pem")), 
 
233
%%    {ok, Key} = public_key:decode_private_key(EncKey, rsa),
 
234
%%    RSAPublicKey = #'RSAPublicKey'{publicExponent =
 
235
%%                                 Key#'RSAPrivateKey'.publicExponent,
 
236
%%                                 modulus = Key#'RSAPrivateKey'.modulus},
 
237
 
 
238
encoded_tbs_cert(Cert) ->
 
239
    {ok, PKIXCert} = 
 
240
        'OTP-PUB-KEY':decode_TBSCert_exclusive(Cert),
 
241
    {'Certificate',
 
242
     {'Certificate_tbsCertificate', EncodedTBSCert}, _, _} = PKIXCert,
 
243
    EncodedTBSCert.
 
244