File 2043-kernel-test-Add-test-cases-for-UDP-and-TCP-for-the-o.patch of Package erlang

From 1ffb62318b5660ae6f449aa9bb771d4f12f3997a Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Fri, 4 Apr 2025 19:24:52 +0200
Subject: [PATCH 3/3] [kernel|test] Add test cases for UDP and TCP for the
 option params

Add test cases for the kernel parameters;
   * TCP: inet_default_listen_options and inet_default_connect_options
   * UDP: inet_default_udp_options

These makes it possible to set "default" values options used when
creating (TCP and UDP) sockets.

OTP-19576
---
 lib/kernel/test/gen_tcp_misc_SUITE.erl | 111 ++++++++++++++++++++++++-
 lib/kernel/test/gen_udp_SUITE.erl      |  64 +++++++++++++-
 2 files changed, 172 insertions(+), 3 deletions(-)

diff --git a/lib/kernel/test/gen_tcp_misc_SUITE.erl b/lib/kernel/test/gen_tcp_misc_SUITE.erl
index 288e9cb5bb..6821cc8e6c 100644
--- a/lib/kernel/test/gen_tcp_misc_SUITE.erl
+++ b/lib/kernel/test/gen_tcp_misc_SUITE.erl
@@ -104,6 +104,7 @@
 	 socket_monitor2/1,
 	 socket_monitor2_manys/1,
 	 socket_monitor2_manyc/1,
+         t_kernel_options/1, do_kernel_options_remote/2,
 	 otp_17492/1,
 	 otp_18357/1,
          otp_18883/1,
@@ -238,7 +239,8 @@ all_std_cases() ->
      {group, socket_monitor},
      otp_17492,
      otp_18707,
-     send_block_unblock
+     send_block_unblock,
+     t_kernel_options
     ].
 
 ticket_cases() ->
@@ -9760,6 +9762,113 @@ payload(N, Bin) ->
     C = rand:uniform($z - $0 + 1) + $0,
     payload(N - 1, <<Bin/binary, C>>).
 
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+%% This is the most basic of tests.
+
+%% Create a new node with kernel option(s) 'inet_default_listen_options'
+%% and 'inet_default_connect_options' set then rpc call a function which
+%% creates socket(s) and reads back their values of that socket (buffer
+%% and recbuf).
+%%
+t_kernel_options(Config) when is_list(Config) ->
+    ?TC_TRY(?FUNCTION_NAME,
+            fun() -> ok end,
+            fun() -> case ?WHICH_LOCAL_ADDR(inet) of
+                         {ok, Addr} ->
+                             Addr;
+                         {error, Reason} ->
+                             throw({skip, Reason})
+                     end
+            end,
+            fun(Addr) ->
+                    do_kernel_options(Config, Addr)
+            end,
+            fun(_) ->
+                    ok
+            end).
+
+do_kernel_options(Config, Addr) ->
+    LBSz   = 12345,
+    LRBSz  = 54321,
+    CBSz   = 23456,
+    CRBSz  = 65432,
+    KOpts = ?F("-kernel inet_default_listen_options "
+               "\"[{buffer,~w},{recbuf,~w}]\" "
+               "-kernel inet_default_connect_options "
+               "\"[{buffer,~w},{recbuf,~w}]\"",
+               [LBSz, LRBSz, CBSz, CRBSz]),
+    ?P("try start node"),
+    case ?START_NODE(?UNIQ_NODE_NAME, KOpts) of
+        {ok, Node} ->
+            LExpected = [{buffer, LBSz}, {recbuf, LRBSz}],
+            CExpected = [{buffer, CBSz}, {recbuf, CRBSz}],
+            %% Listen, Connect, Accept
+            Expected = {LExpected, CExpected, LExpected},
+            ?P("node ~p started - try get (tcp) buffer options", [Node]),
+            case rpc:call(Node,
+                          ?MODULE,
+                          do_kernel_options_remote,
+                          [Config, Addr]) of
+                {
+                 [{buffer, LBSz}, {recbuf, RB1}], % Listen
+                 [{buffer, CBSz}, {recbuf, RB2}], % Connect
+                 [{buffer, LBSz}, {recbuf, RB3}]  % Accept
+                }
+                  when (RB1 =:= LRBSz) andalso
+                       (RB2 >= CRBSz) andalso
+                       (RB3 >= LRBSz) -> 
+                    ?P("options (buffers) verified:"
+                       "~n   listen:  ~p"
+                       "~n   connect: ~p (>= ~p)"
+                       "~n   accept:  ~p (>= ~p)",
+                       [RB1, RB2, CRBSz, RB3, LRBSz]),
+                    (catch ?STOP_NODE(Node)),
+                    ok;
+                Actual ->
+                    ?P("unexpected:"
+                       "~n   Expected: ~p"
+                       "~n   Actual:   ~p", [Expected, Actual]),
+                    (catch ?STOP_NODE(Node)),
+                    exit({unexpected, Expected, Actual})
+            end;
+        {error, Reason} ->
+            ?P("failed start node: ~p", [Reason]),
+            error
+    end.
+
+do_kernel_options_remote(Config, Addr) ->
+    LS = case ?LISTEN(Config, 0, [{ip, Addr}]) of
+             {ok, S1} ->
+                 S1;
+             {error, _} = ERROR1 ->
+                 exit({listen, ERROR1})
+         end,
+    {LAddr, LPort} = case inet:sockname(LS) of
+                         {ok, {A, P}} ->
+                             {A, P};
+                                                  {error, _} = SN_ERROR ->
+                             exit({sockname, SN_ERROR})
+                     end,
+    CS = case ?CONNECT(Config, LAddr, LPort, [{ip, Addr}]) of
+             {ok, S2} ->
+                 S2;
+             {error, _} = ERROR2 ->
+                 exit({connect, ERROR2})
+         end,
+    AS = case gen_tcp:accept(LS) of
+             {ok, S3} ->
+                 S3;
+             {error, _} = ERROR3 ->
+                 exit({accept, ERROR3})
+         end,
+    {ok, LBuffs} = inet:getopts(LS, [buffer, recbuf]),
+    {ok, CBuffs} = inet:getopts(CS, [buffer, recbuf]),
+    {ok, ABuffs} = inet:getopts(AS, [buffer, recbuf]),
+    {LBuffs, CBuffs, ABuffs}.
+
+
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 is_windows() ->
diff --git a/lib/kernel/test/gen_udp_SUITE.erl b/lib/kernel/test/gen_udp_SUITE.erl
index f120fd330e..bb250ccbaa 100644
--- a/lib/kernel/test/gen_udp_SUITE.erl
+++ b/lib/kernel/test/gen_udp_SUITE.erl
@@ -76,6 +76,8 @@
          t_simple_local_sockaddr_in6_send_recv/1,
          t_simple_link_local_sockaddr_in6_send_recv/1,
 
