~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
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
%%----------------------------------------------------------------------
19
21
%% Purpose: Help functions for handling the SSL-Record protocol 
33
35
         current_connection_state/2, pending_connection_state/2,
34
36
         update_security_params/3,
35
37
         set_mac_secret/4,
36
 
         set_master_secret/2, get_master_secret/1, get_pending_master_secret/1,
 
38
         set_master_secret/2, 
37
39
         activate_pending_connection_state/2,
38
 
         increment_sequence_number/2, update_cipher_state/3,
39
 
         set_pending_cipher_state/4,
40
 
         update_compression_state/3]).
 
40
         set_pending_cipher_state/4]).
41
41
 
42
42
%% Handling of incoming data
43
 
-export([get_tls_records/2, compress/3, uncompress/3, cipher/2, decipher/2]).
 
43
-export([get_tls_records/2]).
44
44
 
45
45
%% Encoding records
46
46
-export([encode_handshake/3, encode_alert_record/3,
52
52
%% Misc.
53
53
-export([protocol_version/1, lowest_protocol_version/2,
54
54
         highest_protocol_version/1, supported_protocol_versions/0,
55
 
         highest_protocol_version/0, is_acceptable_version/1]).
 
55
         is_acceptable_version/1]).
56
56
 
57
57
-export([compressions/0]).
58
58
 
 
59
-compile(inline).
 
60
 
59
61
%%====================================================================
60
62
%% Internal application API
61
63
%%====================================================================
172
174
                                       master_secret = MasterSecret}},
173
175
    States#connection_states{pending_read = Read1, pending_write = Write1}.
174
176
 
175
 
%%--------------------------------------------------------------------
176
 
%% Function: get_master_secret(CStates) -> binary()
177
 
%%      CStates = #connection_states{}
178
 
%%
179
 
%% Get master_secret from current state
180
 
%%--------------------------------------------------------------------
181
 
get_master_secret(CStates) ->
182
 
    CS = CStates#connection_states.current_write,
183
 
    SP = CS#connection_state.security_parameters,
184
 
    SP#security_parameters.master_secret.
185
 
 
186
 
%%--------------------------------------------------------------------
187
 
%% Function: get_pending_master_secret(CStates) -> binary()
188
 
%%      CStates = #connection_states{}
189
 
%%
190
 
%% Get master_secret from pending state
191
 
%%--------------------------------------------------------------------
192
 
get_pending_master_secret(CStates) ->
193
 
    CS = CStates#connection_states.pending_write,
194
 
    SP = CS#connection_state.security_parameters,
195
 
    SP#security_parameters.master_secret.
196
177
 
197
178
%%--------------------------------------------------------------------
198
179
%% Function: activate_pending_connection_state(States, Type) -> 
226
207
                            }.
227
208
 
228
209
%%--------------------------------------------------------------------
229
 
%% Function: increment_sequence_number(States, Type) -> #connection_states{} 
230
 
%%      States = #connection_states{}
231
 
%%      Type = read | write
232
 
%%
233
 
%% Description: Creates a new instance of the connection_states record
234
 
%% where the sequence number of the current state of <Type> has been
235
 
%% incremented.
236
 
%%--------------------------------------------------------------------
237
 
increment_sequence_number(States = #connection_states{current_read = Current},
238
 
                          read) ->
239
 
    SeqNr = Current#connection_state.sequence_number + 1,
240
 
    States#connection_states{current_read = Current#connection_state{
241
 
                                              sequence_number = SeqNr
242
 
                                             }};
243
 
 
244
 
increment_sequence_number(States = #connection_states{current_write = Current},
245
 
                          write) ->
246
 
    SeqNr = Current#connection_state.sequence_number + 1,
247
 
    States#connection_states{current_write = Current#connection_state{
248
 
                                               sequence_number = SeqNr
249
 
                                              }}.
250
 
 
251
 
%%--------------------------------------------------------------------
252
 
%% Function: update_cipher_state(CipherState, States, Type) -> 
253
 
%%                                                    #connection_states{}
254
 
%%      CipherState = #cipher_state{}
255
 
%%      States = #connection_states{}
256
 
%%      Type = read | write
257
 
%%
258
 
%% update the cipher state in the specified current connection state
259
 
%%--------------------------------------------------------------------
260
 
update_cipher_state(CipherState, 
261
 
                    States = #connection_states{current_read = Current},
262
 
                    read) ->
263
 
    States#connection_states{current_read = Current#connection_state{
264
 
                                              cipher_state = CipherState
265
 
                                             }};
266
 
 
267
 
update_cipher_state(CipherState,
268
 
                    States = #connection_states{current_write = Current},
269
 
                    write) ->
270
 
    States#connection_states{current_write = Current#connection_state{
