Skip to content

Commit

Permalink
ssl: Honor TLS client ECC extension
Browse files Browse the repository at this point in the history
  • Loading branch information
IngelaAndin committed Oct 7, 2013
1 parent 50e91bd commit c07225b
Show file tree
Hide file tree
Showing 5 changed files with 66 additions and 51 deletions.
2 changes: 1 addition & 1 deletion lib/ssl/src/ssl_cipher.erl
Expand Up @@ -34,7 +34,7 @@

-export([security_parameters/2, security_parameters/3, suite_definition/1,
decipher/5, cipher/5,
suite/1, suites/1, anonymous_suites/0, psk_suites/1, srp_suites/0,
suite/1, suites/1, ec_keyed_suites/0, anonymous_suites/0, psk_suites/1, srp_suites/0,
openssl_suite/1, openssl_suite_name/1, filter/2, filter_suites/1,
hash_algorithm/1, sign_algorithm/1, is_acceptable_hash/2]).

Expand Down
74 changes: 48 additions & 26 deletions lib/ssl/src/ssl_handshake.erl
Expand Up @@ -49,13 +49,13 @@
]).

%% Cipher suites handling
-export([available_suites/2, available_suites/3, cipher_suites/2,
select_session/10]).
-export([available_suites/2, cipher_suites/2,
select_session/10, supported_ecc/1]).

%% Extensions handling
-export([client_hello_extensions/5,
handle_client_hello_extensions/8, %% Returns server hello extensions
handle_server_hello_extensions/9
handle_server_hello_extensions/9, select_curve/2
]).

