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

« back to all changes in this revision

Viewing changes to lib/ssl/src/ssl.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>1999-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 : Main API module for SSL.
43
45
%% Function: start([, Type]) -> ok
44
46
%%
45
47
%%  Type =  permanent | transient | temporary
 
48
%%  Vsns = [Vsn] 
 
49
%%  Vsn = ssl3 | tlsv1 | 'tlsv1.1'
46
50
%%
47
51
%% Description: Starts the ssl application. Default type
48
52
%% is temporary. see application(3)
289
293
        {ok, undefined} ->
290
294
            {error, no_peercert};
291
295
        {ok, BinCert} ->
292
 
            ssl_pkix:decode_cert(BinCert, Opts);
 
296
            PKOpts = [case Opt of ssl -> otp; pkix -> plain end || 
 
297
                         Opt <- Opts, Opt =:= ssl orelse Opt =:= pkix],
 
298
            case PKOpts of
 
299
                [Opt] ->
 
300
                    public_key:pkix_decode_cert(BinCert, Opt);
 
301
                [] ->
 
302
                    {ok, BinCert}
 
303
            end;
293
304
        {error, Reason}  ->
294
305
            {error, Reason}
295
306
    end;
324
335
    cipher_suites(erlang).
325
336
  
326
337
cipher_suites(erlang) ->
327
 
    Version = ssl_record:highest_protocol_version(),
 
338
    Version = ssl_record:highest_protocol_version([]),
328
339
    [ssl_cipher:suite_definition(S) || S <- ssl_cipher:suites(Version)];    
329
340
 
330
341
cipher_suites(openssl) ->
331
 
    Version = ssl_record:highest_protocol_version(),
 
342
    Version = ssl_record:highest_protocol_version([]),
332
343
    [ssl_cipher:openssl_suite_name(S) || S <- ssl_cipher:suites(Version)].
333
344
 
334
345
%%--------------------------------------------------------------------
411
422
%% Description: Returns a list of relevant versions.
412
423
%%--------------------------------------------------------------------
413
424
versions() ->
414
 
%%     TODO: uncomment rel imp when all protocolversions are supported    
415
 
%%     Vsns = ssl_record:supported_protocol_versions(),
416
 
%%     SupportedVsns =  lists:map(fun(Version) -> 
417
 
%%                                     ssl_record:protocol_version(Version)
418
 
%%                             end, Vsns),
419
 
%%     AvailableVsns = ?DEFAULT_SUPPORTED_VERSIONS,
420
 
    SupportedVsns = [sslv3], AvailableVsns = [sslv3],
421
 
    [{ssl_app, ?VSN}, {supported, SupportedVsns}, {available, AvailableVsns}].
 
425
    Vsns = ssl_record:supported_protocol_versions(),
 
426
    SupportedVsns =  lists:map(fun(Version) -> 
 
427
                                       ssl_record:protocol_version(Version)
 
428
                               end, Vsns),
 
429
    AvailableVsns = ?DEFAULT_SUPPORTED_VERSIONS,
 
430
    [{ssl_app, ?VSN}, {supported, SupportedVsns}, 
 
431
     {available, AvailableVsns}].
422
432
 
423
433
%%%--------------------------------------------------------------
424
434
%%% Internal functions
490
500
    ssl_broker:listen(Pid, Port, Options).
491
501
 
492
502
handle_options(Opts0) ->
493
 
    Opts = proplists:expand([{binary, {mode, binary}},
494
 
                             {list, {mode, list}}], Opts0),
 
503
    Opts = proplists:expand([{binary, [{mode, binary}]},
 
504
                             {list, [{mode, list}]}], Opts0),
 
505
    
 
506
    ReuseSessionFun = fun(_, _, _, _) ->
 
507
                              true
 
508
                      end,
 
509
 
 
510
    VerifyFun =  fun(_) ->
 
511
                         false
 
512
                 end,
 
513
 
 
514
 
 
515
    {Verify, FailIfNoPeerCert} = 
 
516
        %% Handle 0, 1, 2 for backwards compatibility
 
517
        case proplists:get_value(verify, Opts, verify_none) of
 
518
            0 ->
 
519
                {verify_none, false};
 
520
            1  ->
 
521
                {verify_peer, false};
 
522
            2 ->
 
523
                {verify_peer, true};
 
524
            verify_none ->
 
525
                {verify_none, false};
 
526
            verify_peer ->
 
527
                {verify_peer, proplists:get_value(fail_if_no_peer_cert,
 
528
                                                  Opts, false)};
 
529
            Value ->
 
530
                throw({error, {eoptions, {verify, Value}}})
 
531
        end,   
 
532
 
495
533
    SSLOptions = #ssl_options{
496
 
      verify     = handle_option(verify, Opts, 0), 
 
534
      versions   = handle_option(versions, Opts, []),
 
535
      verify     = validate_option(verify, Verify),
 
536
      verify_fun = handle_option(verify_fun, Opts, VerifyFun),
 
537
      fail_if_no_peer_cert = validate_option(fail_if_no_peer_cert, 
 
538
                                             FailIfNoPeerCert),
 
