File 0982-Use-milliseconds-for-TLS-1.3-session-ticket-age.patch of Package erlang
From 2a98fdce640c0cd063393ba444dff22f2770a71a Mon Sep 17 00:00:00 2001
From: Anders Kiel Hovgaard <anders.hovgaard@motorolasolutions.com>
Date: Tue, 3 May 2022 13:32:29 +0200
Subject: [PATCH 2/3] Use milliseconds for TLS 1.3 session ticket age
TLS 1.3 session tickets contain a random `ticket_age_add` value and a
`ticket_lifetime` (in seconds). The client adds the `ticket_age_add` to
the ticket age (in milliseconds) and sends this value in the
`obfuscated_ticket_age` field in the `pre_shared_key` extension in the
`ClientHello`, when attempting a session resumption. The
`ticket_lifetime` is in seconds while the `obfuscated_ticket_age` is in
milliseconds. For reference, see RFC 8446 Section 4.2.11.1.
The implementation incorrectly used seconds for the ticket age in both
the client and server code. This means that when using a client which
correctly reports the age in milliseconds, the OTP server would reject
the ticket after only `server_session_ticket_lifetime/1000` seconds.
---
lib/ssl/src/tls_client_ticket_store.erl | 12 +-
lib/ssl/src/tls_connection_1_3.erl | 2 +-
lib/ssl/src/tls_handshake_1_3.erl | 2 +-
lib/ssl/src/tls_server_session_ticket.erl | 6 +-
lib/ssl/test/Makefile | 3 +-
.../test/tls_client_ticket_store_SUITE.erl | 108 ++++++++++++++++++
.../test/tls_server_session_ticket_SUITE.erl | 24 ++--
7 files changed, 136 insertions(+), 21 deletions(-)
create mode 100644 lib/ssl/test/tls_client_ticket_store_SUITE.erl
diff --git a/lib/ssl/src/tls_client_ticket_store.erl b/lib/ssl/src/tls_client_ticket_store.erl
index eb10adc9f1..29d4b345a7 100644
--- a/lib/ssl/src/tls_client_ticket_store.erl
+++ b/lib/ssl/src/tls_client_ticket_store.erl
@@ -202,8 +202,8 @@ iterate_tickets(Iter0, Pid, Ciphers, Hash, SNI, Lifetime, EarlyDataSize, Acc) ->
lock = Lock}, Iter} when Lock =:= undefined orelse
Lock =:= Pid ->
MaxEarlyData = tls_handshake_1_3:get_max_early_data(Extensions),
- Age = erlang:system_time(seconds) - Timestamp,
- if Age < Lifetime ->
+ Age = erlang:system_time(millisecond) - Timestamp,
+ if Age < Lifetime * 1000 ->
case verify_ticket_sni(SNI, TicketSNI) of
match ->
case lists:member(Cipher, Ciphers) of
@@ -274,7 +274,7 @@ get_tickets(#state{db = Db} = State, Pid, [Key|T], Acc) ->
ticket = Ticket,
extensions = Extensions
} = NewSessionTicket,
- TicketAge = erlang:system_time(seconds) - Timestamp,
+ TicketAge = erlang:system_time(millisecond) - Timestamp,
ObfuscatedTicketAge = obfuscate_ticket_age(TicketAge, AgeAdd),
Identity = #psk_identity{
identity = Ticket,
@@ -329,8 +329,8 @@ collect_invalid_tickets(Iter0, Lifetime, Acc) ->
case gb_trees:next(Iter0) of
{Key, #data{timestamp = Timestamp,
lock = undefined}, Iter} ->
- Age = erlang:system_time(seconds) - Timestamp,
- if Age < Lifetime ->
+ Age = erlang:system_time(millisecond) - Timestamp,
+ if Age < Lifetime * 1000 ->
collect_invalid_tickets(Iter, Lifetime, Acc);
true ->
collect_invalid_tickets(Iter, Lifetime, [Key|Acc])
@@ -343,7 +343,7 @@ collect_invalid_tickets(Iter0, Lifetime, Acc) ->
store_ticket(#state{db = Db0, max = Max} = State, Ticket, CipherSuite, SNI, PSK) ->
- Timestamp = erlang:system_time(seconds),
+ Timestamp = erlang:system_time(millisecond),
Size = gb_trees:size(Db0),
Db1 = if Size =:= Max ->
delete_oldest(Db0);
diff --git a/lib/ssl/src/tls_connection_1_3.erl b/lib/ssl/src/tls_connection_1_3.erl
index 19c9a05a2f..b4d4fdde81 100644
--- a/lib/ssl/src/tls_connection_1_3.erl
+++ b/lib/ssl/src/tls_connection_1_3.erl
@@ -560,7 +560,7 @@ handle_new_session_ticket(#new_session_ticket{ticket_nonce = Nonce} = NewSession
tls_client_ticket_store:store_ticket(NewSessionTicket, {Cipher, HKDF}, SNI, PSK).
send_ticket_data(User, NewSessionTicket, CipherSuite, SNI, PSK) ->
- Timestamp = erlang:system_time(seconds),
+ Timestamp = erlang:system_time(millisecond),
TicketData = #{cipher_suite => CipherSuite,
sni => SNI,
psk => PSK,
diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl
index 84ee036a46..cfa6a2d6c0 100644
--- a/lib/ssl/src/tls_handshake_1_3.erl
+++ b/lib/ssl/src/tls_handshake_1_3.erl
@@ -2886,7 +2886,7 @@ process_ticket(#{cipher_suite := CipherSuite,
ticket = Ticket,
extensions = Extensions
} = NewSessionTicket,
- TicketAge = erlang:system_time(seconds) - Timestamp,
+ TicketAge = erlang:system_time(millisecond) - Timestamp,
ObfuscatedTicketAge = obfuscate_ticket_age(TicketAge, AgeAdd),
Identity = #psk_identity{
identity = Ticket,
diff --git a/lib/ssl/src/tls_server_session_ticket.erl b/lib/ssl/src/tls_server_session_ticket.erl
index b625cbcd52..f6b91404fb 100644
--- a/lib/ssl/src/tls_server_session_ticket.erl
+++ b/lib/ssl/src/tls_server_session_ticket.erl
@@ -181,7 +181,7 @@ inital_state([stateful, Lifetime, TicketStoreSize, MaxEarlyDataSize|_]) ->
}.
ticket_age_add() ->
- MaxTicketAge = 7 * 24 * 3600,
+ MaxTicketAge = 7 * 24 * 3600 * 1000,
IntMax = round(math:pow(2,32)) - 1,
MaxAgeAdd = IntMax - MaxTicketAge,
<<?UINT32(I)>> = crypto:strong_rand_bytes(4),
@@ -385,10 +385,10 @@ stateless_living_ticket(0, _, _, _, _) ->
stateless_living_ticket(ObfAge, TicketAgeAdd, Lifetime, Timestamp, Window) ->
ReportedAge = ObfAge - TicketAgeAdd,
RealAge = erlang:system_time(second) - Timestamp,
- (ReportedAge =< Lifetime)
+ (ReportedAge =< Lifetime * 1000)
andalso (RealAge =< Lifetime)
andalso (in_window(RealAge, Window)).
-
+
in_window(_, undefined) ->
true;
in_window(Age, Window) when is_integer(Window) ->
diff --git a/lib/ssl/test/Makefile b/lib/ssl/test/Makefile
index 7b7534bce8..90305c7369 100644
--- a/lib/ssl/test/Makefile
+++ b/lib/ssl/test/Makefile
@@ -96,7 +96,8 @@ MODULES = \
x509_test \
inet_crypto_dist \
openssl_ocsp_SUITE \
- tls_server_session_ticket_SUITE
+ tls_server_session_ticket_SUITE \
+ tls_client_ticket_store_SUITE
ERL_FILES = $(MODULES:%=%.erl)
diff --git a/lib/ssl/test/tls_client_ticket_store_SUITE.erl b/lib/ssl/test/tls_client_ticket_store_SUITE.erl
new file mode 100644
index 0000000000..ebc602c4e8
--- /dev/null
+++ b/lib/ssl/test/tls_client_ticket_store_SUITE.erl
@@ -0,0 +1,108 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 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(tls_client_ticket_store_SUITE).
+-behaviour(ct_suite).
+
+-include_lib("common_test/include/ct.hrl").
+-include_lib("ssl/src/ssl_internal.hrl").
+-include_lib("ssl/src/tls_handshake_1_3.hrl").
+
+%% Callback functions
+-export([all/0, init_per_testcase/2, end_per_testcase/2]).
+
+%% Testcases
+-export([ticket_obfuscated_age/0,
+ ticket_obfuscated_age/1,
+ ticket_expired/0,
+ ticket_expired/1]).
+
+-define(TICKET_STORE_SIZE, 2).
+-define(LIFETIME, 2). % tickets expire after 2 second
+
+%%--------------------------------------------------------------------
+%% Common Test interface functions -----------------------------------
+%%--------------------------------------------------------------------
+all() ->
+ [ticket_obfuscated_age, ticket_expired].
+
+init_per_testcase(_TestCase, Config) ->
+ {ok, Pid} = tls_client_ticket_store:start_link(
+ ?TICKET_STORE_SIZE, ?LIFETIME),
+ [{server_pid, Pid} | Config].
+
+end_per_testcase(_TestCase, Config) ->
+ Pid = ?config(server_pid, Config),
+ exit(Pid, normal),
+ Config.
+
+%%--------------------------------------------------------------------
+%% Test Cases --------------------------------------------------------
+%%--------------------------------------------------------------------
+ticket_obfuscated_age() ->
+ [{doc, "Verify the ticket store computes the obfuscated ticket age correctly"}].
+ticket_obfuscated_age(_Config) ->
+ TicketAgeAdd = 2900512354,
+ Ticket =
+ #new_session_ticket{
+ ticket_lifetime = ?LIFETIME,
+ ticket_age_add = TicketAgeAdd,
+ ticket_nonce = <<0,0,0,0,0,0,0,1>>,
+ ticket = <<1, 1, 1, 1, 1, 1, 1, 1>>,
+ extensions = #{early_data => {early_data_indication_nst, 16384}}
+ },
+ CipherSuite = {Cipher, HashAlgo} = {aes_256_gcm, sha384},
+ SNI = "some-test-sni",
+ PSK = <<10, 10, 10, 10>>,
+
+ ok = tls_client_ticket_store:store_ticket(Ticket, CipherSuite, SNI, PSK),
+
+ timer:sleep(100),
+
+ {Key, _} = tls_client_ticket_store:find_ticket(self(), [Cipher], [HashAlgo], SNI, undefined),
+ [#ticket_data{identity = Identity}] = tls_client_ticket_store:get_tickets(self(), [Key]),
+ #psk_identity{obfuscated_ticket_age = ObfAge} = Identity,
+ Age = ObfAge - TicketAgeAdd,
+ ct:log("Ticket age: ~p (obfuscated age: ~p, ticket age add: ~p)~n",
+ [Age, ObfAge, TicketAgeAdd]),
+ true = Age < 1000 andalso Age >= 100.
+
+ticket_expired() ->
+ [{doc, "Verify the ticket store does not return an expired ticket"}].
+ticket_expired(_Config) ->
+ TicketAgeAdd = 1234563451,
+ Ticket =
+ #new_session_ticket{
+ ticket_lifetime = ?LIFETIME,
+ ticket_age_add = TicketAgeAdd,
+ ticket_nonce = <<0,0,0,0,0,0,0,2>>,
+ ticket = <<2, 2, 2, 2, 2, 2, 2, 2>>,
+ extensions = #{early_data => {early_data_indication_nst, 16384}}
+ },
+ CipherSuite = {Cipher, HashAlgo} = {aes_256_gcm, sha384},
+ SNI = "some-test-sni",
+ PSK = <<20, 20, 20, 20>>,
+
+ ok = tls_client_ticket_store:store_ticket(Ticket, CipherSuite, SNI, PSK),
+
+ timer:sleep(?LIFETIME * 1000 + 500),
+
+ {undefined, undefined} = tls_client_ticket_store:find_ticket(
+ self(), [Cipher], [HashAlgo], SNI, undefined).
diff --git a/lib/ssl/test/tls_server_session_ticket_SUITE.erl b/lib/ssl/test/tls_server_session_ticket_SUITE.erl
index 3a3329c096..be7c80f064 100644
--- a/lib/ssl/test/tls_server_session_ticket_SUITE.erl
+++ b/lib/ssl/test/tls_server_session_ticket_SUITE.erl
@@ -97,7 +97,12 @@ main_test(Config) when is_list(Config) ->
% Reach ticket store size limit - force GB tree pruning
SessionTicket = #new_session_ticket{} =
tls_server_session_ticket:new(Pid, ?PRF, ?MASTER_SECRET),
- {HandshakeHist, OferredPsks} = get_handshake_hist(SessionTicket, ?PSK),
+ TicketRecvTime = erlang:system_time(millisecond),
+ %% Sleep more than the ticket lifetime (which is in seconds) in
+ %% milliseconds, to confirm that the client reported age (which is in
+ %% milliseconds) is compared correctly with the lifetime
+ ct:sleep(5 * ?LIFETIME),
+ {HandshakeHist, OferredPsks} = get_handshake_hist(SessionTicket, TicketRecvTime, ?PSK),
AcceptResponse = {ok, {0, ?PSK}},
AcceptResponse = tls_server_session_ticket:use(Pid, OferredPsks, ?PRF,
[iolist_to_binary(HandshakeHist)]),
@@ -135,8 +140,9 @@ expired_ticket_test() ->
expired_ticket_test(Config) when is_list(Config) ->
Pid = ?config(server_pid, Config),
SessionTicket = tls_server_session_ticket:new(Pid, ?PRF, ?MASTER_SECRET),
- {HandshakeHist, OFPSKs} = get_handshake_hist(SessionTicket, ?PSK),
+ TicketRecvTime = erlang:system_time(millisecond),
ct:sleep({seconds, 2 * ?LIFETIME}),
+ {HandshakeHist, OFPSKs} = get_handshake_hist(SessionTicket, TicketRecvTime, ?PSK),
{ok, undefined} = tls_server_session_ticket:use(Pid, OFPSKs, ?PRF,
[iolist_to_binary(HandshakeHist)]),
true = is_process_alive(Pid).
@@ -155,18 +161,18 @@ misc_test(Config) when is_list(Config) ->
%%--------------------------------------------------------------------
%% Helpers -----------------------------------------------------------
%%--------------------------------------------------------------------
-get_handshake_hist(#new_session_ticket{ticket=Ticket} = T, PSK0) ->
- Ids = [#psk_identity{identity = Ticket, obfuscated_ticket_age = 100}],
- SomeBinder = <<159, 187, 86, 6, 55, 20, 149, 208, 3, 221, 78, 126, 254, 101,
- 123, 251, 151, 189, 17, 53>>,
- OfferedPSKs0 = #offered_psks{identities = Ids, binders = [SomeBinder]},
- Hello0 = get_client_hello(OfferedPSKs0),
+get_handshake_hist(#new_session_ticket{} = T, TicketRecvTime, PSK0) ->
M = #{cipher_suite => {nothing, ?PRF},
sni => nothing,
psk => PSK0,
- timestamp => erlang:system_time(seconds),
+ timestamp => TicketRecvTime,
ticket => T},
TicketData = tls_handshake_1_3:get_ticket_data(self(), manual, [M]),
+ [#ticket_data{identity = Identity}] = TicketData,
+ SomeBinder = <<159, 187, 86, 6, 55, 20, 149, 208, 3, 221, 78, 126, 254, 101,
+ 123, 251, 151, 189, 17, 53>>,
+ OfferedPSKs0 = #offered_psks{identities = [Identity], binders = [SomeBinder]},
+ Hello0 = get_client_hello(OfferedPSKs0),
Hello1 = tls_handshake_1_3:maybe_add_binders(Hello0, TicketData, ?VERSION),
PSK1 = maps:get(pre_shared_key, Hello1#client_hello.extensions),
OfferedPSKs1 = PSK1#pre_shared_key_client_hello.offered_psks,
--
2.35.3