~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/ssl/src/ssl_certificate.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2007-2010. All Rights Reserved.
 
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
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
 
28
28
-include("ssl_handshake.hrl").
29
29
-include("ssl_alert.hrl").
30
30
-include("ssl_internal.hrl").
31
 
-include("ssl_debug.hrl").
 
31
-include_lib("public_key/include/public_key.hrl"). 
32
32
 
33
 
-export([trusted_cert_and_path/3, 
 
33
-export([trusted_cert_and_path/2,
34
34
         certificate_chain/2, 
35
 
         file_to_certificats/1]).
 
35
         file_to_certificats/1,
 
36
         validate_extension/3,
 
37
         is_valid_extkey_usage/2,
 
38
         is_valid_key_usage/2,
 
39
         select_extension/2,
 
40
         extensions_list/1,
 
41
         signature_type/1
 
42
        ]).
36
43
 
37
44
%%====================================================================
38
45
%% Internal application API
39
46
%%====================================================================
40
47
 
41
 
trusted_cert_and_path(CertChain, CertDbRef, Verify) ->
42
 
    [Cert | RestPath] = lists:reverse(CertChain),
43
 
    {ok, OtpCert} = public_key:pkix_decode_cert(Cert, otp),
44
 
    IssuerAnPath = 
 
48
%%--------------------------------------------------------------------
 
49
-spec trusted_cert_and_path([der_cert()], certdb_ref()) ->
 
50
                                   {der_cert() | unknown_ca, [der_cert()]}.
 
51
%%
 
52
%% Description: Extracts the root cert (if not presents tries to 
 
53
%% look it up, if not found {bad_cert, unknown_ca} will be added verification
 
54
%% errors. Returns {RootCert, Path, VerifyErrors}
 
55
%%--------------------------------------------------------------------
 
56
trusted_cert_and_path(CertChain, CertDbRef) ->
 
57
    Path = [Cert | _] = lists:reverse(CertChain),
 
58
    OtpCert = public_key:pkix_decode_cert(Cert, otp),
 
59
    SignedAndIssuerID =
45
60
        case public_key:pkix_is_self_signed(OtpCert) of
46
61
            true ->
47
62
                {ok, IssuerId} = public_key:pkix_issuer_id(OtpCert, self),
48
 
                {IssuerId, RestPath};
49
 
            false  ->
 
63
                {self, IssuerId};
 
64
            false ->
50
65
                case public_key:pkix_issuer_id(OtpCert, other) of
51
66
                    {ok, IssuerId} ->
52
 
                        {IssuerId, [Cert | RestPath]};
 
67
                        {other, IssuerId};
53
68
                    {error, issuer_not_found} ->
54
69
                        case find_issuer(OtpCert, no_candidate) of
55
70
                            {ok, IssuerId} ->
56
 
                                {IssuerId, [Cert | RestPath]};
 
71
                                {other, IssuerId};
57
72
                            Other ->
58
 
                                {Other, RestPath}
 
73
                                Other
59
74
                        end
60
75
                end
61
76
        end,
62
77
    
63
 
    case IssuerAnPath of
64
 
        {{error, issuer_not_found}, _ } ->
65
 
            %% The root CA was not sent and can not be found, we fail if verify = true
66
 
            not_valid(?ALERT_REC(?FATAL, ?UNKNOWN_CA), Verify, {Cert, RestPath});
67
 
        {{SerialNr, Issuer}, Path} ->
68
 
            case ssl_certificate_db:lookup_trusted_cert(CertDbRef, 
69
 
                                                        SerialNr, Issuer) of
 
78
    case SignedAndIssuerID of
 
79
        {error, issuer_not_found} ->
 
80
            %% The root CA was not sent and can not be found.
 
81
            {unknown_ca, Path};
 
82
        {self, _} when length(Path) == 1 ->
 
83
            {selfsigned_peer, Path};
 
84
        {_ ,{SerialNr, Issuer}} ->
 
85
            case ssl_manager:lookup_trusted_cert(CertDbRef, SerialNr, Issuer) of
70
86
                {ok, {BinCert,_}} ->
71
 
                    {BinCert, Path, []};
 
87
                    {BinCert, Path};
72
88
                _ ->
73
 
                    %%  Fail if verify = true
74
 
                    not_valid(?ALERT_REC(?FATAL, ?UNKNOWN_CA),
75
 
                             Verify,  {Cert, RestPath})
 
89
                    %% Root CA could not be verified
 
90
                    {unknown_ca, Path}
76
91
            end
77
92
    end.
78
93
 
79
 
 
 
94
%%--------------------------------------------------------------------
 
95
-spec certificate_chain(undefined | binary(), certdb_ref()) -> 
 
96
                          {error, no_cert} | {ok, [der_cert()]}.
 
97
%%
 
98
%% Description: Return the certificate chain to send to peer.
 
99
%%--------------------------------------------------------------------
80
100
certificate_chain(undefined, _CertsDbRef) ->
81
101
    {error, no_cert};
82
102
certificate_chain(OwnCert, CertsDbRef) ->
83
 
    {ok, ErlCert} = public_key:pkix_decode_cert(OwnCert, otp),
 
103
    ErlCert = public_key:pkix_decode_cert(OwnCert, otp),
84
104
    certificate_chain(ErlCert, OwnCert, CertsDbRef, [OwnCert]).
85
 
 
86
 
file_to_certificats(File) ->
 
105
%%--------------------------------------------------------------------
 
106
-spec file_to_certificats(string()) -> [der_cert()].
 
107
%%
 
108
%% Description: Return list of DER encoded certificates.
 
109
%%--------------------------------------------------------------------
 
110
file_to_certificats(File) -> 
87
111
    {ok, List} = ssl_manager:cache_pem_file(File),
88
 
    [Bin || {cert, Bin, not_encrypted} <- List].
 
112
    [Bin || {'Certificate', Bin, not_encrypted} <- List].
 
113
%%--------------------------------------------------------------------
 
114
-spec validate_extension(term(), #'Extension'{} | {bad_cert, atom()} | valid,
 
115
                         term()) -> {valid, term()} |
 
116
                                    {fail, tuple()} |
 
117
                                    {unknown, term()}.
 
118
%%
 
119
%% Description:  Validates ssl/tls specific extensions
 
120
%%--------------------------------------------------------------------
 
121
validate_extension(_,{extension, #'Extension'{extnID = ?'id-ce-extKeyUsage',
 
122
                                              extnValue = KeyUse}}, Role) ->
 