271
 
                                               cipher_state = CipherState
272
 
                                              }}.
273
 
 
274
 
 
275
 
%%--------------------------------------------------------------------
276
 
%% Function: set_pending_cipher_state(States, CSCW, CSSW, Role) -> 
 
210
%% Function: set_pending_cipher_state(States, ClientState, 
 
211
%%                                    ServerState, Role) -> 
277
212
%%                                                #connection_states{}
278
 
%%  CSCW = CSSW = #cipher_state{}
279
 
%%      States = #connection_states{}
280
 
%%
281
 
%% set the cipher state in the specified pending connection state
282
 
%%--------------------------------------------------------------------
283
 
set_pending_cipher_state(States, CSCW, CSSW, server) ->
284
 
    set_pending_cipher_state(States, CSSW, CSCW, client);
285
 
set_pending_cipher_state(#connection_states{pending_read = PRCS,
286
 
                                            pending_write = PWCS} = States,
287
 
                         CSCW, CSSW, client) ->
288
 
    States#connection_states{
289
 
        pending_read = PRCS#connection_state{cipher_state = CSCW},
290
 
        pending_write = PWCS#connection_state{cipher_state = CSSW}}.
291
 
 
292
 
%%--------------------------------------------------------------------
293
 
%% Function: update_compression_state(CompressionState, States, Type) -> 
294
 
%%                                                    #connection_states{}
295
 
%%      CompressionState = #compression_state{}
296
 
%%      States = #connection_states{}
297
 
%%      Type = read | write
298
 
%%
299
 
%% Description: Creates a new instance of the connection_states record
300
 
%% where the compression state of the current state of <Type> has been
301
 
%% updated.
302
 
%%--------------------------------------------------------------------
303
 
update_compression_state(CompressionState, 
304
 
                         States = #connection_states{current_read = Current},
305
 
                         read) ->
306
 
    States#connection_states{current_read = Current#connection_state{
307
 
                                              compression_state = 
308
 
                                              CompressionState
309
 
                                             }};
310
 
 
311
 
update_compression_state(CompressionState,
312
 
                         States = #connection_states{current_write = Current},
313
 
                         write) ->
314
 
    States#connection_states{current_write = Current#connection_state{
315
 
                                               compression_state = 
316
 
                                               CompressionState
317
 
                                              }}.
 
213
%%       ClientState = ServerState = #cipher_state{}
 
214
%%       States = #connection_states{}
 
215
%%
 
216
%% Description: Set the cipher state in the specified pending connection state.
 
217
%%--------------------------------------------------------------------
 
218
set_pending_cipher_state(#connection_states{pending_read = Read,
 
219
                                            pending_write = Write} = States,
 
220
                         ClientState, ServerState, server) ->
 
221
    States#connection_states{
 
222
        pending_read = Read#connection_state{cipher_state = ClientState},
 
223
        pending_write = Write#connection_state{cipher_state = ServerState}};
 
224
 
 
225
set_pending_cipher_state(#connection_states{pending_read = Read,
 
226
                                            pending_write = Write} = States,
 
227
                         ClientState, ServerState, client) ->
 
228
    States#connection_states{
 
229
        pending_read = Read#connection_state{cipher_state = ServerState},
 
230
        pending_write = Write#connection_state{cipher_state = ClientState}}.
318
231
 
319
232
%%--------------------------------------------------------------------
320
233
%% Function: get_tls_record(Data, Buffer) -> Result
325
238
%% and returns it as a list of #tls_compressed, also returns leftover
326
239
%% data
327
240
%%--------------------------------------------------------------------
 
241
get_tls_records(Data, <<>>) ->
 
242
    get_tls_records_aux(Data, []);
328
243
get_tls_records(Data, Buffer) ->
329
244
    get_tls_records_aux(list_to_binary([Buffer, Data]), []).
330
245
 
 
246
get_tls_records_aux(<<?BYTE(?APPLICATION_DATA),?BYTE(MajVer),?BYTE(MinVer),
 
247
                     ?UINT16(Length), Data:Length/binary, Rest/binary>>, 
 
248
                    Acc) ->
 
249
    get_tls_records_aux(Rest, [#ssl_tls{type = ?APPLICATION_DATA,
 
250
                                        version = {MajVer, MinVer},
 
251
                                        fragment = Data} | Acc]);
 
252
get_tls_records_aux(<<?BYTE(?HANDSHAKE),?BYTE(MajVer),?BYTE(MinVer),
 
253
                     ?UINT16(Length), 
 
254
                     Data:Length/binary, Rest/binary>>, Acc) ->
 
255
    get_tls_records_aux(Rest, [#ssl_tls{type = ?HANDSHAKE,
 
256
                                        version = {MajVer, MinVer},
 
257
                                        fragment=Data} | Acc]);
 
