Skip to content

Commit

Permalink
public_key: Adjust certificate key usage compatible check
Browse files Browse the repository at this point in the history
Consider keyCertSign to compatible with extended key usage for TLS client/server auth in CAs
  • Loading branch information
IngelaAndin committed Jan 31, 2025
1 parent ccc44c9 commit a96aa18
Showing 1 changed file with 62 additions and 43 deletions.
105 changes: 62 additions & 43 deletions lib/public_key/src/pubkey_cert.erl
Original file line number Diff line number Diff line change
Expand Up @@ -756,12 +756,12 @@ validate_extensions(Cert, [#'Extension'{extnID = ?'id-ce-basicConstraints',
SelfSigned, UserState, VerifyFun);

validate_extensions(Cert, [#'Extension'{extnID = ?'id-ce-keyUsage',
extnValue = KeyUse
} | Rest],
extnValue = KeyUses
} | Rest],
#path_validation_state{last_cert=Last} = ValidationState,
ExistBasicCon, SelfSigned,
UserState0, VerifyFun) ->
case Last orelse is_valid_key_usage(KeyUse, keyCertSign) of
case Last orelse lists:member(keyCertSign, KeyUses) of
true ->
validate_extensions(Cert, Rest, ValidationState, ExistBasicCon,
SelfSigned, UserState0, VerifyFun);
Expand Down Expand Up @@ -1781,8 +1781,8 @@ is_fixed_dh_cert(PublicKeyInfo, Extensions) ->
case select_extension(?'id-ce-keyUsage', Extensions) of
undefined ->
is_dh(Algorithm);
#'Extension'{extnValue=KeyUse} ->
is_dh(Algorithm) andalso is_valid_key_usage(KeyUse, keyAgreement)
#'Extension'{extnValue = KeyUses} ->
is_dh(Algorithm) andalso lists:member(keyAgreement, KeyUses)
end.

is_dh(?'dhpublicnumber')->
Expand All @@ -1801,50 +1801,72 @@ is_digitally_sign_cert(Cert) ->
lists:member(keyCertSign, KeyUse)
end.

compatible_ext_key_usage(undefined, _, endentity) -> %% keyusage (first arg )is mandantory in CAs
compatible_ext_key_usage(undefined, _, endentity) ->
true;
compatible_ext_key_usage(_, undefined, _) ->
true;
compatible_ext_key_usage(#'Extension'{extnValue = KeyUse}, #'Extension'{extnValue = Purposes}, _) ->
compatible_ext_key_usage(#'Extension'{extnID = ?'id-ce-keyUsage',
extnValue = KeyUses},
#'Extension'{extnID = ?'id-ce-extKeyUsage',
extnValue = Purposes}, Type) ->
case ext_keyusage_includes_any(Purposes) of
true ->
true;
false ->
is_compatible_purposes(KeyUse, Purposes)
is_compatible_purposes(KeyUses, Purposes, Type)
end.

is_compatible_purposes(_, []) ->
is_compatible_purposes(_, [], _) ->
true;
is_compatible_purposes(KeyUse, [?'id-kp-serverAuth'| Rest]) ->
(lists:member(digitalSignature, KeyUse) orelse
lists:member(keyAgreement, KeyUse)) andalso
is_compatible_purposes(KeyUse, Rest);
is_compatible_purposes(KeyUse, [?'id-kp-clientAuth'| Rest]) ->
(lists:member(digitalSignature, KeyUse)
orelse
(lists:member(keyAgreement, KeyUse) orelse lists:member(keyEncipherment, KeyUse)))
andalso is_compatible_purposes(KeyUse, Rest);
is_compatible_purposes(KeyUse, [?'id-kp-codeSigning'| Rest]) ->
lists:member(digitalSignature, KeyUse) andalso
is_compatible_purposes(KeyUse, Rest);
is_compatible_purposes(KeyUse, [?'id-kp-emailProtection'| Rest]) ->
((lists:member(digitalSignature, KeyUse) orelse
lists:member(nonRepudiation, KeyUse))
orelse
(lists:member(keyAgreement, KeyUse) orelse lists:member(keyEncipherment, KeyUse)))
andalso is_compatible_purposes(KeyUse, Rest);
is_compatible_purposes(KeyUse, [Id| Rest]) when Id == ?'id-kp-timeStamping';
Id == ?'id-kp-OCSPSigning'->
(lists:member(digitalSignature, KeyUse) orelse
lists:member(nonRepudiation, KeyUse)) andalso
is_compatible_purposes(KeyUse, Rest);
is_compatible_purposes(KeyUse, [_| Rest]) -> %% Unknown purposes are for user verify_fun to care about
is_compatible_purposes(KeyUse, Rest).

