File 0302-Test-empty-target-host-name.patch of Package erlang

From a700765980ab776b00f64b57095ac53ac656bb56 Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Wed, 5 Apr 2023 16:13:24 +0200
Subject: [PATCH 3/4] Test empty target host name

---
 lib/kernel/test/gen_sctp_SUITE.erl    | 10 +++++++--
 lib/kernel/test/gen_tcp_api_SUITE.erl | 30 +++++++++++++++------------
 lib/kernel/test/gen_udp_SUITE.erl     | 30 ++++++++++++++++++++++-----
 lib/kernel/test/inet_SUITE.erl        | 15 +++++++++++---
 4 files changed, 62 insertions(+), 23 deletions(-)

diff --git a/lib/kernel/test/gen_sctp_SUITE.erl b/lib/kernel/test/gen_sctp_SUITE.erl
index 297c824965..c1556f69d7 100644
--- a/lib/kernel/test/gen_sctp_SUITE.erl
+++ b/lib/kernel/test/gen_sctp_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2007-2022. All Rights Reserved.
+%% Copyright Ericsson AB 2007-2023. 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.
@@ -16,7 +16,7 @@
 %% limitations under the License.
 %%
 %% %CopyrightEnd%
-%% 
+%%
 -module(gen_sctp_SUITE).
 
 -include_lib("common_test/include/ct.hrl").
@@ -770,6 +770,12 @@ api_listen(Config) when is_list(Config) ->
 
     {ok,Sb} = gen_sctp:open(Pb),
     {ok,Sa} = gen_sctp:open(),