258
get_tls_records_aux(<<?BYTE(?ALERT),?BYTE(MajVer),?BYTE(MinVer),
 
259
                     ?UINT16(Length), Data:Length/binary, 
 
260
                     Rest/binary>>, Acc) ->
 
261
    get_tls_records_aux(Rest, [#ssl_tls{type = ?ALERT,
 
262
                                        version = {MajVer, MinVer},
 
263
                                        fragment = Data} | Acc]);
 
264
get_tls_records_aux(<<?BYTE(?CHANGE_CIPHER_SPEC),?BYTE(MajVer),?BYTE(MinVer),
 
265
                     ?UINT16(Length), Data:Length/binary, Rest/binary>>, 
 
266
                    Acc) ->
 
267
    get_tls_records_aux(Rest, [#ssl_tls{type = ?CHANGE_CIPHER_SPEC,
 
268
                                        version = {MajVer, MinVer},
 
269
                                        fragment = Data} | Acc]);
331
270
%% Matches a ssl v2 client hello message.
332
271
%% The server must be able to receive such messages, from clients that
333
272
%% are willing to use ssl v3 or higher, but have ssl v2 compatibility.
334
 
get_tls_records_aux(<<?BYTE(Byte0), ?BYTE(Byte1),
335
 
                     ?BYTE(?CLIENT_HELLO), ?BYTE(MajVer), ?BYTE(MinVer),
336
 
                     ?UINT16(CSLength), ?UINT16(0),
337
 
                     ?UINT16(CDLength), 
338
 
                     _CipherSuites:CSLength/binary, 
339
 
                     _ChallangeData:CDLength/binary, Data/binary>> = Msg, 
340
 
                    Acc) when (Byte0 bsr 7) == 1 ->
341
 
    Length = Byte0 band 2#01111111 + Byte1 - 1,
342
 
    <<?BYTE(_), ?BYTE(_), ?BYTE(_), Fragment:Length/binary, Data/binary>> = Msg,
343
 
    C = #tls_cipher_text{type = ?HANDSHAKE,
344
 
                         version = #protocol_version{major = MajVer, 
345
 
                                                     minor = MinVer},
346
 
                         length = Length+3,
347
 
                         fragment = <<?BYTE(?CLIENT_HELLO), ?UINT24(Length),
348
 
                                     Fragment/binary>>},
349
 
    get_tls_records_aux(Data, [C | Acc]);
 
273
get_tls_records_aux(<<1:1, Length0:15, Data0:Length0/binary, Rest/binary>>,
 
274
                    Acc) ->
 
275
    case Data0 of
 
276
        <<?BYTE(?CLIENT_HELLO), ?BYTE(MajVer), ?BYTE(MinVer), _/binary>> ->
 
277
            Length = Length0-1,
 
278
            <<?BYTE(_), Data1:Length/binary>> = Data0,
 
279
            Data = <<?BYTE(?CLIENT_HELLO), ?UINT24(Length), Data1/binary>>,
 
280
            get_tls_records_aux(Rest, [#ssl_tls{type = ?HANDSHAKE,
 
281
                                                version = {MajVer, MinVer},
 
282
                                                fragment = Data} | Acc]);
 
283
        _ ->
 
284
            ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE)
 
285
            
 
286
    end;
350
287
 
351
 
get_tls_records_aux(<<?BYTE(CT), ?BYTE(MajVer), ?BYTE(MinVer),
352
 
                     ?UINT16(Length), Data:Length/binary, Rest/binary>>,
353
 
                    Acc) when CT == ?CHANGE_CIPHER_SPEC; 
354
 
                              CT == ?ALERT;
355
 
                              CT == ?HANDSHAKE; 
356
 
                              CT == ?APPLICATION_DATA ->
357
 
    C = #tls_cipher_text{type = CT,
358
 
                         version = #protocol_version{major = MajVer, 
359
 
                                                     minor = MinVer},
360
 
                         length = Length,
361
 
                         fragment = Data},
362
 
    get_tls_records_aux(Rest, [C | Acc]);
363
 
