1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 1998-2021. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20
21%%
22%% Test the behavior of gen_udp. Testing udp is really a very unfunny task,
23%% because udp is not deterministic.
24%%
25-module(gen_udp_SUITE).
26
27-include_lib("common_test/include/ct.hrl").
28-include("kernel_test_lib.hrl").
29
30
31%% XXX - we should pick a port that we _know_ is closed. That's pretty hard.
32-define(CLOSED_PORT, 6666).
33
34-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
35	 init_per_group/2,end_per_group/2]).
36-export([init_per_testcase/2, end_per_testcase/2]).
37
38-export([
39	 send_to_closed/1, active_n/1,
40	 buffer_size/1, binary_passive_recv/1, max_buffer_size/1, bad_address/1,
41	 read_packets/1, recv_poll_after_active_once/1,
42         open_fd/1, connect/1, reconnect/1, implicit_inet6/1,
43         recvtos/1, recvtosttl/1, recvttl/1, recvtclass/1,
44         sendtos/1, sendtosttl/1, sendttl/1, sendtclass/1,
45	 local_basic/1, local_unbound/1,
46	 local_fdopen/1, local_fdopen_unbound/1, local_abstract/1,
47         recv_close/1,
48	 socket_monitor1/1,
49	 socket_monitor1_manys/1,
50	 socket_monitor1_manyc/1,
51	 socket_monitor1_demon_after/1,
52	 socket_monitor2/1,
53	 socket_monitor2_manys/1,
54	 socket_monitor2_manyc/1,
55	 otp_17492/1
56	]).
57
58
59-define(TRY_TC(F), try_tc(F)).
60
61suite() ->
62    [{ct_hooks,[ts_install_cth]},
63     {timetrap,{minutes,1}}].
64
65all() ->
66    %% This is a temporary messure to ensure that we can
67    %% test the socket backend without effecting *all*
68    %% applications on *all* machines.
69    %% This flag is set only for *one* host.
70    case ?TEST_INET_BACKENDS() of
71        true ->
72            [
73             {group, inet_backend_default},
74             {group, inet_backend_inet},
75             {group, inet_backend_socket}
76            ];
77        _ ->
78            [
79             {group, inet_backend_default}
80            ]
81    end.
82
83
84groups() ->
85    [
86     {inet_backend_default,   [], inet_backend_default_cases()},
87     {inet_backend_inet,      [], inet_backend_inet_cases()},
88     {inet_backend_socket,    [], inet_backend_socket_cases()},
89
90     {local,                  [], local_cases()},
91     {socket_monitor,         [], socket_monitor_cases()}
92    ].
93
94inet_backend_default_cases() ->
95    all_cases().
96
97inet_backend_inet_cases() ->
98    all_cases().
99
100inet_backend_socket_cases() ->
101    all_cases().
102
103all_cases() ->
104    [
105     send_to_closed,
106     buffer_size,
107     binary_passive_recv,
108     max_buffer_size,
109     bad_address,
110     read_packets,
111     recv_poll_after_active_once,
112     open_fd,
113     connect,
114     reconnect,
115     implicit_inet6,
116     active_n,
117     recvtos, recvtosttl, recvttl, recvtclass,
118     sendtos, sendtosttl, sendttl, sendtclass,
119     {group, local},
120     recv_close,
121     {group, socket_monitor},
122     otp_17492
123    ].
124
125local_cases() ->
126    [
127     local_basic,
128     local_unbound,
129     local_fdopen,
130     local_fdopen_unbound,
131     local_abstract
132    ].
133
134socket_monitor_cases() ->
135    [
136     socket_monitor1,
137     socket_monitor1_manys,
138     socket_monitor1_manyc,
139     socket_monitor1_demon_after,
140     socket_monitor2,
141     socket_monitor2_manys,
142     socket_monitor2_manyc
143    ].
144
145
146init_per_suite(Config0) ->
147
148    ?P("init_per_suite -> entry with"
149       "~n      Config: ~p"
150       "~n      Nodes:  ~p", [Config0, erlang:nodes()]),
151
152    case ?LIB:init_per_suite(Config0) of
153        {skip, _} = SKIP ->
154            SKIP;
155
156        Config1 when is_list(Config1) ->
157
158            ?P("init_per_suite -> end when "
159               "~n      Config: ~p", [Config1]),
160
161            %% We need a monitor on this node also
162            kernel_test_sys_monitor:start(),
163
164            Config1
165    end.
166
167end_per_suite(Config0) ->
168
169    ?P("end_per_suite -> entry with"
170       "~n      Config: ~p"
171       "~n      Nodes:  ~p", [Config0, erlang:nodes()]),
172
173    %% Stop the local monitor
174    kernel_test_sys_monitor:stop(),
175
176    Config1 = ?LIB:end_per_suite(Config0),
177
178    ?P("end_per_suite -> "
179       "~n      Nodes: ~p", [erlang:nodes()]),
180
181    Config1.
182
183init_per_group(inet_backend_default = _GroupName, Config) ->
184    [{socket_create_opts, []} | Config];
185init_per_group(inet_backend_inet = _GroupName, Config) ->
186    case ?EXPLICIT_INET_BACKEND() of
187        true ->
188            %% The environment trumps us,
189            %% so only the default group should be run!
190            {skip, "explicit inet backend"};
191        false ->
192            [{socket_create_opts, [{inet_backend, inet}]} | Config]
193    end;
194init_per_group(inet_backend_socket = _GroupName, Config) ->
195    case ?EXPLICIT_INET_BACKEND() of
196        true ->
197            %% The environment trumps us,
198            %% so only the default group should be run!
199            {skip, "explicit inet backend"};
200        false ->
201            [{socket_create_opts, [{inet_backend, socket}]} | Config]
202    end;
203init_per_group(local, Config) ->
204    case ?OPEN(Config, 0, [local]) of
205	{ok,S} ->
206	    ok = gen_udp:close(S),
207	    Config;
208	{error, eafnosupport} ->
209	    {skip, "AF_LOCAL not supported"}
210    end;
211init_per_group(_GroupName, Config) ->
212    Config.
213
214end_per_group(local, _Config) ->
215    delete_local_filenames();
216end_per_group(_GroupName, Config) ->
217    Config.
218
219
220init_per_testcase(Case, Config0) ->
221    ?P("init_per_testcase -> entry with"
222       "~n   Config:   ~p"
223       "~n   Nodes:    ~p"
224       "~n   Links:    ~p"
225       "~n   Monitors: ~p",
226       [Config0, erlang:nodes(), pi(links), pi(monitors)]),
227
228    kernel_test_global_sys_monitor:reset_events(),
229
230    Config1 = init_per_testcase2(Case, Config0),
231
232    ?P("init_per_testcase -> done when"
233       "~n   Nodes:    ~p"
234       "~n   Links:    ~p"
235       "~n   Monitors: ~p", [erlang:nodes(), pi(links), pi(monitors)]),
236    Config1.
237
238init_per_testcase2(read_packets, Config) ->
239    ct:timetrap({minutes, 2}),
240    Config;
241init_per_testcase2(_Case, Config) ->
242    Config.
243
244
245end_per_testcase(_Case, Config) ->
246    ?P("end_per_testcase -> entry with"
247       "~n   Config:   ~p"
248       "~n   Nodes:    ~p"
249       "~n   Links:    ~p"
250       "~n   Monitors: ~p",
251       [Config, erlang:nodes(), pi(links), pi(monitors)]),
252
253    ?P("system events during test: "
254       "~n   ~p", [kernel_test_global_sys_monitor:events()]),
255
256    ?P("end_per_testcase -> done with"
257       "~n   Nodes:    ~p"
258       "~n   Links:    ~p"
259       "~n   Monitors: ~p", [erlang:nodes(), pi(links), pi(monitors)]),
260    ok.
261
262
263%%-------------------------------------------------------------
264%% Send two packets to a closed port (on some systems this causes the socket
265%% to be closed).
266
267%% Tests core functionality.
268send_to_closed(Config) when is_list(Config) ->
269    ?TC_TRY(?FUNCTION_NAME, fun() -> do_send_to_closed(Config) end).
270
271do_send_to_closed(Config) ->
272    {ok, Sock} = ?OPEN(Config, 0),
273    ok = gen_udp:send(Sock, {127,0,0,1}, ?CLOSED_PORT, "foo"),
274    timer:sleep(2),
275    ok = gen_udp:send(Sock, {127,0,0,1}, ?CLOSED_PORT, "foo"),
276    ok = gen_udp:close(Sock),
277    ok.
278
279
280
281%%-------------------------------------------------------------
282%% Test that the UDP socket buffer sizes are settable
283
284%% Test UDP buffer size setting.
285buffer_size(Config) when is_list(Config) ->
286    ?TC_TRY(?FUNCTION_NAME, fun() -> do_buffer_size(Config) end).
287
288do_buffer_size(Config) when is_list(Config) ->
289    Len = 256,
290    Bin = list_to_binary(lists:seq(0, Len-1)),
291    M = 8192 div Len,
292    Spec0 =
293	[{opt,M},{safe,M-3},{long,M+1},
294	 {opt,2*M},{safe,2*M-3},{long,2*M+1},
295	 {opt,4*M},{safe,4*M-3},{long,4*M+1}],
296    Spec =
297	[case Tag of
298	     opt ->
299		 [{recbuf,Val*Len},{sndbuf,(Val + 2)*Len}];
300	     safe ->
301		 {list_to_binary(lists:duplicate(Val, Bin)),
302		  [correct]};
303	     long ->
304		 {list_to_binary(lists:duplicate(Val, Bin)),
305		  [truncated,emsgsize,timeout]}
306	 end || {Tag,Val} <- Spec0],
307    %%
308    {ok, ClientSocket}  = ?OPEN(Config, 0, [binary]),
309    {ok, ClientPort} = inet:port(ClientSocket),
310    Client = self(),
311    ClientIP = {127,0,0,1},
312    ServerIP = {127,0,0,1},
313    ?P("Client: {~p, ~p}, ~p", [ClientIP, ClientPort, ClientSocket]),
314    Server =
315	spawn_link(
316	  fun () ->
317		  {ok, ServerSocket}  = ?OPEN(Config, 0, [binary]),
318		  {ok, ServerPort} = inet:port(ServerSocket),
319		  Client ! {self(),port,ServerPort},
320		  buffer_size_server(Client, ClientIP, ClientPort,
321				     ServerSocket, 1, Spec),
322		  ok = gen_udp:close(ServerSocket)
323	  end),
324    Mref = erlang:monitor(process, Server),
325    receive
326	{Server, port, ServerPort} ->
327            ?P("Server: {~p, ~p}, ~p", [ServerIP, ServerPort, Server]),
328	    buffer_size_client(Server, ServerIP, ServerPort,
329			       ClientSocket, 1, Spec)
330    end,
331    ok = gen_udp:close(ClientSocket),
332    receive
333	{'DOWN',Mref,_,_,normal} ->
334	    ok
335    end.
336
337buffer_size_client(_, _, _, _, _, []) ->
338    ok;
339buffer_size_client(Server, IP, Port,
340		   Socket, Cnt, [Opts|T]) when is_list(Opts) ->
341    ?P("buffer_size_client -> Cnt=~w setopts ~p", [Cnt, Opts]),
342    ok = inet:setopts(Socket, Opts),
343    GOpts = [K || {K, _} <- Opts],
344    ?P("buffer_size_client -> opts result: ~p", [inet:getopts(Socket, GOpts)]),
345    Server ! {self(),setopts,Cnt},
346    receive {Server,setopts,Cnt} -> ok end,
347    buffer_size_client(Server, IP, Port, Socket, Cnt+1, T);
348buffer_size_client(Server, IP, Port,
349		   Socket, Cnt, [{B,Replies}|T]=Opts) when is_binary(B) ->
350    ?P("buffer_size_client -> Cnt=~w send size ~w expecting ~p when"
351       "~n   Info: ~p",
352       [Cnt, size(B), Replies, inet:info(Socket)]),
353    case gen_udp:send(Socket, IP, Port, <<Cnt,B/binary>>) of
354	ok ->
355	    receive
356		{Server, Cnt, Reply} ->
357		    Tag =
358			if
359			    is_tuple(Reply) ->
360				element(1, Reply);
361			    is_atom(Reply) ->
362				Reply
363			end,
364		    case lists:member(Tag, Replies) of
365			true -> ok;
366			false ->
367                            ?P("missing from expected replies: "
368                               "~n   Tag:     ~p"
369                               "~n   Replies: ~p", [Tag, Replies]),
370			    ct:fail({reply_mismatch,Cnt,Reply,Replies,
371				     byte_size(B),
372				     inet:getopts(Socket,
373						  [sndbuf,recbuf])})
374		    end,
375		    buffer_size_client(Server, IP, Port, Socket, Cnt+1, T)
376	    after 1313 ->
377		    buffer_size_client(Server, IP, Port, Socket, Cnt, Opts)
378	    end;
379
380	{error, enobufs = Reason} ->
381	    ?P("<WARNING> send failed with '~w' - system overload => SKIP"),
382	    ?SKIPE(Reason);
383
384	{error, Reason} ->
385	    ?P("<ERROR> Client failed sending ~w bytes of data: "
386	       "~n   SndBuf: ~p"
387	       "~n   Reason: ~p",
388	       [size(B), inet:getopts(Socket, [sndbuf]), Reason]),
389	    ct:fail(Reason)
390    end.
391
392buffer_size_server(_, _, _, _, _, []) ->
393    ok;
394buffer_size_server(Client, IP, Port,
395		   Socket, Cnt, [Opts|T]) when is_list(Opts) ->
396    ?P("buffer_size_server -> await client setopts"),
397    receive {Client, setopts, Cnt} -> ok end,
398    ?P("buffer_size_server -> Cnt=~w setopts ~p", [Cnt, Opts]),
399    ok = inet:setopts(Socket, Opts),
400    GOpts = [K || {K, _} <- Opts],
401    ?P("buffer_size_server -> opts result: ~p", [inet:getopts(Socket, GOpts)]),
402    Client ! {self(), setopts, Cnt},
403    buffer_size_server(Client, IP, Port, Socket, Cnt+1, T);
404buffer_size_server(Client, IP, Port,
405		   Socket, Cnt, [{B,_}|T]) when is_binary(B) ->
406    ?P("buffer_size_server -> try receive: Cnt=~w and ~w bytes of data",
407       [Cnt, size(B)]),
408    Reply = case buffer_size_server_recv(Socket, IP, Port, Cnt) of
409                D when is_binary(D) ->
410                    SizeD = byte_size(D),
411                    ?P("buffer_size_server -> received: ~w bytes of data",
412                       [SizeD]),
413                    case B of
414                        D ->
415                            correct;
416                        <<D:SizeD/binary,_/binary>> ->
417                            truncated;
418                        _ ->
419                            {unexpected,D}
420                    end;
421                Error ->
422                    ?P("buffer_size_server -> error: Cnt=~w received error ~w",
423                       [Cnt, Error]),
424                    Error
425            end,
426    ?P("buffer_size_server -> send reply '~p'", [Reply]),
427    Client ! {self(), Cnt, Reply},
428    buffer_size_server(Client, IP, Port, Socket, Cnt+1, T).
429
430buffer_size_server_recv(Socket, IP, Port, Cnt) ->
431    ?P("buffer_size_server -> await data: "
432       "~n   Socket: ~p"
433       "~n   IP:     ~p"
434       "~n   Port:   ~p"
435       "~n   Cnt:    ~p", [Socket, IP, Port, Cnt]),
436    receive
437	{udp, Socket, IP, Port, <<Cnt, B/binary>>} ->
438            ?P("buffer_size_server -> received (~w) ~w bytes", [Cnt, size(B)]),
439	    B;
440	{udp, Socket, IP, Port, <<_B/binary>>} ->
441            ?P("buffer_size_server -> received unexpected ~w bytes",
442               [size(_B)]),
443	    buffer_size_server_recv(Socket, IP, Port, Cnt);
444
445	{udp, Socket, IP, Port, _CRAP} ->
446            ?P("buffer_size_server -> received unexpected crap"),
447	    buffer_size_server_recv(Socket, IP, Port, Cnt);
448
449	{udp, XSocket, XIP, XPort, _CRAP} ->
450            ?P("buffer_size_server -> received unexpected udp message: "
451               "~n   XSocket: ~p"
452               "~n   Socket:  ~p"
453               "~n   XIP:     ~p"
454               "~n   IP:      ~p"
455               "~n   XPort:   ~p"
456               "~n   Port:    ~p",
457               [XSocket, Socket, XIP, IP, XPort, Port]),
458	    buffer_size_server_recv(Socket, IP, Port, Cnt);
459
460	{udp_error, Socket, Error} ->
461            ?P("buffer_size_server -> error: ~p", [Error]),
462	    Error
463
464    after 5000 ->
465            ?P("buffer_size_server -> timeout"),
466	    {timeout, flush()}
467    end.
468
469
470%%-------------------------------------------------------------
471%% OTP-15206: Keep buffer small for udp
472%%-------------------------------------------------------------
473max_buffer_size(Config) when is_list(Config) ->
474    ?TC_TRY(?FUNCTION_NAME, fun() -> do_max_buffer_size(Config) end).
475
476do_max_buffer_size(Config) when is_list(Config) ->
477    ?P("create socket"),
478    {ok, Socket} = ?OPEN(Config, 0, [binary]),
479    ?P("get buffers"),
480    {ok, [{recbuf, RecBuf0}, {buffer, Buffer0}]} =
481        inet:getopts(Socket, [recbuf, buffer]),
482    ?P("buffers: "
483       "~n   RecBuf: ~p"
484       "~n   Buffer: ~p", [RecBuf0, Buffer0]),
485    NewRecBuf = 1 bsl 20,
486    ?P("set recbuf: ~w", [NewRecBuf]),
487    ok = inet:setopts(Socket, [{recbuf, NewRecBuf}]),
488    ?P("get buffers"),
489    case inet:getopts(Socket, [recbuf, buffer]) of
490        {ok, [{recbuf, RecBuf}, {buffer, 65536 = Buffer}]} ->
491            ?P("buffers: expected"
492               "~n   RecBuf: ~p"
493               "~n   Buffer: ~p", [RecBuf, Buffer]),
494            gen_udp:close(Socket),
495            ok;
496        {ok, [{recbuf, RecBuf}, {buffer, Buffer}]} ->
497            ?P("buffers: unexpected"
498               "~n   RecBuf: ~p"
499               "~n   Buffer: ~p", [RecBuf, Buffer]),
500            gen_udp:close(Socket),
501            ct:fail({unexpected_buffer_size, Buffer});
502        {error, Reason} ->
503            ?P("failed extracting buffers"
504               "~n   ~p", [Reason]),
505            (catch gen_udp:close(Socket)),
506            ct:fail({unexpected_getopts_error, Reason})
507    end,
508    ?P("done"),
509    ok.
510
511
512
513
514%%-------------------------------------------------------------
515%% OTP-3823 gen_udp:recv does not return address in binary mode
516%%
517
518%% OTP-3823 gen_udp:recv does not return address in binary mode.
519binary_passive_recv(Config) when is_list(Config) ->
520    ?TC_TRY(?FUNCTION_NAME, fun() -> do_binary_passive_recv(Config) end).
521
522do_binary_passive_recv(Config) when is_list(Config) ->
523    D1       = "The quick brown fox jumps over a lazy dog",
524    D2       = list_to_binary(D1),
525    D3       = ["The quick", <<" brown ">>, "fox jumps ", <<"over ">>,
526		<<>>, $a, [[], " lazy ", <<"dog">>]],
527    D2       = iolist_to_binary(D3),
528    B        = D2,
529    ?P("open receive socket"),
530    {ok, R}  = ?OPEN(Config, 0, [binary, {active, false}]),
531    {ok, RP} = inet:port(R),
532    ?P("open send socket"),
533    {ok, S}  = ?OPEN(Config, 0),
534    {ok, SP} = inet:port(S),
535    ?P("try send (to port ~w) ~w bytes (as a list)", [RP, length(D1)]),
536    ok       = gen_udp:send(S, localhost, RP, D1),
537    ?P("try recv (from port ~w) ~w bytes", [SP, byte_size(B)+1]),
538    {ok, {{127, 0, 0, 1}, SP, B}} = gen_udp:recv(R, byte_size(B)+1),
539    ?P("try send (to port ~w) ~w bytes (as a binary)", [RP, byte_size(D2)]),
540    ok       = gen_udp:send(S, localhost, RP, D2),
541    ?P("try recv (from port ~w) ~w bytes", [SP, byte_size(B)+1]),
542    {ok, {{127, 0, 0, 1}, SP, B}} = gen_udp:recv(R, byte_size(B)+1),
543    ?P("try send (to port ~w) ~w bytes (as a iolist)", [RP, iolist_size(D3)]),
544    ok       = gen_udp:send(S, localhost, RP, D3),
545    ?P("try recv (from port ~w) ~w bytes", [SP, byte_size(B)+1]),
546    {ok, {{127, 0, 0, 1}, SP, B}} = gen_udp:recv(R, byte_size(B)+1),
547    ?P("cleanup"),
548    ok       = gen_udp:close(S),
549    ok       = gen_udp:close(R),
550    ?P("done"),
551    ok.
552
553
554%%-------------------------------------------------------------
555%% OTP-3836 inet_udp crashes when IP-address is larger than 255.
556
557%% OTP-3836 inet_udp crashes when IP-address is larger than 255.
558bad_address(Config) when is_list(Config) ->
559    ?TC_TRY(?FUNCTION_NAME, fun() -> do_bad_address(Config) end).
560
561do_bad_address(Config) when is_list(Config) ->
562    ?P("create sockets"),
563    {ok, R}   = ?OPEN(Config, 0),
564    {ok, RP}  = inet:port(R),
565    {ok, S}   = ?OPEN(Config, 0),
566    {ok, _SP} = inet:port(S),
567
568    ?P("try send to invalid address 1 - expect failure"),
569    case (catch gen_udp:send(S, {127,0,0,1,0}, RP, "void")) of
570        {'EXIT', badarg} ->
571            ok;
572        Any1 ->
573            ?P("<ERROR> unexpected result: "
574               "~n   ~p", [Any1]),
575            ct:fail({unexpected_result, 1, Any1})
576    end,
577
578    ?P("try send to invalid address 2 - expect failure"),
579    case (catch gen_udp:send(S, {127,0,0,256}, RP, "void")) of
580        {'EXIT', badarg} ->
581            ok;
582        Any2 ->
583            ?P("<ERROR> unexpected result: "
584               "~n   ~p", [Any2]),
585            ct:fail({unexpected_result, 2, Any2})
586    end,
587
588    ?P("cleanup"),
589    ok       = gen_udp:close(S),
590    ok       = gen_udp:close(R),
591
592    ?P("done"),
593    ok.
594
595
596%%-------------------------------------------------------------
597%% OTP-6249 UDP option for number of packet reads
598%%
599%% Starts a slave node that on command sends a bunch of messages
600%% to our UDP port. The receiving process just receives and
601%% ignores the incoming messages.
602%% A tracing process traces the receiving port for
603%% 'send' and scheduling events. From the trace,
604%% how many messages are received per in/out scheduling,
605%% which should never be more than the read_packet parameter.
606
607%% OTP-6249 UDP option for number of packet reads.
608read_packets(Config) when is_list(Config) ->
609    Cond = fun() ->
610		   case ?IS_SOCKET_BACKEND(Config) of
611		       true ->
612                           %% We have not (yet) implemented support for
613                           %% this option. We accept it but do not use it.
614			   {skip, "Not complient with socket"};
615		       false ->
616			   ok
617		   end
618	   end,
619    TC   = fun() -> do_read_packets(Config) end,
620    ?TC_TRY(?FUNCTION_NAME, Cond, TC).
621
622do_read_packets(Config) when is_list(Config) ->
623    N1   = 5,
624    N2   = 1,
625    Msgs = 30000,
626    ?P("open socket (with read-packets: ~p)", [N1]),
627    {ok, R}   = ?OPEN(Config, 0, [{read_packets,N1}]),
628    {ok, RP}  = inet:port(R),
629    ?P("create slave node"),
630    {ok,Node} = start_node(gen_udp_SUITE_read_packets),
631    %%
632    ?P("perform read-packets test"),
633    {V1, Trace1} = read_packets_test(Config, R, RP, Msgs, Node),
634    ?P("verify read-packets (to ~w)", [N1]),
635    {ok,[{read_packets,N1}]} = inet:getopts(R, [read_packets]),
636    %%
637    ?P("set new read-packets: ~p", [N2]),
638    ok = inet:setopts(R, [{read_packets, N2}]),
639    ?P("perform read-packets test"),
640    {V2, Trace2} = read_packets_test(Config, R, RP, Msgs, Node),
641    ?P("verify read-packets (to ~w)", [N2]),
642    {ok, [{read_packets,N2}]} = inet:getopts(R, [read_packets]),
643    %%
644    ?P("stop slave node"),
645    stop_node(Node),
646
647    ?P("dump trace 1"),
648    dump_terms(Config, "trace1.terms", Trace1),
649    ?P("dump trace 2"),
650    dump_terms(Config, "trace2.terms", Trace2),
651
652    %% Because of the inherit racy-ness of the feature it is
653    %% hard to test that it behaves correctly.
654    %% Right now (OTP 21) a port task takes 5% of the
655    %% allotted port task reductions to execute, so
656    %% the max number of executions a port is allowed to
657    %% do before being re-scheduled is N * 20
658
659    ?P("read-packets test verification when: "
660       "~n      N1: ~p"
661       "~n      V1: ~p"
662       "~n   vs"
663       "~n      N2: ~p"
664       "~n      V2: ~p", [N1, V1, N2, V2]),
665    if
666        V1 > (N1 * 20) ->
667            ct:fail("Got ~p msgs, max was ~p", [V1, N1]);
668        V2 > (N2 * 20) ->
669            ct:fail("Got ~p msgs, max was ~p", [V2, N2]);
670        true ->
671            ok
672    end,
673    ?P("done"),
674    ok.
675
676dump_terms(Config, Name, Terms) ->
677    FName = filename:join(proplists:get_value(priv_dir, Config),Name),
678    file:write_file(FName, term_to_binary(Terms)),
679    ct:log("Logged terms to ~s",[FName]).
680
681read_packets_test(Config, R, RP, Msgs, Node) ->
682    Receiver = self(),
683    Tracer =
684	spawn_link(
685	  fun () ->
686		  receive
687		      {Receiver,get_trace} ->
688			  Receiver ! {self(),{trace,flush()}}
689		  end
690	  end),
691    Sender =
692	spawn_opt(
693	  Node,
694	  fun () ->
695		  {ok, S}  = ?OPEN(Config, 0),
696		  {ok, SP} = inet:port(S),
697		  Receiver ! {self(),{port,SP}},
698		  receive
699		      {Receiver,go} ->
700			  read_packets_send(S, RP, Msgs)
701		  end
702	  end,
703	  [link,{priority,high}]),
704    receive
705	{Sender,{port,SP}} ->
706	    erlang:trace(R, true,
707			 [running_ports,'send',{tracer,Tracer}]),
708	    erlang:yield(),
709	    Sender ! {Receiver,go},
710	    read_packets_recv(Msgs),
711	    erlang:trace(R, false, [all]),
712	    Tracer ! {Receiver,get_trace},
713	    receive
714		{Tracer,{trace,Trace}} ->
715		    {read_packets_verify(R, SP, Trace), Trace}
716	    end
717    end.
718
719read_packets_send(_S, _RP, 0) ->
720    ok;
721read_packets_send(S, RP, Msgs) ->
722    ok = gen_udp:send(S, localhost, RP, "UDP FLOOOOOOD"),
723    read_packets_send(S, RP, Msgs - 1).
724
725read_packets_recv(0) ->
726    ok;
727read_packets_recv(N) ->
728    receive
729	_ ->
730	    read_packets_recv(N - 1)
731    after 5000 ->
732	    timeout
733    end.
734
735read_packets_verify(R, SP, Trace) ->
736    [Max | _] = Pkts = lists:reverse(lists:sort(read_packets_verify(R, SP, Trace, 0))),
737    ?P("read-packets verify: ~p", [lists:sublist(Pkts,10)]),
738    Max.
739
740read_packets_verify(R, SP, [{trace,R,OutIn,_}|Trace], M)
741  when OutIn =:= out; OutIn =:= in ->
742    push(M, read_packets_verify(R, SP, Trace, 0));
743read_packets_verify(R, SP, [{trace, R,'receive',timeout}|Trace], M) ->
744    push(M, read_packets_verify(R, SP, Trace, 0));
745read_packets_verify(R, SP,
746		    [{trace,R,'send',{udp,R,{127,0,0,1},SP,_Msg}, Self} | Trace], M)
747  when Self =:= self() ->
748    read_packets_verify(R, SP, Trace, M+1);
749read_packets_verify(_R, _SP, [], M) ->
750    push(M, []);
751read_packets_verify(R, SP, [T | Trace], M) ->
752    ct:fail(
753      {read_packets_verify, mismatch, self(),
754       {R, SP, [T, length(Trace)], M}});
755read_packets_verify(_R, _SP, Trace, M) ->
756    ct:fail({read_packets_verify,mismatch,Trace,M}).
757
758push(0, Vs) ->
759    Vs;
760push(V, Vs) ->
761    [V|Vs].
762
763flush() ->
764    receive
765	X ->
766	    [X|flush()]
767    after 200 ->
768	    []
769    end.
770
771
772%% OTP-16059
773%% UDP recv with timeout 0 corrupts internal state so that after a
774%% recv under {active, once} the UDP recv poll wastes incoming data
775recv_poll_after_active_once(Config) when is_list(Config) ->
776    Msg1 = <<"Hej!">>,
777    Msg2 = <<"Hej igen!">>,
778    Addr = {127,0,0,1},
779    {ok,S1} = ?OPEN(Config, 0, [binary, {active, once}]),
780    {ok,P1} = inet:port(S1),
781    {ok,S2} = ?OPEN(Config, 0, [binary, {active, false}]),
782    {ok,P2} = inet:port(S2),
783    ok = gen_udp:send(S2, Addr, P1, Msg1),
784    receive
785        {udp, S1, Addr, P2, Msg1} ->
786            {error, timeout} = gen_udp:recv(S1, 0, 0),
787            ok = gen_udp:send(S2, Addr, P1, Msg2),
788            receive after 500 -> ok end, % Give the kernel time to deliver
789            {ok, {Addr, P2, Msg2}} = gen_udp:recv(S1, 0, 0),
790            ok
791    end.
792
793
794%% Test that the 'fd' option works.
795open_fd(Config) when is_list(Config) ->
796    ?TC_TRY(?FUNCTION_NAME, fun() -> do_open_fd(Config) end).
797
798do_open_fd(Config) when is_list(Config) ->
799    Msg = "Det gör ont när knoppar brista. Varför skulle annars våren tveka?",
800    Addr = {127,0,0,1},
801    ?P("try open first (default domain = inet) socket and get its fd"),
802    {S1, FD} = case ?OPEN(Config, 0) of
803                   {ok, Sock1} when is_port(Sock1) ->
804                       {ok, FileDesc1} = prim_inet:getfd(Sock1),
805                       {Sock1, FileDesc1};
806                   {ok, Sock1} ->
807                      {ok, [{fd, FileDesc1}]} =
808                          gen_udp_socket:getopts(Sock1, [fd]),
809                      {Sock1, FileDesc1}
810               end,
811    ?P("try get the socket port number"),
812    {ok, P2} = inet:port(S1),
813
814    ?P("try open second (domain = inet6) socket with FD = ~w "
815       "and expect *failure*", [FD]),
816
817    case ?OPEN(Config, 0, [inet6, {fd,FD}]) of
818        {error, einval = Reason} ->
819            ?P("expected failure reason ~w", [Reason]),
820            ok;
821        {error, eafnosupport = Reason} ->
822            ?P("expected failure reason ~w (IPv6 not supported?)", [Reason]),
823            ok;
824        {error, Reason} ->
825            ?P("unexpected failure: ~w", [Reason]),
826            ct:fail({unexpected_failure, Reason});
827        {ok, Socket} ->
828            ?P("unexpected success: "
829               "~n   ~p", [inet:info(Socket)]),
830            (catch gen_udp:close(Socket)),
831            (catch gen_udp:close(S1)),
832            ct:fail(unexpected_succes)
833    end,
834
835    ?P("try open second socket with FD = ~w "
836       "and expect success", [FD]),
837    {ok, S2} = ?OPEN(Config, 0, [{fd, FD}]),
838    {ok, P2} = inet:port(S2),
839
840    ?P("try open third socket and expect success"),
841    {ok, S3} = ?OPEN(Config, 0),
842    {ok, P3} = inet:port(S3),
843
844    ?P("try send message from socket 3 to socket 2 (~w)", [P2]),
845    ok = gen_udp:send(S3, Addr, P2, Msg),
846    receive
847	{udp, S2, Addr, P3, Msg} ->
848            ?P("expected recv - "
849               "try send message from socket 2 to socket 3 (~w)", [P3]),
850	    ok = gen_udp:send(S2, Addr, P3, Msg),
851	    receive
852		{udp, S3, Addr, P2, Msg} ->
853                    ?P("expected recv - done"),
854		    ok
855	    after 1000 ->
856                    ?P("unexpected timeout"),
857		    ct:fail(io_lib:format("~w", [flush()]))
858	    end
859    after 1000 ->
860            ?P("unexpected timeout"),
861	    ct:fail(io_lib:format("~w", [flush()]))
862    end,
863    ?P("cleanup"),
864    (catch gen_udp:close(S3)),
865    (catch gen_udp:close(S2)),
866    (catch gen_udp:close(S1)),
867    ?P("done"),
868    ok.
869
870active_n(Config) when is_list(Config) ->
871    ?TC_TRY(?FUNCTION_NAME, fun() -> do_active_n(Config) end).
872
873do_active_n(Config) when is_list(Config) ->
874    N = 3,
875    ?P("create socket (1) with active = ~w", [N]),
876    S1 = ok(?OPEN(Config, 0, [{active,N}])),
877    ?P("verify socket active = ~w (~p)", [N, which_info(S1)]),
878    [{active,N}] = ok(inet:getopts(S1, [active])),
879
880    ?P("set active = ~w and expect passive", [-N]),
881    ok = inet:setopts(S1, [{active,-N}]),
882    receive
883        {udp_passive, S1} ->
884            ?P("expected passive received"),
885            ok
886    after
887        5000 ->
888            ?P("ERROR: passive *not* received"),
889            exit({error,udp_passive_failure})
890    end,
891    ?P("verify socket active passive (=false) (~p)", [which_info(S1)]),
892    [{active,false}] = ok(inet:getopts(S1, [active])),
893
894    ?P("set active = 0 and expect passive message"),
895    ok = inet:setopts(S1, [{active, 0}]),
896    receive
897        {udp_passive, S1} ->
898            ?P("expected passive received"),
899            ok
900    after
901        5000 ->
902            ?P("ERROR: passive *not* received"),
903            exit({error,udp_passive_failure})
904    end,
905
906    ?P("set active = 32767 (=max) and expect success"),
907    ok = inet:setopts(S1, [{active,32767}]),
908    ?P("try set active = 1 (already at max) and expect failure (einval)"),
909    {error, einval} = inet:setopts(S1, [{active,1}]),
910    ?P("set active = -32769 (<min) and expect failure (einval)"),
911    {error, einval} = inet:setopts(S1, [{active,-32769}]),
912    ?P("set active = -32768 and expect passive message"),
913    ok = inet:setopts(S1, [{active,-32768}]),
914    receive
915        {udp_passive, S1} ->
916            ?P("expected passive received"),
917            ok
918    after
919        5000 ->
920            ?P("ERROR: passive *not* received"),
921            exit({error,udp_passive_failure})
922    end,
923
924    ?P("verify socket active passive (=false), (~p)", [which_info(S1)]),
925    [{active,false}] = ok(inet:getopts(S1, [active])),
926    ?P("set active = ~w and expect success", [N]),
927    ok = inet:setopts(S1, [{active,N}]),
928    ?P("set active = ~w and expect success", [true]),
929    ok = inet:setopts(S1, [{active,true}]),
930    ?P("verify socket active active (=true) (~p)", [which_info(S1)]),
931    [{active,true}] = ok(inet:getopts(S1, [active])),
932    ?P("verify nothing in the message queue"),
933    receive
934        Unexpected_1 ->
935            ?P("ERROR: something in the message queue: "
936               "~n   ~p", [Unexpected_1]),
937            exit({error, active_n, Unexpected_1})
938    after
939        0 ->
940            ?P("nothing in the message queue"),
941            ok
942    end,
943
944    ?P("set active = ~w and expect success", [N]),
945    ok = inet:setopts(S1, [{active,N}]),
946    ?P("set active = ~w and expect success", [once]),
947    ok = inet:setopts(S1, [{active,once}]),
948    ?P("verify socket active active (=once) (~p)", [which_info(S1)]),
949    [{active,once}] = ok(inet:getopts(S1, [active])),
950    receive
951        Unexpected_2 ->
952            ?P("ERROR: something in the message queue: "
953               "~n   ~p", [Unexpected_2]),
954            exit({error,active_n, Unexpected_2})
955    after
956        0 ->
957            ?P("nothing in the message queue"),
958            ok
959    end,
960
961    ?P("set active = ~w and expect failure (einval)", [32768]),
962    {error,einval} = inet:setopts(S1, [{active,32768}]),
963    ?P("set active = ~w and expect success", [false]),
964    ok = inet:setopts(S1, [{active,false}]),
965    ?P("verify socket active passive (=false) (~p)", [which_info(S1)]),
966    [{active,false}] = ok(inet:getopts(S1, [active])),
967
968    S1Port = ok(inet:port(S1)),
969    ?P("create socket (2) with active = ~w", [N]),
970    S2 = ok(?OPEN(Config, 0, [{active,N}])),
971    S2Port = ok(inet:port(S2)),
972    ?P("verify socket (2) active = ~w (~p)", [N, which_info(S2)]),
973    [{active,N}] = ok(inet:getopts(S2, [active])),
974    ?P("set socket (1) active = ~w and expect success", [N]),
975    ok = inet:setopts(S1, [{active,N}]),
976    ?P("verify socket (1) active = ~w (~p)", [N, which_info(S1)]),
977    [{active,N}] = ok(inet:getopts(S1, [active])),
978    ?P("generate ~w message(s) and send them: S1 -> S2 and S2 -> S1 when:"
979       "~n   Socket 1 info: ~p"
980       "~n   Socket 2 info: ~p", [N, inet:info(S1), inet:info(S2)]),
981    lists:foreach(
982      fun(I) ->
983              Msg = "message "++integer_to_list(I),
984              ?P("send message ~w from S2 to S1 (~w):"
985                 "~n   S1: ~p"
986                 "~n   S2: ~p",
987                 [I, S1Port, inet:info(S1), inet:info(S2)]),
988              ok = gen_udp:send(S2, "localhost", S1Port, Msg),
989              ?P("expect message on S1"),
990              receive
991                  {udp, S1, _, S2Port, Msg} ->
992                      ?P("expected message received on S1 - "
993                         "send message back: from S1 to S2 (~w): "
994                         "~n   ~p", [S2Port, inet:info(S1)]),
995                      ok = gen_udp:send(S1, "localhost", S2Port, Msg)
996              after
997                  5000 ->
998                      ?P("ERROR: received nothing (->S1)"),
999                      exit({error,timeout})
1000              end,
1001              ?P("expect message on S2"),
1002              receive
1003                  {udp, S2, _, S1Port, Msg} ->
1004                      ?P("expected message received on S2: "
1005                         "~n   ~p", [inet:info(S2)]),
1006                      ok
1007              after
1008                  5000 ->
1009                      ?P("ERROR: received nothing (->S2)"),
1010                      exit({error,timeout})
1011              end
1012      end, lists:seq(1,N)),
1013    ?P("expect passive message for socket (1)"),
1014    receive
1015        {udp_passive, S1} ->
1016            ?P("received passive message for socket (1) - "
1017               "verify socket active passive (false)"),
1018            [{active,false}] = ok(inet:getopts(S1, [active]))
1019    after
1020        5000 ->
1021            ?P("ERROR: received nothing (1)"),
1022            exit({error,udp_passive})
1023    end,
1024    ?P("expect passive message for socket (2)"),
1025    receive
1026        {udp_passive,S2} ->
1027            ?P("received passive message for socket (2) - "
1028               "verify socket active passive (false)"),
1029            [{active,false}] = ok(inet:getopts(S2, [active]))
1030    after
1031        5000 ->
1032            ?P("ERROR: received nothing (2)"),
1033            exit({error,udp_passive})
1034    end,
1035
1036    ?P("create socket (3) with active = ~w and expect passive message", [0]),
1037    S3 = ok(?OPEN(Config, 0, [{active,0}])),
1038    receive
1039        {udp_passive,S3} ->
1040            ?P("received passive message for socket (3) - "
1041               "verify socket active passive (false)"),
1042            [{active,false}] = ok(inet:getopts(S3, [active]))
1043    after
1044        5000 ->
1045            ?P("ERROR: received nothing (3)"),
1046            exit({error,udp_passive})
1047    end,
1048
1049    ?P("cleanup"),
1050    ok = gen_udp:close(S3),
1051    ok = gen_udp:close(S2),
1052    ok = gen_udp:close(S1),
1053
1054    ?P("done"),
1055    ok.
1056
1057
1058
1059recvtos(Config) ->
1060    test_recv_opts(
1061      Config,
1062      inet, [{recvtos,tos,96}], false,
1063      fun recvtos_ok/2).
1064
1065recvtosttl(Config) ->
1066    test_recv_opts(
1067      Config,
1068      inet, [{recvtos,tos,96},{recvttl,ttl,33}], false,
1069      fun (OSType, OSVer) ->
1070              recvtos_ok(OSType, OSVer) andalso recvttl_ok(OSType, OSVer)
1071      end).
1072
1073recvttl(Config) ->
1074    test_recv_opts(
1075      Config,
1076      inet, [{recvttl,ttl,33}], false,
1077      fun recvttl_ok/2).
1078
1079recvtclass(Config) ->
1080    {ok,IFs} = inet:getifaddrs(),
1081    case
1082        [Name ||
1083            {Name,Opts} <- IFs,
1084            lists:member({addr,{0,0,0,0,0,0,0,1}}, Opts)]
1085    of
1086        [_] ->
1087            test_recv_opts(
1088              Config,
1089              inet6, [{recvtclass,tclass,224}], false,
1090              fun recvtclass_ok/2);
1091        [] ->
1092            {skip,ipv6_not_supported,IFs}
1093    end.
1094
1095
1096sendtos(Config) ->
1097    ?TC_TRY(sendtos, fun() -> do_sendtos(Config) end).
1098
1099do_sendtos(Config) ->
1100    test_recv_opts(
1101      Config,
1102      inet, [{recvtos,tos,96}], true,
1103      fun sendtos_ok/2).
1104
1105sendtosttl(Config) ->
1106    ?TC_TRY(sendtosttl, fun() -> do_sendtosttl(Config) end).
1107
1108do_sendtosttl(Config) ->
1109    test_recv_opts(
1110      Config,
1111      inet, [{recvtos,tos,96},{recvttl,ttl,33}], true,
1112      fun (OSType, OSVer) ->
1113              sendtos_ok(OSType, OSVer) andalso sendttl_ok(OSType, OSVer)
1114      end).
1115
1116sendttl(Config) ->
1117    ?TC_TRY(sendttl, fun() -> do_sendttl(Config) end).
1118
1119do_sendttl(Config) ->
1120    test_recv_opts(
1121      Config,
1122      inet, [{recvttl,ttl,33}], true,
1123      fun sendttl_ok/2).
1124
1125sendtclass(Config) ->
1126    ?TC_TRY(sendtclass, fun() -> do_sendtclass(Config) end).
1127
1128do_sendtclass(Config) ->
1129    {ok,IFs} = inet:getifaddrs(),
1130    case
1131        [Name ||
1132            {Name,Opts} <- IFs,
1133            lists:member({addr,{0,0,0,0,0,0,0,1}}, Opts)]
1134    of
1135        [_] ->
1136            test_recv_opts(
1137              Config,
1138              inet6, [{recvtclass,tclass,224}], true,
1139              fun sendtclass_ok/2);
1140        [] ->
1141            {skip, {ipv6_not_supported, IFs}}
1142    end.
1143
1144
1145%% These version numbers are just above the highest noted in daily tests
1146%% where the test fails for a plausible reason, that is the lowest
1147%% where we can expect that the test might succeed, so
1148%% skip on platforms lower than this.
1149%%
1150%% On newer versions it might be fixed, but we'll see about that
1151%% when machines with newer versions gets installed...
1152%% If the test still fails for a plausible reason these
1153%% version numbers simply should be increased.
1154%% Or maybe we should change to only test on known good platforms?
1155
1156%% Using the option returns einval, so it is not implemented.
1157recvtos_ok({unix,darwin}, OSVer) -> not semver_lt(OSVer, {17,6,0});
1158%% Using the option returns einval, so it is not implemented.
1159recvtos_ok({unix,openbsd}, _OSVer) -> false; % not semver_lt(OSVer, {6,9,0});
1160%% Using the option returns einval, so it is not implemented.
1161recvtos_ok({unix,netbsd}, _OSVer) -> false;
1162%% Using the option returns einval, so it is not implemented.
1163recvtos_ok({unix,sunos}, OSVer) -> not semver_lt(OSVer, {5,12,0});
1164%%
1165recvtos_ok({unix,_}, _) -> true;
1166recvtos_ok(_, _) -> false.
1167
1168%% Option has no effect
1169recvttl_ok({unix,sunos}, OSVer) -> not semver_lt(OSVer, {5,12,0});
1170%%
1171recvttl_ok({unix,_}, _) -> true;
1172recvttl_ok(_, _) -> false.
1173
1174%% Using the option returns einval, so it is not implemented.
1175recvtclass_ok({unix,darwin}, OSVer) -> not semver_lt(OSVer, {9,9,0});
1176recvtclass_ok({unix,linux}, OSVer) -> not semver_lt(OSVer, {2,6,11});
1177%% Option has no effect
1178recvtclass_ok({unix,sunos}, OSVer) -> not semver_lt(OSVer, {5,12,0});
1179%%
1180recvtclass_ok({unix,_}, _) -> true;
1181recvtclass_ok(_, _) -> false.
1182
1183
1184%% To send ancillary data seems to require much higher version numbers
1185%% than receiving it...
1186%%
1187
1188%% Using the option returns einval, so it is not implemented.
1189sendtos_ok({unix,darwin}, OSVer) -> not semver_lt(OSVer, {19,0,0});
1190sendtos_ok({unix,netbsd}, _OSVer) -> false;
1191sendtos_ok({unix,openbsd}, _OSVer) -> false; % not semver_lt(OSVer, {6,9,0});
1192sendtos_ok({unix,sunos}, OSVer) -> not semver_lt(OSVer, {5,12,0});
1193sendtos_ok({unix,linux}, OSVer) -> not semver_lt(OSVer, {4,0,0});
1194sendtos_ok({unix,freebsd}, _OSVer) -> false; % not semver_lt(OSVer, {13,1,0});
1195%%
1196sendtos_ok({unix,_}, _) -> true;
1197sendtos_ok(_, _) -> false.
1198
1199%% Using the option returns einval, so it is not implemented.
1200sendttl_ok({unix,darwin}, _OSVer) -> false; % not semver_lt(OSVer, {19,6,0});
1201sendttl_ok({unix,linux}, OSVer) -> not semver_lt(OSVer, {4,0,0});
1202%% Using the option returns enoprotoopt, so it is not implemented.
1203sendttl_ok({unix,freebsd}, _OSVer) -> false; % not semver_lt(OSVer, {13,1,0});
1204%% Option has no effect
1205sendttl_ok({unix,sunos}, OSVer) -> not semver_lt(OSVer, {5,12,0});
1206sendttl_ok({unix,openbsd}, _OSVer) -> false; % not semver_lt(OSVer, {6,9,0});
1207%%
1208sendttl_ok({unix,_}, _) -> true;
1209sendttl_ok(_, _) -> false.
1210
1211%% Using the option returns einval, so it is not implemented.
1212sendtclass_ok({unix,darwin}, OSVer) -> not semver_lt(OSVer, {9,9,0});
1213sendtclass_ok({unix,linux}, OSVer) -> not semver_lt(OSVer, {2,6,11});
1214%% Option has no effect
1215sendtclass_ok({unix,sunos}, OSVer) -> not semver_lt(OSVer, {5,12,0});
1216%%
1217sendtclass_ok({unix,_}, _) -> true;
1218sendtclass_ok(_, _) -> false.
1219
1220
1221semver_lt({X1,Y1,Z1} = V1, {X2,Y2,Z2} = V2) ->
1222    ?P("semver_lt -> OS version check:"
1223       "~n   Version 1: ~p"
1224       "~n   Version 2: ~p", [V1, V2]),
1225    if
1226        X1 > X2 -> ?P("semver_lt -> X1 > X2: ~p > ~p", [X1, X2]), false;
1227        X1 < X2 -> ?P("semver_lt -> X1 < X2: ~p < ~p", [X1, X2]), true;
1228        Y1 > Y2 -> ?P("semver_lt -> Y1 > Y2: ~p > ~p", [Y1, Y2]), false;
1229        Y1 < Y2 -> ?P("semver_lt -> Y1 < Y2: ~p < ~p", [Y1, Y2]), true;
1230        Z1 > Z2 -> ?P("semver_lt -> Z1 > Z2: ~p > ~p", [Z1, Z2]), false;
1231        Z1 < Z2 -> ?P("semver_lt -> Z1 < Z2: ~p < ~p", [Z1, Z2]), true;
1232        true    -> ?P("semver_lt -> default"), false
1233    end;
1234semver_lt(V1, {_,_,_} = V2) ->
1235    ?P("semver_lt -> fallback OS version check when: "
1236       "~n   Version 1: ~p"
1237       "~n   Version 2: ~p", [V1, V2]),
1238    false.
1239
1240test_recv_opts(Config, Family, Spec, TestSend, OSFilter) ->
1241    OSType = os:type(),
1242    OSVer  = os:version(),
1243    case OSFilter(OSType, OSVer) of
1244        true ->
1245            ?P("OS: ~p, ~p", [OSType, OSVer]),
1246            test_recv_opts(Config,
1247                           Family, Spec, TestSend, OSType, OSVer);
1248        false ->
1249            {skip,{not_supported_for_os_version,{OSType,OSVer}}}
1250    end.
1251%%
1252test_recv_opts(Config, Family, Spec, TestSend, _OSType, _OSVer) ->
1253    Timeout = 5000,
1254    RecvOpts = [RecvOpt || {RecvOpt,_,_} <- Spec],
1255    TrueRecvOpts = [{RecvOpt,true} || {RecvOpt,_,_} <- Spec],
1256    FalseRecvOpts = [{RecvOpt,false} || {RecvOpt,_,_} <- Spec],
1257    Opts = [Opt || {_,Opt,_} <- Spec],
1258    OptsVals = [{Opt,Val} || {_,Opt,Val} <- Spec],
1259    TrueRecvOpts_OptsVals = TrueRecvOpts ++ OptsVals,
1260    Addr =
1261        case Family of
1262            inet ->
1263                {127,0,0,1};
1264            inet6 ->
1265                {0,0,0,0,0,0,0,1}
1266        end,
1267    %%
1268    ?P("try open socket (1) with true opts"),
1269    {ok, S1} = ?OPEN(Config, 0, [Family, binary, {active,false}|TrueRecvOpts]),
1270    {ok, P1} = inet:port(S1),
1271    ?P("try get (true) socket (1) opts"),
1272    {ok, TrueRecvOpts} = inet:getopts(S1, RecvOpts),
1273    ?P("try set (false) socket (1) opts"),
1274    ok = inet:setopts(S1, FalseRecvOpts),
1275    ?P("verify (false) socket (1) opts"),
1276    {ok, FalseRecvOpts} = inet:getopts(S1, RecvOpts),
1277    ok = inet:setopts(S1, TrueRecvOpts_OptsVals),
1278    {ok,TrueRecvOpts_OptsVals} = inet:getopts(S1, RecvOpts ++ Opts),
1279    %%
1280    %% S1 now has true receive options and set option values
1281    %%
1282    ?P("try open socket (2) with false opts"),
1283    {ok, S2} =
1284        ?OPEN(Config, 0, [Family, binary, {active,true} | FalseRecvOpts]),
1285    {ok, P2} = inet:port(S2),
1286    ?P("try get (false) socket (2) opts"),
1287    {ok, FalseRecvOpts_OptsVals2} = inet:getopts(S2, RecvOpts ++ Opts),
1288    OptsVals2 = FalseRecvOpts_OptsVals2 -- FalseRecvOpts,
1289    ?P("info: "
1290       "~n   Socket 1:    ~p"
1291       "~n   Socket 2:    ~p"
1292       "~n   Opts Vals 2: ~p", [inet:info(S1), inet:info(S2), OptsVals2]),
1293
1294    %%
1295    %% S2 now has false receive options and default option values,
1296    %% OptsVals2 contains the default option values
1297    %%
1298    ?P("send/3: S2 -> S1"),
1299    ok = gen_udp:send(S2, {Addr,P1}, <<"abcde">>),
1300    ?P("send/4: S1 -> S2"),
1301    ok = gen_udp:send(S1, Addr, P2, <<"fghij">>),
1302    TestSend andalso
1303        begin
1304            ?P("send/5: S2 -> S1"
1305               "~n   ~p", [OptsVals]),
1306            case gen_udp:send(S2, Addr, P1, OptsVals, <<"ABCDE">>) of
1307                ok ->
1308                    ok;
1309                {error, enoprotoopt = Reason1} ->
1310                    ?SKIPT(?F("send (1) failed: ~p", [Reason1]))
1311            end,
1312            ?P("send/4: S2 -> S1"
1313               "~n   ~p", [OptsVals]),
1314            case gen_udp:send(S2, {Addr,P1}, OptsVals, <<"12345">>) of
1315                ok ->
1316                    ok;
1317                {error, enoprotoopt = Reason2} ->
1318                    ?SKIPT(?F("send (2) failed: ~p", [Reason2]))
1319            end
1320        end,
1321    ?P("try S1 recv"),
1322    {ok,{_,P2,OptsVals3, <<"abcde">>}} = gen_udp:recv(S1, 0, Timeout),
1323    ?P("S1 recv: "
1324       "~n   OptsVals3: ~p", [OptsVals3]),
1325    verify_sets_eq(OptsVals3, OptsVals2),
1326    TestSend andalso
1327        begin
1328            ?P("try S1 recv"),
1329            {ok,{_,P2,OptsVals0,<<"ABCDE">>}} = gen_udp:recv(S1, 0, Timeout),
1330            ?P("S1 recv: "
1331               "~n   OptsVals0: ~p", [OptsVals0]),
1332            ?P("try S1 recv"),
1333            {ok,{_,P2,OptsVals1,<<"12345">>}} = gen_udp:recv(S1, 0, Timeout),
1334            ?P("S1 recv: "
1335               "~n   OptsVals1: ~p", [OptsVals1]),
1336            verify_sets_eq(OptsVals0, OptsVals),
1337            verify_sets_eq(OptsVals1, OptsVals)
1338        end,
1339    ?P("await message on S2"),
1340    receive
1341        {udp, S2, _, P1, <<"fghij">>} ->
1342            ?P("S2 received message"),
1343            ok;
1344        Other1 ->
1345            exit({unexpected,Other1})
1346    after Timeout ->
1347            exit(timeout)
1348    end,
1349    %%
1350    ?P("try set (false) socket (1) opts"),
1351    ok = inet:setopts(S1, FalseRecvOpts),
1352    ?P("verify (false) socket (1) opts"),
1353    {ok, FalseRecvOpts} = inet:getopts(S1, RecvOpts),
1354    ?P("try set (true) socket (1) opts"),
1355    ok = inet:setopts(S2, TrueRecvOpts),
1356    ?P("verify (true) socket (1) opts"),
1357    {ok,TrueRecvOpts} = inet:getopts(S2, RecvOpts),
1358    %%
1359    %% S1 now has false receive options and set option values
1360    %%
1361    %% S2 now has true receive options and default option values
1362    %%
1363    ?P("send/4: S2 -> S1"),
1364    ok = gen_udp:send(S2, {Addr,P1}, [], <<"klmno">>),
1365    ?P("send/3: S1 -> S2"),
1366    ok = gen_udp:send(S1, {Family,{loopback,P2}}, <<"pqrst">>),
1367    TestSend andalso
1368        begin
1369            ?P("send/4: S1 -> S2"
1370               "~n   ~p", [OptsVals]),
1371            ok = gen_udp:send(S1, {Family,{loopback,P2}}, OptsVals2, <<"PQRST">>)
1372        end,
1373    ?P("try recv data on S1"),
1374    {ok,{_,P2,<<"klmno">>}} = gen_udp:recv(S1, 0, Timeout),
1375    ?P("await message on S2"),
1376    receive
1377        {udp,S2,_,P1,OptsVals4,<<"pqrst">>} ->
1378            ?P("S2 message received: "
1379               "~n   OptsVals4: ~p", [OptsVals4]),
1380            verify_sets_eq(OptsVals4, OptsVals);
1381        Other2 ->
1382            exit({unexpected,Other2})
1383    after Timeout ->
1384            exit(timeout)
1385    end,
1386    ?P("(maybe, ~p) await message on S2", [TestSend]),
1387    TestSend andalso
1388        receive
1389            {udp, S2, _, P1, OptsVals5, <<"PQRST">>} ->
1390                ?P("S2 message received: "
1391                   "~n   OptsVals5: ~p", [OptsVals5]),
1392                verify_sets_eq(OptsVals5, OptsVals2);
1393            Other3 ->
1394                exit({unexpected,Other3})
1395        after Timeout ->
1396                exit(timeout)
1397        end,
1398
1399    ?P("cleanup"),
1400    ok = gen_udp:close(S1),
1401    ok = gen_udp:close(S2),
1402%%%    exit({{_OSType,_OSVer},success}), % In search for the truth
1403
1404    ?P("done"),
1405    ok.
1406
1407verify_sets_eq(L1, L2) ->
1408    L = lists:sort(L1),
1409    case lists:sort(L2) of
1410        L ->
1411            ok;
1412        _ ->
1413            exit({sets_neq, L1, L2})
1414    end.
1415
1416
1417local_basic(Config) ->
1418    ?TC_TRY(?FUNCTION_NAME, fun() -> do_local_basic(Config) end).
1419
1420
1421do_local_basic(Config) ->
1422    ?P("begin"),
1423    SFile = local_filename(server),
1424    SAddr = {local,bin_filename(SFile)},
1425    CFile = local_filename(client),
1426    CAddr = {local,bin_filename(CFile)},
1427    _ = file:delete(SFile),
1428    _ = file:delete(CFile),
1429    %%
1430    ?P("create server socket"),
1431    S = ok(?OPEN(Config, 0, [{ifaddr,{local,SFile}},{active,false}])),
1432    ?P("create client socket"),
1433    C = ok(?OPEN(Config, 0, [{ifaddr,{local,CFile}},{active,false}])),
1434    SAddr = ok(inet:sockname(S)),
1435    CAddr = ok(inet:sockname(C)),
1436    ?P("SockName(s):"
1437       "~n   Server: ~p"
1438       "~n   Client: ~p", [SAddr, CAddr]),
1439    local_handshake(S, SAddr, C, CAddr),
1440
1441    ?P("cleanup"),
1442    ok = gen_udp:close(S),
1443    ok = gen_udp:close(C),
1444    %%
1445    ok = file:delete(SFile),
1446    ok = file:delete(CFile),
1447    ?P("end"),
1448    ok.
1449
1450local_unbound(Config) ->
1451    SFile = local_filename(server),
1452    SAddr = {local,bin_filename(SFile)},
1453    _ = file:delete(SFile),
1454    %%
1455    S = ok(?OPEN(Config, 0, [{ifaddr,SAddr},{active,false}])),
1456    C = ok(?OPEN(Config, 0, [local,{active,false}])),
1457    SAddr = ok(inet:sockname(S)),
1458    local_handshake(S, SAddr, C, undefined),
1459    ok = gen_udp:close(S),
1460    ok = gen_udp:close(C),
1461    %%
1462    ok = file:delete(SFile),
1463    ok.
1464
1465local_fdopen(Config) ->
1466    ?TC_TRY(?FUNCTION_NAME, fun() -> do_local_fdopen(Config) end).
1467
1468
1469do_local_fdopen(Config) ->
1470    ?P("begin"),
1471    SFile = local_filename(server),
1472    SAddr = {local,bin_filename(SFile)},
1473    CFile = local_filename(client),
1474    CAddr = {local,bin_filename(CFile)},
1475    _ = file:delete(SFile),
1476    _ = file:delete(CFile),
1477
1478    %%
1479    ?P("try create \"dummy\" (server) socket"),
1480    {S0, FD} = case ?OPEN(Config, 0, [{ifaddr,SAddr},{active,false}]) of
1481                   {ok, Sock0} when is_port(Sock0) ->
1482                       ?P("(port) try extract FD"),
1483                       Fd = ok(prim_inet:getfd(Sock0)),
1484                       {Sock0, Fd};
1485                   {ok, Sock0} -> % socket
1486                       ?P("(socket) try extract FD"),
1487                       {ok, [{fd, Fd}]} =
1488                           gen_udp_socket:getopts(Sock0, [fd]),
1489                       {Sock0, Fd}
1490               end,
1491    ?P("try create (client) socket"),
1492    C  = ok(?OPEN(Config, 0, [{ifaddr,{local,CFile}},{active,false}])),
1493    SAddr = ok(inet:sockname(S0)),
1494    CAddr = ok(inet:sockname(C)),
1495    ?P("try create (server) socket using fd = ~w", [FD]),
1496    S  = ok(?OPEN(Config, 0, [{fd, FD}, local, {active,false}])),
1497    SAddr = ok(inet:sockname(S)),
1498
1499    ?P("perform handshake"),
1500    local_handshake(S, SAddr, C, CAddr),
1501
1502    ?P("cleanup"),
1503    ok = gen_udp:close(S),
1504    ok = gen_udp:close(S0),
1505    ok = gen_udp:close(C),
1506    %%
1507    ok = file:delete(SFile),
1508    ok = file:delete(CFile),
1509    ?P("done"),
1510    ok.
1511
1512local_fdopen_unbound(Config) ->
1513    ?TC_TRY(?FUNCTION_NAME, fun() -> do_local_fdopen_unbound(Config) end).
1514
1515do_local_fdopen_unbound(Config) ->
1516    ?P("begin"),
1517    SFile = local_filename(server),
1518    SAddr = {local,bin_filename(SFile)},
1519    _ = file:delete(SFile),
1520
1521    %%
1522    ?P("try create (server) socket"),
1523    S  = ok(?OPEN(Config, 0, [{ifaddr,SAddr},{active,false}])),
1524    ?P("try create \"dummy\" (client) socket"),
1525    {C0, FD} = case ?OPEN(Config, 0, [local,{active,false}]) of
1526                   {ok, Sock0} when is_port(Sock0) ->
1527                       ?P("(port) try extract FD"),
1528                       Fd = ok(prim_inet:getfd(Sock0)),
1529                       {Sock0, Fd};
1530                   {ok, Sock0} -> % socket
1531                       ?P("(socket) try extract FD"),
1532                       {ok, [{fd, Fd}]} =
1533                           gen_udp_socket:getopts(Sock0, [fd]),
1534                       {Sock0, Fd}
1535               end,
1536    SAddr = ok(inet:sockname(S)),
1537    ?P("try create (client) socket using fd = ~w", [FD]),
1538    C  = ok(?OPEN(Config, 0, [{fd,Fd},local,{active,false}])),
1539
1540    ?P("perform handshake"),
1541    local_handshake(S, SAddr, C, undefined),
1542
1543    ?P("cleanup"),
1544    ok = gen_udp:close(S),
1545    ok = gen_udp:close(C),
1546    ok = gen_udp:close(C0),
1547    %%
1548    ok = file:delete(SFile),
1549
1550    ?P("done"),
1551    ok.
1552
1553local_abstract(Config) ->
1554    ?TC_TRY(?FUNCTION_NAME, fun() -> do_local_abstract(Config) end).
1555
1556do_local_abstract(Config) ->
1557    case os:type() of
1558	{unix,linux} ->
1559            ?P("create server socket"),
1560	    S = ok(?OPEN(Config, 0, [{ifaddr,{local,<<>>}},{active,false}])),
1561            ?P("create client socket"),
1562	    C = ok(?OPEN(Config, 0, [{ifaddr,{local,<<>>}},{active,false}])),
1563            ?P("verify sockname(s)"),
1564	    {local,_} = SAddr = ok(inet:sockname(S)),
1565	    {local,_} = CAddr = ok(inet:sockname(C)),
1566            ?P("perform handshake"),
1567	    local_handshake(S, SAddr, C, CAddr),
1568            ?P("cleanup"),
1569	    ok = gen_udp:close(S),
1570	    ok = gen_udp:close(C),
1571            ?P("done"),
1572	    ok;
1573	_ ->
1574	    {skip, "AF_LOCAL Abstract Addresses only supported on Linux"}
1575    end.
1576
1577
1578local_handshake(S, SAddr, C, CAddr) ->
1579    SData = "9876543210",
1580    CData = "0123456789",
1581    ?P("try (client) send"),
1582    ok = gen_udp:send(C, SAddr, 0, CData),
1583    ?P("try (server) recv"),
1584    case ok(gen_tcp:recv(S, 112)) of
1585	{{unspec,<<>>}, 0, CData} when CAddr =:= undefined ->
1586	    ok;
1587	{{local,<<>>}, 0, CData} when CAddr =:= undefined ->
1588	    ok;
1589	{CAddr, 0, CData} when CAddr =/= undefined ->
1590	    ok = gen_udp:send(S, CAddr, 0, SData),
1591	    {SAddr, 0, SData} = ok(gen_tcp:recv(C, 112)),
1592	    ok
1593
1594    end.
1595
1596
1597
1598%%-------------------------------------------------------------
1599%% Open a passive socket. Create a socket that reads from it.
1600%% Then close the socket.
1601recv_close(Config) when is_list(Config) ->
1602    ?P("begin"),
1603    {ok, Sock} = ?OPEN(Config, 0, [{active, false}]),
1604    RECV = fun() ->
1605                   ?P("try recv"),
1606                   Res = gen_udp:recv(Sock, 0),
1607                   ?P("recv res: ~p", [Res]),
1608                   exit(Res)
1609           end,
1610    ?P("spawn reader"),
1611    {Pid, MRef} = spawn_monitor(RECV),
1612    receive
1613        {'DOWN', MRef, process, Pid, PreReason} ->
1614            %% Make sure id does not die for some other reason...
1615            ?line ct:fail("Unexpected pre close from reader (~p): ~p",
1616                          [Pid, PreReason])
1617    after 5000 -> % Just in case...
1618            ok
1619    end,
1620    ?P("close socket"),
1621    ok = gen_udp:close(Sock),
1622    ?P("await reader termination"),
1623    receive
1624        {'DOWN', MRef, process, Pid, {error, closed}} ->
1625            ?P("expected reader termination result"),
1626            ok;
1627        {'DOWN', MRef, process, Pid, PostReason} ->
1628            ?P("unexpected reader termination: ~p", [PostReason]),
1629            ?line ct:fail("Unexpected post close from reader (~p): ~p",
1630                          [Pid, PostReason])
1631    after 5000 ->
1632            ?P("unexpected reader termination timeout"),
1633            demonitor(MRef, [flush]),
1634            exit(Pid, kill),
1635            ?line ct:fail("Reader (~p) termination timeout", [Pid])
1636    end,
1637    ?P("done"),
1638    ok.
1639
1640
1641
1642
1643%% Test that connect/3 has effect.
1644connect(Config) when is_list(Config) ->
1645    ?TC_TRY(?FUNCTION_NAME, fun() -> do_connect(Config) end).
1646
1647do_connect(Config) when is_list(Config) ->
1648    ?P("begin"),
1649    Addr = {127,0,0,1},
1650    ?P("try create first socket"),
1651    {ok, S1} = ?OPEN(Config, 0),
1652    {ok, P1} = inet:port(S1),
1653    ?P("try create second socket"),
1654    {ok, S2} = ?OPEN(Config, 0),
1655    ?P("try set second socket active: false: "
1656       "~n   ~p", [inet:info(S2)]),
1657    ok = inet:setopts(S2, [{active, false}]),
1658    ?P("try close first socket"),
1659    ok = gen_udp:close(S1),
1660    ?P("try connect second socket to: ~p, ~p", [Addr, P1]),
1661    ok = gen_udp:connect(S2, Addr, P1),
1662    ?P("try send on second socket"),
1663    ok = gen_udp:send(S2, <<16#deadbeef:32>>),
1664    ?P("try recv on second socket - expect failure: "
1665       "~n   ~p", [inet:info(S2)]),
1666    ok = case gen_udp:recv(S2, 0, 500) of
1667	     {error, econnrefused} -> ok;
1668	     {error, econnreset}   -> ok;
1669	     Other ->
1670                 ?P("UNEXPECTED failure: ~p:"
1671                    "~n   ~p", [Other, inet:info(S2)]),
1672                 Other
1673	 end,
1674    ?P("done"),
1675    ok.
1676
1677
1678
1679reconnect(Config) when is_list(Config) ->
1680    ?TC_TRY(?FUNCTION_NAME, fun () -> do_reconnect(Config) end).
1681
1682do_reconnect(Config) ->
1683    LoopAddr = {127,0,0,1},
1684    XtrnAddr = {8,8,8,8},
1685    DestPort = 53,
1686    {S, Port} = open_port_0(Config, []),
1687    ?P("Socket: ~w", [S]),
1688    %% Connect to a loopback destination
1689    ok = gen_udp:connect(S, LoopAddr, DestPort),
1690    {ok, {LoopAddr,DestPort}} = inet:peername(S),
1691    {ok, {LocalAddr,Port}} = inet:sockname(S),
1692    ?P("Socket addr: ~w", [LocalAddr]),
1693    %% Reconnect to external destination
1694    ok = gen_udp:connect(S, XtrnAddr, DestPort),
1695    {ok, {XtrnAddr,DestPort}} = inet:peername(S),
1696    {ok, {RoutableAddr,Port}} = inet:sockname(S),
1697    %% We should have a non-loopback address here
1698    true = RoutableAddr =/= LocalAddr,
1699    %% Reconnect to loopback
1700    ok = gen_udp:connect(S, LoopAddr, DestPort),
1701    {ok, {LoopAddr,DestPort}} = inet:peername(S),
1702    {ok, {LocalAddr,Port}} = inet:sockname(S),
1703    ok = inet:close(S).
1704
1705%% For Linux to keep the port when we reconnect;
1706%% we need to first bind to a specific port.
1707%% If we bind to port 0 and get an ephemeral port
1708%% it apparently can change when we reconnect to a different
1709%% destination depending on routing and interfaces.
1710%%
1711%% I consider this a workaround for a Linux bug,
1712%% ironically in a test case that tests
1713%% a workaround for another Linux bug (related)...
1714%%
1715open_port_0(Config, Opts) ->
1716    open_port_0(Config, 0, Opts, 10).
1717%%
1718open_port_0(Config, Port, Opts, N) ->
1719    case ?OPEN(Config, Port, Opts) of
1720        {ok, S} ->
1721            if
1722                Port =:= 0 ->
1723                    {ok, Port_1} = inet:port(S),
1724                    ok = gen_udp:close(S),
1725                    %% Speculate that we can open a socket with that port
1726                    open_port_0(Config, Port_1, Opts, N);
1727                true ->
1728                    ?P("Socket port: ~w", [Port]),
1729                    {S, Port}
1730            end;
1731        {error, eaddrinuse} when Port =/= 0 ->
1732            open_port_0(Config, 0, Opts, N - 1);
1733        {error, _} = Error ->
1734            Error
1735    end.
1736
1737%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1738
1739implicit_inet6(Config) when is_list(Config) ->
1740    ?TC_TRY(implicit_inet6, fun() -> do_implicit_inet6(Config) end).
1741
1742do_implicit_inet6(Config) ->
1743    Host = ok(inet:gethostname()),
1744    case inet:getaddr(Host, inet6) of
1745	{ok, {16#fe80,0,0,0,_,_,_,_} = Addr} ->
1746	     ?SKIPT("Got link local IPv6 address: "
1747                    ++inet:ntoa(Addr));
1748	{ok, Addr} ->
1749	    implicit_inet6(Config, Host, Addr);
1750	{error, Reason} ->
1751	    ?SKIPT("Can not look up IPv6 address: "
1752                   ++atom_to_list(Reason))
1753    end.
1754
1755implicit_inet6(Config, Host, Addr) ->
1756    Active = {active,false},
1757    Loopback = {0,0,0,0,0,0,0,1},
1758    ?P("try 1 with explit inet6 on loopback"),
1759    S1 = case ?OPEN(Config, 0, [inet6, Active, {ip, Loopback}]) of
1760             {ok, Sock1} ->
1761                 Sock1;
1762             {error, eaddrnotavail = Reason1} ->
1763                 ?SKIPT(open_failed_str(Reason1));
1764             _ ->
1765                 ?SKIPT("IPv6 not supported")
1766         end,
1767    implicit_inet6(Config, S1, Active, Loopback),
1768    ok = gen_udp:close(S1),
1769    %%
1770    Localaddr = ok(get_localaddr()),
1771    ?P("try 2 on local addr (~p)", [Localaddr]),
1772    S2 = case ?OPEN(Config, 0, [{ip, Localaddr}, Active]) of
1773             {ok, Sock2} ->
1774                 Sock2;
1775             {error, eaddrnotavail = Reason2} ->
1776                 ?SKIPT(open_failed_str(Reason2))
1777         end,
1778    implicit_inet6(Config, S2, Active, Localaddr),
1779    ok = gen_udp:close(S2),
1780    %%
1781    ?P("try 3 on addr ~p (~p)", [Addr, Host]),
1782    S3 = case ?OPEN(Config, 0, [{ifaddr, Addr}, Active]) of
1783             {ok, Sock3} ->
1784                 Sock3;
1785             {error, eaddrnotavail = Reason3} ->
1786                 ?SKIPT(open_failed_str(Reason3))
1787         end,
1788    implicit_inet6(Config, S3, Active, Addr),
1789    ok = gen_udp:close(S3),
1790    ok.
1791
1792implicit_inet6(Config, S1, Active, Addr) ->
1793    ?P("get (\"local\") port number"),
1794    P1 = ok(inet:port(S1)),
1795    ?P("open \"remote\" socket"),
1796    S2 = case ?OPEN(Config, 0, [inet6, Active]) of
1797             {ok, Sock2} ->
1798                 Sock2;
1799             {error, eaddrnotavail = Reason3} ->
1800                 ?SKIPT(open_failed_str(Reason3))
1801         end,
1802    ?P("get (\"remote\") port number"),
1803    P2 = ok(inet:port(S2)),
1804    ?P("connect (\"remote\") socket (to ~p:~p)", [Addr, P1]),
1805    ok = gen_udp:connect(S2, Addr, P1),
1806    ?P("connect (\"local\") socket (to ~p:~p)", [Addr, P2]),
1807    ok = gen_udp:connect(S1, Addr, P2),
1808    ?P("peername of \"local\" socket"),
1809    {Addr,P2} = ok(inet:peername(S1)),
1810    ?P("peername of \"remote\" socket"),
1811    {Addr,P1} = ok(inet:peername(S2)),
1812    ?P("sockname of \"local\" socket"),
1813    {Addr,P1} = ok(inet:sockname(S1)),
1814    ?P("sockname of \"remote\" socket"),
1815    {Addr,P2} = ok(inet:sockname(S2)),
1816    ?P("send ping on \"local\" socket (to ~p:~p)", [Addr, P2]),
1817    ok = gen_udp:send(S1, Addr, P2, "ping"),
1818    ?P("recv ping on \"remote\" socket (from ~p:~p)", [Addr, P1]),
1819    {Addr,P1,"ping"} = ok(gen_udp:recv(S2, 1024, 1000)),
1820    ?P("send pong on \"remote\" socket (to ~p:~p)", [Addr, P1]),
1821    ok = gen_udp:send(S2, Addr, P1, "pong"),
1822    ?P("recv ping on \"local\" socket (from ~p:~p)", [Addr, P2]),
1823    {Addr,P2,"pong"} = ok(gen_udp:recv(S1, 1024)),
1824    ?P("close \"remote\" socket"),
1825    ok = gen_udp:close(S2),
1826    ok.
1827
1828
1829
1830%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1831
1832%% This is the most basic of tests.
1833%% We create a socket, then spawns processes that create
1834%% monitors to it...
1835socket_monitor1(Config) when is_list(Config) ->
1836    ct:timetrap(?MINS(1)),
1837    ?TC_TRY(socket_monitor1,
1838            fun() -> do_socket_monitor1(Config) end).
1839
1840do_socket_monitor1(Config) ->
1841    ?P("begin"),
1842    Self         = self(),
1843    Type         = ?SOCKET_TYPE(Config),
1844    {ok, Sock1} = ?OPEN(Config),
1845    F  = fun(S, Fun) -> spawn_monitor(fun() -> Fun(S, Self) end) end,
1846    F1 = fun(Socket, Parent) when is_pid(Parent) ->
1847		 ?P("[client] create monitor"),
1848		 MRef = inet:monitor(Socket),
1849		 Parent ! {self(), ready},
1850		 sm_await_socket_down(MRef, Socket, Type)
1851	 end,
1852    ?P("spawn client"),
1853    {Pid1, Mon1} = F(Sock1, F1),
1854    ?P("await client ready"),
1855    sm_await_client_ready(Pid1),
1856    ?P("close socket"),
1857    gen_udp:close(Sock1),
1858    ?P("await client termination"),
1859    sm_await_down(Pid1, Mon1, ok),
1860    ?P("done"),
1861    ok.
1862
1863sm_await_socket_down(ExpMon, ExpSock, ExpType) ->
1864    sm_await_socket_down(ExpMon, ExpSock, ExpType, "client").
1865
1866sm_await_socket_down(ExpMon, ExpSock, ExpType, Name) ->
1867    receive
1868	{'DOWN', Mon, Type, Sock, Info} when (Type =:= ExpType) andalso
1869					     (Mon  =:= ExpMon)  andalso
1870					     (Sock =:= ExpSock) ->
1871	    ?P("[~s] received expected (socket) down message: "
1872	       "~n   Mon:  ~p"
1873	       "~n   Type: ~p"
1874	       "~n   Sock: ~p"
1875	       "~n   Info: ~p", [Name, Mon, Type, Sock, Info]),
1876	    exit(ok);
1877
1878	Any ->
1879	    ?P("[~s] received unexpected message: "
1880	       "~n   ~p", [Name, Any]),
1881	    exit({unexpected_message, Any})
1882    end.
1883
1884sm_await_client_ready(Pid) ->
1885    sm_await_client_ready(Pid, "client").
1886
1887sm_await_client_ready(Pid, Name) ->
1888    receive
1889	{Pid, ready} ->
1890	    ?P("received ~s ready", [Name])
1891    end.
1892
1893sm_await_down(Pid, Mon, ExpRes) ->
1894    receive
1895	{'DOWN', Mon, process, Pid, ExpRes} ->
1896	    ?P("received expected process down message from ~p", [Pid]),
1897	    ok;
1898	{'DOWN', Mon, process, Pid, UnexpRes} ->
1899	    ?P("received unexpected process down message from ~p: "
1900	       "~n   ~p", [Pid, UnexpRes]),
1901	    ct:fail({unexpected_down, UnexpRes})
1902    end.
1903
1904
1905%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1906
1907%% This is the most basic of tests.
1908%% We create "many" socket(s), then spawn processes that create
1909%% monitors to them...
1910socket_monitor1_manys(Config) when is_list(Config) ->
1911    ct:timetrap(?MINS(1)),
1912    ?TC_TRY(socket_monitor1_manys,
1913            fun() -> do_socket_monitor1_manys(Config) end).
1914
1915do_socket_monitor1_manys(Config) ->
1916    ?P("begin"),
1917    Self         = self(),
1918    Type         = ?SOCKET_TYPE(Config),
1919    ?P("[client] create socket(s)"),
1920    {ok, Sock1} = ?OPEN(Config),
1921    {ok, Sock2} = ?OPEN(Config),
1922    {ok, Sock3} = ?OPEN(Config),
1923    {ok, Sock4} = ?OPEN(Config),
1924    {ok, Sock5} = ?OPEN(Config),
1925    F  = fun(S, Fun) -> spawn_monitor(fun() -> Fun(S, Self) end) end,
1926    F1 = fun(Sockets, Parent) when is_list(Sockets) andalso is_pid(Parent) ->
1927		 ?P("[client] create monitor(s)"),
1928		 Monitors = [{inet:monitor(Socket), Socket} ||
1929				Socket <- Sockets],
1930		 Parent ! {self(), ready},
1931		 sm_await_socket_down2(Monitors, Type)
1932	 end,
1933    ?P("spawn client"),
1934    {Pid1, Mon1} = F([Sock1, Sock2, Sock3, Sock4, Sock5], F1),
1935    ?P("await client ready"),
1936    sm_await_client_ready(Pid1),
1937    ?P("close socket(s)"),
1938    gen_udp:close(Sock1),
1939    gen_udp:close(Sock2),
1940    gen_udp:close(Sock3),
1941    gen_udp:close(Sock4),
1942    gen_udp:close(Sock5),
1943    ?P("await client termination"),
1944    sm_await_down(Pid1, Mon1, ok),
1945    ?P("done"),
1946    ok.
1947
1948
1949sm_await_socket_down2(Monitors, ExpType) ->
1950    sm_await_socket_down2(Monitors, ExpType, "client").
1951
1952sm_await_socket_down2([], _ExpType, Name) ->
1953    ?P("[~s] all sockets down", [Name]),
1954    exit(ok);
1955sm_await_socket_down2(Mons, ExpType, Name) when is_list(Mons) ->
1956    ?P("[~s] await socket down", [Name]),
1957    receive
1958	{'DOWN', Mon, Type, Sock, Info} when (Type =:= ExpType) ->
1959	    ?P("[~s] received expected (socket) down message: "
1960	       "~n   Mon:  ~p"
1961	       "~n   Type: ~p"
1962	       "~n   Sock: ~p"
1963	       "~n   Info: ~p", [Name, Mon, Type, Sock, Info]),
1964	    case lists:keysearch(Mon, 1, Mons) of
1965		{value, {Mon, Sock}} ->
1966		    Mons2 = lists:keydelete(Mon, 1, Mons),
1967		    sm_await_socket_down2(Mons2, ExpType, Name);
1968		{value, Value} ->
1969		    ?P("[~s] Unexpected socket down: "
1970		       "~n   Value: ~p", [Name, Value]),
1971		    ct:fail({unexpected_monitor, Mon, Value});
1972		false ->
1973		    ct:fail({unknown_monitor, Mon})
1974	    end
1975    end.
1976
1977
1978
1979%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1980
1981%% This is the most basic of tests.
1982%% We create a socket, then spawn client process(es) that create
1983%% monitors to it...
1984socket_monitor1_manyc(Config) when is_list(Config) ->
1985    ct:timetrap(?MINS(1)),
1986    ?TC_TRY(socket_monitor1_manyc,
1987            fun() -> do_socket_monitor1_manyc(Config) end).
1988
1989do_socket_monitor1_manyc(Config) ->
1990    ?P("begin"),
1991    Self         = self(),
1992    Type         = ?SOCKET_TYPE(Config),
1993    {ok, Sock1}  = ?OPEN(Config),
1994    F  = fun(S, Fun, Name) ->
1995		 spawn_monitor(fun() -> Fun(S, Name, Self) end)
1996	 end,
1997    F1 = fun(Socket, Name, Parent) when is_list(Name) andalso is_pid(Parent) ->
1998		 ?P("[~s] monitor socket", [Name]),
1999		 MRef = inet:monitor(Socket),
2000		 Parent ! {self(), ready},
2001		 sm_await_socket_down(MRef, Socket, Type)
2002	 end,
2003    ?P("spawn client(s)"),
2004    {Pid1, Mon1} = F(Sock1, F1, "client1"),
2005    {Pid2, Mon2} = F(Sock1, F1, "client2"),
2006    {Pid3, Mon3} = F(Sock1, F1, "client3"),
2007    {Pid4, Mon4} = F(Sock1, F1, "client4"),
2008    {Pid5, Mon5} = F(Sock1, F1, "client5"),
2009    ?P("await client(s) ready"),
2010    sm_await_client_ready(Pid1, "client1"),
2011    sm_await_client_ready(Pid2, "client2"),
2012    sm_await_client_ready(Pid3, "client3"),
2013    sm_await_client_ready(Pid4, "client4"),
2014    sm_await_client_ready(Pid5, "client5"),
2015    ?P("close socket"),
2016    gen_udp:close(Sock1),
2017    ?P("await client(s) termination"),
2018    sm_await_down(Pid1, Mon1, ok),
2019    sm_await_down(Pid2, Mon2, ok),
2020    sm_await_down(Pid3, Mon3, ok),
2021    sm_await_down(Pid4, Mon4, ok),
2022    sm_await_down(Pid5, Mon5, ok),
2023    ?P("done"),
2024    ok.
2025
2026
2027%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2028
2029%% This is the most basic of tests.
2030%% We create a socket, then spawns processes that create
2031%% monitors to it...
2032socket_monitor1_demon_after(Config) when is_list(Config) ->
2033    ct:timetrap(?MINS(1)),
2034    ?TC_TRY(socket_monitor1_demon_after,
2035            fun() -> do_socket_monitor1_demon_after(Config) end).
2036
2037do_socket_monitor1_demon_after(Config) ->
2038    ?P("begin"),
2039    Self         = self(),
2040    Type         = ?SOCKET_TYPE(Config),
2041    {ok, Sock1}  = ?OPEN(Config),
2042    F  = fun(S, Fun) -> spawn_monitor(fun() -> Fun(S, Self) end) end,
2043    F1 = fun(Socket, Parent) when is_pid(Parent) ->
2044		 ?P("[client] create monitor"),
2045		 MRef = inet:monitor(Socket),
2046		 ?P("[client] sleep some"),
2047		 ?SLEEP(?SECS(1)),
2048		 ?P("[client] cancel (socket) monitor"),
2049		 inet:cancel_monitor(MRef),
2050		 ?P("[client] announce ready"),
2051		 Parent ! {self(), ready},
2052		 sm_await_no_socket_down(MRef, Socket, Type)
2053	 end,
2054    ?P("spawn client"),
2055    {Pid1, Mon1} = F(Sock1, F1),
2056    ?P("await client ready"),
2057    sm_await_client_ready(Pid1),
2058    ?P("close socket"),
2059    gen_udp:close(Sock1),
2060    ?P("await client termination"),
2061    sm_await_down(Pid1, Mon1, ok),
2062    ?P("done"),
2063    ok.
2064
2065
2066sm_await_no_socket_down(ExpMon, ExpSock, ExpType) ->
2067    sm_await_no_socket_down(ExpMon, ExpSock, ExpType, "client").
2068
2069sm_await_no_socket_down(ExpMon, ExpSock, ExpType, Name) ->
2070    receive
2071	{'DOWN', Mon, Type, Sock, Info} when (Type =:= ExpType) andalso
2072					     (Mon  =:= ExpMon)  andalso
2073					     (Sock =:= ExpSock) ->
2074	    ?P("[~s] received unexpected (socket) down message: "
2075	       "~n   Mon:  ~p"
2076	       "~n   Type: ~p"
2077	       "~n   Sock: ~p"
2078	       "~n   Info: ~p", [Name, Mon, Type, Sock, Info]),
2079	    exit({unexpected_down, Mon, Type, Sock, Info});
2080
2081	Any ->
2082	    ?P("[~s] received unexpected message: "
2083	       "~n   ~p", [Name, Any]),
2084	    exit({unexpected_message, Any})
2085
2086    after 1000 ->
2087	    ?P("[~s] expected message timeout", [Name]),
2088	    exit(ok)
2089    end.
2090
2091
2092%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2093
2094%% This is the most basic of tests.
2095%% Spawn a process that creates a socket, then spawns processes
2096%% that create monitors to it...
2097socket_monitor2(Config) when is_list(Config) ->
2098    ct:timetrap(?MINS(1)),
2099    ?TC_TRY(socket_monitor2,
2100            fun() -> do_socket_monitor2(Config) end).
2101
2102do_socket_monitor2(Config) ->
2103    ?P("begin"),
2104    Type         = ?SOCKET_TYPE(Config),
2105    Self         = self(),
2106    {OwnerPid, OwnerMon} =
2107	spawn_monitor(fun() ->
2108			      ?P("[owner] create (listen) socket"),
2109			      {ok, S} = ?OPEN(Config),
2110			      ?P("[owner] send socket to ctrl"),
2111			      Self ! {socket, S},
2112			      ?P("[owner] ready"),
2113			      receive
2114				  {Self, die} ->
2115				      exit(normal)
2116			      end
2117		      end),
2118    Sock1 = receive
2119                {socket, S} ->
2120                    ?P("received socket from owner"),
2121                    S;
2122                {'DOWN', OwnerMon, process, OwnerPid, OwnerReason} ->
2123                    ?P("received unexpected owner termination: "
2124                       "~n   ~p", [OwnerReason]),
2125                    ct:fail({unexpected_owner_termination, OwnerReason})
2126	     end,
2127    F  = fun(S, Fun) -> spawn_monitor(fun() -> Fun(S, Self) end) end,
2128    F1 = fun(Socket, Parent) when is_pid(Parent) ->
2129		 ?P("[client] create monitor"),
2130		 MRef = inet:monitor(Socket),
2131		 Parent ! {self(), ready},
2132		 sm_await_socket_down(MRef, Socket, Type)
2133	 end,
2134    ?P("spawn client"),
2135    {Pid1, Mon1} = F(Sock1, F1),
2136    ?P("spawn client"),
2137    sm_await_client_ready(Pid1),
2138    ?P("kill owner"),
2139    exit(OwnerPid, kill),
2140    ?P("await owner termination"),
2141    sm_await_down(OwnerPid, OwnerMon, killed),
2142    ?P("await client termination"),
2143    sm_await_down(Pid1, Mon1, ok),
2144    ?P("done"),
2145    ok.
2146
2147
2148%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2149
2150%% This is the most basic of tests.
2151%% Spawn a process that creates "many" socket(s), then spawns
2152%% a process that create monitors to them...
2153
2154socket_monitor2_manys(Config) when is_list(Config) ->
2155    ct:timetrap(?MINS(1)),
2156    ?TC_TRY(socket_monitor2_manys,
2157            fun() -> do_socket_monitor2_manys(Config) end).
2158
2159do_socket_monitor2_manys(Config) ->
2160    ?P("begin"),
2161    Type         = ?SOCKET_TYPE(Config),
2162    Self         = self(),
2163    ?P("spawn owner"),
2164    {OwnerPid, OwnerMon} =
2165	spawn_monitor(fun() ->
2166			      ?P("[owner] create (listen) socket(s)"),
2167			      {ok, S1} = ?OPEN(Config),
2168			      {ok, S2} = ?OPEN(Config),
2169			      {ok, S3} = ?OPEN(Config),
2170			      {ok, S4} = ?OPEN(Config),
2171			      {ok, S5} = ?OPEN(Config),
2172			      ?P("[owner] send (listen) socket(s) to ctrl"),
2173			      Self ! {socket, [S1, S2, S3, S4, S5]},
2174			      ?P("[owner] ready"),
2175			      receive
2176				  {Self, die} ->
2177				      exit(normal)
2178			      end
2179		      end),
2180    ?P("await sockets (from owner)"),
2181    Socks = receive
2182                {socket, Ss} ->
2183                    ?P("received socket(s) from owner"),
2184                    Ss;
2185                {'DOWN', OwnerMon, process, OwnerPid, OwnerReason} ->
2186                    ?P("received unexpected owner termination: "
2187                       "~n   ~p", [OwnerReason]),
2188                    ct:fail({unexpected_owner_termination, OwnerReason})
2189            end,
2190    F  = fun(S, Fun) -> spawn_monitor(fun() -> Fun(S, Self) end) end,
2191    F1 = fun(Sockets, Parent) when is_list(Sockets) andalso is_pid(Parent) ->
2192		 ?P("[client] create monitor(s)"),
2193		 Monitors = [{inet:monitor(Socket), Socket} ||
2194				Socket <- Sockets],
2195		 ?P("[client] announce ready"),
2196		 Parent ! {self(), ready},
2197		 sm_await_socket_down2(Monitors, Type)
2198	 end,
2199    ?P("spawn client"),
2200    {Pid1, Mon1} = F(Socks, F1),
2201    ?P("await client ready"),
2202    sm_await_client_ready(Pid1),
2203    ?P("kill owner"),
2204    exit(OwnerPid, kill),
2205    ?P("await owner (~p) termination", [OwnerPid]),
2206    sm_await_down(OwnerPid, OwnerMon, killed),
2207    ?P("await client termination"),
2208    sm_await_down(Pid1, Mon1, ok),
2209    ?P("done"),
2210    ok.
2211
2212
2213%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2214
2215%% This is the most basic of tests.
2216%% Spawn a process that creates a socket, then spawns (client)
2217%% processes that create monitors to it...
2218socket_monitor2_manyc(Config) when is_list(Config) ->
2219    ct:timetrap(?MINS(1)),
2220    ?TC_TRY(socket_monitor2_manyc,
2221            fun() -> do_socket_monitor2_manyc(Config) end).
2222
2223do_socket_monitor2_manyc(Config) ->
2224    ?P("begin"),
2225    Type         = ?SOCKET_TYPE(Config),
2226    Self         = self(),
2227    {OwnerPid, OwnerMon} =
2228	spawn_monitor(fun() ->
2229			      {ok, S} = ?OPEN(Config),
2230			      Self ! {socket, S},
2231			      receive
2232				  {Self, die} ->
2233				      exit(normal)
2234			      end
2235		      end),
2236    Sock1 = receive
2237		 {socket, S} ->
2238		     ?P("received socket from owner"),
2239		     S;
2240		 {'DOWN', OwnerMon, process, OwnerPid, OwnerReason} ->
2241		     ?P("received unexpected owner termination: "
2242			"~n   ~p", [OwnerReason]),
2243		     ct:fail({unexpected_owner_termination, OwnerReason})
2244	     end,
2245    F  = fun(S, Fun, Name) ->
2246		 spawn_monitor(fun() -> Fun(S, Name, Self) end)
2247	 end,
2248    F1 = fun(Socket, Name, Parent) when is_list(Name) andalso is_pid(Parent) ->
2249		 ?P("[~s] create monitor", [Name]),
2250		 MRef = inet:monitor(Socket),
2251		 Parent ! {self(), ready},
2252		 sm_await_socket_down(MRef, Socket, Type, Name)
2253	 end,
2254    ?P("spawn client(s)"),
2255    {Pid1, Mon1} = F(Sock1, F1, "client1"),
2256    {Pid2, Mon2} = F(Sock1, F1, "client2"),
2257    {Pid3, Mon3} = F(Sock1, F1, "client3"),
2258    {Pid4, Mon4} = F(Sock1, F1, "client4"),
2259    {Pid5, Mon5} = F(Sock1, F1, "client5"),
2260    ?P("await client(s) ready"),
2261    sm_await_client_ready(Pid1, "client1"),
2262    sm_await_client_ready(Pid2, "client2"),
2263    sm_await_client_ready(Pid3, "client3"),
2264    sm_await_client_ready(Pid4, "client4"),
2265    sm_await_client_ready(Pid5, "client5"),
2266    ?P("kill owner"),
2267    exit(OwnerPid, kill),
2268    ?P("await owner termination"),
2269    sm_await_down(OwnerPid, OwnerMon, killed),
2270    ?P("await client(s) termination"),
2271    sm_await_down(Pid1, Mon1, ok),
2272    sm_await_down(Pid2, Mon2, ok),
2273    sm_await_down(Pid3, Mon3, ok),
2274    sm_await_down(Pid4, Mon4, ok),
2275    sm_await_down(Pid5, Mon5, ok),
2276    ?P("done"),
2277    ok.
2278
2279
2280
2281%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2282
2283%% This is the most basic of tests.
2284%% Spawn a process that creates a socket, then spawns (client)
2285%% processes that create monitors to it...
2286otp_17492(Config) when is_list(Config) ->
2287    ct:timetrap(?MINS(1)),
2288    ?TC_TRY(otp_17492, fun() -> do_otp_17492(Config) end).
2289
2290do_otp_17492(Config) ->
2291    ?P("begin"),
2292
2293    Self = self(),
2294
2295    ?P("try create socket"),
2296    {ok, L} = ?OPEN(Config, 0, []),
2297
2298    ?P("try get (created) socket info"),
2299    try inet:info(L) of
2300	#{owner := Owner} = Info when is_pid(Owner) andalso (Owner =:= Self) ->
2301	    ?P("(created) socket info: ~p", [Info]);
2302	OBadInfo ->
2303	    ?P("(created) socket info: ~p", [OBadInfo]),
2304	    (catch gen_udp:close(L)),
2305	    ct:fail({invalid_created_info, OBadInfo})
2306    catch
2307	OC:OE:OS ->
2308	    ?P("Failed get (created) Listen socket info: "
2309	       "~n   Class: ~p"
2310	       "~n   Error: ~p"
2311	       "~n   Stack: ~p", [OC, OE, OS]),
2312	    (catch gen_udp:close(L)),
2313	    ct:fail({unexpected_created_info_result, {OC, OE, OS}})
2314    end,
2315
2316    ?P("try close socket"),
2317    ok = gen_udp:close(L),
2318
2319    ?P("try get (closed) socket info"),
2320    try inet:info(L) of
2321	#{states := [closed]} = CInfo when is_port(L) ->
2322	    ?P("(closed) socket info: "
2323	       "~n   ~p", [CInfo]);
2324	#{rstates := [closed], wstates := [closed]} = CInfo ->
2325	    ?P("(closed) socket info: "
2326	       "~n   ~p", [CInfo]);
2327	CBadInfo ->
2328	    ?P("(closed) socket info: ~p", [CBadInfo]),
2329	    ct:fail({invalid_closed_info, CBadInfo})
2330    catch
2331	CC:CE:CS ->
2332	    ?P("Failed get (closed) socket info: "
2333	       "~n   Class: ~p"
2334	       "~n   Error: ~p"
2335	       "~n   Stack: ~p", [CC, CE, CS]),
2336	    (catch gen_udp:close(L)),
2337	    ct:fail({unexpected_closed_info_result, {CC, CE, CS}})
2338    end,
2339
2340    ?P("done"),
2341    ok.
2342
2343
2344%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2345
2346ok({ok,V}) -> V;
2347ok(NotOk) ->
2348    try throw(not_ok)
2349    catch
2350	throw:not_ok:Stacktrace ->
2351	    raise_error({not_ok, NotOk}, tl(Stacktrace))
2352    end.
2353
2354raise_error(Reason, Stacktrace) ->
2355    erlang:raise(error, Reason, Stacktrace).
2356
2357local_filename(Tag) ->
2358    "/tmp/" ?MODULE_STRING "_" ++ os:getpid() ++ "_" ++ atom_to_list(Tag).
2359
2360bin_filename(String) ->
2361    unicode:characters_to_binary(String, file:native_name_encoding()).
2362
2363delete_local_filenames() ->
2364    _ =
2365	[file:delete(F) ||
2366	    F <-
2367		filelib:wildcard(
2368		  "/tmp/" ?MODULE_STRING "_" ++ os:getpid() ++ "_*")],
2369    ok.
2370
2371get_localaddr() ->
2372    get_localaddr(["localhost", "localhost6", "ip6-localhost"]).
2373
2374get_localaddr([]) ->
2375    {error, localaddr_not_found};
2376get_localaddr([Localhost|Ls]) ->
2377    case inet:getaddr(Localhost, inet6) of
2378       {ok, LocalAddr} ->
2379           ?P("found local address: ~s ~p", [Localhost, LocalAddr]),
2380           {ok, LocalAddr};
2381       _ ->
2382           get_localaddr(Ls)
2383    end.
2384
2385
2386%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2387
2388which_info(Sock) ->
2389    which_info([istate, active], inet:info(Sock), #{}).
2390
2391which_info([], _Info, Acc) ->
2392    Acc;
2393which_info([Key|Keys], Info, Acc) ->
2394    case maps:find(Key, Info) of
2395        {ok, Value} ->
2396            which_info(Keys, Info, Acc#{Key => Value});
2397        error ->
2398            which_info(Keys, Info, Acc)
2399    end.
2400
2401
2402pi(Item) ->
2403    {Item, Val} = process_info(self(), Item),
2404    Val.
2405
2406
2407%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2408
2409%%
2410%% Utils
2411%%
2412
2413start_node(Name) ->
2414    Pa = filename:dirname(code:which(?MODULE)),
2415    test_server:start_node(Name, slave, [{args, "-pa " ++ Pa}]).
2416
2417stop_node(Node) ->
2418    test_server:stop_node(Node).
2419
2420
2421%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2422
2423open_failed_str(Reason) ->
2424    ?F("Open failed: ~w", [Reason]).
2425