+
+    {error, nxdomain} = gen_sctp:connect(Sa, "", 65535, []),
+    {error, nxdomain} = gen_sctp:connect(Sa, '', 65535, []),
+    {error, nxdomain} = gen_sctp:connect(Sa, ".", 65535, []),
+    {error, nxdomain} = gen_sctp:connect(Sa, '.', 65535, []),
+
     case gen_sctp:connect(Sa, localhost, Pb, []) of
 	{error,econnrefused} ->
 	    {ok,{Localhost,
diff --git a/lib/kernel/test/gen_tcp_api_SUITE.erl b/lib/kernel/test/gen_tcp_api_SUITE.erl
index 593a784bcc..41dd745250 100644
--- a/lib/kernel/test/gen_tcp_api_SUITE.erl
+++ b/lib/kernel/test/gen_tcp_api_SUITE.erl
@@ -1,8 +1,8 @@
 %%
 %% %CopyrightBegin%
-%% 
-%% Copyright Ericsson AB 1998-2022. All Rights Reserved.
-%% 
+%%
+%% Copyright Ericsson AB 1998-2023. 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
@@ -14,7 +14,7 @@
 %% 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(gen_tcp_api_SUITE).
@@ -353,15 +353,19 @@ t_connect_src_port(Config) when is_list(Config) ->
 %% invalid things.
 t_connect_bad(Config) when is_list(Config) ->
     NonExistingPort = 45638,		% Not in use, I hope.
-    {error, Reason1} = gen_tcp:connect(localhost, NonExistingPort, 
-                                       ?INET_BACKEND_OPTS(Config)),
-    io:format("Error for connection attempt to port not in use: ~p",
-	      [Reason1]),
-
-    {error, Reason2} = gen_tcp:connect("non-existing-host-xxx", 7,
-                                       ?INET_BACKEND_OPTS(Config)),
-    io:format("Error for connection attempt to non-existing host: ~p",
-	      [Reason2]),
+    t_connect_bad(Config, localhost, NonExistingPort, "port not in use"),
+    t_connect_bad(Config, "non-existing-host-xxx", 7, "non-existing host"),
+    t_connect_bad(Config, "",                      7, "empty host string"),
+    t_connect_bad(Config, '',                      7, "empty host atom"),
+    t_connect_bad(Config, ".",                     7, "root domain string"),
+    t_connect_bad(Config, '.',                     7, "root domain atom").
+
+t_connect_bad(Config, Host, Port, Descr) ->
+    {error, Reason} =
+        gen_tcp:connect(Host, Port,?INET_BACKEND_OPTS(Config)),
+    io:format(
+      "Error for connection attempt to " ++ Descr ++ ": ~p~n",
+      [Reason]),
     ok.
 
 
diff --git a/lib/kernel/test/gen_udp_SUITE.erl b/lib/kernel/test/gen_udp_SUITE.erl
index 4419999036..44c3c7708b 100644
--- a/lib/kernel/test/gen_udp_SUITE.erl
+++ b/lib/kernel/test/gen_udp_SUITE.erl
@@ -1,8 +1,8 @@
 %%
 %% %CopyrightBegin%
-%% 
-%% Copyright Ericsson AB 1998-2022. All Rights Reserved.
-%% 
+%%
+%% Copyright Ericsson AB 1998-2023. 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
@@ -14,7 +14,7 @@
 %% 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%
 %%
 
@@ -37,7 +37,7 @@
          init_per_testcase/2, end_per_testcase/2]).
 
 -export([
-	 send_to_closed/1, active_n/1,
+	 send_to_closed/1, send_to_empty/1, active_n/1,
 	 buffer_size/1, binary_passive_recv/1, max_buffer_size/1, bad_address/1,
 	 read_packets/1, recv_poll_after_active_once/1,
          open_fd/1, connect/1, reconnect/1, implicit_inet6/1,
@@ -118,6 +118,7 @@ inet_backend_socket_cases() ->
 all_cases() ->
     [
      send_to_closed,
+     send_to_empty,
      buffer_size,
      binary_passive_recv,
      max_buffer_size,
@@ -339,6 +340,20 @@ do_send_to_closed(Config) ->
 
 
 
+%%-------------------------------------------------------------
+%% Send to the empty host name
+
+send_to_empty(Config) when is_list(Config) ->
+    ?TC_TRY(?FUNCTION_NAME, fun() -> do_send_to_empty(Config) end).
+
+do_send_to_empty(Config) ->
+    {ok, Sock} = ?OPEN(Config, 0),
+    {error, nxdomain} = gen_udp:send(Sock, "", ?CLOSED_PORT, "xXx"),
+    {error, nxdomain} = gen_udp:send(Sock, '', ?CLOSED_PORT, "xXx"),
+    {error, nxdomain} = gen_udp:send(Sock, ".", ?CLOSED_PORT, "xXx"),
+    {error, nxdomain} = gen_udp:send(Sock, '.', ?CLOSED_PORT, "xXx"),
+    ok.
+
 %%-------------------------------------------------------------
 %% Test that the UDP socket buffer sizes are settable
 
@@ -1744,6 +1759,11 @@ do_connect(Config) when is_list(Config) ->
     ?P("sleep some"),
     ct:sleep({seconds, 5}),
 
+    ?P("try some doomed connect targets: ~p", [P1]),
+    {error, nxdomain} = gen_udp:connect(S2, "", ?CLOSED_PORT),
+    {error, nxdomain} = gen_udp:connect(S2, '', ?CLOSED_PORT),
+    {error, nxdomain} = gen_udp:connect(S2, ".", ?CLOSED_PORT),
+    {error, nxdomain} = gen_udp:connect(S2, '.', ?CLOSED_PORT),
     ?P("try connect second socket to: ~p, ~p", [Addr, P1]),
     ok = gen_udp:connect(S2, Addr, P1),
     ?P("try send on second socket"),
diff --git a/lib/kernel/test/inet_SUITE.erl b/lib/kernel/test/inet_SUITE.erl
index 6298130a09..2a59edaaf2 100644
--- a/lib/kernel/test/inet_SUITE.erl
+++ b/lib/kernel/test/inet_SUITE.erl
@@ -33,7 +33,7 @@
 
 	 t_gethostbyaddr/0, t_gethostbyaddr/1,
 	 t_getaddr/0, t_getaddr/1,
-	 t_gethostbyname/0, t_gethostbyname/1,
+	 t_gethostbyname/0, t_gethostbyname/1, t_gethostbyname_empty/1,
 	 t_gethostbyaddr_v6/0, t_gethostbyaddr_v6/1,
 	 t_getaddr_v6/0, t_getaddr_v6/1,
 	 t_gethostbyname_v6/0, t_gethostbyname_v6/1,
@@ -70,7 +70,7 @@ suite() ->
 
 all() -> 
     [
-     t_gethostbyaddr, t_gethostbyname, t_getaddr,
+     t_gethostbyaddr, t_gethostbyname, t_gethostbyname_empty, t_getaddr,
      t_gethostbyaddr_v6, t_gethostbyname_v6, t_getaddr_v6,
      ipv4_to_ipv6, host_and_addr, is_ip_address, {group, parse},
      t_gethostnative, gethostnative_parallell, cname_loop,
@@ -367,6 +367,15 @@ do_gethostbyname(Config) when is_list(Config) ->
     {error,nxdomain} = inet:gethostbyname(IP_46_Str),
     ok.
 
+
+t_gethostbyname_empty(Config) when is_list(Config) ->
+    {error,nxdomain} = inet:gethostbyname(""),
+    {error,nxdomain} = inet:gethostbyname(''),
+    {error,nxdomain} = inet:gethostbyname("."),
+    {error,nxdomain} = inet:gethostbyname('.'),
+    ok.
+
+
 t_gethostbyname_v6() -> required(v6).
 %% Test the inet:gethostbyname/1 inet6 function.
 t_gethostbyname_v6(Config) when is_list(Config) ->
-- 
2.35.3

openSUSE Build Service is sponsored by