get_tls_records_aux(<<?BYTE(_CT), ?BYTE(_MajVer), ?BYTE(_MinVer),
 
288
get_tls_records_aux(<<0:1, _CT:7, ?BYTE(_MajVer), ?BYTE(_MinVer),
364
289
                     ?UINT16(Length), _/binary>>,
365
290
                    _Acc) when Length > ?MAX_CIPHER_TEXT_LENGTH->
366
 
    error;                                        % TODO appropriate error code
 
291
    ?ALERT_REC(?FATAL, ?RECORD_OVERFLOW);
 
292
 
 
293
get_tls_records_aux(<<1:1, Length0:15, _/binary>>,_Acc) 
 
294
  when Length0 > ?MAX_CIPHER_TEXT_LENGTH->
 
295
    ?ALERT_REC(?FATAL, ?RECORD_OVERFLOW);
 
296
 
367
297
get_tls_records_aux(Data, Acc) ->
368
298
    {lists:reverse(Acc), Data}.
369
299
 
375
305
%% or vice versa.
376
306
%%--------------------------------------------------------------------
377
307
protocol_version('tlsv1.1') ->
378
 
    #protocol_version{major = 3, minor = 2};
 
308
    {3, 2};
379
309
protocol_version(tlsv1) ->
380
 
    #protocol_version{major = 3, minor = 1};
 
310
    {3, 1};
381
311
protocol_version(sslv3) ->
382
 
    #protocol_version{major = 3, minor = 0};
 
312
    {3, 0};
383
313
protocol_version(sslv2) ->
384
 
    #protocol_version{major = 2, minor = 0};
385
 
protocol_version(#protocol_version{major = 3, minor = 2}) ->
 
314
    {2, 0};
 
315
protocol_version({3, 2}) ->
386
316
    'tlsv1.1';
387
 
protocol_version(#protocol_version{major = 3, minor = 1}) ->
 
317
protocol_version({3, 1}) ->
388
318
    tlsv1;
389
 
protocol_version(#protocol_version{major = 3, minor = 0}) ->
 
319
protocol_version({3, 0}) ->
390
320
    sslv3;
391
 
protocol_version(#protocol_version{major = 2, minor = 0}) ->
 
321
protocol_version({2, 0}) ->
392
322
    sslv2.
393
323
%%--------------------------------------------------------------------
394
324
%% Function: protocol_version(Version1, Version2) -> #protocol_version{}
396
326
%%     
397
327
%% Description: Lowes protocol version of two given versions 
398
328
%%--------------------------------------------------------------------
399
 
lowest_protocol_version(Version = #protocol_version{major = M, minor = N}, 
400
 
                        #protocol_version{major = M, minor = O}) 
401
 
  when N < O ->
402
 
    Version;
403
 
lowest_protocol_version(#protocol_version{major = M, minor = _}, 
404
 
                        Version = #protocol_version{major = M, minor = _}) ->
405
 
    Version;
406
 
lowest_protocol_version(Version = #protocol_version{major = M}, 
407
 
                        #protocol_version{major = N}) when M < N ->
 
329
lowest_protocol_version(Version = {M, N}, {M, O})   when N < O ->
 
330
    Version;
 
331
lowest_protocol_version({M, _}, 
 
332
                        Version = {M, _}) ->
 
333
    Version;
 
334
lowest_protocol_version(Version = {M,_}, 
 
335
                        {N, _}) when M < N ->
408
336
    Version;
409
337
lowest_protocol_version(_,Version) ->
410
338
    Version.
414
342
%%     
415
343
%% Description: Highest protocol version present in a list
416
344
%%--------------------------------------------------------------------
 
345
highest_protocol_version([]) ->
 
346
    highest_protocol_version();
417
347
highest_protocol_version(Versions) ->
418
348
    [Ver | Vers] = Versions,
419
349
    highest_protocol_version(Ver, Vers).
420
350
 
421
351
highest_protocol_version(Version, []) ->
422
352
    Version;
423
 
highest_protocol_version(Version = #protocol_version{major = N, 
424
 
                                                     minor = M}, 
425
 
                         [#protocol_version{major = N, 
426
 
                                            minor = O} | Rest]) 
427
 
  when M > O ->
428
 
    highest_protocol_version(Version, Rest);
429
 
highest_protocol_version(#protocol_version{major = M, 
430
 
                                           minor = _}, 
431
 
                         [Version = 
432
 
                          #protocol_version{major = M, 
433
 
                                            minor = _} | Rest]) ->
434
 
    highest_protocol_version(Version, Rest);
435
 
highest_protocol_version(Version = #protocol_version{major = M}, 
436
 
                         [#protocol_version{major = N} | Rest]) 
437
 
  when M > N ->
 
353
highest_protocol_version(Version = {N, M}, [{N, O} | Rest])   when M > O ->
 
354
    highest_protocol_version(Version, Rest);
 
355
highest_protocol_version({M, _}, [Version = {M, _} | Rest]) ->
 
356
    highest_protocol_version(Version, Rest);
 
357
highest_protocol_version(Version = {M,_}, [{N,_} | Rest])  when M > N ->
438
358
    highest_protocol_version(Version, Rest);
439
359
highest_protocol_version(_, [Version | Rest]) ->
440
360
    highest_protocol_version(Version, Rest).
447
367
%%--------------------------------------------------------------------
448
368
supported_protocol_versions() ->
449
369
    Fun = fun(Version) ->
450
 
                  ssl_record:protocol_version(Version)
 
370
                  protocol_version(Version)
451
371
          end,
452
372
    case application:get_env(ssl, protocol_version) of
453
373
        undefined ->
461
381
    end.
462
382
 
463
383
%%--------------------------------------------------------------------
464
 
%% Function: protocol_version(Versions) -> #protocol_version{}
465
 
%%     Versions = [#protocol_version{}]
466
 
%%     
467
 
%% Description: Highest protocol version supported
468
 
%%--------------------------------------------------------------------
469
 
highest_protocol_version() ->
470
 
    highest_protocol_version(supported_protocol_versions()).
471
 
 
472
 
%%--------------------------------------------------------------------
473
384
%% Function: is_acceptable_version(Version) -> true | false
474
385
%%     Version = #protocol_version{}
475
386
%%     
476
387
%% Description: ssl version 2 is not acceptable security risks are too big.
477
388
%%--------------------------------------------------------------------
478
 
is_acceptable_version(#protocol_version{major = N}) 
 
389
is_acceptable_version({N,_}) 
479
390
  when N >= ?LOWEST_MAJOR_SUPPORTED_VERSION ->
480
391
    true;
481
392
is_acceptable_version(_) ->
482
393
    false.
483
394
 
484
395
%%--------------------------------------------------------------------
485
 
%% Function: random() -> 32-bytes binary()
486
 
%%     
487
 
%% Description: generates a random binary for the hello-messages
488
 
%%--------------------------------------------------------------------
489
 
random() ->
490
 
    Secs_since_1970 = calendar:datetime_to_gregorian_seconds(
491
 
                        calendar:universal_time()) - 62167219200,
492
 
    Random_28_bytes = crypto:rand_bytes(28),
493
 
    <<?UINT32(Secs_since_1970), Random_28_bytes/binary>>.
494
 
 
495
 
%%--------------------------------------------------------------------
496
396
%% Function: compressions() -> binary()
497
397
%%     
498
398
%% Description: return a list of compressions supported (currently none)
501
401
    [?byte(?NULL)].
502
402
 
503
403
%%--------------------------------------------------------------------
504
 
%% Function: uncompress(Method, #tls_compressed{}, CompressionState)
505
 
%%           -> {#tls_plain_text, NewCompState}
506
 
%%     
507
 
%% expand compressed data using given compression
508
 
%%--------------------------------------------------------------------
509
 
uncompress(?NULL, #tls_compressed{type = Type,
510
 
                                  version = Version,
511
 
                                  length = Length,
512
 
                                  fragment = Fragment}, CS) ->
513
 
    {#tls_plain_text{type = Type,
514
 
                     version = Version,
515
 
                     length = Length,
516
 
                     fragment = Fragment}, CS}.
517
 
 
518
 
 
519
 
%%--------------------------------------------------------------------
520
 
%% Function: compress(Method, #tls_plain_text{}, CompressionState)
521
 
%%           -> {#tls_compressed, NewCompState}
522
 
%%     
523
 
%% compress data using given compression
524
 
%%--------------------------------------------------------------------
525
 
compress(?NULL, #tls_plain_text{type = Type,
526
 
                                version = Version,
527
 
                                length = Length,
528
 
                                fragment = Fragment}, CS) ->
529
 
    {#tls_compressed{type = Type,
530
 
                     version = Version,
531
 
                     length = Length,
532
 
                     fragment = Fragment}, CS}.
533
 
 
534
 
%%--------------------------------------------------------------------
535
 
%% Function: cipher(Method, #tls_compressed{}, ConnectionState)
536
 
%%                  {#tls_cipher_text, NewConnectionState}
537
 
%%
538
 
%%
539
 
%%--------------------------------------------------------------------
540
 
cipher(#tls_compressed{type = Type, version = Version,
541
 
                       length = Length, fragment = Fragment}, CS0) ->
542
 
    {Hash, CS1} = hash_and_bump_seqno(CS0, Type, Version, Length, Fragment),
543
 
    SP = CS1#connection_state.security_parameters,
544
 
    CipherS0 = CS1#connection_state.cipher_state,
545
 
    BCA = SP#security_parameters.bulk_cipher_algorithm,
546
 
    ?DBG_HEX(Fragment),
547
 
    {Ciphered, CipherS1} = ssl_cipher:cipher(BCA, CipherS0, Hash, Fragment),
548
 
    ?DBG_HEX(Ciphered),
549
 
    CS2 = CS1#connection_state{cipher_state=CipherS1},
550
 
    {#tls_cipher_text{type = Type,
551
 
                      version = Version,
552
 
                      length = erlang:iolist_size(Ciphered),
553
 
                      cipher = BCA, %% TODO, kolla om det är BCA det ska vara...
554
 
                      fragment = Ciphered}, CS2}.
555
 
 
556
 
%%--------------------------------------------------------------------
557
 
%% Function: decipher(Method, #tls_cipher_text{}, ConnectionState)
558
 
%%           -> {#tls_compressed, NewConnectionState}
559
 
%%
560
 
%%
561
 
%%--------------------------------------------------------------------
562
 
decipher(#tls_cipher_text{type = Type,
563
 
                          version = Version,
564
 
                          length = Length,
565
 
                          cipher = _Cipher,
566
 
                          fragment = Fragment}, CS)
567
 
  when Type == ?CHANGE_CIPHER_SPEC ->
568
 
    %% These are never encrypted
569
 
    {#tls_compressed{type = Type,
570
 
                     version = Version,
571
 
                     length = Length,
572
 
                     fragment = erlang:iolist_to_binary(Fragment)}, CS};                          
573
 
decipher(#tls_cipher_text{type = Type,
574
 
                          version = Version,
575
 
                          %%length = Length,
576
 
                          cipher = _Cipher,
577
 
                          fragment = Fragment}, CS0) ->
578
 
    SP = CS0#connection_state.security_parameters,
579
 
    BCA = SP#security_parameters.bulk_cipher_algorithm, % eller Cipher?
580
 
    HashSz = SP#security_parameters.hash_size,
581
 
    CipherS0 = CS0#connection_state.cipher_state,
582
 
    {T, Mac, CipherS1} = ssl_cipher:decipher(BCA, HashSz, CipherS0, Fragment),
583
 
    CS1 = CS0#connection_state{cipher_state = CipherS1},
584
 
    TLength = size(T),
585
 
    {Hash, CS2} = hash_and_bump_seqno(CS1, Type, Version, TLength, Fragment),
586
 
    ok = check_hash(Hash, Mac),
587
 
    {#tls_compressed{type = Type,
588
 
                     version = Version,
589
 
                     length = TLength,
590
 
                     fragment = T}, CS2}.
591
 
 
592
 
check_hash(_, _) ->
593
 
    ok. %% TODO kolla också
 
404
%% Function: decode_cipher_text(CipherText, ConnectionStates0) -> 
 
405
%%                                     {Plain, ConnectionStates}
 
406
%%     
 
407
%% Description: Decode cipher text
 
408
%%--------------------------------------------------------------------
 
409
decode_cipher_text(CipherText, ConnnectionStates0) ->
 
410
    ReadState0 = ConnnectionStates0#connection_states.current_read,
 
411
    #connection_state{compression_state = CompressionS0,
 
412
                      security_parameters = SecParams} = ReadState0,
 
413
    CompressAlg = SecParams#security_parameters.compression_algorithm,
 
414
    {Compressed, ReadState1} = decipher(CipherText, ReadState0),
 
415
    {Plain, CompressionS1} = uncompress(CompressAlg, 
 
416
                                        Compressed, CompressionS0),
 
417
    ConnnectionStates = ConnnectionStates0#connection_states{
 
418
             current_read = ReadState1#connection_state{
 
419
                              compression_state = CompressionS1}},
 
420
    {Plain, ConnnectionStates}.
594
421
 
595
422
%%--------------------------------------------------------------------
596
423
%%% Internal functions
597
424
%%--------------------------------------------------------------------
 
425
highest_protocol_version() ->
 
426
    highest_protocol_version(supported_protocol_versions()).
598
427
 
599
428
initial_connection_state(ConnectionEnd) ->
600
429
    #connection_state{security_parameters =
620
449
empty_security_params(ConnectionEnd = ?SERVER) ->
621
450
    #security_parameters{connection_end = ConnectionEnd,
622
451
                         server_random = random()}.
 
452
random() ->
 
453
    Secs_since_1970 = calendar:datetime_to_gregorian_seconds(
 
454
                        calendar:universal_time()) - 62167219200,
 
455
    Random_28_bytes = crypto:rand_bytes(28),
 
456
    <<?UINT32(Secs_since_1970), Random_28_bytes/binary>>.
623
457
 
624
458
record_protocol_role(client) ->
625
459
    ?CLIENT;
639
473
            lists:reverse(Acc, [Bin])
640
474
    end.
641
475
 
 
476
encode_data(Frag, Version, ConnectionStates) 
 
477
  when erlang:byte_size(Frag) < (?MAX_PLAIN_TEXT_LENGTH - 2048) -> 
 
478
    encode_plain_text(?APPLICATION_DATA,Version,Frag,ConnectionStates);
642
479
encode_data(Frag, Version, ConnectionStates) ->
643
 
    Bin = erlang:iolist_to_binary(Frag),
644
 
    Data = split_bin(Bin, ?MAX_PLAIN_TEXT_LENGTH-2048),
 
480
    Data = split_bin(Frag, ?MAX_PLAIN_TEXT_LENGTH - 2048),
645
481
    {CS1, Acc} = 
646
482
        lists:foldl(fun(B, {CS0, Acc}) ->
647
 
                            T = #tls_plain_text{type = ?APPLICATION_DATA, 
648
 
                                                version = Version,
649
 
                                                length = size(B), 
650
 
                                                fragment = B},
651
 
                            {ET, CS1} = encode_plain_text(T, CS0),
 
483
                            {ET, CS1} = 
 
484
                                encode_plain_text(?APPLICATION_DATA,
 
485
                                                  Version, B, CS0),
652
486
                            {CS1, [ET | Acc]}
653
487
                    end, {ConnectionStates, []}, Data),
654
488
    {lists:reverse(Acc), CS1}.
655
489
 
656
490
encode_handshake(Frag, Version, ConnectionStates) ->
657
 
    PT = #tls_plain_text{type = ?HANDSHAKE,
658
 
                         version = Version,
659
 
                         length = erlang:iolist_size(Frag),
660
 
                         fragment = Frag},
