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

« back to all changes in this revision

Viewing changes to lib/ssl/src/ssl_connection.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
 
29
29
 
30
30
-behaviour(gen_fsm).
31
31
 
32
 
-include("ssl_debug.hrl").
33
32
-include("ssl_handshake.hrl").
34
33
-include("ssl_alert.hrl").
35
34
-include("ssl_record.hrl").
39
38
-include_lib("public_key/include/public_key.hrl"). 
40
39
 
41
40
%% Internal application API
42
 
-export([send/2, send/3, recv/3, connect/7, accept/6, close/1, shutdown/2,
 
41
-export([send/2, recv/3, connect/7, ssl_accept/6, handshake/2,
 
42
         socket_control/3, close/1, shutdown/2,
43
43
         new_user/2, get_opts/2, set_opts/2, info/1, session_info/1, 
44
 
         peer_certificate/1,
45
 
         sockname/1, peername/1]).
 
44
         peer_certificate/1, sockname/1, peername/1, renegotiation/1]).
46
45
 
47
46
%% Called by ssl_connection_sup
48
47
-export([start_link/7]). 
49
48
 
50
49
%% gen_fsm callbacks
51
 
-export([init/1, hello/2, certify/2, cipher/2, connection/2, connection/3, abbreviated/2,
52
 
         handle_event/3,
 
50
-export([init/1, hello/2, certify/2, cipher/2, connection/2, 
 
51
         abbreviated/2, handle_event/3,
53
52
         handle_sync_event/4, handle_info/3, terminate/3, code_change/4]).
54
53
 
55
54
-record(state, {
58
57
          transport_cb,       % atom() - callback module 
59
58
          data_tag,           % atom()  - ex tcp.
60
59
          close_tag,          % atom()  - ex tcp_closed
 
60
          error_tag,          % atom() - ex  tcp_error
61
61
          host,               % string() | ipadress()
62
62
          port,               % integer()
63
63
          socket,             % socket() 
64
64
          ssl_options,        % #ssl_options{}
65
65
          socket_options,     % #socket_options{}
66
66
          connection_states,  % #connection_states{} from ssl_record.hrl
 
67
          tls_packets = [],        % Not yet handled decode ssl/tls packets.
67
68
          tls_record_buffer,  % binary() buffer of incomplete records
68
69
          tls_handshake_buffer, % binary() buffer of incomplete handshakes
69
70
          %% {{md5_hash, sha_hash}, {prev_md5, prev_sha}} (binary())
70
71
          tls_handshake_hashes, % see above 
71
72
          tls_cipher_texts,     % list() received but not deciphered yet
72
 
          own_cert,             % binary()  
73
 
          session,              % #session{} from ssl_handshake.erl
 
73
          session,              % #session{} from ssl_handshake.hrl
74
74
          session_cache,        % 
75
75
          session_cache_cb,     %
76
 
          negotiated_version,   % #protocol_version{}
 
76
          negotiated_version,   % tls_version()
77
77
          supported_protocol_versions, % [atom()]
78
78
          client_certificate_requested = false,
79
79
          key_algorithm,       % atom as defined by cipher_suite
80
80
          public_key_info,     % PKIX: {Algorithm, PublicKey, PublicKeyParams}
81
 
          private_key,         % PKIX: 'RSAPrivateKey'
82
 
          diffie_hellman_params, % 
 
81
          private_key,         % PKIX: #'RSAPrivateKey'{}
 
82
          diffie_hellman_params, % PKIX: #'DHParameter'{} relevant for server side
 
83
          diffie_hellman_keys, % {PublicKey, PrivateKey}
83
84
          premaster_secret,    %
84
85
          cert_db_ref,         % ets_table()
85
86
          from,                % term(), where to reply
86
87
          bytes_to_read,       % integer(), # bytes to read in passive mode
87
88
          user_data_buffer,    % binary()
88
 
%%        tls_buffer,          % Keeps a lookahead one packet if available
89
 
          log_alert            % boolan() 
 
89
          log_alert,           % boolean() 
 
90
          renegotiation,        % {boolean(), From | internal | peer}
 
91
          recv_during_renegotiation,  %boolean() 
 
92
          send_queue,           % queue()
 
93
          terminated = false   %
90
94
         }).
91
95
 
 
96
-define(DEFAULT_DIFFIE_HELLMAN_PARAMS, 
 
97
        #'DHParameter'{prime = ?DEFAULT_DIFFIE_HELLMAN_PRIME, 
 
98
                       base = ?DEFAULT_DIFFIE_HELLMAN_GENERATOR}).
 
99
 
 
100
-type state_name()           :: hello | abbreviated | certify | cipher | connection.
 
101
-type gen_fsm_state_return() :: {next_state, state_name(), #state{}} |
 
102
                                {next_state, state_name(), #state{}, timeout()} |
 
103
                                {stop, term(), #state{}}.
 
104
 
92
105
%%====================================================================
93
106
%% Internal application API
94
107
%%====================================================================       
95
108
 
96
109
%%--------------------------------------------------------------------
97
 
%% Function: 
 
110
-spec send(pid(), iolist()) -> ok | {error, reason()}.
98
111
%%
99
 
%% Description: 
 
112
%% Description: Sends data over the ssl connection
100
113
%%--------------------------------------------------------------------
101
114
send(Pid, Data) -> 
102
 
    sync_send_event(Pid, {application_data, erlang:iolist_to_binary(Data)}, infinity).
103
 
send(Pid, Data, Timeout) -> 
104
 
    sync_send_event(Pid, {application_data, erlang:iolist_to_binary(Data)}, Timeout).
 
115
    sync_send_all_state_event(Pid, {application_data, 
 
116
                                    erlang:iolist_to_binary(Data)}, infinity).
 
117
 
105
118
%%--------------------------------------------------------------------
106
 
%% Function: 
 
119
-spec recv(pid(), integer(), timeout()) ->  
 
120
    {ok, binary() | list()} | {error, reason()}.
107
121
%%
108
 
%% Description: 
 
122
%% Description:  Receives data when active = false
109
123
%%--------------------------------------------------------------------
110
 
recv(Pid, Length, Timeout) -> % TODO: Prio with renegotiate? 
 
124
recv(Pid, Length, Timeout) -> 
111
125
    sync_send_all_state_event(Pid, {recv, Length}, Timeout).
112
126
%%--------------------------------------------------------------------
113
 
%% Function: 
 
127
-spec connect(host(), port_num(), port(), {#ssl_options{}, #socket_options{}},
 
128
              pid(), tuple(), timeout()) ->
 
129
                     {ok, #sslsocket{}} | {error, reason()}.
114
130
%%
115
 
%% Description: 
 
131
%% Description: Connect to a ssl server.
116
132
%%--------------------------------------------------------------------
117
133
connect(Host, Port, Socket, Options, User, CbInfo, Timeout) ->
118
 
    start_fsm(client, Host, Port, Socket, Options, User, CbInfo,
119
 
              Timeout).
120
 
%%--------------------------------------------------------------------
121
 
%% Function: 
122
 
%%
123
 
%% Description: 
124
 
%%--------------------------------------------------------------------
125
 
accept(Port, Socket, Opts, User, CbInfo, Timeout) ->
126
 
    start_fsm(server, "localhost", Port, Socket, Opts, User, 
127
 
              CbInfo, Timeout).
128
 
%%--------------------------------------------------------------------
129
 
%% Function: 
130
 
%%
131
 
%% Description: 
 
134
    try start_fsm(client, Host, Port, Socket, Options, User, CbInfo,
 
135
                  Timeout)
 
136
    catch
 
137
        exit:{noproc, _} ->
 
138
            {error, ssl_not_started}
 
139
    end.
 
140
%%--------------------------------------------------------------------
 
141
-spec ssl_accept(port_num(), port(), {#ssl_options{}, #socket_options{}}, 
 
142
                                      pid(), tuple(), timeout()) ->
 
143
    {ok, #sslsocket{}} | {error, reason()}.
 
144
%%
 
145
%% Description: Performs accept on a ssl listen socket. e.i. performs
 
146
%%              ssl handshake. 
 
147
%%--------------------------------------------------------------------
 
148
ssl_accept(Port, Socket, Opts, User, CbInfo, Timeout) ->
 
149
    try start_fsm(server, "localhost", Port, Socket, Opts, User, 
 
150
                  CbInfo, Timeout)
 
151
    catch
 
152
        exit:{noproc, _} ->
 
153
            {error, ssl_not_started}
 
154
    end.        
 
155
 
 
156
%%--------------------------------------------------------------------
 
157
-spec handshake(#sslsocket{}, timeout()) ->  ok | {error, reason()}.
 
158
%%
 
159
%% Description: Starts ssl handshake. 
 
160
%%--------------------------------------------------------------------
 
161
handshake(#sslsocket{pid = Pid}, Timeout) ->  
 
162
    case sync_send_all_state_event(Pid, start, Timeout) of
 
163
        connected ->
 
164
            ok;
 
165
        Error ->
 
166
            Error
 
167
    end.
 
168
%--------------------------------------------------------------------
 
169
-spec socket_control(port(), pid(), atom()) -> 
 
170
    {ok, #sslsocket{}} | {error, reason()}.  
 
171
%%
 
172
%% Description: Set the ssl process to own the accept socket
 
173
%%--------------------------------------------------------------------      
 
174
socket_control(Socket, Pid, CbModule) ->
 
175
    case CbModule:controlling_process(Socket, Pid) of
 
176
        ok ->
 
177
            {ok, sslsocket(Pid)};
 
178
        {error, Reason} ->
 
179
            {error, Reason}
 
180
    end.
 
181
 
 
182
%%--------------------------------------------------------------------
 
183
-spec close(pid()) -> ok | {error, reason()}.  
 
184
%%
 
185
%% Description:  Close a ssl connection
132
186
%%--------------------------------------------------------------------
133
187
close(ConnectionPid) ->
134
188
    case sync_send_all_state_event(ConnectionPid, close) of
139
193
    end.
140
194
 
141
195
%%--------------------------------------------------------------------
142
 
%% Function: 
 
196
-spec shutdown(pid(), atom()) -> ok | {error, reason()}.  
143
197
%%
144
 
%% Description: 
 
198
%% Description: Same as gen_tcp:shutdown/2
145
199
%%--------------------------------------------------------------------
146
200
shutdown(ConnectionPid, How) ->
147
201
    sync_send_all_state_event(ConnectionPid, {shutdown, How}).
148
202
 
149
 
 
150
203
%%--------------------------------------------------------------------
151
 
%% Function: 
 
204
-spec new_user(pid(), pid()) ->  ok | {error, reason()}.
152
205
%%
153
 
%% Description: 
 
206
%% Description:  Changes process that receives the messages when active = true
 
207
%% or once. 
154
208
%%--------------------------------------------------------------------
155
209
new_user(ConnectionPid, User) ->
156
210
    sync_send_all_state_event(ConnectionPid, {new_user, User}).
157
211
%%--------------------------------------------------------------------
158
 
%% Function: 
 
212
-spec sockname(pid()) -> {ok, {tuple(), port_num()}} | {error, reason()}.
159
213
%%
160
 
%% Description: 
 
214
%% Description:  Same as inet:sockname/1
161
215
%%--------------------------------------------------------------------
162
216
sockname(ConnectionPid) ->
163
217
    sync_send_all_state_event(ConnectionPid, sockname).
164
218
%%--------------------------------------------------------------------
165
 
%% Function: 
 
219
-spec peername(pid()) -> {ok, {tuple(), port_num()}} | {error, reason()}.
166
220
%%
167
 
%% Description: 
 
221
%% Description:  Same as inet:peername/1
168
222
%%--------------------------------------------------------------------
169
223
peername(ConnectionPid) ->
170
224
    sync_send_all_state_event(ConnectionPid, peername).
171
225
%%--------------------------------------------------------------------
172
 
%% Function: 
 
226
-spec get_opts(pid(), list()) -> {ok, list()} | {error, reason()}.    
173
227
%%
174
 
%% Description: 
 
228
%% Description: Same as inet:getopts/2
175
229
%%--------------------------------------------------------------------
176
 
get_opts({ListenSocket, {_SslOpts, SockOpts}, _}, OptTags) ->
177
 
    get_socket_opts(ListenSocket, OptTags, SockOpts, []);
178
230
get_opts(ConnectionPid, OptTags) ->
179
231
    sync_send_all_state_event(ConnectionPid, {get_opts, OptTags}).
180
232
%%--------------------------------------------------------------------
181
 
%% Function: 
 
233
-spec set_opts(pid(), list()) -> ok | {error, reason()}. 
182
234
%%
183
 
%% Description: 
 
235
%% Description:  Same as inet:setopts/2
184
236
%%--------------------------------------------------------------------
185
237
set_opts(ConnectionPid, Options) ->
186
238
    sync_send_all_state_event(ConnectionPid, {set_opts, Options}).
187
239
 
188
240
%%--------------------------------------------------------------------
189
 
%% Function: 
 
241
-spec info(pid()) ->  {ok, {atom(), tuple()}} | {error, reason()}. 
190
242
%%
191
 
%% Description: 
 
243
%% Description:  Returns ssl protocol and cipher used for the connection
192
244
%%--------------------------------------------------------------------
193
245
info(ConnectionPid) ->
194
246
    sync_send_all_state_event(ConnectionPid, info). 
195
247
 
196
248
%%--------------------------------------------------------------------
197
 
%% Function: 
 
249
-spec session_info(pid()) -> {ok, list()} | {error, reason()}. 
198
250
%%
199
 
%% Description: 
 
251
%% Description:  Returns info about the ssl session
200
252
%%--------------------------------------------------------------------
201
253
session_info(ConnectionPid) ->
202
254
    sync_send_all_state_event(ConnectionPid, session_info). 
203
255
 
204
256
%%--------------------------------------------------------------------
205
 
%% Function: 
 
257
-spec peer_certificate(pid()) -> {ok, binary()| undefined} | {error, reason()}.
206
258
%%
207
 
%% Description: 
 
259
%% Description: Returns the peer cert
208
260
%%--------------------------------------------------------------------
209
261
peer_certificate(ConnectionPid) ->
210
262
    sync_send_all_state_event(ConnectionPid, peer_certificate). 
211
263
 
 
264
%%--------------------------------------------------------------------
 
265
-spec renegotiation(pid()) -> ok | {error, reason()}.
 
266
%%
 
267
%% Description: Starts a renegotiation of the ssl session.
 
268
%%--------------------------------------------------------------------
 
269
renegotiation(ConnectionPid) ->
 
270
    sync_send_all_state_event(ConnectionPid, renegotiate). 
 
271
 
212
272
%%====================================================================
213
273
%% ssl_connection_sup API
214
274
%%====================================================================
215
275
 
216
276
%%--------------------------------------------------------------------
217
 
%% Function: start_link() -> {ok,Pid} | ignore | {error,Error}
 
277
-spec start_link(atom(), host(), port_num(), port(), list(), pid(), tuple()) ->
 
278
    {ok, pid()} | ignore |  {error, reason()}.
218
279
%%
219
280
%% Description: Creates a gen_fsm process which calls Module:init/1 to
220
281
%% initialize. To ensure a synchronized start-up procedure, this function
224
285
    gen_fsm:start_link(?MODULE, [Role, Host, Port, Socket, Options,
225
286
                                 User, CbInfo], []).
226
287
 
227
 
 
228
288
%%====================================================================
229
289
%% gen_fsm callbacks
230
290
%%====================================================================
231
291
%%--------------------------------------------------------------------
232
 
%% Function: init(Args) -> {ok, StateName, State} |
233
 
%%                         {ok, StateName, State, Timeout} |
234
 
%%                         ignore                              |
235
 
%%                         {stop, StopReason}                   
 
292
-spec init(list()) -> {ok, state_name(), #state{}, timeout()} | {stop, term()}.
 
293
%% Possible return values not used now.
 
294
%%                        | {ok, state_name(), #state{}} |
 
295
%%                        ignore  
236
296
%% Description:Whenever a gen_fsm is started using gen_fsm:start/[3,4] or
237
297
%% gen_fsm:start_link/3,4, this function is called by the new process to 
238
298
%% initialize. 
239
299
%%--------------------------------------------------------------------
240
 
init([Role, Host, Port, Socket, {SSLOpts, _} = Options, 
 
300
init([Role, Host, Port, Socket, {SSLOpts0, _} = Options, 
241
301
      User, CbInfo]) ->
242
302
    State0 = initial_state(Role, Host, Port, Socket, Options, User, CbInfo),
243
303
    Hashes0 = ssl_handshake:init_hashes(),    
244
304
 
245
 
    try ssl_init(SSLOpts, Role) of
246
 
        {ok, Ref, CacheRef, OwnCert, Key} ->       
 
305
    try ssl_init(SSLOpts0, Role) of
 
306
        {ok, Ref, CacheRef, OwnCert, Key, DHParams} ->     
 
307
            Session = State0#state.session,
247
308
            State = State0#state{tls_handshake_hashes = Hashes0,
248
 
                                 own_cert = OwnCert,
 
309
                                 session = Session#session{own_certificate = OwnCert},
249
310
                                 cert_db_ref = Ref,
250
311
                                 session_cache = CacheRef,
251
 
                                 private_key = Key},
252
 
            {ok, hello, State}
 
312
                                 private_key = Key,
 
313
                                 diffie_hellman_params = DHParams},
 
314
            {ok, hello, State, get_timeout(State)}
253
315
    catch   
254
316
        throw:Error ->
255
317
            {stop, Error}
256
318
    end.
257
 
  
258
 
%%--------------------------------------------------------------------
259
 
%% Function: 
260
 
%% state_name(Event, State) -> {next_state, NextStateName, NextState}|
261
 
%%                             {next_state, NextStateName, 
262
 
%%                                NextState, Timeout} |
263
 
%%                             {stop, Reason, NewState}
264
 
%% Description:There should be one instance of this function for each possible
265
 
%% state name. Whenever a gen_fsm receives an event sent using
266
 
%% gen_fsm:send_event/2, the instance of this function with the same name as
267
 
%% the current state name StateName is called to handle the event. It is also 
268
 
%% called if a timeout occurs. 
269
 
%%--------------------------------------------------------------------
270
 
hello(socket_control, #state{host = Host, port = Port, role = client,
271
 
                             ssl_options = SslOpts, 
272
 
                             transport_cb = Transport, socket = Socket,
273
 
                             connection_states = ConnectionStates}
274
 
      = State0) ->
275
 
    Hello = ssl_handshake:client_hello(Host, Port, ConnectionStates, SslOpts),
 
319
   
 
320
%%--------------------------------------------------------------------
 
321
%% -spec state_name(event(), #state{}) -> gen_fsm_state_return()
 
322
%%
 
323
%% Description:There should be one instance of this function for each
 
324
%% possible state name. Whenever a gen_fsm receives an event sent
 
325
%% using gen_fsm:send_event/2, the instance of this function with the
 
326
%% same name as the current state name StateName is called to handle
 
327
%% the event. It is also called if a timeout occurs.
 
328
%%
 
329
%%--------------------------------------------------------------------
 
330
-spec hello(start | #hello_request{} | #client_hello{} | #server_hello{} | term(),
 
331
            #state{}) -> gen_fsm_state_return().    
 
332
%%--------------------------------------------------------------------
 
333
hello(start, #state{host = Host, port = Port, role = client,
 
334
                    ssl_options = SslOpts, 
 
335
                    session = #session{own_certificate = Cert} = Session0,
 
336
                    transport_cb = Transport, socket = Socket,
 
337
                    connection_states = ConnectionStates,
 
338
                    renegotiation = {Renegotiation, _}} = State0) ->
 
339
    Hello = ssl_handshake:client_hello(Host, Port, 
 
340
                                       ConnectionStates, 
 
341
                                       SslOpts, Renegotiation, Cert),
 
342
 
276
343
    Version = Hello#client_hello.client_version,
277
344
    Hashes0 = ssl_handshake:init_hashes(),
278
345
    {BinMsg, CS2, Hashes1} = 
279
346
        encode_handshake(Hello, Version, ConnectionStates, Hashes0),
280
347
    Transport:send(Socket, BinMsg),
281
 
    State = State0#state{connection_states = CS2,
 
348
    State1 = State0#state{connection_states = CS2,
282
349
                         negotiated_version = Version, %% Requested version
283
 
                         session = 
284
 
                         #session{session_id = Hello#client_hello.session_id,
285
 
                                  is_resumable = false},
286
 
                         tls_handshake_hashes = Hashes1},
287
 
    {next_state, hello, next_record(State)};
288
 
    
289
 
hello(socket_control, #state{role = server} = State) ->
290
 
    {next_state, hello, next_record(State)};
291
 
 
292
 
hello(hello, #state{role = client} = State) ->
293
 
    {next_state, hello, State};
 
350
                          session =
 
351
                              Session0#session{session_id = Hello#client_hello.session_id,
 
352
                                               is_resumable = false},
 
353
                          tls_handshake_hashes = Hashes1},
 
354
    {Record, State} = next_record(State1),
 
355
    next_state(hello, Record, State);
 
356
 
 
357
hello(start, #state{role = server} = State0) ->
 
358
    {Record, State} = next_record(State0),
 
359
    next_state(hello, Record, State);
 
360
 
 
361
hello(#hello_request{}, #state{role = client} = State0) ->
 
362
    {Record, State} = next_record(State0),
 
363
    next_state(hello, Record, State);
294
364
 
295
365
hello(#server_hello{cipher_suite = CipherSuite,
296
366
                    compression_method = Compression} = Hello,
297
 
      #state{session = Session0 = #session{session_id = OldId},
 
367
      #state{session = #session{session_id = OldId},
298
368
             connection_states = ConnectionStates0,
299
369
             role = client,
300
370
             negotiated_version = ReqVersion,
301
 
             host = Host, port = Port,
302
 
             session_cache = Cache,
303
 
             session_cache_cb = CacheCb} = State0) ->
304
 
    {Version, NewId, ConnectionStates1} =
305
 
        ssl_handshake:hello(Hello, ConnectionStates0),
306
 
 
307
 
    {KeyAlgorithm, _, _, _} = 
308
 
        ssl_cipher:suite_definition(CipherSuite),
309
 
    
310
 
    PremasterSecret = make_premaster_secret(ReqVersion),
311
 
    
312
 
    State = State0#state{key_algorithm = KeyAlgorithm,
313
 
                         negotiated_version = Version,
314
 
                         connection_states = ConnectionStates1,
315
 
                         premaster_secret = PremasterSecret},
316
 
 
317
 
    case ssl_session:is_new(OldId, NewId) of
318
 
        true ->
319
 
            Session = Session0#session{session_id = NewId,
320
 
                                       cipher_suite = CipherSuite,
321
 
                                       compression_method = Compression}, 
322
 
            {next_state, certify, 
323
 
             next_record(State#state{session = Session})};
324
 
        false ->
325
 
            Session = CacheCb:lookup(Cache, {{Host, Port}, NewId}),
326
 
            case ssl_handshake:master_secret(Version, Session, 
327
 
                                             ConnectionStates1, client) of
328
 
                {_, ConnectionStates2} ->       
329
 
                    {next_state, abbreviated,
330
 
                     next_record(State#state{
331
 
                                   connection_states = ConnectionStates2,
332
 
                                   session = Session})};
333
 
                #alert{} = Alert ->
334
 
                    handle_own_alert(Alert, Version, hello, State), 
335
 
                    {stop, normal, State}
336
 
            end
 
371
             renegotiation = {Renegotiation, _},
 
372
             ssl_options = SslOptions} = State0) ->
 
373
    case ssl_handshake:hello(Hello, SslOptions, ConnectionStates0, Renegotiation) of
 
374
        {Version, NewId, ConnectionStates} ->
 
375
            {KeyAlgorithm, _, _} =
 
376
                ssl_cipher:suite_definition(CipherSuite),
 
377
            
 
378
            PremasterSecret = make_premaster_secret(ReqVersion, KeyAlgorithm),
 
379
            
 
380
            State = State0#state{key_algorithm = KeyAlgorithm,
 
381
                                 negotiated_version = Version,
 
382
                                 connection_states = ConnectionStates,
 
383
                                 premaster_secret = PremasterSecret},
 
384
            
 
385
            case ssl_session:is_new(OldId, NewId) of
 
386
                true ->
 
387
                    handle_new_session(NewId, CipherSuite, Compression, State);
 
388
                false ->
 
389
                    handle_resumed_session(NewId, State#state{connection_states = ConnectionStates}) 
 
390
            end;
 
391
        #alert{} = Alert ->
 
392
            handle_own_alert(Alert, ReqVersion, hello, State0), 
 
393
            {stop, normal, State0}
337
394
    end;
338
395
 
339
396
hello(Hello = #client_hello{client_version = ClientVersion}, 
340
397
      State = #state{connection_states = ConnectionStates0,
341
 
                     port = Port, session = Session0,
342
 
                     session_cache = Cache,
 
398
                     port = Port, session = #session{own_certificate = Cert} = Session0,
 
399
                     renegotiation = {Renegotiation, _},
 
400
                     session_cache = Cache,               
343
401
                     session_cache_cb = CacheCb,
344
402
                     ssl_options = SslOpts}) ->
345
 
    
346
 
    case ssl_handshake:hello(Hello, {Port, SslOpts,  
347
 
                                     Session0, Cache, CacheCb,
348
 
                                     ConnectionStates0}) of
 
403
    case ssl_handshake:hello(Hello, SslOpts, {Port, Session0, Cache, CacheCb,
 
404
                                     ConnectionStates0, Cert}, Renegotiation) of
349
405
        {Version, {Type, Session}, ConnectionStates} ->       
350
406
            do_server_hello(Type, State#state{connection_states  = 
351
407
                                              ConnectionStates,
354
410
        #alert{} = Alert ->
355
411
            handle_own_alert(Alert, ClientVersion, hello, State), 
356
412
            {stop, normal, State}
357
 
    end.
358
 
 
359
 
abbreviated(socket_control, #state{role = server} = State) ->
360
 
    {next_state, abbreviated, State};
361
 
abbreviated(hello, State) ->
362
 
    {next_state, certify, State};
363
 
 
364
 
abbreviated(Finished = #finished{},
 
413
    end;
 
414
 
 
415
hello(timeout, State) ->
 
416
    { next_state, hello, State, hibernate };
 
417
 
 
418
hello(Msg, State) ->
 
419
    handle_unexpected_message(Msg, hello, State).
 
420
%%--------------------------------------------------------------------
 
421
-spec abbreviated(#hello_request{} | #finished{} | term(),
 
422
                  #state{}) -> gen_fsm_state_return().   
 
423
%%--------------------------------------------------------------------
 
424
abbreviated(#hello_request{}, State0) ->
 
425
    {Record, State} = next_record(State0),
 
426
    next_state(hello, Record, State);
 
427
 
 
428
abbreviated(#finished{verify_data = Data} = Finished,
365
429
            #state{role = server,
366
430
                   negotiated_version = Version,
367
431
                   tls_handshake_hashes = Hashes,
368
432
                   session = #session{master_secret = MasterSecret},
369
 
                   from = From} = State) ->
 
433
                  connection_states = ConnectionStates0} = 
 
434
            State) ->
370
435
    case ssl_handshake:verify_connection(Version, Finished, client,
371
436
                                         MasterSecret, Hashes) of
372
 
        verified ->
373
 
            gen_fsm:reply(From, connected),
374
 
            {next_state, connection, next_record_if_active(State)};
375
 
        #alert{} = Alert ->
 
437
        verified ->  
 
438
            ConnectionStates = ssl_record:set_client_verify_data(current_both, Data, ConnectionStates0),
 
439
            next_state_connection(abbreviated, 
 
440
                                  ack_connection(State#state{connection_states = ConnectionStates}));
 
441
        #alert{} = Alert ->
376
442
            handle_own_alert(Alert, Version, abbreviated, State),
377
443
            {stop, normal, State} 
378
444
    end;
379
445
 
380
 
abbreviated(Finished = #finished{},
 
446
abbreviated(#finished{verify_data = Data} = Finished,
381
447
            #state{role = client, tls_handshake_hashes = Hashes0,
382
448
                   session = #session{master_secret = MasterSecret},
383
 
                   from = From,
384
 
                   negotiated_version = Version} = State) ->
 
449
                   negotiated_version = Version,
 
450
                   connection_states = ConnectionStates0} = State) ->
385
451
    case ssl_handshake:verify_connection(Version, Finished, server,
386
452
                                         MasterSecret, Hashes0) of
387
453
        verified ->
388
 
            {ConnectionStates, Hashes} = finalize_client_handshake(State),
389
 
            gen_fsm:reply(From, connected),
390
 
            {next_state, connection,
391
 
             next_record_if_active(State#state{tls_handshake_hashes = Hashes,
392
 
                                               connection_states = 
393
 
                                               ConnectionStates})};
 
454
            ConnectionStates1 = ssl_record:set_server_verify_data(current_read, Data, ConnectionStates0),
 
455
            {ConnectionStates, Hashes} = 
 
456
                finalize_handshake(State#state{connection_states = ConnectionStates1}, abbreviated),
 
457
            next_state_connection(abbreviated, 
 
458
                                  ack_connection(State#state{tls_handshake_hashes = Hashes,
 
459
                                                             connection_states = 
 
460
                                                             ConnectionStates}));
394
461
        #alert{} = Alert ->
395
462
            handle_own_alert(Alert, Version, abbreviated, State),
396
463
            {stop, normal, State} 
397
 
    end.
398
 
 
399
 
certify(socket_control, #state{role = server} = State) ->
400
 
    {next_state, certify, State};
401
 
certify(hello, State) ->
402
 
    {next_state, certify, State};
 
464
    end;
 
465
 
 
466
abbreviated(timeout, State) ->
 
467
    { next_state, abbreviated, State, hibernate };
 
468
 
 
469
abbreviated(Msg, State) ->
 
470
    handle_unexpected_message(Msg, abbreviated, State).
 
471
 
 
472
%%--------------------------------------------------------------------
 
473
-spec certify(#hello_request{} | #certificate{} |  #server_key_exchange{} |
 
474
              #certificate_request{} | #server_hello_done{} | #client_key_exchange{} | term(),
 
475
              #state{}) -> gen_fsm_state_return().   
 
476
%%--------------------------------------------------------------------
 
477
certify(#hello_request{}, State0) ->
 
478
    {Record, State} = next_record(State0),
 
479
    next_state(hello, Record, State);
403
480
 
404
481
certify(#certificate{asn1_certificates = []}, 
405
482
        #state{role = server, negotiated_version = Version,
414
491
        #state{role = server,
415
492
               ssl_options = #ssl_options{verify = verify_peer,
416
493
                                          fail_if_no_peer_cert = false}} = 
417
 
        State) ->
418
 
    {next_state, certify, next_record(State#state{client_certificate_requested = false})};
 
494
        State0) ->
 
495
    {Record, State} = next_record(State0#state{client_certificate_requested = false}),
 
496
    next_state(certify, Record, State);
419
497
 
420
498
certify(#certificate{} = Cert, 
421
 
        #state{session = Session, 
422
 
               negotiated_version = Version,
 
499
        #state{negotiated_version = Version,
 
500
               role = Role,
423
501
               cert_db_ref = CertDbRef,
424
 
               ssl_options = Opts} = State0) ->
 
502
               ssl_options = Opts} = State) ->
425
503
    case ssl_handshake:certify(Cert, CertDbRef, Opts#ssl_options.depth, 
426
504
                               Opts#ssl_options.verify,
427
 
                               Opts#ssl_options.verify_fun) of
 
505
                               Opts#ssl_options.verify_fun, Role) of
428
506
        {PeerCert, PublicKeyInfo} ->
429
 
            State = State0#state{session = 
430
 
                                 Session#session{peer_certificate = PeerCert},                           
431
 
                                 public_key_info = PublicKeyInfo,
432
 
                                 client_certificate_requested = false
433
 
                                },
434
 
            {next_state, certify, next_record(State)};
 
507
            handle_peer_cert(PeerCert, PublicKeyInfo, 
 
508
                             State#state{client_certificate_requested = false});
435
509
        #alert{} = Alert ->
436
 
            handle_own_alert(Alert, Version, certify_certificate, State0),
437
 
            {stop, normal, State0}
 
510
            handle_own_alert(Alert, Version, certify_certificate, State),
 
511
            {stop, normal, State}
438
512
    end;
439
513
 
440
514
certify(#server_key_exchange{} = KeyExchangeMsg, 
441
 
        #state{role = client,
442
 
               key_algorithm = Alg} = State) 
443
 
  when Alg == dhe_dss; Alg == dhe_rsa; Alg == dh_anon; Alg == krb5 ->
444
 
    NewState = handle_server_key(KeyExchangeMsg, State),
445
 
    {next_state, certify, NewState};
446
 
 
447
 
certify(#server_key_exchange{}, 
448
 
        State = #state{role = client, negotiated_version = Version,
449
 
                       key_algorithm = Alg}) 
450
 
  when Alg == rsa; Alg == dh_dss; Alg == dh_rsa ->
451
 
    Alert = ?ALERT_REC(?FATAL, ?UNEXPECTED_MESSAGE),
452
 
    handle_own_alert(Alert, Version, certify_server_key_exchange, State),
453
 
    {stop, normal, State};
454
 
 
455
 
certify(KeyExchangeMsg = #server_key_exchange{}, State = 
456
 
        #state{role = server}) ->
457
 
    NewState = handle_clinet_key(KeyExchangeMsg, State),
458
 
    {next_state, cipher, NewState};
459
 
 
460
 
certify(#certificate_request{}, State) ->
461
 
    NewState = State#state{client_certificate_requested = true},
462
 
    {next_state, certify, next_record(NewState)};
463
 
 
 
515
        #state{role = client, negotiated_version = Version,
 
516
               key_algorithm = Alg} = State0) 
 
517
  when Alg == dhe_dss; Alg == dhe_rsa;  Alg == dh_anon ->
 
518
    case handle_server_key(KeyExchangeMsg, State0) of
 
519
        #state{} = State1 ->
 
520
            {Record, State} = next_record(State1),
 
521
            next_state(certify, Record, State);
 
522
        #alert{} = Alert ->
 
523
            handle_own_alert(Alert, Version, certify_server_keyexchange, 
 
524
                             State0),
 
525
            {stop, normal, State0}
 
526
    end;
 
527
 
 
528
certify(#server_key_exchange{} = Msg, 
 
529
        #state{role = client, key_algorithm = rsa} = State) -> 
 
530
    handle_unexpected_message(Msg, certify_server_keyexchange, State);
 
531
 
 
532
certify(#certificate_request{}, State0) ->
 
533
    {Record, State} = next_record(State0#state{client_certificate_requested = true}),
 
534
    next_state(certify, Record, State);
 
535
 
 
536
%% Master secret was determined with help of server-key exchange msg
 
537
certify(#server_hello_done{},
 
538
        #state{session = #session{master_secret = MasterSecret} = Session,
 
539
               connection_states = ConnectionStates0,
 
540
               negotiated_version = Version,
 
541
               premaster_secret = undefined,
 
542
               role = client} = State0) ->
 
543
    case ssl_handshake:master_secret(Version, Session, 
 
544
                                     ConnectionStates0, client) of
 
545
        {MasterSecret, ConnectionStates1} -> 
 
546
            State = State0#state{connection_states = ConnectionStates1},
 
547
            client_certify_and_key_exchange(State);
 
548
        #alert{} = Alert ->
 
549
            handle_own_alert(Alert, Version, 
 
550
                             certify_server_hello_done, State0),
 
551
            {stop, normal, State0} 
 
552
    end;
 
553
 
 
554
%% Master secret is calculated from premaster_secret
464
555
certify(#server_hello_done{},
465
556
        #state{session = Session0,
466
557
               connection_states = ConnectionStates0,
480
571
            {stop, normal, State0} 
481
572
    end;
482
573
 
483
 
certify(#client_key_exchange{},
484
 
        State = #state{role = server,
485
 
                       client_certificate_requested = true,
486
 
                       ssl_options = #ssl_options{fail_if_no_peer_cert = true},
487
 
                       negotiated_version = Version}) ->
 
574
certify(#client_key_exchange{} = Msg,
 
575
        #state{role = server,
 
576
               client_certificate_requested = true,
 
577
               ssl_options = #ssl_options{fail_if_no_peer_cert = true}} = State) ->
488
578
    %% We expect a certificate here
489
 
    Alert = ?ALERT_REC(?FATAL, ?UNEXPECTED_MESSAGE),
490
 
    handle_own_alert(Alert, Version, certify_server_waiting_certificate, State),
491
 
    {stop, normal, State};
492
 
 
493
 
 
494
 
certify(#client_key_exchange{exchange_keys 
495
 
                             = #encrypted_premaster_secret{premaster_secret 
496
 
                                                           = EncPMS}},
497
 
        #state{negotiated_version = Version,
498
 
               connection_states = ConnectionStates0,
499
 
               session = Session0,
500
 
               private_key = Key} = State0) ->
501
 
    try ssl_handshake:decrypt_premaster_secret(EncPMS, Key) of
502
 
        PremasterSecret ->
503
 
            case ssl_handshake:master_secret(Version, PremasterSecret, 
504
 
                                             ConnectionStates0, server) of
505
 
                {MasterSecret, ConnectionStates} ->
506
 
                    Session = Session0#session{master_secret = MasterSecret},
507
 
                    State = State0#state{connection_states = ConnectionStates,
508
 
                                         session = Session},
509
 
                    {next_state, cipher, next_record(State)};
510
 
                #alert{} = Alert ->
511
 
                    handle_own_alert(Alert, Version, 
512
 
                                     certify_client_key_exchange, State0),
513
 
                    {stop, normal, State0} 
514
 
            end
 
579
    handle_unexpected_message(Msg, certify_client_key_exchange, State);
 
580
 
 
581
certify(#client_key_exchange{exchange_keys = Keys},
 
582
        State = #state{key_algorithm = KeyAlg, negotiated_version = Version}) ->
 
583
    try
 
584
        certify_client_key_exchange(ssl_handshake:decode_client_key(Keys, KeyAlg, Version), State)
515
585
    catch 
516
586
        #alert{} = Alert ->
517
 
            handle_own_alert(Alert, Version, certify_client_key_exchange, 
518
 
                             State0),
 
587
            handle_own_alert(Alert, Version, certify_client_key_exchange, State),
 
588
            {stop, normal, State}
 
589
    end;
 
590
 
 
591
certify(timeout, State) ->
 
592
    { next_state, certify, State, hibernate };
 
593
 
 
594
certify(Msg, State) ->
 
595
    handle_unexpected_message(Msg, certify, State).
 
596
 
 
597
certify_client_key_exchange(#encrypted_premaster_secret{premaster_secret= EncPMS},
 
598
                            #state{negotiated_version = Version,
 
599
                                   connection_states = ConnectionStates0,
 
600
                                   session = Session0,
 
601
                                   private_key = Key} = State0) ->
 
602
    PremasterSecret = ssl_handshake:decrypt_premaster_secret(EncPMS, Key),
 
603
    case ssl_handshake:master_secret(Version, PremasterSecret,
 
604
                                     ConnectionStates0, server) of
 
605
        {MasterSecret, ConnectionStates} ->
 
606
            Session = Session0#session{master_secret = MasterSecret},
 
607
            State1 = State0#state{connection_states = ConnectionStates,
 
608
                                  session = Session},
 
609
            {Record, State} = next_record(State1),
 
610
            next_state(cipher, Record, State);
 
611
        #alert{} = Alert ->
 
612
            handle_own_alert(Alert, Version,
 
613
                             certify_client_key_exchange, State0),
 
614
            {stop, normal, State0} 
 
615
    end;
 
616
 
 
617
certify_client_key_exchange(#client_diffie_hellman_public{dh_public = ClientPublicDhKey},
 
618
                            #state{negotiated_version = Version,
 
619
                                   diffie_hellman_params = #'DHParameter'{prime = P,
 
620
                                                                          base = G},
 
621
                                   diffie_hellman_keys = {_, ServerDhPrivateKey}} = State0) ->
 
622
    case dh_master_secret(crypto:mpint(P), crypto:mpint(G), ClientPublicDhKey, ServerDhPrivateKey, State0) of
 
623
        #state{} = State1 ->
 
624
            {Record, State} = next_record(State1),
 
625
            next_state(cipher, Record, State);
 
626
        #alert{} = Alert ->
 
627
            handle_own_alert(Alert, Version, 
 
628
                             certify_client_key_exchange, State0),
519
629
            {stop, normal, State0} 
520
630
    end.
521
631
 
522
 
cipher(socket_control, #state{role = server} = State) ->
523
 
    {next_state, cipher, State};
524
 
cipher(hello, State) ->
525
 
    {next_state, cipher, State};
 
632
%%--------------------------------------------------------------------
 
633
-spec cipher(#hello_request{} | #certificate_verify{} | #finished{} | term(),
 
634
             #state{}) -> gen_fsm_state_return().  
 
635
%%--------------------------------------------------------------------
 
636
cipher(#hello_request{}, State0) ->
 
637
    {Record, State} = next_record(State0),
 
638
    next_state(hello, Record, State);
526
639
 
527
640
cipher(#certificate_verify{signature = Signature}, 
528
641
       #state{role = server, 
529
642
              public_key_info = PublicKeyInfo,
530
643
              negotiated_version = Version,
531
644
              session = #session{master_secret = MasterSecret},
532
 
              key_algorithm = Algorithm,
533
645
              tls_handshake_hashes = Hashes
534
 
             } = State) -> 
 
646
             } = State0) -> 
535
647
    case ssl_handshake:certificate_verify(Signature, PublicKeyInfo,
536
 
                                          Version, MasterSecret, 
537
 
                                          Algorithm, Hashes) of
 
648
                                          Version, MasterSecret, Hashes) of
538
649
        valid ->
539
 
            {next_state, cipher, next_record(State)};
 
650
            {Record, State} = next_record(State0),
 
651
            next_state(cipher, Record, State);
540
652
        #alert{} = Alert ->
541
 
            handle_own_alert(Alert, Version, cipher, State), 
542
 
            {stop, normal, State}
 
653
            handle_own_alert(Alert, Version, cipher, State0), 
 
654
            {stop, normal, State0}
543
655
    end;
544
656
 
545
 
cipher(#finished{} = Finished, 
546
 
       State = #state{from = From,
547
 
                      negotiated_version = Version,
548
 
                      host = Host,
549
 
                      port = Port,
550
 
                      role = Role,
551
 
                      session = #session{master_secret = MasterSecret} 
552
 
                      = Session0,
553
 
                      tls_handshake_hashes = Hashes}) ->    
554
 
 
 
657
cipher(#finished{verify_data = Data} = Finished, 
 
658
       #state{negotiated_version = Version,
 
659
              host = Host,
 
660
              port = Port,
 
661
              role = Role,
 
662
              session = #session{master_secret = MasterSecret} 
 
663
              = Session0,
 
664
              tls_handshake_hashes = Hashes0} = State) ->
