File 3961-ssl-Add-more-guards-to-api-functions.patch of Package erlang
From 278a98fca2aa15de82dedf7c7cd989befb4e335e Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Mon, 19 Feb 2024 17:14:20 +0100
Subject: [PATCH] ssl: Add more guards to api functions
Gives function_clause earlier instead of strange crashes/error messages later.
---
lib/ssl/src/ssl.erl | 87 ++++++++++++++++++++--------------
lib/ssl/src/ssl_gen_statem.erl | 4 +-
lib/ssl/test/ssl_api_SUITE.erl | 21 +++++++-
3 files changed, 73 insertions(+), 39 deletions(-)
diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl
index 4c6204a486..3583029b51 100644
--- a/lib/ssl/src/ssl.erl
+++ b/lib/ssl/src/ssl.erl
@@ -1769,6 +1769,9 @@ can verify.
-type tls_options_name() :: atom().
%% -------------------------------------------------------------------------------------------------------
+-define(IS_TIMEOUT(Timeout),
+ ((is_integer(Timeout) andalso Timeout >= 0) orelse (Timeout == infinity))).
+
%%%--------------------------------------------------------------------
%%% API
%%%--------------------------------------------------------------------
@@ -1818,7 +1821,8 @@ stop() ->
TCPSocket :: socket(),
TLSOptions :: [tls_client_option()].
-connect(Socket, SslOptions) ->
+connect(Socket, SslOptions)
+ when is_list(SslOptions) ->
connect(Socket, SslOptions, infinity).
-spec connect(TCPSocket, TLSOptions, Timeout) ->
@@ -1857,9 +1861,9 @@ owning the sslsocket will receive messages of type `t:active_msgs/0`
Port :: inet:port_number(),
TLSOptions :: [tls_client_option()].
-connect(Socket, SslOptions0, Timeout) when is_list(SslOptions0) andalso
- (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) ->
-
+connect(Socket, SslOptions0, Timeout)
+ when is_list(SslOptions0), ?IS_TIMEOUT(Timeout) ->
+
CbInfo = handle_option_cb_info(SslOptions0, tls),
Transport = element(1, CbInfo),
try handle_options(Transport, Socket, SslOptions0, client, undefined) of
@@ -1868,8 +1872,9 @@ connect(Socket, SslOptions0, Timeout) when is_list(SslOptions0) andalso
catch
_:{error, Reason} ->
{error, Reason}
- end;
-connect(Host, Port, Options) ->
+ end;
+connect(Host, Port, Options)
+ when is_integer(Port), is_list(Options) ->
connect(Host, Port, Options, infinity).
-spec connect(Host, Port, TLSOptions, Timeout) ->
@@ -1914,7 +1919,8 @@ owning the sslsocket will receive messages of type `t:active_msgs/0`
TLSOptions :: [tls_client_option()],
Timeout :: timeout().
-connect(Host, Port, Options, Timeout) when (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) ->
+connect(Host, Port, Options, Timeout)
+ when is_integer(Port), is_list(Options), ?IS_TIMEOUT(Timeout) ->
try
{ok, Config} = handle_options(Options, client, Host),
case Config#config.connection_cb of
@@ -1940,7 +1946,8 @@ connect(Host, Port, Options, Timeout) when (is_integer(Timeout) andalso Timeout
%%--------------------------------------------------------------------
listen(_Port, []) ->
{error, nooptions};
-listen(Port, Options0) ->
+listen(Port, Options0)
+ when is_integer(Port), is_list(Options0) ->
try
{ok, Config} = handle_options(Options0, server),
do_listen(Port, Config, Config#config.connection_cb)
@@ -1984,8 +1991,8 @@ connection is accepted within the given time, `{error, timeout}` is returned.
SslSocket :: sslsocket().
transport_accept(#sslsocket{pid = {ListenSocket,
- #config{connection_cb = ConnectionCb} = Config}}, Timeout)
- when (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) ->
+ #config{connection_cb = ConnectionCb} = Config}}, Timeout)
+ when ?IS_TIMEOUT(Timeout) ->
case ConnectionCb of
tls_gen_connection ->
tls_socket:accept(ListenSocket, Config, Timeout);
@@ -2039,8 +2046,8 @@ owning the sslsocket will receive messages of type `t:active_msgs/0`
Ext :: protocol_extensions(),
Reason :: closed | timeout | error_alert().
-handshake(#sslsocket{} = Socket, Timeout) when (is_integer(Timeout) andalso Timeout >= 0) or
- (Timeout == infinity) ->
+handshake(#sslsocket{} = Socket, Timeout)
+ when ?IS_TIMEOUT(Timeout) ->
ssl_gen_statem:handshake(Socket, Timeout);
%% If Socket is a ordinary socket(): upgrades a gen_tcp, or equivalent, socket to
@@ -2091,11 +2098,11 @@ owning the sslsocket will receive messages of type `t:active_msgs/0`
Ext :: protocol_extensions(),
Reason :: closed | timeout | {options, any()} | error_alert().
-handshake(#sslsocket{} = Socket, [], Timeout) when (is_integer(Timeout) andalso Timeout >= 0) or
- (Timeout == infinity)->
+handshake(#sslsocket{} = Socket, [], Timeout)
+ when ?IS_TIMEOUT(Timeout) ->
handshake(Socket, Timeout);
-handshake(#sslsocket{fd = {_, _, _, Trackers}} = Socket, SslOpts, Timeout) when
- (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity)->
+handshake(#sslsocket{fd = {_, _, _, Trackers}} = Socket, SslOpts, Timeout)
+ when is_list(SslOpts), ?IS_TIMEOUT(Timeout) ->
try
Tracker = proplists:get_value(option_tracker, Trackers),
{ok, EmOpts, _} = tls_socket:get_all_opts(Tracker),
@@ -2104,8 +2111,8 @@ handshake(#sslsocket{fd = {_, _, _, Trackers}} = Socket, SslOpts, Timeout) when
catch
Error = {error, _Reason} -> Error
end;
-handshake(#sslsocket{pid = [Pid|_], fd = {_, _, _}} = Socket, SslOpts, Timeout) when
- (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity)->
+handshake(#sslsocket{pid = [Pid|_], fd = {_, _, _}} = Socket, SslOpts, Timeout)
+ when is_list(SslOpts), ?IS_TIMEOUT(Timeout) ->
try
{ok, EmOpts, _} = dtls_packet_demux:get_all_opts(Pid),
ssl_gen_statem:handshake(Socket, {SslOpts,
@@ -2113,7 +2120,8 @@ handshake(#sslsocket{pid = [Pid|_], fd = {_, _, _}} = Socket, SslOpts, Timeout)
catch
Error = {error, _Reason} -> Error
end;
-handshake(Socket, SslOptions, Timeout) when (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) ->
+handshake(Socket, SslOptions, Timeout)
+ when is_list(SslOptions), ?IS_TIMEOUT(Timeout) ->
CbInfo = handle_option_cb_info(SslOptions, tls),
Transport = element(1, CbInfo),
ConnetionCb = connection_cb(SslOptions),
@@ -2147,6 +2155,7 @@ handshake(Socket, SslOptions, Timeout) when (is_integer(Timeout) andalso Timeout
%%--------------------------------------------------------------------
handshake_continue(Socket, SSLOptions) ->
handshake_continue(Socket, SSLOptions, infinity).
+
%%--------------------------------------------------------------------
-spec handshake_continue(HsSocket, Options, Timeout) ->
{ok, SslSocket} | {error, Reason} when
@@ -2161,8 +2170,10 @@ handshake_continue(Socket, SSLOptions) ->
%%
%% Description: Continues the handshake possible with newly supplied options.
%%--------------------------------------------------------------------
-handshake_continue(Socket, SSLOptions, Timeout) ->
+handshake_continue(Socket, SSLOptions, Timeout)
+ when is_list(SSLOptions), ?IS_TIMEOUT(Timeout) ->
ssl_gen_statem:handshake_continue(Socket, SSLOptions, Timeout).
+
%%--------------------------------------------------------------------
-spec handshake_cancel(#sslsocket{}) -> any().
%%
@@ -2208,10 +2219,8 @@ connection.
%%
%% Description: Close an ssl connection
%%--------------------------------------------------------------------
-close(#sslsocket{pid = [TLSPid|_]},
- {Pid, Timeout} = DownGrade) when is_pid(TLSPid),
- is_pid(Pid),
- (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) ->
+close(#sslsocket{pid = [TLSPid|_]}, {Pid, Timeout} = DownGrade)
+ when is_pid(TLSPid), is_pid(Pid), ?IS_TIMEOUT(Timeout) ->
case ssl_gen_statem:close(TLSPid, {close, DownGrade}) of
ok -> %% In normal close {error, closed} is regarded as ok, as it is not interesting which side
%% that got to do the actual close. But in the downgrade case only {ok, Port} is a success.
@@ -2219,8 +2228,8 @@ close(#sslsocket{pid = [TLSPid|_]},
Other ->
Other
end;
-close(#sslsocket{pid = [TLSPid|_]}, Timeout) when is_pid(TLSPid),
- (is_integer(Timeout) andalso Timeout >= 0) or (Timeout == infinity) ->
+close(#sslsocket{pid = [TLSPid|_]}, Timeout)
+ when is_pid(TLSPid), ?IS_TIMEOUT(Timeout) ->
ssl_gen_statem:close(TLSPid, {close, Timeout});
close(#sslsocket{pid = {dtls, #config{dtls_handler = {_, _}}}} = DTLSListen, _) ->
dtls_socket:close(DTLSListen);
@@ -2287,9 +2296,7 @@ value is `infinity`.
HttpPacket :: any().
recv(#sslsocket{pid = [Pid|_]}, Length, Timeout)
- when is_pid(Pid) andalso
- (is_integer(Length) andalso Length >= 0) andalso
- ((is_integer(Timeout) andalso Timeout >= 0) orelse Timeout == infinity) ->
+ when is_pid(Pid), (is_integer(Length) andalso Length >= 0), ?IS_TIMEOUT(Timeout) ->
ssl_gen_statem:recv(Pid, Length, Timeout);
recv(#sslsocket{pid = {dtls,_}}, _, _) ->
{error,enotconn};
@@ -2311,14 +2318,16 @@ the owner of an SSL socket, and receives all messages from the socket.
%% Description: Changes process that receives the messages when active = true
%% or once.
%%--------------------------------------------------------------------
-controlling_process(#sslsocket{pid = [Pid|_]}, NewOwner) when is_pid(Pid), is_pid(NewOwner) ->
+controlling_process(#sslsocket{pid = [Pid|_]}, NewOwner)
+ when is_pid(Pid), is_pid(NewOwner) ->
ssl_gen_statem:new_user(Pid, NewOwner);
-controlling_process(#sslsocket{pid = {dtls, _}},
- NewOwner) when is_pid(NewOwner) ->
+controlling_process(#sslsocket{pid = {dtls, _}}, NewOwner)
+ when is_pid(NewOwner) ->
ok; %% Meaningless but let it be allowed to conform with TLS
controlling_process(#sslsocket{pid = {Listen,
#config{transport_info = {Transport,_,_,_,_}}}},
- NewOwner) when is_pid(NewOwner) ->
+ NewOwner)
+ when is_pid(NewOwner) ->
%% Meaningless but let it be allowed to conform with normal sockets
Transport:controlling_process(Listen, NewOwner).
@@ -2376,7 +2385,8 @@ set to `true`.
%%
%% Description: Return SSL information for the connection
%%--------------------------------------------------------------------
-connection_information(#sslsocket{pid = [Pid|_]}, Items) when is_pid(Pid) ->
+connection_information(#sslsocket{pid = [Pid|_]}, Items)
+ when is_pid(Pid), is_list(Items) ->
case ssl_gen_statem:connection_information(Pid, include_security_info(Items)) of
{ok, Info} ->
{ok, [Item || Item = {Key, Value} <- Info, lists:member(Key, Items),
@@ -2751,7 +2761,9 @@ groups(default) ->
%%--------------------------------------------------------------------
getopts(#sslsocket{pid = [Pid|_]}, OptionTags) when is_pid(Pid), is_list(OptionTags) ->
ssl_gen_statem:get_opts(Pid, OptionTags);
-getopts(#sslsocket{pid = {dtls, #config{transport_info = {Transport,_,_,_,_}}}} = ListenSocket, OptionTags) when is_list(OptionTags) ->
+getopts(#sslsocket{pid = {dtls, #config{transport_info = {Transport,_,_,_,_}}}} = ListenSocket,
+ OptionTags)
+ when is_list(OptionTags) ->
try dtls_socket:getopts(Transport, ListenSocket, OptionTags) of
{ok, _} = Result ->
Result;
@@ -2813,7 +2825,9 @@ setopts(#sslsocket{pid = [Pid|_]}, Options0) when is_pid(Pid), is_list(Options0)
_:_ ->
{error, {options, {not_a_proplist, Options0}}}
end;
-setopts(#sslsocket{pid = {dtls, #config{transport_info = {Transport,_,_,_,_}}}} = ListenSocket, Options) when is_list(Options) ->
+setopts(#sslsocket{pid = {dtls, #config{transport_info = {Transport,_,_,_,_}}}} = ListenSocket,
+ Options)
+ when is_list(Options) ->
try dtls_socket:setopts(Transport, ListenSocket, Options) of
ok ->
ok;
@@ -2823,7 +2837,8 @@ setopts(#sslsocket{pid = {dtls, #config{transport_info = {Transport,_,_,_,_}}}}
_:Error ->
{error, {options, {socket_options, Options, Error}}}
end;
-setopts(#sslsocket{pid = {_, #config{transport_info = {Transport,_,_,_,_}}}} = ListenSocket, Options) when is_list(Options) ->
+setopts(#sslsocket{pid = {_, #config{transport_info = {Transport,_,_,_,_}}}} = ListenSocket, Options)
+ when is_list(Options) ->
try tls_socket:setopts(Transport, ListenSocket, Options) of
ok ->
ok;
diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl
index 9c157d6bc7..a79d0a3084 100644
--- a/lib/ssl/src/ssl_gen_statem.erl
+++ b/lib/ssl/src/ssl_gen_statem.erl
@@ -313,8 +313,8 @@ handshake(#sslsocket{pid = [Pid|_]} = Socket, Timeout) ->
end.
%%--------------------------------------------------------------------
--spec handshake(#sslsocket{}, {ssl_options(),#socket_options{}}, timeout()) ->
- {ok, #sslsocket{}} | {ok, #sslsocket{}, map()} | {error, reason()}.
+-spec handshake(#sslsocket{}, {SSLOpts::list(), #socket_options{}}, timeout()) ->
+ {ok, #sslsocket{}} | {ok, #sslsocket{}, map()} | {error, reason()}.
%%
%% Description: Starts ssl handshake with some new options
%%--------------------------------------------------------------------
diff --git a/lib/ssl/test/ssl_api_SUITE.erl b/lib/ssl/test/ssl_api_SUITE.erl
index 7f68815ac5..fa960cdfa6 100644
--- a/lib/ssl/test/ssl_api_SUITE.erl
+++ b/lib/ssl/test/ssl_api_SUITE.erl
@@ -2130,6 +2130,9 @@ max_handshake_size(Config) when is_list(Config) ->
%%-------------------------------------------------------------------
+
+-define(FUNC_CLAUSE(EXPR), try EXPR, error(should_fail) catch _:function_clause -> ok end).
+
options_not_proplist() ->
[{doc,"Test what happens if an option is not a key value tuple"}].
@@ -2138,7 +2141,23 @@ options_not_proplist(Config) when is_list(Config) ->
client, [<<"spdy/3">>,<<"http/1.1">>], <<"http/1.1">>},
{option_not_a_key_value_tuple, BadOption} =
ssl:connect("twitter.com", 443, [binary, {active, false},
- BadOption]).
+ BadOption]),
+ ?FUNC_CLAUSE(ssl:connect("twitter.com", 443)),
+ ?FUNC_CLAUSE(ssl:connect("twitter.com", 443, infinity)),
+ ?FUNC_CLAUSE(ssl:connect("twitter.com", [], infinity_misspelled)),
+ ?FUNC_CLAUSE(ssl:connect("twitter.com", foo, [], infinity)),
+ %% While at it test some other functions as well for regression testing
+ ?FUNC_CLAUSE(ssl:listen([], 443)),
+ ?FUNC_CLAUSE(ssl:transport_accept(#sslsocket{}, [])),
+ ?FUNC_CLAUSE(ssl:handshake(#sslsocket{}, [])),
+ ?FUNC_CLAUSE(ssl:handshake(foo, #sslsocket{})),
+ ?FUNC_CLAUSE(ssl:handshake(foo, #sslsocket{}, 1000)),
+ ?FUNC_CLAUSE(ssl:handshake(#sslsocket{}, 1000, 1000)),
+ ?FUNC_CLAUSE(ssl:handshake(#sslsocket{}, [opt_list], [])),
+ ?FUNC_CLAUSE(ssl:handshake_continue(socket, [opt_list], [])),
+ ?FUNC_CLAUSE(ssl:handshake_continue(socket, 1000, 1000)),
+
+ ok.
%%-------------------------------------------------------------------
invalid_options() ->
--
2.35.3