661
 
    encode_plain_text(PT, ConnectionStates).
 
491
    encode_plain_text(?HANDSHAKE, Version, Frag, ConnectionStates).
662
492
 
663
493
encode_alert_record(#alert{level = Level, description = Description},
664
494
                    Version, ConnectionStates) ->
665
 
    PT = #tls_plain_text{type = ?ALERT,
666
 
                         version = Version,
667
 
                         length = 2,
668
 
                         fragment = <<?BYTE(Level), ?BYTE(Description)>>},
669
 
    encode_plain_text(PT, ConnectionStates).
 
495
    encode_plain_text(?ALERT, Version, <<?BYTE(Level), ?BYTE(Description)>>, 
 
496
                      ConnectionStates).
670
497
 
671
498
encode_change_cipher_spec(Version, ConnectionStates) ->
672
 
    PT = #tls_plain_text{type = ?CHANGE_CIPHER_SPEC,
673
 
                         version = Version,
674
 
                         length = 1,
675
 
                         fragment = [1]},
676
 
    encode_plain_text(PT, ConnectionStates).
 
499
    encode_plain_text(?CHANGE_CIPHER_SPEC, Version, <<1:8>>, ConnectionStates).
677
500
 
678
 
encode_plain_text(PT, ConnectionStates) ->
679
 
    CS0 = ConnectionStates#connection_states.current_write,
