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

« back to all changes in this revision

Viewing changes to lib/public_key/src/public_key.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
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
 
 
21
-module(public_key).
 
22
 
 
23
-include("public_key.hrl").
 
24
 
 
25
-export([decode_private_key/1, decode_private_key/2, 
 
26
         decrypt_private/2, decrypt_private/3, encrypt_public/2, 
 
27
         encrypt_public/3, decrypt_public/2, decrypt_public/3, 
 
28
         encrypt_private/2, encrypt_private/3, 
 
29
         sign/2, sign/3,
 
30
         verify_signature/3, verify_signature/4, verify_signature/5,
 
31
         pem_to_der/1, pem_to_der/2,
 
32
         pkix_decode_cert/2, pkix_encode_cert/1,
 
33
         pkix_is_self_signed/1, pkix_is_fixed_dh_cert/1,
 
34
         pkix_issuer_id/2,
 
35
         pkix_is_issuer/2, pkix_normalize_general_name/1,
 
36
         pkix_path_validation/3
 
37
        ]).
 
38
 
 
39
%%====================================================================
 
40
%% API
 
41
%%====================================================================
 
42
 
 
43
%%--------------------------------------------------------------------
 
44
%% Function: decode_private_key(KeyInfo [,Password]) -> 
 
45
%%                                     {ok, PrivateKey} | {error, Reason}
 
46
%%
 
47
%%      KeyInfo = {Type, der_bin(), ChipherInfo} - as returned from
 
48
%%      pem_to_der/[1,2] for private keys
 
49
%%      Type = rsa_private_key | dsa_private_key
 
50
%%      ChipherInfo = opaque() | no_encryption
 
51
%%
 
52
%% Description: Decodes an asn1 der encoded private key.
 
53
%%--------------------------------------------------------------------
 
54
decode_private_key(KeyInfo) ->
 
55
    decode_private_key(KeyInfo, no_passwd).
 
56
 
 
57
decode_private_key(KeyInfo = {rsa_private_key, _, _}, Password) ->
 
58
    DerEncoded = pubkey_pem:decode_key(KeyInfo, Password),
 
59
    'OTP-PUB-KEY':decode('RSAPrivateKey', DerEncoded);
 
60
decode_private_key(KeyInfo = {dsa_private_key, _, _}, Password) ->
 
61
    DerEncoded = pubkey_pem:decode_key(KeyInfo, Password),
 
62
    'OTP-PUB-KEY':decode('DSAPrivateKey', DerEncoded).
 
63
 
 
64
%%--------------------------------------------------------------------
 
65
%% Function: decrypt_private(CipherText, Key) -> 
 
66
%%           decrypt_private(CipherText, Key, Options) -> PlainTex
 
67
%%           decrypt_public(CipherText, Key) -> 
 
68
%%           decrypt_public(CipherText, Key, Options) -> PlainTex
 
69
%%
 
70
%%      CipherText = binary()
 
71
%%      Key = rsa_key()
 
72
%%      PlainText = binary()
 
73
%%
 
74
%% Description: Decrypts <CipherText>.
 
75
%%--------------------------------------------------------------------
 
76
decrypt_private(CipherText, Key) ->
 
77
    decrypt_private(CipherText, Key, []).
 
78
decrypt_private(CipherText, Key, Options)  ->
 
79
    Padding = proplists:get_value(rsa_pad, Options, rsa_pkcs1_padding),
 
80
    pubkey_crypto:decrypt_private(CipherText, Key, Padding).
 
81
 
 
82
decrypt_public(CipherText, Key) ->
 
83
    decrypt_public(CipherText, Key, []).
 
84
decrypt_public(CipherText, Key, Options)  ->
 
85
    Padding = proplists:get_value(rsa_pad, Options, rsa_pkcs1_padding),
 
86
    pubkey_crypto:decrypt_public(CipherText, Key, Padding).
 
87
 
 
88
%%--------------------------------------------------------------------
 
89
%% Function: encrypt_public(PlainText, Key, Options) -> CipherText
 
90
%%           encrypt_private(PlainText, Key, Options) -> CipherText
 
91
%%
 
92
%%      PlainText = iolist()
 
93
%%      Key = rsa_private_key()
 
94
%%      CipherText = binary()
 
95
%%
 
96
%% Description: Encrypts <Plain>
 
97
%%--------------------------------------------------------------------
 
98
encrypt_public(PlainText, Key) ->
 
