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

« back to all changes in this revision

Viewing changes to lib/ssl/src/ssl_manager.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
27
27
-include("ssl_internal.hrl").
28
28
 
29
29
%% Internal application API
30
 
-export([start_link/1, 
31
 
         connection_init/2, cache_pem_file/1,
32
 
         lookup_trusted_cert/3, issuer_candidate/1, client_session_id/3, 
33
 
         server_session_id/3,
 
30
-export([start_link/1, start_link_dist/1,
 
31
         connection_init/2, cache_pem_file/2,
 
32
         lookup_trusted_cert/4,
 
33
         client_session_id/4, server_session_id/4,
34
34
         register_session/2, register_session/3, invalidate_session/2,
35
35
         invalidate_session/3]).
36
36
 
43
43
 
44
44
-include("ssl_handshake.hrl").
45
45
-include("ssl_internal.hrl").
 
46
-include_lib("kernel/include/file.hrl").
46
47
 
47
48
-record(state, {
48
49
          session_cache,
49
50
          session_cache_cb,
50
51
          session_lifetime,
51
52
          certificate_db,
52
 
          session_validation_timer
 
53
          session_validation_timer,
 
54
          last_delay_timer  = {undefined, undefined}%% Keep for testing purposes
53
55
         }).
54
56
 
55
57
-define('24H_in_msec', 8640000).
56
58
-define('24H_in_sec', 8640).
57
59
-define(SESSION_VALIDATION_INTERVAL, 60000).
58
60
-define(CERTIFICATE_CACHE_CLEANUP, 30000).
 
61
-define(CLEAN_SESSION_DB, 60000).
59
62
 
60
63
%%====================================================================
61
64
%% API
63
66
%%--------------------------------------------------------------------
64
67
-spec start_link(list()) -> {ok, pid()} | ignore | {error, term()}.
65
68
%%
66
 
%% Description: Starts the server
 
69
%% Description: Starts the ssl manager that takes care of sessions
 
70
%% and certificate caching.
67
71
%%--------------------------------------------------------------------
68
72
start_link(Opts) ->
69
 
    gen_server:start_link({local, ?MODULE}, ?MODULE, [Opts], []).
70
 
 
71
 
%%--------------------------------------------------------------------
72
 
-spec connection_init(string()| {der, list()}, client | server) -> {ok, reference(), cache_ref()}.
 
73
    gen_server:start_link({local, ?MODULE}, ?MODULE, [?MODULE, Opts], []).
 
74
 
 
75
%%--------------------------------------------------------------------
 
76
-spec start_link_dist(list()) -> {ok, pid()} | ignore | {error, term()}.
 
77
%%
 
78
%% Description: Starts a special instance of the ssl manager to
 
79
%% be used by the erlang distribution. Note disables soft upgrade!
 
80
%%--------------------------------------------------------------------
 
81
start_link_dist(Opts) ->
 
82
    gen_server:start_link({local, ssl_manager_dist}, ?MODULE, [ssl_manager_dist, Opts], []).
 
83
 
 
84
%%--------------------------------------------------------------------
 
85
-spec connection_init(string()| {der, list()}, client | server) ->
 
86
                             {ok, certdb_ref(), db_handle(), db_handle()}.
73
87
%%                           
74
88
%% Description: Do necessary initializations for a new connection.
75
89
%%--------------------------------------------------------------------
76
90
connection_init(Trustedcerts, Role) ->
77
91
    call({connection_init, Trustedcerts, Role}).
78
92
%%--------------------------------------------------------------------
79
 
-spec cache_pem_file(string()) -> {ok, term()}. 
 
93
-spec cache_pem_file(string(), term()) -> {ok, term()} | {error, reason()}.
80
94
%%                  
81
 
%% Description: Cach a pem file and 
 
95
%% Description: Cach a pem file and return its content.
82
96
%%--------------------------------------------------------------------
83
 
cache_pem_file(File) ->   
84
 
    case ssl_certificate_db:lookup_cached_certs(File) of
85
 
        [{_,Content}] ->
86
 
            {ok, Content};
87
 
        [] ->
88
 
            call({cache_pem, File})
 
97
cache_pem_file(File, DbHandle) ->
 
98
    try file:read_file_info(File) of
 
99
        {ok, #file_info{mtime = LastWrite}} ->
 
100
            cache_pem_file(File, LastWrite, DbHandle)
 
101
    catch
 
102
        _:Reason ->
 
103
            {error, Reason}
89
104
    end.
90
105
%%--------------------------------------------------------------------
91
 
-spec lookup_trusted_cert(reference(), serialnumber(), issuer()) -> 
 
106
-spec lookup_trusted_cert(term(), reference(), serialnumber(), issuer()) ->
92
107
                                 undefined | 
93
108
                                 {ok, {der_cert(), #'OTPCertificate'{}}}.
94
109
%%                               
95
110
%% Description: Lookup the trusted cert with Key = {reference(),
96
111
%% serialnumber(), issuer()}.
97
112
%% --------------------------------------------------------------------
98
 
lookup_trusted_cert(Ref, SerialNumber, Issuer) ->
99
 
    ssl_certificate_db:lookup_trusted_cert(Ref, SerialNumber, Issuer).
100
 
%%--------------------------------------------------------------------
101
 
-spec issuer_candidate(cert_key() | no_candidate) -> 
102
 
                              {cert_key(), {der_cert(), #'OTPCertificate'{}}} | no_more_candidates.      
103
 
%%
104
 
%% Description: Return next issuer candidate.
105
 
%%--------------------------------------------------------------------
106
 
issuer_candidate(PrevCandidateKey) ->
107
 
    ssl_certificate_db:issuer_candidate(PrevCandidateKey).
108
 
%%--------------------------------------------------------------------
109
 
-spec client_session_id(host(), port_num(), #ssl_options{}) -> session_id().
 
113
lookup_trusted_cert(DbHandle, Ref, SerialNumber, Issuer) ->
 
114
    ssl_certificate_db:lookup_trusted_cert(DbHandle, Ref, SerialNumber, Issuer).
 
115
 
 
116
%%--------------------------------------------------------------------
 
117
-spec client_session_id(host(), inet:port_number(), #ssl_options{},
 
118
                        der_cert() | undefined) -> session_id().
110
119
%%
111
120
%% Description: Select a session id for the client.
112
121
%%--------------------------------------------------------------------
113
 
client_session_id(Host, Port, SslOpts) ->
114
 
    call({client_session_id, Host, Port, SslOpts}).
 
122
client_session_id(Host, Port, SslOpts, OwnCert) ->
 
123
    call({client_session_id, Host, Port, SslOpts, OwnCert}).
115
124
 
116
125
%%--------------------------------------------------------------------
117
 
-spec server_session_id(host(), port_num(), #ssl_options{}) -> session_id().
 
126
-spec server_session_id(host(), inet:port_number(), #ssl_options{},
 
127
                        der_cert()) -> session_id().
118
128
%%
119
129
%% Description: Select a session id for the server.
120
130
%%--------------------------------------------------------------------
121
 
server_session_id(Port, SuggestedSessionId, SslOpts) ->
122
 
    call({server_session_id, Port, SuggestedSessionId, SslOpts}).
 
131
server_session_id(Port, SuggestedSessionId, SslOpts, OwnCert) ->
 
132
    call({server_session_id, Port, SuggestedSessionId, SslOpts, OwnCert}).
123
133
 
124
134
%%--------------------------------------------------------------------
125
 
-spec register_session(port_num(), #session{}) -> ok.
126
 
-spec register_session(host(), port_num(), #session{}) -> ok.
 
135
-spec register_session(inet:port_number(), #session{}) -> ok.
 
136
-spec register_session(host(), inet:port_number(), #session{}) -> ok.
127
137
%%
128
138
%% Description: Make the session available for reuse.
129
139
%%--------------------------------------------------------------------
133
143
register_session(Port, Session) ->
134
144
    cast({register_session, Port, Session}).
135
145
%%--------------------------------------------------------------------
136
 
-spec invalidate_session(port_num(), #session{}) -> ok.
137
 
-spec invalidate_session(host(), port_num(), #session{}) -> ok.
 
146
-spec invalidate_session(inet:port_number(), #session{}) -> ok.
 
147
-spec invalidate_session(host(), inet:port_number(), #session{}) -> ok.
138
148
%%
139
 
%% Description: Make the session unavilable for reuse.
 
149
%% Description: Make the session unavailable for reuse. After
 
150
%% a the session has been marked "is_resumable = false" for some while
 
151
%% it will be safe to remove the data from the session database.
140
152
%%--------------------------------------------------------------------
141
153
invalidate_session(Host, Port, Session) ->
142
154
    cast({invalidate_session, Host, Port, Session}).
155
167
%%
156
168
%% Description: Initiates the server
157
169
%%--------------------------------------------------------------------
158
 
init([Opts]) ->
 
170
init([Name, Opts]) ->
 
171
    put(ssl_manager, Name),
159
172
    process_flag(trap_exit, true),
160
173
    CacheCb = proplists:get_value(session_cb, Opts, ssl_session_cache),
161
174
    SessionLifeTime =  
182
195
%% Description: Handling call messages
183
196
%%--------------------------------------------------------------------
184
197
handle_call({{connection_init, "", _Role}, Pid}, _From, 
185
 
            #state{session_cache = Cache} = State) ->
 
198
            #state{certificate_db = [CertDb |_],
 
199
                   session_cache = Cache} = State) ->
186
200
    erlang:monitor(process, Pid),
187
 
    Result = {ok, make_ref(), Cache},
 
201
    Result = {ok, make_ref(),CertDb, Cache},
188
202
    {reply, Result, State};
189
203
 
190
204
handle_call({{connection_init, Trustedcerts, _Role}, Pid}, _From,
191
 
            #state{certificate_db = Db,
 
205
            #state{certificate_db = [CertDb|_] =Db,
192
206
                   session_cache = Cache} = State) ->
193
207
    erlang:monitor(process, Pid),
194
208
    Result = 
195
209
        try
196
210
            {ok, Ref} = ssl_certificate_db:add_trusted_certs(Pid, Trustedcerts, Db),
197
 
            {ok, Ref, Cache}
 
211
            {ok, Ref, CertDb, Cache}
198
212
        catch
199
213
            _:Reason ->
200
214
                {error, Reason}
201
215
        end,
202
216
    {reply, Result, State};
203
217
 
204
 
handle_call({{client_session_id, Host, Port, SslOpts}, _}, _, 
 
218
handle_call({{client_session_id, Host, Port, SslOpts, OwnCert}, _}, _,
205
219
            #state{session_cache = Cache,
206
220
                  session_cache_cb = CacheCb} = State) ->
207
 
    Id = ssl_session:id({Host, Port, SslOpts}, Cache, CacheCb),
 
221
    Id = ssl_session:id({Host, Port, SslOpts}, Cache, CacheCb, OwnCert),
208
222
    {reply, Id, State};
209
223
 
210
 
handle_call({{server_session_id, Port, SuggestedSessionId, SslOpts}, _},
 
224
handle_call({{server_session_id, Port, SuggestedSessionId, SslOpts, OwnCert}, _},
211
225
            _, #state{session_cache_cb = CacheCb,
212
226
                      session_cache = Cache,
213
227
                      session_lifetime = LifeTime} = State) ->
214
228
    Id = ssl_session:id(Port, SuggestedSessionId, SslOpts,
215
 
                        Cache, CacheCb, LifeTime),
 
229
                        Cache, CacheCb, LifeTime, OwnCert),
216
230
    {reply, Id, State};
217
231
 
218
 
handle_call({{cache_pem, File},Pid}, _, State = #state{certificate_db = Db}) ->
219
 
    try ssl_certificate_db:cache_pem_file(Pid,File,Db) of
 
232
handle_call({{cache_pem, File, LastWrite}, Pid}, _, 
 
233
            #state{certificate_db = Db} = State) ->
 
234
    try ssl_certificate_db:cache_pem_file(Pid, File, LastWrite, Db) of
220
235
        Result ->
221
236
            {reply, Result, State}
222
237
    catch 
223
238
        _:Reason ->
224
239
            {reply, {error, Reason}, State}
225
 
    end.
 
240
    end;
 
241
handle_call({{recache_pem, File, LastWrite}, Pid}, From,
 
242
            #state{certificate_db = Db} = State) ->
 
243
    ssl_certificate_db:uncache_pem_file(File, Db),
 
244
    cast({recache_pem, File, LastWrite, Pid, From}),
 
245
    {noreply, State}.
 
246
 
226
247
%%--------------------------------------------------------------------
227
248
-spec  handle_cast(msg(), #state{}) -> {noreply, #state{}}.
228
249
%% Possible return values not used now.  
248
269
    CacheCb:update(Cache, {Port, NewSession#session.session_id}, NewSession),
249
270
    {noreply, State};
250
271
 
251
 
handle_cast({invalidate_session, Host, Port, 
252
 
             #session{session_id = ID}}, 
253
 
            #state{session_cache = Cache,
254
 
                   session_cache_cb = CacheCb} = State) ->
255
 
    CacheCb:delete(Cache, {{Host, Port}, ID}),
256
 
    {noreply, State};
257
 
 
258
 
handle_cast({invalidate_session, Port, #session{session_id = ID}}, 
259
 
            #state{session_cache = Cache,
260
 
                   session_cache_cb = CacheCb} = State) ->
261
 
    CacheCb:delete(Cache, {Port, ID}),
262
 
    {noreply, State}.
 
272
handle_cast({invalidate_session, Host, Port,
 
273
             #session{session_id = ID} = Session},
 
274
            #state{session_cache = Cache,
 
275
                   session_cache_cb = CacheCb} = State) ->
 
276
    invalidate_session(Cache, CacheCb, {{Host, Port}, ID}, Session, State);
 
277
 
 
278
handle_cast({invalidate_session, Port, #session{session_id = ID} = Session},
 
279
            #state{session_cache = Cache,
 
280
                   session_cache_cb = CacheCb} = State) ->
 
281
    invalidate_session(Cache, CacheCb, {Port, ID}, Session, State);
 
282
 
 
283
handle_cast({recache_pem, File, LastWrite, Pid, From},
 
284
            #state{certificate_db = [_, FileToRefDb, _]} = State0) ->
 
285
    case ssl_certificate_db:lookup(File, FileToRefDb) of
 
286
        undefined ->
 
287
            {reply, Msg, State} =
 
288
                handle_call({{cache_pem, File, LastWrite}, Pid}, From, State0),
 
289
            gen_server:reply(From, Msg),
 
290
            {noreply, State};
 
291
        _ -> %% Send message to self letting cleanup messages be handled
 
292
             %% first so that no reference to the old version of file
 
293
             %% exists when we cache the new one.
 
294
            cast({recache_pem, File, LastWrite, Pid, From}),
 
295
            {noreply, State0}
 
296
    end.
263
297
 
264
298
%%--------------------------------------------------------------------
265
299
-spec handle_info(msg(), #state{}) -> {noreply, #state{}}.
268
302
%%                                    {stop, reason(), #state{}}.
269
303
%%
270
304
%% Description: Handling all non call/cast messages
271
 
%%-------------------------------------------------------------------- 
 
305
%%-------------------------------------------------------------------
272
306
handle_info(validate_sessions, #state{session_cache_cb = CacheCb,
273
307
                                      session_cache = Cache,
274
308
                                      session_lifetime = LifeTime
278
312
    start_session_validator(Cache, CacheCb, LifeTime),
279
313
    {noreply, State#state{session_validation_timer = Timer}};
280
314
 
 
315
handle_info({delayed_clean_session, Key}, #state{session_cache = Cache,
 
316
                   session_cache_cb = CacheCb
 
317
                   } = State) ->
 
318
    CacheCb:delete(Cache, Key),
 
319
    {noreply, State};
 
320
 
281
321
handle_info({'EXIT', _, _}, State) ->
282
322
    %% Session validator died!! Do we need to take any action?
283
323
    %% maybe error log
286
326
handle_info({'DOWN', _Ref, _Type, _Pid, ecacertfile}, State) ->
287
327
    {noreply, State};
288
328
 
 
329
handle_info({'DOWN', _Ref, _Type, Pid, shutdown}, State) ->
 
330
    handle_info({remove_trusted_certs, Pid}, State);
289
331
handle_info({'DOWN', _Ref, _Type, Pid, _Reason}, State) ->
290
332
    erlang:send_after(?CERTIFICATE_CACHE_CLEANUP, self(), 
291
333
                      {remove_trusted_certs, Pid}),
292
334
    {noreply, State};
293
335
handle_info({remove_trusted_certs, Pid}, 
294
 
            State = #state{certificate_db = Db}) ->
 
336
            #state{certificate_db = Db} = State) ->
295
337
    ssl_certificate_db:remove_trusted_certs(Pid, Db),
296
338
    {noreply, State};
297
339
 
327
369
%%% Internal functions
328
370
%%--------------------------------------------------------------------
329
371
call(Msg) ->
330
 
    gen_server:call(?MODULE, {Msg, self()}, infinity).
 
372
    gen_server:call(get(ssl_manager), {Msg, self()}, infinity).
331
373
 
332
374
cast(Msg) ->
333
 
    gen_server:cast(?MODULE, Msg).
 
375
    gen_server:cast(get(ssl_manager), Msg).
334
376
 
335
377
validate_session(Host, Port, Session, LifeTime) ->
336
378
    case ssl_session:valid_session(Session, LifeTime) of
350
392
                    
351
393
start_session_validator(Cache, CacheCb, LifeTime) ->
352
394
    spawn_link(?MODULE, init_session_validator, 
353
 
               [[Cache, CacheCb, LifeTime]]).
 
395
               [[get(ssl_manager), Cache, CacheCb, LifeTime]]).
354
396
 
355
 
init_session_validator([Cache, CacheCb, LifeTime]) ->
 
397
init_session_validator([SslManagerName, Cache, CacheCb, LifeTime]) ->
 
398
    put(ssl_manager, SslManagerName),
356
399
    CacheCb:foldl(fun session_validation/2,
357
400
                  LifeTime, Cache).
358
401
 
362
405
session_validation({{Port, _}, Session}, LifeTime) ->
363
406
    validate_session(Port, Session, LifeTime),
364
407
    LifeTime.
 
408
 
 
409
cache_pem_file(File, LastWrite, DbHandle) ->
 
410
    case ssl_certificate_db:lookup_cached_certs(DbHandle,File) of
 
411
        [{_, {Mtime, Content}}] ->
 
412
            case LastWrite of
 
413
                Mtime ->
 
414
                    {ok, Content};
 
415
                _ ->
 
416
                    call({recache_pem, File, LastWrite})
 
417
            end;
 
418
        [] ->
 
419
            call({cache_pem, File, LastWrite})
 
420
    end.
 
421
 
 
422
delay_time() ->
 
423
    case application:get_env(ssl, session_delay_cleanup_time) of
 
424
        {ok, Time} when is_integer(Time) ->
 
425
            Time;
 
426
        _ ->
 
427
           ?CLEAN_SESSION_DB
 
428
    end.
 
429
 
 
430
invalidate_session(Cache, CacheCb, Key, Session, #state{last_delay_timer = LastTimer} = State) ->
 
431
    case CacheCb:lookup(Cache, Key) of
 
432
        undefined -> %% Session is already invalidated
 
433
            {noreply, State};
 
434
        #session{is_resumable = new} ->
 
435
            CacheCb:delete(Cache, Key),
 
436
            {noreply, State};
 
437
        _ ->
 
438
            %% When a registered session is invalidated we need to wait a while before deleting
 
439
            %% it as there might be pending connections that rightfully needs to look
 
440
            %% up the session data but new connections should not get to use this session.
 
441
            CacheCb:update(Cache, Key, Session#session{is_resumable = false}),
 
442
            TRef =
 
443
                erlang:send_after(delay_time(), self(), {delayed_clean_session, Key}),
 
444
            {noreply, State#state{last_delay_timer = last_delay_timer(Key, TRef, LastTimer)}}
 
445
    end.
 
446
 
 
447
last_delay_timer({{_,_},_}, TRef, {LastServer, _}) ->
 
448
    {LastServer, TRef};
 
449
last_delay_timer({_,_}, TRef, {_, LastClient}) ->
 
450
    {TRef, LastClient}.