555
665
    case ssl_handshake:verify_connection(Version, Finished, 
556
666
                                         opposite_role(Role), 
557
 
                                         MasterSecret, Hashes) of
 
667
                                         MasterSecret, Hashes0) of
558
668
        verified ->
559
 
            gen_fsm:reply(From, connected),
560
669
            Session = register_session(Role, Host, Port, Session0),
561
 
            case Role of
562
 
                client ->
563
 
                    {next_state, connection, 
564
 
                     next_record_if_active(State#state{session = Session})};
565
 
                server ->
566
 
                    {NewConnectionStates, NewHashes} = 
567
 
                        finalize_server_handshake(State#state{
568
 
                                                    session = Session}),
569
 
                    NewState = 
570
 
                        State#state{connection_states = NewConnectionStates,
571
 
                                    session = Session,
572
 
                                    tls_handshake_hashes = NewHashes},
573
 
                    {next_state, connection, next_record_if_active(NewState)}
574
 
            end;
 
670
            cipher_role(Role, Data, Session, State);
575
671
        #alert{} = Alert ->
576
672
            handle_own_alert(Alert, Version, cipher, State),
577
673
            {stop, normal, State} 
578
 
    end.
579
 
 
580
 
connection(socket_control, #state{role = server} = State) ->
581
 
    {next_state, connection, State};
582
 
connection(hello, State = #state{host = Host, port = Port,
583
 
                                 socket = Socket,
584
 
                                 ssl_options = SslOpts,
585
 
                                 negotiated_version = Version,
586
 
                                 transport_cb = Transport,
587
 
                                 connection_states = ConnectionStates0,
588
 
                                 tls_handshake_hashes = Hashes0}) ->
