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

« back to all changes in this revision

Viewing changes to lib/ssl/src/ssl_handshake.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
 
28
28
-include("ssl_cipher.hrl").
29
29
-include("ssl_alert.hrl").
30
30
-include("ssl_internal.hrl").
31
 
-include("ssl_debug.hrl").
32
31
-include_lib("public_key/include/public_key.hrl").
33
32
 
34
 
-export([master_secret/4, client_hello/4, server_hello/3, hello/2, 
35
 
         certify/5, certificate/3, 
36
 
         client_certificate_verify/6, 
37
 
         certificate_verify/6, certificate_request/2,
38
 
         key_exchange/2, finished/4,
39
 
         verify_connection/5, 
40
 
         get_tls_handshake/4,
41
 
         server_hello_done/0, sig_alg/1,
42
 
         encode_handshake/3, init_hashes/0, 
43
 
         update_hashes/2, decrypt_premaster_secret/2]).
 
33
-export([master_secret/4, client_hello/6, server_hello/4, hello/4,
 
34
         hello_request/0, certify/6, certificate/3,
 
35
         client_certificate_verify/5, certificate_verify/5,
 
36
         certificate_request/2, key_exchange/2, server_key_exchange_hash/2,
 
37
         finished/4, verify_connection/5, get_tls_handshake/2,
 
38
         decode_client_key/3, server_hello_done/0,
 
39
         encode_handshake/2, init_hashes/0, update_hashes/2,
 
40
         decrypt_premaster_secret/2]).
 
41
 
 
42
-type tls_handshake() :: #client_hello{} | #server_hello{} |
 
43
                         #server_hello_done{} | #certificate{} | #certificate_request{} |
 
44
                         #client_key_exchange{} | #finished{} | #certificate_verify{} |
 
45
                         #hello_request{}.
44
46
 
45
47
%%====================================================================
46
48
%% Internal application API
47
49
%%====================================================================
48
50
%%--------------------------------------------------------------------
49
 
%% Function: client_hello(Host, Port, ConnectionStates, SslOpts) -> 
50
 
%%                                                  #client_hello{} 
51
 
%%      Host
52
 
%%      Port
53
 
%%      ConnectionStates = #connection_states{}
54
 
%%      SslOpts = #ssl_options{}
 
51
-spec client_hello(host(), port_num(), #connection_states{},
 
52
                   #ssl_options{}, boolean(), der_cert()) -> #client_hello{}.
55
53
%%
56
54
%% Description: Creates a client hello message.
57
55
%%--------------------------------------------------------------------
58
56
client_hello(Host, Port, ConnectionStates, #ssl_options{versions = Versions,
59
 
                                                        ciphers = Ciphers} 
60
 
             = SslOpts) ->
 
57
                                                        ciphers = UserSuites} 
 
58
             = SslOpts, Renegotiation, OwnCert) ->
61
59
    
62
60
    Fun = fun(Version) ->
63
61
                  ssl_record:protocol_version(Version)
65
63
    Version = ssl_record:highest_protocol_version(lists:map(Fun, Versions)),
66
64
    Pending = ssl_record:pending_connection_state(ConnectionStates, read),
67
65
    SecParams = Pending#connection_state.security_parameters,
68
 
   
69
 
    Id = ssl_manager:client_session_id(Host, Port, SslOpts),
 
66
    Ciphers = available_suites(UserSuites, Version),
 
67
 
 
68
    Id = ssl_manager:client_session_id(Host, Port, SslOpts, OwnCert),
70
69
 
71
70
    #client_hello{session_id = Id, 
72
71
                  client_version = Version,
73
 
                  cipher_suites = Ciphers,
 
72
                  cipher_suites = cipher_suites(Ciphers, Renegotiation),
74
73
                  compression_methods = ssl_record:compressions(),
75
 
                  random = SecParams#security_parameters.client_random
 
74
                  random = SecParams#security_parameters.client_random,
 
75
                  renegotiation_info  = 
 
76
                  renegotiation_info(client, ConnectionStates, Renegotiation)
76
77
                 }.
77
78
 
78
79
%%--------------------------------------------------------------------
79
 
%% Function: server_hello(Host, Port, SessionId, 
80
 
%%                        Version, ConnectionStates) -> #server_hello{} 
81
 
%%      SessionId
82
 
%%      Version
83
 
%%      ConnectionStates 
84
 
%%      
 
80
-spec server_hello(session_id(), tls_version(), #connection_states{}, 
 
81
                   boolean()) -> #server_hello{}.
85
82
%%
86
83
%% Description: Creates a server hello message.
87
84
%%--------------------------------------------------------------------
88
 
server_hello(SessionId, Version, ConnectionStates) ->
 
85
server_hello(SessionId, Version, ConnectionStates, Renegotiation) ->
89
86
    Pending = ssl_record:pending_connection_state(ConnectionStates, read),
90
87
    SecParams = Pending#connection_state.security_parameters,
91
88
    #server_hello{server_version = Version,
93
90
                  compression_method = 
94
91
                  SecParams#security_parameters.compression_algorithm,
95
92
                  random = SecParams#security_parameters.server_random,
96
 
                  session_id = SessionId
 
93
                  session_id = SessionId,
 
94
                  renegotiation_info = 
 
95
                  renegotiation_info(server, ConnectionStates, Renegotiation)
97
96
                 }.
98
97
 
99
98
%%--------------------------------------------------------------------
100
 
%% Function: hello(Hello, Info) -> 
101
 
%%                                   {Version, Id, NewConnectionStates} |
102
 
%%                                   #alert{}
 
99
-spec hello_request() -> #hello_request{}.
103
100
%%
104
 
%%      Hello = #client_hello{} | #server_hello{}
105
 
%%      Info = ConnectionStates | {Port, Session, ConnectionStates}
106
 
%%      ConnectionStates = #connection_states{}
 
101
%% Description: Creates a hello request message sent by server to 
 
102
%% trigger renegotiation.
 
103
%%--------------------------------------------------------------------
 
104
hello_request() ->
 
105
    #hello_request{}.
 
106
 
 
107
%%--------------------------------------------------------------------
 
108
-spec hello(#server_hello{} | #client_hello{}, #ssl_options{},
 
109
            #connection_states{} | {port_num(), #session{}, cache_ref(),
 
110
                                    atom(), #connection_states{}, binary()},
 
111
            boolean()) -> {tls_version(), session_id(), #connection_states{}}| 
 
112
                          {tls_version(), {resumed | new, #session{}}, 
 
113
                           #connection_states{}} | #alert{}.
107
114
%%
108
115
%% Description: Handles a recieved hello message
109
116
%%--------------------------------------------------------------------
110
117
hello(#server_hello{cipher_suite = CipherSuite, server_version = Version,
111
118
                    compression_method = Compression, random = Random,
112
 
                    session_id = SessionId}, ConnectionStates) ->
113
 
    NewConnectionStates =
114
 
        hello_pending_connection_states(client, CipherSuite, Random, 
115
 
                                        Compression, ConnectionStates),
116
 
    {Version, SessionId, NewConnectionStates};
 
119
                    session_id = SessionId, renegotiation_info = Info},
 
120
      #ssl_options{secure_renegotiate = SecureRenegotation},
 
121
      ConnectionStates0, Renegotiation) ->
117
122
 
118
 
hello(#client_hello{client_version = ClientVersion, random = Random} = Hello,
119
 
      {Port, #ssl_options{versions = Versions} = SslOpts,
120
 
       Session0, Cache, CacheCb, ConnectionStates0}) ->
 
123
    case ssl_record:is_acceptable_version(Version) of
 
124
        true ->
 
125
            case handle_renegotiation_info(client, Info, ConnectionStates0, 
 
126
                                           Renegotiation, SecureRenegotation, []) of
 
127
                {ok, ConnectionStates1} ->
 
128
                    ConnectionStates =
 
129
                        hello_pending_connection_states(client, CipherSuite, Random, 
 
130
                                                        Compression, ConnectionStates1),
 
131
                    {Version, SessionId, ConnectionStates};
 
132
                #alert{} = Alert ->
 
133
                    Alert
 
134
            end;
 
135
        false ->
 
136
            ?ALERT_REC(?FATAL, ?PROTOCOL_VERSION)
 
137
    end;
 
138
                               
 
139
hello(#client_hello{client_version = ClientVersion, random = Random,
 
140
                    cipher_suites = CipherSuites,
 
141
                    renegotiation_info = Info} = Hello,
 
142
      #ssl_options{versions = Versions, 
 
143
                   secure_renegotiate = SecureRenegotation} = SslOpts,
 
144
      {Port, Session0, Cache, CacheCb, ConnectionStates0, Cert}, Renegotiation) ->
121
145
    Version = select_version(ClientVersion, Versions),
122
146
    case ssl_record:is_acceptable_version(Version) of
123
147
        true ->
124
148
            {Type, #session{cipher_suite = CipherSuite,
125
149
                            compression_method = Compression} = Session} 
126
150
                = select_session(Hello, Port, Session0, Version, 
127
 
                                 SslOpts, Cache, CacheCb),
 
151
                                 SslOpts, Cache, CacheCb, Cert),
128
152
            case CipherSuite of 
129
153
                no_suite ->
130
154
                    ?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY);
131
155
                _ ->
132
 
                    ConnectionStates =
133
 
                        hello_pending_connection_states(server, 
134
 
                                                        CipherSuite,
135
 
                                                        Random, 
136
 
                                                        Compression,
137
 
                                                        ConnectionStates0),
138
 
                    {Version, {Type, Session}, ConnectionStates}
 