680
 
    CompS0 = CS0#connection_state.compression_state,
681
 
    SecParams = (CS0#connection_state.security_parameters),
682
 
    CompAlg = SecParams#security_parameters.compression_algorithm,
683
 
    {Comp, CompS1} = compress(CompAlg, PT, CompS0),
 
501
encode_plain_text(Type, Version, Data, ConnectionStates) ->
 
502
    #connection_states{current_write=#connection_state{
 
503
                         compression_state=CompS0,
 
504
                         security_parameters=
 
505
                         #security_parameters{compression_algorithm=CompAlg}
 
506
                        }=CS0} = ConnectionStates,
 
507
    {Comp, CompS1} = compress(CompAlg, Data, CompS0),
684
508
    CS1 = CS0#connection_state{compression_state = CompS1},
685
 
    {CipherText, CS2} = cipher(Comp, CS1),
686
 
    CTBin = encode_tls_cipher_text(CipherText),
 
509
    {CipherText, CS2} = cipher(Type, Version, Comp, CS1),
 
510
    CTBin = encode_tls_cipher_text(Type, Version, CipherText),
687
511
    {CTBin, ConnectionStates#connection_states{current_write = CS2}}.
688
512
 
689
 
encode_tls_cipher_text(#tls_cipher_text{type = Type,
690
 
                                        version = Version,
691
 
                                        length = Length,
692
 
                                        fragment = Fragment}) ->