589
 
 
590
 
    Hello = ssl_handshake:client_hello(Host, Port, 
591
 
                                       ConnectionStates0, SslOpts),
 
674
    end;
 
675
 
 
676
cipher(timeout, State) ->
 
677
    { next_state, cipher, State, hibernate };
 
678
 
 
679
cipher(Msg, State) ->
 
680
    handle_unexpected_message(Msg, cipher, State).
 
681
 
 
682
%%--------------------------------------------------------------------
 
683
-spec connection(#hello_request{} | #client_hello{} | term(),
 
684
                 #state{}) -> gen_fsm_state_return().  
 
685
%%--------------------------------------------------------------------
 
686
connection(#hello_request{}, #state{host = Host, port = Port,
 
687
                                    socket = Socket,
 
688
                                    session = #session{own_certificate = Cert},
 
689
                                    ssl_options = SslOpts,
 
690
                                    negotiated_version = Version,
 
691
                                    transport_cb = Transport,
 
692
                                    connection_states = ConnectionStates0,
 
693
                                    renegotiation = {Renegotiation, _},
 
694
                                    tls_handshake_hashes = Hashes0} = State0) ->
 
695
    Hello = ssl_handshake:client_hello(Host, Port, ConnectionStates0,
 
696
                                       SslOpts, Renegotiation, Cert),
 
697
  
592
698
    {BinMsg, ConnectionStates1, Hashes1} =
593
699
        encode_handshake(Hello, Version, ConnectionStates0, Hashes0),
594
700
    Transport:send(Socket, BinMsg),
595
 
    {next_state, hello, State#state{connection_states = ConnectionStates1,
596
 
                                    tls_handshake_hashes = Hashes1}}.
597
 
 
598
 
%%--------------------------------------------------------------------
599
 
%% Function:
600
 
%% state_name(Event, From, State) -> {next_state, NextStateName, NextState} |
601
 
%%                                   {next_state, NextStateName, 
602
 
%%                                     NextState, Timeout} |
603
 
%%                                   {reply, Reply, NextStateName, NextState}|
604
 
%%                                   {reply, Reply, NextStateName, 
605
 
%%                                    NextState, Timeout} |
606
 
%%                                   {stop, Reason, NewState}|
607
 
%%                                   {stop, Reason, Reply, NewState}
608
 
%% Description: There should be one instance of this function for each
609
 
%% possible state name. Whenever a gen_fsm receives an event sent using
610
 
%% gen_fsm:sync_send_event/2,3, the instance of this function with the same
611
 
%% name as the current state name StateName is called to handle the event.
612
 
%%--------------------------------------------------------------------
613
 
connection({application_data, Data}, _From, 
614
 
           State = #state{socket = Socket,
615
 
                          negotiated_version = Version,
616
 
                          transport_cb = Transport,
617
 
                          connection_states = ConnectionStates0}) ->
 
701
    {Record, State} = next_record(State0#state{connection_states =  
 
702
                                               ConnectionStates1,
 
703
                                               tls_handshake_hashes = Hashes1}),
 
704
    next_state(hello, Record, State);
 
