Skip to content

Commit c4e2704

Browse files
committed
ssl, public_key: Add possiblity to provide customize options to key signing fun
1 parent 4d8b10e commit c4e2704

File tree

5 files changed

+25
-7
lines changed

5 files changed

+25
-7
lines changed

lib/public_key/doc/src/public_key.xml

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -145,6 +145,14 @@
145145
</desc>
146146
</datatype>
147147

148+
<datatype>
149+
<name name="custom_key_opts"/>
150+
<desc>
151+
<p>Can be provided together with a custom private key, that specifies a key fun,
152+
to provide additional options understood by the fun.</p>
153+
</desc>
154+
</datatype>
155+
148156
<datatype>
149157
<name name="ed_oid_name"/>
150158
<desc>

lib/public_key/src/public_key.erl

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -124,6 +124,7 @@
124124
ed_private_key() |
125125
#{algorithm := eddsa | rsa_pss_pss | ecdsa | rsa | dsa,
126126
sign_fun => fun()} .
127+
-type custom_key_opts() :: [term()].
127128
-type rsa_public_key() :: #'RSAPublicKey'{}.
128129
-type rsa_private_key() :: #'RSAPrivateKey'{} | #{algorithm := rsa,
129130
encrypt_fun => fun()}.
@@ -646,7 +647,7 @@ encrypt_private(PlainText, Key) ->
646647
CipherText
647648
when PlainText :: binary(),
648649
Key :: rsa_private_key(),
649-
Options :: crypto:pk_encrypt_decrypt_opts(),
650+
Options :: crypto:pk_encrypt_decrypt_opts() | custom_key_opts(),
650651
CipherText :: binary() .
651652
encrypt_private(PlainText, Key, Options)
652653
when is_binary(PlainText),
@@ -842,7 +843,7 @@ sign(DigestOrPlainText, DigestType, Key) ->
842843
Signature when Msg :: binary() | {digest,binary()},
843844
DigestType :: digest_type(),
844845
Key :: private_key(),
845-
Options :: crypto:pk_sign_verify_opts(),
846+
Options :: crypto:pk_sign_verify_opts() | custom_key_opts(),
846847
Signature :: binary() .
847848
sign(Digest, none, Key = #'DSAPrivateKey'{}, Options) when is_binary(Digest) ->
848849
%% Backwards compatible

lib/ssl/doc/src/ssl.xml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -345,7 +345,7 @@
345345
<desc>
346346

347347
<p>The user's private key. The map formats referring to a
348-
crypto engine/provider (with key reference information) or Erlang fun,
348+
crypto engine/provider (with key reference information) or Erlang fun (with possible custom options),
349349
can both be used for customized signing with
350350
for instance hardware security modules (HSM) or trusted
351351
platform modules (TPM). </p>

lib/ssl/src/ssl.erl

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -355,7 +355,9 @@
355355
password => crypto:password()} |
356356
#{algorithm := sign_algo(),
357357
sign_fun := fun(),
358-
encrypt_fun => fun() %% Only TLS-1.0, TLS-1.1 and rsa-key
358+
sign_opts => list(),
359+
encrypt_fun => fun(), %% Only TLS-1.0, TLS-1.1 and rsa-key
360+
encrypt_opts => list()
359361
}. % exported
360362
-type key_pem() :: file:filename().
361363
-type key_pem_password() :: iodata() | fun(() -> iodata()).

lib/ssl/src/ssl_handshake.erl

Lines changed: 10 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2152,13 +2152,15 @@ do_digitally_signed(Version, Msg, HashAlgo, {#'RSAPrivateKey'{} = Key,
21522152
#'RSASSA-PSS-params'{}}, SignAlgo) when ?TLS_GTE(Version, ?TLS_1_2) ->
21532153
Options = signature_options(SignAlgo, HashAlgo),
21542154
public_key:sign(Msg, HashAlgo, Key, Options);
2155-
do_digitally_signed(Version, {digest, Digest}, _HashAlgo, #'RSAPrivateKey'{} = Key, rsa)
2155+
do_digitally_signed(Version, {digest, Digest}, _HashAlgo, #'RSAPrivateKey'{} = Key, rsa)
21562156
when ?TLS_LTE(Version, ?TLS_1_1) ->
21572157
public_key:encrypt_private(Digest, Key,
21582158
[{rsa_pad, rsa_pkcs1_padding}]);
2159-
do_digitally_signed(Version, {digest, Digest}, _HashAlgo, #{algorithm := rsa, encrypt_fun := _} = Key, rsa)
2159+
do_digitally_signed(Version, {digest, Digest}, _HashAlgo, #{algorithm := rsa, encrypt_fun := Fun} = Key0, rsa)
21602160
when ?TLS_LTE(Version, ?TLS_1_1) ->
2161-
public_key:encrypt_private(Digest, Key, [{rsa_pad, rsa_pkcs1_padding}]);
2161+
CustomOpts = maps:get(encrypt_opts, Key0, []),
2162+
Key = #{algorithm => rsa, encrypt_fun => Fun},
2163+
public_key:encrypt_private(Digest, Key, CustomOpts ++ [{rsa_pad, rsa_pkcs1_padding}]);
21622164
do_digitally_signed(Version, {digest, Digest}, _,
21632165
#{algorithm := rsa, engine := _} = Engine, rsa) when ?TLS_LTE(Version, ?TLS_1_1) ->
21642166
crypto:private_encrypt(rsa, Digest, maps:remove(algorithm, Engine),
@@ -2168,6 +2170,11 @@ do_digitally_signed(_, Msg, HashAlgo, #{algorithm := Alg, engine := _} = Engine,
21682170
crypto:sign(Alg, HashAlgo, Msg, maps:remove(algorithm, Engine), Options);
21692171
do_digitally_signed(Version, {digest, _} = Msg , HashAlgo, Key, _) when ?TLS_LTE(Version,?TLS_1_1) ->
21702172
public_key:sign(Msg, HashAlgo, Key);
2173+
do_digitally_signed(_, Msg, HashAlgo, #{algorithm := SignAlgo, sign_fun := Fun} = Key0, SignAlgo) ->
2174+
CustomOpts = maps:get(sign_opts, Key0, []),
2175+
Options = signature_options(SignAlgo, HashAlgo),
2176+
Key = #{algorithm => SignAlgo, sign_fun => Fun},
2177+
public_key:sign(Msg, HashAlgo, Key, CustomOpts ++ Options);
21712178
do_digitally_signed(_, Msg, HashAlgo, Key, SignAlgo) ->
21722179
Options = signature_options(SignAlgo, HashAlgo),
21732180
public_key:sign(Msg, HashAlgo, Key, Options).

0 commit comments

Comments
 (0)