File 4101-ssl-Improve-DTLS-socket-handling.patch of Package erlang
From a305aa52892e79d132332b29b5e1eb6d1c78ce05 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Wed, 11 Sep 2024 14:35:18 +0200
Subject: [PATCH 1/3] ssl: Improve DTLS socket handling
Remove dead code and adhere to call backs
---
lib/ssl/src/dtls_packet_demux.erl | 33 +++++++++++++++++++------------
lib/ssl/src/dtls_socket.erl | 21 +++-----------------
2 files changed, 23 insertions(+), 31 deletions(-)
diff --git a/lib/ssl/src/dtls_packet_demux.erl b/lib/ssl/src/dtls_packet_demux.erl
index 97ba511f4c..573e7e0f1b 100644
--- a/lib/ssl/src/dtls_packet_demux.erl
+++ b/lib/ssl/src/dtls_packet_demux.erl
@@ -173,8 +173,9 @@ handle_call({new_connection, Old, _Pid}, _,
end;
handle_call({get_sock_opts, {SocketOptNames, EmOptNames}}, _, #state{listener = Socket,
+ transport = TransportInfo,
emulated_options = EmOpts} = State) ->
- case get_socket_opts(Socket, SocketOptNames) of
+ case get_socket_opts(Socket, SocketOptNames, element(1, TransportInfo)) of
{ok, Opts} ->
{reply, {ok, emulated_opts_list(EmOpts, EmOptNames, []) ++ Opts}, State};
{error, Reason} ->
@@ -183,15 +184,17 @@ handle_call({get_sock_opts, {SocketOptNames, EmOptNames}}, _, #state{listener =
handle_call(get_all_opts, _, #state{dtls_options = DTLSOptions,
emulated_options = EmOpts} = State) ->
{reply, {ok, EmOpts, DTLSOptions}, State};
-handle_call({set_sock_opts, {SocketOpts, NewEmOpts}}, _, #state{listener = Socket, emulated_options = EmOpts0} = State) ->
- set_socket_opts(Socket, SocketOpts),
+handle_call({set_sock_opts, {SocketOpts, NewEmOpts}}, _, #state{listener = Socket, emulated_options = EmOpts0,
+ transport = TransportInfo} = State) ->
+ set_socket_opts(Socket, SocketOpts, element(1, TransportInfo)),
EmOpts = do_set_emulated_opts(NewEmOpts, EmOpts0),
{reply, ok, State#state{emulated_options = EmOpts}};
-handle_call({set_all_opts, {SocketOpts, NewEmOpts, SslOpts}}, _, #state{listener = Socket} = State) ->
- set_socket_opts(Socket, SocketOpts),
+handle_call({set_all_opts, {SocketOpts, NewEmOpts, SslOpts}}, _, #state{listener = Socket,
+ transport = TransportInfo} = State) ->
+ set_socket_opts(Socket, SocketOpts, element(1, TransportInfo)),
{reply, ok, State#state{emulated_options = NewEmOpts, dtls_options = SslOpts}};
-handle_call({getstat, Options}, _, #state{listener = Socket, transport = {TransportCb, _,_,_,_}} = State) ->
- Stats = dtls_socket:getstat(TransportCb, Socket, Options),
+handle_call({getstat, Options}, _, #state{listener = Socket, transport = TransportInfo} = State) ->
+ Stats = dtls_socket:getstat(element(1, TransportInfo), Socket, Options),
{reply, Stats, State}.
handle_cast({active_once, Client, Pid}, State0) ->
@@ -386,15 +389,19 @@ call(Server, Msg) ->
{error, closed}
end.
-set_socket_opts(_, []) ->
+set_socket_opts(_, [], _) ->
ok;
-set_socket_opts(Socket, SocketOpts) ->
- inet:setopts(Socket, SocketOpts).
+set_socket_opts(Socket, SocketOpts, gen_udp) ->
+ inet:setopts(Socket, SocketOpts);
+set_socket_opts(Socket, SocketOpts, Cb) ->
+ Cb:setopts(Socket, SocketOpts).
-get_socket_opts(_, []) ->
+get_socket_opts(_, [], _) ->
{ok, []};
-get_socket_opts(Socket, SocketOpts) ->
- inet:getopts(Socket, SocketOpts).
+get_socket_opts(Socket, SocketOpts, gen_udp) ->
+ inet:getopts(Socket, SocketOpts);
+get_socket_opts(Socket, SocketOpts, Cb) ->
+ Cb:getopts(Socket, SocketOpts).
do_set_emulated_opts([], Opts) ->
Opts;
diff --git a/lib/ssl/src/dtls_socket.erl b/lib/ssl/src/dtls_socket.erl
index 2f8f7ed5d2..ddf250c6a1 100644
--- a/lib/ssl/src/dtls_socket.erl
+++ b/lib/ssl/src/dtls_socket.erl
@@ -69,9 +69,9 @@ listen(Port, #config{inet_ssl = SockOpts,
Error
end.
-accept(dtls, #config{transport_info = {Transport,_,_,_,_},
- connection_cb = ConnectionCb,
- dtls_handler = {Listener, _}}, _Timeout) ->
+accept({Listener,_}, #config{transport_info = Info,
+ connection_cb = ConnectionCb}, _Timeout) ->
+ Transport = element(1, Info),
case dtls_packet_demux:accept(Listener, self()) of
{ok, Pid, Socket} ->
{ok, socket([Pid], Transport, {Listener, Socket}, ConnectionCb)};
@@ -172,16 +172,6 @@ check_active_n(EmulatedOpts, Socket = #sslsocket{pid = {dtls, #config{dtls_handl
getopts(_, #sslsocket{pid = {dtls, #config{dtls_handler = {ListenPid, _}}}}, Options) ->
SplitOpts = tls_socket:split_options(Options),
dtls_packet_demux:get_sock_opts(ListenPid, SplitOpts);
-getopts(gen_udp, #sslsocket{pid = {Socket, #config{emulated = EmOpts}}}, Options) ->
- {SockOptNames, EmulatedOptNames} = tls_socket:split_options(Options),
- EmulatedOpts = get_emulated_opts(EmOpts, EmulatedOptNames),
- SocketOpts = tls_socket:get_socket_opts(Socket, SockOptNames, inet),
- {ok, EmulatedOpts ++ SocketOpts};
-getopts(_Transport, #sslsocket{pid = {Socket, #config{emulated = EmOpts}}}, Options) ->
- {SockOptNames, EmulatedOptNames} = tls_socket:split_options(Options),
- EmulatedOpts = get_emulated_opts(EmOpts, EmulatedOptNames),
- SocketOpts = tls_socket:get_socket_opts(Socket, SockOptNames, inet),
- {ok, EmulatedOpts ++ SocketOpts};
%%% Following clauses will not be called for emulated options, they are handled in the connection process
getopts(gen_udp, {_,{{_, _},Socket}}, Options) ->
inet:getopts(Socket, Options);
@@ -235,11 +225,6 @@ default_inet_values() ->
default_cb_info() ->
{gen_udp, udp, udp_closed, udp_error, udp_passive}.
-get_emulated_opts(EmOpts, EmOptNames) ->
- lists:map(fun(Name) -> {value, Value} = lists:keysearch(Name, 1, EmOpts),
- Value end,
- EmOptNames).
-
emulated_socket_options(InetValues, #socket_options{
mode = Mode,
packet = Packet,
--
2.43.0