156
                    case handle_renegotiation_info(server, Info, ConnectionStates0,
 
157
                                                   Renegotiation, SecureRenegotation, 
 
158
                                                   CipherSuites) of
 
159
                        {ok, ConnectionStates1} ->
 
160
                            ConnectionStates =
 
161
                                hello_pending_connection_states(server, 
 
162
                                                                CipherSuite,
 
163
                                                                Random, 
 
164
                                                                Compression,
 
165
                                                                ConnectionStates1),
 
166
                            {Version, {Type, Session}, ConnectionStates};
 
167
                        #alert{} = Alert ->
 
168
                            Alert
 
169
                    end
139
170
            end;
140
171
        false ->
141
172
            ?ALERT_REC(?FATAL, ?PROTOCOL_VERSION)
142
173
    end.
143
174
 
144
175
%%--------------------------------------------------------------------
145
 
%% Function: certify(Certs, CertDbRef, MaxPathLen) ->
146
 
%%                                 {PeerCert, PublicKeyInfo}  | #alert{}
147
 
%%
148
 
%%      Certs = #certificate{}
149
 
%%      CertDbRef = reference()
150
 
%%      MaxPathLen = integer() | nolimit
 
176
-spec certify(#certificate{}, term(), integer() | nolimit,
 
177
              verify_peer | verify_none, {fun(), term},
 
178
              client | server) ->  {der_cert(), public_key_info()} | #alert{}.
151
179
%%
152
180
%% Description: Handles a certificate handshake message
153
181
%%--------------------------------------------------------------------
154
 
certify(#certificate{asn1_certificates = ASN1Certs}, CertDbRef, 
155
 
        MaxPathLen, Verify, VerifyFun) -> 
 
182
certify(#certificate{asn1_certificates = ASN1Certs}, CertDbRef,
 
183
        MaxPathLen, _Verify, VerifyFunAndState, Role) ->
156
184
    [PeerCert | _] = ASN1Certs,
157
 
    VerifyBool =  verify_bool(Verify),
158
 
  
159
 
    try
160
 
        %% Allow missing root_cert and check that with VerifyFun
161
 
        ssl_certificate:trusted_cert_and_path(ASN1Certs, CertDbRef, false) of
162
 
        {TrustedErlCert, CertPath, VerifyErrors} ->
163
 
            Result = public_key:pkix_path_validation(TrustedErlCert, 
164
 
                                                     CertPath, 
165
 
                                                     [{max_path_length, 
166
 
                                                       MaxPathLen},
167
 
                                                      {verify, VerifyBool},
168
 
                                                      {acc_errors, 
169
 
                                                       VerifyErrors}]),
170
 
            case Result of
171
 
                {error, Reason} ->
172
 
                    path_validation_alert(Reason, Verify);
173
 
                {ok, {PublicKeyInfo,_, []}} ->
174
 
                    {PeerCert, PublicKeyInfo};
175
 
                {ok, {PublicKeyInfo,_, AccErrors = [Error | _]}} ->
176
 
                    case VerifyFun(AccErrors) of
177
 
                        true ->
178
 
                            {PeerCert, PublicKeyInfo};
179
 
                        false ->
180
 
                            path_validation_alert(Error, Verify)
181
 
                    end
182
 
            end
183
 
    catch 
184
 
        throw:Alert ->
185
 
            Alert
 
185
      
 
186
    ValidationFunAndState =
 
187
        case VerifyFunAndState of
 
188
            undefined ->
 
189
                {fun(OtpCert, ExtensionOrError, SslState) ->
 
190
                         ssl_certificate:validate_extension(OtpCert,
 
191
                                                            ExtensionOrError, SslState)
 
192
                 end, Role};
 
193
            {Fun, UserState0} ->
 
194
                {fun(OtpCert, ExtensionOrError, {SslState, UserState}) ->
 
195
                         case ssl_certificate:validate_extension(OtpCert,
 
196
                                                                 ExtensionOrError,
 
197
                                                                 SslState) of
 
198
                             {valid, NewSslState} ->
 
199
                                 {valid, {NewSslState, UserState}};
 
200
                             {fail, Reason} ->
 
201
                                 apply_user_fun(Fun, OtpCert, Reason, UserState,
 
202
                                                SslState);
 
203
                             {unknown, _} ->
 
204
                                 apply_user_fun(Fun, OtpCert,
 
205
                                                ExtensionOrError, UserState, SslState)
 
206
                         end
 
207
                 end, {Role, UserState0}}
 
208
        end,
 
209
 
 
210
    {TrustedErlCert, CertPath}  =
 
211
        ssl_certificate:trusted_cert_and_path(ASN1Certs, CertDbRef),
 
212
 
 
213
    case public_key:pkix_path_validation(TrustedErlCert,
 
214
                                         CertPath,
 
215
                                         [{max_path_length,
 
216
                                           MaxPathLen},
 
217
                                          {verify_fun, ValidationFunAndState}]) of
 
218
        {ok, {PublicKeyInfo,_}} ->
 
219
            {PeerCert, PublicKeyInfo};
 
220
        {error, Reason} ->
 
221
            path_validation_alert(Reason)
186
222
    end.
187
 
            
 
223
 
188
224
%%--------------------------------------------------------------------
189
 
%% Function: certificate(OwnCert, CertDbRef, Role) -> #certificate{}
190
 
%%
191
 
%%      OwnCert = binary()
192
 
%%      CertDbRef = term() as returned by ssl_certificate_db:create()
 
225
-spec certificate(der_cert(), term(), client | server) -> #certificate{} | #alert{}. 
193
226
%%
194
227
%% Description: Creates a certificate message.
195
228
%%--------------------------------------------------------------------
201
234
            {error, _} -> 
202
235
                %% If no suitable certificate is available, the client
203
236
                %% SHOULD send a certificate message containing no
204
 
                %% certificates. (chapter 7.4.6. rfc 4346) 
 
237
                %% certificates. (chapter 7.4.6. RFC 4346)
205
238
                []       
206
239
        end,
207
240
    #certificate{asn1_certificates = Chain};
215
248
    end.
216
249
 
217
250
%%--------------------------------------------------------------------
218
 
%% Function: client_certificate_verify(Cert, ConnectionStates) -> 
219
 
%%                                          #certificate_verify{} | ignore
220
 
%% Cert             = #'OTPcertificate'{}
221
 
%% ConnectionStates = #connection_states{}
 
251
-spec client_certificate_verify(undefined | der_cert(), binary(),
 
252
                                tls_version(), private_key(),
 
253
                                {{binary(), binary()},{binary(), binary()}}) ->  
 
254
    #certificate_verify{} | ignore | #alert{}.
222
255
%%
223
256
%% Description: Creates a certificate_verify message, called by the client.
224
257
%%--------------------------------------------------------------------
225
 
client_certificate_verify(undefined, _, _, _, _, _) ->
226
 
    ignore;
227
 
client_certificate_verify(_, _, _, _, undefined, _) ->
228
 
    ignore;
229
 
client_certificate_verify(OwnCert, MasterSecret, Version, Algorithm,
 
258
client_certificate_verify(undefined, _, _, _, _) ->
 
259
    ignore;
 
260
client_certificate_verify(_, _, _, undefined, _) ->
 
261
    ignore;
 
262
client_certificate_verify(OwnCert, MasterSecret, Version,
230
263
                          PrivateKey, {Hashes0, _}) ->
231
264
    case public_key:pkix_is_fixed_dh_cert(OwnCert) of
232
265
        true ->
233
 
            ignore;
 
266
            ?ALERT_REC(?FATAL, ?UNSUPPORTED_CERTIFICATE);
234
267
        false ->            
235
268
            Hashes = 
236
269
                calc_certificate_verify(Version, MasterSecret,
237
 
                                        Algorithm, Hashes0), 
 
270
                                        alg_oid(PrivateKey), Hashes0),
238
271
            Signed = digitally_signed(Hashes, PrivateKey),
239
272
            #certificate_verify{signature = Signed}
240
273
    end.
241
274
 
242
275
%%--------------------------------------------------------------------
243
 
%% Function: certificate_verify(Signature, PublicKeyInfo) -> valid | #alert{}
244
 
%%
245
 
%% Signature     = binary()
246
 
%% PublicKeyInfo = {Algorithm, PublicKey, PublicKeyParams}
 
276
-spec certificate_verify(binary(), public_key_info(), tls_version(),
 
277
                         binary(), {_, {binary(), binary()}}) -> valid | #alert{}.
247
278
%%
248
279
%% Description: Checks that the certificate_verify message is valid.
249
280
%%--------------------------------------------------------------------
250
 
certificate_verify(Signature, {_, PublicKey, _}, Version, 
251
 
                   MasterSecret, Algorithm, {_, Hashes0})
252
 
  when Algorithm =:= rsa; Algorithm =:= dh_rsa; Algorithm =:= dhe_rsa ->
 
281
certificate_verify(Signature, {?'rsaEncryption'= Algorithm, PublicKey, _}, Version,
 
282
                   MasterSecret, {_, Hashes0}) ->
253
283
    Hashes = calc_certificate_verify(Version, MasterSecret,
254
284
                                           Algorithm, Hashes0),
255
 
    case public_key:decrypt_public(Signature, PublicKey, 
 
285
    case public_key:decrypt_public(Signature, PublicKey,
256
286
                                   [{rsa_pad, rsa_pkcs1_padding}]) of
257
287
        Hashes ->
258
288
            valid;
259
289
        _ ->
260
290
            ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE)
 
291
    end;
 
292
certificate_verify(Signature, {?'id-dsa' = Algorithm, PublicKey, PublicKeyParams}, Version,
 
293
                   MasterSecret, {_, Hashes0}) ->
 
294
    Hashes = calc_certificate_verify(Version, MasterSecret,
 
295
                                     Algorithm, Hashes0),
 
296
    case public_key:verify(Hashes, none, Signature, {PublicKey, PublicKeyParams}) of
 
297
        true ->
 
298
            valid;
 
299
        false ->
 
300
            ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE)
261
301
    end.
262
 
%% TODO dsa clause
 
302
 
263
303
 
264
304
%%--------------------------------------------------------------------
265
 
%% Function: certificate_request(ConnectionStates, CertDbRef) -> 
266
 
%%                                                #certificate_request{}
 
305
-spec certificate_request(#connection_states{}, certdb_ref()) -> 
 
306
    #certificate_request{}.
267
307
%%
268
308
%% Description: Creates a certificate_request message, called by the server.
269
309
%%--------------------------------------------------------------------
279
319
                   }.
280
320
 
281
321
%%--------------------------------------------------------------------
282
 
%% Function: key_exchange(Role, Secret, Params) -> 
283
 
%%                         #client_key_exchange{} | #server_key_exchange{}
284
 
%%
285
 
%%      Secret -
286
 
%%      Params - 
 
322
-spec key_exchange(client | server, 
 
323
                   {premaster_secret, binary(), public_key_info()} |
 
324
                   {dh, binary()} |
 
325
                   {dh, {binary(), binary()}, #'DHParameter'{}, key_algo(),
 
326
                   binary(), binary(), private_key()}) ->
 
327
    #client_key_exchange{} | #server_key_exchange{}.
287
328
%%
288
329
%% Description: Creates a keyexchange message.
289
330
%%--------------------------------------------------------------------
291
332
    EncPremasterSecret =
292
333
        encrypted_premaster_secret(Secret, PublicKey),
293
334
    #client_key_exchange{exchange_keys = EncPremasterSecret};
294
 
key_exchange(client, fixed_diffie_hellman) -> 
295
 
    #client_key_exchange{exchange_keys = 
296
 
                         #client_diffie_hellman_public{
297
 
                           dh_public = <<>>
298
 
                          }};
299
 
key_exchange(client, {dh, PublicKey}) ->
300
 
    Len = byte_size(PublicKey), 
 
335
 
 
336
key_exchange(client, {dh, <<?UINT32(Len), PublicKey:Len/binary>>}) ->
301
337
    #client_key_exchange{
302
 
                exchange_keys = #client_diffie_hellman_public{
303
 
                  dh_public = <<?UINT16(Len), PublicKey/binary>>}
 
338
              exchange_keys = #client_diffie_hellman_public{
 
339
                dh_public = PublicKey}
304
340
               };
305
341
 
306
 
%% key_exchange(server, {{?'dhpublicnumber', _PublicKey, 
307
 
%%                     #'DomainParameters'{p = P, g = G, y = Y},
308
 
%%                     SignAlgorithm, ClientRandom, ServerRandom}})  ->
309
 
%%     ServerDHParams = #server_dh_params{dh_p = P, dh_g = G, dh_y = Y},
310
 
%%     PLen = byte_size(P),
311
 
%%     GLen = byte_size(G),
312
 
%%     YLen = byte_size(Y),
313
 
%%     Hash = server_key_exchange_hash(SignAlgorithm, <<ClientRandom/binary, 
314
 
%%                                                  ServerRandom/binary, 
315
 
%%                                                  ?UINT16(PLen), P/binary, 
316
 
%%                                                  ?UINT16(GLen), G/binary,
317
 
%%                                                  ?UINT16(YLen), Y/binary>>),
318
 
%%     Signed = digitally_signed(Hash, PrivateKey),
319
 
%%     #server_key_exchange{
320
 
%%                params = ServerDHParams,
321
 
%%                signed_params = Signed
322
 
%%               };
323
 
key_exchange(_, _) ->
324
 
    %%TODO : Real imp
325
 
    #server_key_exchange{}.
 
342
key_exchange(server, {dh, {<<?UINT32(Len), PublicKey:Len/binary>>, _}, 
 
343
                      #'DHParameter'{prime = P, base = G},
 
344
                      KeyAlgo, ClientRandom, ServerRandom, PrivateKey}) ->
 
345
    <<?UINT32(_), PBin/binary>> = crypto:mpint(P),
 
346
    <<?UINT32(_), GBin/binary>> = crypto:mpint(G),
 
347
    PLen = byte_size(PBin),
 
348
    GLen = byte_size(GBin),
 
349
    YLen = byte_size(PublicKey),
 
350
    ServerDHParams = #server_dh_params{dh_p = PBin, 
 
351
                                       dh_g = GBin, dh_y = PublicKey},    
 
352
 
 
353
    case KeyAlgo of
 
354
        dh_anon ->
 
355
            #server_key_exchange{params = ServerDHParams,
 
356
                                 signed_params = <<>>};
 
357
        _ ->
 
358
            Hash =
 
359
                server_key_exchange_hash(KeyAlgo, <<ClientRandom/binary,
 
360
                                                    ServerRandom/binary,
 
361
                                                    ?UINT16(PLen), PBin/binary,
 
362
                                                    ?UINT16(GLen), GBin/binary,
 
363
                                                    ?UINT16(YLen), PublicKey/binary>>),
 
364
            Signed = digitally_signed(Hash, PrivateKey),
 
365
            #server_key_exchange{params = ServerDHParams,
 
366
                                 signed_params = Signed}
 
367
    end.
326
368
 
327
369
%%--------------------------------------------------------------------
328
 
%% Function: master_secret(Version, Session/PremasterSecret, 
329
 
%%                         ConnectionStates, Role) -> 
330
 
%%                          {MasterSecret, NewConnectionStates} | #alert{}
331
 
%%      Version = #protocol_version{}
332
 
%%      Session = #session{} (session contains master secret)
333
 
%%      PremasterSecret = binary()  
334
 
%%      ConnectionStates = #connection_states{}
335
 
%%      Role = client | server
336
 
%%
 
370
-spec master_secret(tls_version(), #session{} | binary(), #connection_states{},
 
371
                   client | server) -> {binary(), #connection_states{}} | #alert{}.
 
372
%%    
337
373
%% Description: Sets or calculates the master secret and calculate keys,
338
374
%% updating the pending connection states. The Mastersecret and the update
339
375
%% connection states are returned or an alert if the calculation fails.
370
406
    end.
371
407
 
372
408
%%--------------------------------------------------------------------
373
 
%% Function: finished(Version, Role, MacSecret, Hashes) -> #finished{}
374
 
%%
375
 
%%      ConnectionStates = #connection_states{}
 
409
-spec finished(tls_version(), client | server, binary(), {{binary(), binary()},_}) ->
 
410
    #finished{}.
376
411
%%
377
412
%% Description: Creates a handshake finished message
378
413
%%-------------------------------------------------------------------
381
416
              calc_finished(Version, Role, MasterSecret, Hashes)}.
382
417
 
383
418
%%--------------------------------------------------------------------
384
 
%% Function: verify_connection(Finished, Role, 
385
 
%%                             MasterSecret, Hashes) -> verified | #alert{}
386
 
%% 
387
 
%% Finished = #finished{}
388
 
%% Role = client | server - the role of the process that sent the finished
389
 
%% message.
390
 
%% MasterSecret = binary()
391
 
%% Hashes = binary() -  {md5_hash, sha_hash} 
392
 
%%
 
419
-spec verify_connection(tls_version(), #finished{}, client | server, binary(), 
 
420
                        {_, {binary(), binary()}}) -> verified | #alert{}.
393
421
%%
394
422
%% Description: Checks the ssl handshake finished message to verify
395
423
%%              the connection.
397
425
verify_connection(Version, #finished{verify_data = Data}, 
398
426
                  Role, MasterSecret, {_, {MD5, SHA}}) -> 
399
427
    %% use the previous hashes
400
 
    ?DBG_HEX(crypto:md5_final(MD5)),
401
 
    ?DBG_HEX(crypto:sha_final(SHA)),
402
428
    case calc_finished(Version, Role, MasterSecret, {MD5, SHA}) of
403
429
        Data ->
404
430
            verified;
405
 
        _E ->
406
 
            ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE)
 
431
        _ ->
 
432
            ?ALERT_REC(?FATAL, ?DECRYPT_ERROR)
407
433
    end.
408
 
            
 
434
%%--------------------------------------------------------------------
 
435
-spec server_hello_done() ->  #server_hello_done{}.
 
436
%%     
 
437
%% Description: Creates a server hello done message.
 
438
%%--------------------------------------------------------------------      
409
439
server_hello_done() ->
410
440
    #server_hello_done{}.
411
441
 
412
442
%%--------------------------------------------------------------------
413
 
%% Function: encode_handshake(HandshakeRec) -> BinHandshake
414
 
%% HandshakeRec = #client_hello | #server_hello{} | server_hello_done |
415
 
%%              #certificate{} | #client_key_exchange{} | #finished{} |
416
 
%%              #client_certify_request{}
 
443
-spec encode_handshake(tls_handshake(), tls_version()) -> iolist().
417
444
%%     
418
 
%% encode a handshake packet to binary
 
445
%% Description: Encode a handshake packet to binary
419
446
%%--------------------------------------------------------------------
420
 
encode_handshake(Package, Version, SigAlg) ->
421
 
    {MsgType, Bin} = enc_hs(Package, Version, SigAlg),
 
447
encode_handshake(Package, Version) ->
 
448
    {MsgType, Bin} = enc_hs(Package, Version),
422
449
    Len = byte_size(Bin),
423
450
    [MsgType, ?uint24(Len), Bin].
424
451
 
425
452
%%--------------------------------------------------------------------
426
 
%% Function: get_tls_handshake(Data, Buffer) -> Result
427
 
%%      Result = {[#handshake{}], [Raw], NewBuffer}
428
 
%%      Data = Buffer = NewBuffer = Raw = binary()
 
453
-spec get_tls_handshake(binary(), binary() | iolist()) ->
 
454
     {[tls_handshake()], binary()}.
429
455
%%
430
456
%% Description: Given buffered and new data from ssl_record, collects
431
 
%% and returns it as a list of #handshake, also returns leftover
 
457
%% and returns it as a list of handshake messages, also returns leftover
432
458
%% data.
433
459
%%--------------------------------------------------------------------
434
 
get_tls_handshake(Data, <<>>, KeyAlg, Version) ->
435
 
    get_tls_handshake_aux(Data, KeyAlg, Version, []);
436
 
get_tls_handshake(Data, Buffer, KeyAlg, Version) ->
437
 
    get_tls_handshake_aux(list_to_binary([Buffer, Data]), 
438
 
                          KeyAlg, Version, []).
439
 
 
440
 
get_tls_handshake_aux(<<?BYTE(Type), ?UINT24(Length), Body:Length/binary,Rest/binary>>, 
441
 
                      KeyAlg, Version, Acc) ->
 
460
get_tls_handshake(Data, <<>>) ->
 
461
    get_tls_handshake_aux(Data, []);
 
462
get_tls_handshake(Data, Buffer) ->
 
463
    get_tls_handshake_aux(list_to_binary([Buffer, Data]), []).
 
464
 
 
465
%%--------------------------------------------------------------------
 
466
-spec decode_client_key(binary(), key_algo(), tls_version()) ->
 
467
                            #encrypted_premaster_secret{} | #client_diffie_hellman_public{}.
 
468
%%
 
469
%% Description: Decode client_key data and return appropriate type
 
470
%%--------------------------------------------------------------------
 
471
decode_client_key(ClientKey, Type, Version) ->
 
472
    dec_client_key(ClientKey, key_exchange_alg(Type), Version).
 
473
 
 
474
%%--------------------------------------------------------------------
 
475
-spec init_hashes() ->{{binary(), binary()}, {binary(), binary()}}.
 
476
 
 
477
%%
 
478
%% Description: Calls crypto hash (md5 and sha) init functions to
 
479
%% initalize the hash context.
 
480
%%--------------------------------------------------------------------
 
481
init_hashes() ->
 
482
    T = {crypto:md5_init(), crypto:sha_init()},
 
483
    {T, T}.
 
484
 
 
485
%%--------------------------------------------------------------------
 
486
-spec update_hashes({{binary(), binary()}, {binary(), binary()}}, Data ::term()) ->
 
487
                           {{binary(), binary()}, {binary(), binary()}}.
 
488
%%
 
489
%% Description: Calls crypto hash (md5 and sha) update functions to
 
490
%% update the hash context with Data.
 
491
%%--------------------------------------------------------------------
 
492
update_hashes(Hashes, % special-case SSL2 client hello
 
493
              <<?CLIENT_HELLO, ?UINT24(_), ?BYTE(Major), ?BYTE(Minor),
 
494
                ?UINT16(CSLength), ?UINT16(0),
 
495
                ?UINT16(CDLength),
 
496
               CipherSuites:CSLength/binary,
 
497
               ChallengeData:CDLength/binary>>) ->
 
498
    update_hashes(Hashes,
 
499
                  <<?CLIENT_HELLO, ?BYTE(Major), ?BYTE(Minor),
 
500
                   ?UINT16(CSLength), ?UINT16(0),
 
501
                   ?UINT16(CDLength),
 
502
                   CipherSuites:CSLength/binary,
 
503
                   ChallengeData:CDLength/binary>>);
 
504
update_hashes({{MD50, SHA0}, _Prev}, Data) ->
 
505
    {MD51, SHA1} = {crypto:md5_update(MD50, Data),
 
506
                    crypto:sha_update(SHA0, Data)},
 
507
    {{MD51, SHA1}, {MD50, SHA0}}.
 
508
 
 
509
%%--------------------------------------------------------------------
 
510
-spec decrypt_premaster_secret(binary(), #'RSAPrivateKey'{}) -> binary().
 
511
 
 
512
%%
 
513
%% Description: Public key decryption using the private key.
 
514
%%--------------------------------------------------------------------
 
515
decrypt_premaster_secret(Secret, RSAPrivateKey) ->
 
516
    try public_key:decrypt_private(Secret, RSAPrivateKey,
 
517
                                   [{rsa_pad, rsa_pkcs1_padding}])
 
518
    catch
 
519
        _:_ ->
 
520
            throw(?ALERT_REC(?FATAL, ?DECRYPT_ERROR))
 
521
    end.
 
522
 
 
523
%%--------------------------------------------------------------------
 
524
-spec server_key_exchange_hash(rsa | dhe_rsa| dhe_dss | dh_anon, binary()) -> binary().
 
525
 
 
526
%%
 
527
%% Description: Calculate server key exchange hash
 
528
%%--------------------------------------------------------------------
 
529
server_key_exchange_hash(Algorithm, Value) when Algorithm == rsa;
 
530
                                                Algorithm == dhe_rsa ->
 
531
    MD5 = crypto:md5(Value),
 
532
    SHA =  crypto:sha(Value),
 
533
    <<MD5/binary, SHA/binary>>;
 
534
 
 
535
server_key_exchange_hash(dhe_dss, Value) ->
 
536
    crypto:sha(Value).
 
537
 
 
538
%%--------------------------------------------------------------------
 
539
%%% Internal functions
 
540
%%--------------------------------------------------------------------
 
541
get_tls_handshake_aux(<<?BYTE(Type), ?UINT24(Length), 
 
542
                        Body:Length/binary,Rest/binary>>, Acc) ->
442
543
    Raw = <<?BYTE(Type), ?UINT24(Length), Body/binary>>,
443
 
    H = dec_hs(Type, Body, KeyAlg, Version),
444
 
    get_tls_handshake_aux(Rest, KeyAlg, Version, [{H,Raw} | Acc]);
445
 
get_tls_handshake_aux(Data, _KeyAlg, _Version, Acc) ->
 
544
    H = dec_hs(Type, Body),
 
545
    get_tls_handshake_aux(Rest, [{H,Raw} | Acc]);
 
546
get_tls_handshake_aux(Data, Acc) ->
446
547
    {lists:reverse(Acc), Data}.
447
548
 
448
 
%%--------------------------------------------------------------------
449
 
%% Function: sig_alg(atom()) -> integer()
450
 
%%
451
 
%% Description: Convert from key exchange as atom to signature
452
 
%% algorithm as a ?SIGNATURE_... constant
453
 
%%--------------------------------------------------------------------
454
 
 
455
 
sig_alg(dh_anon) ->
456
 
    ?SIGNATURE_ANONYMOUS;
457
 
sig_alg(Alg) when Alg == dhe_rsa; Alg == rsa; Alg == dh_rsa ->
458
 
    ?SIGNATURE_RSA;
459
 
sig_alg(Alg) when Alg == dh_dss; Alg == dhe_dss ->
460
 
    ?SIGNATURE_DSA;
461
 
sig_alg(_) ->
462
 
    ?NULL.
463
 
 
464
 
 
465
 
%%--------------------------------------------------------------------
466
 
%%% Internal functions
467
 
%%--------------------------------------------------------------------
468
 
verify_bool(verify_peer) ->
469
 
    true;
470
 
verify_bool(verify_none) ->
471
 
    false.
472
 
 
473
 
path_validation_alert({bad_cert, cert_expired}, _) ->
 
549
path_validation_alert({bad_cert, cert_expired}) ->
474
550
    ?ALERT_REC(?FATAL, ?CERTIFICATE_EXPIRED);
475
 
path_validation_alert({bad_cert, invalid_issuer}, _) ->
476
 
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
477
 
path_validation_alert({bad_cert, invalid_signature} , _) ->
478
 
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
479
 
path_validation_alert({bad_cert, name_not_permitted}, _) ->
480
 
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
481
 
path_validation_alert({bad_cert, unknown_critical_extension}, _) ->
 
551
path_validation_alert({bad_cert, invalid_issuer}) ->
 
552
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
 
553
path_validation_alert({bad_cert, invalid_signature}) ->
 
554
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
 
555
path_validation_alert({bad_cert, name_not_permitted}) ->
 
556
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
 
557
path_validation_alert({bad_cert, unknown_critical_extension}) ->
482
558
    ?ALERT_REC(?FATAL, ?UNSUPPORTED_CERTIFICATE);
483
 
path_validation_alert({bad_cert, cert_revoked}, _) ->
 
559
path_validation_alert({bad_cert, cert_revoked}) ->
484
560
    ?ALERT_REC(?FATAL, ?CERTIFICATE_REVOKED);
485
 
path_validation_alert(_, _) ->
 
561
path_validation_alert({bad_cert, selfsigned_peer}) ->
 
562
    ?ALERT_REC(?FATAL, ?BAD_CERTIFICATE);
 
563
path_validation_alert({bad_cert, unknown_ca}) ->
 
564
     ?ALERT_REC(?FATAL, ?UNKNOWN_CA);
 
565
path_validation_alert(_) ->
486
566
    ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE).
487
567
 
488
568
select_session(Hello, Port, Session, Version, 
489
 
               #ssl_options{ciphers = UserSuites} = SslOpts, Cache, CacheCb) ->
 
569
               #ssl_options{ciphers = UserSuites} = SslOpts, Cache, CacheCb, Cert) ->
490
570
    SuggestedSessionId = Hello#client_hello.session_id,
491
571
    SessionId = ssl_manager:server_session_id(Port, SuggestedSessionId, 
492
 
                                              SslOpts),
 
572
                                              SslOpts, Cert),
493
573
    
494
 
    Suites = case UserSuites of
495
 
                 [] ->
496
 
                     ssl_cipher:suites(Version);
497
 
                 _ ->
498
 
                   UserSuites
499
 
             end,
500
 
 
 
574
    Suites = available_suites(Cert, UserSuites, Version), 
501
575
    case ssl_session:is_new(SuggestedSessionId, SessionId) of
502
576
        true ->
503
577
            CipherSuite = 
510
584
        false ->            
511
585
            {resumed, CacheCb:lookup(Cache, {Port, SessionId})}
512
586
    end.
513
 
            
 
587
 
 
588
available_suites(UserSuites, Version) ->
 
589
    case UserSuites of
 
590
        [] ->
 
591
            ssl_cipher:suites(Version);
 
592
        _ ->
 
593
            UserSuites
 
594
    end.
 
595
 
 
596
available_suites(ServerCert, UserSuites, Version) ->
 
597
    ssl_cipher:filter(ServerCert, available_suites(UserSuites, Version)).
 
598
 
 
599
cipher_suites(Suites, false) ->
 
600
    [?TLS_EMPTY_RENEGOTIATION_INFO_SCSV | Suites];
 
601
cipher_suites(Suites, true) ->
 
602
    Suites.
 
603
 
 
604
renegotiation_info(client, _, false) ->
 
605
    #renegotiation_info{renegotiated_connection = undefined};
 
606
renegotiation_info(server, ConnectionStates, false) ->
 
607
    CS  = ssl_record:current_connection_state(ConnectionStates, read),
 
608
    case CS#connection_state.secure_renegotiation of
 
609
        true ->
 
610
            #renegotiation_info{renegotiated_connection = ?byte(0)};
 
611
        false ->
 
612
            #renegotiation_info{renegotiated_connection = undefined}
 
613
    end;
 
614
renegotiation_info(client, ConnectionStates, true) ->
 
615
    CS = ssl_record:current_connection_state(ConnectionStates, read),
 
616
    case CS#connection_state.secure_renegotiation of
 
617
        true ->
 
618
            Data = CS#connection_state.client_verify_data,
 
619
            #renegotiation_info{renegotiated_connection = Data};
 
620
        false ->
 
621
            #renegotiation_info{renegotiated_connection = undefined}
 
622
    end;
 
623
 
 
624
renegotiation_info(server, ConnectionStates, true) ->
 
625
    CS = ssl_record:current_connection_state(ConnectionStates, read),
 
626
    case CS#connection_state.secure_renegotiation of
 
627
        true ->
 
628
            CData = CS#connection_state.client_verify_data,
 
629
            SData  =CS#connection_state.server_verify_data,
 
630
            #renegotiation_info{renegotiated_connection = <<CData/binary, SData/binary>>};
 
631
        false ->
 
632
            #renegotiation_info{renegotiated_connection = undefined}
 
633
    end. 
 
634
 
 
635
handle_renegotiation_info(_, #renegotiation_info{renegotiated_connection = ?byte(0)}, 
 
636
                          ConnectionStates, false, _, _) ->
 
637
    {ok, ssl_record:set_renegotiation_flag(true, ConnectionStates)};
 
638
 
 
639
handle_renegotiation_info(server, undefined, ConnectionStates, _, _, CipherSuites) -> 
 
640
    case is_member(?TLS_EMPTY_RENEGOTIATION_INFO_SCSV, CipherSuites) of
 
641
        true ->
 
642
            {ok, ssl_record:set_renegotiation_flag(true, ConnectionStates)};
 
643
        false ->
 
644
            {ok, ssl_record:set_renegotiation_flag(false, ConnectionStates)}
 
645
    end;
 
646
 
 
647
handle_renegotiation_info(_, undefined, ConnectionStates, false, _, _) ->
 
648
    {ok, ssl_record:set_renegotiation_flag(false, ConnectionStates)};
 
649
 
 
650
handle_renegotiation_info(client, #renegotiation_info{renegotiated_connection = ClientServerVerify}, 
 
651
                          ConnectionStates, true, _, _) ->
 
652
    CS = ssl_record:current_connection_state(ConnectionStates, read),
 
653
    CData = CS#connection_state.client_verify_data,
 
654
    SData = CS#connection_state.server_verify_data,    
 
655
    case <<CData/binary, SData/binary>> == ClientServerVerify of
 
656
        true ->
 
657
            {ok, ConnectionStates};
 
658
        false ->
 
659
            ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE)
 
660
    end;
 
661
handle_renegotiation_info(server, #renegotiation_info{renegotiated_connection = ClientVerify}, 
 
662
                          ConnectionStates, true, _, CipherSuites) ->
 
663
    
 
664
      case is_member(?TLS_EMPTY_RENEGOTIATION_INFO_SCSV, CipherSuites) of
 
665
          true ->
 
666
              ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE);
 
667
          false ->      
 
668
              CS = ssl_record:current_connection_state(ConnectionStates, read),
 
669
              Data = CS#connection_state.client_verify_data,
 
670
              case Data == ClientVerify of
 
671
                  true ->
 
672
                      {ok, ConnectionStates};
 
673
                  false ->
 
674
                      ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE)
 
675
              end
 
676
      end;
 
677
 
 
678
handle_renegotiation_info(client, undefined, ConnectionStates, true, SecureRenegotation, _) ->
 
679
    handle_renegotiation_info(ConnectionStates, SecureRenegotation);
 
680
 
 
681
handle_renegotiation_info(server, undefined, ConnectionStates, true, SecureRenegotation, CipherSuites) ->
 
682
     case is_member(?TLS_EMPTY_RENEGOTIATION_INFO_SCSV, CipherSuites) of
 
683
          true ->
 
684
             ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE);
 
685
         false ->
 
686
             handle_renegotiation_info(ConnectionStates, SecureRenegotation)
 
687
     end.
 
688
 
 
689
handle_renegotiation_info(ConnectionStates, SecureRenegotation) ->
 
690
    CS = ssl_record:current_connection_state(ConnectionStates, read),
 
691
    case {SecureRenegotation, CS#connection_state.secure_renegotiation} of
 
692
        {_, true} ->
 
693
            ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE);
 
694
        {true, false} ->
 
695
            ?ALERT_REC(?FATAL, ?NO_RENEGOTIATION);
 
696
        {false, false} ->
 
697
            {ok, ConnectionStates}
 
698
    end.
 
699
 
514
700
%% Update pending connection states with parameters exchanged via 
515
701
%% hello messages
516
702
%% NOTE : Role is the role of the receiver of the hello message
582
768
                         hash_size = HashSize,
583
769
                         key_material_length = KML,
584
770
                         expanded_key_material_length = EKML,
585
 
                         iv_size = IVS,
586
 
                         exportable = Exportable},
 
771
                         iv_size = IVS},
587
772
              ConnectionStates, Role) ->
588
773
    {ClientWriteMacSecret, ServerWriteMacSecret, ClientWriteKey,
589
774
     ServerWriteKey, ClientIV, ServerIV} =
590
 
        setup_keys(Version, Exportable, MasterSecret, ServerRandom, 
 
775
        setup_keys(Version, MasterSecret, ServerRandom, 
591
776
                   ClientRandom, HashSize, KML, EKML, IVS),
592
 
    ?DBG_HEX(ClientWriteKey),
593
 
    ?DBG_HEX(ClientIV),
 
777
 
594
778
    ConnStates1 = ssl_record:set_master_secret(MasterSecret, ConnectionStates),
595
779
    ConnStates2 =
596
780
        ssl_record:set_mac_secret(ClientWriteMacSecret, ServerWriteMacSecret,
603
787
                                         ServerCipherState, Role)}.
604
788
 
605
789
 
606
 
dec_hs(?HELLO_REQUEST, <<>>, _, _) ->
 
790
dec_hs(?HELLO_REQUEST, <<>>) ->
607
791
    #hello_request{};
608
792
 
609
793
%% Client hello v2.
613
797
                       ?UINT16(CSLength), ?UINT16(0),
614
798
                       ?UINT16(CDLength), 
615
799
                       CipherSuites:CSLength/binary, 
616
 
                       ChallengeData:CDLength/binary>>,
617
 
       _, _) ->
618
 
    ?DBG_HEX(CipherSuites),
619
 
    ?DBG_HEX(CipherSuites),
 
800
                       ChallengeData:CDLength/binary>>) ->
620
801
    #client_hello{client_version = {Major, Minor},
621
802
                  random = ssl_ssl2:client_random(ChallengeData, CDLength),
622
803
                  session_id = 0,
623
804
                  cipher_suites = from_3bytes(CipherSuites),
624
 
                  compression_methods = [?NULL]
 
805
                  compression_methods = [?NULL],
 
806
                  renegotiation_info = undefined
625
807
                 };
626
808
dec_hs(?CLIENT_HELLO, <<?BYTE(Major), ?BYTE(Minor), Random:32/binary,
627
809
                       ?BYTE(SID_length), Session_ID:SID_length/binary,
628
810
                       ?UINT16(Cs_length), CipherSuites:Cs_length/binary,
629
811
                       ?BYTE(Cm_length), Comp_methods:Cm_length/binary,
630
 
                       _FutureCompatData/binary>>,
631
 
       _, _) ->
 