539
      verify_client_once =  handle_option(verify_client_once, Opts, false),
497
540
      depth      = handle_option(depth,  Opts, 1),
498
541
      certfile   = handle_option(certfile, Opts, ""),
499
542
      keyfile    = handle_option(keyfile,  Opts, ""),
501
544
      password   = handle_option(password, Opts, ""),
502
545
      cacertfile = handle_option(cacertfile, Opts, ""),
503
546
      ciphers    = handle_option(ciphers, Opts, []),
 
547
      %% Server side option
 
548
      reuse_session = handle_option(reuse_session, Opts, ReuseSessionFun),
504
549
      reuse_sessions = handle_option(reuse_sessions, Opts, true),
505
550
      debug      = handle_option(debug, Opts, [])
506
551
     },
511
556
      active  = handle_option(active, Opts, true)
512
557
     },
513
558
    
514
 
    SslOREmulated = [verify, depth, certfile, keyfile,
 
559
    SslOREmulated = [versions, verify, verify_fun, 
 
560
                     depth, certfile, keyfile,
515
561
                     key, password, cacertfile, ciphers,
516
562
                     debug, mode, packet, header, active,
517
 
                     reuse_sessions, ssl_imp],
 
563
                     reuse_session, reuse_sessions, ssl_imp],
518
564
 
519
565
    SockOpts = lists:foldl(fun(Key, PropList) -> 
520
566
                                    proplists:delete(Key, PropList)
526
572
    validate_option(OptionName, 
527
573
                    proplists:get_value(OptionName, Opts, Default)).
528
574
 
 
575
 
 
576
validate_option(versions, Versions)  ->
 
577
    validate_versions(Versions, Versions);
529
578
validate_option(ssl_imp, Value) when Value == new; Value == old ->
530
579
    Value;
531
 
validate_option(verify, Value) when Value == 0; 
532
 
                                    Value == 1;
533
 
                                    Value == 2 ->
 
580
validate_option(verify, Value) 
 
581
  when Value == verify_none; Value == verify_peer ->
 
582
    Value;
 
583
validate_option(verify_fun, Value) when is_function(Value) ->
534
584
   Value;
 
585
validate_option(fail_if_no_peer_cert, Value) 
 
586
  when Value == true; Value == false ->
 
587
    Value;
 
588
validate_option(verify_client_once, Value) 
 
589
  when Value == true; Value == false ->
 
590
    Value;
535
591
validate_option(depth, Value) when is_integer(Value), 
536
592
                                   Value >= 0, Value =< 255->
537
593
    Value;
548
604
validate_option(cacertfile, Value) when is_list(Value), Value =/= "" ->
549
605
    Value;
550
606
validate_option(ciphers, Value)  when is_list(Value) ->
551
 
    Version = ssl_record:highest_protocol_version(),
 
607
    Version = ssl_record:highest_protocol_version([]),
552
608
    try cipher_suites(Version, Value) of
553
609
        Ciphers ->
554
610
            Ciphers
557
613
            throw({error, {eoptions, {ciphers, Value}}})
558
614
    end;
559
615
 
 
616
validate_option(reuse_session, Value) when is_function(Value) ->
 
617
    Value;
 
618
 
560
619
validate_option(reuse_sessions, Value) when Value == true; 
561
620
                                            Value == false ->
562
621
    Value;
569
628
                                    Value == 1;
570
629
                                    Value == 2;
571
630
                                    Value == 4;
 
631
                                    Value == asn1;
 
632
                                    Value == fcgi;
 
633
                                    Value == sunrm;
 
634
                                    Value == http;
 
635
                                    Value == httph;
572
636
                                    Value == cdr;
 
637
                                    Value == tpkt;
573
638
                                    Value == line  ->
574
639
    Value;
575
640
validate_option(header, Value)  when is_integer(Value) ->
584
649
validate_option(Opt, Value) ->
585
650
    throw({error, {eoptions, {Opt, Value}}}).
586
651
    
 
652
validate_versions([], Versions) ->
 
653
    Versions;
 
654
validate_versions([Version | Rest], Versions) when Version == 'tlsv1.1'; 
 
655
                                                   Version == tlsv1; 
 
656
                                                   Version == sslv3 ->
 
657
    validate_versions(Rest, Versions);                                     
 
658
validate_versions(Ver, Versions) ->
 
659
    throw({error, {eoptions, {Ver, {versions, Versions}}}}).
 
660
 
 
661
 
587
662
listen_options({_, _, InetOpts}) ->
588
663
    %% Packet, mode, active and header must be  
589
664
    %% emulated. 
601
676
    [mode, packet, active, header].
602
677
 
603
678
internal_inet_values() ->
604
 
    [{packet, 0}, {header, 0},{active, false}, {mode, binary}].
 
679
    [{packet, 0},{header, 0},{active, false},{mode,binary}].
 
680
    %%[{packet, ssl},{header, 0},{active, false},{mode,binary}].
605
681
 
606
682
ssl_connection_options({SslOpts, SocketOpts, _}) ->
607
683
    {SslOpts, SocketOpts}.