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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%<copyright>
 
2
%% <year>2007-2008</year>
 
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
 
4
%%</copyright>
 
5
%%<legalnotice>
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
6
 
%% 
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
 
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
16
%%
 
17
%% The Initial Developer of the Original Code is Ericsson AB.
 
18
%%</legalnotice>
17
19
%%----------------------------------------------------------------------
18
20
%% Purpose: Help funtions for handling the SSL-handshake protocol
19
21
%%----------------------------------------------------------------------
25
27
-include("ssl_cipher.hrl").
26
28
-include("ssl_alert.hrl").
27
29
-include("ssl_internal.hrl").
28
 
-include("ssl_pkix.hrl").
29
30
-include("ssl_debug.hrl").
 
31
-include_lib("public_key/include/public_key.hrl").
30
32
 
31
33
-export([master_secret/4, client_hello/4, server_hello/3, hello/2, 
32
 
         certify/3, certificate/3, 
33
 
         certificate_verify/6, key_exchange/3,  finished/4,
34
 
         verify_connection/5, get_tls_handshake/2,
 
34
         certify/5, certificate/3, 
 
35
         client_certificate_verify/6, 
 
36
         certificate_verify/6, certificate_request/2,
 
37
         key_exchange/2, finished/4,
 
38
         verify_connection/5, 
 
39
         get_tls_handshake/4,
35
40
         server_hello_done/0, sig_alg/1,
36
 
         decode_handshake/3, encode_handshake/2, init_hashes/0, 
 
41
         encode_handshake/3, init_hashes/0, 
37
42
         update_hashes/2, decrypt_premaster_secret/2]).
38
43
 
39
44
%%====================================================================
49
54
%%
50
55
%% Description: Creates a client hello message.
51
56
%%--------------------------------------------------------------------
52
 
client_hello(Host, Port, ConnectionStates, SslOpts) ->
 
57
client_hello(Host, Port, ConnectionStates, #ssl_options{versions = Versions,
 
58
                                                        ciphers = Ciphers} 
 
59
             = SslOpts) ->
53
60
    
54
 
    Version = ssl_record:highest_protocol_version(),
 
61
    Fun = fun(Version) ->
 
62
                  ssl_record:protocol_version(Version)
 
63
          end,
 
64
    Version = ssl_record:highest_protocol_version(lists:map(Fun, Versions)),
55
65
    Pending = ssl_record:pending_connection_state(ConnectionStates, read),
56
66
    SecParams = Pending#connection_state.security_parameters,
57
67
   
58
 
    Id = ssl_manager:client_session_id(Host, 
59
 
                                  Port, SslOpts),
 
68
    Id = ssl_manager:client_session_id(Host, Port, SslOpts),
 
69
 
60
70
    #client_hello{session_id = Id, 
61
71
                  client_version = Version,
62
 
                  cipher_suites = SslOpts#ssl_options.ciphers,
 
72
                  cipher_suites = Ciphers,
63
73
                  compression_methods = ssl_record:compressions(),
64
74
                  random = SecParams#security_parameters.client_random
65
75
                 }.
77
87
server_hello(SessionId, Version, ConnectionStates) ->
78
88
    Pending = ssl_record:pending_connection_state(ConnectionStates, read),
79
89
    SecParams = Pending#connection_state.security_parameters,
80
 
    
81
90
    #server_hello{server_version = Version,
82
91
                  cipher_suite = SecParams#security_parameters.cipher_suite,
83
92
                  compression_method = 
111
120
    
112
121
    {Version, SessionId, NewConnectionStates};
113
122
 
114
 
hello(Hello = #client_hello{}, {Port, UserSuites,
115
 
                                Session0, ConnectionStates0}) ->
 
123
hello(Hello = #client_hello{}, {Port, 
 
124
                                #ssl_options{versions = Versions} = SslOpts,
 
125
                                Session0, Cache, CacheCb,
 
126
                                ConnectionStates0}) ->
116
127
    
117
 
    Version = select_version(Hello#client_hello.client_version),
 
128
    Version = select_version(Hello#client_hello.client_version, Versions),
118
129
  
119
130
    case ssl_record:is_acceptable_version(Version) of
120
131
        true ->
121
132
            {Type, #session{cipher_suite = CipherSuite,
122
133
                            compression_method = Compression} = Session} 
123
 
             = select_session(Hello, Port, Session0, Version, UserSuites),
 
134
                = select_session(Hello, Port, Session0, Version, 
 
135
                                 SslOpts, Cache, CacheCb),
124
136
             
125
137
            case CipherSuite of 
126
138
                no_suite ->
127
 
                    #alert{level = ?FATAL,
128
 
                           description = ?INSUFFICIENT_SECURITY};
 
139
                    ?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY);
129
140
                _ ->
130
141
                    Random = Hello#client_hello.random, 
131
142
                    ConnectionStates =
137
148
                    {Version, {Type, Session}, ConnectionStates}
138
149
            end;
139
150
        false ->
140
 
            #alert{level = ?FATAL,
141
 
                   description = ?PROTOCOL_VERSION}
 
151
            ?ALERT_REC(?FATAL, ?PROTOCOL_VERSION)
142
152
    end.
143
153
 
144
154
%%--------------------------------------------------------------------
145
155
%% Function: certify(Certs, CertDbRef, MaxPathLen) ->
146
 
%%                                           #'Certificate'{} | #alert{}
 
156
%%                                 {PeerCert, PublicKeyInfo}  | #alert{}
147
157
%%
148
158
%%      Certs = #certificate{}
149
159
%%      CertDbRef = reference()
151
161
%%
152
162
%% Description: Handles a certificate handshake message
153
163
%%--------------------------------------------------------------------
154
 
