Skip to content

Commit

Permalink
public_key: Fix case insensitive match for countryname
Browse files Browse the repository at this point in the history
Modernizes string functions used.

Closes #7546
Closes #6149
  • Loading branch information
IngelaAndin committed Aug 15, 2023
1 parent fe02a02 commit 61f29a0
Show file tree
Hide file tree
Showing 3 changed files with 68 additions and 27 deletions.
69 changes: 44 additions & 25 deletions lib/public_key/src/pubkey_cert.erl
Original file line number Diff line number Diff line change
Expand Up @@ -408,9 +408,8 @@ match_name(emailAddress, Name, [PermittedName | Rest]) ->
match_name(dNSName, Name, [PermittedName | Rest]) ->
Fun = fun(Domain, [$.|Domain]) -> true;
(Name1,Name2) ->
lists:suffix(string:to_lower(Name2),
string:to_lower(Name1))
end,
is_suffix(Name2, Name1)
end,
match_name(Fun, Name, [$.|PermittedName], Rest);

match_name(x400Address, OrAddress, [PermittedAddr | Rest]) ->
Expand Down Expand Up @@ -558,11 +557,11 @@ root_cert(Name, Opts) ->
%%--------------------------------------------------------------------
do_normalize_general_name(Issuer) ->
Normalize = fun([{Description, Type, {printableString, Value}}]) ->
NewValue = string:to_lower(strip_spaces(Value)),
[{Description, Type, {printableString, NewValue}}];
(Atter) ->
Atter
end,
NewValue = string:casefold(strip_spaces(Value, false)),
[{Description, Type, {printableString, NewValue}}];
(Atter) ->
Atter
end,
lists:map(Normalize, Issuer).

%% See rfc3280 4.1.2.6 Subject: regarding emails.
Expand Down Expand Up @@ -668,14 +667,28 @@ is_dir_name(_,[],false) ->
is_dir_name(_,_,_) ->
false.

is_dir_name2(Value, Value) -> true;
is_dir_name2({printableString, Value1}, {printableString, Value2}) ->
string:to_lower(strip_spaces(Value1)) =:=
string:to_lower(strip_spaces(Value2));
is_dir_name2({utf8String, Value1}, String) ->
is_dir_name2({printableString, unicode:characters_to_list(Value1)}, String);
is_dir_name2(String, {utf8String, Value1}) ->
is_dir_name2(String, {printableString, unicode:characters_to_list(Value1)});
%% attribute values in types other than PrintableString are case
%% sensitive (this permits matching of attribute values as binary
%% objects); that is term comparison will compare. Rules origninate
%% from RFC 3280 section 4.1.24. However fallback to case insensite
%% matching also for utf8 strings, as this is done by the
%% pkits_suite interop suite
is_dir_name2(Str, Str) ->
true;
is_dir_name2({T1, Str1}, Str2)
when T1 == printableString; T1 == utf8String ->
is_dir_name2(Str1, Str2);
is_dir_name2(Str1, {T2, Str2})
when T2 == printableString; T2 == utf8String ->
is_dir_name2(Str1, Str2);
is_dir_name2(Str1, Str2)
when (is_list(Str1) orelse is_binary(Str1)) andalso
(is_list(Str2) orelse is_binary(Str2)) ->
%%attribute values in PrintableString are compared after
%%removing leading and trailing white space and converting internal
%%substrings of one or more consecutive white space characters to a
%%single space. They are case insensetive.
string:equal(strip_spaces(Str1, true), strip_spaces(Str2, true), true);
is_dir_name2(_, _) ->
false.

Expand All @@ -693,13 +706,19 @@ decode_general_name([{directoryName, Issuer}]) ->
decode_general_name([{_, Issuer}]) ->
Issuer.

%% Strip all leading and trailing spaces and make
%% sure there is no double spaces in between.
strip_spaces(String) ->
NewString =
lists:foldl(fun(Char, Acc) -> Acc ++ Char ++ " " end, [],
string:tokens(String, " ")),
string:strip(NewString).
strip_spaces(String0, KeepDeep) ->
Trimmed = string:trim(String0),
strip_many_spaces(string:split(Trimmed, " ", all), KeepDeep).

