File 3121-public_key-date-sliding-window-validation-function.patch of Package erlang
From 2da6b55ae28713c876ca27f7b374d0f921468cb5 Mon Sep 17 00:00:00 2001
From: Kiko Fernandez-Reyes <kiko@erlang.org>
Date: Mon, 19 Dec 2022 10:23:41 +0100
Subject: [PATCH 1/3] public_key: date sliding window validation function
---
lib/public_key/src/pubkey_cert.erl | 79 ++++++++++---
lib/public_key/test/Makefile | 3 +-
lib/public_key/test/pubkey_cert_SUITE.erl | 128 ++++++++++++++++++++++
3 files changed, 193 insertions(+), 17 deletions(-)
create mode 100644 lib/public_key/test/pubkey_cert_SUITE.erl
diff --git a/lib/public_key/src/pubkey_cert.erl b/lib/public_key/src/pubkey_cert.erl
index 7770f02da6..7bfcf1e24d 100644
--- a/lib/public_key/src/pubkey_cert.erl
+++ b/lib/public_key/src/pubkey_cert.erl
@@ -134,7 +134,7 @@ prepare_for_next_cert(OtpCert, ValidationState = #path_validation_state{
}.
%%--------------------------------------------------------------------
--spec validate_time(#'OTPCertificate'{}, term(), fun()) -> term().
+-spec validate_time(#'OTPCertificate'{}, term(), fun()) -> term() | no_return().
%%
%% Description: Check that the certificate validity period includes the
%% current time.
@@ -144,8 +144,8 @@ validate_time(OtpCert, UserState, VerifyFun) ->
{'Validity', NotBeforeStr, NotAfterStr}
= TBSCert#'OTPTBSCertificate'.validity,
Now = calendar:datetime_to_gregorian_seconds(calendar:universal_time()),
- NotBefore = time_str_2_gregorian_sec(NotBeforeStr),
- NotAfter = time_str_2_gregorian_sec(NotAfterStr),
+ NotBefore = time_str_2_gregorian_sec(notBefore, NotBeforeStr),
+ NotAfter = time_str_2_gregorian_sec(notAfter, NotAfterStr),
case ((NotBefore =< Now) and (Now =< NotAfter)) of
true ->
@@ -633,19 +633,44 @@ public_key_info(PublicKeyInfo,
end,
{Algorithm, PublicKey, NewPublicKeyParams}.
-time_str_2_gregorian_sec({utcTime, [Y1,Y2,M1,M2,D1,D2,H1,H2,M3,M4,S1,S2,Z]}) ->
- case list_to_integer([Y1,Y2]) of
- N when N >= 50 ->
- time_str_2_gregorian_sec({generalTime,
- [$1,$9,Y1,Y2,M1,M2,D1,D2,
- H1,H2,M3,M4,S1,S2,Z]});
- _ ->
- time_str_2_gregorian_sec({generalTime,
- [$2,$0,Y1,Y2,M1,M2,D1,D2,
- H1,H2,M3,M4,S1,S2,Z]})
- end;
-
-time_str_2_gregorian_sec({_,[Y1,Y2,Y3,Y4,M1,M2,D1,D2,H1,H2,M3,M4,S1,S2,$Z]}) ->
+%% time_str_2_gregorian_sec/2 is a wrapper (decorator pattern) over
+%% time_str_2_gregorian_sec/1. the decorator deals with notBefore and notAfter
+%% property differently when we pass utcTime because the data format is
+%% ambiguous YYMMDD. on generalTime the year ambiguity cannot happen because
+%% years are expressed in a 4-digit format, i.e., YYYYMMDD.
+-spec time_str_2_gregorian_sec(PeriodOfTime, Time) -> Seconds :: non_neg_integer() when
+ PeriodOfTime :: notBefore | notAfter,
+ Time :: {utcTime | generalTime, [non_neg_integer() | char()]}.
+time_str_2_gregorian_sec(notBefore, {utcTime, [FirstDigitYear | _]=UtcTime}) ->
+ %% To be compliant with PKITS Certification Path Validation,
+ %% we must accept certificates with notBefore = 50, meaning 1950.
+ %% Once the PKITS certification path validation is updated,
+ %% we must update this function body and test case
+ %% {"4.2.3", "Valid pre2000 UTC notBefore Date Test3 EE"}
+ %% in pkits_SUITE.erl
+ Y1 = erlang:list_to_integer([FirstDigitYear]),
+ YearPrefix = case (Y1 > 4 andalso Y1 =< 9) of
+ true -> [$1, $9];
+ false ->
+ {Y, _M, _D} = erlang:date(),
+ integer_to_list(Y div 100)
+ end,
+ time_str_2_gregorian_sec({generalTime, YearPrefix ++ UtcTime});
+
+time_str_2_gregorian_sec(notAfter, {utcTime, UtcTime}) ->
+ SlidingDate = sliding_year_window(UtcTime),
+ time_str_2_gregorian_sec({generalTime, SlidingDate});
+
+time_str_2_gregorian_sec(_, {generalTime, _Time}=GeneralTime) ->
+ time_str_2_gregorian_sec(GeneralTime).
+
+%% converts 'Time' as a string into gregorian time in seconds.
+-spec time_str_2_gregorian_sec(Time) -> Seconds :: non_neg_integer() when
+ Time :: {generalTime | utcTime, string()}.
+time_str_2_gregorian_sec({utcTime, UtcTime}) ->
+ time_str_2_gregorian_sec(notAfter, {utcTime, UtcTime});
+
+time_str_2_gregorian_sec({generalTime,[Y1,Y2,Y3,Y4,M1,M2,D1,D2,H1,H2,M3,M4,S1,S2,$Z]}) ->
Year = list_to_integer([Y1, Y2, Y3, Y4]),
Month = list_to_integer([M1, M2]),
Day = list_to_integer([D1, D2]),
@@ -655,6 +680,28 @@ time_str_2_gregorian_sec({_,[Y1,Y2,Y3,Y4,M1,M2,D1,D2,H1,H2,M3,M4,S1,S2,$Z]}) ->
calendar:datetime_to_gregorian_seconds({{Year, Month, Day},
{Hour, Min, Sec}}).
+%% Sliding window algorithm to calculate the time.
+%% The value is set as taking {Y1, Y2} from the first two digits of
+%% current_date - 50 or current_date - 49.
+sliding_year_window([Y1,Y2,M1,M2,D1,D2,H1,H2,M3,M4,S1,S2,Z]) ->
+ {{CurrentYear,_, _}, _} = calendar:universal_time(),
+ LastTwoDigitYear = CurrentYear rem 100,
+ MinYear = mod(LastTwoDigitYear - 50, 100),
+ YearWindow = case list_to_integer([Y1,Y2]) of
+ N when N < MinYear -> CurrentYear + 50;
+ N when N >= MinYear -> CurrentYear - 49
+ end,
+ [Year1, Year2] = integer_to_list(YearWindow div 100),
+ [Year1,Year2,Y1,Y2,M1,M2,D1,D2,H1,H2,M3,M4,S1,S2,Z].
+
+
+%% Helper function to perform modulo calculation for integer
+-spec mod(A :: integer(), B :: non_neg_integer()) -> non_neg_integer().
+mod(A, B) when A > 0 -> A rem B;
+mod(A, B) when A < 0 -> mod(A+B, B);
+mod(0, _) -> 0.
+
+
is_dir_name([], [], _Exact) -> true;
is_dir_name([H|R1],[H|R2], Exact) -> is_dir_name(R1,R2, Exact);
is_dir_name([[{'AttributeTypeAndValue', Type, What1}]|Rest1],
diff --git a/lib/public_key/test/Makefile b/lib/public_key/test/Makefile
index aa42cf281f..57879c20e6 100644
--- a/lib/public_key/test/Makefile
+++ b/lib/public_key/test/Makefile
@@ -33,6 +33,7 @@ MODULES= \
public_key_SUITE \
pbe_SUITE \
pkits_SUITE \
+ pubkey_cert_SUITE \
pubkey_ssh_SUITE
ERL_FILES= $(MODULES:%=%.erl)
diff --git a/lib/public_key/test/pubkey_cert_SUITE.erl b/lib/public_key/test/pubkey_cert_SUITE.erl
new file mode 100644
index 0000000000..0bf7ffe313
--- /dev/null
+++ b/lib/public_key/test/pubkey_cert_SUITE.erl
@@ -0,0 +1,128 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2011-2022. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(pubkey_cert_SUITE).
+
+-include_lib("common_test/include/ct.hrl").
+%% -include_lib("public_key/include/public_key.hrl").
+
+%% Note: This directive should only be used in test suites.
+-compile(export_all).
+
+%%--------------------------------------------------------------------
+%% Common Test interface functions -----------------------------------
+%%--------------------------------------------------------------------
+
+all() ->
+ [{group, time_str_2_gregorian_sec}].
+
+groups() ->
+ [{time_str_2_gregorian_sec, [], time_str_two_gregorian()}].
+
+time_str_two_gregorian() ->
+ [ time_str_2_gregorian_utc_post2000
+ , time_str_2_gregorian_utc_limit_pre2000
+ , time_str_2_gregorian_utc_limit_post2000
+ , time_str_2_gregorian_generaltime_pre2000
+ , time_str_2_gregorian_generaltime_post2000
+ ].
+
+%%--------------------------------------------------------------------
+%% Test Cases --------------------------------------------------------
+%%--------------------------------------------------------------------
+time_str_2_gregorian_utc_post2000() ->
+ [{doc, "Tests a valid gregorian Utc time"}].
+time_str_2_gregorian_utc_post2000(_) ->
+ YYMMDD = "450101",
+ HHMMSSZ = "000000Z",
+ ExpectedYear = 2045,
+ UtcTime = {utcTime, YYMMDD ++ HHMMSSZ},
+ {ExpectedDate, _} = convert_to_datetime_format(UtcTime, ExpectedYear),
+
+ Result = pubkey_cert:time_str_2_gregorian_sec(UtcTime),
+ {ExpectedDate, _} = calendar:gregorian_seconds_to_datetime(Result).
+
+
+time_str_2_gregorian_utc_limit_pre2000() ->
+ [{doc, "Tests a valid gregorian Utc time"}].
+time_str_2_gregorian_utc_limit_pre2000(_) ->
+ YYMMDD = "720101",
+ HHMMSSZ = "000000Z",
+ ExpectedYear = 1972,
+ UtcTime = {utcTime, YYMMDD ++ HHMMSSZ},
+ {ExpectedDate, _} = convert_to_datetime_format(UtcTime, ExpectedYear),
+
+ Result = pubkey_cert:time_str_2_gregorian_sec(UtcTime),
+ {ExpectedDate, _} = calendar:gregorian_seconds_to_datetime(Result).
+
+
+time_str_2_gregorian_utc_limit_post2000() ->
+ [{doc, "Tests a valid gregorian Utc time"}].
+time_str_2_gregorian_utc_limit_post2000(_) ->
+ YYMMDD = "710101",
+ HHMMSSZ = "000000Z",
+ ExpectedYear = 2071,
+ UtcTime = {utcTime, YYMMDD ++ HHMMSSZ},
+ {ExpectedDate, _} = convert_to_datetime_format(UtcTime, ExpectedYear),
+
+ Result = pubkey_cert:time_str_2_gregorian_sec(UtcTime),
+ {ExpectedDate, _} = calendar:gregorian_seconds_to_datetime(Result).
+
+
+time_str_2_gregorian_generaltime_pre2000() ->
+ [{doc, "Tests a valid gregorian Utc time"}].
+time_str_2_gregorian_generaltime_pre2000(_) ->
+ [Year | _]=YYMMDD = ["1972", "01", "01"],
+ HHMMSSZ = "000000Z",
+ GeneralTime = {generalTime, lists:flatten(YYMMDD) ++ HHMMSSZ},
+ {ExpectedYear, _} = convert_to_datetime_format(GeneralTime
+ , erlang:list_to_integer(Year)),
+
+ Result = pubkey_cert:time_str_2_gregorian_sec(GeneralTime),
+ {ExpectedYear, _} = calendar:gregorian_seconds_to_datetime(Result).
+
+
+time_str_2_gregorian_generaltime_post2000() ->
+ [{doc, "Tests a valid gregorian Utc time"}].
+time_str_2_gregorian_generaltime_post2000(_) ->
+ [Year | _]=YYMMDD = ["2045", "01", "01"],
+ HHMMSSZ = "000000Z",
+ GeneralTime = {generalTime, lists:flatten(YYMMDD) ++ HHMMSSZ},
+ {ExpectedYear, _} = convert_to_datetime_format(GeneralTime
+ , erlang:list_to_integer(Year)),
+
+ Result = pubkey_cert:time_str_2_gregorian_sec(GeneralTime),
+ {ExpectedYear, _} = calendar:gregorian_seconds_to_datetime(Result).
+
+
+convert_to_datetime_format({utcTime, [Y1, Y2, M1, M2, D1, D2 | _]}, ExpectedYear) ->
+ YYMMDD = [[Y1, Y2], [M1, M2], [D1, D2]],
+ [Y, M, D] = lists:map(fun (Str) -> erlang:list_to_integer(Str) end
+ , YYMMDD),
+ case (ExpectedYear rem 100) =:= Y of
+ true -> {{ExpectedYear, M, D}, {0, 0, 0}};
+ false -> error
+ end;
+
+convert_to_datetime_format({generalTime, [Y1, Y2, Y3, Y4, M1, M2, D1, D2 | _]}, ExpectedYear) ->
+ YYMMDD = [[Y1, Y2, Y3, Y4], [M1, M2], [D1, D2]],
+ [ExpectedYear, M, D] = lists:map(fun (Str) -> erlang:list_to_integer(Str) end
+ , YYMMDD),
+ {{ExpectedYear, M, D}, {0, 0, 0}}.
--
2.35.3