705
connection(#client_hello{} = Hello, #state{role = server} = State) ->
 
706
    hello(Hello, State);
 
707
 
 
708
connection(timeout, State) ->
 
709
    {next_state, connection, State, hibernate};
 
710
 
 
711
connection(Msg, State) ->
 
712
    handle_unexpected_message(Msg, connection, State).
 
713
%%--------------------------------------------------------------------
 
714
-spec handle_event(term(), state_name(), #state{}) -> term().
 
715
%% As it is not currently used gen_fsm_state_return() makes
 
716
%% dialyzer unhappy!
 
717
%%
 
718
%% Description: Whenever a gen_fsm receives an event sent using
 
719
%% gen_fsm:send_all_state_event/2, this function is called to handle
 
720
%% the event. Not currently used!
 
721
%%--------------------------------------------------------------------
 
722
handle_event(_Event, StateName, State) ->
 
723
    {next_state, StateName, State, get_timeout(State)}.
 
724
 
 
725
%%--------------------------------------------------------------------
 
726
-spec handle_sync_event(term(), from(), state_name(), #state{}) -> 
 
727
                               gen_fsm_state_return() |  
 
728
                               {reply, reply(), state_name(), #state{}} |
 
729
                               {reply, reply(), state_name(), #state{}, timeout()} |
 
730
                               {stop, reason(), reply(), #state{}}.
 
731
%%
 
732
%% Description: Whenever a gen_fsm receives an event sent using
 
733
%% gen_fsm:sync_send_all_state_event/2,3, this function is called to handle
 
734
%% the event.
 
735
%%--------------------------------------------------------------------
 
736
handle_sync_event({application_data, Data0}, From, connection, 
 
737
                  #state{socket = Socket,
 
738
                         negotiated_version = Version,
 
739
                         transport_cb = Transport,
 
740
                         connection_states = ConnectionStates0,
 
741
                         send_queue = SendQueue,
 
742
                         socket_options = SockOpts,
 
743
                         ssl_options = #ssl_options{renegotiate_at = RenegotiateAt}} 
 
744
                  = State) ->
618
745
    %% We should look into having a worker process to do this to 
619
746
    %% parallize send and receive decoding and not block the receiver
620
747
    %% if sending is overloading the socket.
621
 
    {Msgs, ConnectionStates1} = encode_data(Data, Version, ConnectionStates0),
622
 
    Result = Transport:send(Socket, Msgs),
623
 
    {reply, Result, 
624
 
     connection, State#state{connection_states = ConnectionStates1}}.
625
 
 
626
 
%%--------------------------------------------------------------------
627
 
%% Function: 
628
 
%% handle_event(Event, StateName, State) -> {next_state, NextStateName, 
629
 
%%                                                  NextState} |
630
 
%%                                          {next_state, NextStateName, 
631
 
%%                                                  NextState, Timeout} |
632
 
%%                                          {stop, Reason, NewState}
633
 
%% Description: Whenever a gen_fsm receives an event sent using
634
 
%% gen_fsm:send_all_state_event/2, this function is called to handle
635
 
%% the event.
636
 
%%--------------------------------------------------------------------
637
 
handle_event(#ssl_tls{type = ?HANDSHAKE, fragment = Data},
638
 
             StateName,
639
 
             State = #state{key_algorithm = KeyAlg,
640
 
                            tls_handshake_buffer = Buf0,
641
 
                            negotiated_version = Version}) ->
642
 
    Handle = 
643
 
        fun({Packet, Raw}, {next_state, SName, AS=#state{tls_handshake_hashes=Hs0}}) ->         
644
 
                Hs1 = ssl_handshake:update_hashes(Hs0, Raw),
645
 
                ?MODULE:SName(Packet, AS#state{tls_handshake_hashes=Hs1});
646
 
           (_, StopState) -> StopState
647
 
        end,
648
748
    try
649
 
        {Packets, Buf} = ssl_handshake:get_tls_handshake(Data,Buf0, KeyAlg,Version),
650
 
        Start = {next_state, StateName, State#state{tls_handshake_buffer = Buf}},
651
 
        lists:foldl(Handle, Start, Packets)
652
 
    catch throw:#alert{} = Alert ->
653
 
            handle_own_alert(Alert, Version, StateName, State), 
654
 
            {stop, normal, State}
655
 
    end;
656
 
 
657
 
handle_event(#ssl_tls{type = ?APPLICATION_DATA, fragment = Data},
658
 
             StateName, State0) ->
659
 
    case application_data(Data, State0) of
660
 
        Stop = {stop,_,_} ->
661
 
            Stop;
662
 
        State ->
663
 
            {next_state, StateName, State}
664
 
    end;
665
 
 
666
 
handle_event(#ssl_tls{type = ?CHANGE_CIPHER_SPEC, fragment = <<1>>} = 
667
 
             _ChangeCipher,
668
 
             StateName, 
669
 
             State = #state{connection_states = ConnectionStates0}) ->
670
 
    ?DBG_TERM(_ChangeCipher),
671
 
    ConnectionStates1 =
672
 
        ssl_record:activate_pending_connection_state(ConnectionStates0, read),
673
 
    {next_state, StateName, 
674
 
     next_record(State#state{connection_states = ConnectionStates1})};
675
 
 
676
 
handle_event(#ssl_tls{type = ?ALERT, fragment = Data}, StateName, State) ->
677
 
    Alerts = decode_alerts(Data),
678
 
    ?DBG_TERM(Alerts),
679
 
    [alert_event(A) || A <- Alerts],
680
 
    {next_state, StateName, State};
681
 
 
682
 
handle_event(#alert{level = ?FATAL} = Alert, connection, 
683
 
             #state{from = From, user_application = {_Mon, Pid}, log_alert = Log,
684
 
                    host = Host, port = Port, session = Session,
685
 
                    role = Role, socket_options = Opts} = State) ->
686
 
    invalidate_session(Role, Host, Port, Session),
687
 
    log_alert(Log, connection, Alert),
688
 
    alert_user(Opts#socket_options.active, Pid, From, Alert, Role),
689
 
    {stop, normal, State};
690
 
handle_event(#alert{level = ?WARNING, description = ?CLOSE_NOTIFY} = Alert, 
691
 
             connection, #state{from = From,
692
 
                                role = Role,
693
 
                                user_application = {_Mon, Pid}, 
694
 
                                socket_options = Opts} = State) ->
695
 
    alert_user(Opts#socket_options.active, Pid, From, Alert, Role),
696
 
    {stop, normal, State};
697
 
 
698
 
handle_event(#alert{level = ?FATAL} = Alert, StateName,
699
 
             #state{from = From, host = Host, port = Port, session = Session,
700
 
                    log_alert = Log, role = Role} = State) ->
701
 
    invalidate_session(Role, Host, Port, Session),
702
 
    log_alert(Log, StateName, Alert),
703
 
    alert_user(From, Alert, Role),
704
 
    {stop, normal, State};
705
 
handle_event(#alert{level = ?WARNING, description = ?CLOSE_NOTIFY} = Alert, 
706
 
             _, #state{from = From, role = Role} = State) -> 
707
 
    alert_user(From, Alert, Role),
708
 
    {stop, normal, State};
709
 
handle_event(#alert{level = ?WARNING} = Alert, StateName, 
710
 
             #state{log_alert = Log} = State) ->
711
 
    log_alert(Log, StateName, Alert),
712
 
%%TODO:  Could be user_canceled or no_negotiation should the latter be 
713
 
    %% treated as fatal?! 
714
 
    {next_state, StateName, next_record(State)}.
715
 
 
716
 
%%--------------------------------------------------------------------
717
 
%% Function: 
718
 
%% handle_sync_event(Event, From, StateName, 
719
 
%%                   State) -> {next_state, NextStateName, NextState} |
720
 
%%                             {next_state, NextStateName, NextState, 
721
 
%%                              Timeout} |
722
 
%%                             {reply, Reply, NextStateName, NextState}|
723
 
%%                             {reply, Reply, NextStateName, NextState, 
724
 
%%                              Timeout} |
725
 
%%                             {stop, Reason, NewState} |
726
 
%%                             {stop, Reason, Reply, NewState}
727
 
%% Description: Whenever a gen_fsm receives an event sent using
728
 
%% gen_fsm:sync_send_all_state_event/2,3, this function is called to handle
729
 
%% the event.
730
 
%%--------------------------------------------------------------------
731
 
handle_sync_event(started, From, StateName, State) ->
732
 
    {next_state, StateName, State#state{from = From}};
733
 
 
734
 
handle_sync_event(close, From, _StateName, State) ->
735
 
    {stop, normal, ok, State#state{from = From}};
736
 
 
737
 
handle_sync_event({shutdown, How}, From, StateName,
738
 
                  #state{transport_cb = CbModule,
 
749
        Data = encode_packet(Data0, SockOpts),
 
750
        case encode_data(Data, Version, ConnectionStates0, RenegotiateAt) of
 
751
            {Msgs, [], ConnectionStates} ->
 
752
                Result = Transport:send(Socket, Msgs),
 
753
                {reply, Result,
 
754
                 connection, State#state{connection_states = ConnectionStates},
 
755
                 get_timeout(State)};
 
756
            {Msgs, RestData, ConnectionStates} ->
 
757
                if 
 
758
                    Msgs =/= [] ->
 
759
                        Transport:send(Socket, Msgs);
 
760
                    true ->
 
761
                        ok
 
762
                end,
 
763
                renegotiate(State#state{connection_states = ConnectionStates,
 
764
                                        send_queue = queue:in_r({From, RestData}, SendQueue),
 
765
                                        renegotiation = {true, internal}})
 
766
        end
 
767
    catch throw:Error ->
 
768
            {reply, Error, connection, State, get_timeout(State)}
 
769
    end;
 
770
handle_sync_event({application_data, Data}, From, StateName, 
 
771
                  #state{send_queue = Queue} = State) ->
 
772
    %% In renegotiation priorities handshake, send data when handshake is finished
 
773
    {next_state, StateName,
 
774
     State#state{send_queue = queue:in({From, Data}, Queue)},
 
775
     get_timeout(State)};
 
776
 
 
777
handle_sync_event(start, From, hello, State) ->
 
778
    hello(start, State#state{from = From});
 
779
 
 
780
%% The two clauses below could happen if a server upgrades a socket in
 
781
%% active mode. Note that in this case we are lucky that
 
782
%% controlling_process has been evalueated before receiving handshake
 
783
%% messages from client. The server should put the socket in passive
 
784
%% mode before telling the client that it is willing to upgrade
 
785
%% and before calling ssl:ssl_accept/2. These clauses are 
 
786
%% here to make sure it is the users problem and not owers if
 
787
%% they upgrade a active socket. 
 
788
handle_sync_event(start, _, connection, State) ->
 
789
    {reply, connected, connection, State, get_timeout(State)};
 
790
handle_sync_event(start, From, StateName, State) ->
 
791
    {next_state, StateName, State#state{from = From}, get_timeout(State)};
 
792
 
 
793
handle_sync_event(close, _, StateName, State) ->
 
794
    %% Run terminate before returning
 
795
    %% so that the reuseaddr inet-option will work
 
796
    %% as intended.
 
797
    (catch terminate(user_close, StateName, State)),
 
798
    {stop, normal, ok, State#state{terminated = true}};
 
799
 
 
800
handle_sync_event({shutdown, How0}, _, StateName,
 
801
                  #state{transport_cb = Transport,
 
802
                         negotiated_version = Version,
 
803
                         connection_states = ConnectionStates,
739
804
                         socket = Socket} = State) ->
740
 
    case CbModule:shutdown(Socket, How) of
 
805
    case How0 of
 
806
        How when How == write; How == both ->       
 
807
            Alert = ?ALERT_REC(?WARNING, ?CLOSE_NOTIFY),
 
808
            {BinMsg, _} =
 
809
                encode_alert(Alert, Version, ConnectionStates),
 
810
            Transport:send(Socket, BinMsg);
 
811
        _ ->
 
812
            ok
 
813
    end,
 
814
    
 
815
    case Transport:shutdown(Socket, How0) of
741
816
        ok ->
742
 
            {reply, ok, StateName, State};
 
817
            {reply, ok, StateName, State, get_timeout(State)};
743
818
        Error ->
744
 
            {stop, normal, Error, State#state{from = From}}
 
819
            {stop, normal, Error, State}
745
820
    end;
746
821
    
747
 
%% TODO: men vad g�r next_record om det �r t.ex. renegotiate? kanske
748
 
%% inte bra... t�l att t�nkas p�!
749
 
handle_sync_event({recv, N}, From, StateName,
750
 
                  State0 = #state{user_data_buffer = Buffer}) ->
751
 
    State1 = State0#state{bytes_to_read = N, from = From},
752
 
    case Buffer of
753
 
        <<>> ->
754
 
            State = next_record(State1),
755
 
            {next_state, StateName, State};
756
 
        _ ->
757
 
            case application_data(<<>>, State1) of
758
 
                Stop = {stop, _, _} ->
759
 
                    Stop;
760
 
                State ->
761
 
                    {next_state, StateName, State}
762
 
            end
763
 
    end;
 
822
handle_sync_event({recv, N}, From, connection = StateName, State0) ->
 
823
    passive_receive(State0#state{bytes_to_read = N, from = From}, StateName);
 
824
 
 
825
%% Doing renegotiate wait with handling request until renegotiate is
 
826
%% finished. Will be handled by next_state_connection/2.
 
827
handle_sync_event({recv, N}, From, StateName, State) ->
 
828
    {next_state, StateName,
 
829
     State#state{bytes_to_read = N, from = From,
 
830
                 recv_during_renegotiation = true},
 
831
     get_timeout(State)};
764
832
 
765
833
handle_sync_event({new_user, User}, _From, StateName, 
766
834
                  State =#state{user_application = {OldMon, _}}) ->
767
835
    NewMon = erlang:monitor(process, User),
768
836
    erlang:demonitor(OldMon, [flush]),
769
 
    {reply, ok, StateName, State#state{user_application = {NewMon,User}}};
 
837
    {reply, ok, StateName, State#state{user_application = {NewMon,User}},
 
838
     get_timeout(State)};
770
839
 
771
840
handle_sync_event({get_opts, OptTags}, _From, StateName,
772
841
                  #state{socket = Socket,
773
842
                         socket_options = SockOpts} = State) ->
774
843
    OptsReply = get_socket_opts(Socket, OptTags, SockOpts, []),
775
 
    {reply, OptsReply, StateName, State};
 
844
    {reply, OptsReply, StateName, State, get_timeout(State)};
776
845
 
777
846
handle_sync_event(sockname, _From, StateName,
778
847
                  #state{socket = Socket} = State) ->
779
848
    SockNameReply = inet:sockname(Socket),
780
 
    {reply, SockNameReply, StateName, State};
 
849
    {reply, SockNameReply, StateName, State, get_timeout(State)};
781
850
 
782
851
handle_sync_event(peername, _From, StateName,
783
852
                  #state{socket = Socket} = State) ->
784
853
    PeerNameReply = inet:peername(Socket),
785
 
    {reply, PeerNameReply, StateName, State};
 
854
    {reply, PeerNameReply, StateName, State, get_timeout(State)};
786
855
 
787
856
handle_sync_event({set_opts, Opts0}, _From, StateName, 
788
857
                  #state{socket_options = Opts1, 
792
861
    State1 = State0#state{socket_options = Opts},
793
862
    if 
794
863
        Opts#socket_options.active =:= false ->
795
 
            {reply, ok, StateName, State1};
 
864
            {reply, ok, StateName, State1, get_timeout(State1)};
796
865
        Buffer =:= <<>>, Opts1#socket_options.active =:= false ->
797
866
            %% Need data, set active once
798
 
            {reply, ok, StateName, next_record_if_active(State1)};
 
867
            {Record, State2} = next_record_if_active(State1),
 
868
            case next_state(StateName, Record, State2) of
 
869
                {next_state, StateName, State, Timeout} ->
 
870
                    {reply, ok, StateName, State, Timeout};
 
871
                {stop, Reason, State} ->
 
872
                    {stop, Reason, State}
 
873
            end;
799
874
        Buffer =:= <<>> ->
800
875
            %% Active once already set 
801
 
            {reply, ok, StateName, State1};
 
876
            {reply, ok, StateName, State1, get_timeout(State1)};
802
877
        true ->
803
878
            case application_data(<<>>, State1) of
804
879
                Stop = {stop,_,_} ->
805
880
                    Stop;
806
 
                State ->
807
 
                    {reply, ok, StateName, State}
 
881
                {Record, State2} ->
 
882
                    case next_state(StateName, Record, State2) of
 
883
                        {next_state, StateName, State, Timeout} ->
 
884
                            {reply, ok, StateName, State, Timeout};
 
885
                        {stop, Reason, State} ->
 
886
                            {stop, Reason, State}
 
887
                    end
808
888
            end
809
 
    end;        
 
889
    end;
 
890
 
 
891
handle_sync_event(renegotiate, From, connection, State) ->
 
892
    renegotiate(State#state{renegotiation = {true, From}});
 
893
 
 
894
handle_sync_event(renegotiate, _, StateName, State) ->
 
895
    {reply, {error, already_renegotiating}, StateName, State, get_timeout(State)};
810
896
 
811
897
handle_sync_event(info, _, StateName, 
812
898
                  #state{negotiated_version = Version,
814
900
    
815
901
    AtomVersion = ssl_record:protocol_version(Version),
816
902
    {reply, {ok, {AtomVersion, ssl_cipher:suite_definition(Suite)}}, 
817
 
     StateName, State};
 
903
     StateName, State, get_timeout(State)};
818
904
 
819
905
handle_sync_event(session_info, _, StateName, 
820
906
                  #state{session = #session{session_id = Id,
821
907
                                            cipher_suite = Suite}} = State) ->
822
908
    {reply, [{session_id, Id}, 
823
909
             {cipher_suite, ssl_cipher:suite_definition(Suite)}], 
824
 
     StateName, State};
 
910
     StateName, State, get_timeout(State)};
825
911
 
826
912
handle_sync_event(peer_certificate, _, StateName, 
827
913
                  #state{session = #session{peer_certificate = Cert}} 
828
914
                  = State) ->
829
 
    {reply, {ok, Cert}, StateName, State}.
830
 
 
 
915
    {reply, {ok, Cert}, StateName, State, get_timeout(State)}.
831
916
 
832
917
%%--------------------------------------------------------------------
833
 
%% Function: 
834
 
%% handle_info(Info,StateName,State)-> {next_state, NextStateName, NextState}|
835
 
%%                                     {next_state, NextStateName, NextState, 
836
 
%%                                       Timeout} |
837
 
%%                                     {stop, Reason, NewState}
 
918
-spec handle_info(msg(),state_name(), #state{}) -> 
 
919
                         {next_state, state_name(), #state{}}|
 
920
                         {next_state, state_name(), #state{}, timeout()} |
 
921
                         {stop, reason(), #state{}}.
 
922
%%
838
923
%% Description: This function is called by a gen_fsm when it receives any
839
924
%% other message than a synchronous or asynchronous event
840
925
%% (or a system message).
841
926
%%--------------------------------------------------------------------
842
927
 
843
928
%% raw data from TCP, unpack records
844
 
handle_info({Protocol, _, Data}, StateName, State =
 
929
handle_info({Protocol, _, Data}, StateName,
845
930
            #state{data_tag = Protocol,
846
 
                   negotiated_version = Version,
847
 
                   tls_record_buffer = Buf0,
848
 
                   tls_cipher_texts = CT0}) ->
849
 
    case ssl_record:get_tls_records(Data, Buf0) of
850
 
        {Records, Buf1} ->
851
 
            CT1 = CT0 ++ Records,
852
 
            {next_state, StateName, 
853
 
             next_record(State#state{tls_record_buffer = Buf1,
854
 
                                     tls_cipher_texts = CT1})};
 
931
                   negotiated_version = Version} = State0) ->
 
932
    case next_tls_record(Data, State0) of
 
933
        {Record, State} ->
 
934
            next_state(StateName, Record, State);
855
935
        #alert{} = Alert ->
856
 
            handle_own_alert(Alert, Version, StateName, State), 
857
 
            {stop, normal, State}
 
936
            handle_own_alert(Alert, Version, StateName, State0), 
 
937
            {stop, normal, State0}
858
938
    end;
859
939
 
860
 
%% %% This is the code for {packet,ssl} removed because it was slower 
861
 
%% %% than handling it in erlang.
862
 
%% handle_info(Data = #ssl_tls{}, StateName, 
863
 
%%          State = #state{tls_buffer = Buffer,
864
 
%%                         socket = Socket,
865
 
%%                         connection_states = ConnectionStates0}) ->
866
 
%%     case Buffer of
867
 
%%      buffer ->
868
 
%%          {next_state, StateName, State#state{tls_buffer = [Data]}};
869
 
%%      continue ->
870
 
%%          inet:setopts(Socket, [{active,once}]),
871
 
%%          {Plain, ConnectionStates} =
872
 
%%              ssl_record:decode_cipher_text(Data, ConnectionStates0),
873
 
%%          gen_fsm:send_all_state_event(self(), Plain),
874
 
%%          {next_state, StateName, 
875
 
%%           State#state{tls_buffer = buffer, 
876
 
%%                       connection_states = ConnectionStates}};
877
 
%%      List when is_list(List) ->
878
 
%%          {next_state, StateName, 
879
 
%%           State#state{tls_buffer = Buffer ++ [Data]}}        
880
 
%%     end;
881
 
 
882
 
%% handle_info(CloseMsg = {_, Socket}, StateName0, 
883
 
%%          #state{socket = Socket,tls_buffer = [Msg]} = State0) ->
884
 
%%     %% Hmm we have a ssl_tls msg buffered, handle that first
885
 
%%     %% and it proberbly is a close alert  
886
 
%%     {next_state, StateName0, State0#state{tls_buffer=[Msg,{ssl_close,CloseMsg}]}};
887
 
        
888
940
handle_info({CloseTag, Socket}, _StateName,
889
941
            #state{socket = Socket, close_tag = CloseTag,
890
942
                   negotiated_version = Version, host = Host,
903
955
               ?ALERT_REC(?WARNING, ?CLOSE_NOTIFY), Role),
904
956
    {stop, normal, State};
905
957
 
 
958
handle_info({ErrorTag, Socket, econnaborted}, StateName,  
 
959
            #state{socket = Socket, from = User, role = Role, 
 
960
                   error_tag = ErrorTag} = State)  when StateName =/= connection ->
 
961
    alert_user(User, ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE), Role),
 
962
    {stop, normal, State};
 
963
 
 
964
handle_info({ErrorTag, Socket, Reason}, _,  
 
965
            #state{socket = Socket, from = User, 
 
966
                   role = Role, error_tag = ErrorTag} = State)  ->
 
967
    Report = io_lib:format("SSL: Socket error: ~p ~n", [Reason]),
 
968
    error_logger:info_report(Report),
 
969
    alert_user(User,  ?ALERT_REC(?FATAL, ?CLOSE_NOTIFY), Role),
 
970
    {stop, normal, State};
 
971
 
906
972
handle_info({'DOWN', MonitorRef, _, _, _}, _, 
907
973
            State = #state{user_application={MonitorRef,_Pid}}) ->
908
974
    {stop, normal, State};   
909
975
 
910
 
handle_info(A, StateName, State) ->
911
 
    io:format("SSL: Bad info (state ~w): ~w\n", [StateName, A]),
912
 
    {stop, bad_info, State}.
 
976
handle_info(Msg, StateName, State) ->
 
977
    Report = io_lib:format("SSL: Got unexpected info: ~p ~n", [Msg]),
 
978
    error_logger:info_report(Report),
 
979
    {next_state, StateName, State, get_timeout(State)}.
913
980
 
914
981
%%--------------------------------------------------------------------
915
 
%% Function: terminate(Reason, StateName, State) -> void()
 
982
-spec terminate(reason(), state_name(), #state{}) -> term().
 
983
%%
916
984
%% Description:This function is called by a gen_fsm when it is about
917
985
%% to terminate. It should be the opposite of Module:init/1 and do any
918
986
%% necessary cleaning up. When it returns, the gen_fsm terminates with
919
987
%% Reason. The return value is ignored.
920
988
%%--------------------------------------------------------------------
921
 
terminate(_Reason, connection, _S=#state{negotiated_version = Version,
 
989
terminate(_, _, #state{terminated = true}) ->
 
990
    %% Happens when user closes the connection using ssl:close/1
 
991
    %% we want to guarantee that Transport:close has been called
 
992
    %% when ssl:close/1 returns.
 
993
    ok;
 
994
terminate(Reason, connection, #state{negotiated_version = Version,
922
995
                                      connection_states = ConnectionStates,
923
996
                                      transport_cb = Transport,
924
 
                                      socket = Socket}) ->
925
 
    {BinAlert, _} = encode_alert(?ALERT_REC(?WARNING,?CLOSE_NOTIFY),
926
 
                                 Version, ConnectionStates),
 
997
                                      socket = Socket, send_queue = SendQueue,
 
998
                                      renegotiation = Renegotiate}) ->
 
999
    notify_senders(SendQueue),
 
1000
    notify_renegotiater(Renegotiate),
 
1001
    BinAlert = terminate_alert(Reason, Version, ConnectionStates),
927
1002
    Transport:send(Socket, BinAlert),
 
1003
    workaround_transport_delivery_problems(Socket, Transport, Reason),
928
1004
    Transport:close(Socket);
929
 
terminate(_Reason, _StateName, _S=#state{transport_cb = Transport, socket = Socket}) ->
930
 
    Transport:close(Socket),
931
 
    ok.
 
1005
terminate(Reason, _StateName, #state{transport_cb = Transport,
 
1006
                                      socket = Socket, send_queue = SendQueue,
 
1007
                                      renegotiation = Renegotiate}) ->
 
1008
    notify_senders(SendQueue),
 
1009
    notify_renegotiater(Renegotiate),
 
1010
    workaround_transport_delivery_problems(Socket, Transport, Reason),
 
1011
    Transport:close(Socket).
932
1012
 
933
1013
%%--------------------------------------------------------------------
934
 
%% Function:
 
1014
-spec code_change(term(), state_name(), #state{}, list()) -> {ok, state_name(), #state{}}.
 
1015
%%                       
935
1016
%% code_change(OldVsn, StateName, State, Extra) -> {ok, StateName, NewState}
936
1017
%% Description: Convert process state when code is changed
937
1018
%%--------------------------------------------------------------------
941
1022
%%--------------------------------------------------------------------
942
1023
%%% Internal functions
943
1024
%%--------------------------------------------------------------------
944
 
start_fsm(Role, Host, Port, Socket, Opts,  User, {CbModule, _,_} = CbInfo, 
 
1025
start_fsm(Role, Host, Port, Socket, Opts,  User, {CbModule, _,_, _} = CbInfo, 
945
1026
          Timeout) -> 
946
 
    case ssl_connection_sup:start_child([Role, Host, Port, Socket, 
947
 
                                         Opts, User, CbInfo]) of
948
 
        {ok, Pid} -> 
949
 
            CbModule:controlling_process(Socket, Pid),
950
 
            send_event(Pid, socket_control),
951
 
            case sync_send_all_state_event(Pid, started, Timeout) of
952
 
                connected ->
953
 
                    {ok, sslsocket(Pid)};
954
 
                {error, Reason} ->
955
 
                    {error, Reason}
956
 
            end;
957
 
        {error, Reason} ->
958
 
            {error, Reason}
 
1027
    try 
 
1028
        {ok, Pid} = ssl_connection_sup:start_child([Role, Host, Port, Socket, 
 
1029
                                                    Opts, User, CbInfo]), 
 
1030
        {ok, SslSocket} = socket_control(Socket, Pid, CbModule),
 
1031
        ok = handshake(SslSocket, Timeout),
 
1032
        {ok, SslSocket} 
 
1033
    catch
 
1034
        error:{badmatch, {error, _} = Error} ->
 
1035
            Error
959
1036
    end.
960
 
 
 
1037
 
961
1038
ssl_init(SslOpts, Role) ->
962
1039
    {ok, CertDbRef, CacheRef, OwnCert} = init_certificates(SslOpts, Role),
963
1040
    PrivateKey =
964
1041
        init_private_key(SslOpts#ssl_options.key, SslOpts#ssl_options.keyfile,
965
1042
                         SslOpts#ssl_options.password, Role),
966
 
    ?DBG_TERM(PrivateKey),
967
 
    {ok, CertDbRef, CacheRef, OwnCert, PrivateKey}.
968
 
 
969
 
init_certificates(#ssl_options{cacertfile = CACertFile,
970
 
                               certfile = CertFile}, Role) ->
971
 
 
972
 
    case ssl_manager:connection_init(CACertFile, Role) of
973
 
        {ok, CertDbRef, CacheRef} ->
974
 
            init_certificates(CertDbRef, CacheRef, CertFile, Role);
975
 
        {error, _Error} ->
976
 
            Report = io_lib:format("SSL: Error ~p ~n",[_Error]),
977
 
            error_logger:error_report(Report),
978
 
            throw(ecacertfile)
979
 
    end.
980
 
 
981
 
init_certificates(CertDbRef, CacheRef, CertFile, client) -> 
 
1043
    DHParams = init_diffie_hellman(SslOpts#ssl_options.dh, SslOpts#ssl_options.dhfile, Role),
 
1044
    {ok, CertDbRef, CacheRef, OwnCert, PrivateKey, DHParams}.
 
1045
 
 
1046
 
 
1047
init_certificates(#ssl_options{cacerts = CaCerts,
 
1048
                               cacertfile = CACertFile,
 
1049
                               certfile = CertFile,
 
1050
                               cert = Cert}, Role) ->
 
1051
    {ok, CertDbRef, CacheRef} = 
 
1052
        try 
 
1053
            Certs = case CaCerts of
 
1054
                        undefined ->
 
1055
                            CACertFile;
 
1056
                        _ ->
 
1057
                            {der, CaCerts}
 
1058
                    end,
 
1059
            {ok, _, _} = ssl_manager:connection_init(Certs, Role)
 
1060
        catch
 
1061
            Error:Reason ->
 
1062
                handle_file_error(?LINE, Error, Reason, CACertFile, ecacertfile,
 
1063
                                  erlang:get_stacktrace())
 
1064
        end,
 
1065
    init_certificates(Cert, CertDbRef, CacheRef, CertFile, Role).
 
1066
 
 
1067
init_certificates(undefined, CertDbRef, CacheRef, "", _) ->
 
1068
    {ok, CertDbRef, CacheRef, undefined};
 
1069
 
 
1070
init_certificates(undefined, CertDbRef, CacheRef, CertFile, client) ->
982
1071
    try 
983
1072
        [OwnCert] = ssl_certificate:file_to_certificats(CertFile),
984
1073
        {ok, CertDbRef, CacheRef, OwnCert}
985
 
    catch _E:_R  ->
 
1074
    catch _Error:_Reason  ->
986
1075
            {ok, CertDbRef, CacheRef, undefined}
987
1076
    end;
988
1077
 
989
 
init_certificates(CertDbRef, CacheRef, CertFile, server) ->
990
 
     try 
 
1078
init_certificates(undefined, CertDbRef, CacheRef, CertFile, server) ->
 
1079
    try
991
1080
        [OwnCert] = ssl_certificate:file_to_certificats(CertFile),
992
1081
        {ok, CertDbRef, CacheRef, OwnCert}
993
 
    catch _E:_R  ->
994
 
            Report = io_lib:format("SSL: ~p: ~p:~p ~p~n",
995
 
                                   [?LINE, _E,_R, erlang:get_stacktrace()]),
996
 
            error_logger:error_report(Report),
997
 
            throw(ecertfile)
998
 
    end.
 
1082
    catch
 
1083
        Error:Reason ->
 
1084
            handle_file_error(?LINE, Error, Reason, CertFile, ecertfile,
 
1085
                              erlang:get_stacktrace())
 
1086
    end;
 
1087
init_certificates(Cert, CertDbRef, CacheRef, _, _) ->
 
1088
    {ok, CertDbRef, CacheRef, Cert}.
999
1089
 
1000
 
init_private_key(undefined, "", _Password, client) -> 
 
1090
init_private_key(undefined, "", _Password, _Client) ->
1001
1091
    undefined;
1002
1092
init_private_key(undefined, KeyFile, Password, _)  -> 
1003
 
    try 
1004
 
        {ok, List} = ssl_manager:cache_pem_file(KeyFile),
1005
 
        [Der] = [Der || Der = {PKey, _ , _} <- List,
1006
 
                        PKey =:= rsa_private_key orelse PKey =:= dsa_private_key],
1007
 
        {ok, Decoded} = public_key:decode_private_key(Der,Password),
1008
 
        Decoded
1009
 
    catch _E:_R ->
1010
 
            Report = io_lib:format("SSL: ~p: ~p:~p ~p~n",
1011
 
                                   [?LINE, _E,_R, erlang:get_stacktrace()]),
1012
 
            error_logger:error_report(Report),
1013
 
            throw(ekeyfile)
 
1093
    try
 
1094
        {ok, List} = ssl_manager:cache_pem_file(KeyFile), 
 
1095
        [PemEntry] = [PemEntry || PemEntry = {PKey, _ , _} <- List,
 
1096
                                  PKey =:= 'RSAPrivateKey' orelse 
 
1097
                                      PKey =:= 'DSAPrivateKey'],
 
1098
        public_key:pem_entry_decode(PemEntry, Password)
 
1099
    catch 
 
1100
        Error:Reason ->
 
1101
            handle_file_error(?LINE, Error, Reason, KeyFile, ekeyfile,
 
1102
                              erlang:get_stacktrace()) 
1014
1103
    end;
1015
 
init_private_key(PrivateKey, _, _,_) ->
1016
 
    PrivateKey.
1017
 
 
1018
 
send_event(FsmPid, Event) ->
1019
 
    gen_fsm:send_event(FsmPid, Event).
1020
 
 
1021
 
sync_send_event(FsmPid, Event, Timeout) ->
1022
 
    try gen_fsm:sync_send_event(FsmPid, Event, Timeout) of
1023
 
        Reply ->
1024
 
            Reply
 
1104
 
 
1105
init_private_key({rsa, PrivateKey}, _, _,_) ->
 
1106
    public_key:der_decode('RSAPrivateKey', PrivateKey);
 
1107
init_private_key({dsa, PrivateKey},_,_,_) ->
 
1108
    public_key:der_decode('DSAPrivateKey', PrivateKey).
 
1109
 
 
1110
-spec(handle_file_error(_,_,_,_,_,_) -> no_return()).
 
1111
handle_file_error(Line, Error, {badmatch, Reason}, File, Throw, Stack) ->
 
1112
    file_error(Line, Error, Reason, File, Throw, Stack);
 
1113
handle_file_error(Line, Error, Reason, File, Throw, Stack) ->
 
1114
    file_error(Line, Error, Reason, File, Throw, Stack).
 
1115
 
 
1116
-spec(file_error(_,_,_,_,_,_) -> no_return()).
 
1117
file_error(Line, Error, Reason, File, Throw, Stack) ->
 
1118
    Report = io_lib:format("SSL: ~p: ~p:~p ~s~n  ~p~n",
 
1119
                           [Line, Error, Reason, File, Stack]),
 
1120
    error_logger:error_report(Report),
 
1121
    throw(Throw).
 
1122
 
 
1123
init_diffie_hellman(Params, _,_) when is_binary(Params)->
 
1124
    public_key:der_decode('DHParameter', Params);
 
1125
init_diffie_hellman(_,_, client) ->
 
1126
    undefined;
 
1127
init_diffie_hellman(_,undefined, _) ->
 
1128
    ?DEFAULT_DIFFIE_HELLMAN_PARAMS;
 
1129
init_diffie_hellman(_, DHParamFile, server) ->
 
1130
    try
 
1131
        {ok, List} = ssl_manager:cache_pem_file(DHParamFile), 
 
1132
        case [Entry || Entry = {'DHParameter', _ , _} <- List] of
 
1133
            [Entry] ->
 
1134
                public_key:pem_entry_decode(Entry);
 
1135
            [] ->
 
1136
                ?DEFAULT_DIFFIE_HELLMAN_PARAMS
 
1137
        end
1025
1138
    catch
1026
 
        exit:{noproc, _} ->
1027
 
            {error, closed};
1028
 
        exit:{timeout, _} ->
1029
 
            {error, timeout};
1030
 
        exit:{normal, _} ->
1031
 
            {error, closed}
 
1139
        Error:Reason ->
 
1140
            handle_file_error(?LINE, Error, Reason, 
 
1141
                              DHParamFile, edhfile,  erlang:get_stacktrace()) 
1032
1142
    end.
1033
1143
 
1034
 
 
1035
 
 
1036
 
send_all_state_event(FsmPid, Event) ->
1037
 
    gen_fsm:send_all_state_event(FsmPid, Event).
1038
 
 
1039
1144
sync_send_all_state_event(FsmPid, Event) ->
1040
 
    sync_send_all_state_event(FsmPid, Event, ?DEFAULT_TIMEOUT
1041
 
). 
 
1145
    sync_send_all_state_event(FsmPid, Event, infinity).
1042
1146
 
1043
1147
sync_send_all_state_event(FsmPid, Event, Timeout) ->
1044
1148
    try gen_fsm:sync_send_all_state_event(FsmPid, Event, Timeout)
1048
1152
        exit:{timeout, _} ->
1049
1153
            {error, timeout};
1050
1154
        exit:{normal, _} ->
 
1155
            {error, closed};
 
1156
        exit:{shutdown, _} -> 
1051
1157
            {error, closed}
1052
1158
    end.
1053
1159
 
1054
 
%% Events: #alert{}
1055
 
alert_event(Alert) ->
1056
 
    send_all_state_event(self(), Alert).
 
1160
%% We do currently not support cipher suites that use fixed DH.
 
1161
%% If we want to implement that we should add a code
 
1162
%% here to extract DH parameters form cert.
 
1163
handle_peer_cert(PeerCert, PublicKeyInfo, 
 
1164
                 #state{session = Session} = State0) ->
 
1165
    State1 = State0#state{session = 
 
1166
                         Session#session{peer_certificate = PeerCert},
 
1167
                         public_key_info = PublicKeyInfo},
 
1168
    {Record, State} = next_record(State1),
 
1169
    next_state(certify, Record, State).
1057
1170
 
1058
1171
certify_client(#state{client_certificate_requested = true, role = client,
1059
1172
                      connection_states = ConnectionStates0,
1060
1173
                      transport_cb = Transport,
1061
1174
                      negotiated_version = Version,
1062
1175
                      cert_db_ref = CertDbRef,
1063
 
                      own_cert = OwnCert,
 
1176
                      session = #session{own_certificate = OwnCert},
1064
1177
                      socket = Socket,
1065
1178
                      tls_handshake_hashes = Hashes0} = State) ->
1066
1179
    Certificate = ssl_handshake:certificate(OwnCert, CertDbRef, client),
1076
1189
                          connection_states = ConnectionStates0,
1077
1190
                          transport_cb = Transport,
1078
1191
                          negotiated_version = Version,
1079
 
                          own_cert = OwnCert,
1080
1192
                          socket = Socket,
1081
 
                          key_algorithm = KeyAlg,
1082
1193
                          private_key = PrivateKey,
1083
 
                          session = #session{master_secret = MasterSecret},
 
1194
                          session = #session{master_secret = MasterSecret,
 
1195
                                             own_certificate = OwnCert},
1084
1196
                          tls_handshake_hashes = Hashes0} = State) ->
 
1197
 
1085
1198
    case ssl_handshake:client_certificate_verify(OwnCert, MasterSecret, 
1086
 
                                                 Version, KeyAlg, 
1087
 
                                                 PrivateKey, Hashes0) of
1088
 
        ignore -> %% No key or cert or fixed_diffie_hellman
1089
 
            State;
1090
 
        Verified ->
1091
 
            SigAlg = ssl_handshake:sig_alg(KeyAlg),
 
1199
                                                 Version, PrivateKey, Hashes0) of
 
1200
        #certificate_verify{} = Verified ->
1092
1201
            {BinVerified, ConnectionStates1, Hashes1} = 
1093
 
                encode_handshake(Verified, SigAlg, Version, 
 
1202
                encode_handshake(Verified, Version,
1094
1203
                                 ConnectionStates0, Hashes0),
1095
1204
            Transport:send(Socket, BinVerified),
1096
1205
            State#state{connection_states = ConnectionStates1,
1097
 
                        tls_handshake_hashes = Hashes1}
 
1206
                        tls_handshake_hashes = Hashes1};
 
1207
        ignore ->
 
1208
            State;
 
1209
        #alert{} = Alert ->
 
1210
            handle_own_alert(Alert, Version, certify, State)
 
1211
            
1098
1212
    end;
1099
1213
verify_client_cert(#state{client_certificate_requested = false} = State) ->
1100
1214
    State.
1101
1215
 
1102
1216
do_server_hello(Type, #state{negotiated_version = Version,
1103
 
                             session = Session,
1104
 
                             connection_states = ConnectionStates0} 
 
1217
                             session = #session{session_id = SessId} = Session,
 
1218
                             connection_states = ConnectionStates0,
 
1219
                             renegotiation = {Renegotiation, _}} 
1105
1220
                = State0) when is_atom(Type) -> 
 
1221
 
1106
1222
    ServerHello = 
1107
 
        ssl_handshake:server_hello(Session#session.session_id, Version, 
1108
 
                                   ConnectionStates0),
1109
 
    State = server_hello(ServerHello, State0),
 
1223
        ssl_handshake:server_hello(SessId, Version, 
 
1224
                                   ConnectionStates0, Renegotiation),
 
1225
    State1 = server_hello(ServerHello, State0),
1110
1226
    
1111
1227
    case Type of        
1112
1228
        new ->
1113
 
            do_server_hello(ServerHello, State);
 
1229
            new_server_hello(ServerHello, State1);
1114
1230
        resumed ->
 
1231
            ConnectionStates1 = State1#state.connection_states,
1115
1232
            case ssl_handshake:master_secret(Version, Session,
1116
 
                                             ConnectionStates0, server) of
1117
 
                {_, ConnectionStates1} ->
1118
 
                    {ConnectionStates, Hashes} =
1119
 
                        finished(State#state{connection_states =
1120
 
                                             ConnectionStates1}),
1121
 
                    {next_state, abbreviated,
1122
 
                     next_record(State#state{connection_states = 
1123
 
                                             ConnectionStates,
1124
 
                                             tls_handshake_hashes = Hashes})};
 
1233
                                             ConnectionStates1, server) of
 
1234
                {_, ConnectionStates2} ->
 
1235
                    State2 = State1#state{connection_states=ConnectionStates2, 
 
1236
                                          session = Session},               
 
1237
                    {ConnectionStates, Hashes} = 
 
1238
                        finalize_handshake(State2, abbreviated),
 
1239
                    State3 = State2#state{connection_states = 
 
1240
                                          ConnectionStates,
 
1241
                                          tls_handshake_hashes = Hashes},
 
1242
                    {Record, State} = next_record(State3),
 
1243
                    next_state(abbreviated, Record, State);
1125
1244
                #alert{} = Alert ->
1126
 
                    handle_own_alert(Alert, Version, hello, State), 
1127
 
                    {stop, normal, State}
 
1245
                    handle_own_alert(Alert, Version, hello, State1), 
 
1246
                    {stop, normal, State1}
1128
1247
            end
1129
 
    end;
 
1248
    end.
1130
1249
 
1131
 
do_server_hello(#server_hello{cipher_suite = CipherSuite,
 
1250
new_server_hello(#server_hello{cipher_suite = CipherSuite,
1132
1251
                              compression_method = Compression,
1133
1252
                              session_id = SessionId}, 
1134
1253
                #state{session = Session0,
1135
1254
                       negotiated_version = Version} = State0) ->
1136
1255
    try server_certify_and_key_exchange(State0) of 
1137
1256
        #state{} = State1 ->
1138
 
            State = server_hello_done(State1),
 
1257
            State2 = server_hello_done(State1),
1139
1258
            Session = 
1140
1259
                Session0#session{session_id = SessionId,
1141
1260
                                 cipher_suite = CipherSuite,
1142
1261
                                 compression_method = Compression},
1143
 
            {next_state, certify, State#state{session = Session}}
 
1262
            {Record, State} = next_record(State2#state{session = Session}),
 
1263
            next_state(certify, Record, State)
1144
1264
    catch        
1145
1265
        #alert{} = Alert ->  
1146
1266
            handle_own_alert(Alert, Version, hello, State0),
1147
1267
            {stop, normal, State0}
1148
1268
    end.
1149
1269
 
 
1270
handle_new_session(NewId, CipherSuite, Compression, #state{session = Session0} = State0) ->
 
1271
    Session = Session0#session{session_id = NewId,
 
1272
                               cipher_suite = CipherSuite,
 
1273
                               compression_method = Compression}, 
 
1274
    {Record, State} = next_record(State0#state{session = Session}),
 
1275
    next_state(certify, Record, State).
 
1276
 
 
1277
handle_resumed_session(SessId, #state{connection_states = ConnectionStates0,
 
1278
                                      negotiated_version = Version,
 
1279
                                      host = Host, port = Port,
 
1280
                                      session_cache = Cache,
 
1281
                                      session_cache_cb = CacheCb} = State0) ->
 
1282
    Session = CacheCb:lookup(Cache, {{Host, Port}, SessId}),
 
1283
    case ssl_handshake:master_secret(Version, Session, 
 
1284
                                     ConnectionStates0, client) of
 
1285
        {_, ConnectionStates1} ->       
 
1286
            {Record, State} = 
 
1287
                next_record(State0#state{
 
1288
                              connection_states = ConnectionStates1,
 
1289
                              session = Session}),
 
1290
            next_state(abbreviated, Record, State);
 
1291
        #alert{} = Alert ->
 
1292
            handle_own_alert(Alert, Version, hello, State0), 
 
1293
            {stop, normal, State0}
 
1294
    end.
 
1295
 
 
1296
 
1150
1297
client_certify_and_key_exchange(#state{negotiated_version = Version} = 
1151
1298
                                State0) ->
1152
1299
    try do_client_certify_and_key_exchange(State0) of 
1153
1300
        State1 = #state{} ->
1154
 
            {ConnectionStates, Hashes} = finalize_client_handshake(State1),
1155
 
            State = State1#state{connection_states = ConnectionStates,
 
1301
            {ConnectionStates, Hashes} = finalize_handshake(State1, certify),
 
1302
            State2 = State1#state{connection_states = ConnectionStates,
1156
1303
                                 %% Reinitialize 
1157
1304
                                 client_certificate_requested = false,
1158
1305
                                 tls_handshake_hashes = Hashes},
1159
 
            {next_state, cipher, next_record(State)}
1160
 
    
 
1306
            {Record, State} = next_record(State2),
 
1307
            next_state(cipher, Record, State)
1161
1308
    catch        
1162
1309
        #alert{} = Alert ->  
1163
 
            handle_own_alert(Alert, Version, certify_foo, State0),
 
1310
            handle_own_alert(Alert, Version, client_certify_and_key_exchange, State0),
1164
1311
            {stop, normal, State0}
1165
1312
    end.
1166
1313
 
1180
1327
                                 connection_states = ConnectionStates0,
1181
1328
                                 tls_handshake_hashes = Hashes0} = State) ->
1182
1329
    CipherSuite = ServerHello#server_hello.cipher_suite,
1183
 
    {KeyAlgorithm, _, _, _} = ssl_cipher:suite_definition(CipherSuite),
1184
 
    %% Version = ServerHello#server_hello.server_version, TODO ska kontrolleras
 
1330
    {KeyAlgorithm, _, _} = ssl_cipher:suite_definition(CipherSuite),
1185
1331
    {BinMsg, ConnectionStates1, Hashes1} = 
1186
1332
        encode_handshake(ServerHello, Version, ConnectionStates0, Hashes0),
1187
1333
    Transport:send(Socket, BinMsg),
1193
1339
                         socket = Socket,
1194
1340
                         negotiated_version = Version,
1195
1341
                         connection_states = ConnectionStates,
1196
 
                         tls_handshake_hashes = Hashes} = State0) ->
 
1342
                         tls_handshake_hashes = Hashes} = State) ->
1197
1343
    
1198
1344
    HelloDone = ssl_handshake:server_hello_done(),
1199
 
 
 
1345
    
1200
1346
    {BinHelloDone, NewConnectionStates, NewHashes} =
1201
1347
        encode_handshake(HelloDone, Version, ConnectionStates, Hashes),
1202
1348
    Transport:send(Socket, BinHelloDone),
1203
 
    State = State0#state{connection_states = NewConnectionStates,
1204
 
                         tls_handshake_hashes = NewHashes},
1205
 
    next_record(State).
1206
 
    
 
1349
    State#state{connection_states = NewConnectionStates,
 
1350
                tls_handshake_hashes = NewHashes}.
 
1351
 
 
1352
certify_server(#state{key_algorithm = dh_anon} = State) ->
 
1353
    State;
 
1354
 
1207
1355
certify_server(#state{transport_cb = Transport,
1208
 
                      socket = Socket,
1209
 
                      negotiated_version = Version,
1210
 
                      connection_states = ConnectionStates,
1211
 
                      tls_handshake_hashes = Hashes,
1212
 
                      cert_db_ref = CertDbRef,
1213
 
                      own_cert = OwnCert} = State) ->
1214
 
 
 
1356
                      socket = Socket,
 
1357
                      negotiated_version = Version,
 
1358
                      connection_states = ConnectionStates,
 
1359
                      tls_handshake_hashes = Hashes,
 
1360
                      cert_db_ref = CertDbRef,
 
1361
                      session = #session{own_certificate = OwnCert}} = State) ->
1215
1362
    case ssl_handshake:certificate(OwnCert, CertDbRef, server) of
1216
1363
        CertMsg = #certificate{} ->
1217
1364
            {BinCertMsg, NewConnectionStates, NewHashes} =
1224
1371
            throw(Alert)
1225
1372
    end.
1226
1373
 
1227
 
key_exchange(#state{role = server, key_algorithm = Algo} = State) 
1228
 
  when Algo == rsa;
1229
 
       Algo == dh_dss;
1230
 
       Algo == dh_rsa ->
1231
 
    State;
1232
 
 
1233
 
key_exchange(#state{role = server, key_algorithm = rsa_export} = State) ->
1234
 
    %% TODO when the public key in the server certificate is
1235
 
    %% less than or equal to 512 bits in length dont send key_exchange
1236
 
    %% but do it otherwise
1237
 
    State;
1238
 
 
 
1374
key_exchange(#state{role = server, key_algorithm = rsa} = State) ->
 
1375
    State;
1239
1376
key_exchange(#state{role = server, key_algorithm = Algo,
1240
 
                    diffie_hellman_params = Params,
 
1377
                    diffie_hellman_params = #'DHParameter'{prime = P, base = G} = Params,
 
1378
                    private_key = PrivateKey,
1241
1379
                    connection_states = ConnectionStates0,
1242
1380
                    negotiated_version = Version,
1243
1381
                    tls_handshake_hashes = Hashes0,
1245
1383
                    transport_cb = Transport
1246
1384
                   } = State) 
1247
1385
  when Algo == dhe_dss;
1248
 
       Algo == dhe_dss_export;
1249
1386
       Algo == dhe_rsa;
1250
 
       Algo == dhe_rsa_export  ->
1251
 
    Msg =  ssl_handshake:key_exchange(server, Params),
1252
 
    {BinMsg, ConnectionStates1, Hashes1} =
 
1387
       Algo == dh_anon ->
 
1388
    Keys = crypto:dh_generate_key([crypto:mpint(P), crypto:mpint(G)]),
 
1389
    ConnectionState = 
 
1390
        ssl_record:pending_connection_state(ConnectionStates0, read),
 
1391
    SecParams = ConnectionState#connection_state.security_parameters,
 
1392
    #security_parameters{client_random = ClientRandom,
 
1393
                         server_random = ServerRandom} = SecParams, 
 
1394
    Msg =  ssl_handshake:key_exchange(server, {dh, Keys, Params,
 
1395
                                               Algo, ClientRandom, 
 
1396
                                               ServerRandom,
 
1397
                                               PrivateKey}),
 
1398
    {BinMsg, ConnectionStates, Hashes1} =
1253
1399
        encode_handshake(Msg, Version, ConnectionStates0, Hashes0),
1254
1400
    Transport:send(Socket, BinMsg),
1255
 
    State#state{connection_states = ConnectionStates1,
 
1401
    State#state{connection_states = ConnectionStates,
 
1402
                diffie_hellman_keys = Keys,
1256
1403
                tls_handshake_hashes = Hashes1};
1257
1404
 
1258
 
key_exchange(#state{role = server, key_algorithm = dh_anon,
1259
 
                            connection_states = ConnectionStates0,
1260
 
                            negotiated_version = Version,
1261
 
                            tls_handshake_hashes = Hashes0,
1262
 
                            socket = Socket,
1263
 
                            transport_cb = Transport
1264
 
                   } = State) ->
1265
 
    Msg = ssl_handshake:key_exchange(server, anonymous),    
1266
 
    {BinMsg, ConnectionStates1, Hashes1} =
1267
 
        encode_handshake(Msg, Version, ConnectionStates0, Hashes0),
1268
 
    Transport:send(Socket, BinMsg),
1269
 
    State#state{connection_states = ConnectionStates1,
1270
 
                tls_handshake_hashes = Hashes1};
1271
 
   
1272
1405
key_exchange(#state{role = client, 
1273
1406
                    connection_states = ConnectionStates0,
1274
1407
                    key_algorithm = rsa,
1283
1416
    Transport:send(Socket, BinMsg),
1284
1417
    State#state{connection_states = ConnectionStates1,
1285
1418
                tls_handshake_hashes = Hashes1};
1286
 
 
1287
1419
key_exchange(#state{role = client, 
1288
1420
                    connection_states = ConnectionStates0,
1289
1421
                    key_algorithm = Algorithm,
1290
 
                    public_key_info = PublicKeyInfo,
1291
1422
                    negotiated_version = Version,
1292
 
                    diffie_hellman_params = Params,
1293
 
                    own_cert = Cert,
 
1423
                    diffie_hellman_keys = {DhPubKey, _},
1294
1424
                    socket = Socket, transport_cb = Transport,
1295
1425
                    tls_handshake_hashes = Hashes0} = State) 
1296
1426
  when Algorithm == dhe_dss;
1297
 
       Algorithm == dhe_dss_export;
1298
1427
       Algorithm == dhe_rsa;
1299
 
       Algorithm == dhe_rsa_export ->
1300
 
    Msg = dh_key_exchange(Cert, Params, PublicKeyInfo),    
 
1428
       Algorithm == dh_anon ->
 
1429
    Msg =  ssl_handshake:key_exchange(client, {dh, DhPubKey}),
1301
1430
    {BinMsg, ConnectionStates1, Hashes1} =
1302
1431
        encode_handshake(Msg, Version, ConnectionStates0, Hashes0),
1303
1432
    Transport:send(Socket, BinMsg),
1312
1441
    ssl_handshake:key_exchange(client, 
1313
1442
                               {premaster_secret, PremasterSecret,
1314
1443
                                PublicKeyInfo});
1315
 
 
1316
1444
rsa_key_exchange(_, _) ->
1317
1445
    throw (?ALERT_REC(?FATAL,?HANDSHAKE_FAILURE)).
1318
1446
 
1319
 
dh_key_exchange(OwnCert, Params, PublicKeyInfo) ->
1320
 
    case public_key:pkix_is_fixed_dh_cert(OwnCert) of
1321
 
        true ->
1322
 
            ssl_handshake:key_exchange(client, fixed_diffie_hellman);
1323
 
        false ->
1324
 
            ssl_handshake:key_exchange(client, {dh, Params, PublicKeyInfo})
1325
 
    end.
1326
 
 
1327
1447
request_client_cert(#state{ssl_options = #ssl_options{verify = verify_peer},
1328
1448
                           connection_states = ConnectionStates0,
1329
1449
                           cert_db_ref = CertDbRef,
1342
1462
                    State) ->
1343
1463
    State.
1344
1464
 
1345
 
finalize_client_handshake(#state{connection_states = ConnectionStates0} 
1346
 
                          = State) ->
1347
 
    ConnectionStates1 = 
1348
 
        cipher_protocol(State#state{connection_states = 
1349
 
                                    ConnectionStates0}),    
1350
 
    ConnectionStates2 =
1351
 
        ssl_record:activate_pending_connection_state(ConnectionStates1,
 
1465
finalize_handshake(State, StateName) ->
 
1466
    ConnectionStates0 = cipher_protocol(State),    
 
1467
    ConnectionStates =
 
1468
        ssl_record:activate_pending_connection_state(ConnectionStates0,
1352
1469
                                                     write),
1353
 
    finished(State#state{connection_states = ConnectionStates2}).
 
1470
    finished(State#state{connection_states = ConnectionStates}, StateName).
1354
1471
    
1355
 
 
1356
 
finalize_server_handshake(State) ->
1357
 
    ConnectionStates0 = cipher_protocol(State),
1358
 
    ConnectionStates = 
1359
 
        ssl_record:activate_pending_connection_state(ConnectionStates0, write),
1360
 
    finished(State#state{connection_states = ConnectionStates}).
1361
 
 
1362
 
cipher_protocol(#state{connection_states = ConnectionStates,
 
1472
cipher_protocol(#state{connection_states = ConnectionStates0,
1363
1473
                       socket = Socket,
1364
1474
                       negotiated_version = Version,
1365
1475
                       transport_cb = Transport}) ->
1366
 
    {BinChangeCipher, NewConnectionStates} =
1367
 
        encode_change_cipher(#change_cipher_spec{}, Version, ConnectionStates),
 
1476
    {BinChangeCipher, ConnectionStates} =
 
1477
        encode_change_cipher(#change_cipher_spec{}, 
 
1478
                             Version, ConnectionStates0),
1368
1479
    Transport:send(Socket, BinChangeCipher),
1369
 
    NewConnectionStates.
 
1480
    ConnectionStates.
1370
1481
   
1371
1482
finished(#state{role = Role, socket = Socket, negotiated_version = Version,
1372
1483
                transport_cb = Transport,
1373
1484
                session = Session,
1374
 
                connection_states = ConnectionStates,
1375
 
                tls_handshake_hashes = Hashes}) ->
 
1485
                connection_states = ConnectionStates0,
 
1486
                tls_handshake_hashes = Hashes0}, StateName) ->
1376
1487
    MasterSecret = Session#session.master_secret,
1377
 
    Finished = ssl_handshake:finished(Version, Role, MasterSecret, Hashes),
1378
 
    {BinFinished, NewConnectionStates, NewHashes} = 
1379
 
        encode_handshake(Finished, Version, ConnectionStates, Hashes),
 
1488
    Finished = ssl_handshake:finished(Version, Role, MasterSecret, Hashes0),
 
1489
    ConnectionStates1 = save_verify_data(Role, Finished, ConnectionStates0, StateName),
 
1490
    {BinFinished, ConnectionStates, Hashes} = 
 
1491
        encode_handshake(Finished, Version, ConnectionStates1, Hashes0),
1380
1492
    Transport:send(Socket, BinFinished),
1381
 
    {NewConnectionStates, NewHashes}.
1382
 
 
1383
 
handle_server_key(_KeyExchangeMsg, State) ->
1384
 
    State.
1385
 
handle_clinet_key(_KeyExchangeMsg, State) ->
1386
 
    State.
1387
 
 
 
1493
    {ConnectionStates, Hashes}.
 
1494
 
 
1495
save_verify_data(client, #finished{verify_data = Data}, ConnectionStates, certify) ->
 
1496
    ssl_record:set_client_verify_data(current_write, Data, ConnectionStates);
 
1497
save_verify_data(server, #finished{verify_data = Data}, ConnectionStates, cipher) ->
 
1498
    ssl_record:set_server_verify_data(current_both, Data, ConnectionStates);
 
1499
save_verify_data(client, #finished{verify_data = Data}, ConnectionStates, abbreviated) ->
 
1500
    ssl_record:set_client_verify_data(current_both, Data, ConnectionStates);
 
1501
save_verify_data(server, #finished{verify_data = Data}, ConnectionStates, abbreviated) ->
 
1502
    ssl_record:set_server_verify_data(current_write, Data, ConnectionStates).
 
1503
 
 
1504
handle_server_key(#server_key_exchange{params =
 
1505
                                           #server_dh_params{dh_p = P,
 
1506
                                                             dh_g = G,
 
1507
                                                             dh_y = ServerPublicDhKey},
 
1508
                                       signed_params = <<>>},
 
1509
                  #state{key_algorithm = dh_anon} = State) ->
 
1510
    dh_master_secret(P, G, ServerPublicDhKey, undefined, State);
 
1511
 
 
1512
handle_server_key(
 
1513
  #server_key_exchange{params = 
 
1514
                       #server_dh_params{dh_p = P,
 
1515
                                         dh_g = G,
 
1516
                                         dh_y = ServerPublicDhKey}, 
 
1517
                       signed_params = Signed}, 
 
1518
  #state{public_key_info = PubKeyInfo,
 
1519
         key_algorithm = KeyAlgo,
 
1520
         connection_states = ConnectionStates} = State) ->
 
1521
     
 
1522
    PLen = size(P),
 
1523
    GLen = size(G),
 
1524
    YLen = size(ServerPublicDhKey),
 
1525
 
 
1526
    ConnectionState = 
 
1527
        ssl_record:pending_connection_state(ConnectionStates, read),
 
1528
    SecParams = ConnectionState#connection_state.security_parameters,
 
1529
    #security_parameters{client_random = ClientRandom,
 
1530
                         server_random = ServerRandom} = SecParams, 
 
1531
    Hash = ssl_handshake:server_key_exchange_hash(KeyAlgo,
 
1532
                                                  <<ClientRandom/binary, 
 
1533
                                                   ServerRandom/binary, 
 
1534
                                                   ?UINT16(PLen), P/binary, 
 
1535
                                                   ?UINT16(GLen), G/binary,
 
1536
                                                   ?UINT16(YLen),
 
1537
                                                   ServerPublicDhKey/binary>>),
 
1538
    
 
1539
    case verify_dh_params(Signed, Hash, PubKeyInfo) of
 
1540
        true ->
 
1541
            dh_master_secret(P, G, ServerPublicDhKey, undefined, State);
 
1542
        false ->
 
1543
            ?ALERT_REC(?FATAL, ?DECRYPT_ERROR)
 
1544
    end.
 
1545
 
 
1546
verify_dh_params(Signed, Hashes, {?rsaEncryption, PubKey, _PubKeyParams}) ->
 
1547
    case public_key:decrypt_public(Signed, PubKey, 
 
1548
                                   [{rsa_pad, rsa_pkcs1_padding}]) of
 
1549
        Hashes ->
 
1550
            true;
 
1551
        _ ->
 
1552
            false
 
1553
    end;
 
1554
verify_dh_params(Signed, Hash, {?'id-dsa', PublicKey, PublicKeyParams}) ->
 
1555
    public_key:verify(Hash, none, Signed, {PublicKey, PublicKeyParams}). 
 
1556
 
 
1557
dh_master_secret(Prime, Base, PublicDhKey, undefined, State) ->
 
1558
    PMpint = mpint_binary(Prime),
 
1559
    GMpint = mpint_binary(Base),
 
1560
    Keys = {_, PrivateDhKey} =
 
1561
        crypto:dh_generate_key([PMpint,GMpint]),
 
1562
    dh_master_secret(PMpint, GMpint, PublicDhKey, PrivateDhKey, State#state{diffie_hellman_keys = Keys});
 
1563
 
 
1564
dh_master_secret(PMpint, GMpint, PublicDhKey, PrivateDhKey,
 
1565
                 #state{session = Session,
 
1566
                        negotiated_version = Version, role = Role,
 
1567
                        connection_states = ConnectionStates0} = State) ->
 
1568
    PremasterSecret =
 
1569
        crypto:dh_compute_key(mpint_binary(PublicDhKey), PrivateDhKey,
 
1570
                              [PMpint, GMpint]),
 
1571
    case ssl_handshake:master_secret(Version, PremasterSecret,
 
1572
                                     ConnectionStates0, Role) of
 
1573
        {MasterSecret, ConnectionStates} ->
 
1574
            State#state{
 
1575
              session =
 
1576
                  Session#session{master_secret = MasterSecret},
 
1577
              connection_states = ConnectionStates};
 
1578
        #alert{} = Alert ->
 
1579
            Alert
 
1580
    end.
 
1581
 
 
1582
cipher_role(client, Data, Session, #state{connection_states = ConnectionStates0} = State) -> 
 
1583
    ConnectionStates = ssl_record:set_server_verify_data(current_both, Data, ConnectionStates0),
 
1584
    next_state_connection(cipher, ack_connection(State#state{session = Session,
 
1585
                                                             connection_states = ConnectionStates}));
 
1586
     
 
1587
cipher_role(server, Data, Session,  #state{connection_states = ConnectionStates0} = State) -> 
 
1588
    ConnectionStates1 = ssl_record:set_client_verify_data(current_read, Data, ConnectionStates0),
 
1589
    {ConnectionStates, Hashes} = 
 
1590
        finalize_handshake(State#state{connection_states = ConnectionStates1,
 
1591
                                       session = Session}, cipher),
 
1592
    next_state_connection(cipher, ack_connection(State#state{connection_states = 
 
1593
                                                             ConnectionStates,
 
1594
                                                             session = Session,
 
1595
                                                             tls_handshake_hashes =
 
1596
                                                             Hashes})).