693
 
    #protocol_version{major = MajVer, minor = MinVer} = Version,
694
 
    [?byte(Type), ?byte(MajVer), ?byte(MinVer), ?uint16(Length), Fragment].
695
 
 
696
 
decode_cipher_text(CipherText, CSs0) ->
697
 
    CR0 = CSs0#connection_states.current_read,
698
 
    #connection_state{compression_state = CompressionS0,
699
 
                      security_parameters = SP} = CR0,
700
 
    CA = SP#security_parameters.compression_algorithm,
701
 
    {Compressed, CR1} = decipher(CipherText, CR0),
702
 
    {Plain, CompressionS1} = uncompress(CA, Compressed, CompressionS0),
703
 
    CSs1 = CSs0#connection_states{
704
 
             current_read = CR1#connection_state{
705
 
                              compression_state = CompressionS1}},
706
 
    {Plain, CSs1}.
 
513
encode_tls_cipher_text(Type,{MajVer,MinVer},Fragment) ->
 
514
    Length = erlang:iolist_size(Fragment),
 
515
    [<<?BYTE(Type), ?BYTE(MajVer), ?BYTE(MinVer), ?UINT16(Length)>>, Fragment].
 
516
 
 
517
cipher(Type, Version, Fragment, CS0) ->
 
518
    Length =  erlang:iolist_size(Fragment),
 