%% MISC
Expand Down Expand Up @@ -89,7 +89,7 @@ client_hello_extensions(Version, CipherSuites, SslOpts, ConnectionStates, Renego
{EcPointFormats, EllipticCurves} =
case advertises_ec_ciphers(lists:map(fun ssl_cipher:suite_definition/1, CipherSuites)) of
true ->
ecc_extensions(tls_v1, Version);
client_ecc_extensions(tls_v1, Version);
false ->
{undefined, undefined}
end,
Expand Down Expand Up @@ -861,22 +861,29 @@ available_suites(UserSuites, Version) ->
UserSuites
end.

available_suites(ServerCert, UserSuites, Version) ->
ssl_cipher:filter(ServerCert, available_suites(UserSuites, Version)).
available_suites(ServerCert, UserSuites, Version, Curve) ->
ssl_cipher:filter(ServerCert, available_suites(UserSuites, Version))
-- unavailable_ecc_suites(Curve).

unavailable_ecc_suites(no_curve) ->
ssl_cipher:ec_keyed_suites();
unavailable_ecc_suites(_) ->
[].

cipher_suites(Suites, false) ->
[?TLS_EMPTY_RENEGOTIATION_INFO_SCSV | Suites];
cipher_suites(Suites, true) ->
Suites.

select_session(SuggestedSessionId, CipherSuites, Compressions, Port, Session, Version,
select_session(SuggestedSessionId, CipherSuites, Compressions, Port, #session{ecc = ECCCurve} =
Session, Version,
#ssl_options{ciphers = UserSuites} = SslOpts, Cache, CacheCb, Cert) ->
{SessionId, Resumed} = ssl_session:server_id(Port, SuggestedSessionId,
SslOpts, Cert,
Cache, CacheCb),
Suites = ssl_handshake:available_suites(Cert, UserSuites, Version),
case Resumed of
undefined ->
Suites = available_suites(Cert, UserSuites, Version, ECCCurve),
CipherSuite = select_cipher_suite(CipherSuites, Suites),
Compression = select_compression(Compressions),
{new, Session#session{session_id = SessionId,
Expand All @@ -886,6 +893,13 @@ select_session(SuggestedSessionId, CipherSuites, Compressions, Port, Session, Ve
{resumed, Resumed}
end.

supported_ecc(Version) ->
case tls_v1:ecc_curves(Version) of
[] ->
undefined;
Curves ->
#elliptic_curves{elliptic_curve_list = Curves}
end.
%%-------------certificate handling --------------------------------

certificate_types({KeyExchange, _, _, _})
Expand Down Expand Up @@ -926,9 +940,8 @@ certificate_authorities_from_db(CertDbHandle, CertDbRef) ->
handle_client_hello_extensions(RecordCB, Random,
#hello_extensions{renegotiation_info = Info,
srp = SRP,
next_protocol_negotiation = NextProtocolNegotiation,
ec_point_formats = EcPointFormats0,
elliptic_curves = EllipticCurves0}, Version,
ec_point_formats = ECCFormat,
next_protocol_negotiation = NextProtocolNegotiation}, Version,
#ssl_options{secure_renegotiate = SecureRenegotation} = Opts,
#session{cipher_suite = CipherSuite, compression_method = Compression} = Session0,
ConnectionStates0, Renegotiation) ->
Expand All @@ -937,12 +950,11 @@ handle_client_hello_extensions(RecordCB, Random,
Random, CipherSuite, Compression,
ConnectionStates0, Renegotiation, SecureRenegotation),
ProtocolsToAdvertise = handle_next_protocol_extension(NextProtocolNegotiation, Renegotiation, Opts),
{EcPointFormats, EllipticCurves} = handle_ecc_extensions(Version, EcPointFormats0, EllipticCurves0),

ServerHelloExtensions = #hello_extensions{
renegotiation_info = renegotiation_info(RecordCB, server,
ConnectionStates, Renegotiation),
ec_point_formats = EcPointFormats,
elliptic_curves = EllipticCurves,
ec_point_formats = server_ecc_extension(Version, ECCFormat),
next_protocol_negotiation =
encode_protocols_advertised_on_server(ProtocolsToAdvertise)
},
Expand Down Expand Up @@ -1078,7 +1090,7 @@ srp_user(#ssl_options{srp_identity = {UserName, _}}) ->
srp_user(_) ->
undefined.

ecc_extensions(Module, Version) ->
client_ecc_extensions(Module, Version) ->
CryptoSupport = proplists:get_value(public_keys, crypto:supports()),
case proplists:get_bool(ecdh, CryptoSupport) of
true ->
Expand All @@ -1089,27 +1101,20 @@ ecc_extensions(Module, Version) ->
{undefined, undefined}
end.

handle_ecc_extensions(Version, EcPointFormats0, EllipticCurves0) ->
server_ecc_extension(_Version, EcPointFormats) ->
CryptoSupport = proplists:get_value(public_keys, crypto:supports()),
case proplists:get_bool(ecdh, CryptoSupport) of
true ->
EcPointFormats1 = handle_ecc_point_fmt_extension(EcPointFormats0),
EllipticCurves1 = handle_ecc_curves_extension(Version, EllipticCurves0),
{EcPointFormats1, EllipticCurves1};
_ ->
{undefined, undefined}
handle_ecc_point_fmt_extension(EcPointFormats);
false ->
undefined
end.

handle_ecc_point_fmt_extension(undefined) ->
undefined;
handle_ecc_point_fmt_extension(_) ->
#ec_point_formats{ec_point_format_list = [?ECPOINT_UNCOMPRESSED]}.

handle_ecc_curves_extension(_Version, undefined) ->
undefined;
handle_ecc_curves_extension(Version, _) ->
#elliptic_curves{elliptic_curve_list = tls_v1:ecc_curves(Version)}.

advertises_ec_ciphers([]) ->
false;
advertises_ec_ciphers([{ecdh_ecdsa, _,_,_} | _]) ->
Expand All @@ -1124,6 +1129,22 @@ advertises_ec_ciphers([{ecdh_anon, _,_,_} | _]) ->
true;
advertises_ec_ciphers([_| Rest]) ->
advertises_ec_ciphers(Rest).
select_curve(#elliptic_curves{elliptic_curve_list = ClientCurves},
#elliptic_curves{elliptic_curve_list = ServerCurves}) ->
select_curve(ClientCurves, ServerCurves);
select_curve(undefined, _) ->
%% Client did not send ECC extension use default curve if
%% ECC cipher is negotiated
{namedCurve, ?secp256k1};
select_curve(_, []) ->
no_curve;
select_curve(Curves, [Curve| Rest]) ->
case lists:member(Curve, Curves) of
true ->
{namedCurve, Curve};
false ->
select_curve(Curves, Rest)
end.

%%--------------------------------------------------------------------
%%% Internal functions
Expand Down Expand Up @@ -1648,3 +1669,4 @@ advertised_hash_signs({Major, Minor}) when Major >= 3 andalso Minor >= 3 ->
({Hash, _}) -> proplists:get_bool(Hash, Hashs) end, HashSigns)};
advertised_hash_signs(_) ->
undefined.

3 changes: 2 additions & 1 deletion lib/ssl/src/ssl_handshake.hrl
Expand Up @@ -45,7 +45,8 @@
master_secret,
srp_username,
is_resumable,
time_stamp
time_stamp,
ecc
}).

-define(NUM_OF_SESSION_ID_BYTES, 32). % TSL 1.1 & SSL 3
Expand Down
31 changes: 12 additions & 19 deletions lib/ssl/src/tls_connection.erl
Expand Up @@ -97,8 +97,7 @@
terminated = false, %
allow_renegotiate = true,
expecting_next_protocol_negotiation = false :: boolean(),
next_protocol = undefined :: undefined | binary(),
client_ecc % {Curves, PointFmt}
next_protocol = undefined :: undefined | binary()
}).

