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

« back to all changes in this revision

Viewing changes to lib/ssl/src/ssl_session.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
3
%% 
4
 
%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2007-2010. 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
28
28
-include("ssl_internal.hrl").
29
29
 
30
30
%% Internal application API
31
 
-export([is_new/2, id/3, id/6, valid_session/2]).
 
31
-export([is_new/2, id/4, id/7, valid_session/2]).
32
32
 
33
33
-define(GEN_UNIQUE_ID_MAX_TRIES, 10).
34
34
 
 
35
-type seconds()   :: integer(). 
 
36
 
35
37
%%--------------------------------------------------------------------
36
 
%% Function: is_new(ClientSuggestedId, ServerDecidedId) -> true | false
37
 
%%
38
 
%%      ClientSuggestedId = binary() 
39
 
%%      ServerDecidedId = binary()
 
38
-spec is_new(session_id(), session_id()) -> boolean().
40
39
%%
41
40
%% Description: Checks if the session id decided by the server is a
42
41
%%              new or resumed sesion id.
45
44
    true;
46
45
is_new(SessionId, SessionId) ->
47
46
    false;
48
 
is_new(_, _) ->
 
47
is_new(_ClientSuggestion, _ServerDecision) ->
49
48
    true.
50
49
 
51
50
%%--------------------------------------------------------------------
52
 
%% Function: id(ClientInfo, Cache, CacheCb) -> SessionId 
53
 
%%
54
 
%%      ClientInfo = {HostIP, Port, SslOpts}
55
 
%%      HostIP = ipadress()
56
 
%%      Port = integer() 
57
 
%%      CacheCb = atom()
58
 
%%      SessionId = binary()
 
51
-spec id({host(), port_num(), #ssl_options{}}, cache_ref(), atom(),
 
52
         undefined | binary()) -> binary().
59
53
%%
60
54
%% Description: Should be called by the client side to get an id 
61
55
%%              for the client hello message.
62
56
%%--------------------------------------------------------------------
63
 
id(ClientInfo, Cache, CacheCb) ->
64
 
    case select_session(ClientInfo, Cache, CacheCb) of
 
57
id(ClientInfo, Cache, CacheCb, OwnCert) ->
 
58
    case select_session(ClientInfo, Cache, CacheCb, OwnCert) of
65
59
        no_session ->
66
60
            <<>>;
67
61
        SessionId ->
69
63
    end.
70
64
 
71
65
%%--------------------------------------------------------------------
72
 
%% Function: id(Port, SuggestedSessionId, ReuseFun, CacheCb,
73
 
%%              SecondLifeTime) -> SessionId 
74
 
%%
75
 
%%      Port = integer() 
76
 
%%      SuggestedSessionId = SessionId = binary()
77
 
%%      ReuseFun = fun(SessionId, PeerCert, Compression, CipherSuite) -> 
78
 
%%                                                             true | false 
79
 
%%      CacheCb = atom()
 
66
-spec id(port_num(), binary(), #ssl_options{}, cache_ref(), 
 
67
         atom(), seconds(), binary()) -> binary().
80
68
%%
81
69
%% Description: Should be called by the server side to get an id 
82
70
%%              for the server hello message.
83
71
%%--------------------------------------------------------------------
84
 
id(Port, <<>>, _, Cache, CacheCb, _) ->
 
72
id(Port, <<>>, _, Cache, CacheCb, _, _) ->
85
73
    new_id(Port, ?GEN_UNIQUE_ID_MAX_TRIES, Cache, CacheCb);
86
74
 
87
75
id(Port, SuggestedSessionId, #ssl_options{reuse_sessions = ReuseEnabled,
88
76
                                          reuse_session = ReuseFun}, 
89
 
   Cache, CacheCb, SecondLifeTime) ->
 
77
   Cache, CacheCb, SecondLifeTime, OwnCert) ->
90
78
    case is_resumable(SuggestedSessionId, Port, ReuseEnabled, 
91
 
                      ReuseFun, Cache, CacheCb, SecondLifeTime) of
 
79
                      ReuseFun, Cache, CacheCb, SecondLifeTime, OwnCert) of
92
80
        true ->
93
81
            SuggestedSessionId;
94
82
        false ->
95
83
            new_id(Port, ?GEN_UNIQUE_ID_MAX_TRIES, Cache, CacheCb)
96
84
    end.
97
85
%%--------------------------------------------------------------------
98
 
%% Function: valid_session(Session, LifeTime) -> true | false 
99
 
%%
100
 
%%      Session  = #session{}
101
 
%%      LifeTime = integer() - seconds
 
86
-spec valid_session(#session{}, seconds()) -> boolean().
102
87
%%
103
88
%% Description: Check that the session has not expired
104
89
%%--------------------------------------------------------------------
109
94
%%--------------------------------------------------------------------
110
95
%%% Internal functions
111
96
%%--------------------------------------------------------------------
112
 
select_session({HostIP, Port, SslOpts}, Cache, CacheCb) ->    
 
97
select_session({HostIP, Port, SslOpts}, Cache, CacheCb, OwnCert) ->
113
98
    Sessions = CacheCb:select_session(Cache, {HostIP, Port}),
114
 
    select_session(Sessions, SslOpts).
 
99
    select_session(Sessions, SslOpts, OwnCert).
115
100
 
116
 
select_session([], _) ->
 
101
select_session([], _, _) ->
117
102
    no_session;
118
103
 
119
104
select_session(Sessions, #ssl_options{ciphers = Ciphers,
120
 
                                      reuse_sessions = ReuseSession}) ->
 
105
                                      reuse_sessions = ReuseSession}, OwnCert) ->
121
106
    IsResumable = 
122
107
        fun(Session) -> 
123
108
                ReuseSession andalso (Session#session.is_resumable) andalso  
124
109
                    lists:member(Session#session.cipher_suite, Ciphers)
 
110
                    andalso (OwnCert == Session#session.own_certificate)
125
111
        end,
126
112
    case [Id || [Id, Session] <- Sessions, IsResumable(Session)] of
127
113
        [] ->
129
115
        List ->
130
116
            hd(List)
131
117
    end.
132
 
            
 
118
 
133
119
%% If we can not generate a not allready in use session ID in
134
120
%% ?GEN_UNIQUE_ID_MAX_TRIES we make the new session uncacheable The
135
121
%% value of ?GEN_UNIQUE_ID_MAX_TRIES is stolen from open SSL which
156
142
    end.
157
143
 
158
144
is_resumable(SuggestedSessionId, Port, ReuseEnabled, ReuseFun, Cache, 
159
 
             CacheCb, SecondLifeTime) ->
 
145
             CacheCb, SecondLifeTime, OwnCert) ->
160
146
    case CacheCb:lookup(Cache, {Port, SuggestedSessionId}) of
161
147
        #session{cipher_suite = CipherSuite,
 
148
                 own_certificate = SessionOwnCert,
162
149
                 compression_method = Compression,
163
150
                 is_resumable = Is_resumable,
164
151
                 peer_certificate = PeerCert} = Session ->
165
152
            ReuseEnabled 
166
153
                andalso Is_resumable  
 
154
                andalso (OwnCert == SessionOwnCert)
167
155
                andalso valid_session(Session, SecondLifeTime) 
168
156
                andalso ReuseFun(SuggestedSessionId, PeerCert, 
169
157
                                 Compression, CipherSuite);