99
    encrypt_public(PlainText, Key, []).
 
100
encrypt_public(PlainText, Key, Options)  ->
 
101
    Padding = proplists:get_value(rsa_pad, Options, rsa_pkcs1_oaep_padding),
 
102
    pubkey_crypto:encrypt_public(PlainText, Key, Padding).
 
103
 
 
104
encrypt_private(PlainText, Key) ->
 
105
    encrypt_private(PlainText, Key, []).
 
106
encrypt_private(PlainText, Key, Options)  ->
 
107
    Padding = proplists:get_value(rsa_pad, Options, rsa_pkcs1_oaep_padding),
 
108
    pubkey_crypto:encrypt_private(PlainText, Key, Padding).
 
109
 
 
110
%%--------------------------------------------------------------------
 
111
%% Function: pem_to_der(File) ->
 
112
%%           pem_to_der(File, Password) -> {ok, [Entry]} | {error, Reason}
 
113
%%
 
114
%%      File = path()
 
115
%%      Password = string()
 
116
%%      Entry = {entry_type(), der_bin(), ChipherInfo}
 
117
%%      ChipherInfo = opague() | no_encryption
 
118
%%      der_bin() = binary()
 
119
%%      entry_type() = cert | cert_req | rsa_private_key | dsa_private_key
 
120
%%      dh_params
 
121
%%
 
122
%% Description: Read and decode PEM file and returns entries as asn1
 
123
%% der encoded entities. Currently supported entry types are
 
124
%% certificates, certificate requests, rsa private keys and dsa
 
125
%% private keys. In the case of a key entry ChipherInfo will be
 
126
%% used by decode_private_key/2 if the key is protected by a password.
 
127
%%--------------------------------------------------------------------
 
128
pem_to_der(File) ->
 
129
    pubkey_pem:read_file(File).
 
130
 
 
131
pem_to_der(File, Password) ->
 
132
    pubkey_pem:read_file(File, Password).
 
133
 
 
134
%%--------------------------------------------------------------------
 
135
%% Function: pkix_decode_cert(BerCert, Type) -> {ok, Cert} | {error, Reason}
 
136
%%
 
137
%%      BerCert = binary()
 
138
%%      Type = plain | otp
 
139
%%      Cert = certificate()
 
140
%%
 
141
%% Description:  Decodes an asn1 ber encoded pkix certificate.
 
142
%% otp - Uses OTP-PKIX.asn1 to decode known extensions and
 
143
%% enhance the signature field in #'Certificate'{} and '#TBSCertificate'{}. 
 
144
%%--------------------------------------------------------------------
 
145
pkix_decode_cert(BinCert, Type) ->
 
146
    pubkey_cert_records:decode_cert(BinCert, Type).
 
147
 
 
148
%%--------------------------------------------------------------------
 
149
%% Function: pkix_encode_cert(Cert) -> {ok, binary()} | {error, Reason}
 
150
%%
 
151
%%      Cert = #'Certificate'{} 
 
152
%%
 
153
%% Description: Encodes a certificate record using asn1.
 
154
%%--------------------------------------------------------------------
 
155
pkix_encode_cert(Cert) ->
 
156
    pubkey_cert_records:encode_cert(Cert).
 
157
    
 
158
%%--------------------------------------------------------------------
 
159
%% Function: pkix_path_validation(TrustedCert, CertChain, Options) -> 
 
160
%%   {ok, {{algorithm(), public_key(), public_key_params()} policy_tree()}} |
 
161
%%   {error, Reason}
 
162
%%
 
163
%% Description: Performs a bacis path validation according to RFC 3280.
 
164
%%--------------------------------------------------------------------
 
165
pkix_path_validation(TrustedCert, CertChain, Options)
 
166
  when is_binary(TrustedCert) ->
 
167
    {ok, OtpCert} = pkix_decode_cert(TrustedCert, otp),
 
168
    pkix_path_validation(OtpCert, CertChain, Options);
 
