File 0474-kernel-test-Add-udp-open-module-test.patch of Package erlang
From fca8ef3ed44d9e6c61c37262350e3aac6b092aaf Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Wed, 2 Jul 2025 10:45:59 +0200
Subject: [PATCH 4/4] [kernel|test] Add (udp) open module test
Add (gen_udp) open test case for module option testing.
OTP-19695
---
lib/kernel/test/Makefile | 2 +
lib/kernel/test/gen_udp_SUITE.erl | 155 ++++++++++++++++++++++++++++-
lib/kernel/test/test_inet6_udp.erl | 90 +++++++++++++++++
lib/kernel/test/test_inet_udp.erl | 90 +++++++++++++++++
4 files changed, 334 insertions(+), 3 deletions(-)
create mode 100644 lib/kernel/test/test_inet6_udp.erl
create mode 100644 lib/kernel/test/test_inet_udp.erl
diff --git a/lib/kernel/test/Makefile b/lib/kernel/test/Makefile
index a7499ad8db..67df3be751 100644
--- a/lib/kernel/test/Makefile
+++ b/lib/kernel/test/Makefile
@@ -92,6 +92,8 @@ MODULES= \
gen_tcp_api_SUITE \
test_inet_tcp \
test_inet6_tcp \
+ test_inet_udp \
+ test_inet6_udp \
gen_tcp_dist \
gen_tcp_echo_SUITE \
gen_tcp_misc_SUITE \
diff --git a/lib/kernel/test/gen_udp_SUITE.erl b/lib/kernel/test/gen_udp_SUITE.erl
index 67573eed8e..206c9d0b56 100644
--- a/lib/kernel/test/gen_udp_SUITE.erl
+++ b/lib/kernel/test/gen_udp_SUITE.erl
@@ -79,6 +79,8 @@
t_simple_local_sockaddr_in6_send_recv/1,
t_simple_link_local_sockaddr_in6_send_recv/1,
+ t_module_open/1,
+
otp_18323_opts_processing/1,
otp_18323_open/1,
otp_19332/1,
@@ -103,11 +104,13 @@ all() ->
[
{group, inet_backend_default},
{group, inet_backend_inet},
- {group, inet_backend_socket}
+ {group, inet_backend_socket},
+ {group, s_misc}
];
_ ->
[
- {group, inet_backend_default}
+ {group, inet_backend_default},
+ {group, s_misc}
]
end.
@@ -125,7 +128,9 @@ groups() ->
{sockaddr, [], sockaddr_cases()},
{tickets, [], tickets_cases()},
{otp18323, [], otp18323_cases()},
- {otp19332, [], otp19332_cases()}
+ {otp19332, [], otp19332_cases()},
+ {s_misc, [], s_misc_cases()},
+ {t_module, [], t_module_cases()}
].
inet_backend_default_cases() ->
@@ -215,6 +220,18 @@ otp19332_cases() ->
otp_19332
].
+s_misc_cases() ->
+ [
+ {group, t_module}
+ ].
+
+t_module_cases() ->
+ [
+ t_module_open
+ ].
+
+
+
init_per_suite(Config0) ->
?P("init_per_suite -> entry with"
@@ -3584,6 +3601,138 @@ do_otp_19357_open_with_ipv6_option(#{local_addr := Addr}) ->
ok.
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+t_module_open(Config) ->
+ Cond = fun() ->
+ ok
+ end,
+ Pre = fun() ->
+ S0 = #{debug => false,
+ config => Config},
+ S1 = case ?WHICH_LOCAL_ADDR(inet) of
+ {ok, Addr4} ->
+ ?P("pre -> found IPv4 local address:"
+ "~n ~p", [Addr4]),
+ S0#{inet => Addr4};
+ {error, _Reason4} ->
+ S0
+ end,
+ S2 = case ?WHICH_LOCAL_ADDR(inet6) of
+ {ok, Addr6} ->
+ ?P("pre -> found IPv6 local address:"
+ "~n ~p", [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_open(State) end,
+ Post = fun(_) -> ok end,
+ ?TC_TRY(?FUNCTION_NAME,
+ Cond, Pre, TC, Post).
+
+do_t_module_open(State) ->
+ do_t_module_open_inet(State),
+ do_t_module_open_inet6(State),
+ ok.
+
+do_t_module_open_inet(#{inet := Addr,
+ debug := Debug,
+ config := _Config} = _State) ->
+ ?P("*** begin IPv4 checks ***"),
+ do_t_module_open(test_inet_udp, inet, Addr, Debug);
+do_t_module_open_inet(_) ->
+ ?P("*** no IPv4 address ***"),
+ ok.
+
+do_t_module_open_inet6(#{inet6 := Addr,
+ debug := Debug,
+ config := _Config} = _State) ->
+ ?P("*** begin IPv6 checks *** "),
+ do_t_module_open(test_inet6_udp, inet6, Addr, Debug);
+do_t_module_open_inet6(_) ->
+ ?P("*** no IPv6 address ***"),
+ ok.
+
+do_t_module_open(Mod, Fam, Addr, Debug) ->
+ ?P("create socket with module (~w)", [Mod]),
+ do_t_module_open2(Mod,
+ [{udp_module, Mod}], Debug, error),
+
+ ?P("create socket with module (~w) and (~w) domain", [Mod, Fam]),
+ do_t_module_open2(Mod,
+ [{udp_module, Mod}, Fam], Debug, error),
+
+ ?P("create socket with (~w) domain and module (~w)", [Fam, Mod]),
+ do_t_module_open2(Mod,
+ [Fam, {udp_module, Mod}], Debug, error),
+
+ ?P("create socket with module (~w) and ip-option", [Mod]),
+ do_t_module_open2(Mod,
+ [{udp_module, Mod}, {ip, Addr}], Debug, error),
+
+ ?P("create socket with ip-option and module (~w)", [Mod]),
+ do_t_module_open2(Mod,
+ [{ip, Addr}, {udp_module, Mod}], Debug, error),
+
+ ?P("create socket with (~w) domain wo module (~w)", [Fam, Mod]),
+ do_t_module_open2(Mod,
+ [Fam], Debug, success),
+
+ ?P("create socket with ip-option wo module (~w)", [Mod]),
+ do_t_module_open2(Mod,
+ [{ip, Addr}], Debug, success),
+
+ ?P("done"),
+ ok.
+
+do_t_module_open2(Module, Opts, Debug, FailureAction) ->
+ case gen_udp:open(0, Opts ++ [{debug, Debug}]) of
+ {ok, Sock} ->
+ ?P("socket created: "
+ "~n ~p"
+ "~n wait for notification", [Sock]),
+ do_t_module_await_notification(Module, open, 2, FailureAction),
+ ?P("close socket"),
+ _ = gen_udp:close(Sock),
+ ok;
+ {error, Reason} ->
+ ?P("failed create 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.
+
+
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
ok({ok,V}) -> V;
diff --git a/lib/kernel/test/test_inet6_udp.erl b/lib/kernel/test/test_inet6_udp.erl
new file mode 100644
index 0000000000..ffe44f979b
--- /dev/null
+++ b/lib/kernel/test/test_inet6_udp.erl
@@ -0,0 +1,90 @@
+%%
+%% %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_udp).
+-moduledoc false.
+
+-export([open/1, open/2, close/1]).
+-export([send/2, send/4, recv/2, recv/3, connect/2, connect/3]).
+-export([controlling_process/2]).
+-export([fdopen/2]).
+
+-export([getserv/1, getaddr/1, getaddr/2, translate_ip/1]).
+
+%% -define(FAMILY, inet6).
+%% -define(PROTO, udp).
+%% -define(TYPE, dgram).
+
+-define(MOD, inet6_udp).
+-define(NOTIFY(), self() ! {?MODULE, ?FUNCTION_NAME, ?FUNCTION_ARITY, ?LINE}).
+
+
+%% inet_udp port lookup
+getserv(Port) when is_integer(Port) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Port);
+getserv(Name) when is_atom(Name) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Name).
+
+%% inet_udp address lookup
+getaddr(Address) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address).
+getaddr(Address, Timer) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address, Timer).
+
+%% inet_udp special this side addresses
+translate_ip(IP) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(IP).
+
+-spec open(_) -> {ok, port()} | {error, atom()}.
+open(Port) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Port).
+
+-spec open(_, _) -> {ok, port()} | {error, atom()}.
+open(Port, Opts) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Port, Opts).
+
+send(S, Arg1, Arg2, Arg3) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Arg1, Arg2, Arg3).
+
+send(S, Data) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Data).
+
+connect(S, SockAddr) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, SockAddr).
+
+connect(S, Addr, Port) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Addr, Port).
+
+recv(S, Len) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Len).
+
+recv(S, Len, Time) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Len, Time).
+
+-spec close(port()) -> ok.
+close(S) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S).
+
+controlling_process(S, NewOwner) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, NewOwner).
+
+%%
+%% 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_udp.erl b/lib/kernel/test/test_inet_udp.erl
new file mode 100644
index 0000000000..7f9c3a9ccb
--- /dev/null
+++ b/lib/kernel/test/test_inet_udp.erl
@@ -0,0 +1,90 @@
+%%
+%% %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_udp).
+-moduledoc false.
+
+-export([open/1, open/2, close/1]).
+-export([send/2, send/4, recv/2, recv/3, connect/2, connect/3]).
+-export([controlling_process/2]).
+-export([fdopen/2]).
+
+-export([getserv/1, getaddr/1, getaddr/2, translate_ip/1]).
+
+%% -define(FAMILY, inet).
+%% -define(PROTO, udp).
+%% -define(TYPE, dgram).
+
+-define(MOD, inet_udp).
+-define(NOTIFY(), self() ! {?MODULE, ?FUNCTION_NAME, ?FUNCTION_ARITY, ?LINE}).
+
+
+%% inet_udp port lookup
+getserv(Port) when is_integer(Port) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Port);
+getserv(Name) when is_atom(Name) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Name).
+
+%% inet_udp address lookup
+getaddr(Address) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address).
+getaddr(Address, Timer) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Address, Timer).
+
+%% inet_udp special this side addresses
+translate_ip(IP) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(IP).
+
+-spec open(_) -> {ok, port()} | {error, atom()}.
+open(Port) -> ?NOTIFY(), ?MOD:?FUNCTION_NAME(Port).
+
+-spec open(_, _) -> {ok, port()} | {error, atom()}.
+open(Port, Opts) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Port, Opts).
+
+send(S, Arg1, Arg2, Arg3) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Arg1, Arg2, Arg3).
+
+send(S, Data) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Data).
+
+connect(S, SockAddr) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, SockAddr).
+
+connect(S, Addr, Port) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Addr, Port).
+
+recv(S, Len) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Len).
+
+recv(S, Len, Time) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, Len, Time).
+
+-spec close(port()) -> ok.
+close(S) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S).
+
+controlling_process(S, NewOwner) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(S, NewOwner).
+
+%%
+%% Create a port/socket from a file descriptor
+%%
+fdopen(Fd, Opts) ->
+ ?NOTIFY(), ?MOD:?FUNCTION_NAME(Fd, Opts).
+
--
2.43.0