Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
3722-ssl-Enable-certs_keys-config.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 3722-ssl-Enable-certs_keys-config.patch of Package erlang
From c38aed90932536aca8da4829284dd9143383468a Mon Sep 17 00:00:00 2001 From: Ingela Anderton Andin <ingela@erlang.org> Date: Wed, 16 Feb 2022 11:04:47 +0100 Subject: [PATCH 2/2] ssl: Enable certs_keys config Closes GH-4143 --- lib/ssl/doc/src/ssl.xml | 42 +++++- lib/ssl/doc/src/using_ssl.xml | 155 ++++++++++++------- lib/ssl/src/dtls_connection.erl | 10 +- lib/ssl/src/ssl.erl | 20 ++- lib/ssl/src/ssl_certificate.erl | 34 ++++- lib/ssl/src/ssl_config.erl | 193 +++++++++++++++++++++--- lib/ssl/src/ssl_connection.hrl | 9 +- lib/ssl/src/ssl_gen_statem.erl | 8 +- lib/ssl/src/ssl_handshake.erl | 22 ++- lib/ssl/src/ssl_internal.hrl | 1 + lib/ssl/src/tls_connection.erl | 10 +- lib/ssl/src/tls_dtls_connection.erl | 5 +- lib/ssl/src/tls_handshake_1_3.erl | 7 +- lib/ssl/test/ssl_api_SUITE.erl | 222 ++++++++++++++++++++++++++++ lib/ssl/test/ssl_test_lib.erl | 1 + 15 files changed, 637 insertions(+), 102 deletions(-) diff --git a/lib/ssl/doc/src/ssl.xml b/lib/ssl/doc/src/ssl.xml index 495f4426fa..3d3cc28a47 100644 --- a/lib/ssl/doc/src/ssl.xml +++ b/lib/ssl/doc/src/ssl.xml @@ -356,13 +356,53 @@ </datatype> <datatype> - <name name="key_password"/> + <name name="key_pem_password"/> <desc> <p>String containing the user's password or a function returning same type. Only used if the private keyfile is password-protected.</p> </desc> </datatype> + <datatype> + <name name="certs_keys"/> + <desc> + <p>A list of a certificate (or possible a certificate and its + chain) and the associated key of the certificate, that may be + used to authenticate the client or the server. The + certificate key pair that is considered best and matches + negotiated parameters for the connection will be selected. + Different signature algorithms are prioritized in the order + <c> eddsa, ecdsa, rsa_pss_pss, rsa and dsa </c>. If more than + one key is supplied for the same signing algorithm (which is + probably an unusual use case) they will prioritized by + strength unless it is a so called <c>engine key</c> that will + be favoured over other keys. As engine keys cannot be + inspected, supplying more than one engine key will make no + sense. This offers flexibility to for instance configure a + newer certificate that is expected to be used in most cases + and an older but acceptable certificate that will only be used + to communicate with legacy systems. Note that there is a trade + off between the induced overhead and the flexibility so + alternatives should be chosen for good reasons. If the <c>certs_keys</c> option is specified it + overrides all single certificate and key options. For examples see <seeguide marker="ssl:using_ssl"> the Users Guide</seeguide> + </p> + + <note><p> <c>eddsa</c> certificates are only supported by TLS-1.3 that does not support <c>dsa</c> certificates. + <c>rsa_pss_pss</c> (RSA certificates using Probabilistic Signature Scheme) are supported in TLS-1.2 and TLS-1.3, but some + TLS-1.2 implementations may not support <c>rsa_pss_pss</c>. + </p></note> + </desc> + </datatype> + + <datatype> + <name name="cert_key_conf"/> + <desc> + <p> A certificate (or possibly a certificate and its chain) and its associated key on one of the + possible formats. For the PEM file format there may also be a password associated with the file containg the key. + </p> + </desc> + </datatype> + <datatype> <name name="cipher_suites"/> <desc> diff --git a/lib/ssl/doc/src/using_ssl.xml b/lib/ssl/doc/src/using_ssl.xml index ae082b98db..559b20dedd 100644 --- a/lib/ssl/doc/src/using_ssl.xml +++ b/lib/ssl/doc/src/using_ssl.xml @@ -36,22 +36,26 @@ <seemfa marker="ssl:ssl#versions/0"><c>ssl:versions/0</c></seemfa> .</p> - <p>To see all supported cipher suites, call - <seemfa marker="ssl:ssl#cipher_suites/2"><c>ssl:cipher_suites(all, 'tlsv1.3')</c> </seemfa>. - The available cipher suites for a connection depend on the TLS version and pre TLS-1.3 also - on the certificate. To see the default cipher suite list change <c>all</c> to <c>default</c>. - Note that TLS 1.3 and previous versions does not have any cipher suites in common, - for listing cipher suites for a specific version use - <seemfa marker="ssl:ssl#cipher_suites/2"><c>ssl:cipher_suites(exclusive, 'tlsv1.3')</c> </seemfa>. - Specific cipher suites that you want your connection to use can also be - specified. Default is to use the strongest available.</p> + <p>To see all supported cipher suites, call <seemfa + marker="ssl:ssl#cipher_suites/2"><c>ssl:cipher_suites(all, + 'tlsv1.3')</c> </seemfa>. The available cipher suites for a + connection depend on the TLS version and pre TLS-1.3 also on the + certificate. To see the default cipher suite list change <c>all</c> + to <c>default</c>. Note that TLS 1.3 and previous versions does not + have any cipher suites in common, for listing cipher suites for a + specific version use <seemfa + marker="ssl:ssl#cipher_suites/2"><c>ssl:cipher_suites(exclusive, + 'tlsv1.3')</c> </seemfa>. Specific cipher suites that you want your + connection to use can also be specified. Default is to use the + strongest available.</p> <section> <title>Setting up Connections</title> - <p>This section shows a small example of how to set up client/server connections - using the Erlang shell. The returned value of the <c>sslsocket</c> is abbreviated - with <c>[...]</c> as it can be fairly large and is opaque.</p> + <p>This section shows a small example of how to set up + client/server connections using the Erlang shell. The returned + value of the <c>sslsocket</c> is abbreviated with <c>[...]</c> as + it can be fairly large and is opaque.</p> <section> <title>Minimal Example</title> @@ -67,8 +71,19 @@ ok</code> <p><em>Step 2:</em> Create a TLS listen socket: (To run DTLS add the option {protocol, dtls})</p> <code type="erl">2 server> {ok, ListenSocket} = -ssl:listen(9999, [{certfile, "cert.pem"}, {keyfile, "key.pem"},{reuseaddr, true}]). +ssl:listen(9999, [{certfile, "cert.pem"}, + {keyfile, "key.pem"}, + {reuseaddr, true}]). {ok,{sslsocket, [...]}}</code> + + + <p><em>Step 2: From OTP-25 it is equivalent to</em> </p> + <code type="erl">2 server> {ok, ListenSocket} = +ssl:listen(9999, [{certs_keys, [#{certfile => "cert.pem", + keyfile => "key.pem"}], + {reuseaddr, true}]). +{ok,{sslsocket, [...]}}</code> + <p><em>Step 3:</em> Do a transport accept on the TLS listen socket:</p> <code type="erl">3 server> {ok, TLSTransportSocket} = ssl:transport_accept(ListenSocket). @@ -134,9 +149,11 @@ ok</code> <code type="erl">2 client> {ok, Socket} = gen_tcp:connect("localhost", 9999, [], infinity).</code> - <p><em>Step 5:</em> Ensure <c>active</c> is set to <c>false</c> before trying - to upgrade a connection to a TLS connection, otherwise - TLS handshake messages can be delivered to the wrong process:</p> + <p><em>Step 5:</em> Ensure <c>active</c> is set to <c>false</c> + before trying to upgrade a connection to a TLS connection, + otherwise TLS handshake messages can be delivered to the wrong + process:</p> + <code type="erl">4 server> inet:setopts(Socket, [{active, false}]). ok</code> @@ -145,9 +162,11 @@ ok</code> {certfile, "cert.pem"}, {keyfile, "key.pem"}]). {ok,{sslsocket,[...]}}</code> - <p><em>Step 7:</em> Upgrade to a TLS connection. The client and server - must agree upon the upgrade. The server must call - <c>ssl:handshake/2</c> before the client calls <c>ssl:connect/3.</c></p> + <p><em>Step 7:</em> Upgrade to a TLS connection. The client and + server must agree upon the upgrade. The server must call + <c>ssl:handshake/2</c> before the client calls + <c>ssl:connect/3.</c></p> + <code type="erl">3 client>{ok, TLSSocket} = ssl:connect(Socket, [{cacertfile, "cacerts.pem"}, {certfile, "cert.pem"}, {keyfile, "key.pem"}], infinity). {ok,{sslsocket,[...]}}</code> @@ -160,8 +179,9 @@ ok</code> <code type="erl">4 server> ssl:setopts(TLSSocket, [{active, true}]). ok</code> - <p><em>Step 10:</em> Flush the shell message queue to see that the message - was sent on the client side:</p> + <p><em>Step 10:</em> Flush the shell message queue to see that + the message was sent on the client side:</p> + <code type="erl">5 server> flush(). Shell got {ssl,{sslsocket,[...]},"foo"} ok</code> @@ -173,6 +193,7 @@ ok</code> <p>Fetch default cipher suite list for a TLS/DTLS version. Change default to all to get all possible cipher suites.</p> + <code type="erl">1> Default = ssl:cipher_suites(default, 'tlsv1.2'). [#{cipher => aes_256_gcm,key_exchange => ecdhe_ecdsa, mac => aead,prf => sha384}, ....] @@ -183,7 +204,8 @@ ok</code> <code type="erl">2> NoRSA = ssl:filter_cipher_suites(Default, [{key_exchange, fun(rsa) -> false; - (_) -> true end}]). + (_) -> true + end}]). [...] </code> @@ -191,9 +213,11 @@ ok</code> <code type="erl"> 3> Suites = ssl:filter_cipher_suites(Default, [{key_exchange, fun(ecdh_ecdsa) -> true; - (_) -> false end}, - {cipher, fun(aes_128_cbc) ->true; - (_) ->false end}]). + (_) -> false + end}, + {cipher, fun(aes_128_cbc) -> true; + (_) ->false + end}]). [#{cipher => aes_128_cbc,key_exchange => ecdh_ecdsa, mac => sha256,prf => sha256}, #{cipher => aes_128_cbc,key_exchange => ecdh_ecdsa,mac => sha, @@ -226,7 +250,8 @@ ok</code> </p> <code type="erl">2> {ok, EngineRef} = crypto:engine_load(<<"dynamic">>, - [{<<"SO_PATH">>, "/tmp/user/engines/MyEngine"},<<"LOAD">>],[]). +[{<<"SO_PATH">>, "/tmp/user/engines/MyEngine"},<<"LOAD">>], +[]). {ok,#Ref<0.2399045421.3028942852.173962>} </code> @@ -251,24 +276,23 @@ ssl:connect("localhost", 9999, <section> <title>Session Reuse pre TLS 1.3</title> - <p>Clients can request to reuse a session established - by a previous full handshake between that client and server by - sending the id of the session in the initial handshake - message. The server may or may not agree to reuse it. If agreed - the server will send back the id and if not it will send a new - id. The ssl application has several options for handling session - reuse.</p> + <p>Clients can request to reuse a session established by a + previous full handshake between that client and server by sending + the id of the session in the initial handshake message. The server + may or may not agree to reuse it. If agreed the server will send + back the id and if not it will send a new id. The ssl application + has several options for handling session reuse.</p> <p>On the client side the ssl application will save session data to try to automate session reuse on behalf of the client processes - on the Erlang node. Note that only verified sessions will be - saved for security reasons, that is session resumption relies on - the certificate validation to have been run in the original + on the Erlang node. Note that only verified sessions will be saved + for security reasons, that is session resumption relies on the + certificate validation to have been run in the original handshake. To minimize memory consumption only unique sessions will be saved unless the special <c>save</c> value is specified for the following option <c> {reuse_sessions, boolean() | - save}</c> in which case a full handshake will be performed and that - specific session will have been saved before the handshake + save}</c> in which case a full handshake will be performed and + that specific session will have been saved before the handshake returns. The session id and even an opaque binary containing the session data can be retrieved using <c>ssl:connection_information/1</c> function. A saved session @@ -320,7 +344,8 @@ ok <p>Step 2- Using <c>save</c> Option </p> <code type="erl"> -%% We want save this particular session for reuse although it has the same basis as C1 +%% We want save this particular session for +%% reuse although it has the same basis as C1 6> {ok, C3} = ssl:connect("localhost", 9999, [{verify, verify_peer}, {versions, ['tlsv1.2']}, {cacertfile, "cacerts.pem"}, @@ -365,11 +390,12 @@ ok <code type="erl"> %% Perform a full handshake and the session will not be saved for reuse -12> {ok, C9} = ssl:connect("localhost", 9999, [{verify, verify_peer}, - {versions, ['tlsv1.2']}, - {cacertfile, "cacerts.pem"}, - {reuse_sessions, false}, - {server_name_indication, disable}]). +12> {ok, C9} = +ssl:connect("localhost", 9999, [{verify, verify_peer}, + {versions, ['tlsv1.2']}, + {cacertfile, "cacerts.pem"}, + {reuse_sessions, false}, + {server_name_indication, disable}]). {ok,{sslsocket,{gen_tcp,#Port<0.14>,tls_connection, ...}} %% Fetch session ID and data for C9 connection @@ -451,7 +477,11 @@ ok <p>An example with automatic and manual session resumption:</p> - <p><em>Step 1 (server):</em> Start the server:</p> + + <p><em>Step 1 (server):</em> Start the server: Note that from OTP-25 the + options certfile and keyfile can be replaced by + [{certs_keys, [#{certfile => "cert.pem", keyfile => "key.pem"}]}]</p> + <code type="erl"> {ok, _} = application:ensure_all_started(ssl). LOpts = [{certfile, "cert.pem"}, @@ -462,6 +492,27 @@ ok {ok, CSock} = ssl:transport_accept(LSock). </code> + + <p><em>Step 1 (server):</em> with alternative certificates, + in this example the EDDSA certificate will be preferred if TLS-1.3 + is negotiated and the RSA certificate will always be used for TLS-1.2 + as it does not support the EDDSA algorithm: Added in OTP-25</p> + + <code type="erl"> + {ok, _} = application:ensure_all_started(ssl). + LOpts = [{certs_keys, [#{certfile => "eddsacert.pem", + keyfile => "eddsakey.pem"}, + #{certfile => "rsacert.pem", + keyfile => "rsakey.pem", + password => "foobar"} + ]}], + {versions, ['tlsv1.2','tlsv1.3']}, + {session_tickets, stateless}]. + {ok, LSock} = ssl:listen(8001, LOpts). + {ok, CSock} = ssl:transport_accept(LSock). + </code> + + <p><em>Step 2 (client):</em> Start the client and connect to server:</p> <code type="erl"> {ok, _} = application:ensure_all_started(ssl). @@ -490,8 +541,9 @@ ok <![CDATA[<<<]]> Post-Handshake, NewSessionTicket ... </code> - <p>At this point the client has stored the received session tickets and ready to use them when - establishing new connections to the same server.</p> + <p>At this point the client has stored the received session + tickets and ready to use them when establishing new connections to + the same server.</p> <p><em>Step 4 (server):</em> Accept a new connection on the server:</p> <code type="erl"> @@ -530,7 +582,7 @@ ok <p><em>Step 8 (client):</em> Make a new connection to server:</p> <code type="erl"> {ok, _} = application:ensure_all_started(ssl). - COpts2 = [{cacertfile, "cert.pem"}, + COpts2 = [{cacertfile, "cacerts.pem"}, {versions, ['tlsv1.2','tlsv1.3']}, {log_level, debug}, {session_tickets, manual}]. @@ -542,8 +594,8 @@ ok ssl:handshake(CSock3). </code> - <p>After the handshake is performed, the user process receives messages with the tickets - sent by the server.</p> + <p>After the handshake is performed, the user process receivess + messages with the tickets sent by the server.</p> <p><em>Step 10 (client):</em> Receive a new session ticket:</p> <code type="erl"> @@ -641,7 +693,8 @@ ok %% Wait for session tickets timer:sleep(500), - %% Close socket if server cannot handle multiple connections e.g. openssl s_server + %% Close socket if server cannot handle multiple + %% connections e.g. openssl s_server ssl:close(Sock0), %% Second handshake 0-RTT diff --git a/lib/ssl/src/dtls_connection.erl b/lib/ssl/src/dtls_connection.erl index 65076994f9..b3e510c05d 100644 --- a/lib/ssl/src/dtls_connection.erl +++ b/lib/ssl/src/dtls_connection.erl @@ -208,13 +208,14 @@ initial_hello({call, From}, {start, Timeout}, session_cache_cb = CacheCb}, protocol_specific = PS, handshake_env = #handshake_env{renegotiation = {Renegotiation, _}}, - connection_env = #connection_env{cert_key_pairs = CertKeyPairs} = CEnv, + connection_env = #connection_env{cert_key_alts = CertKeyAlts} = CEnv, ssl_options = #{versions := Versions} = SslOpts, session = Session0, connection_states = ConnectionStates0 } = State0) -> Packages = maps:get(active_n, PS), dtls_socket:setopts(Transport, Socket, [{active,Packages}]), + CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts), Session = ssl_session:client_select_session({Host, Port, SslOpts}, Cache, CacheCb, Session0, CertKeyPairs), Hello = dtls_handshake:client_hello(Host, Port, ConnectionStates0, SslOpts, Session#session.session_id, Renegotiation), @@ -516,13 +517,14 @@ connection(internal, #hello_request{}, #state{static_env = #static_env{host = Ho session_cache_cb = CacheCb }, handshake_env = #handshake_env{renegotiation = {Renegotiation, _}}, - connection_env = #connection_env{cert_key_pairs = CertKeyPairs} = CEnv, + connection_env = #connection_env{cert_key_alts = CertKeyAlts} = CEnv, session = Session0, ssl_options = #{versions := Versions} = SslOpts, connection_states = ConnectionStates0, protocol_specific = PS } = State0) -> #{current_cookie_secret := Cookie} = PS, + CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts), Session = ssl_session:client_select_session({Host, Port, SslOpts}, Cache, CacheCb, Session0, CertKeyPairs), Hello = dtls_handshake:client_hello(Host, Port, Cookie, ConnectionStates0, SslOpts, Session#session.session_id, Renegotiation, undefined), @@ -681,14 +683,14 @@ handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State handshake_env = #handshake_env{kex_algorithm = KeyExAlg, renegotiation = {Renegotiation, _}, negotiated_protocol = CurrentProtocol} = HsEnv, - connection_env = #connection_env{cert_key_pairs = CertKeyPairs} = CEnv, + connection_env = #connection_env{cert_key_alts = CertKeyAlts} = CEnv, session = Session0, ssl_options = SslOpts} = tls_dtls_connection:handle_sni_extension(State0, Hello), SessionTracker = proplists:get_value(session_id_tracker, Trackers), {Version, {Type, Session}, ConnectionStates, Protocol0, ServerHelloExt, HashSign} = dtls_handshake:hello(Hello, SslOpts, {SessionTracker, Session0, - ConnectionStates0, CertKeyPairs, KeyExAlg}, Renegotiation), + ConnectionStates0, CertKeyAlts, KeyExAlg}, Renegotiation), Protocol = case Protocol0 of undefined -> CurrentProtocol; _ -> Protocol0 diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl index 83e5b5d942..e151c785e6 100644 --- a/lib/ssl/src/ssl.erl +++ b/lib/ssl/src/ssl.erl @@ -311,7 +311,8 @@ {certfile, cert_pem()} | {key, key()} | {keyfile, key_pem()} | - {password, key_password()} | + {password, key_pem_password()} | + {certs_keys, certs_keys()} | {ciphers, cipher_suites()} | {eccs, [named_curve()]} | {signature_algs, signature_algs()} | @@ -350,8 +351,14 @@ key_id := crypto:key_id(), password => crypto:password()}. % exported -type key_pem() :: file:filename(). --type key_password() :: iodata() | fun(() -> iodata()). --type cipher_suites() :: ciphers(). +-type key_pem_password() :: iodata() | fun(() -> iodata()). +-type certs_keys() :: [cert_key_conf()]. +-type cert_key_conf() :: #{cert => cert(), + key => key(), + certfile => cert_pem(), + keyfile => key_pem(), + password => key_pem_password()}. +-type cipher_suites() :: ciphers(). -type ciphers() :: [erl_cipher_suite()] | string(). % (according to old API) exported -type cipher_filters() :: list({key_exchange | cipher | mac | prf, @@ -1756,6 +1763,11 @@ handle_option(password = Option, unbound, OptionsMap, #{rules := Rules}) -> handle_option(password = Option, Value0, OptionsMap, _Env) -> Value = validate_option(Option, Value0), OptionsMap#{password => Value}; +handle_option(certs_keys, unbound, OptionsMap, _Env) -> + OptionsMap; +handle_option(certs_keys = Option, Value0, OptionsMap, _Env) -> + Value = validate_option(Option, Value0), + OptionsMap#{certs_keys => Value}; handle_option(psk_identity = Option, unbound, OptionsMap, #{rules := Rules}) -> Value = validate_option(Option, default_value(Option, Rules)), OptionsMap#{Option => Value}; @@ -2308,6 +2320,8 @@ validate_option(password, Value, _) validate_option(password, Value, _) when is_function(Value, 0) -> Value; +validate_option(certs_keys, Value, _) when is_list(Value) -> + Value; validate_option(protocol, Value = tls, _) -> Value; validate_option(protocol, Value = dtls, _) -> diff --git a/lib/ssl/src/ssl_certificate.erl b/lib/ssl/src/ssl_certificate.erl index eef6aa875a..05162c34d6 100644 --- a/lib/ssl/src/ssl_certificate.erl +++ b/lib/ssl/src/ssl_certificate.erl @@ -80,7 +80,9 @@ public_key_type/1, foldl_db/3, find_cross_sign_root_paths/4, - handle_cert_auths/4 + handle_cert_auths/4, + available_cert_key_pairs/1, + available_cert_key_pairs/2 ]). %%==================================================================== @@ -326,6 +328,36 @@ handle_cert_auths([_ | Certs] = EChain, CertAuths, _, _) -> {error, EChain, not_in_auth_domain} end. +available_cert_key_pairs(CertKeyGroups) -> + %% To be able to find possible TLS session pre TLS-1.3 + %% that may be reused. At this point the version is + %% not negotiated. + RevAlgos = [dsa, rsa, rsa_pss_pss, ecdsa], + cert_key_group_to_list(RevAlgos, CertKeyGroups, []). + +%% Create the prioritized list of cert key pairs that +%% are availble for use in the negotiated version +available_cert_key_pairs(CertKeyGroups, {3, 4}) -> + RevAlgos = [rsa, rsa_pss_pss, ecdsa, eddsa], + cert_key_group_to_list(RevAlgos, CertKeyGroups, []); +available_cert_key_pairs(CertKeyGroups, {3, 3}) -> + RevAlgos = [dsa, rsa, rsa_pss_pss, ecdsa], + cert_key_group_to_list(RevAlgos, CertKeyGroups, []); +available_cert_key_pairs(CertKeyGroups, {3, N}) when N < 3-> + RevAlgos = [dsa, rsa, ecdsa], + cert_key_group_to_list(RevAlgos, CertKeyGroups, []). + +cert_key_group_to_list([], _, Acc) -> + final_group_list(Acc); +cert_key_group_to_list([Algo| Rest], CertKeyGroups, Acc) -> + CertKeyPairs = maps:get(Algo, CertKeyGroups, []), + cert_key_group_to_list(Rest, CertKeyGroups, CertKeyPairs ++ Acc). + +final_group_list([]) -> + [#{certs => [[]], private_key => #{}}]; +final_group_list(List) -> + List. + %%-------------------------------------------------------------------- %%% Internal functions %%-------------------------------------------------------------------- diff --git a/lib/ssl/src/ssl_config.erl b/lib/ssl/src/ssl_config.erl index 91bd03decf..46578c05a5 100644 --- a/lib/ssl/src/ssl_config.erl +++ b/lib/ssl/src/ssl_config.erl @@ -41,20 +41,162 @@ %% Internal application API %%==================================================================== init(#{erl_dist := ErlDist, - key := Key, - keyfile := KeyFile, - password := Password, %% Can be fun() or string() dh := DH, dhfile := DHFile} = SslOpts, Role) -> init_manager_name(ErlDist), + #{pem_cache := PemCache} = Config = init_cacerts(SslOpts, Role), + DHParams = init_diffie_hellman(PemCache, DH, DHFile, Role), + + CertKeyAlts = init_certs_keys(SslOpts, Role, PemCache), + + {ok, Config#{cert_key_alts => CertKeyAlts, dh_params => DHParams}}. - {ok, #{pem_cache := PemCache} = Config, Certs} - = init_certificates(SslOpts, Role), +init_certs_keys(#{certs_keys := CertsKeys}, Role, PemCache) -> + Pairs = lists:map(fun(CertKey) -> cert_key_pair(CertKey, Role, PemCache) end, CertsKeys), + CertKeyGroups = group_pairs(Pairs), + prioritize_groups(CertKeyGroups); +init_certs_keys(SslOpts, Role, PemCache) -> + KeyPair = init_cert_key_pair(SslOpts, Role, PemCache), + group_pairs([KeyPair]). + +init_cert_key_pair(#{key := Key, + keyfile := KeyFile, + password := Password} = Opts, Role, PemCache) -> + {ok, Certs} = init_certificates(Opts, PemCache, Role), PrivateKey = init_private_key(PemCache, Key, KeyFile, Password, Role), - DHParams = init_diffie_hellman(PemCache, DH, DHFile, Role), - {ok, Config#{cert_key_pairs => [#{private_key => PrivateKey, certs => Certs}], dh_params => DHParams}}. + #{private_key => PrivateKey, certs => Certs}. + +cert_key_pair(CertKey, Role, PemCache) -> + CertKeyPairConf = cert_conf(key_conf(CertKey)), + init_cert_key_pair(CertKeyPairConf, Role, PemCache). + + +group_pairs([#{certs := [[]]}]) -> + #{eddsa => [], + ecdsa => [], + rsa_pss_pss => [], + rsa => [], + dsa => [] + }; +group_pairs(Pairs) -> + group_pairs(Pairs, #{eddsa => [], + ecdsa => [], + rsa_pss_pss => [], + rsa => [], + dsa => [] + }). +group_pairs([], Group) -> + Group; +group_pairs([#{private_key := #'ECPrivateKey'{parameters = {namedCurve, ?'id-Ed25519'}}} = Pair | Rest], #{eddsa := EDDSA} = Group) -> + group_pairs(Rest, Group#{eddsa => [Pair | EDDSA]}); +group_pairs([#{private_key := #'ECPrivateKey'{parameters = {namedCurve, ?'id-Ed448'}}} = Pair | Rest], #{eddsa := EDDSA} = Group) -> + group_pairs(Rest, Group#{eddsa => [Pair | EDDSA]}); +group_pairs([#{private_key := #'ECPrivateKey'{}} = Pair | Rest], #{ecdsa := ECDSA} = Group) -> + group_pairs(Rest, Group#{ecdsa => [Pair | ECDSA]}); +group_pairs([#{private_key := {#'RSAPrivateKey'{}, #'RSASSA-PSS-params'{}}} = Pair | Rest], #{rsa_pss_pss := RSAPSS} = Group) -> + group_pairs(Rest, Group#{rsa_pss_pss => [Pair | RSAPSS]}); +group_pairs([#{private_key := #'RSAPrivateKey'{}} = Pair | Rest], #{rsa := RSA} = Group) -> + group_pairs(Rest, Group#{rsa => [Pair | RSA]}); +group_pairs([#{private_key := #'DSAPrivateKey'{}} = Pair | Rest], #{dsa := DSA} = Group) -> + group_pairs(Rest, Group#{dsa => [Pair | DSA]}); +group_pairs([#{private_key := #{algorithm := dss, engine := _}} = Pair | Rest], Group) -> + Pairs = maps:get(dsa, Group), + group_pairs(Rest, Group#{dsa => [Pair | Pairs]}); +group_pairs([#{private_key := #{algorithm := Alg, engine := _}} = Pair | Rest], Group) -> + Pairs = maps:get(Alg, Group), + group_pairs(Rest, Group#{Alg => [Pair | Pairs]}). + +prioritize_groups(#{eddsa := EDDSA, + ecdsa := ECDSA, + rsa_pss_pss := RSAPSS, + rsa := RSA, + dsa := DSA} = CertKeyGroups) -> + CertKeyGroups#{eddsa => prio_eddsa(EDDSA), + ecdsa => prio_ecdsa(ECDSA), + rsa_pss_pss => prio_rsa_pss(RSAPSS), + rsa => prio_rsa(RSA), + dsa => prio_dsa(DSA)}. + +prio_eddsa(EDDSA) -> + %% Engine not supported yet + using_curve({namedCurve, ?'id-Ed25519'}, EDDSA, []) ++ using_curve({namedCurve, ?'id-Ed448'}, EDDSA, []). + +prio_ecdsa(ECDSA) -> + EnginePairs = [Pair || Pair = #{private_key := #{engine := _}} <- ECDSA], + Curves = tls_v1:ecc_curves(all), + EnginePairs ++ lists:foldr(fun(Curve, AccIn) -> + CurveOid = pubkey_cert_records:namedCurves(Curve), + Pairs = using_curve({namedCurve, CurveOid}, ECDSA -- EnginePairs, []), + Pairs ++ AccIn + end, [], Curves). +using_curve(_, [], Acc) -> + lists:reverse(Acc); +using_curve(Curve, [#{private_key := #'ECPrivateKey'{parameters = Curve}} = Pair | Rest], Acc) -> + using_curve(Curve, Rest, [Pair | Acc]); +using_curve(Curve, [_ | Rest], Acc) -> + using_curve(Curve, Rest, Acc). + +prio_rsa_pss(RSAPSS) -> + Order = fun(#{privat_key := {#'RSAPrivateKey'{modulus = N}, Params1}}, + #{private_key := {#'RSAPrivateKey'{modulus = N}, Params2}}) -> + prio_params_1(Params1, Params2); + (#{private_key := {#'RSAPrivateKey'{modulus = N}, _}}, + #{private_key := {#'RSAPrivateKey'{modulus = M}, _}}) when M > N -> + true; + (#{private_key := #{engine := _}}, _) -> + true; + (_,_) -> + false + end, + lists:sort(Order, RSAPSS). + +prio_params_1(#'RSASSA-PSS-params'{hashAlgorithm = #'HashAlgorithm'{algorithm = Oid1}}, + #'RSASSA-PSS-params'{hashAlgorithm = #'HashAlgorithm'{algorithm = Oid2}}) -> + public_key:pkix_hash_type(Oid1) > public_key:pkix_hash_type(Oid2). + +prio_rsa(RSA) -> + Order = fun(#{key := #'RSAPrivateKey'{modulus = N}}, + #{key := #'RSAPrivateKey'{modulus = M}}) when M > N -> + true; + (#{private_key := #{engine := _}}, _) -> + true; + (_,_) -> + false + end, + lists:sort(Order, RSA). + +prio_dsa(DSA) -> + Order = fun(#{key := #'DSAPrivateKey'{q = N}}, + #{key := #'DSAPrivateKey'{q = M}}) when M > N -> + true; + (#{private_key := #{engine := _}}, _) -> + true; + (_,_) -> + false + end, + lists:sort(Order, DSA). + +key_conf(#{key := _} = Conf) -> + Conf#{certfile => <<>>, + keyfile => <<>>, + password => undefined}; +key_conf(#{keyfile := _} = Conf) -> + case maps:get(password, Conf, undefined) of + undefined -> + Conf#{key => undefined, + password => undefined}; + _ -> + Conf#{key => undefined} + end. + +cert_conf(#{cert := Bin} = Conf) when is_binary(Bin)-> + Conf#{cert => [Bin]}; +cert_conf(#{cert := _} = Conf) -> + Conf#{certfile => <<>>}; +cert_conf(#{certfile := _} = Conf) -> + Conf#{cert => undefined}. pre_1_3_session_opts(Role) -> {Cb, InitArgs} = session_cb_opts(Role), @@ -119,12 +261,10 @@ init_manager_name(true) -> put(ssl_manager, ssl_manager:name(dist)), put(ssl_pem_cache, ssl_pem_cache:name(dist)). -init_certificates(#{cacerts := CaCerts, - cacertfile := CACertFile, - certfile := CertFile, - cert := OwnCerts, - crl_cache := CRLCache - }, Role) -> +init_cacerts(#{cacerts := CaCerts, + cacertfile := CACertFile, + crl_cache := CRLCache + }, Role) -> {ok, Config} = try Certs = case CaCerts of @@ -138,31 +278,36 @@ init_certificates(#{cacerts := CaCerts, _:Reason -> file_error(CACertFile, {cacertfile, Reason}) end, - init_certificates(OwnCerts, Config, CertFile, Role). + Config. -init_certificates(undefined, Config, <<>>, _) -> - {ok, Config, [[]]}; +init_certificates(#{certfile := CertFile, + cert := OwnCerts}, PemCache, Role) -> + init_certificates(OwnCerts, PemCache, CertFile, Role). -init_certificates(undefined, #{pem_cache := PemCache} = Config, CertFile, client) -> +init_certificates(undefined, _, <<>>, _) -> + {ok, [[]]}; +init_certificates(undefined, PemCache, CertFile, client) -> try %% OwnCert | [OwnCert | Chain] OwnCerts = ssl_certificate:file_to_certificats(CertFile, PemCache), - {ok, Config, OwnCerts} + {ok, OwnCerts} catch _Error:_Reason -> - {ok, Config, [[]]} + {ok, [[]]} end; - -init_certificates(undefined, #{pem_cache := PemCache} = Config, CertFile, server) -> +init_certificates(undefined, PemCache, CertFile, server) -> try %% OwnCert | [OwnCert | Chain] OwnCerts = ssl_certificate:file_to_certificats(CertFile, PemCache), - {ok, Config, OwnCerts} + {ok, OwnCerts} catch _:Reason -> file_error(CertFile, {certfile, Reason}) end; -init_certificates(OwnCerts, Config, _, _) -> - {ok, Config, OwnCerts}. +init_certificates(OwnCerts, _, _, _) when is_binary(OwnCerts)-> + {ok, [OwnCerts]}; +init_certificates(OwnCerts, _, _, _) -> + {ok, OwnCerts}. + init_private_key(_, #{algorithm := Alg} = Key, _, _Password, _Client) when Alg == ecdsa; Alg == rsa; Alg == dss -> diff --git a/lib/ssl/src/ssl_connection.hrl b/lib/ssl/src/ssl_connection.hrl index 86ee57d7fa..2ee37ffb30 100644 --- a/lib/ssl/src/ssl_connection.hrl +++ b/lib/ssl/src/ssl_connection.hrl @@ -97,9 +97,12 @@ socket_tls_closed = false ::boolean(), negotiated_version :: ssl_record:ssl_version() | 'undefined', erl_dist_handle = undefined :: erlang:dist_handle() | 'undefined', - cert_key_pairs = undefined :: [#{private_key => public_key:private_key(), - certs => [public_key:der_encoded()]}] - | secret_printout() | 'undefined' + cert_key_alts = undefined :: #{eddsa => list(), + ecdsa => list(), + rsa_pss_pss => list(), + rsa => list(), + dsa => list() + } | secret_printout() | 'undefined' }). -record(state, { diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl index 6aba9c1b71..eaad3f0967 100644 --- a/lib/ssl/src/ssl_gen_statem.erl +++ b/lib/ssl/src/ssl_gen_statem.erl @@ -160,7 +160,7 @@ ssl_config(Opts, Role, #state{static_env = InitStatEnv0, fileref_db_handle := FileRefHandle, session_cache := CacheHandle, crl_db_info := CRLDbHandle, - cert_key_pairs := CertKeyPairs, + cert_key_alts := CertKeyAlts, dh_params := DHParams}} = ssl_config:init(Opts, Role), TimeStamp = erlang:monotonic_time(), @@ -175,7 +175,7 @@ ssl_config(Opts, Role, #state{static_env = InitStatEnv0, }, handshake_env = HsEnv#handshake_env{diffie_hellman_params = DHParams, continue_status = ContinueStatus}, - connection_env = CEnv#connection_env{cert_key_pairs = CertKeyPairs}, + connection_env = CEnv#connection_env{cert_key_alts = CertKeyAlts}, ssl_options = Opts}. %%-------------------------------------------------------------------- @@ -1282,7 +1282,7 @@ handle_sni_hostname(Hostname, fileref_db_handle := FileRefHandle, session_cache := CacheHandle, crl_db_info := CRLDbHandle, - cert_key_pairs := CertKeyPairs, + cert_key_alts := CertKeyAlts, dh_params := DHParams}} = ssl_config:init(NewOptions, Role), State0#state{ @@ -1293,7 +1293,7 @@ handle_sni_hostname(Hostname, crl_db = CRLDbHandle, session_cache = CacheHandle }, - connection_env = CEnv#connection_env{cert_key_pairs = CertKeyPairs}, + connection_env = CEnv#connection_env{cert_key_alts = CertKeyAlts}, ssl_options = NewOptions, handshake_env = HsEnv#handshake_env{sni_hostname = Hostname, diffie_hellman_params = DHParams} diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl index a109e30f18..02bc8ea838 100644 --- a/lib/ssl/src/ssl_handshake.erl +++ b/lib/ssl/src/ssl_handshake.erl @@ -971,6 +971,7 @@ decode_suites('2_bytes', Dec) -> decode_suites('3_bytes', Dec) -> from_3bytes(Dec). + %%==================================================================== %% Cipher suite handling %%==================================================================== @@ -1046,7 +1047,8 @@ cipher_suites(Suites, true) -> prf({3,_N}, PRFAlgo, Secret, Label, Seed, WantedLength) -> {ok, tls_v1:prf(PRFAlgo, Secret, Label, Seed, WantedLength)}. -select_session(SuggestedSessionId, CipherSuites, HashSigns, Compressions, SessIdTracker, Session0, Version, SslOpts, CertKeyPairs) -> +select_session(SuggestedSessionId, CipherSuites, HashSigns, Compressions, SessIdTracker, Session0, Version, SslOpts, CertKeyAlts) -> + CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts, Version), {SessionId, Resumed} = ssl_session:server_select_session(Version, SessIdTracker, SuggestedSessionId, SslOpts, CertKeyPairs), case Resumed of @@ -1095,10 +1097,24 @@ select_cert_key_pair_and_params(CipherSuites, [#{private_key := Key, certs := [C no_suite -> select_cert_key_pair_and_params(CipherSuites, Rest, HashSigns, ECCCurve0, Opts, Version); CipherSuite0 -> - CurveAndSuite = cert_curve(Cert, ECCCurve0, CipherSuite0), - {Certs, Key, CurveAndSuite} + case is_acceptable_cert(Cert, HashSigns, ssl:tls_version(Version)) of + true -> + CurveAndSuite = cert_curve(Cert, ECCCurve0, CipherSuite0), + {Certs, Key, CurveAndSuite}; + false -> + select_cert_key_pair_and_params(CipherSuites, Rest, HashSigns, ECCCurve0, Opts, Version) + end end. +is_acceptable_cert(Cert, HashSigns, {Major, Minor}) when Major == 3, + Minor >= 3 -> + {SignAlgo0, Param, _, _, _} = get_cert_params(Cert), + SignAlgo = sign_algo(SignAlgo0, Param), + is_acceptable_hash_sign(SignAlgo, HashSigns); +is_acceptable_cert(_,_,_) -> + %% Not negotiable pre TLS-1.2. So if cert is available for version it is acceptable + true. + supported_ecc({Major, Minor}) when ((Major == 3) and (Minor >= 1)) orelse (Major > 3) -> Curves = tls_v1:ecc_curves(Minor), #elliptic_curves{elliptic_curve_list = Curves}; diff --git a/lib/ssl/src/ssl_internal.hrl b/lib/ssl/src/ssl_internal.hrl index 4e87ea0acb..93d7c2456e 100644 --- a/lib/ssl/src/ssl_internal.hrl +++ b/lib/ssl/src/ssl_internal.hrl @@ -132,6 +132,7 @@ cacerts]}, cacerts => {undefined, [versions]}, cert => {undefined, [versions]}, + certs_keys => {undefined, [versions]}, certfile => {<<>>, [versions]}, certificate_authorities => {false, [versions]}, ciphers => {[], [versions]}, diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl index 05cf5bb6c3..52c72d7d69 100644 --- a/lib/ssl/src/tls_connection.erl +++ b/lib/ssl/src/tls_connection.erl @@ -141,11 +141,12 @@ init([Role, Sender, Host, Port, Socket, Options, User, CbInfo]) -> State1 = #state{static_env = #static_env{session_cache = Cache, session_cache_cb = CacheCb }, - connection_env = #connection_env{cert_key_pairs = CertKeyPairs}, + connection_env = #connection_env{cert_key_alts = CertKeyAlts}, ssl_options = SslOptions, session = Session0} = ssl_gen_statem:ssl_config(State0#state.ssl_options, Role, State0), State = case Role of client -> + CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts), Session = ssl_session:client_select_session({Host, Port, SslOptions}, Cache, CacheCb, Session0, CertKeyPairs), State1#state{session = Session}; server -> @@ -353,13 +354,14 @@ connection(internal, #hello_request{}, handshake_env = #handshake_env{ renegotiation = {Renegotiation, peer}, ocsp_stapling_state = OcspState}, - connection_env = #connection_env{cert_key_pairs = CertKeyPairs}, + connection_env = #connection_env{cert_key_alts = CertKeyAlts}, session = Session0, ssl_options = SslOpts, protocol_specific = #{sender := Pid}, connection_states = ConnectionStates} = State0) -> try tls_sender:peer_renegotiate(Pid) of {ok, Write} -> + CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts), Session = ssl_session:client_select_session({Host, Port, SslOpts}, Cache, CacheCb, Session0, CertKeyPairs), Hello = tls_handshake:client_hello(Host, Port, ConnectionStates, SslOpts, Session#session.session_id, @@ -513,7 +515,7 @@ handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State renegotiation = {Renegotiation, _}, negotiated_protocol = CurrentProtocol, sni_guided_cert_selection = SNICertSelection} = HsEnv, - connection_env = #connection_env{cert_key_pairs = CertKeyPairs} = CEnv, + connection_env = #connection_env{cert_key_alts = CertKeyAlts} = CEnv, session = Session0, ssl_options = SslOpts} = State, SessionTracker = proplists:get_value(session_id_tracker, Trackers), @@ -522,7 +524,7 @@ handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State tls_handshake:hello(Hello, SslOpts, {SessionTracker, Session0, - ConnectionStates0, CertKeyPairs, KeyExAlg}, + ConnectionStates0, CertKeyAlts, KeyExAlg}, Renegotiation), Protocol = case Protocol0 of undefined -> CurrentProtocol; diff --git a/lib/ssl/src/tls_dtls_connection.erl b/lib/ssl/src/tls_dtls_connection.erl index 9f0bf8132e..ce0372b84e 100644 --- a/lib/ssl/src/tls_dtls_connection.erl +++ b/lib/ssl/src/tls_dtls_connection.erl @@ -409,7 +409,7 @@ certify(internal, #certificate_request{}, #state{static_env = #static_env{role = client, protocol_cb = Connection}, session = Session0, - connection_env = #connection_env{cert_key_pairs = [#{certs := [[]]}]}} = State) -> + connection_env = #connection_env{cert_key_alts = [#{certs := [[]]}]}} = State) -> %% The client does not have a certificate and will send an empty reply, the server may fail %% or accept the connection by its own preference. No signature algorithms needed as there is %% no certificate to verify. @@ -422,11 +422,12 @@ certify(internal, #certificate_request{} = CertRequest, cert_db = CertDbHandle, cert_db_ref = CertDbRef}, connection_env = #connection_env{negotiated_version = Version, - cert_key_pairs = CertKeyPairs + cert_key_alts = CertKeyAlts }, session = Session0, ssl_options = #{signature_algs := SupportedHashSigns}} = State) -> TLSVersion = ssl:tls_version(Version), + CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts, ssl:tls_version(Version)), Session = select_client_cert_key_pair(Session0, CertRequest, CertKeyPairs, SupportedHashSigns, TLSVersion, CertDbHandle, CertDbRef), diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl index 84ee036a46..a68c7de159 100644 --- a/lib/ssl/src/tls_handshake_1_3.erl +++ b/lib/ssl/src/tls_handshake_1_3.erl @@ -652,7 +652,7 @@ do_start(#client_hello{cipher_suites = ClientCiphers, #state{connection_states = ConnectionStates0, session = Session0, - connection_env = #connection_env{cert_key_pairs = CertKeyPairs}} = State1 = + connection_env = #connection_env{cert_key_alts = CertKeyAlts}} = State1 = Maybe(ssl_gen_statem:handle_sni_extension(SNI, State0)), Maybe(validate_cookie(Cookie, State1)), @@ -667,6 +667,7 @@ do_start(#client_hello{cipher_suites = ClientCiphers, Cipher = Maybe(select_cipher_suite(HonorCipherOrder, ClientCiphers, ServerCiphers)), Groups = Maybe(select_common_groups(ServerGroups, ClientGroups)), Maybe(validate_client_key_share(ClientGroups, ClientShares)), + CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts, {3,4}), #session{own_certificates = [Cert|_]} = Session = Maybe(select_server_cert_key_pair(Session0, CertKeyPairs, ClientSignAlgs, ClientSignAlgsCert, CertAuths, State0, @@ -1431,7 +1432,8 @@ create_change_cipher_spec(#state{ssl_options = #{log_level := LogLevel}}) -> process_certificate_request(#certificate_request_1_3{ extensions = Extensions}, #state{ssl_options = #{signature_algs := ClientSignAlgs}, - connection_env = #connection_env{cert_key_pairs = CertKeyPairs}, + connection_env = #connection_env{cert_key_alts = CertKeyAlts, + negotiated_version = Version}, static_env = #static_env{cert_db = CertDbHandle, cert_db_ref = CertDbRef}, session = Session0} = State) -> @@ -1441,6 +1443,7 @@ process_certificate_request(#certificate_request_1_3{ maps:get(signature_algs_cert, Extensions, undefined)), CertAuths = get_certificate_authorities(maps:get(certificate_authorities, Extensions, undefined)), + CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts, Version), Session = select_client_cert_key_pair(Session0, CertKeyPairs, ServerSignAlgs, ServerSignAlgsCert, ClientSignAlgs, CertDbHandle, CertDbRef, CertAuths), diff --git a/lib/ssl/test/ssl_api_SUITE.erl b/lib/ssl/test/ssl_api_SUITE.erl index c686fac6d6..b839d72a22 100644 --- a/lib/ssl/test/ssl_api_SUITE.erl +++ b/lib/ssl/test/ssl_api_SUITE.erl @@ -50,6 +50,8 @@ peercert/1, peercert_with_client_cert/0, peercert_with_client_cert/1, + select_best_cert/0, + select_best_cert/1, connection_information/0, connection_information/1, secret_connection_info/0, @@ -205,6 +207,7 @@ log/2, get_connection_information/3, protocol_version_check/2, + check_peercert/2, %%TODO Keep? run_error_server/1, run_error_server_close/1, @@ -269,6 +272,7 @@ gen_api_tests() -> [ peercert, peercert_with_client_cert, + select_best_cert, connection_information, secret_connection_info, keylog_connection_info, @@ -427,6 +431,23 @@ init_per_testcase(check_random_nonce, Config) -> ssl_test_lib:ct_log_supported_protocol_versions(Config), ct:timetrap({seconds, 20}), Config; +init_per_testcase(select_best_cert, Config) -> + ct:timetrap({seconds, 10}), + Version = ssl_test_lib:protocol_version(Config), + %% We need to make sure TLS-1.3 can be supported as + %% want to generate a TLS-1.3 specific certificate that will not + %% be chosen + case Version of + 'tlsv1.2' -> + case ssl_test_lib:sufficient_crypto_support('tlsv1.3') of + true -> + Config; + false -> + {skip, "Crypto does not support EDDSA"} + end; + _ -> + Config + end; init_per_testcase(_TestCase, Config) -> ssl_test_lib:ct_log_supported_protocol_versions(Config), ct:timetrap({seconds, 10}), @@ -508,6 +529,24 @@ peercert_with_client_cert(Config) when is_list(Config) -> ssl_test_lib:close(Server), ssl_test_lib:close(Client). +%%-------------------------------------------------------------------- +select_best_cert() -> + [{doc,"Basic test of the certs_keys option."}]. + +select_best_cert(Config) when is_list(Config) -> + Version = ssl_test_lib:protocol_version(Config), + Conf = test_config(Version, Config), + lists:foreach( + fun({#{server_config := SConfig, + client_config := CConfig}, + {client_peer, CExpected}, + {server_peer, SExpected}}) -> + selected_peer(CExpected, SExpected, + ssl_test_lib:ssl_options(CConfig, Config), + ssl_test_lib:ssl_options(SConfig, Config), + Conf) + end, Conf). + %%-------------------------------------------------------------------- connection_information() -> [{doc,"Test the API function ssl:connection_information/1"}]. @@ -3169,3 +3208,186 @@ dtls_exclusive_non_default_version(DTLSVersion) -> tls_v1:srp_exclusive(Minor) ++ tls_v1:rsa_exclusive(Minor) ++ tls_v1:des_exclusive(Minor). + +selected_peer(ExpectedClient, + ExpectedServer, ClientOpts, ServerOpts, Config) -> + {ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config), + + Server = ssl_test_lib:start_server([{node, ServerNode}, {port, 0}, + {from, self()}, + {mfa, {?MODULE, check_peercert, [ExpectedServer]}}, + {options, ssl_test_lib:ssl_options(ServerOpts, Config)}]), + Port = ssl_test_lib:inet_port(Server), + + Client = ssl_test_lib:start_client([{node, ClientNode}, {port, Port}, + {host, Hostname}, + {from, self()}, + {mfa, {?MODULE, check_peercert, [ExpectedClient]}}, + {options, ssl_test_lib:ssl_options(ClientOpts, Config)} + ]), + + ssl_test_lib:check_result(Server, ok, Client, ok), + %% Make sure to start next test fresh + ssl:stop(), + ssl:start(). + +test_config('tlsv1.3', _) -> + #{server_config := SEDDSAOpts, + client_config := CEDDSAOpts} = eddsa_cert_chains(), + #{server_config := SECDSAOpts, + client_config := CECDSAOpts } = ecdsa_cert_chains(), + + {SEDDSACert, SEDDSAKey, SEDDSACACerts} = get_single_options(cert, key, cacerts, SEDDSAOpts), + {CEDDSACert, CEDDSAKey, CEDDSACACerts} = get_single_options(cert, key, cacerts, CEDDSAOpts), + + {SECDSACert, SECDSAKey, SECDSACACerts} = get_single_options(cert, key, cacerts, SECDSAOpts), + {CECDSACert, CECDSAKey, CECDSACACerts} = get_single_options(cert, key, cacerts, CECDSAOpts), + + ServerCertKeys = [#{cert => SECDSACert, key => SECDSAKey}, + #{cert => SEDDSACert, key => SEDDSAKey}], + + ClientCertKeys = [#{cert => CECDSACert, key => CECDSAKey}, + #{cert => CEDDSACert, key => CEDDSAKey}], + + [{#{server_config => [{certs_keys,ServerCertKeys}, + {verify, verify_peer}, {versions, ['tlsv1.3', 'tlsv1.2']}, + {cacerts, SEDDSACACerts ++ SECDSACACerts}], + client_config => [{certs_keys, ClientCertKeys}, + {verify, verify_peer}, {versions, ['tlsv1.3', 'tlsv1.2']}, + {cacerts, CEDDSACACerts ++ CECDSACACerts}] + }, + {client_peer, SEDDSACert}, {server_peer, CEDDSACert}}, + {#{server_config => [{certs_keys, ServerCertKeys}, + {verify, verify_peer}, {versions, ['tlsv1.2']}, + {cacerts, SEDDSACACerts ++ SECDSACACerts}], + client_config => [{certs_keys, ClientCertKeys}, + {verify, verify_peer}, {versions, ['tlsv1.2']}, + {cacerts, CEDDSACACerts ++ CECDSACACerts}]}, + {client_peer, SECDSACert}, {server_peer, CECDSACert}} + ]; +test_config('tlsv1.2', _) -> + #{server_config := SRSAOpts, + client_config := CRSAOpts} = eddsa_cert_chains(), + #{server_config := SDSAOpts, + client_config := CDSAOpts} = dsa_cert_chains(), + + {SRSACert, SRSAKey, SRSACACerts} = get_single_options(cert, key, cacerts, SRSAOpts), + {CRSACert, CRSAKey, CRSACACerts} = get_single_options(cert, key, cacerts, CRSAOpts), + + {SDSACert, SDSAKey, SDSACACerts} = get_single_options(cert, key, cacerts, SDSAOpts), + {CDSACert, CDSAKey, CDSACACerts} = get_single_options(cert, key, cacerts, CDSAOpts), + + + [{#{server_config => [{certs_keys, [#{cert => SDSACert, key => SDSAKey}, #{cert => SRSACert, key => SRSAKey}]}, + {verify, verify_peer}, {versions, ['tlsv1.3', 'tlsv1.2']}, + {cacerts, SRSACACerts ++ SDSACACerts}], + client_config => [{certs_keys, [#{cert => CDSACert, key => CDSAKey}, #{cert => CRSACert, key => CRSAKey}]}, + {verify, verify_peer}, {versions, ['tlsv1.3', 'tlsv1.2']}, + {cacerts, CRSACACerts ++ CDSACACerts}] + }, {client_peer, SRSACert}, {server_peer, CRSACert}}, + {#{server_config => [{certs_keys, [#{cert => SDSACert, key => SDSAKey}, #{cert => SRSACert, key => SRSAKey}]}, + {verify, verify_peer}, {versions, ['tlsv1.2']}, + {cacerts, SRSACACerts ++ SDSACACerts}], + client_config => [{certs_keys, [#{cert => CDSACert, key => CDSAKey}, #{cert => CRSACert, key => CRSAKey}]}, + {verify, verify_peer}, {versions, ['tlsv1.2']}, + {cacerts, CRSACACerts ++ CDSACACerts}] + }, {client_peer, SDSACert}, {server_peer, CDSACert}}]; +test_config('dtlsv1.2', Config) -> + #{server_config := SRSAPSSOpts, + client_config := CRSAPSSOpts} = ssl_test_lib:make_rsa_pss_pem(rsa_pss_pss, [], Config, "dtls_pss_pss_conf"), + #{server_config := SRSAPSSRSAEOpts, + client_config := CRSAPSSRSAEOpts} = ssl_test_lib:make_rsa_pss_pem(rsa_pss_rsae, [], Config, "dtls_pss_rsae_conf"), + + {SRSAPSSCert, SRSAPSSKey, SRSAPSSCACerts} = get_single_options(certfile, keyfile, cacertfile, SRSAPSSOpts), + {CRSAPSSCert, CRSAPSSKey, CRSAPSSCACerts} = get_single_options(certfile, keyfile, cacertfile, CRSAPSSOpts), + + {SRSAPSSRSAECert, SRSAPSSRSAEKey, SRSAPSSRSAECACerts} = get_single_options(certfile, keyfile, cacertfile, SRSAPSSRSAEOpts), + {CRSAPSSRSAECert, CRSAPSSRSAEKey, CRSAPSSRSAECACerts} = get_single_options(certfile, keyfile, cacertfile, CRSAPSSRSAEOpts), + + [{#{server_config => [{certs_keys, [#{certfile => SRSAPSSRSAECert, keyfile => SRSAPSSRSAEKey}, + #{certfile => SRSAPSSCert, keyfile => SRSAPSSKey}]}, + {verify, verify_peer}, + {cacertfile, CRSAPSSCACerts}], + client_config => [{certs_keys, [#{certfile => CRSAPSSRSAECert, keyfile => CRSAPSSRSAEKey}, + #{certfile => CRSAPSSCert, keyfile => CRSAPSSKey}]}, + {verify, verify_peer}, + {cacertfile, SRSAPSSCACerts}] + }, + {client_peer, pem_to_der_cert(SRSAPSSCert)}, {server_peer, pem_to_der_cert(CRSAPSSCert)}}, + {#{server_config => [{certs_keys, [#{certfile => SRSAPSSRSAECert, keyfile => SRSAPSSRSAEKey}, + #{certfile => SRSAPSSCert, keyfile => SRSAPSSKey}]}, + {verify, verify_peer}, + {cacertfile, CRSAPSSRSAECACerts}], + client_config => [{certs_keys, [#{certfile => CRSAPSSRSAECert, keyfile => CRSAPSSRSAEKey}]}, + {verify, verify_peer}, {signature_algs, [rsa_pss_rsae_sha256]}, + {cacertfile, SRSAPSSRSAECACerts}] + }, + {client_peer, pem_to_der_cert(SRSAPSSRSAECert)}, {server_peer, pem_to_der_cert(CRSAPSSRSAECert)}} + ]; +test_config(_, Config) -> + RSAConf1 = ssl_test_lib:make_rsa_cert(Config), + SRSA1Opts = proplists:get_value(server_rsa_opts, RSAConf1), + CRSA1Opts = proplists:get_value(client_rsa_opts, RSAConf1), + + RSAConf2 = ssl_test_lib:make_rsa_1024_cert(Config), + SRSA2Opts = proplists:get_value(server_rsa_1024_opts, RSAConf2), + CRSA2Opts = proplists:get_value(client_rsa_1024_opts, RSAConf2), + + {SRSA1Cert, SRSA1Key, _SRSA1CACerts} = get_single_options(certfile, keyfile, cacertfile, SRSA1Opts), + {CRSA1Cert, CRSA1Key, _CRSA1CACerts} = get_single_options(certfile, keyfile, cacertfile, CRSA1Opts), + + {SRSA2Cert, SRSA2Key, SRSA2CACerts} = get_single_options(certfile, keyfile, cacertfile, SRSA2Opts), + {CRSA2Cert, CRSA2Key, CRSA2CACerts} = get_single_options(certfile, keyfile, cacertfile, CRSA2Opts), + + [{#{server_config => [{certs_keys, [#{certfile => SRSA2Cert, keyfile => SRSA2Key}, + #{certfile => SRSA1Cert, keyfile => SRSA1Key}]}, + {verify, verify_peer}, + {cacertfile, CRSA2CACerts}], + client_config => [{certs_keys, [#{certfile => CRSA2Cert, keyfile => CRSA2Key}, + #{certfile => CRSA1Cert, keyfile => CRSA1Key}]}, + {verify, verify_peer}, + {cacertfile, SRSA2CACerts}] + }, {client_peer, pem_to_der_cert(SRSA2Cert)}, {server_peer, pem_to_der_cert(CRSA2Cert)}}]. + +check_peercert(Socket, Cert) -> + case ssl:peercert(Socket) of + {ok, Cert} -> + ok; + {ok, Other} -> + {error, {{expected, public_key:pkix_decode_cert(Cert, otp)}, {got, public_key:pkix_decode_cert(Other, otp)}}} + end. + + +eddsa_cert_chains() -> + public_key:pkix_test_data(#{server_chain => #{root => ssl_test_lib:eddsa_conf(), + intermediates => [ssl_test_lib:eddsa_conf()], + peer => ssl_test_lib:eddsa_conf()}, + client_chain => #{root => ssl_test_lib:eddsa_conf(), + intermediates => [ssl_test_lib:eddsa_conf()], + peer => ssl_test_lib:eddsa_conf()}}). + +ecdsa_cert_chains() -> + public_key:pkix_test_data(#{server_chain => #{root => ssl_test_lib:ecdsa_conf(), + intermediates => [ssl_test_lib:ecdsa_conf()], + peer => ssl_test_lib:ecdsa_conf()}, + client_chain => #{root => ssl_test_lib:ecdsa_conf(), + intermediates => [ssl_test_lib:ecdsa_conf()], + peer => ssl_test_lib:ecdsa_conf()}}). +dsa_cert_chains() -> + public_key:pkix_test_data(#{server_chain => #{root => [{key, ssl_test_lib:hardcode_dsa_key(1)}], + intermediates => [[{key, ssl_test_lib:hardcode_dsa_key(2)}]], + peer => [{key, ssl_test_lib:hardcode_dsa_key(3)}] + }, + client_chain => #{root => [{key, ssl_test_lib:hardcode_dsa_key(3)}], + intermediates => [[{key, ssl_test_lib:hardcode_dsa_key(2)}]], + peer => [{key, ssl_test_lib:hardcode_dsa_key(1)}]}}). + +get_single_options(CertOptName, KeyOptName, CaOptName, Opts) -> + CertOpt = proplists:get_value(CertOptName, Opts), + KeyOpt = proplists:get_value(KeyOptName, Opts), + CaOpt = proplists:get_value(CaOptName, Opts), + {CertOpt, KeyOpt, CaOpt}. + +pem_to_der_cert(Pem) -> + [{'Certificate', Der, _}] = ssl_test_lib:pem_to_der(Pem), + Der. diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl index c303704f58..4489a758e0 100644 --- a/lib/ssl/test/ssl_test_lib.erl +++ b/lib/ssl/test/ssl_test_lib.erl @@ -126,6 +126,7 @@ client_msg/2, server_msg/2, hardcode_rsa_key/1, + hardcode_dsa_key/1, bigger_buffers/0, stop/2, working_openssl_client/0, -- 2.34.1
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor