~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

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
 
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/3]).
31
31
 
32
32
%%====================================================================
33
33
%% Internal application API
74
74
            {ok, Certs}
75
75
    end.
76
76
 
 
77
lookup_cached_certs(File) ->
 
78
    ets:lookup(certificate_db_name(), {file, File}).
 
79
 
77
80
%%--------------------------------------------------------------------
78
81
%% Function: add_trusted_certs(Pid, File, Db) -> {ok, Ref}
79
82
%% Pid = pid() 
90
93
              undefined ->
91
94
                  NewRef = make_ref(),
92
95
                  add_certs_from_file(File, NewRef, CertsDb),
93
 
                  insert(File, NewRef, 1, FileToRefDb),      
 
96
                  insert(File, NewRef, 1, FileToRefDb),
94
97
                  NewRef;
95
98
              [OldRef] ->
96
99
                  ref_count(File,FileToRefDb,1),
104
107
%%
105
108
%% Description: Cache file as binary in DB
106
109
%%--------------------------------------------------------------------
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,
 
110
cache_pem_file(Pid, File, [CertsDb, _FileToRefDb, PidToFileDb]) ->
 
111
    Res = {ok, Content} = public_key:pem_to_der(File),
 
112
    insert({file, File}, Content, CertsDb),
113
113
    insert(Pid, File, PidToFileDb),
114
 
    {ok, FileToRefDb}.
 
114
    Res.
115
115
 
116
116
%%--------------------------------------------------------------------
117
117
%% Function: remove_trusted_certs(Pid, Db) -> _ 
123
123
    Files = lookup(Pid, PidToFileDb),
124
124
    delete(Pid, PidToFileDb),
125
125
    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
 
                        _ ->
 
126
                    delete({file,File}, CertsDb),
 
127
                    try
 
128
                        0 = ref_count(File, FileToRefDb, -1),
 
129
                        case lookup(File, FileToRefDb) of
 
130
                            [Ref] when is_reference(Ref) ->
 
131
                                remove_certs(Ref, CertsDb);
 
132
                            _ -> ok
 
133
                        end,
 
134
                        delete(File, FileToRefDb)
 
135
                    catch _:_ ->
135
136
                            ok
136
137
                    end
137
138
            end,
168
169
    case ets:next(Db, PrevCandidateKey) of
169
170
        '$end_of_table' ->
170
171
            no_more_candidates;
 
172
        {file, _} = Key ->
 
173
            issuer_candidate(Key);
171
174
        Key ->
172
175
            [Cert] = lookup(Key, Db),
173
176
            {Key, Cert}
189
192
    ets:update_counter(Db,Key,N).
190
193
 
191
194
delete(Key, Db) ->
192
 
    true = ets:delete(Db, Key).
 
195
    _ = ets:delete(Db, Key).
193
196
 
194
197
lookup(Key, Db) ->
195
198
    case ets:lookup(Db, Key) of