strip_many_spaces([OnlySingleSpace], _) ->
OnlySingleSpace;
strip_many_spaces(Strings, KeepDeep) ->
Split = [string:trim(Str, leading, " ") || Str <- Strings, Str /= []],
DeepList = lists:join(" ", Split),
case KeepDeep of
true -> DeepList;
false -> unicode:characters_to_list(DeepList)
end.

%% No extensions present
validate_extensions(OtpCert, asn1_NOVALUE, ValidationState, ExistBasicCon,
Expand Down Expand Up @@ -1047,9 +1066,9 @@ is_valid_email_address(Canditate, Permitted, [_, _]) ->
case_insensitive_match(Canditate, Permitted).

is_suffix(Suffix, Str) ->
lists:suffix(string:to_lower(Suffix), string:to_lower(Str)).
lists:suffix(string:casefold(Suffix), string:casefold(Str)).
case_insensitive_match(Str1, Str2) ->
string:to_lower(Str1) == string:to_lower(Str2).
string:equal(Str1, Str2, true).

is_or_address(Address, Canditate) ->
%% TODO: Is case_insensitive_match sufficient?
Expand Down
5 changes: 3 additions & 2 deletions lib/public_key/test/pkits_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -379,7 +379,7 @@ string_name_chain() ->
[{doc,"Test name chaining"}].
string_name_chain(Config) when is_list(Config) ->
run([{ "4.3.9", "Valid UTF8String Encoded Names Test9 EE", ok},
%%{ "4.3.10", "Valid Rollover from PrintableString to UTF8String Test10 EE", ok},
%%{ "4.3.10", "Valid Rollover from PrintableString to UTF8String Test10 EE", ok},
{ "4.3.11", "Valid UTF8String Case Insensitive Match Test11 EE", ok}]).

%%----------------------------verifying_paths_with_self_issued_certificates-------------------------------------------------
Expand Down Expand Up @@ -1463,7 +1463,8 @@ intermidiate_cas(Chap) when Chap == "4.5.8" ->


%%%%%%%%%%%%%%% CRL mappings %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%

crl_names("4.3.10") ->
["PrintableString to UTF8String CA CRL"];
crl_names("4.4.1") ->
["Trust Anchor Root CRL"];
crl_names("4.4.2") ->
Expand Down
21 changes: 21 additions & 0 deletions lib/public_key/test/public_key_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -112,6 +112,8 @@
pkix_test_data_all_default/1,
pkix_test_data/0,
pkix_test_data/1,
pkix_is_issuer/0,
pkix_is_issuer/1,
short_cert_issuer_hash/0,
short_cert_issuer_hash/1,
short_crl_issuer_hash/0,
Expand Down Expand Up @@ -156,6 +158,7 @@ all() ->
pkix_verify_hostname_options,
pkix_test_data_all_default,
pkix_test_data,
pkix_is_issuer,
short_cert_issuer_hash,
short_crl_issuer_hash
].
Expand Down Expand Up @@ -1123,6 +1126,7 @@ pkix_test_data_all_default(Config) when is_list(Config) ->
check_conf_member(ServerConf1, [key, cert, cacerts]),
check_conf_member(ClientConf1, [key, cert, cacerts]).

%%--------------------------------------------------------------------

pkix_test_data() ->
[{doc, "Test API function pkix_test_data/1"}].
Expand Down Expand Up @@ -1167,6 +1171,23 @@ check_conf_member(Conf, [Member | Rest]) ->
ct:fail({misssing_conf, Member})
end.

%%--------------------------------------------------------------------
pkix_is_issuer() ->
[{doc, "Test pubkey_cert:pkix_is_issuer with cert that have diffent cases on countryname"}].

pkix_is_issuer(Config) when is_list(Config) ->
Upper = {rdnSequence,
[[{'AttributeTypeAndValue',{2,5,4,6},"GB"}],
[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"MYORG">>}}],
[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"INTERMEDIATE">>}}],
[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"INTERMEDIATE">>}}]]},
Lower = {rdnSequence,
[[{'AttributeTypeAndValue',{2,5,4,6},"gb"}],
[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"MYORG">>}}],
[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"INTERMEDIATE">>}}],
[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"INTERMEDIATE">>}}]]},
true = pubkey_cert:is_issuer(Upper, Lower).

%%--------------------------------------------------------------------
short_cert_issuer_hash() ->
[{doc, "Test OpenSSL-style hash for certificate issuer"}].
Expand Down

0 comments on commit 61f29a0

Please sign in to comment.