1388
1597
encode_alert(#alert{} = Alert, Version, ConnectionStates) ->
1389
 
    ?DBG_TERM(Alert),
1390
1598
    ssl_record:encode_alert_record(Alert, Version, ConnectionStates).
1391
1599
 
1392
1600
encode_change_cipher(#change_cipher_spec{}, Version, ConnectionStates) ->
1393
 
    ?DBG_TERM(#change_cipher_spec{}),
1394
1601
    ssl_record:encode_change_cipher_spec(Version, ConnectionStates).
1395
1602
 
1396
 
encode_handshake(HandshakeRec, Version, ConnectionStates, Hashes) ->
1397
 
    encode_handshake(HandshakeRec, undefined, Version, 
1398
 
                     ConnectionStates, Hashes).
1399
 
 
1400
 
encode_handshake(HandshakeRec, SigAlg, Version, ConnectionStates0, Hashes0) ->
1401
 
    ?DBG_TERM(HandshakeRec),
1402
 
    Frag = ssl_handshake:encode_handshake(HandshakeRec, Version, SigAlg),
 
1603
encode_handshake(HandshakeRec, Version, ConnectionStates0, Hashes0) ->
 
1604
    Frag = ssl_handshake:encode_handshake(HandshakeRec, Version),
1403
1605
    Hashes1 = ssl_handshake:update_hashes(Hashes0, Frag),
1404
1606
    {E, ConnectionStates1} =
1405
1607
        ssl_record:encode_handshake(Frag, Version, ConnectionStates0),
1406
1608
    {E, ConnectionStates1, Hashes1}.
1407
1609
 
1408
 
encode_data(Data, Version, ConnectionStates) ->
1409
 
    ssl_record:encode_data(Data, Version, ConnectionStates).
 
1610
encode_packet(Data, #socket_options{packet=Packet}) ->
 
1611
    case Packet of
 
1612
        1 -> encode_size_packet(Data, 8,  (1 bsl 8) - 1);
 
1613
        2 -> encode_size_packet(Data, 16, (1 bsl 16) - 1);
 
1614
        4 -> encode_size_packet(Data, 32, (1 bsl 32) - 1);
 
1615
        _ -> Data
 
1616
    end.
 
1617
 
 
1618
encode_size_packet(Bin, Size, Max) ->
 
1619
    Len = byte_size(Bin),
 
1620
    case Len > Max of
 
1621
        true  -> throw({error, {badarg, {packet_to_large, Len, Max}}});
 
1622
        false -> <<Len:Size, Bin/binary>>
 
1623
    end.
 
1624
 
 
1625
encode_data(Data, Version, ConnectionStates, RenegotiateAt) ->
 
1626
    ssl_record:encode_data(Data, Version, ConnectionStates, RenegotiateAt).
1410
1627
 
1411
1628
decode_alerts(Bin) ->
1412
1629
    decode_alerts(Bin, []).
1417
1634
decode_alerts(<<>>, Acc) ->
1418
1635
    lists:reverse(Acc, []).
1419
1636
 
 
1637
passive_receive(State0 = #state{user_data_buffer = Buffer}, StateName) -> 
 
1638
    case Buffer of
 
1639
        <<>> ->
 
1640
            {Record, State} = next_record(State0),
 
1641
            next_state(StateName, Record, State);
 
1642
        _ ->
 
1643
            case application_data(<<>>, State0) of
 
1644
                Stop = {stop, _, _} ->
 
1645
                    Stop;
 
1646
                {Record, State} ->
 
1647
                    next_state(StateName, Record, State)
 
1648
            end
 
1649
    end.
 
1650
 
1420
1651
application_data(Data, #state{user_application = {_Mon, Pid},
1421
1652
                              socket_options = SOpts,
1422
1653
                              bytes_to_read = BytesToRead,
1428
1659
                  true -> <<Buffer0/binary, Data/binary>>
1429
1660
              end,
1430
1661
    case get_data(SOpts, BytesToRead, Buffer1) of
1431
 
        {ok, <<>>, Buffer} -> % no reply, we need more data
1432
 
            next_record(State0#state{user_data_buffer = Buffer});
1433
1662
        {ok, ClientData, Buffer} -> % Send data
1434
1663
            SocketOpt = deliver_app_data(SOpts, ClientData, Pid, From),
1435
1664
            State = State0#state{user_data_buffer = Buffer,
1438
1667
                                 socket_options = SocketOpt 
1439
1668
                                },
1440
1669
            if
1441
 
                SocketOpt#socket_options.active =:= false -> 
1442
 
                    State; %% Passive mode, wait for active once or recv
1443
 
                Buffer =:= <<>> -> %% Active and empty, get more data
1444
 
                    next_record(State);
1445
 
                true -> %% We have more data
1446
 
                    application_data(<<>>, State)
 
1670
                SocketOpt#socket_options.active =:= false; Buffer =:= <<>> -> 
 
1671
                    %% Passive mode, wait for active once or recv
 
1672
                    %% Active and empty, get more data
 
1673
                    next_record_if_active(State);
 
1674
                true -> %% We have more data
 
1675
                    application_data(<<>>, State)
1447
1676
            end;
 
1677
        {more, Buffer} -> % no reply, we need more data
 
1678
            next_record(State0#state{user_data_buffer = Buffer});
1448
1679
        {error,_Reason} -> %% Invalid packet in packet mode
1449
1680
            deliver_packet_error(SOpts, Buffer1, Pid, From),
1450
1681
            {stop, normal, State0}
1451
1682
    end.
1452
1683
 
1453
1684
%% Picks ClientData 
 
1685
get_data(_, _, <<>>) ->
 
1686
    {more, <<>>};
1454
1687
get_data(#socket_options{active=Active, packet=Raw}, BytesToRead, Buffer) 
1455
1688
  when Raw =:= raw; Raw =:= 0 ->   %% Raw Mode
1456
1689
    if 
1463
1696
            {ok, Data, Rest};
1464
1697
        true ->
1465
1698
            %% Passive Mode not enough data
1466
 
            {ok, <<>>, Buffer}
 
1699
            {more, Buffer}
1467
1700
    end;
1468
1701
get_data(#socket_options{packet=Type, packet_size=Size}, _, Buffer) ->
1469
1702
    PacketOpts = [{packet_size, Size}], 
1470
 
    case erlang:decode_packet(Type, Buffer, PacketOpts) of
 
1703
    case decode_packet(Type, Buffer, PacketOpts) of
1471
1704
        {more, _} ->
1472
 
            {ok, <<>>, Buffer};
 
1705
            {more, Buffer};
1473
1706
        Decoded ->
1474
1707
            Decoded
1475
1708
    end.
1476
1709
 
1477
 
deliver_app_data(SO = #socket_options{active=once}, Data, Pid, From) ->
1478
 
    send_or_reply(once, Pid, From, format_reply(SO, Data)),
1479
 
    SO#socket_options{active=false};
1480
 
deliver_app_data(SO= #socket_options{active=Active}, Data, Pid, From) ->
1481
 
    send_or_reply(Active, Pid, From, format_reply(SO, Data)),
1482
 
    SO.
1483
 
 
1484
 
format_reply(#socket_options{active=false, mode=Mode, header=Header}, Data) ->
1485
 
    {ok, format_reply(Mode, Header, Data)};
1486
 
format_reply(#socket_options{active=_, mode=Mode, header=Header}, Data) ->
1487
 
    {ssl, sslsocket(), format_reply(Mode, Header, Data)}.
1488
 
 
1489
 
deliver_packet_error(SO= #socket_options{active=Active}, Data, Pid, From) ->
 
1710
decode_packet({http, headers}, Buffer, PacketOpts) ->
 
1711
    decode_packet(httph, Buffer, PacketOpts);
 
1712
decode_packet({http_bin, headers}, Buffer, PacketOpts) ->
 
1713
    decode_packet(httph_bin, Buffer, PacketOpts);
 
1714
decode_packet(Type, Buffer, PacketOpts) ->
 
1715
    erlang:decode_packet(Type, Buffer, PacketOpts).
 
1716
 
 
1717
%% Just like with gen_tcp sockets, an ssl socket that has been configured with
 
1718
%% {packet, http} (or {packet, http_bin}) will automatically switch to expect
 
1719
%% HTTP headers after it sees a HTTP Request or HTTP Response line. We
 
1720
%% represent the current state as follows:
 
1721
%%    #socket_options.packet =:= http: Expect a HTTP Request/Response line
 
1722
%%    #socket_options.packet =:= {http, headers}: Expect HTTP Headers
 
1723
%% Note that if the user has explicitly configured the socket to expect
 
1724
%% HTTP headers using the {packet, httph} option, we don't do any automatic
 
1725
%% switching of states.
 
1726
deliver_app_data(SOpts = #socket_options{active=Active, packet=Type},
 
1727
                        Data, Pid, From) ->
 
1728
    send_or_reply(Active, Pid, From, format_reply(SOpts, Data)),
 
1729
    SO = case Data of
 
1730
             {P, _, _, _} when ((P =:= http_request) or (P =:= http_response)),
 
1731
                               ((Type =:= http) or (Type =:= http_bin)) ->
 
1732
                 SOpts#socket_options{packet={Type, headers}};
 
1733
             http_eoh when tuple_size(Type) =:= 2 ->
 
1734
                 % End of headers - expect another Request/Response line
 
1735
                 {Type1, headers} = Type,
 
1736
                 SOpts#socket_options{packet=Type1};
 
1737
             _ ->
 
1738
                 SOpts
 
1739
         end,
 
1740
    case Active of
 
1741
        once ->
 
1742
            SO#socket_options{active=false};
 
1743
        _ ->
 
1744
            SO
 
1745
    end.
 
1746
 
 
1747
format_reply(#socket_options{active = false, mode = Mode, packet = Packet,
 
1748
                             header = Header}, Data) ->
 
1749
    {ok, format_reply(Mode, Packet, Header, Data)};
 
1750
format_reply(#socket_options{active = _, mode = Mode, packet = Packet, 
 
1751
                             header = Header}, Data) ->
 
1752
    {ssl, sslsocket(), format_reply(Mode, Packet, Header, Data)}.
 
1753
 
 
1754
deliver_packet_error(SO= #socket_options{active = Active}, Data, Pid, From) ->
1490
1755
    send_or_reply(Active, Pid, From, format_packet_error(SO, Data)).
1491
1756
 
1492
 
format_packet_error(#socket_options{active=false, mode=Mode}, Data) ->
1493
 
    {error, {invalid_packet, format_reply(Mode, raw, Data)}};
1494
 
format_packet_error(#socket_options{active=_, mode=Mode}, Data) ->
1495
 
    {ssl_error, sslsocket(), {invalid_packet, format_reply(Mode, raw, Data)}}.
1496
 
 
1497
 
format_reply(list,     _, Data) ->  binary_to_list(Data);
1498
 
format_reply(binary,   0, Data) ->  Data;
1499
 
format_reply(binary, raw, Data) ->  Data;
1500
 
format_reply(binary,   N, Data) ->  % Header mode
1501
 
    <<Header:N/binary, Rest/binary>> = Data,
1502
 
    [binary_to_list(Header), Rest].
1503
 
 
1504
 
%% tcp_closed
1505
 
send_or_reply(false, _Pid, undefined, _Data) ->
1506
 
    Report = io_lib:format("SSL(debug): Unexpected Data ~p ~n",[_Data]),
1507
 
    error_logger:error_report(Report),
1508
 
    erlang:error({badarg, _Pid, undefined, _Data}),
1509
 
    ok;
1510
 
send_or_reply(false, _Pid, From, Data) ->
 
1757
format_packet_error(#socket_options{active = false, mode = Mode}, Data) ->
 
1758
    {error, {invalid_packet, format_reply(Mode, raw, 0, Data)}};
 
1759
format_packet_error(#socket_options{active = _, mode = Mode}, Data) ->
 
1760
    {ssl_error, sslsocket(), {invalid_packet, format_reply(Mode, raw, 0, Data)}}.
 
1761
 
 
1762
format_reply(binary, _, N, Data) when N > 0 ->  % Header mode
 
1763
    header(N, Data);
 
1764
format_reply(binary, _, _, Data) ->  
 
1765
    Data;
 
1766
format_reply(list, Packet, _, Data)
 
1767
  when Packet == http; Packet == {http, headers};  Packet == http_bin; Packet == {http_bin, headers} ->
 
1768
    Data;
 
1769
format_reply(list, _,_, Data) ->
 
1770
    binary_to_list(Data).
 
1771
 
 
1772
header(0, <<>>) ->
 
1773
    <<>>;
 
1774
header(_, <<>>) ->
 
1775
    [];
 
1776
header(0, Binary) ->
 
1777
    Binary;
 
1778
header(N, Binary) ->
 
1779
    <<?BYTE(ByteN), NewBinary/binary>> = Binary,
 
1780
    [ByteN | header(N-1, NewBinary)].
 
1781
 
 
1782
send_or_reply(false, _Pid, From, Data) when From =/= undefined ->
1511
1783
    gen_fsm:reply(From, Data);
1512
1784
send_or_reply(_, Pid, _From, Data) ->
1513
1785
    send_user(Pid, Data).
1520
1792
send_user(Pid, Msg) ->
1521
1793
    Pid ! Msg.
1522
1794
 
1523
 
%% %% This is the code for {packet,ssl} removed because it was slower 
1524
 
%% %% than handling it in erlang.
1525
 
%% next_record(#state{socket = Socket, 
1526
 
%%                 tls_buffer = [Msg|Rest],
1527
 
%%                 connection_states = ConnectionStates0} = State) ->
1528
 
%%     Buffer =
1529
 
%%      case Rest of
1530
 
%%          [] -> 
1531
 
%%              inet:setopts(Socket, [{active,once}]),
1532
 
%%              buffer;
1533
 
%%          _ -> Rest
1534
 
%%      end,
1535
 
%%     case Msg of
1536
 
%%      #ssl_tls{} ->
1537
 
%%          {Plain, ConnectionStates} =
1538
 
%%              ssl_record:decode_cipher_text(Msg, ConnectionStates0),
1539
 
%%          gen_fsm:send_all_state_event(self(), Plain),
1540
 
%%          State#state{tls_buffer=Buffer, connection_states = ConnectionStates};
1541
 
%%      {ssl_close, Msg} ->
1542
 
%%          self() ! Msg,
1543
 
%%          State#state{tls_buffer=Buffer}
1544
 
%%     end;
1545
 
%% next_record(#state{socket = Socket, tls_buffer = undefined} = State) ->
1546
 
%%     inet:setopts(Socket, [{active,once}]),
1547
 
%%     State#state{tls_buffer=continue};
1548
 
%% next_record(State) ->
1549
 
%%     State#state{tls_buffer=continue}.
1550
 
 
1551
 
next_record(#state{tls_cipher_texts = [], socket = Socket} = State) ->
 
1795
handle_tls_handshake(Handle, StateName, #state{tls_packets = [Packet]} = State) ->
 
1796
    FsmReturn = {next_state, StateName, State#state{tls_packets = []}},
 
1797
    Handle(Packet, FsmReturn);
 
1798
 
 
1799
handle_tls_handshake(Handle, StateName, #state{tls_packets = [Packet | Packets]} = State0) ->
 
1800
    FsmReturn = {next_state, StateName, State0#state{tls_packets = Packets}},
 
1801
    case Handle(Packet, FsmReturn) of
 
1802
        {next_state, NextStateName, State, _Timeout} ->
 
1803
            handle_tls_handshake(Handle, NextStateName, State);
 
1804
        {stop, _,_} = Stop ->
 
1805
            Stop
 
1806
    end.
 
1807
 
 
1808
next_state(_, #alert{} = Alert, #state{negotiated_version = Version} = State) ->
 
1809
    handle_own_alert(Alert, Version, decipher_error, State),
 
1810
    {stop, normal, State};
 
1811
 
 
1812
next_state(Next, no_record, State) ->
 
1813
    {next_state, Next, State, get_timeout(State)};
 
1814
 
 
1815
next_state(Next, #ssl_tls{type = ?ALERT, fragment = EncAlerts}, State) ->
 
1816
    Alerts = decode_alerts(EncAlerts),
 
1817
    handle_alerts(Alerts,  {next_state, Next, State, get_timeout(State)});
 
1818
 
 
1819
next_state(StateName, #ssl_tls{type = ?HANDSHAKE, fragment = Data},
 
1820
           State0 = #state{tls_handshake_buffer = Buf0, negotiated_version = Version}) ->
 
1821
    Handle = 
 
1822
        fun({#hello_request{} = Packet, _}, {next_state, connection = SName, State}) ->
 
1823
                %% This message should not be included in handshake
 
1824
                %% message hashes. Starts new handshake (renegotiation)
 
1825
                Hs0 = ssl_handshake:init_hashes(),
 
1826
                ?MODULE:SName(Packet, State#state{tls_handshake_hashes=Hs0,
 
1827
                                                  renegotiation = {true, peer}});
 
1828
           ({#hello_request{} = Packet, _}, {next_state, SName, State}) ->
 
1829
                %% This message should not be included in handshake
 
1830
                %% message hashes. Already in negotiation so it will be ignored!
 
1831
                ?MODULE:SName(Packet, State);
 
1832
           ({#client_hello{} = Packet, Raw}, {next_state, connection = SName, State}) ->
 
1833
                Hs0 = ssl_handshake:init_hashes(),
 
1834
                Hs1 = ssl_handshake:update_hashes(Hs0, Raw),
 
1835
                ?MODULE:SName(Packet, State#state{tls_handshake_hashes=Hs1,
 
1836
                                                  renegotiation = {true, peer}});
 
1837
           ({Packet, Raw}, {next_state, SName, State = #state{tls_handshake_hashes=Hs0}}) ->
 
1838
                Hs1 = ssl_handshake:update_hashes(Hs0, Raw),
 
1839
                ?MODULE:SName(Packet, State#state{tls_handshake_hashes=Hs1});
 
1840
           (_, StopState) -> StopState
 
1841
        end,
 
1842
    try
 
1843
        {Packets, Buf} = ssl_handshake:get_tls_handshake(Data,Buf0),
 
1844
        State = State0#state{tls_packets = Packets, tls_handshake_buffer = Buf},
 
1845
        handle_tls_handshake(Handle, StateName, State)
 
1846
    catch throw:#alert{} = Alert ->
 
1847
            handle_own_alert(Alert, Version, StateName, State0), 
 
1848
            {stop, normal, State0}
 
1849
    end;
 
1850
 
 
1851
next_state(StateName, #ssl_tls{type = ?APPLICATION_DATA, fragment = Data}, State0) ->
 
1852
    case application_data(Data, State0) of
 
1853
        Stop = {stop,_,_} ->
 
1854
            Stop;
 
1855
        {Record, State} ->
 
1856
            next_state(StateName, Record, State)
 
1857
    end;
 
1858
next_state(StateName, #ssl_tls{type = ?CHANGE_CIPHER_SPEC, fragment = <<1>>} = 
 
1859
           _ChangeCipher, 
 
1860
           #state{connection_states = ConnectionStates0} = State0) ->
 
1861
    ConnectionStates1 =
 
1862
        ssl_record:activate_pending_connection_state(ConnectionStates0, read),
 
1863
    {Record, State} = next_record(State0#state{connection_states = ConnectionStates1}),
 
1864
    next_state(StateName, Record, State);
 
1865
next_state(StateName, #ssl_tls{type = _Unknown}, State0) ->
 
1866
    %% Ignore unknown type 
 
1867
    {Record, State} = next_record(State0),
 
1868
    next_state(StateName, Record, State).
 
1869
 
 
1870
next_tls_record(Data, #state{tls_record_buffer = Buf0,
 
1871
                       tls_cipher_texts = CT0} = State0) ->
 
1872
    case ssl_record:get_tls_records(Data, Buf0) of
 
1873
        {Records, Buf1} ->
 
1874
            CT1 = CT0 ++ Records,
 
1875
            next_record(State0#state{tls_record_buffer = Buf1,
 
1876
                                     tls_cipher_texts = CT1});
 
1877
        #alert{} = Alert ->
 
1878
            Alert
 
1879
    end.
 
1880
 
 
1881
next_record(#state{tls_packets = [], tls_cipher_texts = [], socket = Socket} = State) ->
1552
1882
    inet:setopts(Socket, [{active,once}]),
1553
 
    State;
1554
 
next_record(#state{tls_cipher_texts = [CT | Rest], 
 
1883
    {no_record, State};
 
1884
next_record(#state{tls_packets = [], tls_cipher_texts = [CT | Rest],
1555
1885
                   connection_states = ConnStates0} = State) ->
1556
 
    {Plain, ConnStates} = ssl_record:decode_cipher_text(CT, ConnStates0),
1557
 
    gen_fsm:send_all_state_event(self(), Plain),
1558
 
    State#state{tls_cipher_texts = Rest, connection_states = ConnStates}.
 
1886
    case ssl_record:decode_cipher_text(CT, ConnStates0) of
 
1887
        {Plain, ConnStates} ->                
 
1888
            {Plain, State#state{tls_cipher_texts = Rest, connection_states = ConnStates}};
 
1889
        #alert{} = Alert ->
 
1890
            {Alert, State}
 
1891
    end;
 
1892
next_record(State) ->
 
1893
    {no_record, State}.
1559
1894
 
1560
1895
next_record_if_active(State = 
1561
1896
                      #state{socket_options = 
1562
1897
                             #socket_options{active = false}}) ->    
1563
 
    State;
 
1898
    {no_record ,State};
 
1899
 
1564
1900
next_record_if_active(State) ->
1565
1901
    next_record(State).
1566
1902
 
 
1903
next_state_connection(StateName, #state{send_queue = Queue0,
 
1904
                                        negotiated_version = Version,
 
1905
                                        socket = Socket,
 
1906
                                        transport_cb = Transport,
 
1907
                                        connection_states = ConnectionStates0,
 
1908
                                        ssl_options = #ssl_options{renegotiate_at = RenegotiateAt}
 
1909
                                       } = State) ->     
 
1910
    %% Send queued up data
 
1911
    case queue:out(Queue0) of
 
1912
        {{value, {From, Data}}, Queue} ->
 
1913
            case encode_data(Data, Version, ConnectionStates0, RenegotiateAt) of
 
1914
                {Msgs, [], ConnectionStates} ->
 
1915
                    Result = Transport:send(Socket, Msgs),
 
1916
                    gen_fsm:reply(From, Result),
 
1917
                    next_state_connection(StateName,
 
1918
                                          State#state{connection_states = ConnectionStates,
 
1919
                                                      send_queue = Queue});
 
1920
                %% This is unlikely to happen. User configuration of the 
 
1921
                %% undocumented test option renegotiation_at can make it more likely.
 
1922
                {Msgs, RestData, ConnectionStates} ->
 
1923
                    if 
 
1924
                        Msgs =/= [] -> 
 
1925
                            Transport:send(Socket, Msgs);
 
1926
                        true ->
 
1927
                            ok
 
1928
                    end,
 
1929
                    renegotiate(State#state{connection_states = ConnectionStates,
 
1930
                                            send_queue = queue:in_r({From, RestData}, Queue),
 
1931
                                            renegotiation = {true, internal}})
 
1932
            end;
 
1933
        {empty, Queue0} ->
 
1934
            next_state_is_connection(State)
 
1935
    end.
 
1936
 
 
1937
%% In next_state_is_connection/1: clear tls_handshake_hashes,
 
1938
%% premaster_secret and public_key_info (only needed during handshake)
 
1939
%% to reduce memory foot print of a connection.
 
1940
next_state_is_connection(State = 
 
1941
                      #state{recv_during_renegotiation = true, socket_options = 
 
1942
                             #socket_options{active = false}})  -> 
 
1943
    passive_receive(State#state{recv_during_renegotiation = false,
 
1944
                                premaster_secret = undefined,
 
1945
                                public_key_info = undefined,
 
1946
                                tls_handshake_hashes = {<<>>, <<>>}}, connection);
 
1947
 
 
1948
next_state_is_connection(State0) ->
 
1949
    {Record, State} = next_record_if_active(State0),
 
1950
    next_state(connection, Record, State#state{premaster_secret = undefined,
 
1951
                                               public_key_info = undefined,
 
1952
                                               tls_handshake_hashes = {<<>>, <<>>}}).
 
1953
 
1567
1954
register_session(_, _, _, #session{is_resumable = true} = Session) ->
1568
1955
    Session; %% Already registered
1569
1956
register_session(client, Host, Port, Session0) ->
1581
1968
    ssl_manager:invalidate_session(Port, Session).
1582
1969
 
1583
1970
initial_state(Role, Host, Port, Socket, {SSLOptions, SocketOptions}, User,
1584
 
              {CbModule, DataTag, CloseTag}) ->
 
1971
              {CbModule, DataTag, CloseTag, ErrorTag}) ->
1585
1972
    ConnectionStates = ssl_record:init_connection_states(Role),
1586
1973
    
1587
1974
    SessionCacheCb = case application:get_env(ssl, session_cb) of
1601
1988
           transport_cb = CbModule,
1602
1989
           data_tag = DataTag,
1603
1990
           close_tag = CloseTag,
 
1991
           error_tag = ErrorTag,
1604
1992
           role = Role,
1605
1993
           host = Host,
1606
1994
           port = Port,
1613
2001
           bytes_to_read = 0,
1614
2002
           user_data_buffer = <<>>,
1615
2003
           log_alert = true,
1616
 
           session_cache_cb = SessionCacheCb
 
2004
           session_cache_cb = SessionCacheCb,
 
2005
           renegotiation = {false, first},
 
2006
           recv_during_renegotiation = false,
 
2007
           send_queue = queue:new()
1617
2008
          }.
1618
2009
 
1619
2010
sslsocket(Pid) ->
1628
2019
    get_socket_opts(Socket, Tags, SockOpts, 
1629
2020
                    [{mode, SockOpts#socket_options.mode} | Acc]);
1630
2021
get_socket_opts(Socket, [packet | Tags], SockOpts, Acc) ->
1631
 
    get_socket_opts(Socket, Tags, SockOpts, 
1632
 
                    [{packet, SockOpts#socket_options.packet} | Acc]);
 
2022
    case SockOpts#socket_options.packet of
 
2023
        {Type, headers} ->
 
2024
            get_socket_opts(Socket, Tags, SockOpts, [{packet, Type} | Acc]);
 
2025
        Type ->
 
2026
            get_socket_opts(Socket, Tags, SockOpts, [{packet, Type} | Acc])
 
2027
    end;
1633
2028
get_socket_opts(Socket, [header | Tags], SockOpts, Acc) ->
1634
2029
    get_socket_opts(Socket, Tags, SockOpts, 
1635
2030
                    [{header, SockOpts#socket_options.header} | Acc]);
1651
2046
    inet:setopts(Socket, Other),
1652
2047
    SockOpts;
1653
2048
set_socket_opts(Socket, [{mode, Mode}| Opts], SockOpts, Other) ->
1654
 
    set_socket_opts(Socket, Opts, SockOpts#socket_options{mode = Mode}, Other);
 
2049
    set_socket_opts(Socket, Opts, 
 
2050
                    SockOpts#socket_options{mode = Mode}, Other);
1655
2051
set_socket_opts(Socket, [{packet, Packet}| Opts], SockOpts, Other) ->
1656
2052
    set_socket_opts(Socket, Opts, 
1657
2053
                    SockOpts#socket_options{packet = Packet}, Other);
1664
2060
set_socket_opts(Socket, [Opt | Opts], SockOpts, Other) ->
1665
2061
    set_socket_opts(Socket, Opts, SockOpts, [Opt | Other]).
1666
2062
 
 
2063
handle_alerts([], Result) ->
 
2064
    Result;
 
2065
handle_alerts(_, {stop, _, _} = Stop) ->
 
2066
    %% If it is a fatal alert immediately close 
 
2067
    Stop;
 
2068
handle_alerts([Alert | Alerts], {next_state, StateName, State, _Timeout}) ->
 
2069
    handle_alerts(Alerts, handle_alert(Alert, StateName, State)).
 
2070
 
 
2071
handle_alert(#alert{level = ?FATAL} = Alert, StateName,
 
2072
             #state{from = From, host = Host, port = Port, session = Session,
 
2073
                    user_application = {_Mon, Pid},
 
2074
                    log_alert = Log, role = Role, socket_options = Opts} = State) ->
 
2075
    invalidate_session(Role, Host, Port, Session),
 
2076
    log_alert(Log, StateName, Alert),
 
2077
    alert_user(StateName, Opts, Pid, From, Alert, Role),
 
2078
    {stop, normal, State};
 
2079
 
 
2080
handle_alert(#alert{level = ?WARNING, description = ?CLOSE_NOTIFY} = Alert, 
 
2081
             StateName, #state{from = From, role = Role,  
 
2082
                               user_application = {_Mon, Pid}, socket_options = Opts} = State) -> 
 
2083
    alert_user(StateName, Opts, Pid, From, Alert, Role),
 
2084
    {stop, normal, State};
 
2085
 
 
2086
handle_alert(#alert{level = ?WARNING, description = ?NO_RENEGOTIATION} = Alert, StateName, 
 
2087
             #state{log_alert = Log, renegotiation = {true, internal}, from = From,
 
2088
                    role = Role} = State) ->
 
2089
    log_alert(Log, StateName, Alert),
 
2090
    alert_user(From, Alert, Role),
 
2091
    {stop, normal, State};
 
2092
 
 
2093
handle_alert(#alert{level = ?WARNING, description = ?NO_RENEGOTIATION} = Alert, StateName, 
 
2094
             #state{log_alert = Log, renegotiation = {true, From}} = State0) ->
 
2095
    log_alert(Log, StateName, Alert),
 
2096
    gen_fsm:reply(From, {error, renegotiation_rejected}),
 
2097
    {Record, State} = next_record(State0),
 
2098
    next_state(connection, Record, State);
 
2099
 
 
2100
handle_alert(#alert{level = ?WARNING, description = ?USER_CANCELED} = Alert, StateName, 
 
2101
             #state{log_alert = Log} = State0) ->
 
2102
    log_alert(Log, StateName, Alert),
 
2103
    {Record, State} = next_record(State0),
 
2104
    next_state(StateName, Record, State).
 
2105
 
 
2106
alert_user(connection, Opts, Pid, From, Alert, Role) ->
 
2107
    alert_user(Opts#socket_options.active, Pid, From, Alert, Role);
 
2108
alert_user(_, _, _, From, Alert, Role) ->
 
2109
    alert_user(From, Alert, Role).
 
2110
 
1667
2111
alert_user(From, Alert, Role) ->
1668
2112
    alert_user(false, no_pid, From, Alert, Role).
1669
2113
 
1670
2114
alert_user(false = Active, Pid, From,  Alert, Role) ->
 
2115
    %% If there is an outstanding ssl_accept | recv
 
2116
    %% From will be defined and send_or_reply will
 
2117
    %% send the appropriate error message.
1671
2118
    ReasonCode = ssl_alert:reason_code(Alert, Role),
1672
2119
    send_or_reply(Active, Pid, From, {error, ReasonCode});
1673
2120
alert_user(Active, Pid, From, Alert, Role) ->
1680
2127
                          {ssl_error, sslsocket(), ReasonCode})
1681
2128
    end.
1682
2129
 
1683
 
log_alert(true, StateName, Alert) ->
 
2130
log_alert(true, Info, Alert) ->
1684
2131
    Txt = ssl_alert:alert_txt(Alert),
1685
 
    error_logger:format("SSL: ~p: ~s\n", [StateName, Txt]);
 
2132
    error_logger:format("SSL: ~p: ~s\n", [Info, Txt]);
1686
2133
log_alert(false, _, _) ->
1687
2134
    ok.
1688
2135
 
1689
 
handle_own_alert(Alert, Version, StateName, 
 
2136
handle_own_alert(Alert, Version, Info, 
1690
2137
                 #state{transport_cb = Transport,
1691
2138
                        socket = Socket,
1692
2139
                        from = User,
1693
2140
                        role = Role,
1694
2141
                        connection_states = ConnectionStates,
1695
2142
                        log_alert = Log}) ->
1696
 
    {BinMsg, _} =
 
2143
    try %% Try to tell the other side
 
2144
        {BinMsg, _} =
1697
2145
        encode_alert(Alert, Version, ConnectionStates),
1698
 
    Transport:send(Socket, BinMsg),
1699
 
    log_alert(Log, StateName, Alert),
1700
 
    alert_user(User, Alert, Role).
1701
 
 
1702
 
make_premaster_secret({MajVer, MinVer}) ->
 
2146
        linux_workaround_transport_delivery_problems(Alert, Socket),
 
2147
        Transport:send(Socket, BinMsg)
 
2148
    catch _:_ ->  %% Can crash if we are in a uninitialized state
 
2149
            ignore
 
2150
    end,
 
2151
    try %% Try to tell the local user
 
2152
        log_alert(Log, Info, Alert),
 
2153
        alert_user(User, Alert, Role)
 
2154
    catch _:_ ->
 
2155
            ok
 
2156
    end.
 
2157
 
 
2158
handle_unexpected_message(Msg, Info, #state{negotiated_version = Version} = State) ->
 
2159
    Alert =  ?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE),
 
2160
    handle_own_alert(Alert, Version, {Info, Msg}, State),
 
2161
    {stop, normal, State}.
 
2162
 
 
2163
make_premaster_secret({MajVer, MinVer}, rsa) ->
1703
2164
    Rand = crypto:rand_bytes(?NUM_OF_PREMASTERSECRET_BYTES-2),
1704
 
    <<?BYTE(MajVer), ?BYTE(MinVer), Rand/binary>>.
 
2165
    <<?BYTE(MajVer), ?BYTE(MinVer), Rand/binary>>;
 
2166
make_premaster_secret(_, _) ->
 
2167
    undefined.
 
2168
 
 
2169
mpint_binary(Binary)  ->
 
2170
    Size = byte_size(Binary),
 
2171
    <<?UINT32(Size), Binary/binary>>.
 
2172
 
 
2173
 
 
2174
ack_connection(#state{renegotiation = {true, Initiater}} = State) 
 
2175
  when Initiater == internal;
 
2176
       Initiater == peer ->
 
2177
    State#state{renegotiation = undefined};
 
2178
ack_connection(#state{renegotiation = {true, From}} = State) ->    
 
2179
    gen_fsm:reply(From, ok),
 
2180
    State#state{renegotiation = undefined};
 
2181
ack_connection(#state{renegotiation = {false, first}, 
 
2182
                                  from = From} = State) when From =/= undefined ->
 
2183
    gen_fsm:reply(From, connected),
 
2184
    State#state{renegotiation = undefined};
 
2185
ack_connection(State) ->
 
2186
    State.
 
2187
 
 
2188
renegotiate(#state{role = client} = State) ->
 
2189
    %% Handle same way as if server requested
 
2190
    %% the renegotiation
 
2191
    Hs0 = ssl_handshake:init_hashes(),
 
2192
    connection(#hello_request{}, State#state{tls_handshake_hashes = Hs0});  
 
2193
renegotiate(#state{role = server,
 
2194
                   socket = Socket,
 
2195
                   transport_cb = Transport,
 
2196
                   negotiated_version = Version,
 
2197
                   connection_states = ConnectionStates0} = State0) ->
 
2198
    HelloRequest = ssl_handshake:hello_request(),
 
2199
    Frag = ssl_handshake:encode_handshake(HelloRequest, Version),
 
2200
    Hs0 = ssl_handshake:init_hashes(),
 
2201
    {BinMsg, ConnectionStates} = 
 
2202
        ssl_record:encode_handshake(Frag, Version, ConnectionStates0),
 
2203
    Transport:send(Socket, BinMsg),
 
2204
    {Record, State} = next_record(State0#state{connection_states = 
 
2205
                                               ConnectionStates,
 
2206
                                               tls_handshake_hashes = Hs0}),
 
2207
    next_state(hello, Record, State).
 
2208
 
 
2209
notify_senders(SendQueue) -> 
 
2210
    lists:foreach(fun({From, _}) ->
 
2211
                          gen_fsm:reply(From, {error, closed})
 
2212
                  end, queue:to_list(SendQueue)).
 
2213
 
 
2214
notify_renegotiater({true, From}) when not is_atom(From)  ->
 
2215
    gen_fsm:reply(From, {error, closed});
 
2216
notify_renegotiater(_) ->
 
2217
    ok.
 
2218
 
 
2219
terminate_alert(Reason, Version, ConnectionStates) when Reason == normal; Reason == shutdown;
 
2220
                                                        Reason == user_close ->
 
2221
    {BinAlert, _} = encode_alert(?ALERT_REC(?WARNING, ?CLOSE_NOTIFY),
 
2222
                                 Version, ConnectionStates),
 
2223
    BinAlert;
 
2224
terminate_alert(_, Version, ConnectionStates) ->
 
2225
    {BinAlert, _} = encode_alert(?ALERT_REC(?FATAL, ?INTERNAL_ERROR),
 
2226
                                 Version, ConnectionStates),
 
2227
    BinAlert.
 
2228
 
 
2229
workaround_transport_delivery_problems(_,_, user_close) ->
 
2230
    ok;
 
2231
workaround_transport_delivery_problems(Socket, Transport, _) ->
 
2232
    %% Standard trick to try to make sure all
 
2233
    %% data sent to to tcp port is really sent
 
2234
    %% before tcp port is closed so that the peer will
 
2235
    %% get a correct error message.
 
2236
    inet:setopts(Socket, [{active, false}]),
 
2237
    Transport:shutdown(Socket, write),
 
2238
    Transport:recv(Socket, 0).
 
2239
 
 
2240
linux_workaround_transport_delivery_problems(#alert{level = ?FATAL}, Socket) ->
 
2241
    case os:type() of
 
2242
        {unix, linux} ->
 
2243
            inet:setopts(Socket, [{nodelay, true}]);
 
2244
        _ ->
 
2245
            ok
 
2246
    end;
 
2247
linux_workaround_transport_delivery_problems(_, _) ->
 
2248
    ok.
 
2249
 
 
2250
get_timeout(#state{ssl_options=#ssl_options{hibernate_after=undefined}}) ->
 
2251
    infinity;
 
2252
get_timeout(#state{ssl_options=#ssl_options{hibernate_after=HibernateAfter}}) ->
 
2253
    HibernateAfter.