812
                       Extensions/binary>>) ->
 
813
    
 
814
    RenegotiationInfo = proplists:get_value(renegotiation_info, dec_hello_extensions(Extensions),
 
815
                                           undefined),    
632
816
    #client_hello{
633
817
        client_version = {Major,Minor},
634
818
        random = Random,
635
819
        session_id = Session_ID,
636
820
        cipher_suites = from_2bytes(CipherSuites),
637
 
        compression_methods = Comp_methods
638
 
       };
639
 
dec_hs(?SERVER_HELLO, <<?BYTE(Major), ?BYTE(Minor), Random:32/binary,
640
 
                       ?BYTE(SID_length), Session_ID:SID_length/binary,
641
 
                       Cipher_suite:2/binary, ?BYTE(Comp_method)>>, _, _) ->
642
 
    #server_hello{
643
 
        server_version = {Major,Minor},
644
 
        random = Random,
645
 
        session_id = Session_ID,
646
 
        cipher_suite = Cipher_suite,
647
 
        compression_method = Comp_method
648
 
       };
649
 
dec_hs(?CERTIFICATE, <<?UINT24(ACLen), ASN1Certs:ACLen/binary>>, _, _) ->
 
821
        compression_methods = Comp_methods,
 
822
        renegotiation_info = RenegotiationInfo 
 
823
       };
 
824
 
 
825
dec_hs(?SERVER_HELLO, <<?BYTE(Major), ?BYTE(Minor), Random:32/binary,
 
826
                       ?BYTE(SID_length), Session_ID:SID_length/binary,
 
827
                       Cipher_suite:2/binary, ?BYTE(Comp_method)>>) ->
 
828
    #server_hello{
 
829
        server_version = {Major,Minor},
 
830
        random = Random,
 
831
        session_id = Session_ID,
 
832
        cipher_suite = Cipher_suite,
 
833
        compression_method = Comp_method,
 
834
        renegotiation_info = undefined};
 
835
 
 
836
dec_hs(?SERVER_HELLO, <<?BYTE(Major), ?BYTE(Minor), Random:32/binary,
 
837
                       ?BYTE(SID_length), Session_ID:SID_length/binary,
 
838
                       Cipher_suite:2/binary, ?BYTE(Comp_method), 
 
839
                       ?UINT16(ExtLen), Extensions:ExtLen/binary>>) ->
 
840
    
 
841
    RenegotiationInfo = proplists:get_value(renegotiation_info, dec_hello_extensions(Extensions, []),
 
842
                                           undefined),   
 
843
    #server_hello{
 
844
        server_version = {Major,Minor},
 
845
        random = Random,
 
846
        session_id = Session_ID,
 
847
        cipher_suite = Cipher_suite,
 
848
        compression_method = Comp_method,
 
849
        renegotiation_info = RenegotiationInfo};
 
850
dec_hs(?CERTIFICATE, <<?UINT24(ACLen), ASN1Certs:ACLen/binary>>) ->
650
851
    #certificate{asn1_certificates = certs_to_list(ASN1Certs)};
651
 
dec_hs(?SERVER_KEY_EXCHANGE, <<?UINT16(ModLen), Mod:ModLen/binary,
652
 
                              ?UINT16(ExpLen), Exp:ExpLen/binary,
653
 
                              Sig/binary>>,
654
 
       ?KEY_EXCHANGE_RSA, _) ->
655
 
    #server_key_exchange{params = #server_rsa_params{rsa_modulus = Mod, 
656
 
                                                     rsa_exponent = Exp}, 
657
 
                         signed_params = Sig};  
658
 
dec_hs(?SERVER_KEY_EXCHANGE, <<?UINT16(PLen), P:PLen/binary,
659
 
                              ?UINT16(GLen), G:GLen/binary,
660
 
                              ?UINT16(YLen), Y:YLen/binary,
661
 
                              Sig/binary>>,
662
 
       ?KEY_EXCHANGE_DIFFIE_HELLMAN, _) ->
663
 
    #server_key_exchange{params = #server_dh_params{dh_p = P,dh_g = G, dh_y = Y},
 
852
 
 
853
dec_hs(?SERVER_KEY_EXCHANGE, <<?UINT16(PLen), P:PLen/binary,
 
854
                              ?UINT16(GLen), G:GLen/binary,
 
855
                              ?UINT16(YLen), Y:YLen/binary,
 
856
                               ?UINT16(0)>>) -> %% May happen if key_algorithm is dh_anon
 
857
    #server_key_exchange{params = #server_dh_params{dh_p = P,dh_g = G,
 
858
                                                    dh_y = Y},
 
859
                         signed_params = <<>>};
 
860
dec_hs(?SERVER_KEY_EXCHANGE, <<?UINT16(PLen), P:PLen/binary,
 
861
                              ?UINT16(GLen), G:GLen/binary,
 
862
                              ?UINT16(YLen), Y:YLen/binary,
 
863
                              ?UINT16(Len), Sig:Len/binary>>) ->
 
864
    #server_key_exchange{params = #server_dh_params{dh_p = P,dh_g = G, 
 
865
                                                    dh_y = Y},
664
866
                         signed_params = Sig};
665
867
dec_hs(?CERTIFICATE_REQUEST,
666
868
       <<?BYTE(CertTypesLen), CertTypes:CertTypesLen/binary,
667
 
        ?UINT16(CertAuthsLen), CertAuths:CertAuthsLen/binary>>, _, _) ->
668
 
    %% TODO: maybe we should chop up CertAuths into a list?
 
869
        ?UINT16(CertAuthsLen), CertAuths:CertAuthsLen/binary>>) ->
669
870
    #certificate_request{certificate_types = CertTypes,
670
871
                         certificate_authorities = CertAuths};
671
 
dec_hs(?SERVER_HELLO_DONE, <<>>, _, _) ->
 
872
dec_hs(?SERVER_HELLO_DONE, <<>>) ->
672
873
    #server_hello_done{};
673
 
dec_hs(?CERTIFICATE_VERIFY,<<?UINT16(_), Signature/binary>>, _, _)->
 
874
dec_hs(?CERTIFICATE_VERIFY,<<?UINT16(_), Signature/binary>>)->
674
875
    #certificate_verify{signature = Signature};
675
 
dec_hs(?CLIENT_KEY_EXCHANGE, PKEPMS, rsa, {3, 0}) ->
676
 
    PreSecret = #encrypted_premaster_secret{premaster_secret = PKEPMS},
677
 
    #client_key_exchange{exchange_keys = PreSecret};
678
 
dec_hs(?CLIENT_KEY_EXCHANGE, <<?UINT16(_), PKEPMS/binary>>, rsa, _) ->
679
 
    PreSecret = #encrypted_premaster_secret{premaster_secret = PKEPMS},
680
 
    #client_key_exchange{exchange_keys = PreSecret};
681
 
dec_hs(?CLIENT_KEY_EXCHANGE, <<>>, ?KEY_EXCHANGE_DIFFIE_HELLMAN, _) -> 
682
 
    %% TODO: Should check whether the cert already contains a suitable DH-key (7.4.7.2)
683
 
    throw(?ALERT_REC(?FATAL, implicit_public_value_encoding));
684
 
dec_hs(?CLIENT_KEY_EXCHANGE, <<?UINT16(DH_YCLen), DH_YC:DH_YCLen/binary>>,
685
 
       ?KEY_EXCHANGE_DIFFIE_HELLMAN, _) ->
686
 
    #client_diffie_hellman_public{dh_public = DH_YC};
687
 
dec_hs(?FINISHED, VerifyData, _, _) ->
 
876
dec_hs(?CLIENT_KEY_EXCHANGE, PKEPMS) ->
 
877
    #client_key_exchange{exchange_keys = PKEPMS};
 
878
dec_hs(?FINISHED, VerifyData) ->
688
879
    #finished{verify_data = VerifyData};
689
 
dec_hs(_, _, _, _) ->
 
880
dec_hs(_, _) ->
690
881
    throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE)).
691
882
 
 
883
dec_client_key(PKEPMS, ?KEY_EXCHANGE_RSA, {3, 0}) ->
 
884
    #encrypted_premaster_secret{premaster_secret = PKEPMS};
 
885
dec_client_key(<<?UINT16(_), PKEPMS/binary>>, ?KEY_EXCHANGE_RSA, _) ->
 
886
    #encrypted_premaster_secret{premaster_secret = PKEPMS};
 
887
dec_client_key(<<>>, ?KEY_EXCHANGE_DIFFIE_HELLMAN, _) ->
 
888
    throw(?ALERT_REC(?FATAL, ?UNSUPPORTED_CERTIFICATE));
 
889
dec_client_key(<<?UINT16(DH_YLen), DH_Y:DH_YLen/binary>>,
 
890
               ?KEY_EXCHANGE_DIFFIE_HELLMAN, _) ->
 
891
    #client_diffie_hellman_public{dh_public = DH_Y}.
 
892
 
 
893
dec_hello_extensions(<<>>) ->
 
894
    [];
 
895
dec_hello_extensions(<<?UINT16(ExtLen), Extensions:ExtLen/binary>>) ->
 
896
    dec_hello_extensions(Extensions, []);
 
897
dec_hello_extensions(_) ->
 
898
    [].
 
899
 
 
900
dec_hello_extensions(<<>>, Acc) ->
 
901
    Acc;
 
902
dec_hello_extensions(<<?UINT16(?RENEGOTIATION_EXT), ?UINT16(Len), Info:Len/binary, Rest/binary>>, Acc) ->
 
903
    RenegotiateInfo = case Len of
 
904
                          1 ->  % Initial handshake
 
905
                              Info; % should be <<0>> will be matched in handle_renegotiation_info
 
906
                          _ ->
 
907
                              VerifyLen = Len - 1,
 
908
                              <<?BYTE(VerifyLen), VerifyInfo/binary>> = Info,
 
909
                              VerifyInfo
 
910
                      end,          
 
911
    dec_hello_extensions(Rest, [{renegotiation_info, 
 
912
                           #renegotiation_info{renegotiated_connection = RenegotiateInfo}} | Acc]);
 
913
dec_hello_extensions(<<?UINT16(_), ?UINT16(Len), _Unknown:Len, Rest/binary>>, Acc) ->
 
914
    dec_hello_extensions(Rest, Acc);
 
915
%% Need this clause?
 
916
dec_hello_extensions(_, Acc) ->
 
917
    Acc.
 
918
 
692
919
encrypted_premaster_secret(Secret, RSAPublicKey) -> 
693
920
    try 
694
921
        PreMasterSecret = public_key:encrypt_public(Secret, RSAPublicKey, 
700
927
            throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE))
701
928
    end.
702
929
 
703
 
decrypt_premaster_secret(Secret, RSAPrivateKey) ->
704
 
    try public_key:decrypt_private(Secret, RSAPrivateKey,  
705
 
                                   [{rsa_pad, rsa_pkcs1_padding}])
706
 
    catch
707
 
        _:_ ->
708
 
            throw(?ALERT_REC(?FATAL, ?DECRYPTION_FAILED))
709
 
    end.
710
 
    
711
930
%% encode/decode stream of certificate data to/from list of certificate data 
712
931
certs_to_list(ASN1Certs) ->
713
932
    certs_to_list(ASN1Certs, []).
723
942
                        <<?UINT24(CertLen), Cert/binary>>
724
943
                    end || Cert <- ACList]).
725
944
 
726
 
enc_hs(#hello_request{}, _Version, _) ->
 
945
enc_hs(#hello_request{}, _Version) ->
727
946
    {?HELLO_REQUEST, <<>>};
728
 
enc_hs(#client_hello{
729
 
        client_version = {Major, Minor},
730
 
        random = Random,
731
 
        session_id = SessionID,
732
 
        cipher_suites = CipherSuites,
733
 
        compression_methods = CompMethods}, _Version, _) ->
 
947
enc_hs(#client_hello{client_version = {Major, Minor},
 
948
                     random = Random,
 
949
                     session_id = SessionID,
 
950
                     cipher_suites = CipherSuites,
 
951
                     compression_methods = CompMethods, 
 
952
                     renegotiation_info = RenegotiationInfo}, _Version) ->
734
953
    SIDLength = byte_size(SessionID),
735
954
    BinCompMethods = list_to_binary(CompMethods),
736
955
    CmLength = byte_size(BinCompMethods),
737
956
    BinCipherSuites = list_to_binary(CipherSuites),
738
957
    CsLength = byte_size(BinCipherSuites),
 
958
    Extensions  = hello_extensions(RenegotiationInfo),
 
959
    ExtensionsBin = enc_hello_extensions(Extensions),
739
960
    {?CLIENT_HELLO, <<?BYTE(Major), ?BYTE(Minor), Random:32/binary,
740
961
                     ?BYTE(SIDLength), SessionID/binary,
741
962
                     ?UINT16(CsLength), BinCipherSuites/binary,
742
 
                     ?BYTE(CmLength), BinCompMethods/binary>>};
743
 
enc_hs(#server_hello{
744
 
        server_version = {Major, Minor},
745
 
        random = Random,
746
 
        session_id = Session_ID,
747
 
        cipher_suite = Cipher_suite,
748
 
        compression_method = Comp_method}, _Version, _) ->
 
963
                     ?BYTE(CmLength), BinCompMethods/binary, ExtensionsBin/binary>>};
 
964
 
 
965
enc_hs(#server_hello{server_version = {Major, Minor},
 
966
                     random = Random,
 
967
                     session_id = Session_ID,
 
968
                     cipher_suite = Cipher_suite,
 
969
                     compression_method = Comp_method,
 
970
                     renegotiation_info = RenegotiationInfo}, _Version) ->
749
971
    SID_length = byte_size(Session_ID),
 
972
    Extensions  = hello_extensions(RenegotiationInfo),
 
973
    ExtensionsBin = enc_hello_extensions(Extensions),
750
974
    {?SERVER_HELLO, <<?BYTE(Major), ?BYTE(Minor), Random:32/binary,
751
975
                     ?BYTE(SID_length), Session_ID/binary,
752
 
                     Cipher_suite/binary, ?BYTE(Comp_method)>>};
753
 
enc_hs(#certificate{asn1_certificates = ASN1CertList}, _Version, _) ->
 
976
                     Cipher_suite/binary, ?BYTE(Comp_method), ExtensionsBin/binary>>};
 
977
enc_hs(#certificate{asn1_certificates = ASN1CertList}, _Version) ->
754
978
    ASN1Certs = certs_from_list(ASN1CertList),
755
979
    ACLen = erlang:iolist_size(ASN1Certs),
756
980
    {?CERTIFICATE, <<?UINT24(ACLen), ASN1Certs:ACLen/binary>>};
757
 
enc_hs(#server_key_exchange{params = #server_rsa_params{rsa_modulus = Mod,
758
 
                                                        rsa_exponent = Exp},
759
 
        signed_params = SignedParams}, _Version, _) ->
760
 
    ModLen = byte_size(Mod),
761
 
    ExpLen = byte_size(Exp),
762
 
    {?SERVER_KEY_EXCHANGE, <<?UINT16(ModLen), Mod/binary,
763
 
                            ?UINT16(ExpLen), Exp/binary,
764
 
                            SignedParams/binary>>
765
 
    };
766
981
enc_hs(#server_key_exchange{params = #server_dh_params{
767
982
                              dh_p = P, dh_g = G, dh_y = Y},
768
 
        signed_params = SignedParams}, _Version, _) ->
 
983
        signed_params = SignedParams}, _Version) ->
769
984
    PLen = byte_size(P),
770
985
    GLen = byte_size(G),
771
986
    YLen = byte_size(Y),
772
 
    {?SERVER_KEY_EXCHANGE, <<?UINT16(PLen), P:PLen/binary,
773
 
                            ?UINT16(GLen), G:GLen/binary,
774
 
                            ?UINT16(YLen), Y:YLen/binary,
775
 
                            SignedParams/binary>>
 
987
    SignedLen = byte_size(SignedParams),
 
988
    {?SERVER_KEY_EXCHANGE, <<?UINT16(PLen), P/binary, 
 
989
                            ?UINT16(GLen), G/binary,
 
990
                            ?UINT16(YLen), Y/binary,
 
991
                            ?UINT16(SignedLen), SignedParams/binary>>
776
992
    };
777
993
enc_hs(#certificate_request{certificate_types = CertTypes,
778
994
                            certificate_authorities = CertAuths}, 
779
 
       _Version, _) ->
 
995
       _Version) ->
780
996
    CertTypesLen = byte_size(CertTypes),
781
997
    CertAuthsLen = byte_size(CertAuths),
782
998
    {?CERTIFICATE_REQUEST,
783
999
       <<?BYTE(CertTypesLen), CertTypes/binary,
784
1000
        ?UINT16(CertAuthsLen), CertAuths/binary>>
785
1001
    };
786
 
enc_hs(#server_hello_done{}, _Version, _) ->
 
1002
enc_hs(#server_hello_done{}, _Version) ->
787
1003
    {?SERVER_HELLO_DONE, <<>>};
788
 
enc_hs(#client_key_exchange{exchange_keys = ExchangeKeys}, Version, _) ->
 
1004
enc_hs(#client_key_exchange{exchange_keys = ExchangeKeys}, Version) ->
789
1005
    {?CLIENT_KEY_EXCHANGE, enc_cke(ExchangeKeys, Version)};
790
 
enc_hs(#certificate_verify{signature = BinSig}, _, _) ->
 
1006
enc_hs(#certificate_verify{signature = BinSig}, _) ->
791
1007
    EncSig = enc_bin_sig(BinSig),
792
1008
    {?CERTIFICATE_VERIFY, EncSig};
793
 
enc_hs(#finished{verify_data = VerifyData}, _Version, _) ->
 
1009
enc_hs(#finished{verify_data = VerifyData}, _Version) ->
794
1010
    {?FINISHED, VerifyData}.
795
1011
 
796
1012
enc_cke(#encrypted_premaster_secret{premaster_secret = PKEPMS},{3, 0}) ->
806
1022
    Size = byte_size(BinSig),
807
1023
    <<?UINT16(Size), BinSig/binary>>.
808
1024
 
809
 
init_hashes() ->
810
 
    T = {crypto:md5_init(), crypto:sha_init()},
811
 
    {T, T}.
812
 
 
813
 
update_hashes(Hashes, % special-case SSL2 client hello
814
 
              <<?CLIENT_HELLO, ?UINT24(_), ?BYTE(Major), ?BYTE(Minor),
815
 
               ?UINT16(CSLength), ?UINT16(0),
816
 
               ?UINT16(CDLength), 
817
 
               CipherSuites:CSLength/binary, 
818
 
               ChallengeData:CDLength/binary>>) ->
819
 
    update_hashes(Hashes,
820
 
                  <<?CLIENT_HELLO, ?BYTE(Major), ?BYTE(Minor),
821
 
                   ?UINT16(CSLength), ?UINT16(0),
822
 
                   ?UINT16(CDLength), 
823
 
                   CipherSuites:CSLength/binary, 
824
 
                   ChallengeData:CDLength/binary>>);
825
 
update_hashes({{MD50, SHA0}, _Prev}, Data) ->
826
 
    ?DBG_HEX(Data),
827
 
    {MD51, SHA1} = {crypto:md5_update(MD50, Data),
828
 
                    crypto:sha_update(SHA0, Data)},
829
 
    ?DBG_HEX(crypto:md5_final(MD51)),
830
 
    ?DBG_HEX(crypto:sha_final(SHA1)),
831
 
    {{MD51, SHA1}, {MD50, SHA0}}.
 
1025
%% Renegotiation info, only current extension
 
1026
hello_extensions(#renegotiation_info{renegotiated_connection = undefined}) ->
 
1027
    [];
 
1028
hello_extensions(#renegotiation_info{} = Info) ->
 
1029
    [Info].
 
1030
 
 
1031
enc_hello_extensions(Extensions) ->
 
1032
    enc_hello_extensions(Extensions, <<>>).
 
1033
enc_hello_extensions([], <<>>) ->
 
1034
    <<>>;
 
1035
enc_hello_extensions([], Acc) ->
 
1036
    Size = byte_size(Acc),
 
1037
    <<?UINT16(Size), Acc/binary>>;
 
1038
 
 
1039
enc_hello_extensions([#renegotiation_info{renegotiated_connection = ?byte(0) = Info} | Rest], Acc) ->
 
1040
    Len = byte_size(Info),
 
1041
    enc_hello_extensions(Rest, <<?UINT16(?RENEGOTIATION_EXT), ?UINT16(Len), Info/binary, Acc/binary>>);
 
1042
 
 
1043
enc_hello_extensions([#renegotiation_info{renegotiated_connection = Info} | Rest], Acc) ->
 
1044
    InfoLen = byte_size(Info),
 
1045
    Len = InfoLen +1,
 
1046
    enc_hello_extensions(Rest, <<?UINT16(?RENEGOTIATION_EXT), ?UINT16(Len), ?BYTE(InfoLen), Info/binary, Acc/binary>>).
 
1047
 
832
1048
 
833
1049
from_3bytes(Bin3) ->
834
1050
    from_3bytes(Bin3, []).
848
1064
 
849
1065
certificate_types({KeyExchange, _, _, _})  
850
1066
  when KeyExchange == rsa;
851
 
       KeyExchange == dh_dss;
852
 
       KeyExchange == dh_rsa;
853
1067
       KeyExchange == dhe_dss;
854
1068
       KeyExchange == dhe_rsa ->
855
1069
    <<?BYTE(?RSA_SIGN), ?BYTE(?DSS_SIGN)>>;
856
1070
 
857
1071
certificate_types(_) ->
858
 
    %%TODO: Is this a good default,
859
 
    %% is there a case where we like to request
860
 
    %% a RSA_FIXED_DH or DSS_FIXED_DH
861
1072
    <<?BYTE(?RSA_SIGN)>>.
862
1073
 
863
 
certificate_authorities(_) ->
864
 
    %%TODO Make list of know CA:s
865
 
    <<>>.
866
 
 
867
 
digitally_signed(Hashes, #'RSAPrivateKey'{} = Key) ->
868
 
    public_key:encrypt_private(Hashes, Key,
 
1074
certificate_authorities(CertDbRef) ->
 
1075
    Authorities = certificate_authorities_from_db(CertDbRef),
 
1076
    Enc = fun(#'OTPCertificate'{tbsCertificate=TBSCert}) ->
 
1077
                  OTPSubj = TBSCert#'OTPTBSCertificate'.subject,
 
1078
                  DNEncodedBin = public_key:pkix_encode('Name', OTPSubj, otp),
 
1079
                  %%Subj = public_key:pkix_transform(OTPSubj, encode),
 
1080
                  %% {ok, DNEncoded} = 'OTP-PUB-KEY':encode('Name', Subj),
 
1081
                  %% DNEncodedBin = iolist_to_binary(DNEncoded),
 
1082
                  DNEncodedLen = byte_size(DNEncodedBin),
 
1083
                  <<?UINT16(DNEncodedLen), DNEncodedBin/binary>>
 
1084
          end,
 
1085
    list_to_binary([Enc(Cert) || {_, Cert} <- Authorities]).
 
1086
 
 
1087
certificate_authorities_from_db(CertDbRef) ->
 
1088
    certificate_authorities_from_db(CertDbRef, no_candidate, []).
 
1089
 
 
1090
certificate_authorities_from_db(CertDbRef, PrevKey, Acc) ->
 
1091
    case ssl_manager:issuer_candidate(PrevKey) of
 
1092
        no_more_candidates ->
 
1093
            lists:reverse(Acc);
 
1094
        {{CertDbRef, _, _} = Key, Cert} ->
 
1095
            certificate_authorities_from_db(CertDbRef, Key, [Cert|Acc]);
 
1096
        {Key, _Cert} ->
 
1097
            %% skip certs not from this ssl connection
 
1098
            certificate_authorities_from_db(CertDbRef, Key, Acc)
 
1099
    end.
 
1100
 
 
1101
digitally_signed(Hash, #'RSAPrivateKey'{} = Key) ->
 
1102
    public_key:encrypt_private(Hash, Key,
869
1103
                               [{rsa_pad, rsa_pkcs1_padding}]);
870
 
digitally_signed(Hashes, #'DSAPrivateKey'{} = Key) ->
871
 
    public_key:sign(Hashes, Key).
872
 
 
873
 
 
 
1104
digitally_signed(Hash, #'DSAPrivateKey'{} = Key) ->
 
1105
    public_key:sign(Hash, none, Key).
 
1106
    
874
1107
calc_master_secret({3,0}, PremasterSecret, ClientRandom, ServerRandom) ->
875
1108
    ssl_ssl3:master_secret(PremasterSecret, ClientRandom, ServerRandom);
876
1109
 
878
1111
  when N == 1; N == 2 ->
879
1112
    ssl_tls1:master_secret(PremasterSecret, ClientRandom, ServerRandom).
880
1113
 
881
 
setup_keys({3,0}, Exportable, MasterSecret,
 
1114
setup_keys({3,0}, MasterSecret,
882
1115
           ServerRandom, ClientRandom, HashSize, KML, EKML, IVS) ->
883
 
    ssl_ssl3:setup_keys(Exportable, MasterSecret, ServerRandom, 
 
1116
    ssl_ssl3:setup_keys(MasterSecret, ServerRandom, 
884
1117
                        ClientRandom, HashSize, KML, EKML, IVS);
885
1118
 
886
 
setup_keys({3,1}, _Exportable, MasterSecret,
 
1119
setup_keys({3,1}, MasterSecret,
887
1120
           ServerRandom, ClientRandom, HashSize, KML, _EKML, IVS) ->
888
1121
    ssl_tls1:setup_keys(MasterSecret, ServerRandom, ClientRandom, HashSize, 
889
 
                        KML, IVS);
890
 
 
891
 
setup_keys({3,2}, _Exportable, MasterSecret,
892
 
           ServerRandom, ClientRandom, HashSize, KML, _EKML, _IVS) ->
893
 
    ssl_tls1:setup_keys(MasterSecret, ServerRandom, 
894
 
                        ClientRandom, HashSize, KML).
 
1122
                        KML, IVS).
895
1123
 
896
1124
calc_finished({3, 0}, Role, MasterSecret, Hashes) ->
897
1125
    ssl_ssl3:finished(Role, MasterSecret, Hashes);
905
1133
  when  N == 1; N == 2 ->
906
1134
    ssl_tls1:certificate_verify(Algorithm, Hashes).
907
1135
 
908
 
%% server_key_exchange_hash(Algorithm, Value) when Algorithm == rsa;
909
 
%%                                              Algorithm == dh_rsa;
910
 
%%                                              Algorithm == dhe_rsa ->
911
 
%%     MD5 = crypto:md5_final(Value),
912
 
%%     SHA =  crypto:sha_final(Value),
913
 
%%     <<MD5/binary, SHA/binary>>;
914
 
 
915
 
%% server_key_exchange_hash(Algorithm, Value) when Algorithm == dh_dss;
916
 
%%                                         Algorithm == dhe_dss ->
917
 
%%     crypto:sha_final(Value).
 
1136
key_exchange_alg(rsa) ->
 
1137
    ?KEY_EXCHANGE_RSA;
 
1138
key_exchange_alg(Alg) when Alg == dhe_rsa; Alg == dhe_dss;
 
1139
                            Alg == dh_dss; Alg == dh_rsa; Alg == dh_anon ->
 
1140
    ?KEY_EXCHANGE_DIFFIE_HELLMAN;
 
1141
key_exchange_alg(_) ->
 
1142
    ?NULL.
 
1143
 
 
1144
apply_user_fun(Fun, OtpCert, ExtensionOrError, UserState0, SslState) ->
 
1145
    case Fun(OtpCert, ExtensionOrError, UserState0) of
 
1146
        {valid, UserState} ->
 
1147
            {valid, {SslState, UserState}};
 
1148
        {fail, _} = Fail ->
 
1149
            Fail;
 
1150
        {unknown, UserState} ->
 
1151
            {unknown, {SslState, UserState}}
 
1152
    end.
 
1153
 
 
1154
alg_oid(#'RSAPrivateKey'{}) ->
 
1155
    ?'rsaEncryption';
 
1156
alg_oid(#'DSAPrivateKey'{}) ->
 
1157
    ?'id-dsa'.