Skip to content

Commit

Permalink
ssl, public_key: Add possiblity to provide customize options to key s…
Browse files Browse the repository at this point in the history
…igning fun
  • Loading branch information
IngelaAndin committed Nov 27, 2023
1 parent 4d8b10e commit c4e2704
Show file tree
Hide file tree
Showing 5 changed files with 25 additions and 7 deletions.
8 changes: 8 additions & 0 deletions lib/public_key/doc/src/public_key.xml
Original file line number Diff line number Diff line change
Expand Up @@ -145,6 +145,14 @@
</desc>
</datatype>

<datatype>
<name name="custom_key_opts"/>
<desc>
<p>Can be provided together with a custom private key, that specifies a key fun,
to provide additional options understood by the fun.</p>
</desc>
</datatype>

<datatype>
<name name="ed_oid_name"/>
<desc>
Expand Down
5 changes: 3 additions & 2 deletions lib/public_key/src/public_key.erl
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,7 @@
ed_private_key() |
#{algorithm := eddsa | rsa_pss_pss | ecdsa | rsa | dsa,
sign_fun => fun()} .
-type custom_key_opts() :: [term()].
-type rsa_public_key() :: #'RSAPublicKey'{}.
-type rsa_private_key() :: #'RSAPrivateKey'{} | #{algorithm := rsa,
encrypt_fun => fun()}.
Expand Down Expand Up @@ -646,7 +647,7 @@ encrypt_private(PlainText, Key) ->
CipherText
when PlainText :: binary(),
Key :: rsa_private_key(),
Options :: crypto:pk_encrypt_decrypt_opts(),
Options :: crypto:pk_encrypt_decrypt_opts() | custom_key_opts(),
CipherText :: binary() .
encrypt_private(PlainText, Key, Options)
when is_binary(PlainText),
Expand Down Expand Up @@ -842,7 +843,7 @@ sign(DigestOrPlainText, DigestType, Key) ->
Signature when Msg :: binary() | {digest,binary()},
DigestType :: digest_type(),
Key :: private_key(),
Options :: crypto:pk_sign_verify_opts(),
Options :: crypto:pk_sign_verify_opts() | custom_key_opts(),
Signature :: binary() .
sign(Digest, none, Key = #'DSAPrivateKey'{}, Options) when is_binary(Digest) ->
%% Backwards compatible
Expand Down
2 changes: 1 addition & 1 deletion lib/ssl/doc/src/ssl.xml
Original file line number Diff line number Diff line change
Expand Up @@ -345,7 +345,7 @@
<desc>

<p>The user's private key. The map formats referring to a
crypto engine/provider (with key reference information) or Erlang fun,
crypto engine/provider (with key reference information) or Erlang fun (with possible custom options),
can both be used for customized signing with
for instance hardware security modules (HSM) or trusted
platform modules (TPM). </p>
Expand Down
4 changes: 3 additions & 1 deletion lib/ssl/src/ssl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -355,7 +355,9 @@
password => crypto:password()} |
#{algorithm := sign_algo(),
sign_fun := fun(),
encrypt_fun => fun() %% Only TLS-1.0, TLS-1.1 and rsa-key
sign_opts => list(),
encrypt_fun => fun(), %% Only TLS-1.0, TLS-1.1 and rsa-key
encrypt_opts => list()
}. % exported
-type key_pem() :: file:filename().
-type key_pem_password() :: iodata() | fun(() -> iodata()).
Expand Down
13 changes: 10 additions & 3 deletions lib/ssl/src/ssl_handshake.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2152,13 +2152,15 @@ 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)
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)
do_digitally_signed(Version, {digest, Digest}, _HashAlgo, #{algorithm := rsa, encrypt_fun := Fun} = Key0, rsa)
when ?TLS_LTE(Version, ?TLS_1_1) ->
public_key:encrypt_private(Digest, Key, [{rsa_pad, rsa_pkcs1_padding}]);
CustomOpts = maps:get(encrypt_opts, Key0, []),
Key = #{algorithm => rsa, encrypt_fun => Fun},
public_key:encrypt_private(Digest, Key, CustomOpts ++ [{rsa_pad, rsa_pkcs1_padding}]);
do_digitally_signed(Version, {digest, Digest}, _,
#{algorithm := rsa, engine := _} = Engine, rsa) when ?TLS_LTE(Version, ?TLS_1_1) ->
crypto:private_encrypt(rsa, Digest, maps:remove(algorithm, Engine),
Expand All @@ -2168,6 +2170,11 @@ do_digitally_signed(_, Msg, HashAlgo, #{algorithm := Alg, engine := _} = Engine,
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) ->
public_key:sign(Msg, HashAlgo, Key);
do_digitally_signed(_, Msg, HashAlgo, #{algorithm := SignAlgo, sign_fun := Fun} = Key0, SignAlgo) ->
CustomOpts = maps:get(sign_opts, Key0, []),
Options = signature_options(SignAlgo, HashAlgo),
Key = #{algorithm => SignAlgo, sign_fun => Fun},
public_key:sign(Msg, HashAlgo, Key, CustomOpts ++ Options);
do_digitally_signed(_, Msg, HashAlgo, Key, SignAlgo) ->
Options = signature_options(SignAlgo, HashAlgo),
public_key:sign(Msg, HashAlgo, Key, Options).
Expand Down

0 comments on commit c4e2704

Please sign in to comment.