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

« back to all changes in this revision

Viewing changes to lib/ssl/src/ssl_certificate_db.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-2011. 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
 
22
22
%%----------------------------------------------------------------------
23
23
 
24
24
-module(ssl_certificate_db).
25
 
 
 
25
-include("ssl_internal.hrl").
26
26
-include_lib("public_key/include/public_key.hrl").
27
27
 
28
28
-export([create/0, remove/1, add_trusted_certs/3, 
29
29
         remove_trusted_certs/2, lookup_trusted_cert/3, issuer_candidate/1,
30
 
         cache_pem_file/3]).
 
30
         lookup_cached_certs/1, cache_pem_file/4, uncache_pem_file/2, lookup/2]).
 
31
 
 
32
-type time()      :: {non_neg_integer(), non_neg_integer(), non_neg_integer()}.
31
33
 
32
34
%%====================================================================
33
35
%% Internal application API
34
36
%%====================================================================
35
37
 
36
38
%%--------------------------------------------------------------------
37
 
%% Function: create() -> Db
38
 
%% Db = term() - Reference to the crated database 
 
39
-spec create() -> certdb_ref().
39
40
%% 
40
41
%% Description: Creates a new certificate db.
41
42
%% Note: lookup_trusted_cert/3 may be called from any process but only
47
48
     ets:new(ssl_pid_to_file, [bag, private])]. 
48
49
 
49
50
%%--------------------------------------------------------------------
50
 
%% Function: delete(Db) -> _
51
 
%% Db = Database refererence as returned by create/0
 
51
-spec remove(certdb_ref()) -> term().
52
52
%%
53
53
%% Description: Removes database db  
54
54
%%--------------------------------------------------------------------
56
56
    lists:foreach(fun(Db) -> true = ets:delete(Db) end, Dbs).
57
57
 
58
58
%%--------------------------------------------------------------------
59
 
%% Function: lookup_trusted_cert(Ref, SerialNumber, Issuer) -> {BinCert,DecodedCert}
60
 
%% Ref = ref()
61
 
%% SerialNumber = integer()
62
 
%% Issuer = {rdnSequence, IssuerAttrs}
63
 
%% BinCert = binary()
 
59
-spec lookup_trusted_cert(reference(), serialnumber(), issuer()) -> 
 
60
                                 undefined | {ok, {der_cert(), #'OTPCertificate'{}}}.
 
61
 
64
62
%%
65
63
%% Description: Retrives the trusted certificate identified by 
66
64
%% <SerialNumber, Issuer>. Ref is used as it is specified  
74
72
            {ok, Certs}
75
73
    end.
76
74
 
 
75
lookup_cached_certs(File) ->
 
76
    ets:lookup(certificate_db_name(), {file, File}).
 
77
 
77
78
%%--------------------------------------------------------------------
78
 
%% Function: add_trusted_certs(Pid, File, Db) -> {ok, Ref}
79
 
%% Pid = pid() 
80
 
%% File = string()
81
 
%% Db = Database refererence as returned by create/0
82
 
%% Ref = ref()
 
79
-spec add_trusted_certs(pid(), string() | {der, list()}, certdb_ref()) -> {ok, certdb_ref()}.
83
80
%%
84
81
%% Description: Adds the trusted certificates from file <File> to the
85
82
%% runtime database. Returns Ref that should be handed to lookup_trusted_cert
86
83
%% together with the cert serialnumber and issuer.
87
84
%%--------------------------------------------------------------------
 
85
add_trusted_certs(_Pid, {der, DerList}, [CerDb, _,_]) ->
 
86
    NewRef = make_ref(),
 
87
    add_certs_from_der(DerList, NewRef, CerDb),
 
88
    {ok, NewRef};
88
89
add_trusted_certs(Pid, File, [CertsDb, FileToRefDb, PidToFileDb]) ->
89
90
    Ref = case lookup(File, FileToRefDb) of
90
91
              undefined ->
91
92
                  NewRef = make_ref(),
92
93
                  add_certs_from_file(File, NewRef, CertsDb),
93
 
                  insert(File, NewRef, 1, FileToRefDb),      
 
94
                  insert(File, NewRef, 1, FileToRefDb),
94
95
                  NewRef;
95
96
              [OldRef] ->
96
97
                  ref_count(File,FileToRefDb,1),
98
99
          end,
99
100
    insert(Pid, File, PidToFileDb),
100
101
    {ok, Ref}.
101
 
 
102
102
%%--------------------------------------------------------------------
103
 
%% Function: cache_pem_file(Pid, File, Db) -> FileContent
 
103
-spec cache_pem_file(pid(), string(), time(), certdb_ref()) -> term().
104
104
%%
105
105
%% Description: Cache file as binary in DB
106
106
%%--------------------------------------------------------------------
107
 
cache_pem_file(Pid, File, [_CertsDb, FileToRefDb, PidToFileDb]) ->
108
 
    try ref_count(File, FileToRefDb,1)
109
 
    catch _:_ -> 
110
 
            {ok, Content} = public_key:pem_to_der(File),
111
 
            insert(File,Content,1,FileToRefDb)
112
 
    end,
 
107
cache_pem_file(Pid, File, Time, [CertsDb, _FileToRefDb, PidToFileDb]) ->
 
108
    {ok, PemBin} = file:read_file(File), 
 
109
    Content = public_key:pem_decode(PemBin),
 
110
    insert({file, File}, {Time, Content}, CertsDb),
113
111
    insert(Pid, File, PidToFileDb),
114
 
    {ok, FileToRefDb}.
 
112
    {ok, Content}.
 
113
 
 
114
%--------------------------------------------------------------------
 
115
-spec uncache_pem_file(string(), certdb_ref()) -> no_return().
 
116
%%
 
117
%% Description: If a cached file is no longer valid (changed on disk)
 
118
%% we must terminate the connections using the old file content, and
 
119
%% when those processes are finish the cache will be cleaned. It is
 
120
%% a rare but possible case a new ssl client/server is started with
 
121
%% a filename with the same name as previously started client/server
 
122
%% but with different content.
 
123
%% --------------------------------------------------------------------
 
124
uncache_pem_file(File, [_CertsDb, _FileToRefDb, PidToFileDb]) ->
 
125
    Pids = select(PidToFileDb, [{{'$1', File},[],['$$']}]),
 
126
    lists:foreach(fun([Pid]) ->
 
127
                          exit(Pid, shutdown)
 
128
                  end, Pids).
 
129
 
 
130
 
115
131
 
116
132
%%--------------------------------------------------------------------
117
 
%% Function: remove_trusted_certs(Pid, Db) -> _ 
 
133
-spec remove_trusted_certs(pid(), certdb_ref()) -> term().
 
134
                                  
118
135
%%
119
136
%% Description: Removes trusted certs originating from 
120
137
%% the file associated to Pid from the runtime database.  
123
140
    Files = lookup(Pid, PidToFileDb),
124
141
    delete(Pid, PidToFileDb),
125
142
    Clear = fun(File) ->
126
 
                    case ref_count(File, FileToRefDb, -1) of
127
 
                        0 -> 
128
 
                            case lookup(File, FileToRefDb) of
129
 
                                [Ref] when is_reference(Ref) ->
130
 
                                    remove_certs(Ref, CertsDb);
131
 
                                _ -> ok
132
 
                            end,
133
 
                            delete(File, FileToRefDb);
134
 
                        _ ->
 
143
                    delete({file,File}, CertsDb),
 
144
                    try
 
145
                        0 = ref_count(File, FileToRefDb, -1),
 
146
                        case lookup(File, FileToRefDb) of
 
147
                            [Ref] when is_reference(Ref) ->
 
148
                                remove_certs(Ref, CertsDb);
 
149
                            _ -> ok
 
150
                        end,
 
151
                        delete(File, FileToRefDb)
 
152
                    catch _:_ ->
135
153
                            ok
136
154
                    end
137
155
            end,
143
161
    end.
144
162
 
145
163
%%--------------------------------------------------------------------
146
 
%% Function: issuer_candidate() -> {Key, Candidate} | no_more_candidates   
 
164
-spec issuer_candidate(no_candidate | cert_key() | {file, term()}) -> 
 
165
                              {cert_key(),{der_cert(), #'OTPCertificate'{}}} | no_more_candidates.
147
166
%%
148
 
%%     Candidate
149
 
%%     
150
 
%%     
151
167
%% Description: If a certificat does not define its issuer through
152
168
%%              the extension 'ce-authorityKeyIdentifier' we can
153
169
%%              try to find the issuer in the database over known
154
 
%%              certificates.
 
170
%%              certificates. 
155
171
%%--------------------------------------------------------------------
156
172
issuer_candidate(no_candidate) ->
157
173
    Db = certificate_db_name(),
158
174
    case ets:first(Db) of
159
175
        '$end_of_table' ->
160
176
            no_more_candidates;
 
177
        {file, _} = Key ->
 
178
            issuer_candidate(Key);
161
179
        Key ->
162
180
            [Cert] = lookup(Key, Db),
163
181
            {Key, Cert}
168
186
    case ets:next(Db, PrevCandidateKey) of
169
187
        '$end_of_table' ->
170
188
            no_more_candidates;
 
189
        {file, _} = Key ->
 
190
            issuer_candidate(Key);
171
191
        Key ->
172
192
            [Cert] = lookup(Key, Db),
173
193
            {Key, Cert}
174
194
    end.
175
195
 
176
196
%%--------------------------------------------------------------------
 
197
-spec lookup(term(), term()) -> term() | undefined.
 
198
%%
 
199
%% Description: Looks up an element in a certificat <Db>.
 
200
%%--------------------------------------------------------------------
 
201
lookup(Key, Db) ->
 
202
    case ets:lookup(Db, Key) of
 
203
        [] ->
 
204
            undefined;
 
205
        Contents  ->
 
206
            Pick = fun({_, Data}) -> Data;
 
207
                      ({_,_,Data}) -> Data
 
208
                   end,
 
209
            [Pick(Data) || Data <- Contents]
 
210
    end.
 
211
 
 
212
%%--------------------------------------------------------------------
177
213
%%% Internal functions
178
214
%%--------------------------------------------------------------------
179
215
certificate_db_name() ->
189
225
    ets:update_counter(Db,Key,N).
190
226
 
191
227
delete(Key, Db) ->
192
 
    true = ets:delete(Db, Key).
 
228
    _ = ets:delete(Db, Key).
193
229
 
194
 
lookup(Key, Db) ->
195
 
    case ets:lookup(Db, Key) of
196
 
        [] ->
197
 
            undefined;
198
 
        Contents  ->
199
 
            Pick = fun({_, Data}) -> Data;
200
 
                      ({_,_,Data}) -> Data
201
 
                   end,
202
 
            [Pick(Data) || Data <- Contents]
203
 
    end.
 
230
select(Db, MatchSpec)->
 
231
    ets:select(Db, MatchSpec).
204
232
 
205
233
remove_certs(Ref, CertsDb) ->
206
234
    ets:match_delete(CertsDb, {{Ref, '_', '_'}, '_'}).
207
235
 
 
236
add_certs_from_der(DerList, Ref, CertsDb) ->
 
237
    Add = fun(Cert) -> add_certs(Cert, Ref, CertsDb) end,
 
238
     [Add(Cert) || Cert <- DerList].
 
239
 
208
240
add_certs_from_file(File, Ref, CertsDb) ->   
209
 
    Decode = fun(Cert) ->
210
 
                     {ok, ErlCert} = public_key:pkix_decode_cert(Cert, otp),
211
 
                     TBSCertificate = ErlCert#'OTPCertificate'.tbsCertificate,
212
 
                     SerialNumber = TBSCertificate#'OTPTBSCertificate'.serialNumber,
213
 
                     Issuer = public_key:pkix_normalize_general_name(
214
 
                                TBSCertificate#'OTPTBSCertificate'.issuer),
215
 
                     insert({Ref, SerialNumber, Issuer}, {Cert,ErlCert}, CertsDb)
216
 
             end,
217
 
    {ok,Der} = public_key:pem_to_der(File),
218
 
    [Decode(Cert) || {cert, Cert, not_encrypted} <- Der].
 
241
    Add = fun(Cert) -> add_certs(Cert, Ref, CertsDb) end,
 
242
    {ok, PemBin} = file:read_file(File),
 
243
    PemEntries = public_key:pem_decode(PemBin),
 
244
    [Add(Cert) || {'Certificate', Cert, not_encrypted} <- PemEntries].
219
245
    
 
246
add_certs(Cert, Ref, CertsDb) ->
 
247
    try  ErlCert = public_key:pkix_decode_cert(Cert, otp),
 
248
         TBSCertificate = ErlCert#'OTPCertificate'.tbsCertificate,
 
249
         SerialNumber = TBSCertificate#'OTPTBSCertificate'.serialNumber,
 
250
         Issuer = public_key:pkix_normalize_name(
 
251
                    TBSCertificate#'OTPTBSCertificate'.issuer),
 
252
         insert({Ref, SerialNumber, Issuer}, {Cert,ErlCert}, CertsDb)
 
253
    catch
 
254
        error:_ ->
 
255
            Report = io_lib:format("SSL WARNING: Ignoring a CA cert as "
 
256
                                   "it could not be correctly decoded.~n", []),
 
257
            error_logger:info_report(Report)
 
258
    end.