certify(#certificate{asn1_certificates = ASN1Certs}, CertDbRef, MaxPathLen) -> 
 
164
certify(#certificate{asn1_certificates = ASN1Certs}, CertDbRef, 
 
165
        MaxPathLen, Verify, VerifyFun) -> 
155
166
    [PeerCert | _] = ASN1Certs,
156
 
    Certs = lists:map(fun(Cert) ->
157
 
                              {ok, DecodedCert} =
158
 
                                  ssl_pkix:decode_cert(Cert, [ssl]),
159
 
                              {Cert, DecodedCert}
160
 
                      end, ASN1Certs),
161
 
    {{_BinCert, TrustedErlCert}, CertPath} =
162
 
        ssl_certificate:trusted_cert_and_path(Certs, CertDbRef),
163
 
    InitPathLen = case MaxPathLen of
164
 
                      nolimit ->
165
 
                          length(CertPath);
166
 
                      _ ->
167
 
                          MaxPathLen
168
 
                  end,
169
 
    ValidationState = 
170
 
        ssl_certificate:init_validation_state(TrustedErlCert, InitPathLen),
171
 
    {ok, PublicKeyInfo} = path_validation(CertPath, ValidationState),
172
 
    {PeerCert, PublicKeyInfo}.
173
 
 
 
167
    VerifyBool =  verify_bool(Verify),
 
168
  
 
169
    try 
 
170
        ssl_certificate:trusted_cert_and_path(ASN1Certs, 
 
171
                                              CertDbRef, VerifyBool) of
 
172
        {TrustedErlCert, CertPath, VerifyErrors} ->
 
173
            %% Note VerifyErrors will always be the empty list
 
174
            %% if VerifyBool = true or we will end up in catch branch
 
175
            Result = public_key:pkix_path_validation(TrustedErlCert, 
 
176
                                                     CertPath, 
 
177
                                                     [{max_path_length, 
 
178
                                                       MaxPathLen},
 
179
                                                      {verify, VerifyBool},
 
180
                                                      {acc_errors, 
 
181
                                                       VerifyErrors}]),
 
182
            case Result of
 
183
                {error, Reason} ->
 
184
                    path_validation_alert(Reason, Verify);
 
185
                {ok, {PublicKeyInfo,_, []}} ->
 
186
                    {PeerCert, PublicKeyInfo};
 
187
                {ok, {PublicKeyInfo,_, AccErrors = [Error | _]}} ->
 
188
                    case VerifyFun(AccErrors) of
 
189
                        true ->
 
190
                            {PeerCert, PublicKeyInfo};
 
191
                        false ->
 
192
                            path_validation_alert(Error, Verify)
 
193
                    end
 
194
            end
 
195
    catch 
 
196
        throw:Alert ->
 
197
            Alert
 
198
    end.
 
199
            
174
200
%%--------------------------------------------------------------------
175
201
%% Function: certificate(OwnCert, CertDbRef, Role) -> #certificate{}
176
202
%%
198
224
        {ok, Chain} ->
199
225
            #certificate{asn1_certificates = Chain};
200
226
        {error, _} ->
201
 
            #alert{level  = ?FATAL,
202
 
                   description =  ?INTERNAL_ERROR}
203
 
        end.
 
227
            ?ALERT_REC(?FATAL, ?INTERNAL_ERROR)
 
228
    end.
204
229
 
205
230
%%--------------------------------------------------------------------
206
 
%% Function: certificate_verify(Cert, ConnectionStates) -> 
 
231
%% Function: client_certificate_verify(Cert, ConnectionStates) -> 
207
232
%%                                                #certificate_verify{}
208
 
%% Cert             = #certificate{}
 
233
%% Cert             = #'OTPcertificate'{}
209
234
%% ConnectionStates = #connection_states{}
210
235
%%
211
236
%% Description: Creates a certificate_verify message, called by the client.
212
237
%%--------------------------------------------------------------------
213
 
certificate_verify(OwnCert, ConnectionStates, Version, Algorithm,
214
 
                   PrivateKey, {Hashes, _}) ->
215
 
    ?DBG_TERM(ConnectionStates),
216
 
    case is_fixed_diffie_hellman(OwnCert, ConnectionStates) of
 
238
client_certificate_verify(OwnCert, MasterSecret, Version, Algorithm,
 
239
                   PrivateKey, {Hashes0, _}) ->
 
240
    case public_key:pkix_is_fixed_dh_cert(OwnCert) of
217
241
        true ->
218
242
            fixed_diffie_hellman;
219
243
        false ->
220
 
            MasterSecret =
221
 
                ssl_record:get_pending_master_secret(ConnectionStates),
222
 
            Sig = ssl_cipher:get_handshake_hashes(Version, none,
223
 
                                                     MasterSecret, Hashes),
224
 
            Signed = ssl_cipher:digitally_sign(Algorithm, Sig, PrivateKey),
 
244
            Hashes = 
 
245
                calc_certificate_verify(Version, MasterSecret,
 
246
                                              Algorithm, Hashes0), 
 
247
            Signed = digitally_signed(Hashes, PrivateKey),
225
248
            #certificate_verify{signature = Signed}
226
249
    end.
 
250
 
 
251
%%--------------------------------------------------------------------
 
252
%% Function: certificate_verify(Signature, PublicKeyInfo) -> valid | #alert{}
 
253
%%
 
254
%% Signature     = binary()
 
255
%% PublicKeyInfo = {Algorithm, PublicKey, PublicKeyParams}
 
256
%%
 
257
%% Description: Checks that the certificate_verify message is valid.
 
258
%%--------------------------------------------------------------------
 
259
certificate_verify(Signature, {_, PublicKey, _}, Version, 
 
260
                   MasterSecret, Algorithm, {_, Hashes0}) when Algorithm == rsa;
 
261
                                                               Algorithm == dh_rsa;
 
262
                                                               Algorithm == dhe_rsa ->
 
263
    Hashes = calc_certificate_verify(Version, MasterSecret,
 
264
                                           Algorithm, Hashes0),
 
265
    case public_key:decrypt_public(Signature, PublicKey, 
 
266
                                   [{rsa_pad, rsa_pkcs1_padding}]) of
 
267
        Hashes ->
 
268
            valid;
 
269
        _ ->
 
270
            ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE)
 
271
    end.
 
272
%% TODO dsa cluse
 
273
 
 
274
%%--------------------------------------------------------------------
 
275
%% Function: certificate_request(ConnectionStates, CertDbRef) -> 
 
276
%%                                                #certificate_request{}
 
277
%%
 
278
%% Description: Creates a certificate_request message, called by the server.
 
279
%%--------------------------------------------------------------------
 
280
certificate_request(ConnectionStates, CertDbRef) ->
 
281
    #connection_state{security_parameters = 
 
282
                      #security_parameters{cipher_suite = CipherSuite}} =
 
283
        ssl_record:pending_connection_state(ConnectionStates, read),
 
284
    Types = certificate_types(CipherSuite),
 
285
    Authorities = certificate_authorities(CertDbRef),
 
286
    #certificate_request{
 
287
                    certificate_types = Types,
 
288
                    certificate_authorities = Authorities
 
289
                   }.
 
290
 
227
291
%%--------------------------------------------------------------------
228
292
%% Function: key_exchange(Role, Secret, Params) -> 
229
293
%%                         #client_key_exchange{} | #server_key_exchange{}
233
297
%%
234
298
%% Description: Creates a keyexchange message.
235
299
%%--------------------------------------------------------------------
236
 
key_exchange(client, Secret, {Algorithm, PublicKey, _}) when 
237
 
  Algorithm == rsaEncryption;
238
 
  Algorithm == md2WithRSAEncryption;
239
 
  Algorithm == md5WithRSAEncryption;
240
 
  Algorithm == sha1WithRSAEncryption ->
 
300
key_exchange(client, {premaster_secret, Secret, {_, PublicKey, _}}) ->
241
301
    EncPremasterSecret =
242
302
        encrypted_premaster_secret(Secret, PublicKey),
243
303
    #client_key_exchange{exchange_keys = EncPremasterSecret};
244
 
key_exchange(client, _Secret, _Params = #server_dh_params{}) -> 
245
 
    #client_key_exchange{exchange_keys = #client_diffie_hellman_public{}};
246
 
key_exchange(client, _, _) ->
247
 
    #client_key_exchange{ 
248
 
              %%exchange_keys =  #kerberos_wrapper{}
249
 
             };
250
 
key_exchange(server, _, _) ->
 
304
key_exchange(client, fixed_diffie_hellman) -> 
 
305
    #client_key_exchange{exchange_keys = 
 
306
                         #client_diffie_hellman_public{
 
307
                           dh_public = <<>>
 
308
                          }};
 
309
key_exchange(client, {dh, PublicKey}) ->
 
310
    Len = size(PublicKey), 
 
311
    #client_key_exchange{
 
312
                exchange_keys = #client_diffie_hellman_public{
 
313
                  dh_public = <<?UINT16(Len), PublicKey/binary>>}
 
314
               };
 
315
 
 
316
%% key_exchange(server, {{?'dhpublicnumber', _PublicKey, 
 
317
%%                     #'DomainParameters'{p = P, g = G, y = Y},
 
318
%%                     SignAlgorithm, ClientRandom, ServerRandom}})  ->
 
319
%%     ServerDHParams = #server_dh_params{dh_p = P, dh_g = G, dh_y = Y},
 
320
%%     PLen = size(P),
 
321
%%     GLen = size(G),
 
322
%%     YLen = size(Y),
 
323
%%     Hash = server_key_exchange_hash(SignAlgorithm, <<ClientRandom/binary, 
 
324
%%                                                  ServerRandom/binary, 
 
325
%%                                                  ?UINT16(PLen), P/binary, 
 
326
%%                                                  ?UINT16(GLen), G/binary,
 
327
%%                                                  ?UINT16(YLen), Y/binary>>),
 
328
%%     Signed = digitally_signed(Hash, PrivateKey),
 
329
%%     #server_key_exchange{
 
330
%%                params = ServerDHParams,
 
331
%%                signed_params = Signed
 
332
%%               };
 
333
key_exchange(_, _) ->
 
334
    %%TODO : Real imp
251
335
    #server_key_exchange{}.
252
336
 
253
337
%%--------------------------------------------------------------------
269
353
    ConnectionState = 
270
354
        ssl_record:pending_connection_state(ConnectionStates, read),
271
355
    SecParams = ConnectionState#connection_state.security_parameters,
272
 
    try master_secret(Version, Mastersecret, SecParams, ConnectionStates, Role) of
 
356
    try master_secret(Version, Mastersecret, SecParams, 
 
357
                      ConnectionStates, Role) of
273
358
        Result ->
274
359
            Result
275
360
    catch
276
361
        exit:Reason ->
277
362
            error_logger:error_report("Key calculation failed due to ~p",
278
363
                                      [Reason]),
279
 
            #alert{level = ?FATAL, description = ?HANDSHAKE_FAILURE}
 
364
            ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE)
280
365
    end;
281
366
 
282
367
master_secret(Version, PremasterSecret, ConnectionStates, Role) ->
284
369
        ssl_record:pending_connection_state(ConnectionStates, read),
285
370
    SecParams = ConnectionState#connection_state.security_parameters,
286
371
    #security_parameters{client_random = ClientRandom,
287
 
                         server_random = ServerRandom} = SecParams,             
 
372
                         server_random = ServerRandom} = SecParams, 
288
373
    try master_secret(Version, 
289
 
                      ssl_cipher:master_secret(Version,PremasterSecret,
290
 
                                               ClientRandom, ServerRandom),
 
374
                      calc_master_secret(Version,PremasterSecret,
 
375
                                       ClientRandom, ServerRandom),
291
376
                      SecParams, ConnectionStates, Role) of
292
377
        Result ->
293
378
            Result
296
381
        exit:Reason ->
297
382
            error_logger:error_report("Master secret calculation failed"
298
383
                                      " due to ~p", [Reason]),
299
 
            #alert{level = ?FATAL, description = ?HANDSHAKE_FAILURE}
 
384
            ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE)
300
385
    end.
301
386
 
302
387
%%--------------------------------------------------------------------
308
393
%%-------------------------------------------------------------------
309
394
finished(Version, Role, MasterSecret, {Hashes, _}) -> % use the current hashes
310
395
    #finished{verify_data = 
311
 
              ssl_cipher:get_handshake_hashes(Version, Role, MasterSecret, Hashes)}.
 
396
              calc_finished(Version, Role, MasterSecret, Hashes)}.
312
397
 
313
398
%%--------------------------------------------------------------------
314
399
%% Function: verify_connection(Finished, Role, 
325
410
%%              the connection.
326
411
%%-------------------------------------------------------------------
327
412
verify_connection(Version, #finished{verify_data = Data}, 
328
 
                  Role, MasterSecret, {_, {MD5, SHA}}) -> % use the previous hashes
 
413
                  Role, MasterSecret, {_, {MD5, SHA}}) -> 
 
414
    %% use the previous hashes
329
415
    ?DBG_HEX(crypto:md5_final(MD5)),
330
416
    ?DBG_HEX(crypto:sha_final(SHA)),
331
 
    case ssl_cipher:get_handshake_hashes(Version, Role, MasterSecret, {MD5, SHA}) of
 
417
    case calc_finished(Version, Role, MasterSecret, {MD5, SHA}) of
332
418
        Data ->
333
419
            verified;
334
 
        _ ->
335
 
            #alert{level = ?FATAL,
336
 
                   description = ?HANDSHAKE_FAILURE}
 
420
        _E ->
 
421
            ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE)
337
422
    end.
338
423
            
339
 
%%--------------------------------------------------------------------
340
 
%% Function: decode_handshake(BinHandShake, KeyExchange, SigAlg)
341
 
%%           -> #client_hello | #server_hello{} | server_hello_done |
342
 
%% #certificate{} | #client_key_exchange{} | #finished{} |
343
 
%% #client_certify_request{}
344
 
%%     
345
 
%% decode a binary handshake packet
346
 
%%--------------------------------------------------------------------
347
 
decode_handshake(#handshake{msg_type = MsgType,
348
 
                            body = Contents}, KeyExchangeAlg, SigAlg) ->
349
 
    dec_hs(MsgType, Contents, KeyExchangeAlg, SigAlg);