123
    case is_valid_extkey_usage(KeyUse, Role) of
 
124
        true ->
 
125
            {valid, Role};
 
126
        false ->
 
127
            {fail, {bad_cert, invalid_ext_key_usage}}
 
128
    end;
 
129
validate_extension(_, {bad_cert, _} = Reason, _) ->
 
130
    {fail, Reason};
 
131
validate_extension(_, {extension, _}, Role) ->
 
132
    {unknown, Role};
 
133
validate_extension(_, valid, Role) ->
 
134
    {valid, Role};
 
135
validate_extension(_, valid_peer, Role) ->
 
136
    {valid, Role}.
 
137
 
 
138
%%--------------------------------------------------------------------
 
139
-spec is_valid_key_usage(list(), term()) -> boolean().
 
140
%%
 
141
%% Description: Checks if Use is a valid key usage.
 
142
%%--------------------------------------------------------------------
 
143
is_valid_key_usage(KeyUse, Use) ->
 
144
    lists:member(Use, KeyUse).
 
145
 
 
146
%%--------------------------------------------------------------------
 
147
-spec select_extension(term(), list()) -> undefined | #'Extension'{}.
 
148
%%
 
149
%% Description: Selects the extension identified by Id if present in
 
150
%% a list of extensions.
 
151
%%--------------------------------------------------------------------
 
152
select_extension(_, []) ->
 
153
    undefined;
 
154
select_extension(Id, [#'Extension'{extnID = Id} = Extension | _]) ->
 
155
    Extension;
 
156
select_extension(Id, [_ | Extensions]) ->
 
157
    select_extension(Id, Extensions).
 
158
 
 
159
%%--------------------------------------------------------------------
 
160
-spec extensions_list(asn1_NOVALUE | list()) -> list().
 
161
%%
 
162
%% Description: Handles that 
 
163
%%--------------------------------------------------------------------
 
164
extensions_list(asn1_NOVALUE) ->
 
165
    [];
 
166
extensions_list(Extensions) ->
 
167
    Extensions.
 
168
 
 
169
%%--------------------------------------------------------------------
 
170
-spec signature_type(term()) -> rsa | dsa .
 
171
%%
 
172
%% Description: 
 
173
%%--------------------------------------------------------------------
 
174
signature_type(RSA) when RSA == ?sha1WithRSAEncryption;
 
175
                         RSA == ?md5WithRSAEncryption ->
 
176
    rsa;
 
177
signature_type(?'id-dsa-with-sha1') ->
 
178
    dsa.
89
179
 
90
180
%%--------------------------------------------------------------------
91
181
%%% Internal functions
122
212
    {ok, lists:reverse(Chain)};
123
213
 
124
214
certificate_chain(CertsDbRef, Chain, SerialNr, Issuer, _SelfSigned) ->
125
 
    case ssl_certificate_db:lookup_trusted_cert(CertsDbRef, 
 
215
    case ssl_manager:lookup_trusted_cert(CertsDbRef, 
126
216
                                                SerialNr, Issuer) of
127
217
        {ok, {IssuerCert, ErlCert}} ->
128
 
            {ok, ErlCert} = public_key:pkix_decode_cert(IssuerCert, otp),
 
218
            ErlCert = public_key:pkix_decode_cert(IssuerCert, otp),
129
219
            certificate_chain(ErlCert, IssuerCert, 
130
220
                              CertsDbRef, [IssuerCert | Chain]);
131
221
        _ ->
138
228
    end.
139
229
 
140
230
find_issuer(OtpCert, PrevCandidateKey) ->
141
 
    case ssl_certificate_db:issuer_candidate(PrevCandidateKey) of
 
231
    case ssl_manager:issuer_candidate(PrevCandidateKey) of
142
232
        no_more_candidates ->
143
233
            {error, issuer_not_found};
144
234
        {Key, {_Cert, ErlCertCandidate}} ->
150
240
            end
151
241
    end.
152
242
 
153
 
not_valid(Alert, true, _) ->
154
 
    throw(Alert);
155
 
not_valid(_, false, {ErlCert, Path}) ->
156
 
    {ErlCert, Path, [{bad_cert, unknown_ca}]}.
 
243
is_valid_extkey_usage(KeyUse, client) ->
 
244
    %% Client wants to verify server
 
245
    is_valid_key_usage(KeyUse,?'id-kp-serverAuth');
 
246
is_valid_extkey_usage(KeyUse, server) ->
 
247
    %% Server wants to verify client
 
248
    is_valid_key_usage(KeyUse, ?'id-kp-clientAuth').