ca_known_extend_key_use(ExtKeyUse) ->
is_compatible_purposes(KeyUses, [?'id-kp-serverAuth'| Rest], ca = Type) ->
%% keyCertSign is already verified for a ca and considered compatible
is_compatible_purposes(KeyUses, Rest, Type);
is_compatible_purposes(KeyUses, [?'id-kp-serverAuth'| Rest], endentity = Type) ->
IsServerAuthComp = case lists:member(digitalSignature, KeyUses) of
true ->
true;
false ->
lists:member(keyAgreement, KeyUses) orelse
lists:member(keyEncipherment, KeyUses)
end,
IsServerAuthComp andalso is_compatible_purposes(KeyUses, Rest, Type);
is_compatible_purposes(KeyUses, [?'id-kp-clientAuth'| Rest], ca = Type) ->
%% keyCertSign is already verified for a ca and considered compatible
is_compatible_purposes(KeyUses, Rest, Type);
is_compatible_purposes(KeyUses, [?'id-kp-clientAuth'| Rest], endentity = Type) ->
IsClientAuthComp = case lists:member(digitalSignature, KeyUses) of
true ->
true;
false ->
lists:member(keyAgreement, KeyUses)
end,
IsClientAuthComp andalso is_compatible_purposes(KeyUses, Rest, Type);
is_compatible_purposes(KeyUses, [?'id-kp-codeSigning'| Rest], Type) ->
lists:member(digitalSignature, KeyUses) andalso
is_compatible_purposes(KeyUses, Rest, Type);
is_compatible_purposes(KeyUses, [?'id-kp-emailProtection'| Rest], Type) ->
IsEmailProtCompatible = case (lists:member(digitalSignature, KeyUses) orelse
lists:member(nonRepudiation, KeyUses)) of
true ->
true;
false ->
lists:member(keyAgreement, KeyUses) orelse
lists:member(keyEncipherment, KeyUses)
end,
IsEmailProtCompatible andalso is_compatible_purposes(KeyUses, Rest, Type);
is_compatible_purposes(KeyUses, [Id| Rest],Type) when Id == ?'id-kp-timeStamping';
Id == ?'id-kp-OCSPSigning'->
(lists:member(digitalSignature, KeyUses) orelse
lists:member(nonRepudiation, KeyUses)) andalso
is_compatible_purposes(KeyUses, Rest, Type);
is_compatible_purposes(KeyUses, [_| Rest], Type) -> %% Unknown purposes are for user verify_fun to care about
is_compatible_purposes(KeyUses, Rest, Type).


ca_known_extend_key_use(ExtKeyUses) ->
CAExtSet = ca_known_ext_key_usage(),
Intersertion = sets:intersection(CAExtSet, sets:from_list(ExtKeyUse)),
not sets:is_empty(Intersertion).
Intersertion = sets:intersection(CAExtSet, sets:from_list(ExtKeyUses)),
not sets:is_empty(Intersection).

ca_known_ext_key_usage() ->
%% Following extended key usages are known
Expand All @@ -1864,9 +1886,6 @@ missing_basic_constraints(OtpCert, SelfSigned, ValidationState, VerifyFun, UserS
UserState}
end.

is_valid_key_usage(KeyUse, Use) ->
lists:member(Use, KeyUse).

%%====================================================================
%% Generate test data
%%====================================================================
Expand Down Expand Up @@ -2164,8 +2183,8 @@ verify_options(
{rsa_pss_saltlen, SaltLen},
{rsa_mgf1_md, HashAlgo}].

ext_keyusage_includes_any(KeyUse) when is_list(KeyUse) ->
lists:member(?anyExtendedKeyUsage, KeyUse);
ext_keyusage_includes_any(KeyUses) when is_list(KeyUses) ->
lists:member(?anyExtendedKeyUsage, KeyUses);
ext_keyusage_includes_any(_) ->
false.

Expand Down

0 comments on commit a96aa18

Please sign in to comment.