519
    {Hash, CS1=#connection_state{cipher_state = CipherS0,
 
520
                                 security_parameters=
 
521
                                 #security_parameters{bulk_cipher_algorithm = 
 
522
                                                      BCA}
 
523
                                }} = 
 
524
        hash_and_bump_seqno(CS0, Type, Version, Length, Fragment),
 
525
    ?DBG_HEX(Fragment),
 
526
    {Ciphered, CipherS1} = ssl_cipher:cipher(BCA, CipherS0, Hash, Fragment),
 
527
    ?DBG_HEX(Ciphered),
 
528
    CS2 = CS1#connection_state{cipher_state=CipherS1},
 
529
    {Ciphered, CS2}.
 
530
 
 
531
decipher(TLS=#ssl_tls{type = ?CHANGE_CIPHER_SPEC}, CS) ->
 
532
    %% These are never encrypted
 
533
    {TLS, CS};
 
534
decipher(TLS=#ssl_tls{type=Type, version=Version, fragment=Fragment}, CS0) ->
 
535
    SP = CS0#connection_state.security_parameters,
 
536
    BCA = SP#security_parameters.bulk_cipher_algorithm, % eller Cipher?
 
537
    HashSz = SP#security_parameters.hash_size,
 
538
    CipherS0 = CS0#connection_state.cipher_state,
 
539
    {T, Mac, CipherS1} = ssl_cipher:decipher(BCA, HashSz, CipherS0, Fragment),
 
540
    CS1 = CS0#connection_state{cipher_state = CipherS1},
 
541
    TLength = size(T),
 
542
    {Hash, CS2} = hash_and_bump_seqno(CS1, Type, Version, TLength, Fragment),
 
543
    ok = check_hash(Hash, Mac),
 
544
    {TLS#ssl_tls{fragment = T}, CS2}.
 
545
 
 
546
uncompress(?NULL, Data = #ssl_tls{type = _Type,
 
547
                                  version = _Version,
 
548
                                  fragment = _Fragment}, CS) ->
 
549
    {Data, CS}.
 
550
 
 
551
compress(?NULL, Data, CS) ->
 
552
    {Data, CS}.
707
553
 
708
554
hash_and_bump_seqno(#connection_state{sequence_number = SeqNo,
709
 
                                               mac_secret = MacSecret,
710
 
                                               security_parameters = 
711
 
                                               SecPars} = CS0,
 
555
                                      mac_secret = MacSecret,
 
556
                                      security_parameters = 
 
557
                                      SecPars} = CS0,
712
558
                    Type, Version, Length, Fragment) ->
713
 
    Hash = ssl_cipher:mac_hash(SecPars#security_parameters.mac_algorithm,
714
 
                               Version, MacSecret, SeqNo, Type,
715
 
                               Length, Fragment),
 
559
    Hash = mac_hash(Version, 
 
560
                    SecPars#security_parameters.mac_algorithm,
 
561
                    MacSecret, SeqNo, Type,
 
562
                    Length, Fragment),
716
563
    {Hash, CS0#connection_state{sequence_number = SeqNo+1}}.
 
564
 
 
565
check_hash(_, _) ->
 
566
    ok. %% TODO check this 
 
567
 
 
568
mac_hash(?NULL, {_,_}, _MacSecret, _SeqNo, _Type,
 
569
         _Length, _Fragment) ->
 
570
    <<>>;
 
571
mac_hash({3, 0}, MacAlg, MacSecret, SeqNo, Type, Length, Fragment) ->
 
572
    ssl_ssl3:mac_hash(MacAlg, MacSecret, SeqNo, Type, Length, Fragment);
 
573
mac_hash({3, N} = Version, MacAlg, MacSecret, SeqNo, Type, Length, Fragment)  
 
574
  when  N == 1; N == 2 ->
 
575
    ssl_tls1:mac_hash(MacAlg, MacSecret, SeqNo, Type, Version, 
 
576
                      Length, Fragment).