350
 
decode_handshake(_, _, _) ->
351
 
    not_handshake_packet.
352
 
 
353
424
server_hello_done() ->
354
425
    #server_hello_done{}.
355
426
 
361
432
%%     
362
433
%% encode a handshake packet to binary
363
434
%%--------------------------------------------------------------------
364
 
encode_handshake(Package, SigAlg) ->
365
 
    {MsgType, Bin} = enc_hs(Package, SigAlg),
 
435
encode_handshake(Package, Version, SigAlg) ->
 
436
    {MsgType, Bin} = enc_hs(Package, Version, SigAlg),
366
437
    Len = size(Bin),
367
438
    [MsgType, ?uint24(Len), Bin].
368
439
 
375
446
%% and returns it as a list of #handshake, also returns leftover
376
447
%% data.
377
448
%%--------------------------------------------------------------------
378
 
get_tls_handshake(Data, Buffer) ->
379
 
    get_tls_handshake_aux(list_to_binary([Buffer, Data]), [], []).
 
449
get_tls_handshake(Data, <<>>, KeyAlg, Version) ->
 
450
    get_tls_handshake_aux(Data, KeyAlg, Version, []);
 
451
get_tls_handshake(Data, Buffer, KeyAlg, Version) ->
 
452
    get_tls_handshake_aux(list_to_binary([Buffer, Data]), 
 
453
                          KeyAlg, Version, []).
380
454
 
381
 
get_tls_handshake_aux(<<?BYTE(Type), ?UINT24(Length), Body:Length/binary,
382
 
                       Rest/binary>>, Acc, RawAcc) ->
 
455
get_tls_handshake_aux(<<?BYTE(Type), ?UINT24(Length), Body:Length/binary,Rest/binary>>, 
 
456
                      KeyAlg, Version, Acc) ->
383
457
    Raw = <<?BYTE(Type), ?UINT24(Length), Body/binary>>,
384
 
    H = #handshake{msg_type = Type, length = Length, body = Body},
385
 
    get_tls_handshake_aux(Rest, [H | Acc], [Raw | RawAcc]);
386
 
get_tls_handshake_aux(Data, Acc, RawAcc) ->
387
 
    {lists:reverse(Acc), lists:reverse(RawAcc), Data}.
388
 
 
 
458
    H = dec_hs(Type, Body, KeyAlg, Version),
 
459
    get_tls_handshake_aux(Rest, KeyAlg, Version, [{H,Raw} | Acc]);
 
460
get_tls_handshake_aux(Data, _KeyAlg, _Version, Acc) ->
 
461
    {lists:reverse(Acc), Data}.
389
462
 
390
463
%%--------------------------------------------------------------------
391
464
%% Function: sig_alg(atom()) -> integer()
407
480
%%--------------------------------------------------------------------
408
481
%%% Internal functions
409
482
%%--------------------------------------------------------------------
410
 
select_session(Hello, Port, Session, Version, UserSuites) ->
 
483
verify_bool(verify_peer) ->
 
484
    true;
 
485
verify_bool(verify_none) ->
 
486
    false.
 
487
 
 
488
path_validation_alert({bad_cert, cert_expired}, _) ->
 
489
    ?ALERT_REC(?FATAL, ?CERTIFICATE_EXPIRED);
 
490
path_validation_alert({bad_cert, invalid_issuer}, _) ->
 
491
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
 
492
path_validation_alert({bad_cert, invalid_signature} , _) ->
 
493
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
 
494
path_validation_alert({bad_cert, name_not_permitted}, _) ->
 
495
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
 
496
path_validation_alert({bad_cert, unknown_critical_extension}, _) ->
 
497
    ?ALERT_REC(?FATAL, ?UNSUPPORTED_CERTIFICATE);
 
498
path_validation_alert({bad_cert, cert_revoked}, _) ->
 
499
    ?ALERT_REC(?FATAL, ?CERTIFICATE_REVOKED);
 
500
path_validation_alert(_, _) ->
 
501
    ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE).
 
502
 
 
503
select_session(Hello, Port, Session, Version, 
 
504
               #ssl_options{ciphers = UserSuites} = SslOpts, Cache, CacheCb) ->
411
505
    SuggestedSessionId = Hello#client_hello.session_id,
412
 
    SessionId = ssl_manager:server_session_id(Port, SuggestedSessionId),
 
506
    SessionId = ssl_manager:server_session_id(Port, SuggestedSessionId, 
 
507
                                              SslOpts),
413
508
    
414
509
    Suites = case UserSuites of
415
510
                 [] ->
427
522
            {new, Session#session{session_id = SessionId,
428
523
                                  cipher_suite = CipherSuite,
429
524
                                  compression_method = Compression}};
430
 
        false ->
431
 
            {resumed, ssl_session:cache_lookup(Port, SessionId)}
 
525
        false ->            
 
526
            {resumed, CacheCb:lookup(Cache, {Port, SessionId})}
432
527
    end.
433
528
            
434
529
%% Update pending connection states with parameters exchanged via 
472
567
      compression_algorithm = Compression
473
568
     }.
474
569
 
475
 
select_version(ClientVersion) ->
476
 
    ServerVersion = ssl_record:highest_protocol_version(),
 
570
select_version(ClientVersion, Versions) ->   
 
571
    Fun = fun(Version) ->
 
572
                  ssl_record:protocol_version(Version)
 
573
          end,
 
574
    ServerVersion = ssl_record:highest_protocol_version(lists:map(Fun,
 
575
                                                                  Versions)),
477
576
    ssl_record:lowest_protocol_version(ClientVersion, ServerVersion).
478
577
 
479
578
select_cipher_suite([], _) ->
501
600
                         iv_size = IVS,
502
601
                         exportable = Exportable},
503
602
              ConnectionStates, Role) ->
504
 
    ?DBG_TERM(KML),
505
603
    {ClientWriteMacSecret, ServerWriteMacSecret, ClientWriteKey,
506
604
     ServerWriteKey, ClientIV, ServerIV} =
507
 
        ssl_cipher:setup_keys(Version, Exportable, MasterSecret, ServerRandom, 
508
 
                              ClientRandom, HashSize, KML, EKML, IVS),
 
605
        setup_keys(Version, Exportable, MasterSecret, ServerRandom, 
 
606
                   ClientRandom, HashSize, KML, EKML, IVS),
509
607
    ?DBG_HEX(ClientWriteKey),
510
608
    ?DBG_HEX(ClientIV),
511
609
    ConnStates1 = ssl_record:set_master_secret(MasterSecret, ConnectionStates),
513
611
        ssl_record:set_mac_secret(ClientWriteMacSecret, ServerWriteMacSecret,
514
612
                                  Role, ConnStates1),
515
613
 
