Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
0680-ssl-Fix-dtls-replay-window.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 0680-ssl-Fix-dtls-replay-window.patch of Package erlang
From 315e8a28d05eb8711d066be3776075e070c03bd9 Mon Sep 17 00:00:00 2001 From: Dan Gudmundsson <dgud@erlang.org> Date: Fri, 1 Oct 2021 09:17:11 +0200 Subject: [PATCH] ssl: Fix dtls replay window Code was broken and created a larger mask for each invocation. Also set REPLAY_WINDOW_SIZE to 58 avoids using bignum, spec recommends 64 but says it must at least be 32. --- lib/ssl/src/dtls_record.erl | 65 ++++++++++++++++++++------------- lib/ssl/test/dtls_api_SUITE.erl | 52 +++++++++++++++++++++++++- 2 files changed, 90 insertions(+), 27 deletions(-) diff --git a/lib/ssl/src/dtls_record.erl b/lib/ssl/src/dtls_record.erl index dda8055cbf..ef275fad4c 100644 --- a/lib/ssl/src/dtls_record.erl +++ b/lib/ssl/src/dtls_record.erl @@ -48,12 +48,15 @@ is_higher/2, supported_protocol_versions/0, is_acceptable_version/2, hello_version/2]). +%% Debug (whitebox testing) +-export([init_replay_window/0, is_replay/2, update_replay_window/2]). + -export_type([dtls_atom_version/0]). -type dtls_atom_version() :: dtlsv1 | 'dtlsv1.2'. --define(REPLAY_WINDOW_SIZE, 64). +-define(REPLAY_WINDOW_SIZE, 58). %% No bignums -compile(inline). @@ -82,7 +85,7 @@ init_connection_states(Role, BeastMitigation) -> pending_write => Pending}. empty_connection_state(Empty) -> - Empty#{epoch => undefined, replay_window => init_replay_window(?REPLAY_WINDOW_SIZE)}. + Empty#{epoch => undefined, replay_window => init_replay_window()}. %%-------------------------------------------------------------------- -spec save_current_connection_state(ssl_record:connection_states(), read | write) -> @@ -100,12 +103,12 @@ save_current_connection_state(#{current_write := Current} = States, write) -> next_epoch(#{pending_read := Pending, current_read := #{epoch := Epoch}} = States, read) -> States#{pending_read := Pending#{epoch := Epoch + 1, - replay_window := init_replay_window(?REPLAY_WINDOW_SIZE)}}; + replay_window := init_replay_window()}}; next_epoch(#{pending_write := Pending, current_write := #{epoch := Epoch}} = States, write) -> States#{pending_write := Pending#{epoch := Epoch + 1, - replay_window := init_replay_window(?REPLAY_WINDOW_SIZE)}}. + replay_window := init_replay_window()}}. get_connection_state_by_epoch(Epoch, #{current_write := #{epoch := Epoch} = Current}, write) -> @@ -404,7 +407,7 @@ initial_connection_state(ConnectionEnd, BeastMitigation) -> ssl_record:initial_security_params(ConnectionEnd), epoch => undefined, sequence_number => 0, - replay_window => init_replay_window(?REPLAY_WINDOW_SIZE), + replay_window => init_replay_window(), beast_mitigation => BeastMitigation, compression_state => undefined, cipher_state => undefined, @@ -465,39 +468,49 @@ get_dtls_records_aux(_, Data, Acc, _) -> end. %%-------------------------------------------------------------------- +init_replay_window() -> + init_replay_window(?REPLAY_WINDOW_SIZE). + init_replay_window(Size) -> - #{size => Size, - top => Size, + #{top => Size-1, bottom => 0, - mask => 0 bsl 64 + mask => 0 }. replay_detect(#ssl_tls{sequence_number = SequenceNumber}, #{replay_window := Window}) -> is_replay(SequenceNumber, Window). - -is_replay(SequenceNumber, #{bottom := Bottom}) when SequenceNumber < Bottom -> +is_replay(SequenceNumber, #{bottom := Bottom}) + when SequenceNumber < Bottom -> true; -is_replay(SequenceNumber, #{size := Size, - top := Top, - bottom := Bottom, - mask := Mask}) when (SequenceNumber >= Bottom) andalso (SequenceNumber =< Top) -> - Index = (SequenceNumber rem Size), - (Index band Mask) == 1; - +is_replay(SequenceNumber, #{top := Top, bottom := Bottom, mask := Mask}) + when (Bottom =< SequenceNumber) andalso (SequenceNumber =< Top) -> + Index = SequenceNumber - Bottom, + ((Mask bsr Index) band 1) =:= 1; is_replay(_, _) -> false. -update_replay_window(SequenceNumber, #{replay_window := #{size := Size, - top := Top, - bottom := Bottom, - mask := Mask0} = Window0} = ConnectionStates) -> +update_replay_window(SequenceNumber, + #{replay_window := + #{top := Top, + bottom := Bottom, + mask := Mask0} = Window0} + = ConnectionStates) -> NoNewBits = SequenceNumber - Top, - Index = SequenceNumber rem Size, - Mask = (Mask0 bsl NoNewBits) bor Index, - Window = Window0#{top => SequenceNumber, - bottom => Bottom + NoNewBits, - mask => Mask}, + Window = + case NoNewBits > 0 of + true -> + NewBottom = Bottom + NoNewBits, + Index = SequenceNumber - NewBottom, + Mask = (Mask0 bsr NoNewBits) bor (1 bsl Index), + Window0#{top => Top + NoNewBits, + bottom => NewBottom, + mask => Mask}; + false -> + Index = SequenceNumber - Bottom, + Mask = Mask0 bor (1 bsl Index), + Window0#{mask => Mask} + end, ConnectionStates#{replay_window := Window}. %%-------------------------------------------------------------------- diff --git a/lib/ssl/test/dtls_api_SUITE.erl b/lib/ssl/test/dtls_api_SUITE.erl index eb7a16e0f1..572702af02 100644 --- a/lib/ssl/test/dtls_api_SUITE.erl +++ b/lib/ssl/test/dtls_api_SUITE.erl @@ -32,7 +32,9 @@ end_per_testcase/2]). %% Testcases --export([dtls_listen_owner_dies/0, +-export([ + replay_window/0, replay_window/1, + dtls_listen_owner_dies/0, dtls_listen_owner_dies/1, dtls_listen_close/0, dtls_listen_close/1, @@ -57,6 +59,7 @@ %%-------------------------------------------------------------------- all() -> [ + replay_window, {group, 'dtlsv1.2'}, {group, 'dtlsv1'} ]. @@ -297,6 +300,53 @@ dtls_listen_two_sockets_6(_Config) when is_list(_Config) -> ssl:close(S1), ok. + +replay_window() -> + [{doc, "Whitebox test of replay window"}]. +replay_window(_Config) -> + W0 = dtls_record:init_replay_window(), + Size = 58, + true = replay_window(0, 0, Size-1, [], W0), + ok. + +replay_window(N, Top, Sz, Used, W0) when N < 99000 -> + Bottom = max(0, Top - Sz), + Seq = max(0, Bottom + rand:uniform(Top-Bottom+10)-5), + IsReplay = (Seq < Bottom) orelse lists:member(Seq, Used), + case dtls_record:is_replay(Seq,W0) of + true when IsReplay -> + replay_window(N+1, Top, Sz, Used, W0); + false when (not IsReplay) -> + #{replay_window:=W1} = dtls_record:update_replay_window(Seq, #{replay_window=>W0}), + NewTop = if Seq > Top -> Seq; + true -> Top + end, + NewBottom = max(0, (NewTop - Sz)), + NewUsed = lists:dropwhile(fun(S) -> S < NewBottom end, + lists:sort([Seq|Used])), + replay_window(N+1, NewTop, Sz, NewUsed, W1); + Replay -> + io:format("Try: ~p Top: ~w Sz: ~p Used:~p State: ~w~n", [N, Top, Sz, length(Used), W0]), + io:format("Seq: ~w Replay: ~p (~p)~n ~w~n ~w~n", + [Seq, Replay, IsReplay, Used, bits_to_list(W0)]), + {fail, Replay, Seq, W0} + end; +replay_window(N, Top, Sz, Used, W0) -> + io:format("Try: ~p Top: ~w Sz: ~p Used:~p State: ~w~n", [N, Top, Sz, length(Used), W0]), + io:format("Match ~w ~n", [bits_to_list(W0) =:= Used]), + bits_to_list(W0) =:= Used. + +bits_to_list(#{mask := Bits, bottom:= Bottom}) -> + bits_to_list(Bits, Bottom, []). + +bits_to_list(0, _, Is) -> + lists:reverse(Is); +bits_to_list(Bits, I, Acc) -> + case Bits band 1 of + 1 -> bits_to_list(Bits bsr 1, I+1, [I|Acc]); + 0 -> bits_to_list(Bits bsr 1, I+1, Acc) + end. + %%-------------------------------------------------------------------- %% Internal functions ------------------------------------------------ %%-------------------------------------------------------------------- -- 2.31.1
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor