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

« back to all changes in this revision

Viewing changes to lib/ssl/src/ssl_certificate.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
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 2007-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2007-2011. All Rights Reserved.
5
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
30
30
-include("ssl_internal.hrl").
31
31
-include_lib("public_key/include/public_key.hrl"). 
32
32
 
33
 
-export([trusted_cert_and_path/2,
34
 
         certificate_chain/2, 
35
 
         file_to_certificats/1,
 
33
-export([trusted_cert_and_path/3,
 
34
         certificate_chain/3,
 
35
         file_to_certificats/2,
36
36
         validate_extension/3,
37
37
         is_valid_extkey_usage/2,
38
38
         is_valid_key_usage/2,
46
46
%%====================================================================
47
47
 
48
48
%%--------------------------------------------------------------------
49
 
-spec trusted_cert_and_path([der_cert()], certdb_ref()) ->
 
49
-spec trusted_cert_and_path([der_cert()], db_handle(), certdb_ref()) ->
50
50
                                   {der_cert() | unknown_ca, [der_cert()]}.
51
51
%%
52
52
%% Description: Extracts the root cert (if not presents tries to 
53
53
%% look it up, if not found {bad_cert, unknown_ca} will be added verification
54
54
%% errors. Returns {RootCert, Path, VerifyErrors}
55
55
%%--------------------------------------------------------------------
56
 
trusted_cert_and_path(CertChain, CertDbRef) ->
 
56
trusted_cert_and_path(CertChain, CertDbHandle, CertDbRef) ->
57
57
    Path = [Cert | _] = lists:reverse(CertChain),
58
58
    OtpCert = public_key:pkix_decode_cert(Cert, otp),
59
59
    SignedAndIssuerID =
66
66
                    {ok, IssuerId} ->
67
67
                        {other, IssuerId};
68
68
                    {error, issuer_not_found} ->
69
 
                        case find_issuer(OtpCert, no_candidate) of
 
69
                        case find_issuer(OtpCert, CertDbHandle) of
70
70
                            {ok, IssuerId} ->
71
71
                                {other, IssuerId};
72
72
                            Other ->
82
82
        {self, _} when length(Path) == 1 ->
83
83
            {selfsigned_peer, Path};
84
84
        {_ ,{SerialNr, Issuer}} ->
85
 
            case ssl_manager:lookup_trusted_cert(CertDbRef, SerialNr, Issuer) of
 
85
            case ssl_manager:lookup_trusted_cert(CertDbHandle, CertDbRef, SerialNr, Issuer) of
86
86
                {ok, {BinCert,_}} ->
87
87
                    {BinCert, Path};
88
88
                _ ->
92
92
    end.
93
93
 
94
94
%%--------------------------------------------------------------------
95
 
-spec certificate_chain(undefined | binary(), certdb_ref()) -> 
 
95
-spec certificate_chain(undefined | binary(), db_handle(), certdb_ref()) ->
96
96
                          {error, no_cert} | {ok, [der_cert()]}.
97
97
%%
98
98
%% Description: Return the certificate chain to send to peer.
99
99
%%--------------------------------------------------------------------
100
 
certificate_chain(undefined, _CertsDbRef) ->
 
100
certificate_chain(undefined, _, _) ->
101
101
    {error, no_cert};
102
 
certificate_chain(OwnCert, CertsDbRef) ->
 
102
certificate_chain(OwnCert, CertDbHandle, CertsDbRef) ->
103
103
    ErlCert = public_key:pkix_decode_cert(OwnCert, otp),
104
 
    certificate_chain(ErlCert, OwnCert, CertsDbRef, [OwnCert]).
 
104
    certificate_chain(ErlCert, OwnCert, CertDbHandle, CertsDbRef, [OwnCert]).
105
105
%%--------------------------------------------------------------------
106
 
-spec file_to_certificats(string()) -> [der_cert()].
 
106
-spec file_to_certificats(string(), term()) -> [der_cert()].
107
107
%%
108
108
%% Description: Return list of DER encoded certificates.
109
109
%%--------------------------------------------------------------------
110
 
file_to_certificats(File) -> 
111
 
    {ok, List} = ssl_manager:cache_pem_file(File),
 
110
file_to_certificats(File, DbHandle) ->
 
111
    {ok, List} = ssl_manager:cache_pem_file(File, DbHandle),
112
112
    [Bin || {'Certificate', Bin, not_encrypted} <- List].
113
113
%%--------------------------------------------------------------------
114
114
-spec validate_extension(term(), #'Extension'{} | {bad_cert, atom()} | valid,
180
180
%%--------------------------------------------------------------------
181
181
%%% Internal functions
182
182
%%--------------------------------------------------------------------
183
 
certificate_chain(OtpCert, _Cert, CertsDbRef, Chain) ->    
 
183
certificate_chain(OtpCert, _Cert, CertDbHandle, CertsDbRef, Chain) ->
184
184
    IssuerAndSelfSigned = 
185
185
        case public_key:pkix_is_self_signed(OtpCert) of
186
186
            true ->
191
191
    
192
192
    case IssuerAndSelfSigned of 
193
193
        {_, true = SelfSigned} ->
194
 
            certificate_chain(CertsDbRef, Chain, ignore, ignore, SelfSigned);
 
194
            certificate_chain(CertDbHandle, CertsDbRef, Chain, ignore, ignore, SelfSigned);
195
195
        {{error, issuer_not_found}, SelfSigned} ->
196
 
            case find_issuer(OtpCert, no_candidate) of
 
196
            case find_issuer(OtpCert, CertDbHandle) of
197
197
                {ok, {SerialNr, Issuer}} ->
198
 
                    certificate_chain(CertsDbRef, Chain, 
 
198
                    certificate_chain(CertDbHandle, CertsDbRef, Chain,
199
199
                                      SerialNr, Issuer, SelfSigned);
200
200
                _ ->
201
201
                    %% Guess the the issuer must be the root
205
205
                    {ok, lists:reverse(Chain)}
206
206
            end;
207
207
        {{ok, {SerialNr, Issuer}}, SelfSigned} -> 
208
 
            certificate_chain(CertsDbRef, Chain, SerialNr, Issuer, SelfSigned)
 
208
            certificate_chain(CertDbHandle, CertsDbRef, Chain, SerialNr, Issuer, SelfSigned)
209
209
    end.
210
210
  
211
 
certificate_chain(_CertsDbRef, Chain, _SerialNr, _Issuer, true) ->
 
211
certificate_chain(_,_, Chain, _SerialNr, _Issuer, true) ->
212
212
    {ok, lists:reverse(Chain)};
213
213
 
214
 
certificate_chain(CertsDbRef, Chain, SerialNr, Issuer, _SelfSigned) ->
215
 
    case ssl_manager:lookup_trusted_cert(CertsDbRef, 
 
214
certificate_chain(CertDbHandle, CertsDbRef, Chain, SerialNr, Issuer, _SelfSigned) ->
 
215
    case ssl_manager:lookup_trusted_cert(CertDbHandle, CertsDbRef,
216
216
                                                SerialNr, Issuer) of
217
217
        {ok, {IssuerCert, ErlCert}} ->
218
218
            ErlCert = public_key:pkix_decode_cert(IssuerCert, otp),
219
219
            certificate_chain(ErlCert, IssuerCert, 
220
 
                              CertsDbRef, [IssuerCert | Chain]);
 
220
                              CertDbHandle, CertsDbRef, [IssuerCert | Chain]);
221
221
        _ ->
222
222
            %% The trusted cert may be obmitted from the chain as the
223
223
            %% counter part needs to have it anyway to be able to
227
227
            {ok, lists:reverse(Chain)}                
228
228
    end.
229
229
 
230
 
find_issuer(OtpCert, PrevCandidateKey) ->
231
 
    case ssl_manager:issuer_candidate(PrevCandidateKey) of
232
 
        no_more_candidates ->
233
 
            {error, issuer_not_found};
234
 
        {Key, {_Cert, ErlCertCandidate}} ->
235
 
            case public_key:pkix_is_issuer(OtpCert, ErlCertCandidate) of
236
 
                true ->
237
 
                    public_key:pkix_issuer_id(ErlCertCandidate, self);
238
 
                false ->
239
 
                    find_issuer(OtpCert, Key)
240
 
            end
 
230
find_issuer(OtpCert, CertDbHandle) ->
 
231
    IsIssuerFun = fun({_Key, {_Der, #'OTPCertificate'{} = ErlCertCandidate}}, Acc) ->
 
232
                          case public_key:pkix_is_issuer(OtpCert, ErlCertCandidate) of
 
233
                              true ->
 
234
                                  throw(public_key:pkix_issuer_id(ErlCertCandidate, self));
 
235
                              false ->
 
236
                                  Acc
 
237
                          end;
 
238
                     (_, Acc) ->
 
239
                          Acc
 
240
                  end,
 
241
 
 
242
    try ssl_certificate_db:foldl(IsIssuerFun, issuer_not_found, CertDbHandle) of
 
243
        issuer_not_found ->
 
244
            {error, issuer_not_found}
 
245
    catch 
 
246
        {ok, _IssuerId} = Return ->
 
247
            Return
241
248
    end.
242
249
 
243
250
is_valid_extkey_usage(KeyUse, client) ->