169
 
 
170
pkix_path_validation(#'OTPCertificate'{} = TrustedCert, CertChain, Options) 
 
171
  when is_list(CertChain), is_list(Options) ->
 
172
    MaxPathDefault = length(CertChain),
 
173
    ValidationState = pubkey_cert:init_validation_state(TrustedCert, 
 
174
                                                        MaxPathDefault, 
 
175
                                                        Options),
 
176
    Fun = proplists:get_value(validate_extensions_fun, Options,
 
177
                              fun(Extensions, State, _, AccError) ->
 
178
                                      {Extensions, State, AccError}
 
179
                              end),
 
180
    Verify = proplists:get_value(verify, Options, true),
 
181
    path_validation(CertChain, ValidationState, Fun, Verify).
 
182
%%--------------------------------------------------------------------
 
183
%% Function: pkix_is_fixed_dh_cert(Cert) -> true | false
 
184
%%
 
185
%% Description: Checks if a Certificate is a fixed Diffie-Hellman Cert
 
186
%%--------------------------------------------------------------------
 
187
pkix_is_fixed_dh_cert(#'OTPCertificate'{} = OTPCert) ->
 
188
    pubkey_cert:is_fixed_dh_cert(OTPCert);
 
189
pkix_is_fixed_dh_cert(Cert) when is_binary(Cert) ->
 
190
    {ok, OtpCert} = pkix_decode_cert(Cert, otp),
 
191
    pkix_is_fixed_dh_cert(OtpCert).
 
192
 
 
193
%%--------------------------------------------------------------------
 
194
%% Function: pkix_is_self_signed(Cert) -> true | false
 
195
%%
 
196
%% Description: Checks if a Certificate is self signed. 
 
197
%%--------------------------------------------------------------------
 
198
pkix_is_self_signed(#'OTPCertificate'{} = OTPCert) ->
 
199
    pubkey_cert:is_self_signed(OTPCert);
 
200
pkix_is_self_signed(Cert) when is_binary(Cert) ->
 
201
    {ok, OtpCert} = pkix_decode_cert(Cert, otp),
 
202
    pkix_is_self_signed(OtpCert).
 
203
 
 
204
%%--------------------------------------------------------------------
 
205
%% Function: pkix_issuer_id(Cert) -> {ok, {SerialNr, Issuer}} | {error, Reason}
 
206
%%                                     
 
207
%%      Cert = asn1_der_encoded() | 'OTPCertificate'{}
 
208
%%
 
209
%% Description: Returns the issuer id.  
 
210
%%--------------------------------------------------------------------
 
211
pkix_issuer_id(#'OTPCertificate'{} = OtpCert, self) ->
 
212
    pubkey_cert:issuer_id(OtpCert, self);
 
213
 
 
214
pkix_issuer_id(#'OTPCertificate'{} = OtpCert, other) ->
 
215
    pubkey_cert:issuer_id(OtpCert, other);
 
216
 
 
217
pkix_issuer_id(Cert, Signed) when is_binary(Cert) ->
 
218
    {ok, OtpCert} = pkix_decode_cert(Cert, otp),
 
219
    pkix_issuer_id(OtpCert, Signed).
 
220
 
 
221
%%--------------------------------------------------------------------
 
222
%% Function: pkix_is_issuer(Cert, IssuerCert) -> true | false
 
223
%%
 
224
%%      Cert = asn1_der_encoded() | 'OTPCertificate'{}
 
225
%%      IssuerCert = asn1_der_encoded() | 'OTPCertificate'{}
 
226
%%
 
227
%% Description: Checks if <IssuerCert> issued <Cert>.
 
228
%%--------------------------------------------------------------------
 
229
pkix_is_issuer(Cert, IssuerCert)  when is_binary(Cert) ->
 
230
    {ok, OtpCert} = pkix_decode_cert(Cert, otp),
 
231
    pkix_is_issuer(OtpCert, IssuerCert);
 
232
 
 
233
pkix_is_issuer(Cert, IssuerCert) when is_binary(IssuerCert) ->
 
234
    {ok, OtpIssuerCert} = pkix_decode_cert(IssuerCert, otp),
 
235
    pkix_is_issuer(Cert, OtpIssuerCert);
 
236
 
 
237
pkix_is_issuer(#'OTPCertificate'{tbsCertificate = TBSCert}, 
 
238
               #'OTPCertificate'{tbsCertificate = Candidate}) ->
 
239
    pubkey_cert:is_issuer(TBSCert#'OTPTBSCertificate'.issuer,
 
240
                          Candidate#'OTPTBSCertificate'.subject).
 
241
    
 
242
%%--------------------------------------------------------------------
 
243
%% Function: pkix_normalize_general_name(Issuer) -> 
 
244
%%
 
245
%%      Issuer = general_name() - see PKIX
 
246
%%   
 
247
%% Description: Normalizes a general name so that it can be easily
 
248
%%              compared to another genral name. 
 
249
%%--------------------------------------------------------------------
 
250
pkix_normalize_general_name(Issuer) -> 
 
251
    pubkey_cert:normalize_general_name(Issuer).
 
252
 
 
253
%%--------------------------------------------------------------------
 
254
%% Function:sign(Msg, Key) -> {ok, Signature} 
 
255
%%          sign(Msg, Key, KeyParams) -> {ok, Signature}
 
256
%%
 
257
%%      Msg = binary() | #'TBSCertificate'{}
 
258
%%      Key = private_key()
 
259
%%      KeyParams = key_params()
 
260
%%      Signature = binary()
 
261
%%
 
262
%% Description: Signs plaintext Msg or #TBSCertificate{}, in the later
 
263
%%              case a der encoded "#Certificate{}" will be returned. 
 
264
%%--------------------------------------------------------------------
 
265
sign(Msg, #'RSAPrivateKey'{} = Key) when is_binary(Msg) -> 
 
266
    pubkey_crypto:sign(Msg, Key);
 
267
 
 
268
sign(Msg, #'DSAPrivateKey'{} = Key) when is_binary(Msg) ->
 
269
    pubkey_crypto:sign(Msg, Key);
 
270
 
 
271
sign(#'OTPTBSCertificate'{signature = SigAlg} = TBSCert, Key) ->
 
272
    Msg = pubkey_cert_records:encode_tbs_cert(TBSCert),
 
273
    DigestType = pubkey_cert:digest_type(SigAlg),
 
274
    Signature = pubkey_crypto:sign(DigestType, Msg, Key),
 
275
    Cert = #'OTPCertificate'{tbsCertificate= TBSCert,
 
276
                             signatureAlgorithm = SigAlg,
 
277
                             signature = {0, Signature}
 
278
                            },
 
279
    pkix_encode_cert(Cert).
 
280
 
 
281
sign(DigestType, Msg, Key) ->
 
282
    pubkey_crypto:sign(DigestType, Msg, Key).
 
283
 
 
284
%%--------------------------------------------------------------------
 
285
%% Function: verify_signature(PlainText, DigestType, Signature, Key) ->
 
286
%%           verify_signature(PlainText, DigestType,
 
287
%%                                       Signature, Key, KeyParams) -> 
 
288
%%           verify_signature(DerCert, Key, KeyParams) ->
 
289
%%
 
290
%%      PlainText = binary()
 
291
%%      DigestType = md5 | sha
 
292
%%      DerCert = asn1_der_encoded()
 
293
%%      Signature = binary()
 
294
%%      Key = public_key()
 
295
%%      KeyParams = key_params()
 
296
%%      Verified = boolean()
 
297
%%
 
298
%% Description: Verifies the signature <Signature>.
 
299
%%--------------------------------------------------------------------
 
300
verify_signature(PlainText, DigestType, Signature, #'RSAPublicKey'{} = Key)
 
301
  when is_binary(PlainText), is_binary(Signature), DigestType == sha;
 
302
       DigestType == md5 ->
 
303
    pubkey_crypto:verify(DigestType, PlainText, Signature, Key, undefined).
 
304
 
 
305
verify_signature(PlainText, DigestType, Signature, #'RSAPublicKey'{} = Key,
 
306
                 KeyParams) 
 
307
  when is_binary(PlainText), is_binary(Signature), DigestType == sha;
 
308
       DigestType == md5 ->
 
309
    pubkey_crypto:verify(DigestType, PlainText, Signature, Key, KeyParams);
 
310
verify_signature(PlainText, sha, Signature, Key, #'Dss-Parms'{} = KeyParams) 
 
311
  when is_binary(PlainText), is_binary(Signature), is_integer(Key) ->
 
312
    pubkey_crypto:verify(sha, PlainText, Signature, Key, KeyParams).
 
313
 
 
314
verify_signature(DerCert, Key, #'Dss-Parms'{} = KeyParams) 
 
315
  when is_binary(DerCert), is_integer(Key) ->
 
316
    pubkey_cert:verify_signature(DerCert, Key, KeyParams);
 
317
verify_signature(DerCert,  #'RSAPublicKey'{} = Key, KeyParams) 
 
318
  when is_binary(DerCert) ->
 
319
    pubkey_cert:verify_signature(DerCert, Key, KeyParams).
 
320
 
 
321
%%--------------------------------------------------------------------
 
322
%%% Internal functions
 
323
%%--------------------------------------------------------------------
 
324
path_validation([], #path_validation_state{working_public_key_algorithm
 
325
                                           = Algorithm,
 
326
                                           working_public_key =
 
327
                                           PublicKey,
 
328
                                           working_public_key_parameters 
 
329
                                           = PublicKeyParams,
 
330
                                           valid_policy_tree = Tree,
 
331
                                           acc_errors = AccErrors
 
332
                                          }, _, _) ->
 
333
    {ok, {{Algorithm, PublicKey, PublicKeyParams}, Tree, AccErrors}};
 
334
 
 
335
path_validation([DerCert | Rest], ValidationState = #path_validation_state{
 
336
                                    max_path_length = Len}, 
 
337
                Fun, Verify) when Len >= 0 ->
 
338
    
 
339
    try validate(DerCert, 
 
340
                 ValidationState#path_validation_state{last_cert=Rest=:=[]}, 
 
341
                 Fun, Verify) of 
 
342
        #path_validation_state{} = NewValidationState ->
 
343
            path_validation(Rest, NewValidationState, Fun, Verify)
 
344
    catch   
 
345
        throw:Reason ->
 
346
            {error, Reason}
 
347
    end;
 
348
 
 
349
path_validation(_, _, _, verify_peer) ->
 
350
    {error, {bad_cert, max_path_length_reached}};
 
351
 
 
352
path_validation(_, #path_validation_state{working_public_key_algorithm
 
353
                                           = Algorithm,
 
354
                                           working_public_key =
 
355
                                           PublicKey,
 
356
                                           working_public_key_parameters 
 
357
                                           = PublicKeyParams,
 
358
                                          valid_policy_tree = Tree,
 
359
                                          acc_errors = AccErrors
 
360
                                        }, _, verify_none) ->
 
361
    {ok, {{Algorithm, PublicKey, PublicKeyParams}, Tree, AccErrors}}.
 
362
 
 
363
validate(DerCert, #path_validation_state{working_issuer_name = Issuer,
 
364
                                         working_public_key = Key,
 
365
                                         working_public_key_parameters = 
 
366
                                         KeyParams, 
 
367
                                         permitted_subtrees = Permit,
 
368
                                         excluded_subtrees = Exclude,
 
369
                                         last_cert = Last,
 
370
                                         user_state = UserState0,
 
371
                                         acc_errors = AccErr0} = 
 
372
         ValidationState0, ValidateExtensionFun, Verify) -> 
 
373
    {ok, OtpCert} = pkix_decode_cert(DerCert, otp),
 
374
    %% All validate functions will throw {bad_cert, Reason} if they 
 
375
    %% fail and Verify = true if Verify = false errors
 
376
    %% will be accumulated in the validationstate 
 
377
    AccErr1 = pubkey_cert:validate_time(OtpCert, AccErr0, Verify),
 
378
    AccErr2 = 
 
379
        pubkey_cert:validate_signature(OtpCert, DerCert, Key, KeyParams,
 
380
                                       AccErr1, Verify),
 
381
    AccErr3 = pubkey_cert:validate_issuer(OtpCert, Issuer, AccErr2, Verify),
 
382
 
 
383
    AccErr4 = pubkey_cert:validate_names(OtpCert, Permit, Exclude, Last,
 
384
                                         AccErr3, Verify),
 
385
    AccErr5 = 
 
386
        pubkey_cert:validate_revoked_status(OtpCert, Verify, AccErr4),
 
387
    
 
388
    {ValidationState1, UnknownExtensions0, AccErr6} = 
 
389
        pubkey_cert:validate_extensions(OtpCert, ValidationState0, Verify,
 
390
                                        AccErr5),
 
391
    
 
392
    {UnknownExtensions, UserState, AccErr7} = 
 
393
        ValidateExtensionFun(UnknownExtensions0, UserState0, Verify, AccErr6),
 
394
   
 
395
    %% Check that all critical extensions have been handled 
 
396
    AccErr = 
 
397
        pubkey_cert:validate_unknown_extensions(UnknownExtensions, AccErr7, 
 
398
                                                Verify),
 
399
    ValidationState  = 
 
400
        ValidationState1#path_validation_state{user_state = UserState,
 
401
                                               acc_errors = AccErr},
 
402
    pubkey_cert:prepare_for_next_cert(OtpCert, ValidationState).