516
 
    CSCW = #cipher_state{iv = ClientIV, key = ClientWriteKey},
517
 
    CSSW = #cipher_state{iv = ServerIV, key = ServerWriteKey}, 
 
614
    ClientCipherState = #cipher_state{iv = ClientIV, key = ClientWriteKey},
 
615
    ServerCipherState = #cipher_state{iv = ServerIV, key = ServerWriteKey}, 
518
616
    {MasterSecret, 
519
 
     ssl_record:set_pending_cipher_state(ConnStates2, CSSW, CSCW, Role)}.
520
 
 
521
 
path_validation([], #path_validation_state{working_public_key_algorithm
522
 
                                           = Algorithm,
523
 
                                           working_public_key =
524
 
                                           PublicKey,
525
 
                                           working_public_key_parameters 
526
 
                                           = PublicKeyParams
527
 
                                          }) ->
528
 
    {ok, {Algorithm, PublicKey, PublicKeyParams}};
529
 
 
530
 
path_validation([{Cert, ErlCert}| Rest], 
531
 
                ValidationState = 
532
 
                #path_validation_state{
533
 
                  max_path_length = Len}) when Len >= 0 ->
534
 
    ssl_certificate:validate_time(ErlCert),
535
 
    ssl_certificate:validate_signature(ErlCert, Cert, ValidationState),
536
 
    ssl_certificate:validate_issuer(ErlCert, ValidationState),
537
 
    ssl_certificate:validate_names(ErlCert, ValidationState),
538
 
    ssl_certificate:is_not_revoked(ErlCert),
539
 
    TmpValidationState = 
540
 
        ssl_certificate:validate_extensions(ErlCert, ValidationState),
541
 
    NewValidationState = 
542
 
        ssl_certificate:prepare_for_next_cert(ErlCert, TmpValidationState),
543
 
    path_validation(Rest, NewValidationState);
544
 
 
545
 
path_validation(_, _) ->
546
 
    throw(#alert{level = ?FATAL,
547
 
                 description = ?CERTIFICATE_UNKNOWN}).
 
617
     ssl_record:set_pending_cipher_state(ConnStates2, ClientCipherState, 
 
618
                                         ServerCipherState, Role)}.
 
619
 
548
620
 
549
621
dec_hs(?HELLO_REQUEST, <<>>, _, _) ->
550
622
    #hello_request{};
560
632
       _, _) ->
561
633
    ?DBG_HEX(CipherSuites),
562
634
    ?DBG_HEX(CipherSuites),
563
 
    #client_hello{
564
 
        client_version = #protocol_version{major = Major, minor = Minor},
565
 
        random = ssl_ssl2:client_random(ChallengeData, CDLength),
566
 
        session_id = 0,
567
 
        cipher_suites = from_3bytes(CipherSuites),
568
 
        compression_methods = [?NULL]};
569
 
 
 
635
    #client_hello{client_version = {Major, Minor},
 
636
                  random = ssl_ssl2:client_random(ChallengeData, CDLength),
 
637
                  session_id = 0,
 
638
                  cipher_suites = from_3bytes(CipherSuites),
 
639
                  compression_methods = [?NULL]
 
640
                 };
570
641
dec_hs(?CLIENT_HELLO, <<?BYTE(Major), ?BYTE(Minor), Random:32/binary,
571
642
                       ?BYTE(SID_length), Session_ID:SID_length/binary,
572
643
                       ?UINT16(Cs_length), CipherSuites:Cs_length/binary,
573
 
                       ?BYTE(Cm_length), Comp_methods:Cm_length/binary>>,
 
644
                       ?BYTE(Cm_length), Comp_methods:Cm_length/binary,
 
645
                       _FutureCompatData/binary>>,
574
646
       _, _) ->
575
647
    #client_hello{
576
 
        client_version = #protocol_version{major = Major, minor = Minor},
 
648
        client_version = {Major,Minor},
577
649
        random = Random,
578
650
        session_id = Session_ID,
579
651
        cipher_suites = from_2bytes(CipherSuites),
580
 
        compression_methods = Comp_methods};
 
652
        compression_methods = Comp_methods
 
653
       };
581
654
dec_hs(?SERVER_HELLO, <<?BYTE(Major), ?BYTE(Minor), Random:32/binary,
582
655
                       ?BYTE(SID_length), Session_ID:SID_length/binary,
583
656
                       Cipher_suite:2/binary, ?BYTE(Comp_method)>>, _, _) ->
584
657
    #server_hello{
585
 
        server_version = #protocol_version{major = Major, minor = Minor},
 
658
        server_version = {Major,Minor},
586
659
        random = Random,
587
660
        session_id = Session_ID,
588
661
        cipher_suite = Cipher_suite,
589
 
        compression_method = Comp_method};
 
662
        compression_method = Comp_method
 
663
       };
590
664
dec_hs(?CERTIFICATE, <<?UINT24(ACLen), ASN1Certs:ACLen/binary>>, _, _) ->
591
665
    #certificate{asn1_certificates = certs_to_list(ASN1Certs)};
592
666
dec_hs(?SERVER_KEY_EXCHANGE, <<?UINT16(ModLen), Mod:ModLen/binary,
593
667
                              ?UINT16(ExpLen), Exp:ExpLen/binary,
594
668
                              Sig/binary>>,
595
 
       ?KEY_EXCHANGE_RSA, SigAlg) ->
596
 
    #server_key_exchange{
597
 
        params = #server_rsa_params{
598
 
          rsa_modulus = Mod,
599
 
          rsa_exponent = Exp},
600
 
        signed_params = dec_sig(SigAlg, Sig)};  % TODO: error checking
 
669
       ?KEY_EXCHANGE_RSA, _) ->
 
670
    #server_key_exchange{params = #server_rsa_params{rsa_modulus = Mod, 
 
671
                                                     rsa_exponent = Exp}, 
 
672
                         signed_params = Sig};  
601
673
dec_hs(?SERVER_KEY_EXCHANGE, <<?UINT16(PLen), P:PLen/binary,
602
674
                              ?UINT16(GLen), G:GLen/binary,
603
675
                              ?UINT16(YLen), Y:YLen/binary,
604
676
                              Sig/binary>>,
605
 
       ?KEY_EXCHANGE_DIFFIE_HELLMAN, SigAlg) ->
606
 
    #server_key_exchange{
607
 
        params = #server_dh_params{
608
 
          dh_p = P, dh_g = G, dh_y = Y},
609
 
        signed_params = dec_sig(SigAlg, Sig)};
 
677
       ?KEY_EXCHANGE_DIFFIE_HELLMAN, _) ->
 
678
    #server_key_exchange{params = #server_dh_params{dh_p = P,dh_g = G, dh_y = Y},
 
679
                         signed_params = Sig};
610
680
dec_hs(?CERTIFICATE_REQUEST,
611
681
       <<?BYTE(CertTypesLen), CertTypes:CertTypesLen/binary,
612
682
        ?UINT16(CertAuthsLen), CertAuths:CertAuthsLen/binary>>, _, _) ->
613
683
    %% TODO: maybe we should chop up CertAuths into a list?
614
 
    #certificate_request{
615
 
        certificate_types = CertTypes,
616
 
        certificate_authorities = CertAuths};
 
684
    #certificate_request{certificate_types = CertTypes,
 
685
                         certificate_authorities = CertAuths};
617
686
dec_hs(?SERVER_HELLO_DONE, <<>>, _, _) ->
618
687
    #server_hello_done{};
619
 
dec_hs(?CERTIFICATE_VERIFY, Sig, _, SigAlg)->
620
 
    dec_sig(Sig, SigAlg);
621
 
dec_hs(?CLIENT_KEY_EXCHANGE, PKEPMS, rsa, _) ->
622
 
    #client_key_exchange{
623
 
        exchange_keys = #encrypted_premaster_secret{
624
 
                            premaster_secret = PKEPMS}};
625
 
dec_hs(?CLIENT_KEY_EXCHANGE, <<>>, ?KEY_EXCHANGE_DIFFIE_HELLMAN, _) -> % TODO: Should check whether the cert already contains a suitable DH-key (7.4.7.2)
626
 
    implicit_public_value_encoding;
 
688
dec_hs(?CERTIFICATE_VERIFY,<<?UINT16(_), Signature/binary>>, _, _)->
 
689
    #certificate_verify{signature = Signature};
 
690
dec_hs(?CLIENT_KEY_EXCHANGE, PKEPMS, rsa, {3, 0}) ->
 
691
    PreSecret = #encrypted_premaster_secret{premaster_secret = PKEPMS},
 
692
    #client_key_exchange{exchange_keys = PreSecret};
 
693
dec_hs(?CLIENT_KEY_EXCHANGE, <<?UINT16(_), PKEPMS/binary>>, rsa, _) ->
 
694
    PreSecret = #encrypted_premaster_secret{premaster_secret = PKEPMS},
 
695
    #client_key_exchange{exchange_keys = PreSecret};
 
696
dec_hs(?CLIENT_KEY_EXCHANGE, <<>>, ?KEY_EXCHANGE_DIFFIE_HELLMAN, _) -> 
 
697
    %% TODO: Should check whether the cert already contains a suitable DH-key (7.4.7.2)
 
698
    throw(?ALERT_REC(?FATAL, implicit_public_value_encoding));
627
699
dec_hs(?CLIENT_KEY_EXCHANGE, <<?UINT16(DH_YCLen), DH_YC:DH_YCLen/binary>>,
628
700
       ?KEY_EXCHANGE_DIFFIE_HELLMAN, _) ->
629
 
    #client_diffie_hellman_public{
630
 
        dh_public = DH_YC};
631
 
 
632
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
633
 
%%% Certificate;
 
701
    #client_diffie_hellman_public{dh_public = DH_YC};
634
702
dec_hs(?FINISHED, VerifyData, _, _) ->
635
703
    #finished{verify_data = VerifyData};
636
 
 
637
 
dec_hs(Other, Data, _, _) ->
638
 
    #handshake{msg_type = Other,
639
 
               length = size(Data),
640
 
               body = Data}.
641
 
 
642
 
dec_sig(?SIGNATURE_ANONYMOUS, _) ->
643
 
    #signature{
644
 
         digitally_signed = #digitally_signed{
645
 
           md5_hash = <<>>,
646
 
           sha_hash = <<>>}};
647
 
dec_sig(?SIGNATURE_RSA, <<SHAHash:20/binary>>) ->
648
 
    #signature{
649
 
         digitally_signed = #digitally_signed{
650
 
           md5_hash = <<>>,
651
 
           sha_hash = SHAHash}};
652
 
dec_sig(?SIGNATURE_DSA, <<MD5Hash:16/binary, SHAHash:20/binary>>) ->
653
 
    #signature{
654
 
         digitally_signed = #digitally_signed{
655
 
           md5_hash = MD5Hash,
656
 
           sha_hash = SHAHash}}.
657
 
 
658
 
enc_sig(#signature{
659
 
         digitally_signed = #digitally_signed{
660
 
           md5_hash = M,
661
 
           sha_hash = S}}) ->
662
 
    <<M/binary, S/binary>>.
663
 
 
664
 
is_fixed_diffie_hellman(_, _) ->
665
 
    false.
666
 
 
667
 
encrypted_premaster_secret(Secret, PublicKey) ->
668
 
    %% format block before encrypting
669
 
    %% TODO check if SSL3 only?
670
 
    %% TODO lots of other checks
671
 
    Sz = size(crypto:mpint(PublicKey#'RSAPublicKey'.modulus)) - 4,
672
 
    Block = erlang:iolist_to_binary(ssl_cipher:format_encryption_block(Secret, Sz, 2)),
673
 
    %%<<_:32/integer, M/binary>> = crypto:mpint(PublicKey#'RSAPublicKey'.modulus),
674
 
    %%<<_:32/integer, E/binary>> = crypto:mpint(PublicKey#'RSAPublicKey'.publicExponent),
675
 
    PremasterSecret =
676
 
        ssl_cipher:rsa_encrypt(Block, PublicKey),
677
 
    #encrypted_premaster_secret{premaster_secret = PremasterSecret}.
678
 
 
679
 
decrypt_premaster_secret(Secret, Key) ->
680
 
    Block = ssl_cipher:rsa_decrypt(Secret,
681
 
                                   Key#'RSAPrivateKey'.modulus,
682
 
                                   Key#'RSAPrivateKey'.privateExponent),
683
 
    ssl_cipher:unformat_encryption_block(Block, 2).
684
 
 
 
704
dec_hs(_, _, _, _) ->
 
705
    throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE)).
 
706
 
 
707
encrypted_premaster_secret(Secret, RSAPublicKey) -> 
 
708
    try 
 
709
        PreMasterSecret = public_key:encrypt_public(Secret, RSAPublicKey, 
 
710
                                                    [{rsa_pad, 
 
711
                                                      rsa_pkcs1_padding}]),
 
712
        #encrypted_premaster_secret{premaster_secret = PreMasterSecret}
 
713
    catch
 
714
        _:_->
 
715
            throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE))
 
716
    end.
 
717
 
 
718
decrypt_premaster_secret(Secret, RSAPrivateKey) ->
 
719
    try public_key:decrypt_private(Secret, RSAPrivateKey,  
 
720
                                   [{rsa_pad, rsa_pkcs1_padding}]) of
 
721
        PreMasterSecret ->
 
722
            PreMasterSecret
 
723
    catch
 
724
        _:_ ->
 
725
            throw(?ALERT_REC(?FATAL, ?DECRYPTION_FAILED))
 
726
    end.
 
727
    
685
728
%% encode/decode stream of certificate data to/from list of certificate data 
686
729
certs_to_list(ASN1Certs) ->
687
730
    certs_to_list(ASN1Certs, []).
697
740
                        <<?UINT24(CertLen), Cert/binary>>
698
741
                    end || Cert <- ACList]).