+         t_kernel_options/1, do_kernel_options_remote/1,
+
          otp_18323_opts_processing/1,
          otp_18323_open/1,
          otp_19332/1,
@@ -154,6 +156,7 @@ all_cases() ->
      {group, socket_monitor},
      otp_17492,
      {group, sockaddr},
+     t_kernel_options,
      {group, tickets}
     ].
 
@@ -2842,8 +2845,8 @@ t_simple_local_sockaddr_in6_send_recv(Config) when is_list(Config) ->
                         case ?LIB:which_local_addr(Domain) of
                             {ok, LA} ->
                                 LA;
-                        {error, _} ->
-                            skip("No local address")
+                            {error, _} ->
+                                skip("No local address")
                     end,
                     SockAddr = #{family   => Domain,
                                  addr     => LocalAddr,
@@ -3238,6 +3241,63 @@ do_simple_sockaddr_send_recv(#{family := _Fam} = SockAddr, _) ->
 
     
 
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+%% This is the most basic of tests.
+
+%% Create a new node with kernel option 'inet_default_udp_options' set
+%% then rpc call a function which creates a socket and reads back the
+%% values of that socket (buffer and recbuf).
+%%
+t_kernel_options(Config) when is_list(Config) ->
+    ?TC_TRY(?FUNCTION_NAME,
+            fun() -> ok end,
+            fun() ->
+                    do_kernel_options(Config)
+            end).
+
+
+do_kernel_options(Config) ->
+    BSz   = 12345,
+    RBSz  = 54321,
+    KOpts = ?F("-kernel inet_default_udp_options "
+               "\"[{buffer,~w},{recbuf,~w}]\"", [BSz, RBSz]),
+    ?P("try start node"),
+    case ?START_NODE(?UNIQ_NODE_NAME, KOpts) of
+        {ok, Node} ->
+            Expected = [{buffer, BSz}, {recbuf, RBSz}],
+            ?P("node ~p started - try get (udp) buffer options", [Node]),
+            case rpc:call(Node, ?MODULE, do_kernel_options_remote, [Config]) of
+                {ok, Expected} ->
+                    ?P("options verified"),
+                    (catch ?STOP_NODE(Node)),
+                    ok;
+                {ok, Actual} ->
+                    ?P("unexpected success:"
+                       "~n   Expected: ~p"
+                       "~n   Actual:   ~p", [Expected, Actual]),
+                    (catch ?STOP_NODE(Node)),
+                    exit({unexpected_success, Expected, Actual});
+                {error, Reason} ->
+                    ?P("unexpected failure:"
+                       "~n   ~p", [Reason]),
+                    (catch ?STOP_NODE(Node)),
+                    exit({unexpected_failure, Reason})
+            end;
+        {error, Reason} ->
+            ?P("failed start node: ~p", [Reason]),
+            error
+    end.
+
+do_kernel_options_remote(Config) ->
+    case ?OPEN(Config, 0, []) of
+        {ok, S} ->
+            inet:getopts(S, [buffer, recbuf]);
+        {error, _} = ERROR ->
+            ERROR
+    end.
+
+
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 %% Verify that the options [add|drop]_membership do not mess up
-- 
2.43.0

openSUSE Build Service is sponsored by