File 4881-ssl-Add-missing-DTLS-over-SCTP-adaptions.patch of Package erlang
From 2c057d6b0e2393f0f062495aa68c31cd00eb9042 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Thu, 1 Jun 2023 13:24:59 +0200
Subject: [PATCH 1/3] ssl: Add missing DTLS over SCTP adaptions
---
lib/ssl/src/dtls_gen_connection.erl | 54 ++++++++++++++++++++---------
1 file changed, 37 insertions(+), 17 deletions(-)
diff --git a/lib/ssl/src/dtls_gen_connection.erl b/lib/ssl/src/dtls_gen_connection.erl
index 4964d3d21f..f8d485632c 100644
--- a/lib/ssl/src/dtls_gen_connection.erl
+++ b/lib/ssl/src/dtls_gen_connection.erl
@@ -72,9 +72,8 @@
%% See thread @ http://lists.cluenet.de/pipermail/ipv6-ops/2011-June/005755.html
%% 1280 - headers
--define(PMTUEstimate, 1200).
-
-
+-define(PMTUEstimate_UDP, 1200).
+-define(PMTUEstimate_SCTP, 16384). % 2^14 RFC 6083
%%====================================================================
%% Internal application API
@@ -109,14 +108,20 @@ next_record(#state{handshake_env =
next_record(#state{protocol_buffers =
#protocol_buffers{dtls_cipher_texts = [#ssl_tls{epoch = Epoch} = CT | Rest]}
= Buffers,
- connection_states = #{current_read := #{epoch := Epoch}} = ConnectionStates} = State) ->
+ connection_states = #{current_read := #{epoch := Epoch}} = ConnectionStates,
+ static_env = #static_env{data_tag = DataTag}} = State) ->
CurrentRead = dtls_record:get_connection_state_by_epoch(Epoch, ConnectionStates, read),
- case dtls_record:replay_detect(CT, CurrentRead) of
- false ->
- decode_cipher_text(State) ;
+ case is_reliable(DataTag) of
true ->
- %% Ignore replayed record
- next_record(State#state{protocol_buffers = Buffers#protocol_buffers{dtls_cipher_texts = Rest}})
+ decode_cipher_text(State) ;
+ false ->
+ case dtls_record:replay_detect(CT, CurrentRead) of
+ false ->
+ decode_cipher_text(State);
+ true ->
+ %% Ignore replayed record
+ next_record(State#state{protocol_buffers = Buffers#protocol_buffers{dtls_cipher_texts = Rest}})
+ end
end;
next_record(#state{protocol_buffers =
#protocol_buffers{dtls_cipher_texts = [#ssl_tls{epoch = Epoch} | Rest]}
@@ -157,6 +162,11 @@ next_record(#state{protocol_specific = #{active_n_toggle := true,
next_record(State) ->
{no_record, State}.
+is_reliable(udp) ->
+ false;
+is_reliable(sctp) ->
+ true.
+
next_event(StateName, Record, State) ->
next_event(StateName, Record, State, []).
@@ -245,7 +255,8 @@ new_flight() ->
handshakes_after_change_cipher_spec => []}.
send_handshake_flight(#state{static_env = #static_env{socket = Socket,
- transport_cb = Transport},
+ transport_cb = Transport,
+ data_tag = DataTag},
connection_env = #connection_env{negotiated_version = Version},
flight_buffer = #{handshakes := Flight,
change_cipher_spec := undefined},
@@ -253,7 +264,7 @@ send_handshake_flight(#state{static_env = #static_env{socket = Socket,
ssl_options = #{log_level := LogLevel}} = State0,
Epoch) ->
#{current_write := #{max_fragment_length := MaxFragmentLength}} = ConnectionStates0,
- MaxSize = min(MaxFragmentLength, ?PMTUEstimate),
+ MaxSize = mtu(MaxFragmentLength, DataTag),
{Encoded, ConnectionStates} =
encode_handshake_flight(lists:reverse(Flight), Version, MaxSize, Epoch, ConnectionStates0),
send_packets(Transport, Socket, MaxSize, Encoded),
@@ -261,7 +272,8 @@ send_handshake_flight(#state{static_env = #static_env{socket = Socket,
{State0#state{connection_states = ConnectionStates}, []};
send_handshake_flight(#state{static_env = #static_env{socket = Socket,
- transport_cb = Transport},
+ transport_cb = Transport,
+ data_tag = DataTag},
connection_env = #connection_env{negotiated_version = Version},
flight_buffer = #{handshakes := [_|_] = Flight0,
change_cipher_spec := ChangeCipher,
@@ -270,7 +282,7 @@ send_handshake_flight(#state{static_env = #static_env{socket = Socket,
ssl_options = #{log_level := LogLevel}} = State0,
Epoch) ->
#{current_write := #{max_fragment_length := MaxFragmentLength}} = ConnectionStates0,
- MaxSize = min(MaxFragmentLength, ?PMTUEstimate),
+ MaxSize = mtu(MaxFragmentLength, DataTag),
{HsBefore, ConnectionStates1} =
encode_handshake_flight(lists:reverse(Flight0), Version, MaxSize, Epoch, ConnectionStates0),
{EncChangeCipher, ConnectionStates} = encode_change_cipher(ChangeCipher, Version, Epoch, ConnectionStates1),
@@ -280,7 +292,8 @@ send_handshake_flight(#state{static_env = #static_env{socket = Socket,
{State0#state{connection_states = ConnectionStates}, []};
send_handshake_flight(#state{static_env = #static_env{socket = Socket,
- transport_cb = Transport},
+ transport_cb = Transport,
+ data_tag = DataTag},
connection_env = #connection_env{negotiated_version = Version},
flight_buffer = #{handshakes := [_|_] = Flight0,
change_cipher_spec := ChangeCipher,
@@ -289,7 +302,7 @@ send_handshake_flight(#state{static_env = #static_env{socket = Socket,
ssl_options = #{log_level := LogLevel}} = State0,
Epoch) ->
#{current_write := #{max_fragment_length := MaxFragmentLength}} = ConnectionStates0,
- MaxSize = min(MaxFragmentLength, ?PMTUEstimate),
+ MaxSize = mtu(MaxFragmentLength, DataTag),
{HsBefore, ConnectionStates1} =
encode_handshake_flight(lists:reverse(Flight0), Version, MaxSize, Epoch-1, ConnectionStates0),
{EncChangeCipher, ConnectionStates2} =
@@ -303,7 +316,8 @@ send_handshake_flight(#state{static_env = #static_env{socket = Socket,
{State0#state{connection_states = ConnectionStates}, []};
send_handshake_flight(#state{static_env = #static_env{socket = Socket,
- transport_cb = Transport},
+ transport_cb = Transport,
+ data_tag = DataTag},
connection_env = #connection_env{negotiated_version = Version},
flight_buffer = #{handshakes := [],
change_cipher_spec := ChangeCipher,
@@ -312,7 +326,7 @@ send_handshake_flight(#state{static_env = #static_env{socket = Socket,
ssl_options = #{log_level := LogLevel}} = State0,
Epoch) ->
#{current_write := #{max_fragment_length := MaxFragmentLength}} = ConnectionStates0,
- MaxSize = min(MaxFragmentLength, ?PMTUEstimate),
+ MaxSize = mtu(MaxFragmentLength, DataTag),
{EncChangeCipher, ConnectionStates1} =
encode_change_cipher(ChangeCipher, Version, Epoch-1, ConnectionStates0),
{HsAfter, ConnectionStates} =
@@ -322,6 +336,12 @@ send_handshake_flight(#state{static_env = #static_env{socket = Socket,
ssl_logger:debug(LogLevel, outbound, 'record', [HsAfter]),
{State0#state{connection_states = ConnectionStates}, []}.
+
+mtu(MaxFragmentLength, udp) ->
+ min(MaxFragmentLength, ?PMTUEstimate_UDP);
+mtu(MaxFragmentLength, sctp) ->
+ min(MaxFragmentLength, ?PMTUEstimate_SCTP).
+
%%% DTLS record protocol level application data messages
handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA, fragment = Data}, StateName0, State0) ->
--
2.35.3