Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:26
erlang
1651-Add-sign_fun-entry-in-key-config-option.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 1651-Add-sign_fun-entry-in-key-config-option.patch of Package erlang
From 3002db013159a6c6362c4bb41c89363544b7b6ab Mon Sep 17 00:00:00 2001 From: Luca Succi <luca.succi@stritzinger.com> Date: Mon, 3 Jul 2023 12:32:01 +0200 Subject: [PATCH 1/4] Add 'sign_fun' entry in 'key' config option This option allows the user to define a function tasked to sign an ssl message. This gives total freedom around key handling. Users are free to program such function the way they think is best, allowing them to support any private key storage or to delegate signature to any external service or device. Most notably: this allows to implement custom access to any HSM device. --- lib/public_key/src/public_key.erl | 40 ++++- lib/public_key/test/public_key_SUITE.erl | 45 ++++- lib/ssl/doc/src/ssl.xml | 34 +++- lib/ssl/src/ssl.erl | 206 +++++++++++++---------- lib/ssl/src/ssl_config.erl | 24 ++- lib/ssl/src/ssl_handshake.erl | 15 +- lib/ssl/test/ssl_cert_SUITE.erl | 8 + lib/ssl/test/ssl_cert_tests.erl | 57 +++++++ 8 files changed, 317 insertions(+), 112 deletions(-) diff --git a/lib/public_key/src/public_key.erl b/lib/public_key/src/public_key.erl index 858860e29c..99f12f3a95 100644 --- a/lib/public_key/src/public_key.erl +++ b/lib/public_key/src/public_key.erl @@ -112,10 +112,21 @@ test_root_cert/0 ]). --type public_key() :: rsa_public_key() | rsa_pss_public_key() | dsa_public_key() | ec_public_key() | ed_public_key() . --type private_key() :: rsa_private_key() | rsa_pss_private_key() | dsa_private_key() | ec_private_key() | ed_private_key() . +-type public_key() :: rsa_public_key() | + rsa_pss_public_key() | + dsa_public_key() | + ec_public_key() | + ed_public_key() . +-type private_key() :: rsa_private_key() | + rsa_pss_private_key() | + dsa_private_key() | + ec_private_key() | + ed_private_key() | + #{algorithm := eddsa | rsa_pss_pss | ecdsa | rsa | dsa, + sign_fun => fun()} . -type rsa_public_key() :: #'RSAPublicKey'{}. --type rsa_private_key() :: #'RSAPrivateKey'{}. +-type rsa_private_key() :: #'RSAPrivateKey'{} | #{algorithm := rsa, + encrypt_fun => fun()}. -type dss_public_key() :: integer(). -type rsa_pss_public_key() :: {rsa_pss_public_key(), #'RSASSA-PSS-params'{}}. -type rsa_pss_private_key() :: { #'RSAPrivateKey'{}, #'RSASSA-PSS-params'{}}. @@ -637,14 +648,14 @@ encrypt_private(PlainText, Key) -> Key :: rsa_private_key(), Options :: crypto:pk_encrypt_decrypt_opts(), CipherText :: binary() . -encrypt_private(PlainText, - #'RSAPrivateKey'{modulus = N, publicExponent = E, - privateExponent = D} = Key, - Options) +encrypt_private(PlainText, Key, Options) when is_binary(PlainText), - is_integer(N), is_integer(E), is_integer(D), is_list(Options) -> - crypto:private_encrypt(rsa, PlainText, format_rsa_private_key(Key), default_options(Options)). + Opts = default_options(Options), + case format_sign_key(Key) of + {extern, Fun} -> Fun(PlainText, Opts); + {rsa, CryptoKey} -> crypto:private_encrypt(rsa, PlainText, CryptoKey, Opts) + end. %%-------------------------------------------------------------------- %% Description: List available group sizes among the pre-computed dh groups @@ -840,6 +851,8 @@ sign(DigestOrPlainText, DigestType, Key, Options) -> case format_sign_key(Key) of badarg -> erlang:error(badarg, [DigestOrPlainText, DigestType, Key, Options]); + {extern, Fun} when is_function(Fun) -> + Fun(DigestOrPlainText, DigestType, Options); {Algorithm, CryptoKey} -> crypto:sign(Algorithm, DigestType, DigestOrPlainText, CryptoKey, Options) end. @@ -1505,8 +1518,17 @@ format_pkix_sign_key({#'RSAPrivateKey'{} = Key, _}) -> Key; format_pkix_sign_key(Key) -> Key. + +format_sign_key(#{encrypt_fun := KeyFun}) -> + {extern, KeyFun}; +format_sign_key(#{sign_fun := KeyFun}) -> + {extern, KeyFun}; format_sign_key(Key = #'RSAPrivateKey'{}) -> {rsa, format_rsa_private_key(Key)}; +format_sign_key({#'RSAPrivateKey'{} = Key, _}) -> + %% Params are handled in options arg + %% provided by caller. + {rsa, format_rsa_private_key(Key)}; format_sign_key(#'DSAPrivateKey'{p = P, q = Q, g = G, x = X}) -> {dss, [P, Q, G, X]}; format_sign_key(#'ECPrivateKey'{privateKey = PrivKey, parameters = {namedCurve, Curve} = Param}) diff --git a/lib/public_key/test/public_key_SUITE.erl b/lib/public_key/test/public_key_SUITE.erl index 0c8cf07fb5..ee1ed7b567 100644 --- a/lib/public_key/test/public_key_SUITE.erl +++ b/lib/public_key/test/public_key_SUITE.erl @@ -77,12 +77,16 @@ cert_pem/1, encrypt_decrypt/0, encrypt_decrypt/1, + encrypt_decrypt_sign_fun/0, + encrypt_decrypt_sign_fun/1, rsa_sign_verify/0, rsa_sign_verify/1, rsa_pss_sign_verify/0, rsa_pss_sign_verify/1, dsa_sign_verify/0, dsa_sign_verify/1, + custom_sign_fun_verify/0, + custom_sign_fun_verify/1, pkix/0, pkix/1, pkix_countryname/0, @@ -153,6 +157,7 @@ all() -> appup, {group, pem_decode_encode}, encrypt_decrypt, + encrypt_decrypt_sign_fun, {group, sign_verify}, pkix, pkix_countryname, @@ -190,7 +195,7 @@ groups() -> ec_pem_encode_generated, gen_ec_param_prime_field, gen_ec_param_char_2_field]}, {sign_verify, [], [rsa_sign_verify, rsa_pss_sign_verify, dsa_sign_verify, - eddsa_sign_verify_24_compat]} + eddsa_sign_verify_24_compat, custom_sign_fun_verify]} ]. %%------------------------------------------------------------------- init_per_suite(Config) -> @@ -655,6 +660,22 @@ encrypt_decrypt(Config) when is_list(Config) -> RsaEncrypted2 = public_key:encrypt_public(Msg, PublicKey), Msg = public_key:decrypt_private(RsaEncrypted2, PrivateKey), ok. + +%%-------------------------------------------------------------------- +encrypt_decrypt_sign_fun() -> + [{doc, "Test public_key:encrypt_private with user provided sign_fun"}]. +encrypt_decrypt_sign_fun(Config) when is_list(Config) -> + {PrivateKey, _DerKey} = erl_make_certs:gen_rsa(64), + #'RSAPrivateKey'{modulus=Mod, publicExponent=Exp} = PrivateKey, + EncryptFun = fun (PlainText, Options) -> + public_key:encrypt_private(PlainText, PrivateKey, Options) + end, + CustomPrivKey = #{encrypt_fun => EncryptFun}, + PublicKey = #'RSAPublicKey'{modulus=Mod, publicExponent=Exp}, + Msg = list_to_binary(lists:duplicate(5, "Foo bar 100")), + RsaEncrypted = public_key:encrypt_private(Msg, CustomPrivKey), + Msg = public_key:decrypt_public(RsaEncrypted, PublicKey), + ok. %%-------------------------------------------------------------------- rsa_sign_verify() -> @@ -731,6 +752,28 @@ dsa_sign_verify(Config) when is_list(Config) -> {DSAPublicKey, DSAParams}), false = public_key:verify(Digest, none, <<1:8, DigestSign/binary>>, {DSAPublicKey, DSAParams}). +%%-------------------------------------------------------------------- + +custom_sign_fun_verify() -> + [{doc, "Checks that public_key:sign correctly calls the `sign_fun`"}]. +custom_sign_fun_verify(Config) when is_list(Config) -> + {_, CaKey} = erl_make_certs:make_cert([{key, rsa}]), + PrivateRSA = public_key:pem_entry_decode(CaKey), + #'RSAPrivateKey'{modulus=Mod, publicExponent=Exp} = PrivateRSA, + PublicRSA = #'RSAPublicKey'{modulus=Mod, publicExponent=Exp}, + SignFun = fun (Msg, HashAlgo, Options) -> + public_key:sign(Msg, HashAlgo, PrivateRSA, Options) + end, + CustomKey = #{algorithm => rsa, sign_fun => SignFun}, + + Msg = list_to_binary(lists:duplicate(5, "Foo bar 100")), + RSASign = public_key:sign(Msg, sha, CustomKey), + true = public_key:verify(Msg, sha, RSASign, PublicRSA), + false = public_key:verify(<<1:8, Msg/binary>>, sha, RSASign, PublicRSA), + false = public_key:verify(Msg, sha, <<1:8, RSASign/binary>>, PublicRSA), + + RSASign1 = public_key:sign(Msg, md5, CustomKey), + true = public_key:verify(Msg, md5, RSASign1, PublicRSA). %%-------------------------------------------------------------------- pkix() -> diff --git a/lib/ssl/doc/src/ssl.xml b/lib/ssl/doc/src/ssl.xml index f719c55c32..1ae7d924e6 100644 --- a/lib/ssl/doc/src/ssl.xml +++ b/lib/ssl/doc/src/ssl.xml @@ -343,11 +343,33 @@ <datatype> <name name="key"/> <desc> - <p>The DER-encoded user's private key or a map referring to a crypto - engine and its key reference that optionally can be password protected, - see also <seemfa marker="crypto:crypto#engine_load/3"> crypto:engine_load/3 - </seemfa> and <seeguide marker="crypto:engine_load"> Crypto's Users Guide</seeguide>. If this option - is supplied, it overrides option <c>keyfile</c>.</p> + + <p>The user's private key. The map formats referring to a + crypto engine/provider (with key reference information) or Erlang fun, + can both be used for customized signing with + for instance hardware security modules (HSM) or trusted + platform modules (TPM). </p> + + <list> + <item><p>A DER encoded key will need to specify the ASN-1 type used to + create the encoding.</p></item> + + <item><p>An engine/provider needs to specify specific + information to support this concept and can optionally be + password protected, see also <seemfa + marker="crypto:crypto#engine_load/3"> crypto:engine_load/3 + </seemfa> and <seeguide marker="crypto:engine_load"> + Crypto's Users Guide</seeguide>. </p></item> + + <item><p>A fun option should include a fun that mimics <seemfa + marker="public_key:public_key#sign/4">public_key:sign/4</seemfa> + and possibly <seemfa + marker="public_key:public_key#encrypt_private/3">public_key:private_encrypt/4</seemfa> + if legacy versions TLS-1.0 and TLS-1.1 should be supported. </p></item> + </list> + + <p>If this option is supplied, it overrides option <c>keyfile</c>. + </p> </desc> </datatype> @@ -616,7 +638,7 @@ version. ROOT-CA, and so on. The default value is 10.</p> </desc> </datatype> - + <datatype> <name name="custom_verify"/> <desc> diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl index f21a0fe9b3..5a137c0566 100644 --- a/lib/ssl/src/ssl.erl +++ b/lib/ssl/src/ssl.erl @@ -84,7 +84,7 @@ signature_algs/2, eccs/0, eccs/1, - versions/0, + versions/0, groups/0, groups/1, format_error/1, @@ -111,9 +111,9 @@ -removed({cipher_suites, 1, "use cipher_suites/2,3 instead"}). -removed([{negotiated_next_protocol,1, - "use ssl:negotiated_protocol/1 instead"}]). + "use ssl:negotiated_protocol/1 instead"}]). -removed([{connection_info,1, - "use ssl:connection_information/[1,2] instead"}]). + "use ssl:connection_information/[1,2] instead"}]). -export_type([socket/0, sslsocket/0, @@ -350,11 +350,15 @@ -type cert() :: public_key:der_encoded(). -type cert_pem() :: file:filename(). -type key() :: {'RSAPrivateKey'| 'DSAPrivateKey' | 'ECPrivateKey' |'PrivateKeyInfo', - public_key:der_encoded()} | - #{algorithm := rsa | dss | ecdsa, + public_key:der_encoded()} | + #{algorithm := sign_algo(), engine := crypto:engine_ref(), key_id := crypto:key_id(), - password => crypto:password()}. % exported + password => crypto:password()} | + #{algorithm := sign_algo(), + sign_fun := fun(), + encrypt_fun => fun() %% Only TLS-1.0, TLS-1.1 and rsa-key + }. % exported -type key_pem() :: file:filename(). -type key_pem_password() :: iodata() | fun(() -> iodata()). -type certs_keys() :: [cert_key_conf()]. @@ -367,12 +371,11 @@ -type ciphers() :: [erl_cipher_suite()] | string(). % (according to old API) exported -type cipher_filters() :: list({key_exchange | cipher | mac | prf, - algo_filter()}). % exported + algo_filter()}). % exported -type algo_filter() :: fun((kex_algo()|cipher()|hash()|aead|default_prf) -> true | false). -type keep_secrets() :: boolean(). -type secure_renegotiation() :: boolean(). -type allowed_cert_chain_length() :: integer(). - -type custom_verify() :: {Verifyfun :: fun(), InitialUserState :: any()}. -type policy_opt() :: {policy_set, [public_key:oid()]} | {explicit_policy, boolean()} | {inhibit_policy_mapping, boolean()} | {inhibit_any_policy, boolean()}. -type crl_check() :: boolean() | peer | best_effort. @@ -430,9 +433,9 @@ {use_ticket, use_ticket()} | {early_data, client_early_data()} | {use_srtp, use_srtp()}. - %% {ocsp_stapling, ocsp_stapling()} | - %% {ocsp_responder_certs, ocsp_responder_certs()} | - %% {ocsp_nonce, ocsp_nonce()}. +%% {ocsp_stapling, ocsp_stapling()} | +%% {ocsp_responder_certs, ocsp_responder_certs()} | +%% {ocsp_nonce, ocsp_nonce()}. -type client_verify_type() :: verify_type(). -type client_reuse_session() :: session_id() | {session_id(), SessionData::binary()}. @@ -578,9 +581,9 @@ stop() -> %%-------------------------------------------------------------------- -spec connect(TCPSocket, TLSOptions) -> - {ok, sslsocket()} | - {error, reason()} | - {option_not_a_key_value_tuple, any()} when + {ok, sslsocket()} | + {error, reason()} | + {option_not_a_key_value_tuple, any()} when TCPSocket :: socket(), TLSOptions :: [tls_client_option()]. @@ -588,22 +591,22 @@ connect(Socket, SslOptions) -> connect(Socket, SslOptions, infinity). -spec connect(TCPSocket, TLSOptions, Timeout) -> - {ok, sslsocket()} | {error, reason()} when + {ok, sslsocket()} | {error, reason()} when TCPSocket :: socket(), TLSOptions :: [tls_client_option()], Timeout :: timeout(); (Host, Port, TLSOptions) -> - {ok, sslsocket()} | - {ok, sslsocket(),Ext :: protocol_extensions()} | - {error, reason()} | - {option_not_a_key_value_tuple, any()} when + {ok, sslsocket()} | + {ok, sslsocket(),Ext :: protocol_extensions()} | + {error, reason()} | + {option_not_a_key_value_tuple, any()} when Host :: host(), Port :: inet:port_number(), TLSOptions :: [tls_client_option()]. connect(Socket, SslOptions0, Timeout) when is_list(SslOptions0) andalso (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) -> - + try CbInfo = handle_option_cb_info(SslOptions0, tls), Transport = element(1, CbInfo), @@ -617,10 +620,10 @@ connect(Host, Port, Options) -> connect(Host, Port, Options, infinity). -spec connect(Host, Port, TLSOptions, Timeout) -> - {ok, sslsocket()} | - {ok, sslsocket(),Ext :: protocol_extensions()} | - {error, reason()} | - {option_not_a_key_value_tuple, any()} when + {ok, sslsocket()} | + {ok, sslsocket(),Ext :: protocol_extensions()} | + {error, reason()} | + {option_not_a_key_value_tuple, any()} when Host :: host(), Port :: inet:port_number(), TLSOptions :: [tls_client_option()], @@ -664,7 +667,7 @@ listen(Port, Options0) -> %% Description: Performs transport accept on an ssl listen socket %%-------------------------------------------------------------------- -spec transport_accept(ListenSocket) -> {ok, SslSocket} | - {error, reason()} when + {error, reason()} when ListenSocket :: sslsocket(), SslSocket :: sslsocket(). @@ -672,7 +675,7 @@ transport_accept(ListenSocket) -> transport_accept(ListenSocket, infinity). -spec transport_accept(ListenSocket, Timeout) -> {ok, SslSocket} | - {error, reason()} when + {error, reason()} when ListenSocket :: sslsocket(), Timeout :: timeout(), SslSocket :: sslsocket(). @@ -686,7 +689,7 @@ transport_accept(#sslsocket{pid = {ListenSocket, dtls_gen_connection -> dtls_socket:accept(ListenSocket, Config, Timeout) end. - + %%-------------------------------------------------------------------- %% %% Description: Performs accept on an ssl listen socket. e.i. performs @@ -729,9 +732,9 @@ handshake(#sslsocket{} = Socket, Timeout) when (is_integer(Timeout) andalso Tim handshake(ListenSocket, SslOptions) -> handshake(ListenSocket, SslOptions, infinity). -spec handshake(Socket, Options, Timeout) -> - {ok, SslSocket} | - {ok, SslSocket, Ext} | - {error, Reason} when + {ok, SslSocket} | + {ok, SslSocket, Ext} | + {error, Reason} when Socket :: socket() | sslsocket(), SslSocket :: sslsocket(), Options :: [server_option()], @@ -782,7 +785,7 @@ handshake(Socket, SslOptions, Timeout) when (is_integer(Timeout) andalso Timeout %%-------------------------------------------------------------------- -spec handshake_continue(HsSocket, Options) -> - {ok, SslSocket} | {error, Reason} when + {ok, SslSocket} | {error, Reason} when HsSocket :: sslsocket(), Options :: [tls_client_option() | tls_server_option()], SslSocket :: sslsocket(), @@ -795,7 +798,7 @@ handshake_continue(Socket, SSLOptions) -> handshake_continue(Socket, SSLOptions, infinity). %%-------------------------------------------------------------------- -spec handshake_continue(HsSocket, Options, Timeout) -> - {ok, SslSocket} | {error, Reason} when + {ok, SslSocket} | {error, Reason} when HsSocket :: sslsocket(), Options :: [tls_client_option() | tls_server_option()], Timeout :: timeout(), @@ -850,7 +853,7 @@ close(#sslsocket{pid = [TLSPid|_]}, Other end; close(#sslsocket{pid = [TLSPid|_]}, Timeout) when is_pid(TLSPid), - (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) -> + (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) -> ssl_gen_statem:close(TLSPid, {close, Timeout}); close(#sslsocket{pid = {dtls, #config{dtls_handler = {_, _}}}} = DTLSListen, _) -> dtls_socket:close(DTLSListen); @@ -963,7 +966,7 @@ connection_information(#sslsocket{pid = [Pid|_]}, Items) when is_pid(Pid) -> %%-------------------------------------------------------------------- -spec peername(SslSocket) -> {ok, {Address, Port}} | - {error, reason()} when + {error, reason()} when SslSocket :: sslsocket(), Address :: inet:ip_address(), Port :: inet:port_number(). @@ -1021,12 +1024,12 @@ negotiated_protocol(#sslsocket{pid = [Pid|_]}) when is_pid(Pid) -> %% TLS/DTLS version %%-------------------------------------------------------------------- cipher_suites(Description, Version) when Version == 'tlsv1.3'; - Version == 'tlsv1.2'; - Version == 'tlsv1.1'; - Version == tlsv1 -> + Version == 'tlsv1.2'; + Version == 'tlsv1.1'; + Version == tlsv1 -> cipher_suites(Description, tls_record:protocol_version_name(Version)); cipher_suites(Description, Version) when Version == 'dtlsv1.2'; - Version == 'dtlsv1'-> + Version == 'dtlsv1'-> cipher_suites(Description, dtls_record:protocol_version_name(Version)); cipher_suites(Description, Version) -> [ssl_cipher_format:suite_bin_to_map(Suite) || Suite <- supported_suites(Description, Version)]. @@ -1040,12 +1043,12 @@ cipher_suites(Description, Version) -> %% TLS/DTLS version %%-------------------------------------------------------------------- cipher_suites(Description, Version, StringType) when Version == 'tlsv1.3'; - Version == 'tlsv1.2'; - Version == 'tlsv1.1'; - Version == tlsv1 -> + Version == 'tlsv1.2'; + Version == 'tlsv1.1'; + Version == tlsv1 -> cipher_suites(Description, tls_record:protocol_version_name(Version), StringType); cipher_suites(Description, Version, StringType) when Version == 'dtlsv1.2'; - Version == 'dtlsv1'-> + Version == 'dtlsv1'-> cipher_suites(Description, dtls_record:protocol_version_name(Version), StringType); cipher_suites(Description, Version, rfc) -> [ssl_cipher_format:suite_map_to_str(ssl_cipher_format:suite_bin_to_map(Suite)) @@ -1194,7 +1197,7 @@ groups(default) -> %%-------------------------------------------------------------------- -spec getopts(SslSocket, OptionNames) -> - {ok, [gen_tcp:option()]} | {error, reason()} when + {ok, [gen_tcp:option()]} | {error, reason()} when SslSocket :: sslsocket(), OptionNames :: [gen_tcp:option_name()]. %% @@ -1286,18 +1289,18 @@ setopts(#sslsocket{}, Options) -> %%--------------------------------------------------------------- -spec getstat(SslSocket) -> - {ok, OptionValues} | {error, inet:posix()} when + {ok, OptionValues} | {error, inet:posix()} when SslSocket :: sslsocket(), OptionValues :: [{inet:stat_option(), integer()}]. %% %% Description: Get all statistic options for a socket. %%-------------------------------------------------------------------- getstat(Socket) -> - getstat(Socket, inet:stats()). + getstat(Socket, inet:stats()). %%--------------------------------------------------------------- -spec getstat(SslSocket, Options) -> - {ok, OptionValues} | {error, inet:posix()} when + {ok, OptionValues} | {error, inet:posix()} when SslSocket :: sslsocket(), Options :: [inet:stat_option()], OptionValues :: [{inet:stat_option(), integer()}]. @@ -1350,7 +1353,7 @@ shutdown(#sslsocket{pid = [Pid|_]}, How) when is_pid(Pid) -> %%-------------------------------------------------------------------- -spec sockname(SslSocket) -> - {ok, {Address, Port}} | {error, reason()} when + {ok, {Address, Port}} | {error, reason()} when SslSocket :: sslsocket(), Address :: inet:ip_address(), Port :: inet:port_number(). @@ -1381,18 +1384,18 @@ versions() -> ImplementedTLSVsns = ?ALL_AVAILABLE_VERSIONS, ImplementedDTLSVsns = ?ALL_AVAILABLE_DATAGRAM_VERSIONS, - TLSCryptoSupported = fun(Vsn) -> - tls_record:sufficient_crypto_support(Vsn) + TLSCryptoSupported = fun(Vsn) -> + tls_record:sufficient_crypto_support(Vsn) + end, + DTLSCryptoSupported = fun(Vsn) -> + tls_record:sufficient_crypto_support(dtls_v1:corresponding_tls_version(Vsn)) end, - DTLSCryptoSupported = fun(Vsn) -> - tls_record:sufficient_crypto_support(dtls_v1:corresponding_tls_version(Vsn)) - end, SupportedTLSVsns = [tls_record:protocol_version(Vsn) || Vsn <- ConfTLSVsns, TLSCryptoSupported(Vsn)], SupportedDTLSVsns = [dtls_record:protocol_version(Vsn) || Vsn <- ConfDTLSVsns, DTLSCryptoSupported(Vsn)], AvailableTLSVsns = [Vsn || Vsn <- ImplementedTLSVsns, TLSCryptoSupported(tls_record:protocol_version_name(Vsn))], AvailableDTLSVsns = [Vsn || Vsn <- ImplementedDTLSVsns, DTLSCryptoSupported(dtls_record:protocol_version_name(Vsn))], - + [{ssl_app, ?VSN}, {supported, SupportedTLSVsns}, {supported_dtls, SupportedDTLSVsns}, @@ -1409,7 +1412,7 @@ versions() -> %% Description: Initiates a renegotiation. %%-------------------------------------------------------------------- renegotiate(#sslsocket{pid = [Pid, Sender |_]} = Socket) when is_pid(Pid), - is_pid(Sender) -> + is_pid(Sender) -> case ssl:connection_information(Socket, [protocol]) of {ok, [{protocol, 'tlsv1.3'}]} -> {error, notsup}; @@ -1533,7 +1536,7 @@ str_to_suite(CipherSuiteName) -> _:_ -> {error, {not_recognized, CipherSuiteName}} end. - + %%%-------------------------------------------------------------- %%% Internal functions %%%-------------------------------------------------------------------- @@ -1810,21 +1813,21 @@ opt_verify_fun(UserOpts, Opts, _Env) -> Opts#{verify_fun => VerifyFun}. none_verify_fun() -> - fun(_, {bad_cert, _}, UserState) -> - {valid, UserState}; - (_, {extension, #'Extension'{critical = true}}, UserState) -> - %% This extension is marked as critical, so - %% certificate verification should fail if we don't - %% understand the extension. However, this is - %% `verify_none', so let's accept it anyway. - {valid, UserState}; - (_, {extension, _}, UserState) -> - {unknown, UserState}; - (_, valid, UserState) -> + fun(_, {bad_cert, _}, UserState) -> + {valid, UserState}; + (_, {extension, #'Extension'{critical = true}}, UserState) -> + %% This extension is marked as critical, so + %% certificate verification should fail if we don't + %% understand the extension. However, this is + %% `verify_none', so let's accept it anyway. + {valid, UserState}; + (_, {extension, _}, UserState) -> + {unknown, UserState}; + (_, valid, UserState) -> {valid, UserState}; - (_, valid_peer, UserState) -> - {valid, UserState} - end. + (_, valid_peer, UserState) -> + {valid, UserState} + end. convert_verify_fun() -> fun(_,{bad_cert, _} = Reason, OldFun) -> @@ -1840,7 +1843,7 @@ validate_policy_opts([{Opt, Bool} | Rest]) when Opt == explicit_policy; validate_policy_opts([Opt| _]) -> option_error(cert_policy_opts, Opt). -opt_certs(UserOpts, #{log_level := LogLevel} = Opts0, Env) -> +opt_certs(UserOpts, #{log_level := LogLevel, versions := Versions} = Opts0, Env) -> case get_opt_list(certs_keys, [], UserOpts, Opts0) of {Where, []} when Where =/= new -> opt_old_certs(UserOpts, #{}, Opts0, Env); @@ -1848,11 +1851,11 @@ opt_certs(UserOpts, #{log_level := LogLevel} = Opts0, Env) -> opt_old_certs(UserOpts, CertKey, Opts0, Env); {Where, CKs} when is_list(CKs) -> warn_override(Where, UserOpts, certs_keys, [cert,certfile,key,keyfile,password], LogLevel), - Opts0#{certs_keys => [check_cert_key(CK, #{}, LogLevel) || CK <- CKs]} + Opts0#{certs_keys => [check_cert_key(Versions, CK, #{}, LogLevel) || CK <- CKs]} end. -opt_old_certs(UserOpts, CertKeys, #{log_level := LogLevel}=SSLOpts, _Env) -> - CK = check_cert_key(UserOpts, CertKeys, LogLevel), +opt_old_certs(UserOpts, CertKeys, #{log_level := LogLevel, versions := Versions}=SSLOpts, _Env) -> + CK = check_cert_key(Versions, UserOpts, CertKeys, LogLevel), case maps:keys(CK) =:= [] of true -> SSLOpts#{certs_keys => []}; @@ -1860,7 +1863,7 @@ opt_old_certs(UserOpts, CertKeys, #{log_level := LogLevel}=SSLOpts, _Env) -> SSLOpts#{certs_keys => [CK]} end. -check_cert_key(UserOpts, CertKeys, LogLevel) -> +check_cert_key(Versions, UserOpts, CertKeys, LogLevel) -> CertKeys0 = case get_opt(cert, undefined, UserOpts, CertKeys) of {Where, Cert} when is_binary(Cert) -> warn_override(Where, UserOpts, cert, [certfile], LogLevel), @@ -1895,7 +1898,15 @@ check_cert_key(UserOpts, CertKeys, LogLevel) -> KF == 'RSAPrivateKey'; KF == 'DSAPrivateKey'; KF == 'ECPrivateKey'; KF == 'PrivateKeyInfo' -> CertKeys0#{key => Key}; - {_, #{engine := _, key_id := _, algorithm := _} = Key} -> + {_, #{engine := _, key_id := _, algorithm := Algo} = Key} -> + check_key_algo_version_dep(Versions, Algo), + CertKeys0#{key => Key}; + {_, #{sign_fun := _, algorithm := Algo} = Key} -> + check_key_algo_version_dep(Versions, Algo), + check_key_legacy_version_dep(Versions, Key, Algo), + CertKeys0#{key => Key}; + {_, #{encrypt_fun := _, algorithm := rsa} = Key} -> + check_key_legacy_version_dep(Versions, Key), CertKeys0#{key => Key}; {new, Err1} -> option_error(key, Err1) @@ -1912,6 +1923,29 @@ check_cert_key(UserOpts, CertKeys, LogLevel) -> end, CertKeys2. +check_key_algo_version_dep(Versions, eddsa) -> + assert_version_dep(key, Versions, ['tlsv1.3']); +check_key_algo_version_dep(Versions, rsa_pss_pss) -> + assert_version_dep(key, Versions, ['tlsv1.3', 'tlsv1.2']); +check_key_algo_version_dep(Versions, dsa) -> + assert_version_dep(key, Versions, ['tlsv1.2', 'tlsv1.1', 'tlsv1']); +check_key_algo_version_dep(_,_) -> + true. + +check_key_legacy_version_dep(Versions, Key, rsa) -> + check_key_legacy_version_dep(Versions, Key); +check_key_legacy_version_dep(_,_,_) -> + true. + +check_key_legacy_version_dep(Versions, Key) -> + EncryptFun = maps:get(encrypt_fun, Key, undefined), + case EncryptFun of + undefined -> + assert_version_dep(key, Versions, ['tlsv1.3', 'tlsv1.2']); + _ -> + assert_version_dep(key, Versions, ['tlsv1.1', 'tlsv1']) + end. + opt_cacerts(UserOpts, #{verify := Verify, log_level := LogLevel, versions := Versions} = Opts, #{role := Role}) -> {_, CaCerts} = get_opt_list(cacerts, undefined, UserOpts, Opts), @@ -2244,7 +2278,7 @@ opt_identity(UserOpts, #{versions := Versions} = Opts, _Env) -> PSKSize = byte_size(PSK1), assert_version_dep(psk_identity, Versions, ['tlsv1','tlsv1.1','tlsv1.2']), option_error(not (0 < PSKSize andalso PSKSize < 65536), - psk_identity, {psk_identity, PSK0}), + psk_identity, {psk_identity, PSK0}), PSK1; {_, PSK0} -> PSK0 @@ -2256,7 +2290,7 @@ opt_identity(UserOpts, #{versions := Versions} = Opts, _Env) -> UserSize = byte_size(User), assert_version_dep(srp_identity, Versions, ['tlsv1','tlsv1.1','tlsv1.2']), option_error(not (0 < UserSize andalso UserSize < 65536), - srp_identity, {srp_identity, PSK0}), + srp_identity, {srp_identity, PSK0}), {User, unicode:characters_to_binary(S2)}; {new, Err} -> option_error(srp_identity, Err); @@ -2702,7 +2736,7 @@ all_suites([?TLS_1_3, Version1 |_]) -> ssl_cipher:all_suites(Version1) ++ ssl_cipher:anonymous_suites(Version1); all_suites([Version|_]) -> - ssl_cipher:all_suites(Version) ++ + ssl_cipher:all_suites(Version) ++ ssl_cipher:anonymous_suites(Version). tuple_to_map({Kex, Cipher, Mac}) -> @@ -2868,7 +2902,7 @@ connection_cb(tls) -> connection_cb(dtls) -> dtls_gen_connection; connection_cb(Opts) -> - connection_cb(proplists:get_value(protocol, Opts, tls)). + connection_cb(proplists:get_value(protocol, Opts, tls)). %% Assert that basic options are on the format {Key, Value} @@ -2952,4 +2986,4 @@ format_ocsp_params(Map) -> Nonce = maps:get(ocsp_nonce, Map, '?'), Certs = maps:get(ocsp_responder_certs, Map, '?'), io_lib:format("Stapling = ~W Nonce = ~W Certs = ~W", - [Stapling, 5, Nonce, 5, Certs, 5]). + [Stapling, 5, Nonce, 5, Certs, 5]). diff --git a/lib/ssl/src/ssl_config.erl b/lib/ssl/src/ssl_config.erl index 761a4f4315..fc6a305c32 100644 --- a/lib/ssl/src/ssl_config.erl +++ b/lib/ssl/src/ssl_config.erl @@ -87,6 +87,9 @@ group_pairs([#{private_key := #'DSAPrivateKey'{}} = Pair | Rest], #{dsa := 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, sign_fun := _}} = Pair | Rest], Group) -> + Pairs = maps:get(Alg, Group), + group_pairs(Rest, Group#{Alg => [Pair | Pairs]}); group_pairs([#{private_key := #{algorithm := Alg, engine := _}} = Pair | Rest], Group) -> Pairs = maps:get(Alg, Group), group_pairs(Rest, Group#{Alg => [Pair | Pairs]}); @@ -107,15 +110,22 @@ prioritize_groups(#{eddsa := EDDSA, prio_eddsa(EDDSA) -> %% Engine not supported yet - using_curve({namedCurve, ?'id-Ed25519'}, EDDSA, []) ++ using_curve({namedCurve, ?'id-Ed448'}, EDDSA, []). + SignFunPairs = [Pair || Pair = #{private_key := #{sign_fun := _}} <- EDDSA], + SignFunPairs + ++ using_curve({namedCurve, ?'id-Ed25519'}, EDDSA, []) + ++ using_curve({namedCurve, ?'id-Ed448'}, EDDSA, []). prio_ecdsa(ECDSA, Curves) -> EnginePairs = [Pair || Pair = #{private_key := #{engine := _}} <- ECDSA], + SignFunPairs = [Pair || Pair = #{private_key := #{sign_fun := _}} <- ECDSA], - EnginePairs ++ lists:foldr(fun(Curve, AccIn) -> - CurveOid = pubkey_cert_records:namedCurves(Curve), - Pairs = using_curve({namedCurve, CurveOid}, ECDSA -- EnginePairs, []), - Pairs ++ AccIn - end, [], Curves). + EnginePairs + ++ SignFunPairs + ++ lists:foldr( + fun(Curve, AccIn) -> + CurveOid = pubkey_cert_records:namedCurves(Curve), + Pairs = using_curve({namedCurve, CurveOid}, ECDSA -- EnginePairs -- SignFunPairs, []), + Pairs ++ AccIn + end, [], Curves). using_curve(_, [], Acc) -> lists:reverse(Acc); using_curve(Curve, [#{private_key := #'ECPrivateKey'{parameters = Curve}} = Pair | Rest], Acc) -> @@ -265,6 +275,8 @@ init_certificate_file(CertFile, PemCache, Role) -> file_error(CertFile, {certfile, Reason}) end. +init_private_key(#{algorithm := _, sign_fun := _SignFun} = Key, _, _) -> + Key; init_private_key(#{algorithm := Alg} = Key, _, _PemCache) when Alg =:= ecdsa; Alg =:= rsa; Alg =:= dss -> case maps:is_key(engine, Key) andalso maps:is_key(key_id, Key) of diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl index 05a084a9f2..c72c950d1b 100644 --- a/lib/ssl/src/ssl_handshake.erl +++ b/lib/ssl/src/ssl_handshake.erl @@ -2147,14 +2147,18 @@ do_digitally_signed(Version, Msg, HashAlgo, {#'RSAPrivateKey'{} = Key, #'RSASSA-PSS-params'{}}, SignAlgo) when ?TLS_GTE(Version, ?TLS_1_2) -> Options = signature_options(SignAlgo, HashAlgo), public_key:sign(Msg, HashAlgo, Key, Options); -do_digitally_signed(Version, {digest, Digest}, _HashAlgo, #'RSAPrivateKey'{} = Key, rsa) when ?TLS_LTE(Version, ?TLS_1_1) -> +do_digitally_signed(Version, {digest, Digest}, _HashAlgo, #'RSAPrivateKey'{} = Key, rsa) + when ?TLS_LTE(Version, ?TLS_1_1) -> public_key:encrypt_private(Digest, Key, [{rsa_pad, rsa_pkcs1_padding}]); +do_digitally_signed(Version, {digest, Digest}, _HashAlgo, #{algorithm := rsa, encrypt_fun := _} = Key, rsa) + when ?TLS_LTE(Version, ?TLS_1_1) -> + public_key:encrypt_private(Digest, Key, [{rsa_pad, rsa_pkcs1_padding}]); do_digitally_signed(Version, {digest, Digest}, _, - #{algorithm := rsa} = Engine, rsa) when ?TLS_LTE(Version, ?TLS_1_1) -> + #{algorithm := rsa, engine := _} = Engine, rsa) when ?TLS_LTE(Version, ?TLS_1_1) -> crypto:private_encrypt(rsa, Digest, maps:remove(algorithm, Engine), rsa_pkcs1_padding); -do_digitally_signed(_, Msg, HashAlgo, #{algorithm := Alg} = Engine, SignAlgo) -> +do_digitally_signed(_, Msg, HashAlgo, #{algorithm := Alg, engine := _} = Engine, SignAlgo) -> Options = signature_options(SignAlgo, HashAlgo), crypto:sign(Alg, HashAlgo, Msg, maps:remove(algorithm, Engine), Options); do_digitally_signed(Version, {digest, _} = Msg , HashAlgo, Key, _) when ?TLS_LTE(Version,?TLS_1_1) -> @@ -2162,7 +2166,6 @@ do_digitally_signed(Version, {digest, _} = Msg , HashAlgo, Key, _) when ?TLS_LTE do_digitally_signed(_, Msg, HashAlgo, Key, SignAlgo) -> Options = signature_options(SignAlgo, HashAlgo), public_key:sign(Msg, HashAlgo, Key, Options). - signature_options(SignAlgo, HashAlgo) when SignAlgo =:= rsa_pss_rsae orelse SignAlgo =:= rsa_pss_pss -> @@ -2191,6 +2194,10 @@ bad_key(#'ECPrivateKey'{}) -> unacceptable_ecdsa_key; bad_key(#{algorithm := rsa}) -> unacceptable_rsa_key; +bad_key(#{algorithm := rsa_pss_pss}) -> + unacceptable_rsa_pss_pss_key; +bad_key(#{algorithm := eddsa}) -> + unacceptable_eddsa_key; bad_key(#{algorithm := ecdsa}) -> unacceptable_ecdsa_key. diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl index 28f8d06aa7..5f6007a1a0 100644 --- a/lib/ssl/test/ssl_cert_SUITE.erl +++ b/lib/ssl/test/ssl_cert_SUITE.erl @@ -43,6 +43,8 @@ no_auth/1, auth/0, auth/1, + client_auth_custom_key/0, + client_auth_custom_key/1, client_auth_empty_cert_accepted/0, client_auth_empty_cert_accepted/1, client_auth_empty_cert_rejected/0, @@ -228,6 +230,7 @@ all_version_tests() -> [ no_auth, auth, + client_auth_custom_key, client_auth_empty_cert_accepted, client_auth_empty_cert_rejected, client_auth_use_partial_chain, @@ -459,6 +462,11 @@ auth() -> auth(Config) -> ssl_cert_tests:auth(Config). %%-------------------------------------------------------------------- +client_auth_custom_key() -> + ssl_cert_tests:client_auth_custom_key(). +client_auth_custom_key(Config) -> + ssl_cert_tests:client_auth_custom_key(Config). +%%-------------------------------------------------------------------- client_auth_empty_cert_accepted() -> ssl_cert_tests:client_auth_empty_cert_accepted(). client_auth_empty_cert_accepted(Config) -> diff --git a/lib/ssl/test/ssl_cert_tests.erl b/lib/ssl/test/ssl_cert_tests.erl index 2749d16194..d8795138ae 100644 --- a/lib/ssl/test/ssl_cert_tests.erl +++ b/lib/ssl/test/ssl_cert_tests.erl @@ -29,6 +29,8 @@ no_auth/1, auth/0, auth/1, + client_auth_custom_key/0, + client_auth_custom_key/1, client_auth_empty_cert_accepted/0, client_auth_empty_cert_accepted/1, client_auth_empty_cert_rejected/0, @@ -97,7 +99,35 @@ auth(Config) -> end, ServerOpts = [{verify, verify_peer} | ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config)], ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config). +%%-------------------------------------------------------------------- +client_auth_custom_key() -> + [{doc,"Test that client and server can connect using their own signature function"}]. + +client_auth_custom_key(Config) when is_list(Config) -> + Version = proplists:get_value(version,Config), + ClientOpts0 = case Version of + 'tlsv1.3' -> + [{verify, verify_peer}, + {certificate_authorities, true} | + ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config)]; + _ ->[{verify, verify_peer} | ssl_test_lib:ssl_options(extra_client, client_cert_opts, Config)] + end, + ClientKeyFilePath = proplists:get_value(keyfile, ClientOpts0), + [ClientKeyEntry] = ssl_test_lib:pem_to_der(ClientKeyFilePath), + ClientKey = ssl_test_lib:public_key(public_key:pem_entry_decode(ClientKeyEntry)), + ClientCustomKey = choose_custom_key(ClientKey, Version), + + ClientOpts = [ ClientCustomKey | proplists:delete(key, proplists:delete(keyfile, ClientOpts0))], + + ServerOpts0 = ssl_test_lib:ssl_options(extra_server, server_cert_opts, Config), + ServerKeyFilePath = proplists:get_value(keyfile, ServerOpts0), + [ServerKeyEntry] = ssl_test_lib:pem_to_der(ServerKeyFilePath), + ServerKey = ssl_test_lib:public_key(public_key:pem_entry_decode(ServerKeyEntry)), + ServerCustomKey = choose_custom_key(ServerKey, Version), + ServerOpts = [ ServerCustomKey, {verify, verify_peer} | ServerOpts0], + + ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config). %%-------------------------------------------------------------------- client_auth_empty_cert_accepted() -> [{doc,"Client sends empty cert chain as no cert is configured and server allows it"}]. @@ -517,3 +547,30 @@ group_config(Config, ServerOpts, ClientOpts) -> {[{supported_groups, [x448, x25519]} | ServerOpts], [{groups,"P-256:X25519"} | ClientOpts]} end. + +choose_custom_key(#'RSAPrivateKey'{} = Key, Version) + when (Version == 'dtlsv1') or (Version == 'tlsv1') or (Version == 'tlsv1.1') -> + EFun = fun (PlainText, Options) -> + public_key:encrypt_private(PlainText, Key, Options) + end, + SFun = fun (Msg, HashAlgo, Options) -> + public_key:sign(Msg, HashAlgo, Key, Options) + end, + {key, #{algorithm => rsa, sign_fun => SFun, encrypt_fun => EFun}}; +choose_custom_key(Key, _) -> + Fun = fun (Msg, HashAlgo, Options) -> + public_key:sign(Msg, HashAlgo, Key, Options) + end, + {key, #{algorithm => alg_key(Key), sign_fun => Fun}}. + +alg_key(#'RSAPrivateKey'{}) -> + rsa; +alg_key({#'RSAPrivateKey'{}, #'RSASSA-PSS-params'{}}) -> + rsa_pss_pss; +alg_key(#'DSAPrivateKey'{}) -> + dsa; +alg_key(#'ECPrivateKey'{parameters = {namedCurve, CurveOId}}) when CurveOId == ?'id-Ed25519' orelse + CurveOId == ?'id-Ed448' -> + eddsa; +alg_key(#'ECPrivateKey'{}) -> + ecdsa. -- 2.35.3
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