699
742
 
700
 
enc_hs(#hello_request{}, _) ->
 
743
enc_hs(#hello_request{}, _Version, _) ->
701
744
    {?HELLO_REQUEST, <<>>};
702
745
enc_hs(#client_hello{
703
 
        client_version = #protocol_version{major = Major, minor = Minor},
 
746
        client_version = {Major, Minor},
704
747
        random = Random,
705
748
        session_id = SessionID,
706
749
        cipher_suites = CipherSuites,
707
 
        compression_methods = CompMethods}, _) ->
 
750
        compression_methods = CompMethods}, _Version, _) ->
708
751
    SIDLength = size(SessionID),
709
752
    BinCompMethods = list_to_binary(CompMethods),
710
753
    CmLength = size(BinCompMethods),
715
758
                     ?UINT16(CsLength), BinCipherSuites/binary,
716
759
                     ?BYTE(CmLength), BinCompMethods/binary>>};
717
760
enc_hs(#server_hello{
718
 
        server_version = #protocol_version{major = Major, minor = Minor},
 
761
        server_version = {Major, Minor},
719
762
        random = Random,
720
763
        session_id = Session_ID,
721
764
        cipher_suite = Cipher_suite,
722
 
        compression_method = Comp_method}, _) ->
 
765
        compression_method = Comp_method}, _Version, _) ->
723
766
    SID_length = size(Session_ID),
724
767
    {?SERVER_HELLO, <<?BYTE(Major), ?BYTE(Minor), Random:32/binary,
725
768
                     ?BYTE(SID_length), Session_ID/binary,
726
769
                     Cipher_suite/binary, ?BYTE(Comp_method)>>};
727
 
enc_hs(#certificate{asn1_certificates = ASN1CertList}, _) ->
 
770
enc_hs(#certificate{asn1_certificates = ASN1CertList}, _Version, _) ->
728
771
    ASN1Certs = certs_from_list(ASN1CertList),
729
772
    ACLen = erlang:iolist_size(ASN1Certs),
730
773
    {?CERTIFICATE, <<?UINT24(ACLen), ASN1Certs:ACLen/binary>>};
731
774
enc_hs(#server_key_exchange{params = #server_rsa_params{rsa_modulus = Mod,
732
775
                                                        rsa_exponent = Exp},
733
 
        signed_params = SignedParams}, _) ->
734
 
    EncSig = enc_sig(SignedParams),
 
776
        signed_params = SignedParams}, _Version, _) ->
735
777
    ModLen = size(Mod),
736
778
    ExpLen = size(Exp),
737
779
    {?SERVER_KEY_EXCHANGE, <<?UINT16(ModLen), Mod/binary,
738
780
                            ?UINT16(ExpLen), Exp/binary,
739
 
                            EncSig/binary>>};
 
781
                            SignedParams/binary>>
 
782
    };
740
783
enc_hs(#server_key_exchange{params = #server_dh_params{
741
784
                              dh_p = P, dh_g = G, dh_y = Y},
742
 
        signed_params = SignedParams}, _) ->
743
 
    EncSig = enc_sig(SignedParams),
 
785
        signed_params = SignedParams}, _Version, _) ->
744
786
    PLen = size(P),
745
787
    GLen = size(G),
746
788
    YLen = size(Y),
747
789
    {?SERVER_KEY_EXCHANGE, <<?UINT16(PLen), P:PLen/binary,
748
790
                            ?UINT16(GLen), G:GLen/binary,
749
791
                            ?UINT16(YLen), Y:YLen/binary,
750
 
                            EncSig/binary>>};
 
792
                            SignedParams/binary>>
 
793
    };
751
794
enc_hs(#certificate_request{certificate_types = CertTypes,
752
 
                            certificate_authorities = CertAuths}, _) ->
 
795
                            certificate_authorities = CertAuths}, 
 
796
       _Version, _) ->
753
797
    CertTypesLen = size(CertTypes),
754
798
    CertAuthsLen = size(CertAuths),
755
799
    {?CERTIFICATE_REQUEST,
756
800
       <<?BYTE(CertTypesLen), CertTypes/binary,
757
 
        ?UINT16(CertAuthsLen), CertAuths/binary>>};
758
 
enc_hs(#server_hello_done{}, _) ->
 
801
        ?UINT16(CertAuthsLen), CertAuths/binary>>
 
802
    };
 
803
enc_hs(#server_hello_done{}, _Version, _) ->
759
804
    {?SERVER_HELLO_DONE, <<>>};
760
 
enc_hs(#client_key_exchange{exchange_keys = ExchangeKeys}, _) ->
761
 
    {?CLIENT_KEY_EXCHANGE, enc_cke(ExchangeKeys)};
762
 
enc_hs(#certificate_verify{signature = BinSig0}, SigAlg) ->
763
 
    BinSig = enc_bin_sig(SigAlg, BinSig0),
764
 
    {?CERTIFICATE_VERIFY, BinSig};
765
 
enc_hs(#finished{verify_data = VerifyData}, _) ->
 
805
enc_hs(#client_key_exchange{exchange_keys = ExchangeKeys}, Version, _) ->
 
806
    {?CLIENT_KEY_EXCHANGE, enc_cke(ExchangeKeys, Version)};
 
807
enc_hs(#certificate_verify{signature = BinSig}, _, _) ->
 
808
    EncSig = enc_bin_sig(BinSig),
 
809
    {?CERTIFICATE_VERIFY, EncSig};
 
810
enc_hs(#finished{verify_data = VerifyData}, _Version, _) ->
766
811
    {?FINISHED, VerifyData}.
767
812
 
768
 
enc_cke(#encrypted_premaster_secret{premaster_secret = PKEPMS}) ->
769
 
    PKEPMS.
770
 
%%    PKEPMSLen = size(PKEPMS),
771
 
%%    <<?UINT16(PKEPMSLen), PKEPMS/binary>>.
 
813
enc_cke(#encrypted_premaster_secret{premaster_secret = PKEPMS},{3, 0}) ->
 
814
    PKEPMS;
 
815
enc_cke(#encrypted_premaster_secret{premaster_secret = PKEPMS}, _) ->
 
816
    PKEPMSLen = size(PKEPMS),
 
817
    <<?UINT16(PKEPMSLen), PKEPMS/binary>>;
 
818
enc_cke(#client_diffie_hellman_public{dh_public = DHPublic}, _) ->
 
819
    Len = size(DHPublic),
 
820
    <<?UINT16(Len), DHPublic/binary>>.
772
821
 
773
 
enc_bin_sig(?SIGNATURE_ANONYMOUS, _) ->
774
 
    <<>>;
775
 
enc_bin_sig(_, H) ->
776
 
    Sz = size(H),
777
 
    <<?UINT16(Sz), H/binary>>.
 
822
enc_bin_sig(BinSig) ->
 
823
    Size = size(BinSig),
 
824
    <<?UINT16(Size), BinSig/binary>>.
778
825
 
779
826
init_hashes() ->
780
827
    T = {crypto:md5_init(), crypto:sha_init()},
781
828
    {T, T}.
782
829
 
783
 
%%first_byte(I) when is_integer(I) -> I;
784
 
%%first_byte([F | _])  -> first_byte(F);
785
 
%%first_byte(<<?BYTE(B), _/binary>>) -> B.
786
 
        
787
 
update_hashes(Hashes, % we special-case SSL2 client hello
788
 
              [<<?CLIENT_HELLO, ?UINT24(_), ?BYTE(Major), ?BYTE(Minor),
789
 
                       ?UINT16(CSLength), ?UINT16(0),
790
 
                       ?UINT16(CDLength), 
791
 
                       CipherSuites:CSLength/binary, 
792
 
                       ChallengeData:CDLength/binary>>]) ->
 
830
update_hashes(Hashes, % special-case SSL2 client hello
 
831
              <<?CLIENT_HELLO, ?UINT24(_), ?BYTE(Major), ?BYTE(Minor),
 
832
               ?UINT16(CSLength), ?UINT16(0),
 
833
               ?UINT16(CDLength), 
 
834
               CipherSuites:CSLength/binary, 
 
835
               ChallengeData:CDLength/binary>>) ->
793
836
    update_hashes(Hashes,
794
837
                  <<?CLIENT_HELLO, ?BYTE(Major), ?BYTE(Minor),
795
838
                   ?UINT16(CSLength), ?UINT16(0),
819
862
    lists:reverse(Acc);
820
863
from_2bytes(<<?UINT16(N), Rest/binary>>, Acc) ->
821
864
    from_2bytes(Rest, [?uint16(N) | Acc]).
 
865
 
 
866
certificate_types({KeyExchange, _, _, _})  
 
867
  when KeyExchange == rsa;
 
868
       KeyExchange == dh_dss;
 
869
       KeyExchange == dh_rsa;
 
870
       KeyExchange == dhe_dss;
 
871
       KeyExchange == dhe_rsa ->
 
872
    <<?BYTE(?RSA_SIGN), ?BYTE(?DSS_SIGN)>>;
 
873
 
 
874
certificate_types(_) ->
 
875
    %%TODO: Is this a good default,
 
876
    %% is there a case where we like to request
 
877
    %% a RSA_FIXED_DH or DSS_FIXED_DH
 
878
    <<?BYTE(?RSA_SIGN)>>.
 
879
 
 
880
certificate_authorities(_) ->
 
881
    %%TODO Make list of know CA:s
 
882
    <<>>.
 
883
 
 
884
digitally_signed(Hashes, #'RSAPrivateKey'{} = Key) ->
 
885
    public_key:encrypt_private(Hashes, Key,
 
886
                               [{rsa_pad, rsa_pkcs1_padding}]);
 
887
digitally_signed(Hashes, #'DSAPrivateKey'{} = Key) ->
 
888
    public_key:sign(Hashes, Key).
 
889
 
 
890
 
 
891
calc_master_secret({3,0}, PremasterSecret, ClientRandom, ServerRandom) ->
 
892
    ssl_ssl3:master_secret(PremasterSecret, ClientRandom, ServerRandom);
 
893
 
 
894
calc_master_secret({3,N},PremasterSecret, ClientRandom, ServerRandom) 
 
895
  when N == 1; N == 2 ->
 
896
    ssl_tls1:master_secret(PremasterSecret, ClientRandom, ServerRandom).
 
897
 
 
898
setup_keys({3,0}, Exportable, MasterSecret,
 
899
           ServerRandom, ClientRandom, HashSize, KML, EKML, IVS) ->
 
900
    ssl_ssl3:setup_keys(Exportable, MasterSecret, ServerRandom, 
 
901
                        ClientRandom, HashSize, KML, EKML, IVS);
 
902
 
 
903
setup_keys({3,1}, _Exportable, MasterSecret,
 
904
           ServerRandom, ClientRandom, HashSize, KML, _EKML, IVS) ->
 
905
    ssl_tls1:setup_keys(MasterSecret, ServerRandom, ClientRandom, HashSize, 
 
906
                        KML, IVS);
 
907
 
 
908
setup_keys({3,2}, _Exportable, MasterSecret,
 
909
           ServerRandom, ClientRandom, HashSize, KML, _EKML, _IVS) ->
 
910
    ssl_tls1:setup_keys(MasterSecret, ServerRandom, 
 
911
                        ClientRandom, HashSize, KML).
 
912
 
 
913
calc_finished({3, 0}, Role, MasterSecret, Hashes) ->
 
914
    ssl_ssl3:finished(Role, MasterSecret, Hashes);
 
915
calc_finished({3, N}, Role, MasterSecret, Hashes) 
 
916
  when  N == 1; N == 2 ->
 
917
    ssl_tls1:finished(Role, MasterSecret, Hashes).
 
918
 
 
919
calc_certificate_verify({3, 0}, MasterSecret, Algorithm, Hashes) ->
 
920
    ssl_ssl3:certificate_verify(Algorithm, MasterSecret, Hashes);
 
921
calc_certificate_verify({3, N}, _, Algorithm, Hashes) 
 
922
  when  N == 1; N == 2 ->
 
923
    ssl_tls1:certificate_verify(Algorithm, Hashes).
 
924
 
 
925
%% server_key_exchange_hash(Algorithm, Value) when Algorithm == rsa;
 
926
%%                                              Algorithm == dh_rsa;
 
927
%%                                              Algorithm == dhe_rsa ->
 
928
%%     MD5 = crypto:md5_final(Value),
 
929
%%     SHA =  crypto:sha_final(Value),
 
930
%%     <<MD5/binary, SHA/binary>>;
 
931
 
 
932
%% server_key_exchange_hash(Algorithm, Value) when Algorithm == dh_dss;
 
933
%%                                         Algorithm == dhe_dss ->
 
934
%%     crypto:sha_final(Value).