-define(DEFAULT_DIFFIE_HELLMAN_PARAMS,
Expand Down Expand Up @@ -405,26 +404,24 @@ hello(#server_hello{cipher_suite = CipherSuite,
hello(Hello = #client_hello{client_version = ClientVersion,
extensions = #hello_extensions{hash_signs = HashSigns}},
State = #state{connection_states = ConnectionStates0,
port = Port, session = #session{own_certificate = Cert} = Session0,
port = Port,
session = #session{own_certificate = Cert} = Session0,
renegotiation = {Renegotiation, _},
session_cache = Cache,
session_cache_cb = CacheCb,
ssl_options = SslOpts}) ->
HashSign = ssl_handshake:select_hashsign(HashSigns, Cert),
case tls_handshake:hello(Hello, SslOpts, {Port, Session0, Cache, CacheCb,
ConnectionStates0, Cert}, Renegotiation) of
ConnectionStates0, Cert}, Renegotiation) of
{Version, {Type, #session{cipher_suite = CipherSuite} = Session},
ConnectionStates,
#hello_extensions{ec_point_formats = EcPointFormats,
elliptic_curves = EllipticCurves} = ServerHelloExt} ->
ConnectionStates, ServerHelloExt} ->
{KeyAlg, _, _, _} = ssl_cipher:suite_definition(CipherSuite),
NegotiatedHashSign = negotiated_hashsign(HashSign, KeyAlg, Version),
do_server_hello(Type, ServerHelloExt,
NegotiatedHashSign = negotiated_hashsign(HashSign, KeyAlg, Version),
do_server_hello(Type, ServerHelloExt,
State#state{connection_states = ConnectionStates,
negotiated_version = Version,
session = Session,
hashsign_algorithm = NegotiatedHashSign,
client_ecc = {EllipticCurves, EcPointFormats}});
hashsign_algorithm = NegotiatedHashSign});
#alert{} = Alert ->
handle_own_alert(Alert, ClientVersion, hello, State)
end;
Expand Down Expand Up @@ -1647,12 +1644,13 @@ key_exchange(#state{role = server, key_algorithm = Algo,
negotiated_version = Version,
tls_handshake_history = Handshake0,
socket = Socket,
transport_cb = Transport
transport_cb = Transport,
session = #session{ecc = Curve}
} = State)
when Algo == ecdhe_ecdsa; Algo == ecdhe_rsa;
Algo == ecdh_anon ->

ECDHKeys = public_key:generate_key(select_curve(State)),
ECDHKeys = public_key:generate_key(Curve),
ConnectionState =
ssl_record:pending_connection_state(ConnectionStates0, read),
SecParams = ConnectionState#connection_state.security_parameters,
Expand Down Expand Up @@ -3086,12 +3084,7 @@ default_hashsign(_Version, KeyExchange)
KeyExchange == rsa_psk;
KeyExchange == srp_anon ->
{null, anon}.

select_curve(#state{client_ecc = {[Curve|_], _}}) ->
{namedCurve, Curve};
select_curve(_) ->
{namedCurve, ?secp256k1}.


is_anonymous(Algo) when Algo == dh_anon;
Algo == ecdh_anon;
Algo == psk;
Expand Down
7 changes: 3 additions & 4 deletions lib/ssl/src/tls_handshake.erl
Expand Up @@ -120,17 +120,16 @@ hello(#client_hello{client_version = ClientVersion,
cipher_suites = CipherSuites,
compression_methods = Compressions,
random = Random,
extensions = HelloExt},
extensions = #hello_extensions{elliptic_curves = Curves} = HelloExt},
#ssl_options{versions = Versions} = SslOpts,
{Port, Session0, Cache, CacheCb, ConnectionStates0, Cert}, Renegotiation) ->
Version = ssl_handshake:select_version(tls_record, ClientVersion, Versions),
case tls_record:is_acceptable_version(Version, Versions) of
true ->
%% TODO: need to take supported Curves into Account when selecting the CipherSuite....
%% if whe have an ECDSA cert with an unsupported curve, we need to drop ECDSA ciphers
ECCCurve = ssl_handshake:select_curve(Curves, ssl_handshake:supported_ecc(Version)),
{Type, #session{cipher_suite = CipherSuite} = Session1}
= ssl_handshake:select_session(SugesstedId, CipherSuites, Compressions,
Port, Session0, Version,
Port, Session0#session{ecc = ECCCurve}, Version,
SslOpts, Cache, CacheCb, Cert),
case CipherSuite of
no_suite ->
Expand Down

0 comments on commit c07225b

Please sign in to comment.