File 0914-kernel-test-Add-UDP-test-case-for-recv-socket-close.patch of Package erlang

From 0e15083a36e93fb47a650e1da19e81700eb0d232 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Thu, 14 May 2020 18:48:03 +0200
Subject: [PATCH 2/3] [kernel|test] Add UDP test case for recv socket close

OTP-16654
---
 lib/kernel/test/gen_udp_SUITE.erl | 84 +++++++++++++++++++++++++++----
 1 file changed, 75 insertions(+), 9 deletions(-)

diff --git a/lib/kernel/test/gen_udp_SUITE.erl b/lib/kernel/test/gen_udp_SUITE.erl
index 2720d3cc77..7ec553ec51 100644
--- a/lib/kernel/test/gen_udp_SUITE.erl
+++ b/lib/kernel/test/gen_udp_SUITE.erl
@@ -38,23 +38,44 @@
 	 read_packets/1, recv_poll_after_active_once/1,
          open_fd/1, connect/1, implicit_inet6/1,
 	 local_basic/1, local_unbound/1,
-	 local_fdopen/1, local_fdopen_unbound/1, local_abstract/1]).
+	 local_fdopen/1, local_fdopen_unbound/1, local_abstract/1,
+         recv_close/1]).
 
 suite() ->
     [{ct_hooks,[ts_install_cth]},
      {timetrap,{minutes,1}}].
 
 all() -> 
-    [send_to_closed, buffer_size, binary_passive_recv,
-     bad_address, read_packets, recv_poll_after_active_once,
-     open_fd, connect,
-     implicit_inet6, active_n,
-     {group, local}].
+    [
+     send_to_closed,
+     buffer_size,
+     binary_passive_recv,
+     bad_address,
+     read_packets,
+     recv_poll_after_active_once,
+     open_fd,
+     connect,
+     implicit_inet6,
+     active_n,
+     recvtos, recvtosttl, recvttl, recvtclass,
+     sendtos, sendtosttl, sendttl, sendtclass,
+     {group, local},
+     recv_close
+    ].
 
 groups() -> 
-    [{local, [],
-      [local_basic, local_unbound,
-       local_fdopen, local_fdopen_unbound, local_abstract]}].
+    [
+     {local, [], local_cases()}
+    ].
+
+local_cases() ->
+    [
+     local_basic,
+     local_unbound,
+     local_fdopen,
+     local_fdopen_unbound,
+     local_abstract
+    ].
 
 init_per_suite(Config) ->
     Config.
@@ -698,6 +719,52 @@ local_handshake(S, SAddr, C, CAddr) ->
 
     end.
 
+
+
+%%-------------------------------------------------------------
+%% Open a passive socket. Create a socket that reads from it.
+%% Then close the socket.
+recv_close(Config) when is_list(Config) ->
+    {ok, Sock} = gen_udp:open(0, [{active, false}]),
+    RECV = fun() ->
+                   io:format("~p try recv~n", [self()]),
+                   Res = gen_udp:recv(Sock, 0),
+                   io:format("~p recv res: ~p~n", [self(), Res]),
+                   exit(Res)
+           end,
+    io:format("~p spawn reader", [self()]),
+    {Pid, MRef} = spawn_monitor(RECV),
+    receive
+        {'DOWN', MRef, process, Pid, PreReason} ->
+            %% Make sure id does not die for some other reason...
+            ?line ct:fail("Unexpected pre close from reader (~p): ~p",
+                          [Pid, PreReason])
+    after 5000 -> % Just in case...
+            ok
+    end,
+    io:format("~p close socket", [self()]),
+    ok = gen_udp:close(Sock),
+    io:format("~p await reader termination", [self()]),
+    receive
+        {'DOWN', MRef, process, Pid, {error, closed}} ->
+            io:format("~p expected reader termination result", [self()]),
+            ok;
+        {'DOWN', MRef, process, Pid, PostReason} ->
+            io:format("~p unexpected reader termination: ~p",
+                      [self(), PostReason]),
+            ?line ct:fail("Unexpected post close from reader (~p): ~p",
+                          [Pid, PostReason])
+    after 5000 ->
+            io:format("~p unexpected reader termination timeout", [self()]),
+            demonitor(MRef, [flush]),
+            exit(Pid, kill),
+            ?line ct:fail("Reader (~p) termination timeout", [Pid])
+    end,
+    ok.
+
+
+
+
 %%
 %% Utils
 %%
-- 
2.26.1

openSUSE Build Service is sponsored by