Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
IngelaAndin committed Dec 5, 2024
2 parents e33f66e + 35cc603 commit 7a1fa06
Show file tree
Hide file tree
Showing 9 changed files with 361 additions and 112 deletions.
48 changes: 27 additions & 21 deletions lib/public_key/src/pubkey_cert.erl
Original file line number Diff line number Diff line change
Expand Up @@ -700,21 +700,10 @@ validate_extensions(Cert, asn1_NOVALUE, ValidationState, ExistBasicCon,
SelfSigned, UserState, VerifyFun) ->
validate_extensions(Cert, [], ValidationState, ExistBasicCon,
SelfSigned, UserState, VerifyFun);

validate_extensions(#cert{otp = OtpCert} = Cert,[], ValidationState, basic_constraint, _SelfSigned,
validate_extensions(Cert, [], ValidationState, basic_constraint, _SelfSigned,
UserState0, VerifyFun) ->
TBSCert = OtpCert#'OTPCertificate'.tbsCertificate,
Extensions = extensions_list(TBSCert#'OTPTBSCertificate'.extensions),
KeyUseExt = pubkey_cert:select_extension(?'id-ce-keyUsage', Extensions),
ExtKeyUseExt = pubkey_cert:select_extension(?'id-ce-extKeyUsage', Extensions),
case compatible_ext_key_usage(KeyUseExt, ExtKeyUseExt) of
true ->
{ValidationState, UserState0};
false ->
UserState = verify_fun(Cert, {bad_cert, {key_usage_mismatch, {KeyUseExt, ExtKeyUseExt}}},
UserState0, VerifyFun),
{ValidationState, UserState}
end;
UserState = validate_ext_key_usage(Cert, UserState0, VerifyFun, ca),
{ValidationState, UserState};
validate_extensions(Cert, [], ValidationState =
#path_validation_state{max_path_length = Len,
last_cert = Last},
Expand All @@ -723,8 +712,9 @@ validate_extensions(Cert, [], ValidationState =
true when SelfSigned ->
{ValidationState, UserState0};
true ->
UserState = validate_ext_key_usage(Cert, UserState0, VerifyFun, endentity),
{ValidationState#path_validation_state{max_path_length = Len - 1},
UserState0};
UserState};
false ->
%% basic_constraint must appear in certs used for digital sign
%% see 4.2.1.10 in rfc 3280
Expand All @@ -737,7 +727,6 @@ validate_extensions(Cert, [], ValidationState =
{ValidationState, UserState0}
end
end;

validate_extensions(Cert,
[#'Extension'{extnID = ?'id-ce-basicConstraints',
extnValue =
Expand Down Expand Up @@ -890,6 +879,18 @@ handle_last_cert(Cert, #path_validation_state{last_cert = true,
handle_last_cert(_, ValidationState) ->
ValidationState.

validate_ext_key_usage(#cert{otp = OtpCert} = Cert, UserState, VerifyFun, Type) ->
TBSCert = OtpCert#'OTPCertificate'.tbsCertificate,
Extensions = extensions_list(TBSCert#'OTPTBSCertificate'.extensions),
KeyUseExt = pubkey_cert:select_extension(?'id-ce-keyUsage', Extensions),
ExtKeyUseExt = pubkey_cert:select_extension(?'id-ce-extKeyUsage', Extensions),
case compatible_ext_key_usage(KeyUseExt, ExtKeyUseExt, Type) of
true ->
UserState;
false ->
verify_fun(Cert, {bad_cert, {key_usage_mismatch, {KeyUseExt, ExtKeyUseExt}}},
UserState, VerifyFun)
end.

%%====================================================================
%% Policy handling
Expand Down Expand Up @@ -1799,9 +1800,11 @@ is_digitally_sign_cert(Cert) ->
lists:member(keyCertSign, KeyUse)
end.

compatible_ext_key_usage(_, undefined) ->
compatible_ext_key_usage(undefined, _, endentity) -> %% keyusage (first arg )is mandantory in CAs
true;
compatible_ext_key_usage(#'Extension'{extnValue = KeyUse}, #'Extension'{extnValue = Purposes}) ->
compatible_ext_key_usage(_, undefined, _) ->
true;
compatible_ext_key_usage(#'Extension'{extnValue = KeyUse}, #'Extension'{extnValue = Purposes}, _) ->
case ext_keyusage_includes_any(Purposes) of
true ->
true;
Expand Down Expand Up @@ -2104,7 +2107,7 @@ extensions(Role, Type, Opts) ->

add_default_extensions(_, ca, Exts) ->
Default = [#'Extension'{extnID = ?'id-ce-keyUsage',
extnValue = [keyCertSign, cRLSign],
extnValue = [keyCertSign, digitalSignature, cRLSign],
critical = false},
#'Extension'{extnID = ?'id-ce-basicConstraints',
extnValue = #'BasicConstraints'{cA = true},
Expand All @@ -2121,9 +2124,12 @@ add_default_extensions(server, peer, Exts) ->
critical = false}
],
add_default_extensions(Default, Exts);

add_default_extensions(client, peer, Exts) ->
Exts.
Default = [#'Extension'{extnID = ?'id-ce-keyUsage',
extnValue = [digitalSignature],
critical = false}
],
add_default_extensions(Default, Exts).

add_default_extensions(Defaults0, Exts) ->
Defaults = lists:filtermap(fun(#'Extension'{extnID = ID} = Ext) ->
Expand Down
4 changes: 2 additions & 2 deletions lib/public_key/src/public_key.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1567,7 +1567,7 @@ Available options:
```erlang
fun(OtpCert :: #'OTPCertificate'{},
Event :: {bad_cert, Reason :: atom() | {revoked, atom()}} |
Event :: {bad_cert, Reason :: bad_cert_reason() | {revoked, atom()}} |
{extension, #'Extension'{}},
UserState :: term()) ->
{valid, UserState :: term()} |
Expand All @@ -1581,7 +1581,7 @@ Available options:
```erlang
fun(OtpCert :: #'OTPCertificate'{},
DerCert :: der_encoded(),
Event :: {bad_cert, Reason :: atom() | {revoked, atom()}} |
Event :: {bad_cert, Reason :: bad_cert_reason() | {revoked, atom()}} |
{extension, #'Extension'{}},
UserState :: term()) ->
{valid, UserState :: term()} |
Expand Down
2 changes: 1 addition & 1 deletion lib/ssl/src/ssl.app.src
Original file line number Diff line number Diff line change
Expand Up @@ -92,6 +92,6 @@
{applications, [crypto, public_key, kernel, stdlib]},
{env, []},
{mod, {ssl_app, []}},
{runtime_dependencies, ["stdlib-6.0","public_key-1.16.2","kernel-9.0",
{runtime_dependencies, ["stdlib-6.0","public_key-1.16.4","kernel-9.0",
"erts-15.0","crypto-5.0", "inets-5.10.7",
"runtime_tools-1.15.1"]}]}.
38 changes: 36 additions & 2 deletions lib/ssl/src/ssl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -846,6 +846,20 @@ Common certificate related options to both client and server.
The chain consisted only of one self-signed certificate.
- **{invalid_ext_keyusage, [public_key:oid()]} **
If the peer certificate specifies the extended keyusage extension and does
not include the purpose for either being a TLS server (id-kp-ServerAuth) or
TLS client (id-kp-ClientAuth) depending on the peers role.
- **{ca_invalid_ext_keyusage, [public_key:oid()]} **
If a CA certificate specifies the extended keyusage extension and does
not include the purpose for either being a TLS server
(id-kp-ServerAuth) or TLS client (id-kp-ClientAuth) depending
on the role of the peer chained with this CA, or the option allow_any_ca_purpose is set to `true`
but the special any-value (anyExtendedKeyUsage) is not included in the CA cert purposes.
- **`PKIX X-509-path validation error`**
For possible reasons, see `public_key:pkix_path_validation/3`.
Expand All @@ -856,6 +870,13 @@ Common certificate related options to both client and server.
see [public_key:pkix_path_validation/3](`public_key:pkix_path_validation/3`) for
more details.
- **`{allow_any_ca_purpose, boolean()}`** - Handle certificate extended key usages extension
If a CA certificate has an extended key usage extension but it does not want to
restrict the usages of the key it can include a special `anyExtendedKeyUsage` purpose.
If this is option is set to `true` all key usage purposes is automatically
accepted for a CA that include that purpose, the options default to false.
- **`{cerl_check, Check}`** - Handle certificate revocation lists.
Perform CRL (Certificate Revocation List) verification
Expand Down Expand Up @@ -891,6 +912,7 @@ Common certificate related options to both client and server.
{explicit_policy, boolean()} |
{inhibit_policy_mapping, boolean()} |
{inhibit_any_policy, boolean()}]} |
{allow_any_ca_purpose, Allow::boolean()} |
{crl_check, Check::boolean() | peer | best_effort} |
{crl_cache, crl_cache_opts()} |
{partial_chain, anchor_fun()}.
Expand Down Expand Up @@ -3760,6 +3782,7 @@ ssl_options() ->
use_srtp,
user_lookup_fun,
verify, verify_fun, cert_policy_opts,
allow_any_ca_purpose,
versions
].

Expand Down Expand Up @@ -3928,7 +3951,7 @@ opt_verification(UserOpts, Opts0, #{role := Role} = Env) ->

Opts3 = set_opt_int(depth, 0, 255, ?DEFAULT_DEPTH, UserOpts, Opts2),

Opts = case Role of
Opts4 = case Role of
client ->
opt_verify_fun(UserOpts, Opts3#{partial_chain => PartialChain},
Env);
Expand All @@ -3937,7 +3960,8 @@ opt_verification(UserOpts, Opts0, #{role := Role} = Env) ->
fail_if_no_peer_cert => FailNoPeerCert},
Env)
end,
opt_policies(UserOpts, Opts).
Opts = opt_policies(UserOpts, Opts4),
opt_extend_keyusage(UserOpts, Opts).

default_verify(client) ->
%% Server authenication is by default requiered
Expand Down Expand Up @@ -4002,6 +4026,16 @@ opt_policies(UserOpts, Opts) ->
Opts#{cert_policy_opts => POpts}
end.

opt_extend_keyusage(UserOpts, Opts) ->
case get_opt_bool(allow_any_ca_purpose, false, UserOpts, Opts) of
{default, Value} ->
Opts#{allow_any_ca_purpose => Value};
{old, _OldValue} ->
Opts;
{new, NewValue} ->
Opts#{allow_any_ca_purpose => NewValue}
end.

validate_policy_opts([]) ->
true;
validate_policy_opts([{policy_set, OidList} | Rest]) when is_list(OidList) ->
Expand Down
92 changes: 56 additions & 36 deletions lib/ssl/src/ssl_certificate.erl
Original file line number Diff line number Diff line change
Expand Up @@ -202,25 +202,42 @@ file_to_crls(File, DbHandle) ->
%%
%% Description: Validates ssl/tls specific extensions
%%--------------------------------------------------------------------
validate(_,{extension, #'Extension'{extnID = ?'id-ce-extKeyUsage',
critical = Critical,
extnValue = KeyUse}}, #{path_len := 1} = UserState,
_LogLevel) ->
%% If extension in peer, check for TLS server/client usage
case is_valid_extkey_usage(KeyUse, Critical, UserState) of
true ->
{valid, UserState};
false ->
{unknown, UserState}
validate(_, {extension, #'Extension'{extnID = ?'id-ce-extKeyUsage'} = Ext}, #{path_len := 1} = UserState, _) ->
case verify_extkeyusage(Ext, UserState) of
valid ->
{valid, UserState};
KeyUses ->
{fail, {bad_cert, {invalid_ext_keyusage, KeyUses}}}
end;
validate(_, {extension, _}, UserState, _LogLevel) ->
validate(_, {extension, #'Extension'{extnID = ?'id-ce-extKeyUsage'} = Ext}, UserState, _) ->
case verify_extkeyusage(Ext, UserState) of
valid ->
{valid, UserState};
KeyUses ->
{fail, {bad_cert, {ca_invalid_ext_keyusage, KeyUses}}}
end;
validate(_, {extension, _}, UserState, _) ->
{unknown, UserState};
validate(Issuer, {bad_cert, cert_expired}, #{issuer := Issuer}, _LogLevel) ->
validate(Issuer, {bad_cert, cert_expired}, #{issuer := Issuer}, _) ->
{fail, {bad_cert, root_cert_expired}};
validate(_, {bad_cert, _} = Reason, _, _LogLevel) ->
validate(_, {bad_cert, _} = Reason, _, _) ->
{fail, Reason};
validate(Cert, valid, #{path_len := N} = UserState, LogLevel) ->
case verify_sign_support(Cert, UserState) of
validate(Cert, valid, UserState, LogLevel) ->
common_cert_validation(Cert, UserState, LogLevel);
validate(Cert, valid_peer, UserState0 = #{role := client, server_name := Hostname,
customize_hostname_check := Customize},
LogLevel) when Hostname =/= disable ->
case verify_hostname(Hostname, Customize, Cert, UserState0) of
{valid, UserState} ->
common_cert_validation(Cert, UserState, LogLevel);
Error ->
Error
end;
validate(Cert, valid_peer, UserState, LogLevel) ->
common_cert_validation(Cert, UserState, LogLevel).

common_cert_validation(Cert, #{path_len := N} = UserState, LogLevel) ->
case verify_sign_support(Cert, UserState) of
true ->
case maps:get(cert_ext, UserState, undefined) of
undefined ->
Expand All @@ -231,19 +248,7 @@ validate(Cert, valid, #{path_len := N} = UserState, LogLevel) ->
end;
false ->
{fail, {bad_cert, unsupported_signature}}
end;
validate(Cert, valid_peer, UserState = #{role := client, server_name := Hostname,
customize_hostname_check := Customize},
LogLevel) when Hostname =/= disable ->
case verify_hostname(Hostname, Customize, Cert, UserState) of
{valid, UserState} ->
validate(Cert, valid, UserState, LogLevel);
Error ->
Error
end;
validate(Cert, valid_peer, UserState, LogLevel) ->
validate(Cert, valid, UserState, LogLevel).

end.
%%--------------------------------------------------------------------
-spec is_valid_key_usage(list(), term()) -> boolean().
%%
Expand Down Expand Up @@ -500,20 +505,35 @@ do_find_issuer(IssuerFun, CertDbHandle, CertDb) ->
Return
end.

is_valid_extkey_usage(KeyUse, true, #{role := Role}) when is_list(KeyUse) ->
is_valid_key_usage(KeyUse, ext_keysage(Role));
is_valid_extkey_usage(KeyUse, true, #{role := Role}) ->
is_valid_key_usage([KeyUse], ext_keysage(Role));
is_valid_extkey_usage(_, false, _) ->
false.
verify_extkeyusage( #'Extension'{extnValue = KeyUses}, UserState)->
case is_valid_extkey_usage(KeyUses, UserState) of
true ->
valid;
false ->
KeyUses
end.

is_valid_extkey_usage(KeyUses, #{path_len := PathNum,
role := Role,
allow_any_ca_purpose := Allow}) ->
case PathNum of
1 -> %% Peer Cert
is_valid_key_usage(KeyUses, ext_keyusage(Role));
_ -> %% CA cert
is_valid_key_usage(KeyUses, ext_keyusage(Role))
orelse (Allow andalso ext_keyusage_includes_any(KeyUses))
end.

ext_keysage(client) ->
ext_keyusage(client) ->
%% Client wants to verify server
?'id-kp-serverAuth';
ext_keysage(server) ->
ext_keyusage(server) ->
%% Server wants to verify client
?'id-kp-clientAuth'.

ext_keyusage_includes_any(KeyUse) ->
lists:member(?anyExtendedKeyUsage, KeyUse).

verify_cert_signer(BinCert, SignerTBSCert) ->
PublicKey = public_key(SignerTBSCert#'OTPTBSCertificate'.subjectPublicKeyInfo),
public_key:pkix_verify(BinCert, PublicKey).
Expand Down
Loading

0 comments on commit 7a1fa06

Please sign in to comment.