File 0472-kernel-test-Add-listen-test-case.patch of Package erlang
From 0685d6f925aa9b4e864c20d70c09e422679853f9 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Thu, 26 Jun 2025 10:32:12 +0200
Subject: [PATCH 2/4] [kernel|test] Add listen test case
Add (gen_tcp) listen test case for module option testing.
OTP-19695
---
lib/kernel/test/Makefile | 2 +
lib/kernel/test/gen_tcp_api_SUITE.erl | 134 +++++++++++++++++++++++++-
lib/kernel/test/kernel_test_lib.erl | 14 ++-
lib/kernel/test/test_inet6_tcp.erl | 131 +++++++++++++++++++++++++
lib/kernel/test/test_inet_tcp.erl | 131 +++++++++++++++++++++++++
5 files changed, 409 insertions(+), 3 deletions(-)
create mode 100644 lib/kernel/test/test_inet6_tcp.erl
create mode 100644 lib/kernel/test/test_inet_tcp.erl
diff --git a/lib/kernel/test/Makefile b/lib/kernel/test/Makefile
index fffec45314..a7499ad8db 100644
--- a/lib/kernel/test/Makefile
+++ b/lib/kernel/test/Makefile
@@ -90,6 +90,8 @@ MODULES= \
prim_file_SUITE \
ram_file_SUITE \
gen_tcp_api_SUITE \
+ test_inet_tcp \
+ test_inet6_tcp \
gen_tcp_dist \
gen_tcp_echo_SUITE \
gen_tcp_misc_SUITE \
diff --git a/lib/kernel/test/gen_tcp_api_SUITE.erl b/lib/kernel/test/gen_tcp_api_SUITE.erl
index 351fcae3c1..d18a04583e 100644
--- a/lib/kernel/test/gen_tcp_api_SUITE.erl
+++ b/lib/kernel/test/gen_tcp_api_SUITE.erl
@@ -50,7 +50,9 @@
t_simple_local_sockaddr_in_send_recv/1,
t_simple_link_local_sockaddr_in_send_recv/1,
t_simple_local_sockaddr_in6_send_recv/1,
- t_simple_link_local_sockaddr_in6_send_recv/1
+ t_simple_link_local_sockaddr_in6_send_recv/1,
+
+ t_module_listen/1
]).
-export([getsockfd/0, closesockfd/1]).
@@ -96,6 +98,7 @@ groups() ->
{t_misc, [], t_misc_cases()},
{sockaddr, [], sockaddr_cases()},
{t_local, [], t_local_cases()},
+ {t_module, [], t_module_cases()},
{s_misc, [], s_misc_cases()}
].
@@ -173,7 +176,13 @@ t_local_cases() ->
s_misc_cases() ->
[
- s_accept_with_explicit_socket_backend
+ s_accept_with_explicit_socket_backend,
+ {group, t_module}
+ ].
+
+t_module_cases() ->
+ [
+ t_module_listen
].
init_per_suite(Config0) ->
@@ -1615,6 +1624,127 @@ do_s_accept_with_explicit_socket_backend(Addr) ->
ok.
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+t_module_listen(Config) ->
+ Cond = fun() ->
+ ok
+ end,
+ Pre = fun() ->
+ S0 = #{debug => false,
+ config => Config},
+ S1 = case ?WHICH_LOCAL_ADDR(inet) of
+ {ok, Addr4} ->
+ S0#{inet => Addr4};
+ {error, _Reason4} ->
+ S0
+ end,
+ S2 = case ?WHICH_LOCAL_ADDR(inet6) of
+ {ok, Addr6} ->
+ S1#{inet6 => Addr6};
+ {error, _Reason6} ->
+ S1
+ end,
+ %% Verify that at least one of the domains
+ %% (inet and inet6) exist.
+ case (maps:get(inet, S2, undefined) =/= undefined) orelse
+ (maps:get(inet6, S2, undefined) =/= undefined) of
+ true ->
+ S2;
+ false ->
+ skip(no_available_domains)
+ end
+ end,
+ TC = fun(State) -> do_t_module_listen(State) end,
+ Post = fun(_) -> ok end,
+ ?TC_TRY(?FUNCTION_NAME,
+ Cond, Pre, TC, Post).
+
+do_t_module_listen(State) ->
+ do_t_module_listen_inet(State),
+ do_t_module_listen_inet6(State),
+ ok.
+
+do_t_module_listen_inet(#{inet := Addr,
+ debug := Debug,
+ config := Config} = _State) ->
+ ?P("*** begin IPv4 checks ***"),
+ do_t_module_listen(test_inet_tcp, inet, Addr, Debug, Config);
+do_t_module_listen_inet(_) ->
+ ?P("*** no IPv4 address ***"),
+ ok.
+
+do_t_module_listen_inet6(#{inet6 := Addr,
+ debug := Debug,
+ config := Config} = _State) ->
+ ?P("*** begin IPv6 checks *** "),
+ do_t_module_listen(test_inet6_tcp, inet6, Addr, Debug, Config);
+do_t_module_listen_inet6(_) ->
+ ?P("*** no IPv6 address ***"),
+ ok.
+
+do_t_module_listen(Mod, Fam, Addr, Debug, Config) ->
+ ?P("create listen socket with module (~w)", [Mod]),
+ do_t_module_listen2(Config, Mod,
+ [{tcp_module, Mod}], Debug, error),
+ ?P("create listen socket with module (~w) and (~w) domain", [Mod, Fam]),
+ do_t_module_listen2(Config, Mod,
+ [{tcp_module, Mod}, Fam], Debug, error),
+ ?P("create listen socket with (~w) domain and module (~w)", [Fam, Mod]),
+ do_t_module_listen2(Config, Mod,
+ [Fam, {tcp_module, Mod}], Debug, error),
+ ?P("create listen socket with module (~w) and ip-option", [Mod]),
+ do_t_module_listen2(Config, Mod,
+ [{tcp_module, Mod}, {ip, Addr}], Debug, error),
+ ?P("create listen socket with ip-option and module (~w)", [Mod]),
+ do_t_module_listen2(Config, Mod,
+ [{ip, Addr}, {tcp_module, Mod}], Debug, error),
+ ?P("create listen socket with (inet) domain wo module (~w)", [Mod]),
+ do_t_module_listen2(Config, Mod,
+ [inet], Debug, success),
+ ?P("create listen socket with ip-option wo module (~w)", [Mod]),
+ do_t_module_listen2(Config, Mod,
+ [{ip, Addr}], Debug, success),
+ ok.
+
+do_t_module_listen2(Config, Module, Opts, Debug, FailureAction) ->
+ case ?LISTEN(Config, 0, Opts ++ [{debug, Debug}]) of
+ {ok, LSock} ->
+ ?P("listen socket created: "
+ "~n ~p"
+ "~n wait for notification", [LSock]),
+ do_t_module_await_notification(Module, listen, 2, FailureAction),
+ ?P("close listen socket"),
+ _ = gen_tcp:close(LSock),
+ ok;
+ {error, Reason} ->
+ ?P("failed create listen socket: "
+ "~n ~p", [Reason]),
+ exit({listen, Reason})
+ end.
+
+do_t_module_await_notification(Module, Func, Arity, FailureAction) ->
+ receive
+ {Module, Func, Arity, _} ->
+ ?P("received expected notification: "
+ "~n ~w:~w/~w", [Module, Func, Arity]),
+ ok;
+ {Module, OtherFunc, OtherArity, _} ->
+ ?P("received unexpected notification: "
+ "~n ~w:~w/~w", [Module, OtherFunc, OtherArity]),
+ do_t_module_await_notification(Module, Func, Arity, FailureAction)
+
+ after 5000 ->
+ case FailureAction of
+ error ->
+ exit({notification_timeout, {Func, Arity}});
+ success ->
+ ok
+ end
+ end.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
%%% Utilities
is_socket_supported() ->
diff --git a/lib/kernel/test/test_inet6_tcp.erl b/lib/kernel/test/test_inet6_tcp.erl
new file mode 100644
index 0000000000..9594c07ab3
--- /dev/null
+++ b/lib/kernel/test/test_inet6_tcp.erl
@@ -0,0 +1,131 @@
+%%
+%% %CopyrightBegin%
+%%
+%% SPDX-License-Identifier: Apache-2.0
+%%
+%% Copyright Ericsson AB 2025-2025. 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
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% 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(test_inet6_tcp).
+-moduledoc false.
+
+%% Socket server for TCP/IP
+
+-export([connect/3, connect/4, listen/2, accept/1, accept/2, close/1]).
+-export([send/2, send/3, recv/2, recv/3, unrecv/2]).
+-export([shutdown/2]).
+-export([controlling_process/2]).
+-export([fdopen/2]).
+
+-export([family/0, mask/2, parse_address/1]). % inet_tcp_dist
+-export([getserv/1, getaddr/1, getaddr/2, getaddrs/1, getaddrs/2]).
+-export([translate_ip/1]).
+
+
+%% -define(FAMILY, inet).
+%% -define(PROTO, tcp).
+%% -define(TYPE, stream).
+
+-define(MOD, inet6_tcp).
+-define(NOTIFY(), self() ! {?MODULE, ?FUNCTION_NAME, ?FUNCTION_ARITY, ?LINE}).
+
+
+%% my address family
+family() -> ?NOTIFY(), ?MOD:?FUNCTION_NAME().
+
+%% Apply netmask on address
+mask(M, IP) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(M, IP).
+
+%% Parse address string
+parse_address(Host) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Host).
+
+%% inet_tcp port lookup
+getserv(Arg) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg).
+
+%% inet_tcp address lookup
+getaddr(Address) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address).
+getaddr(Address, Timer) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address, Timer).
+
+%% inet_tcp address lookup
+getaddrs(Address) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address).
+getaddrs(Address, Timer) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address, Timer).
+
+%% inet_udp special this side addresses
+translate_ip(IP) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(IP).
+
+%%
+%% Send data on a socket
+%%
+send(Socket, Packet, Opts) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Packet, Opts).
+send(Socket, Packet) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Packet).
+
+%%
+%% Receive data from a socket (inactive only)
+%%
+recv(Socket, Length) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Length).
+recv(Socket, Length, Timeout) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Length, Timeout).
+
+unrecv(Socket, Data) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Data).
+
+%%
+%% Shutdown one end of a socket
+%%
+shutdown(Socket, How) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, How).
+
+%%
+%% Close a socket (async)
+%%
+close(Socket) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket).
+
+%%
+%% Set controlling process
+%%
+controlling_process(Socket, NewOwner) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, NewOwner).
+
+%%
+%% Connect
+%%
+connect(Arg1, Arg2, Arg3) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1, Arg2, Arg3).
+
+connect(Arg1, Arg2, Arg3, Arg4) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1, Arg2, Arg3, Arg4).
+
+
+%%
+%% Listen
+%%
+listen(Arg1, Arg2) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1, Arg2).
+
+%%
+%% Accept
+%%
+accept(Arg1) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1).
+
+accept(Arg1, Arg2) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1, Arg2).
+
+
+%%
+%% Create a port/socket from a file descriptor
+%%
+fdopen(Fd, Opts) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Fd, Opts).
diff --git a/lib/kernel/test/test_inet_tcp.erl b/lib/kernel/test/test_inet_tcp.erl
new file mode 100644
index 0000000000..c13b1053cc
--- /dev/null
+++ b/lib/kernel/test/test_inet_tcp.erl
@@ -0,0 +1,131 @@
+%%
+%% %CopyrightBegin%
+%%
+%% SPDX-License-Identifier: Apache-2.0
+%%
+%% Copyright Ericsson AB 2025-2025. 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
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% 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(test_inet_tcp).
+-moduledoc false.
+
+%% Socket server for TCP/IP
+
+-export([connect/3, connect/4, listen/2, accept/1, accept/2, close/1]).
+-export([send/2, send/3, recv/2, recv/3, unrecv/2]).
+-export([shutdown/2]).
+-export([controlling_process/2]).
+-export([fdopen/2]).
+
+-export([family/0, mask/2, parse_address/1]). % inet_tcp_dist
+-export([getserv/1, getaddr/1, getaddr/2, getaddrs/1, getaddrs/2]).
+-export([translate_ip/1]).
+
+
+%% -define(FAMILY, inet).
+%% -define(PROTO, tcp).
+%% -define(TYPE, stream).
+
+-define(MOD, inet_tcp).
+-define(NOTIFY(), self() ! {?MODULE, ?FUNCTION_NAME, ?FUNCTION_ARITY, ?LINE}).
+
+
+%% my address family
+family() -> ?NOTIFY(), ?MOD:?FUNCTION_NAME().
+
+%% Apply netmask on address
+mask(M, IP) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(M, IP).
+
+%% Parse address string
+parse_address(Host) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Host).
+
+%% inet_tcp port lookup
+getserv(Arg) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg).
+
+%% inet_tcp address lookup
+getaddr(Address) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address).
+getaddr(Address, Timer) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address, Timer).
+
+%% inet_tcp address lookup
+getaddrs(Address) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address).
+getaddrs(Address, Timer) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address, Timer).
+
+%% inet_udp special this side addresses
+translate_ip(IP) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(IP).
+
+%%
+%% Send data on a socket
+%%
+send(Socket, Packet, Opts) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Packet, Opts).
+send(Socket, Packet) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Packet).
+
+%%
+%% Receive data from a socket (inactive only)
+%%
+recv(Socket, Length) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Length).
+recv(Socket, Length, Timeout) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Length, Timeout).
+
+unrecv(Socket, Data) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, Data).
+
+%%
+%% Shutdown one end of a socket
+%%
+shutdown(Socket, How) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, How).
+
+%%
+%% Close a socket (async)
+%%
+close(Socket) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket).
+
+%%
+%% Set controlling process
+%%
+controlling_process(Socket, NewOwner) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Socket, NewOwner).
+
+%%
+%% Connect
+%%
+connect(Arg1, Arg2, Arg3) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1, Arg2, Arg3).
+
+connect(Arg1, Arg2, Arg3, Arg4) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1, Arg2, Arg3, Arg4).
+
+
+%%
+%% Listen
+%%
+listen(Arg1, Arg2) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1, Arg2).
+
+%%
+%% Accept
+%%
+accept(Arg1) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1).
+
+accept(Arg1, Arg2) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Arg1, Arg2).
+
+
+%%
+%% Create a port/socket from a file descriptor
+%%
+fdopen(Fd, Opts) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Fd, Opts).
--
2.43.0