File 3051-socket_SUITE-do-not-fail-on-IPv6-only-nodes.patch of Package erlang

From 407f9f3af1e8292eca83c7289bc8bbd637901689 Mon Sep 17 00:00:00 2001
From: Maxim Fedorov <maximfca@gmail.com>
Date: Fri, 10 Dec 2021 22:35:10 -0800
Subject: [PATCH] socket_SUITE: do not fail on IPv6-only nodes

Before this change, socket_SUITE fails most of IPv4 tests
with IPv4 address available only on loopback adapter. With this
patch:
 - IPv4-specific tests will be skipped on IPv6-only nodes
 - non-specific tests will utilise either v4 or v6, depending
   on availability (with v4 preferred)
 - minor cleanup (removed unused suite/doc functions)
---
 lib/kernel/test/socket_SUITE.erl    | 2291 +++------------------------
 lib/kernel/test/socket_test_lib.erl |    9 +
 2 files changed, 191 insertions(+), 2109 deletions(-)

diff --git a/lib/kernel/test/socket_SUITE.erl b/lib/kernel/test/socket_SUITE.erl
index 83959c0153..7d8d31ab44 100644
--- a/lib/kernel/test/socket_SUITE.erl
+++ b/lib/kernel/test/socket_SUITE.erl
@@ -197,7 +197,7 @@
          api_opt_sock_sndtimeo_udp4/1,
          api_opt_sock_timestamp_udp4/1,
          api_opt_sock_timestamp_tcp4/1,
-         api_opt_ip_add_drop_membership/1,
+         api_opt_ip_add_drop_membership/0, api_opt_ip_add_drop_membership/1,
          api_opt_ip_pktinfo_udp4/1,
          api_opt_ip_recvopts_udp4/1,
          api_opt_ip_recvorigdstaddr_udp4/1,
@@ -477,10 +477,10 @@
 
          ttest_sgent_cgent_small_tcp4/1,
          ttest_sgent_cgent_small_tcp6/1,
-         ttest_sgent_cgent_medium_tcp4/1,
-         ttest_sgent_cgent_medium_tcp6/1,
-         ttest_sgent_cgent_large_tcp4/1,
-         ttest_sgent_cgent_large_tcp6/1,
+         ttest_sgent_cgent_medium_tcp4/0, ttest_sgent_cgent_medium_tcp4/1,
+         ttest_sgent_cgent_medium_tcp6/0, ttest_sgent_cgent_medium_tcp6/1,
+         ttest_sgent_cgent_large_tcp4/0, ttest_sgent_cgent_large_tcp4/1,
+         ttest_sgent_cgent_large_tcp6/0, ttest_sgent_cgent_large_tcp6/1,
 
          %% Server: transport = gen_tcp, active = true
          %% Client: transport = socket(tcp)
@@ -2211,10 +2211,6 @@ double_data(N, Data) ->
 %% that we can call the "global" info function and that it returns
 %% a non-empty map...
 
-api_m_info(suite) ->
-    [];
-api_m_info(doc) ->
-    [];
 api_m_info(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_m_info,
@@ -2244,10 +2240,6 @@ api_m_info() ->
 %% At the same time, it will test the info function (since it uses it
 %% for verification).
 
-api_m_debug(suite) ->
-    [];
-api_m_debug(doc) ->
-    [];
 api_m_debug(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_m_debug,
@@ -2412,10 +2404,6 @@ api_m_error_bind(Config) when is_list(Co
 
 %% Basically open (create) and info of an IPv4 UDP (dgram) socket.
 %% With some extra checks...
-api_b_open_and_info_udp4(suite) ->
-    [];
-api_b_open_and_info_udp4(doc) ->
-    [];
 api_b_open_and_info_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_info_udp4,
@@ -2432,10 +2420,6 @@ api_b_open_and_info_udp4(_Config) when i
 
 %% Basically open (create) and info of an IPv6 UDP (dgram) socket.
 %% With some extra checks...
-api_b_open_and_info_udp6(suite) ->
-    [];
-api_b_open_and_info_udp6(doc) ->
-    [];
 api_b_open_and_info_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_info_udp6,
@@ -2453,10 +2437,6 @@ api_b_open_and_info_udp6(_Config) when i
 
 %% Basically open (create) and info of an IPv4 TCP (stream) socket.
 %% With some extra checks...
-api_b_open_and_info_tcp4(suite) ->
-    [];
-api_b_open_and_info_tcp4(doc) ->
-    [];
 api_b_open_and_info_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_info_tcp4,
@@ -2473,10 +2453,6 @@ api_b_open_and_info_tcp4(_Config) when i
 
 %% Basically open (create) and info of an IPv6 TCP (stream) socket.
 %% With some extra checks...
-api_b_open_and_info_tcp6(suite) ->
-    [];
-api_b_open_and_info_tcp6(doc) ->
-    [];
 api_b_open_and_info_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_info_tcp6,
@@ -2554,10 +2530,6 @@ api_b_open_and_info(InitState) ->
 
 %% Basically open (create) and close an IPv4 UDP (dgram) socket.
 %% With some extra checks...
-api_b_open_and_close_udp4(suite) ->
-    [];
-api_b_open_and_close_udp4(doc) ->
-    [];
 api_b_open_and_close_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_close_udp4,
@@ -2573,10 +2545,6 @@ api_b_open_and_close_udp4(_Config) when
 
 %% Basically open (create) and close an IPv6 UDP (dgram) socket.
 %% With some extra checks...
-api_b_open_and_close_udp6(suite) ->
-    [];
-api_b_open_and_close_udp6(doc) ->
-    [];
 api_b_open_and_close_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_close_udp6,
@@ -2593,10 +2561,6 @@ api_b_open_and_close_udp6(_Config) when
 
 %% Basically open (create) and close an IPv4 TCP (stream) socket.
 %% With some extra checks...
-api_b_open_and_close_tcp4(suite) ->
-    [];
-api_b_open_and_close_tcp4(doc) ->
-    [];
 api_b_open_and_close_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_close_tcp4,
@@ -2612,10 +2576,6 @@ api_b_open_and_close_tcp4(_Config) when
 
 %% Basically open (create) and close an IPv6 TCP (stream) socket.
 %% With some extra checks...
-api_b_open_and_close_tcp6(suite) ->
-    [];
-api_b_open_and_close_tcp6(doc) ->
-    [];
 api_b_open_and_close_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_close_tcp6,
@@ -2632,10 +2592,6 @@ api_b_open_and_close_tcp6(_Config) when
 
 %% Basically open (create) and close an Unix Domain dgram (UDP) socket.
 %% With some extra checks...
-api_b_open_and_close_udpL(suite) ->
-    [];
-api_b_open_and_close_udpL(doc) ->
-    [];
 api_b_open_and_close_udpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_close_udpL,
@@ -2652,10 +2608,6 @@ api_b_open_and_close_udpL(_Config) when
 
 %% Basically open (create) and close an Unix Domain stream (TCP) socket.
 %% With some extra checks...
-api_b_open_and_close_tcpL(suite) ->
-    [];
-api_b_open_and_close_tcpL(doc) ->
-    [];
 api_b_open_and_close_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_close_tcpL,
@@ -2672,10 +2624,6 @@ api_b_open_and_close_tcpL(_Config) when
 
 %% Basically open (create) and close an Unix Domain dgram (UDP) socket.
 %% With some extra checks...
-api_b_open_and_close_seqpL(suite) ->
-    [];
-api_b_open_and_close_seqpL(doc) ->
-    [];
 api_b_open_and_close_seqpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -2692,10 +2640,6 @@ api_b_open_and_close_seqpL(_Config) when
 
 %% Basically open (create) and close an IPv4 SCTP (seqpacket) socket.
 %% With some extra checks...
-api_b_open_and_close_sctp4(suite) ->
-    [];
-api_b_open_and_close_sctp4(doc) ->
-    [];
 api_b_open_and_close_sctp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_close_sctp4,
@@ -2847,10 +2791,6 @@ api_b_open_and_close(InitState) ->
 
 %% Basically open (create) and (maybe) close an RAW socket.
 
-api_b_open_and_maybe_close_raw(suite) ->
-    [];
-api_b_open_and_maybe_close_raw(doc) ->
-    [];
 api_b_open_and_maybe_close_raw(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_open_and_maybe_close_raw,
@@ -2913,13 +2853,10 @@ do_api_b_open_and_maybe_close_raw(InitSt
 
 %% Basically send and receive on an IPv4 UDP (dgram) socket using
 %% sendto and recvfrom..
-api_b_sendto_and_recvfrom_udp4(suite) ->
-    [];
-api_b_sendto_and_recvfrom_udp4(doc) ->
-    [];
 api_b_sendto_and_recvfrom_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_sendto_and_recvfrom_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Send = fun(Sock, Data, Dest) ->
                                   socket:sendto(Sock, Data, Dest)
@@ -2939,10 +2876,6 @@ api_b_sendto_and_recvfrom_udp4(_Config)
 
 %% Basically send and receive on an IPv4 UDP (dgram) socket using
 %% sendto and recvfrom.
-api_b_sendto_and_recvfrom_udpL(suite) ->
-    [];
-api_b_sendto_and_recvfrom_udpL(doc) ->
-    [];
 api_b_sendto_and_recvfrom_udpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_sendto_and_recvfrom_udpL,
@@ -2969,13 +2902,10 @@ api_b_sendto_and_recvfrom_udpL(_Config)
 
 %% Basically send and receive on an IPv4 UDP (dgram) socket
 %% using sendmsg and recvmsg.
-api_b_sendmsg_and_recvmsg_udp4(suite) ->
-    [];
-api_b_sendmsg_and_recvmsg_udp4(doc) ->
-    [];
 api_b_sendmsg_and_recvmsg_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_sendmsg_and_recvmsg_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Send = fun(Sock, Data, Dest) ->
                                   %% We need tests for this,
@@ -3013,10 +2943,6 @@ api_b_sendmsg_and_recvmsg_udp4(_Config)
 
 %% Basically send and receive on an IPv4 UDP (dgram) socket
 %% using sendmsg and recvmsg.
-api_b_sendmsg_and_recvmsg_udpL(suite) ->
-    [];
-api_b_sendmsg_and_recvmsg_udpL(doc) ->
-    [];
 api_b_sendmsg_and_recvmsg_udpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_sendmsg_and_recvmsg_udpL,
@@ -3201,13 +3127,10 @@ api_b_send_and_recv_udp(InitState) ->
 
 %% Basically send and receive using the "common" functions (send and recv)
 %% on an IPv4 TCP (stream) socket.
-api_b_send_and_recv_tcp4(suite) ->
-    [];
-api_b_send_and_recv_tcp4(doc) ->
-    [];
 api_b_send_and_recv_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_b_send_and_recv_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Send = fun(Sock, Data) ->
                                   socket:send(Sock, Data)
@@ -3228,10 +3151,6 @@ api_b_send_and_recv_tcp4(_Config) when i
 
 %% Basically send and receive using the "common" functions (send and recv)
 %% on an Unix Domain (stream) socket (TCP).
-api_b_send_and_recv_tcpL(suite) ->
-    [];
-api_b_send_and_recv_tcpL(doc) ->
-    [];
 api_b_send_and_recv_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_b_send_and_recv_tcpL,
@@ -3256,10 +3175,6 @@ api_b_send_and_recv_tcpL(_Config) when i
 
 %% Basically send and receive using the "common" functions (send and recv)
 %% on an Unix Domain seqpacket socket.
-api_b_send_and_recv_seqpL(suite) ->
-    [];
-api_b_send_and_recv_seqpL(doc) ->
-    [];
 api_b_send_and_recv_seqpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(?FUNCTION_NAME,
@@ -3284,13 +3199,10 @@ api_b_send_and_recv_seqpL(_Config) when
 
 %% Basically send and receive using the msg functions (sendmsg and recvmsg)
 %% on an IPv4 TCP (stream) socket.
-api_b_sendmsg_and_recvmsg_tcp4(suite) ->
-    [];
-api_b_sendmsg_and_recvmsg_tcp4(doc) ->
-    [];
 api_b_sendmsg_and_recvmsg_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_b_sendmsg_and_recvmsg_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Send = fun(Sock, Data) ->
                                   Msg = #{iov => [Data]},
@@ -3321,10 +3233,6 @@ api_b_sendmsg_and_recvmsg_tcp4(_Config)
 
 %% Basically send and receive using the msg functions (sendmsg and recvmsg)
 %% on an Unix Domain (stream) socket (TCP).
-api_b_sendmsg_and_recvmsg_tcpL(suite) ->
-    [];
-api_b_sendmsg_and_recvmsg_tcpL(doc) ->
-    [];
 api_b_sendmsg_and_recvmsg_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_b_sendmsg_and_recvmsg_tcpL,
@@ -3374,10 +3282,6 @@ api_b_sendmsg_and_recvmsg_tcpL(_Config)
 
 %% Basically send and receive using the msg functions (sendmsg and recvmsg)
 %% on an Unix Domain (stream) socket (TCP).
-api_b_sendmsg_and_recvmsg_seqpL(suite) ->
-    [];
-api_b_sendmsg_and_recvmsg_seqpL(doc) ->
-    [];
 api_b_sendmsg_and_recvmsg_seqpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(?FUNCTION_NAME,
@@ -3842,10 +3746,6 @@ api_b_send_and_recv_conn(InitState) ->
 
 %% Basically send and receive on an IPv4 SCTP (seqpacket) socket
 %% using sendmsg and recvmsg.
-api_b_sendmsg_and_recvmsg_sctp4(suite) ->
-    [];
-api_b_sendmsg_and_recvmsg_sctp4(doc) ->
-    [];
 api_b_sendmsg_and_recvmsg_sctp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_b_sendmsg_and_recvmsg_sctp4,
@@ -4384,6 +4284,7 @@ api_b_send_and_recv_sctp(_InitState) ->
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 api_b_sendmsg_iov_dgram_inet(Config) when is_list(Config) ->
+    has_support_ipv4(),
     api_b_sendmsg_iov_dgram(inet).
 %%
 api_b_sendmsg_iov_dgram_inet6(Config) when is_list(Config) ->
@@ -4395,6 +4296,7 @@ api_b_sendmsg_iov_dgram_local(Config) wh
     api_b_sendmsg_iov_dgram(local).
 
 api_b_sendmsg_iov_stream_inet(Config) when is_list(Config) ->
+    has_support_ipv4(),
     api_b_sendmsg_iov_stream(inet).
 %%
 api_b_sendmsg_iov_stream_inet6(Config) when is_list(Config) ->
@@ -4489,6 +4391,7 @@ api_b_sendmsg_iov_stream(Domain) ->
 
 api_sendfile_inet(Config) when is_list(Config) ->
     has_support_sendfile(),
+    has_support_ipv4(),
     api_sendfile(inet, Config, fun socket:sendfile/2).
 
 api_sendfile_inet6(Config) when is_list(Config) ->
@@ -4505,6 +4408,7 @@ api_sendfile_local(Config) when is_list(
 
 api_sendfile_loop_inet(Config) when is_list(Config) ->
     has_support_sendfile(),
+    has_support_ipv4(),
     api_sendfile(inet, Config, fun sendfile_loop/2).
 
 api_sendfile_loop_inet6(Config) when is_list(Config) ->
@@ -4650,13 +4554,10 @@ api_sendfile_verify_block(S, Data, M, Bl
 %% With some extra checks...
 %% IPv4
 %% Without dup
-api_ffd_open_wod_and_info_udp4(suite) ->
-    [];
-api_ffd_open_wod_and_info_udp4(doc) ->
-    [];
 api_ffd_open_wod_and_info_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_wod_and_info_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain   => inet,
                                  type     => dgram,
@@ -4673,10 +4574,6 @@ api_ffd_open_wod_and_info_udp4(_Config)
 %% With some extra checks...
 %% IPv6
 %% Without dup
-api_ffd_open_wod_and_info_udp6(suite) ->
-    [];
-api_ffd_open_wod_and_info_udp6(doc) ->
-    [];
 api_ffd_open_wod_and_info_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_wod_and_info_udp6,
@@ -4697,13 +4594,10 @@ api_ffd_open_wod_and_info_udp6(_Config)
 %% With some extra checks...
 %% IPv4
 %% With dup
-api_ffd_open_wd_and_info_udp4(suite) ->
-    [];
-api_ffd_open_wd_and_info_udp4(doc) ->
-    [];
 api_ffd_open_wd_and_info_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_wd_open_and_info_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain   => inet,
                                  type     => dgram,
@@ -4720,10 +4614,6 @@ api_ffd_open_wd_and_info_udp4(_Config) w
 %% With some extra checks...
 %% IPv6
 %% With dup
-api_ffd_open_wd_and_info_udp6(suite) ->
-    [];
-api_ffd_open_wd_and_info_udp6(doc) ->
-    [];
 api_ffd_open_wd_and_info_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_wd_open_and_info_udp6,
@@ -4744,13 +4634,10 @@ api_ffd_open_wd_and_info_udp6(_Config) w
 %% With some extra checks...
 %% IPv6
 %% Without dup
-api_ffd_open_wod_and_info_tcp4(suite) ->
-    [];
-api_ffd_open_wod_and_info_tcp4(doc) ->
-    [];
 api_ffd_open_wod_and_info_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_wod_and_info_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain   => inet,
                                  type     => stream,
@@ -4767,10 +4654,6 @@ api_ffd_open_wod_and_info_tcp4(_Config)
 %% With some extra checks...
 %% IPv6
 %% Without dup
-api_ffd_open_wod_and_info_tcp6(suite) ->
-    [];
-api_ffd_open_wod_and_info_tcp6(doc) ->
-    [];
 api_ffd_open_wod_and_info_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_wod_and_info_tcp6,
@@ -4791,13 +4674,10 @@ api_ffd_open_wod_and_info_tcp6(_Config)
 %% With some extra checks...
 %% IPv6
 %% With dup
-api_ffd_open_wd_and_info_tcp4(suite) ->
-    [];
-api_ffd_open_wd_and_info_tcp4(doc) ->
-    [];
 api_ffd_open_wd_and_info_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_wd_and_info_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain   => inet,
                                  type     => stream,
@@ -4814,10 +4694,6 @@ api_ffd_open_wd_and_info_tcp4(_Config) w
 %% With some extra checks...
 %% IPv6
 %% With dup
-api_ffd_open_wd_and_info_tcp6(suite) ->
-    [];
-api_ffd_open_wd_and_info_tcp6(doc) ->
-    [];
 api_ffd_open_wd_and_info_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_wd_and_info_tcp6,
@@ -5039,13 +4915,10 @@ api_ffd_open_and_info(InitState) ->
 %%
 %% </WARNING>
 %%
-api_ffd_open_and_open_wod_and_send_udp4(suite) ->
-    [];
-api_ffd_open_and_open_wod_and_send_udp4(doc) ->
-    [];
 api_ffd_open_and_open_wod_and_send_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_and_open_wod_and_send_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain   => inet,
                                  type     => dgram,
@@ -5074,10 +4947,6 @@ api_ffd_open_and_open_wod_and_send_udp4(
 %%
 %% </WARNING>
 %%
-api_ffd_open_and_open_wod_and_send_udp6(suite) ->
-    [];
-api_ffd_open_and_open_wod_and_send_udp6(doc) ->
-    [];
 api_ffd_open_and_open_wod_and_send_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_and_open_wod_and_send_udp6,
@@ -5101,13 +4970,10 @@ api_ffd_open_and_open_wod_and_send_udp6(
 %% has not been closed (test by sending some data).
 %% IPv4 UDP (dgram) socket.
 %%
-api_ffd_open_and_open_wd_and_send_udp4(suite) ->
-    [];
-api_ffd_open_and_open_wd_and_send_udp4(doc) ->
-    [];
 api_ffd_open_and_open_wd_and_send_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_and_open_wd_and_send_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain   => inet,
                                  type     => dgram,
@@ -5127,10 +4993,6 @@ api_ffd_open_and_open_wd_and_send_udp4(_
 %% has not been closed (test by sending some data).
 %% IPv6 UDP (dgram) socket.
 %%
-api_ffd_open_and_open_wd_and_send_udp6(suite) ->
-    [];
-api_ffd_open_and_open_wd_and_send_udp6(doc) ->
-    [];
 api_ffd_open_and_open_wd_and_send_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_and_open_wd_and_send_udp6,
@@ -5762,10 +5624,6 @@ api_ffd_open_and_open_and_send_udp2(Init
 %%
 %% </WARNING>
 %%
-api_ffd_open_connect_and_open_wod_and_send_tcp4(suite) ->
-    [];
-api_ffd_open_connect_and_open_wod_and_send_tcp4(doc) ->
-    [];
 api_ffd_open_connect_and_open_wod_and_send_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_connect_and_open_wod_and_send_tcp4,
@@ -5797,10 +5655,6 @@ api_ffd_open_connect_and_open_wod_and_se
 %%
 %% </WARNING>
 %%
-api_ffd_open_connect_and_open_wod_and_send_tcp6(suite) ->
-    [];
-api_ffd_open_connect_and_open_wod_and_send_tcp6(doc) ->
-    [];
 api_ffd_open_connect_and_open_wod_and_send_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_connect_and_open_wod_and_send_tcp6,
@@ -5823,10 +5677,6 @@ api_ffd_open_connect_and_open_wod_and_se
 %% Finally close the second socket. Ensure that the original socket
 %% has not been closed (test by sending some data).
 %% IPv4 TCP (stream) socket.
-api_ffd_open_connect_and_open_wd_and_send_tcp4(suite) ->
-    [];
-api_ffd_open_connect_and_open_wd_and_send_tcp4(doc) ->
-    [];
 api_ffd_open_connect_and_open_wd_and_send_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_connect_and_open_wd_and_send_tcp4,
@@ -5849,10 +5699,6 @@ api_ffd_open_connect_and_open_wd_and_sen
 %% Finally close the second socket. Ensure that the original socket
 %% has not been closed (test by sending some data).
 %% IPv6 TCP (stream) socket.
-api_ffd_open_connect_and_open_wd_and_send_tcp6(suite) ->
-    [];
-api_ffd_open_connect_and_open_wd_and_send_tcp6(doc) ->
-    [];
 api_ffd_open_connect_and_open_wd_and_send_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_ffd_open_connect_and_open_wd_and_send_tcp6,
@@ -6524,14 +6370,10 @@ api_ffd_open_connect_and_open_and_send_t
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 %% Basically establish a TCP connection via an async connect. IPv4.
-
-api_a_connect_tcp4(suite) ->
-    [];
-api_a_connect_tcp4(doc) ->
-    [];
 api_a_connect_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     tc_try(api_a_connect_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ok = api_a_connect_tcpD(inet, nowait(Config))
            end).
@@ -6540,11 +6382,6 @@ api_a_connect_tcp4(Config) when is_list(
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 %% Basically establish a TCP connection via an async connect. IPv6.
-
-api_a_connect_tcp6(suite) ->
-    [];
-api_a_connect_tcp6(doc) ->
-    [];
 api_a_connect_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     tc_try(api_a_connect_tcp6,
@@ -7061,14 +6898,11 @@ api_a_connect_tcp(InitState) ->
 %% select message). Note that we only do this for the recvfrom,
 %% since its much more difficult to "arrange" for sendto.
 %%
-api_a_sendto_and_recvfrom_udp4(suite) ->
-    [];
-api_a_sendto_and_recvfrom_udp4(doc) ->
-    [];
 api_a_sendto_and_recvfrom_udp4(Config) when is_list(Config) ->
     ?TT(?SECS(5)),
     Nowait = nowait(Config),
     tc_try(api_a_sendto_and_recvfrom_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Send = fun(Sock, Data, Dest) ->
                                   socket:sendto(Sock, Data, Dest)
@@ -7093,10 +6927,6 @@ api_a_sendto_and_recvfrom_udp4(Config) w
 %% select message). Note that we only do this for the recvfrom,
 %% since its much more difficult to "arrange" for sendto.
 %%
-api_a_sendto_and_recvfrom_udp6(suite) ->
-    [];
-api_a_sendto_and_recvfrom_udp6(doc) ->
-    [];
 api_a_sendto_and_recvfrom_udp6(Config) when is_list(Config) ->
     ?TT(?SECS(5)),
     Nowait = nowait(Config),
@@ -7126,14 +6956,11 @@ api_a_sendto_and_recvfrom_udp6(Config) w
 %% select message). Note that we only do this for the recvmsg,
 %% since its much more difficult to "arrange" for sendmsg.
 %%
-api_a_sendmsg_and_recvmsg_udp4(suite) ->
-    [];
-api_a_sendmsg_and_recvmsg_udp4(doc) ->
-    [];
 api_a_sendmsg_and_recvmsg_udp4(Config) when is_list(Config) ->
     ?TT(?SECS(5)),
     Nowait = nowait(Config),
     tc_try(api_a_sendmsg_and_recvmsg_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Send = fun(Sock, Data, Dest) ->
                                   Msg = #{addr => Dest,
@@ -7171,10 +6998,6 @@ api_a_sendmsg_and_recvmsg_udp4(Config) w
 %% select message). Note that we only do this for the recvmsg,
 %% since its much more difficult to "arrange" for sendmsg.
 %%
-api_a_sendmsg_and_recvmsg_udp6(suite) ->
-    [];
-api_a_sendmsg_and_recvmsg_udp6(doc) ->
-    [];
 api_a_sendmsg_and_recvmsg_udp6(Config) when is_list(Config) ->
     ?TT(?SECS(5)),
     Nowait = nowait(Config),
@@ -7652,14 +7475,11 @@ api_a_send_and_recv_udp(InitState) ->
 %% select message). Note that we only do this for the recv,
 %% since its much more difficult to "arrange" for send.
 %% We *also* test async for accept.
-api_a_send_and_recv_tcp4(suite) ->
-    [];
-api_a_send_and_recv_tcp4(doc) ->
-    [];
 api_a_send_and_recv_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
     tc_try(api_a_send_and_recv_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Send = fun(Sock, Data) ->
                                   socket:send(Sock, Data)
@@ -7684,10 +7504,6 @@ api_a_send_and_recv_tcp4(Config) when is
 %% select message). Note that we only do this for the recv,
 %% since its much more difficult to "arrange" for send.
 %% We *also* test async for accept.
-api_a_send_and_recv_tcp6(suite) ->
-    [];
-api_a_send_and_recv_tcp6(doc) ->
-    [];
 api_a_send_and_recv_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
@@ -7717,14 +7533,11 @@ api_a_send_and_recv_tcp6(Config) when is
 %% select message). Note that we only do this for the recvmsg,
 %% since its much more difficult to "arrange" for sendmsg.
 %% We *also* test async for accept.
-api_a_sendmsg_and_recvmsg_tcp4(suite) ->
-    [];
-api_a_sendmsg_and_recvmsg_tcp4(doc) ->
-    [];
 api_a_sendmsg_and_recvmsg_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
     tc_try(api_a_sendmsg_and_recvmsg_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Send = fun(Sock, Data) ->
                                   Msg = #{iov => [Data]},
@@ -7757,10 +7570,6 @@ api_a_sendmsg_and_recvmsg_tcp4(Config) w
 %% select message). Note that we only do this for the recvmsg,
 %% since its much more difficult to "arrange" for sendmsg.
 %% We *also* test async for accept.
-api_a_sendmsg_and_recvmsg_tcp6(suite) ->
-    [];
-api_a_sendmsg_and_recvmsg_tcp6(doc) ->
-    [];
 api_a_sendmsg_and_recvmsg_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
@@ -8320,14 +8129,11 @@ api_a_send_and_recv_tcp(Config, InitStat
 %% Basically we make an async (Timeout = nowait) call to recvfrom,
 %% wait some time and then cancel. IPv4
 %%
-api_a_recvfrom_cancel_udp4(suite) ->
-    [];
-api_a_recvfrom_cancel_udp4(doc) ->
-    [];
 api_a_recvfrom_cancel_udp4(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
     tc_try(api_a_recvfrom_cancel_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock) ->
                                   case socket:recvfrom(Sock, 0, Nowait) of
@@ -8352,10 +8158,6 @@ api_a_recvfrom_cancel_udp4(Config) when
 %% Basically we make an async (Timeout = nowait) call to recvfrom,
 %% wait some time and then cancel. IPv6
 %%
-api_a_recvfrom_cancel_udp6(suite) ->
-    [];
-api_a_recvfrom_cancel_udp6(doc) ->
-    [];
 api_a_recvfrom_cancel_udp6(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
@@ -8385,14 +8187,11 @@ api_a_recvfrom_cancel_udp6(Config) when
 %% Basically we make an async (Timeout = nowait) call to recvmsg,
 %% wait some time and then cancel. IPv4
 %%
-api_a_recvmsg_cancel_udp4(suite) ->
-    [];
-api_a_recvmsg_cancel_udp4(doc) ->
-    [];
 api_a_recvmsg_cancel_udp4(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
     tc_try(api_a_recvmsg_cancel_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock) ->
                                   case socket:recvmsg(Sock, Nowait) of
@@ -8417,10 +8216,6 @@ api_a_recvmsg_cancel_udp4(Config) when i
 %% Basically we make an async (Timeout = nowait) call to recvmsg,
 %% wait some time and then cancel. IPv6
 %%
-api_a_recvmsg_cancel_udp6(suite) ->
-    [];
-api_a_recvmsg_cancel_udp6(doc) ->
-    [];
 api_a_recvmsg_cancel_udp6(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
@@ -8661,14 +8456,11 @@ api_a_recv_cancel_udp(InitState) ->
 %% Basically we make an async (Timeout = nowait) call to accept,
 %% wait some time and then cancel. IPv4
 %%
-api_a_accept_cancel_tcp4(suite) ->
-    [];
-api_a_accept_cancel_tcp4(doc) ->
-    [];
 api_a_accept_cancel_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
     tc_try(api_a_accept_cancel_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Accept = fun(Sock) ->
                                     case socket:accept(Sock, Nowait) of
@@ -8694,10 +8486,6 @@ api_a_accept_cancel_tcp4(Config) when is
 %% Basically we make an async (Timeout = nowait) call to accept,
 %% wait some time and then cancel. IPv6
 %%
-api_a_accept_cancel_tcp6(suite) ->
-    [];
-api_a_accept_cancel_tcp6(doc) ->
-    [];
 api_a_accept_cancel_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
@@ -8941,14 +8729,11 @@ api_a_accept_cancel_tcp(InitState) ->
 %% Basically we make an async (Timeout = nowait) call to recv,
 %% wait some time and then cancel. IPv4
 %%
-api_a_recv_cancel_tcp4(suite) ->
-    [];
-api_a_recv_cancel_tcp4(doc) ->
-    [];
 api_a_recv_cancel_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
     tc_try(api_a_recv_cancel_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock) ->
                                   socket:recv(Sock, 0, Nowait)
@@ -8966,10 +8751,6 @@ api_a_recv_cancel_tcp4(Config) when is_l
 %% Basically we make an async (Timeout = nowait) call to recv,
 %% wait some time and then cancel. IPv6
 %%
-api_a_recv_cancel_tcp6(suite) ->
-    [];
-api_a_recv_cancel_tcp6(doc) ->
-    [];
 api_a_recv_cancel_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
@@ -8992,14 +8773,11 @@ api_a_recv_cancel_tcp6(Config) when is_l
 %% Basically we make an async (Timeout = nowait) call to recvmsg,
 %% wait some time and then cancel. IPv4
 %%
-api_a_recvmsg_cancel_tcp4(suite) ->
-    [];
-api_a_recvmsg_cancel_tcp4(doc) ->
-    [];
 api_a_recvmsg_cancel_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
     tc_try(api_a_recvmsg_cancel_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock) ->
                                   socket:recvmsg(Sock, Nowait)
@@ -9017,10 +8795,6 @@ api_a_recvmsg_cancel_tcp4(Config) when i
 %% Basically we make an async (Timeout = nowait) call to recvmsg,
 %% wait some time and then cancel. IPv6
 %%
-api_a_recvmsg_cancel_tcp6(suite) ->
-    [];
-api_a_recvmsg_cancel_tcp6(doc) ->
-    [];
 api_a_recvmsg_cancel_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(10)),
     Nowait = nowait(Config),
@@ -9407,14 +9181,11 @@ api_a_recv_cancel_tcp(InitState) ->
 %% (from *several* processes), wait some time and then cancel.
 %% This should result in abort messages to the 'other' processes. IPv4
 %%
-api_a_mrecvfrom_cancel_udp4(suite) ->
-    [];
-api_a_mrecvfrom_cancel_udp4(doc) ->
-    [];
 api_a_mrecvfrom_cancel_udp4(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
     tc_try(api_a_mrecvfrom_cancel_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock) ->
                                   case socket:recvfrom(Sock, 0, Nowait) of
@@ -9440,10 +9211,6 @@ api_a_mrecvfrom_cancel_udp4(Config) when
 %% (from *several* processes), wait some time and then cancel.
 %% This should result in abort messages to the 'other' processes. IPv6
 %%
-api_a_mrecvfrom_cancel_udp6(suite) ->
-    [];
-api_a_mrecvfrom_cancel_udp6(doc) ->
-    [];
 api_a_mrecvfrom_cancel_udp6(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
@@ -9474,14 +9241,11 @@ api_a_mrecvfrom_cancel_udp6(Config) when
 %% (from *several* processes), wait some time and then cancel.
 %% This should result in abort messages to the 'other' processes. IPv4
 %%
-api_a_mrecvmsg_cancel_udp4(suite) ->
-    [];
-api_a_mrecvmsg_cancel_udp4(doc) ->
-    [];
 api_a_mrecvmsg_cancel_udp4(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
     tc_try(api_a_mrecvmsg_cancel_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock) ->
                                   case socket:recvmsg(Sock, Nowait) of
@@ -9507,10 +9271,6 @@ api_a_mrecvmsg_cancel_udp4(Config) when
 %% (from *several* processes), wait some time and then cancel.
 %% This should result in abort messages to the 'other' processes. IPv6
 %%
-api_a_mrecvmsg_cancel_udp6(suite) ->
-    [];
-api_a_mrecvmsg_cancel_udp6(doc) ->
-    [];
 api_a_mrecvmsg_cancel_udp6(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
@@ -9928,14 +9688,11 @@ api_a_mrecv_cancel_udp(InitState) ->
 %% (from *several* processes), wait some time and then cancel,
 %% This should result in abort messages to the 'other' processes. IPv4
 %%
-api_a_maccept_cancel_tcp4(suite) ->
-    [];
-api_a_maccept_cancel_tcp4(doc) ->
-    [];
 api_a_maccept_cancel_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
     tc_try(api_a_maccept_cancel_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Accept = fun(Sock) ->
                                     case socket:accept(Sock, Nowait) of
@@ -9962,10 +9719,6 @@ api_a_maccept_cancel_tcp4(Config) when i
 %% (from *several* processes), wait some time and then cancel,
 %% This should result in abort messages to the 'other' processes. IPv6
 %%
-api_a_maccept_cancel_tcp6(suite) ->
-    [];
-api_a_maccept_cancel_tcp6(doc) ->
-    [];
 api_a_maccept_cancel_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
@@ -10387,14 +10140,11 @@ api_a_maccept_cancel_tcp(InitState) ->
 %% (from *several* processes), wait some time and then cancel,
 %% This should result in abort messages to the 'other' processes. IPv4
 %%
-api_a_mrecv_cancel_tcp4(suite) ->
-    [];
-api_a_mrecv_cancel_tcp4(doc) ->
-    [];
 api_a_mrecv_cancel_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
     tc_try(api_a_mrecv_cancel_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock) ->
                                   socket:recv(Sock, 0, Nowait)
@@ -10413,10 +10163,6 @@ api_a_mrecv_cancel_tcp4(Config) when is_
 %% (from *several* processes), wait some time and then cancel,
 %% This should result in abort messages to the 'other' processes. IPv6
 %%
-api_a_mrecv_cancel_tcp6(suite) ->
-    [];
-api_a_mrecv_cancel_tcp6(doc) ->
-    [];
 api_a_mrecv_cancel_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
@@ -10440,14 +10186,11 @@ api_a_mrecv_cancel_tcp6(Config) when is_
 %% (from *several* processes), wait some time and then cancel,
 %% This should result in abort messages to the 'other' processes. IPv4
 %%
-api_a_mrecvmsg_cancel_tcp4(suite) ->
-    [];
-api_a_mrecvmsg_cancel_tcp4(doc) ->
-    [];
 api_a_mrecvmsg_cancel_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
     tc_try(api_a_mrecvmsg_cancel_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock) ->
                                   socket:recvmsg(Sock, Nowait)
@@ -10466,10 +10209,6 @@ api_a_mrecvmsg_cancel_tcp4(Config) when
 %% (from *several* processes), wait some time and then cancel,
 %% This should result in abort messages to the 'other' processes. IPv6
 %%
-api_a_mrecvmsg_cancel_tcp6(suite) ->
-    [];
-api_a_mrecvmsg_cancel_tcp6(doc) ->
-    [];
 api_a_mrecvmsg_cancel_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(20)),
     Nowait = nowait(Config),
@@ -11037,10 +10776,6 @@ api_a_mrecv_cancel_tcp(InitState) ->
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 %% Perform some simple getopt and setopt with the level = otp options
-api_opt_simple_otp_options(suite) ->
-    [];
-api_opt_simple_otp_options(doc) ->
-    [];
 api_opt_simple_otp_options(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_simple_otp_options,
@@ -11324,10 +11059,6 @@ api_opt_simple_otp_options() ->
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 %% Perform some simple getopt and setopt otp meta option
-api_opt_simple_otp_meta_option(suite) ->
-    [];
-api_opt_simple_otp_meta_option(doc) ->
-    [];
 api_opt_simple_otp_meta_option(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_simple_otp_meta_option,
@@ -11504,10 +11235,6 @@ api_opt_simple_otp_meta_option() ->
 %% Perform some simple operations with the rcvbuf otp option
 %% The operations we test here are only for type = stream and
 %% protocol = tcp.
-api_opt_simple_otp_rcvbuf_option(suite) ->
-    [];
-api_opt_simple_otp_rcvbuf_option(doc) ->
-    [];
 api_opt_simple_otp_rcvbuf_option(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(api_opt_simple_otp_rcvbuf_option,
@@ -12150,7 +11877,7 @@ api_opt_simple_otp_rcvbuf_option() ->
 
     %% Create a data binary of 6*1024 bytes
     Data      = list_to_binary(lists:duplicate(6*4, lists:seq(0, 255))),
-    InitState = #{domain => inet,
+    InitState = #{domain => inet_or_inet6(),
                   data   => Data},
 
     i("create server evaluator"),
@@ -12175,10 +11902,6 @@ api_opt_simple_otp_rcvbuf_option() ->
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
 %% Perform some simple getopt and setopt with the level = otp options
-api_opt_simple_otp_controlling_process(suite) ->
-    [];
-api_opt_simple_otp_controlling_process(doc) ->
-    [];
 api_opt_simple_otp_controlling_process(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(api_opt_simple_otp_controlling_process,
@@ -12399,7 +12122,7 @@ api_opt_simple_otp_controlling_process()
     Client1 = ?SEV_START("tcp-client", ClientSeq, ClientInitState1),
 
     i("start tcp (stream) tester evaluator"),
-    TesterInitState1 = #{domain   => inet, 
+    TesterInitState1 = #{domain   => inet,
                          type     => stream, 
                          protocol => tcp,
                          client   => Client1#ev.pid},
@@ -12413,7 +12136,7 @@ api_opt_simple_otp_controlling_process()
     Client2 = ?SEV_START("udp-client", ClientSeq, ClientInitState2),
 
     i("start udp (dgram) tester evaluator"),
-    TesterInitState2 = #{domain   => inet, 
+    TesterInitState2 = #{domain   => inet,
                          type     => dgram, 
                          protocol => udp,
                          client   => Client2#ev.pid},
@@ -12429,10 +12152,6 @@ api_opt_simple_otp_controlling_process()
 %% Tests the socket option acceptconn for UDP.
 %% This should be possible to get but not set.
 
-api_opt_sock_acceptconn_udp(suite) ->
-    [];
-api_opt_sock_acceptconn_udp(doc) ->
-    [];
 api_opt_sock_acceptconn_udp(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(api_opt_sock_acceptconn_udp,
@@ -12561,7 +12280,7 @@ api_opt_sock_acceptconn_udp() ->
          ?SEV_FINISH_NORMAL
         ],
 
-    Domain = inet,
+    Domain = inet_or_inet6(),
 
     i("start tester evaluator"),
     InitState = #{domain  => Domain},
@@ -12577,10 +12296,6 @@ api_opt_sock_acceptconn_udp() ->
 %% Tests the socket option acceptconn for TCP.
 %% This should be possible to get but not set.
 
-api_opt_sock_acceptconn_tcp(suite) ->
-    [];
-api_opt_sock_acceptconn_tcp(doc) ->
-    [];
 api_opt_sock_acceptconn_tcp(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(api_opt_sock_acceptconn_tcp,
@@ -12917,7 +12632,7 @@ api_opt_sock_acceptconn_tcp() ->
         ],
 
 
-    Domain = inet,
+    Domain = inet_or_inet6(),
 
     i("start tester evaluator"),
     InitState = #{domain  => Domain},
@@ -12932,10 +12647,6 @@ api_opt_sock_acceptconn_tcp() ->
 
 %% Tests the socket option acceptfilter. PLACEHOLDER!
 
-api_opt_sock_acceptfilter(suite) ->
-    [];
-api_opt_sock_acceptfilter(doc) ->
-    [];
 api_opt_sock_acceptfilter(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(api_opt_sock_acceptfilter,
@@ -12950,10 +12661,6 @@ api_opt_sock_acceptfilter(_Config) when
 %% It has not always been possible to 'get' this option
 %% (at least on linux).
 
-api_opt_sock_bindtodevice(suite) ->
-    [];
-api_opt_sock_bindtodevice(doc) ->
-    [];
 api_opt_sock_bindtodevice(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(api_opt_sock_bindtodevice,
@@ -13221,7 +12928,7 @@ api_opt_sock_bindtodevice() ->
          ?SEV_FINISH_NORMAL
         ],
 
-    Domain = inet,
+    Domain = inet_or_inet6(),
 
     i("start tester evaluator"),
     InitState = #{domain  => Domain},
@@ -13238,10 +12945,6 @@ api_opt_sock_bindtodevice() ->
 %% Make it possible for datagram sockets to send packets to a broadcast
 %% address (IPv4 only).
 
-api_opt_sock_broadcast(suite) ->
-    [];
-api_opt_sock_broadcast(doc) ->
-    [];
 api_opt_sock_broadcast(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(api_opt_sock_broadcast,
@@ -13572,7 +13275,7 @@ api_opt_sock_broadcast() ->
          ?SEV_FINISH_NORMAL
         ],
 
-    Domain = inet,
+    Domain = inet_or_inet6(),
 
     i("start tester evaluator"),
     InitState = #{domain => Domain},
@@ -13591,10 +13294,6 @@ api_opt_sock_broadcast() ->
 %% therefore we explicitly test for the result eacces when attempting to
 %% set, and skip if we get it.
 
-api_opt_sock_debug(suite) ->
-    [];
-api_opt_sock_debug(doc) ->
-    [];
 api_opt_sock_debug(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_opt_sock_debug,
@@ -13617,19 +13316,14 @@ api_opt_sock_debug() ->
            cmd  => fun(#{domain := Domain} = State) ->
                            case ?LIB:which_local_host_info(Domain) of
                                {ok, #{name      := Name,
-                                      addr      := Addr,
-                                      broadaddr := BAddr}} ->
+                                      addr      := Addr}} ->
                                    ?SEV_IPRINT("local host info: "
                                                "~n   Name:           ~p"
-                                               "~n   Addr:           ~p"
-                                               "~n   Broadcast Addr: ~p",
-                                               [Name, Addr, BAddr]),
+                                               "~n   Addr:           ~p",
+                                               [Name, Addr]),
                                    LSA = #{family => Domain,
                                            addr   => Addr},
-                                   BSA = #{family => Domain,
-                                           addr   => BAddr},
-                                   {ok, State#{lsa => LSA,
-                                               bsa => BSA}};
+                                   {ok, State#{lsa => LSA}};
                                {error, _} = ERROR ->
                                    ERROR
                            end
@@ -13697,7 +13391,7 @@ api_opt_sock_debug() ->
          ?SEV_FINISH_NORMAL
         ],
 
-    Domain = inet,
+    Domain = inet_or_inet6(),
 
     i("start tester evaluator"),
     InitState = #{domain => Domain},
@@ -13713,10 +13407,6 @@ api_opt_sock_debug() ->
 %% Tests the socket option domain.
 %% This is a read only option. Also not available on all platforms.
 
-api_opt_sock_domain(suite) ->
-    [];
-api_opt_sock_domain(doc) ->
-    [];
 api_opt_sock_domain(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_opt_sock_domain,
@@ -13736,19 +13426,14 @@ api_opt_sock_domain() ->
            cmd  => fun(#{domain := Domain} = State) ->
                            case ?LIB:which_local_host_info(Domain) of
                                {ok, #{name      := Name,
-                                      addr      := Addr,
-                                      broadaddr := BAddr}} ->
+                                      addr      := Addr}} ->
                                    ?SEV_IPRINT("local host info: "
                                                "~n   Name:           ~p"
-                                               "~n   Addr:           ~p"
-                                               "~n   Broadcast Addr: ~p",
-                                               [Name, Addr, BAddr]),
+                                               "~n   Addr:           ~p",
+                                               [Name, Addr]),
                                    LSA = #{family => Domain,
                                            addr   => Addr},
-                                   BSA = #{family => Domain,
-                                           addr   => BAddr},
-                                   {ok, State#{lsa => LSA,
-                                               bsa => BSA}};
+                                   {ok, State#{lsa => LSA}};
                                {error, _} = ERROR ->
                                    ERROR
                            end
@@ -13815,7 +13500,7 @@ api_opt_sock_domain() ->
          ?SEV_FINISH_NORMAL
         ],
 
-    Domain = inet,
+    Domain = inet_or_inet6(),
 
     i("start tester evaluator"),
     InitState = #{domain => Domain},
@@ -13838,10 +13523,6 @@ api_opt_sock_domain() ->
 %% other side"), we only test if we can set and get the value.
 %% Better then nothing.
 
-api_opt_sock_dontroute(suite) ->
-    [];
-api_opt_sock_dontroute(doc) ->
-    [];
 api_opt_sock_dontroute(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_opt_sock_dontroute,
@@ -13864,19 +13545,14 @@ api_opt_sock_dontroute() ->
            cmd  => fun(#{domain := Domain} = State) ->
                            case ?LIB:which_local_host_info(Domain) of
                                {ok, #{name      := Name,
-                                      addr      := Addr,
-                                      broadaddr := BAddr}} ->
+                                      addr      := Addr}} ->
                                    ?SEV_IPRINT("local host info: "
                                                "~n   Name:           ~p"
-                                               "~n   Addr:           ~p"
-                                               "~n   Broadcast Addr: ~p",
-                                               [Name, Addr, BAddr]),
+                                               "~n   Addr:           ~p",
+                                               [Name, Addr]),
                                    LSA = #{family => Domain,
                                            addr   => Addr},
-                                   BSA = #{family => Domain,
-                                           addr   => BAddr},
-                                   {ok, State#{lsa => LSA,
-                                               bsa => BSA}};
+                                   {ok, State#{lsa => LSA}};
                                {error, _} = ERROR ->
                                    ERROR
                            end
@@ -13946,7 +13622,7 @@ api_opt_sock_dontroute() ->
          ?SEV_FINISH_NORMAL
         ],
 
-    Domain = inet,
+    Domain = inet_or_inet6(),
 
     i("start tester evaluator"),
     InitState = #{domain => Domain},
@@ -13961,10 +13637,6 @@ api_opt_sock_dontroute() ->
 
 %% Tests the socket option error. PLACEHOLDER!
 
-api_opt_sock_error(suite) ->
-    [];
-api_opt_sock_error(doc) ->
-    [];
 api_opt_sock_error(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_opt_sock_error,
@@ -13980,10 +13652,6 @@ api_opt_sock_error(_Config) when is_list
 %% the underlying TCP timeouts. So, for now, we just test that we can
 %% change the value.
 
-api_opt_sock_keepalive(suite) ->
-    [];
-api_opt_sock_keepalive(doc) ->
-    [];
 api_opt_sock_keepalive(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_opt_sock_keepalive,
@@ -14006,19 +13674,14 @@ api_opt_sock_keepalive() ->
            cmd  => fun(#{domain := Domain} = State) ->
                            case ?LIB:which_local_host_info(Domain) of
                                {ok, #{name      := Name,
-                                      addr      := Addr,
-                                      broadaddr := BAddr}} ->
+                                      addr      := Addr}} ->
                                    ?SEV_IPRINT("local host info: "
                                                "~n   Name:           ~p"
-                                               "~n   Addr:           ~p"
-                                               "~n   Broadcast Addr: ~p",
-                                               [Name, Addr, BAddr]),
+                                               "~n   Addr:           ~p",
+                                               [Name, Addr]),
                                    LSA = #{family => Domain,
                                            addr   => Addr},
-                                   BSA = #{family => Domain,
-                                           addr   => BAddr},
-                                   {ok, State#{lsa => LSA,
-                                               bsa => BSA}};
+                                   {ok, State#{lsa => LSA}};
                                {error, _} = ERROR ->
                                    ERROR
                            end
@@ -14090,7 +13753,7 @@ api_opt_sock_keepalive() ->
          ?SEV_FINISH_NORMAL
         ],
 
-    Domain = inet,
+    Domain = inet_or_inet6(),
 
     i("start tester evaluator"),
     InitState = #{domain => Domain},
@@ -14105,10 +13768,6 @@ api_opt_sock_keepalive() ->
 
 %% Tests the socket option linger. PLACEHOLDER!
 
-api_opt_sock_linger(suite) ->
-    [];
-api_opt_sock_linger(doc) ->
-    [];
 api_opt_sock_linger(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_opt_sock_linger,
@@ -14121,10 +13780,6 @@ api_opt_sock_linger(_Config) when is_lis
 
 %% Tests the socket option mark. PLACEHOLDER!
 
-api_opt_sock_mark(suite) ->
-    [];
-api_opt_sock_mark(doc) ->
-    [];
 api_opt_sock_mark(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_opt_sock_mark,
@@ -14150,10 +13805,6 @@ api_opt_sock_mark(_Config) when is_list(
 %% linux but maybe not in, say, FreeBSD).
 %%
 
-api_opt_sock_oobinline(suite) ->
-    [];
-api_opt_sock_oobinline(doc) ->
-    [];
 api_opt_sock_oobinline(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_ooinline,
@@ -14179,7 +13830,7 @@ api_opt_sock_oobinline(_Config) when is_
                              (Sock, false) ->
                                   socket:recv(Sock)
                           end,
-                   InitState = #{domain => inet,
+                   InitState = #{domain => inet_or_inet6(),
                                  proto  => tcp,
                                  send   => Send,
                                  recv   => Recv,
@@ -14783,10 +14434,6 @@ do_api_opt_sock_oobinline(InitState) ->
 %% As it is now, the client does *not* get any credentials!
 %% Until this has been done, this case is skipped!.
 
-api_opt_sock_passcred_tcp4(suite) ->
-    [];
-api_opt_sock_passcred_tcp4(doc) ->
-    [];
 api_opt_sock_passcred_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_passcred_tcp4,
@@ -15574,10 +15221,6 @@ api_opt_sock_passcred_tcp(InitState) ->
 %%
 %%
 
-api_opt_sock_peek_off_tcpL(suite) ->
-    [];
-api_opt_sock_peek_off_tcpL(doc) ->
-    [];
 api_opt_sock_peek_off_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_peek_off_tcpL,
@@ -16297,10 +15940,6 @@ api_opt_sock_peek_off(InitState) ->
 %% and decode it...
 %%
 
-api_opt_sock_peercred_tcpL(suite) ->
-    [];
-api_opt_sock_peercred_tcpL(doc) ->
-    [];
 api_opt_sock_peercred_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_peercred_tcpL,
@@ -16836,14 +16475,10 @@ api_opt_sock_peercred_tcp(_InitState) ->
 %%
 %%
 
-api_opt_sock_priority_udp4(suite) ->
-    [];
-api_opt_sock_priority_udp4(doc) ->
-    [];
 api_opt_sock_priority_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_priority_udp4,
-           fun() -> has_support_sock_priority() end,
+           fun() -> has_support_ipv4(), has_support_sock_priority() end,
            fun() ->
                    Set  = fun(Sock, Value) ->
                                   socket:setopt(Sock, socket, priority, Value)
@@ -16869,14 +16504,10 @@ api_opt_sock_priority_udp4(_Config) when
 %%
 %%
 
-api_opt_sock_priority_tcp4(suite) ->
-    [];
-api_opt_sock_priority_tcp4(doc) ->
-    [];
 api_opt_sock_priority_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_priority_tcp4,
-           fun() -> has_support_sock_priority() end,
+           fun() -> has_support_ipv4(), has_support_sock_priority() end,
            fun() ->
                    Set  = fun(Sock, Value) ->
                                   socket:setopt(Sock, socket, priority, Value)
@@ -17010,14 +16641,10 @@ api_opt_sock_priority(InitState) ->
 %%
 %%
 
-api_opt_sock_rcvbuf_udp4(suite) ->
-    [];
-api_opt_sock_rcvbuf_udp4(doc) ->
-    [];
 api_opt_sock_rcvbuf_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_rcvbuf_udp4,
-           fun() -> has_support_sock_rcvbuf() end,
+           fun() -> has_support_ipv4(), has_support_sock_rcvbuf() end,
            fun() ->
                    ok = api_opt_sock_buf_udp4(rcvbuf)
            end).
@@ -17031,14 +16658,10 @@ api_opt_sock_rcvbuf_udp4(_Config) when i
 %%
 %%
 
-api_opt_sock_sndbuf_udp4(suite) ->
-    [];
-api_opt_sock_sndbuf_udp4(doc) ->
-    [];
 api_opt_sock_sndbuf_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_sndbuf_udp4,
-           fun() -> has_support_sock_sndbuf() end,
+           fun() -> has_support_ipv4(), has_support_sock_sndbuf() end,
            fun() ->
                    ok = api_opt_sock_buf_udp4(sndbuf)
            end).
@@ -17167,14 +16790,10 @@ api_opt_sock_buf(InitState) ->
 %% but we don't (we just set the value and read it back...)
 %%
 
-api_opt_sock_rcvtimeo_udp4(suite) ->
-    [];
-api_opt_sock_rcvtimeo_udp4(doc) ->
-    [];
 api_opt_sock_rcvtimeo_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_rcvtimeo_udp4,
-           fun() -> has_support_sock_rcvtimeo() end,
+           fun() -> has_support_ipv4(), has_support_sock_rcvtimeo() end,
            fun() ->
                    ok = api_opt_sock_timeo_udp4(rcvtimeo)
            end).
@@ -17188,14 +16807,10 @@ api_opt_sock_rcvtimeo_udp4(_Config) when
 %%
 %%
 
-api_opt_sock_sndtimeo_udp4(suite) ->
-    [];
-api_opt_sock_sndtimeo_udp4(doc) ->
-    [];
 api_opt_sock_sndtimeo_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_sndtimeo_udp4,
-           fun() -> has_support_sock_sndtimeo() end,
+           fun() -> has_support_ipv4(), has_support_sock_sndtimeo() end,
            fun() ->
                    ok = api_opt_sock_timeo_udp4(sndtimeo)
            end).
@@ -17338,14 +16953,10 @@ api_opt_sock_timeo(InitState) ->
 %%
 %%
 
-api_opt_sock_rcvlowat_udp4(suite) ->
-    [];
-api_opt_sock_rcvlowat_udp4(doc) ->
-    [];
 api_opt_sock_rcvlowat_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_rcvlowat_udp4,
-           fun() -> has_support_sock_rcvlowat() end,
+           fun() -> has_support_ipv4(), has_support_sock_rcvlowat() end,
            fun() ->
                    ok = api_opt_sock_lowat_udp4(rcvlowat)
            end).
@@ -17361,14 +16972,10 @@ api_opt_sock_rcvlowat_udp4(_Config) when
 %% so we skip if we get ENOPROTOOPT when attempting a change.
 %%
 
-api_opt_sock_sndlowat_udp4(suite) ->
-    [];
-api_opt_sock_sndlowat_udp4(doc) ->
-    [];
 api_opt_sock_sndlowat_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_sndlowat_udp4,
-           fun() -> has_support_sock_sndlowat() end,
+           fun() -> has_support_ipv4(), has_support_sock_sndlowat() end,
            fun() ->
                    ok = api_opt_sock_lowat_udp4(sndlowat)
            end).
@@ -17505,14 +17112,10 @@ api_opt_sock_lowat(InitState) ->
 %% All subsequent *received* messages will be timestamped.
 %%
 
-api_opt_sock_timestamp_udp4(suite) ->
-    [];
-api_opt_sock_timestamp_udp4(doc) ->
-    [];
 api_opt_sock_timestamp_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_timestamp_udp4,
-           fun() -> has_support_sock_timestamp() end,
+           fun() -> has_support_ipv4(), has_support_sock_timestamp() end,
            fun() ->
                    Set  = fun(Sock, Value) ->
                                   socket:setopt(Sock, socket, timestamp, Value)
@@ -17891,14 +17494,11 @@ api_opt_sock_timestamp_udp(InitState) ->
 %% Don't actually know if its the distro or the (kernel) version...
 %%
 
-api_opt_sock_timestamp_tcp4(suite) ->
-    [];
-api_opt_sock_timestamp_tcp4(doc) ->
-    [];
 api_opt_sock_timestamp_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_sock_timestamp_tcp4,
            fun() ->
+                   has_support_ipv4(),
                    has_support_sock_timestamp(),
                    is_good_enough_linux({4,4,120}),
                    is_not_freebsd(),
@@ -18696,10 +18296,9 @@ api_opt_sock_timestamp_tcp(InitState) ->
 %%                   When sending, the dest will be the multicast address
 %%                   and port of the receiving socket.
 %% Receiving socket: Bound to the multicast address and port.
-api_opt_ip_add_drop_membership(suite) ->
-    [];
-api_opt_ip_add_drop_membership(doc) ->
-    ["OTP-15908 (ERL-980)"];
+api_opt_ip_add_drop_membership() ->
+    [{doc, "OTP-15908 (ERL-980)"}].
+
 api_opt_ip_add_drop_membership(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(api_opt_ip_add_drop_membership,
@@ -18708,10 +18307,10 @@ api_opt_ip_add_drop_membership(_Config)
                    has_support_ip_drop_membership(),
                    has_support_ip_multicast()
            end,
-           fun() -> api_opt_ip_add_drop_membership() end).
+           fun() -> api_opt_ip_add_drop_membership_do() end).
 
 
-api_opt_ip_add_drop_membership() ->
+api_opt_ip_add_drop_membership_do() ->
     Set = fun(S, Key, Val) ->
                   socket:setopt(S, ip, Key, Val)
           end,
@@ -19038,14 +18637,10 @@ which_local_host_ifname(Domain) ->
 %% we do not test!!
 %%
 
-api_opt_ip_pktinfo_udp4(suite) ->
-    [];
-api_opt_ip_pktinfo_udp4(doc) ->
-    [];
 api_opt_ip_pktinfo_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ip_pktinfo_udp4,
-           fun() -> has_support_ip_pktinfo() end,
+           fun() -> has_support_ipv4(), has_support_ip_pktinfo() end,
            fun() ->
                    Set  = fun(Sock, Value) ->
                                   socket:setopt(Sock, ip, pktinfo, Value)
@@ -19394,14 +18989,11 @@ api_opt_ip_pktinfo_udp(InitState) ->
 %% </NOTE>
 %%
 
-api_opt_ip_recvopts_udp4(suite) ->
-    [];
-api_opt_ip_recvopts_udp4(doc) ->
-    [];
 api_opt_ip_recvopts_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ip_recvopts_udp4,
            fun() ->
+                   has_support_ipv4(),
                    has_support_ip_recvopts(),
                    %% We also use the recvtos and timestamp options
                    %% in this test, so at least one of them must
@@ -19853,14 +19445,10 @@ api_opt_ip_recvopts_udp(InitState) ->
 %%
 %%
 
-api_opt_ip_recvorigdstaddr_udp4(suite) ->
-    [];
-api_opt_ip_recvorigdstaddr_udp4(doc) ->
-    [];
 api_opt_ip_recvorigdstaddr_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ip_recvorigdstaddr_udp4,
-           fun() -> has_support_ip_recvorigdstaddr() end,
+           fun() -> has_support_ipv4(), has_support_ip_recvorigdstaddr() end,
            fun() ->
                    Set  = fun(Sock, Value) ->
                                   socket:setopt(Sock, ip, recvorigdstaddr, Value)
@@ -20109,14 +19697,11 @@ api_opt_ip_recvorigdstaddr_udp(InitState
 %% that method. Instead, set tos (true) on the sending socket.
 %%
 
-api_opt_ip_recvtos_udp4(suite) ->
-    [];
-api_opt_ip_recvtos_udp4(doc) ->
-    [];
 api_opt_ip_recvtos_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ip_recvtos_udp4,
            fun() ->
+                   has_support_ipv4(),
                    has_support_ip_recvtos(),
                    has_support_ip_tos() % Used in the test
            end,
@@ -20486,14 +20071,11 @@ api_opt_ip_recvtos_udp(InitState) ->
 %% skip darwin and OpenBSD.
 %%
 
-api_opt_ip_recvttl_udp4(suite) ->
-    [];
-api_opt_ip_recvttl_udp4(doc) ->
-    [];
 api_opt_ip_recvttl_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ip_recvttl_udp4,
            fun() ->
+                   has_support_ipv4(),
 		   has_support_ip_recvttl(),
 		   is_not_openbsd(),
 		   is_not_darwin()
@@ -20872,14 +20454,10 @@ api_opt_ip_recvttl_udp(InitState) ->
 %% Default value is supposed to be '0'.
 %% 
 
-api_opt_ip_tos_udp4(suite) ->
-    [];
-api_opt_ip_tos_udp4(doc) ->
-    [];
 api_opt_ip_tos_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ip_tos_udp4,
-           fun() -> has_support_ip_tos() end,
+           fun() -> has_support_ipv4(), has_support_ip_tos() end,
            fun() ->
                    Set  = fun(Sock, Value) ->
                                   socket:setopt(Sock, ip, tos, Value)
@@ -21118,14 +20696,11 @@ api_opt_ip_tos_udp(InitState) ->
 %% queue can be read.
 %% 
 
-api_opt_ip_recverr_udp4(suite) ->
-    [];
-api_opt_ip_recverr_udp4(doc) ->
-    [];
 api_opt_ip_recverr_udp4(Config) when is_list(Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ip_recverr_udp4,
            fun() ->
+                   has_support_ipv4(),
                    has_support_ip_recverr()
            end,
            fun() ->
@@ -21157,10 +20732,6 @@ api_opt_ip_recverr_udp4(Config) when is_
 %% queue can be read.
 %% 
 
-api_opt_ipv6_recverr_udp6(suite) ->
-    [];
-api_opt_ipv6_recverr_udp6(doc) ->
-    [];
 api_opt_ipv6_recverr_udp6(Config) when is_list(Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ipv6_recverr_udp6,
@@ -21448,14 +21019,11 @@ api_opt_recverr_udp(Config, InitState) -
 %% the test (since its a IPv4 test case).
 %%
 
-api_opt_ip_mopts_udp4(suite) ->
-    [];
-api_opt_ip_mopts_udp4(doc) ->
-    [];
 api_opt_ip_mopts_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ip_mopts_udp4,
            fun() ->
+                   has_support_ipv4(),
 		   case is_any_options_supported(
 			  [{ip, pktinfo},
 			   {ip, recvorigdstaddr},
@@ -21789,10 +21357,6 @@ api_opt_ip_mopts_udp(InitState) ->
 %% although we only test this with dgram.
 %%
 
-api_opt_ipv6_recvpktinfo_udp6(suite) ->
-    [];
-api_opt_ipv6_recvpktinfo_udp6(doc) ->
-    [];
 api_opt_ipv6_recvpktinfo_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ipv6_recvpktinfo_udp6,
@@ -22056,10 +21620,6 @@ api_opt_ipv6_recvpktinfo_udp(InitState)
 %% leave it as is for now...
 %%
 
-api_opt_ipv6_flowinfo_udp6(suite) ->
-    [];
-api_opt_ipv6_flowinfo_udp6(doc) ->
-    [];
 api_opt_ipv6_flowinfo_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ipv6_flowinfo_udp6,
@@ -22315,10 +21875,6 @@ api_opt_ipv6_flowinfo_udp(InitState) ->
 %% </Note>
 %%
 
-api_opt_ipv6_hoplimit_udp6(suite) ->
-    [];
-api_opt_ipv6_hoplimit_udp6(doc) ->
-    [];
 api_opt_ipv6_hoplimit_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ipv6_hoplimit_udp6,
@@ -22606,10 +22162,6 @@ api_opt_ipv6_hoplimit_udp(InitState) ->
 %% </Note>
 %%
 
-api_opt_ipv6_tclass_udp6(suite) ->
-    [];
-api_opt_ipv6_tclass_udp6(doc) ->
-    [];
 api_opt_ipv6_tclass_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ipv6_tclass_udp6,
@@ -22963,10 +22515,6 @@ api_opt_ipv6_tclass_udp(InitState) ->
 %% the test (since its a IPv6 test case).
 %%
 
-api_opt_ipv6_mopts_udp6(suite) ->
-    [];
-api_opt_ipv6_mopts_udp6(doc) ->
-    [];
 api_opt_ipv6_mopts_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_ipv6_mopts_udp6,
@@ -23258,14 +22806,10 @@ api_opt_ipv6_mopts_udp(InitState) ->
 %% allgorithm was allowed, so...
 %% For now, we only test that we can get (it could be a bug in our code)
 
-api_opt_tcp_congestion_tcp4(suite) ->
-    [];
-api_opt_tcp_congestion_tcp4(doc) ->
-    [];
 api_opt_tcp_congestion_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_tcp_congestion_tcp4,
-           fun() -> has_support_tcp_congestion() end,
+           fun() -> has_support_ipv4(), has_support_tcp_congestion() end,
            fun() ->
                    Set  = fun(Sock, Value) when is_list(Value) ->
                                   socket:setopt(Sock, tcp, congestion, Value)
@@ -23449,14 +22993,10 @@ api_opt_tcp_congestion_tcp(InitState) ->
 %% Reading the man page it seems like (on linux) that the
 %% value resets itself after some (short) time...
 
-api_opt_tcp_cork_tcp4(suite) ->
-    [];
-api_opt_tcp_cork_tcp4(doc) ->
-    [];
 api_opt_tcp_cork_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_tcp_cork_tcp4,
-           fun() -> has_support_tcp_cork() end,
+           fun() -> has_support_ipv4(), has_support_tcp_cork() end,
            fun() ->
                    Set  = fun(Sock, Value) when is_boolean(Value) ->
                                   socket:setopt(Sock, tcp, cork, Value)
@@ -23571,14 +23111,10 @@ api_opt_tcp_cork_tcp(InitState) ->
 %% to what is an acceptable value.
 %%
 
-api_opt_tcp_maxseg_tcp4(suite) ->
-    [];
-api_opt_tcp_maxseg_tcp4(doc) ->
-    [];
 api_opt_tcp_maxseg_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_tcp_maxseg_tcp4,
-           fun() -> has_support_tcp_maxseg() end,
+           fun() -> has_support_ipv4(), has_support_tcp_maxseg() end,
            fun() ->
                    Set  = fun(Sock, Value) when is_integer(Value) ->
                                   socket:setopt(Sock, tcp, maxseg, Value)
@@ -23698,14 +23234,10 @@ api_opt_tcp_maxseg_tcp(InitState) ->
 %% This is a very simple test. We simple set and get the value.
 %% To test that it has an effect is just "to much work"...
 
-api_opt_tcp_nodelay_tcp4(suite) ->
-    [];
-api_opt_tcp_nodelay_tcp4(doc) ->
-    [];
 api_opt_tcp_nodelay_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_tcp_nodelay_tcp4,
-           fun() -> has_support_tcp_nodelay() end,
+           fun() -> has_support_ipv4(), has_support_tcp_nodelay() end,
            fun() ->
                    Set  = fun(Sock, Value) when is_boolean(Value) ->
                                   socket:setopt(Sock, tcp, nodelay, Value)
@@ -23816,14 +23348,10 @@ api_opt_tcp_nodelay_tcp(InitState) ->
 %% To test that it has an effect is just "to much work"...
 %%
 
-api_opt_udp_cork_udp4(suite) ->
-    [];
-api_opt_udp_cork_udp4(doc) ->
-    [];
 api_opt_udp_cork_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(api_opt_udp_cork_udp4,
-           fun() -> has_support_udp_cork() end,
+           fun() -> has_support_ipv4(), has_support_udp_cork() end,
            fun() ->
                    Set  = fun(Sock, Value) when is_boolean(Value) ->
                                   socket:setopt(Sock, udp, cork, Value)
@@ -23939,13 +23467,9 @@ api_opt_udp_cork_udp(InitState) ->
 
 %% This test case is intended to test the connect timeout option
 %% on an IPv4 TCP (stream) socket.
-api_to_connect_tcp4(suite) ->
-    [];
-api_to_connect_tcp4(doc) ->
-    [];
 api_to_connect_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
-    Cond = fun() -> api_to_connect_cond() end,
+    Cond = fun() -> has_support_ipv4(), api_to_connect_cond() end,
     tc_try(api_to_connect_tcp4,
            Cond,
            fun() ->
@@ -23998,10 +23522,6 @@ api_to_connect_cond(_, _) ->
 
 %% This test case is intended to test the connect timeout option
 %% on an IPv6 TCP (stream) socket.
-api_to_connect_tcp6(suite) ->
-    [];
-api_to_connect_tcp6(doc) ->
-    [];
 api_to_connect_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_connect_tcp6,
@@ -24511,13 +24031,10 @@ api_to_connect_tcp_await_timeout3([Sock|
 
 %% This test case is intended to test the accept timeout option
 %% on an IPv4 TCP (stream) socket.
-api_to_accept_tcp4(suite) ->
-    [];
-api_to_accept_tcp4(doc) ->
-    [];
 api_to_accept_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_accept_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain => inet, timeout => 5000},
                    ok = api_to_accept_tcp(InitState)
@@ -24528,13 +24045,9 @@ api_to_accept_tcp4(_Config) when is_list
 
 %% This test case is intended to test the accept timeout option
 %% on an IPv6 TCP (stream) socket.
-api_to_accept_tcp6(suite) ->
-    [];
-api_to_accept_tcp6(doc) ->
-    [];
 api_to_accept_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
-    tc_try(api_to_accept_tcp4,
+    tc_try(api_to_accept_tcp6,
            fun() -> has_support_ipv6() end,
            fun() ->
                    InitState = #{domain => inet6, timeout => 5000},
@@ -24625,13 +24138,10 @@ api_to_accept_tcp(InitState) ->
 %% This test case is intended to test the multi accept timeout option
 %% on an IPv4 TCP (stream) socket with multiple acceptor processes 
 %% (three in this case).
-api_to_maccept_tcp4(suite) ->
-    [];
-api_to_maccept_tcp4(doc) ->
-    [];
 api_to_maccept_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(20)),
     tc_try(api_to_maccept_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain => inet, timeout => 5000},
                    ok = api_to_maccept_tcp(InitState)
@@ -24642,13 +24152,9 @@ api_to_maccept_tcp4(_Config) when is_lis
 
 %% This test case is intended to test the accept timeout option
 %% on an IPv6 TCP (stream) socket.
-api_to_maccept_tcp6(suite) ->
-    [];
-api_to_maccept_tcp6(doc) ->
-    [];
 api_to_maccept_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(20)),
-    tc_try(api_to_maccept_tcp4,
+    tc_try(api_to_maccept_tcp6,
            fun() -> has_support_ipv6() end,
            fun() ->
                    InitState = #{domain => inet6, timeout => 5000},
@@ -24995,12 +24501,9 @@ api_to_maccept_tcp(InitState) ->
 
 %% This test case is intended to test the send timeout option
 %% on an IPv4 TCP (stream) socket.
-api_to_send_tcp4(suite) ->
-    [];
-api_to_send_tcp4(doc) ->
-    [];
 api_to_send_tcp4(_Config) when is_list(_Config) ->
     tc_try(api_to_send_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    not_yet_implemented()%% ,
                    %% ok = api_to_send_tcp(inet)
@@ -25011,10 +24514,6 @@ api_to_send_tcp4(_Config) when is_list(_
 
 %% This test case is intended to test the send timeout option
 %% on an IPv6 TCP (stream) socket.
-api_to_send_tcp6(suite) ->
-    [];
-api_to_send_tcp6(doc) ->
-    [];
 api_to_send_tcp6(_Config) when is_list(_Config) ->
     tc_try(api_to_send_tcp6,
            fun() -> has_support_ipv6() end,
@@ -25028,12 +24527,9 @@ api_to_send_tcp6(_Config) when is_list(_
 
 %% This test case is intended to test the sendto timeout option
 %% on an IPv4 UDP (dgram) socket.
-api_to_sendto_udp4(suite) ->
-    [];
-api_to_sendto_udp4(doc) ->
-    [];
 api_to_sendto_udp4(_Config) when is_list(_Config) ->
     tc_try(api_to_sendto_udp4,
+           fun () -> has_support_ipv4() end,
            fun() ->
                    not_yet_implemented()%% ,
                    %% ok = api_to_sendto_to_udp(inet)
@@ -25044,10 +24540,6 @@ api_to_sendto_udp4(_Config) when is_list
 
 %% This test case is intended to test the sendto timeout option
 %% on an IPv6 UDP (dgram) socket.
-api_to_sendto_udp6(suite) ->
-    [];
-api_to_sendto_udp6(doc) ->
-    [];
 api_to_sendto_udp6(_Config) when is_list(_Config) ->
     tc_try(api_to_sendto_udp6,
            fun() -> has_support_ipv6() end,
@@ -25061,12 +24553,9 @@ api_to_sendto_udp6(_Config) when is_list
 
 %% This test case is intended to test the sendmsg timeout option
 %% on an IPv4 TCP (stream) socket.
-api_to_sendmsg_tcp4(suite) ->
-    [];
-api_to_sendmsg_tcp4(doc) ->
-    [];
 api_to_sendmsg_tcp4(_Config) when is_list(_Config) ->
     tc_try(api_to_sendmsg_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    not_yet_implemented()%% ,
                    %% ok = api_to_sendmsg_tcp(inet)
@@ -25077,10 +24566,6 @@ api_to_sendmsg_tcp4(_Config) when is_lis
 
 %% This test case is intended to test the sendmsg timeout option
 %% on an IPv6 TCP (stream) socket.
-api_to_sendmsg_tcp6(suite) ->
-    [];
-api_to_sendmsg_tcp6(doc) ->
-    [];
 api_to_sendmsg_tcp6(_Config) when is_list(_Config) ->
     tc_try(api_to_sendmsg_tcp6,
            fun() -> has_support_ipv6() end,
@@ -25095,12 +24580,9 @@ api_to_sendmsg_tcp6(_Config) when is_lis
 %% This test case is intended to test the recv timeout option
 %% on an IPv4 UDP (dgram) socket. To test this we must connect
 %% the socket.
-api_to_recv_udp4(suite) ->
-    [];
-api_to_recv_udp4(doc) ->
-    [];
 api_to_recv_udp4(_Config) when is_list(_Config) ->
     tc_try(api_to_recv_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    not_yet_implemented()%%,
                    %%ok = api_to_recv_udp(inet)
@@ -25112,10 +24594,6 @@ api_to_recv_udp4(_Config) when is_list(_
 %% This test case is intended to test the recv timeout option
 %% on an IPv6 UDP (dgram) socket. To test this we must connect
 %% the socket.
-api_to_recv_udp6(suite) ->
-    [];
-api_to_recv_udp6(doc) ->
-    [];
 api_to_recv_udp6(_Config) when is_list(_Config) ->
     tc_try(api_to_recv_udp6,
            fun() -> has_support_ipv6() end,
@@ -25129,13 +24607,10 @@ api_to_recv_udp6(_Config) when is_list(_
 
 %% This test case is intended to test the recv timeout option
 %% on an IPv4 TCP (stream) socket.
-api_to_recv_tcp4(suite) ->
-    [];
-api_to_recv_tcp4(doc) ->
-    [];
 api_to_recv_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_recv_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock, To) -> socket:recv(Sock, 0, To) end,
                    InitState = #{domain  => inet,
@@ -25149,10 +24624,6 @@ api_to_recv_tcp4(_Config) when is_list(_
 
 %% This test case is intended to test the recv timeout option
 %% on an IPv6 TCP (stream) socket.
-api_to_recv_tcp6(suite) ->
-    [];
-api_to_recv_tcp6(doc) ->
-    [];
 api_to_recv_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_recv_tcp6,
@@ -25486,13 +24957,10 @@ api_to_receive_tcp(InitState) ->
 
 %% This test case is intended to test the recvfrom timeout option
 %% on an IPv4 UDP (dgram) socket.
-api_to_recvfrom_udp4(suite) ->
-    [];
-api_to_recvfrom_udp4(doc) ->
-    [];
 api_to_recvfrom_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_recvfrom_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock, To) -> socket:recvfrom(Sock, 0, To) end,
                    InitState = #{domain  => inet,
@@ -25506,10 +24974,6 @@ api_to_recvfrom_udp4(_Config) when is_li
 
 %% This test case is intended to test the recvfrom timeout option
 %% on an IPv6 UDP (dgram) socket.
-api_to_recvfrom_udp6(suite) ->
-    [];
-api_to_recvfrom_udp6(doc) ->
-    [];
 api_to_recvfrom_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_recvfrom_udp6,
@@ -25602,13 +25066,10 @@ api_to_receive_udp(InitState) ->
 
 %% This test case is intended to test the recvmsg timeout option
 %% on an IPv4 UDP (dgram) socket.
-api_to_recvmsg_udp4(suite) ->
-    [];
-api_to_recvmsg_udp4(doc) ->
-    [];
 api_to_recvmsg_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_recvmsg_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock, To) -> socket:recvmsg(Sock, To) end,
                    InitState = #{domain  => inet,
@@ -25622,10 +25083,6 @@ api_to_recvmsg_udp4(_Config) when is_lis
 
 %% This test case is intended to test the recvmsg timeout option
 %% on an IPv6 UDP (dgram) socket.
-api_to_recvmsg_udp6(suite) ->
-    [];
-api_to_recvmsg_udp6(doc) ->
-    [];
 api_to_recvmsg_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_recvmsg_udp6,
@@ -25643,13 +25100,10 @@ api_to_recvmsg_udp6(_Config) when is_lis
 
 %% This test case is intended to test the recvmsg timeout option
 %% on an IPv4 TCP (stream) socket.
-api_to_recvmsg_tcp4(suite) ->
-    [];
-api_to_recvmsg_tcp4(doc) ->
-    [];
 api_to_recvmsg_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_recvmsg_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv = fun(Sock, To) -> socket:recvmsg(Sock, To) end,
                    InitState = #{domain  => inet,
@@ -25663,10 +25117,6 @@ api_to_recvmsg_tcp4(_Config) when is_lis
 
 %% This test case is intended to test the recvmsg timeout option
 %% on an IPv6 TCP (stream) socket.
-api_to_recvmsg_tcp6(suite) ->
-    [];
-api_to_recvmsg_tcp6(doc) ->
-    [];
 api_to_recvmsg_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(api_to_recvmsg_tcp6,
@@ -25693,10 +25143,6 @@ api_to_recvmsg_tcp6(_Config) when is_lis
 %% We create a bunch of different sockets and ensure that the registry
 %% has the correct info.
 
-reg_s_single_open_and_close_and_count(suite) ->
-    [];
-reg_s_single_open_and_close_and_count(doc) ->
-    [];
 reg_s_single_open_and_close_and_count(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(reg_s_single_open_and_close_and_count,
@@ -26086,10 +25532,6 @@ reg_sr_num2(Existing, F) ->
 %% We create a bunch of different sockets and ensure that the registry
 %% has the correct info.
 
-reg_s_optional_open_and_close_and_count(suite) ->
-    [];
-reg_s_optional_open_and_close_and_count(doc) ->
-    [];
 reg_s_optional_open_and_close_and_count(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(reg_s_optional_open_and_close_and_count,
@@ -26198,10 +25640,6 @@ reg_s_optional_open_and_close_and_count(
 %% Create one socket, monitor from a different process then close socket.
 %% The process that did the monitor shall receive a socket DOWN.
 
-monitor_simple_open_and_close(suite) ->
-    [];
-monitor_simple_open_and_close(doc) ->
-    [];
 monitor_simple_open_and_close(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(monitor_simple_open_and_close,
@@ -26458,10 +25896,6 @@ mon_simple_open_and_close(InitState) ->
 %% owner process.
 %% The process that did the monitor shall receive a socket DOWN.
 
-monitor_simple_open_and_exit(suite) ->
-    [];
-monitor_simple_open_and_exit(doc) ->
-    [];
 monitor_simple_open_and_exit(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(monitor_simple_open_and_exit,
@@ -26653,10 +26087,6 @@ mon_simple_open_and_exit(InitState) ->
 %% (demonitor) and then close socket.
 %% The process that did the monitor shall *not* receive a socket DOWN.
 
-monitor_simple_open_and_demon_and_close(suite) ->
-    [];
-monitor_simple_open_and_demon_and_close(doc) ->
-    [];
 monitor_simple_open_and_demon_and_close(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(monitor_simple_open_and_demon_and_close,
@@ -26848,10 +26278,6 @@ mon_simple_open_and_demon_and_close(Init
 %% Create several sockets, monitor from a different process then close
 %% socket. The process that did the monitor shall receive a socket DOWN.
 
-monitor_open_and_close_multi_socks(suite) ->
-    [];
-monitor_open_and_close_multi_socks(doc) ->
-    [];
 monitor_open_and_close_multi_socks(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(monitor_open_and_close_multi_socks,
@@ -27293,10 +26719,6 @@ mon_open_and_close_multi_socks(InitState
 %% the owner process.
 %% The process that did the monitor shall receive a socket DOWN.
 
-monitor_open_and_exit_multi_socks(suite) ->
-    [];
-monitor_open_and_exit_multi_socks(doc) ->
-    [];
 monitor_open_and_exit_multi_socks(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(monitor_open_and_exit_multi_socks,
@@ -27614,10 +27036,6 @@ mon_open_and_exit_multi_socks(InitState)
 %% The process that did the monitor shall receive a socket DOWN for
 %% the sockets that are still monitored.
 
-monitor_open_and_demon_and_close_multi_socks(suite) ->
-    [];
-monitor_open_and_demon_and_close_multi_socks(doc) ->
-    [];
 monitor_open_and_demon_and_close_multi_socks(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(monitor_open_and_demon_and_close_multi_socks,
@@ -27987,10 +27405,6 @@ mon_open_and_demon_and_close_multi_socks
 %% processes, then close socket (from 'owner').
 %% The processes that did the monitor shall receive a socket DOWN.
 
-monitor_open_and_close_multi_mon(suite) ->
-    [];
-monitor_open_and_close_multi_mon(doc) ->
-    [];
 monitor_open_and_close_multi_mon(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(monitor_open_and_close_multi_mon,
@@ -28580,10 +27994,6 @@ mon_open_and_close_multi_mon(InitState)
 %% processes, then close socket (from 'owner').
 %% The processes that did the monitor shall receive a socket DOWN.
 
-monitor_open_and_exit_multi_mon(suite) ->
-    [];
-monitor_open_and_exit_multi_mon(doc) ->
-    [];
 monitor_open_and_exit_multi_mon(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(monitor_open_and_exit_multi_mon,
@@ -29138,10 +28548,6 @@ mon_open_and_exit_multi_mon(InitState) -
 %% The processes that did the monitor shall receive one socket DOWN for
 %% each socket.
 
-monitor_open_and_close_multi_socks_and_mon(suite) ->
-    [];
-monitor_open_and_close_multi_socks_and_mon(doc) ->
-    [];
 monitor_open_and_close_multi_socks_and_mon(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(monitor_open_and_close_multi_socks_and_mon,
@@ -30096,10 +29502,6 @@ mon_open_and_close_multi_socks_and_mon(I
 %% The processes that did the monitor shall receive one socket DOWN for
 %% each socket.
 
-monitor_open_and_exit_multi_socks_and_mon(suite) ->
-    [];
-monitor_open_and_exit_multi_socks_and_mon(doc) ->
-    [];
 monitor_open_and_exit_multi_socks_and_mon(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(monitor_open_and_exit_multi_socks_and_mon,
@@ -30847,10 +30249,6 @@ mon_open_and_exit_multi_socks_and_mon(In
 %% The processes that did the monitor shall receive one socket DOWN for
 %% each socket.
 
-monitor_closed_socket(suite) ->
-    [];
-monitor_closed_socket(doc) ->
-    [];
 monitor_closed_socket(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(monitor_closed_socket,
@@ -31146,10 +30544,6 @@ mon_closed_socket(InitState) ->
 %% ("removed") when the controlling process terminates (without explicitly 
 %% calling the close function). For a IPv4 TCP (stream) socket.
 
-sc_cpe_socket_cleanup_tcp4(suite) ->
-    [];
-sc_cpe_socket_cleanup_tcp4(doc) ->
-    [];
 sc_cpe_socket_cleanup_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_cpe_socket_cleanup_tcp4,
@@ -31166,10 +30560,6 @@ sc_cpe_socket_cleanup_tcp4(_Config) when
 %% ("removed") when the controlling process terminates (without explicitly 
 %% calling the close function). For a IPv6 TCP (stream) socket.
 
-sc_cpe_socket_cleanup_tcp6(suite) ->
-    [];
-sc_cpe_socket_cleanup_tcp6(doc) ->
-    [];
 sc_cpe_socket_cleanup_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_cpe_socket_cleanup_tcp6,
@@ -31187,10 +30577,6 @@ sc_cpe_socket_cleanup_tcp6(_Config) when
 %% ("removed") when the controlling process terminates (without explicitly 
 %% calling the close function). For a Unix Domain (stream) socket (TCP).
 
-sc_cpe_socket_cleanup_tcpL(suite) ->
-    [];
-sc_cpe_socket_cleanup_tcpL(doc) ->
-    [];
 sc_cpe_socket_cleanup_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_cpe_socket_cleanup_tcpL,
@@ -31208,13 +30594,10 @@ sc_cpe_socket_cleanup_tcpL(_Config) when
 %% ("removed") when the controlling process terminates (without explicitly 
 %% calling the close function). For a IPv4 UDP (dgram) socket.
 
-sc_cpe_socket_cleanup_udp4(suite) ->
-    [];
-sc_cpe_socket_cleanup_udp4(doc) ->
-    [];
 sc_cpe_socket_cleanup_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_cpe_socket_cleanup_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain   => inet,
                                  type     => dgram,
@@ -31229,10 +30612,6 @@ sc_cpe_socket_cleanup_udp4(_Config) when
 %% (removed) when the controlling process terminates (without explicitly 
 %% calling the close function). For a IPv6 UDP (dgram) socket.
 
-sc_cpe_socket_cleanup_udp6(suite) ->
-    [];
-sc_cpe_socket_cleanup_udp6(doc) ->
-    [];
 sc_cpe_socket_cleanup_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_cpe_socket_cleanup_udp6,
@@ -31250,10 +30629,6 @@ sc_cpe_socket_cleanup_udp6(_Config) when
 %% ("removed") when the controlling process terminates (without explicitly 
 %% calling the close function). For a Unix Domain (dgram) socket (UDP).
 
-sc_cpe_socket_cleanup_udpL(suite) ->
-    [];
-sc_cpe_socket_cleanup_udpL(doc) ->
-    [];
 sc_cpe_socket_cleanup_udpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_cpe_socket_cleanup_udpL,
@@ -31412,13 +30787,10 @@ sc_cpe_socket_cleanup(InitState) ->
 %% 
 %% </KOLLA>
 
-sc_lc_recv_response_tcp4(suite) ->
-    [];
-sc_lc_recv_response_tcp4(doc) ->
-    [];
 sc_lc_recv_response_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_lc_recv_response_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv      = fun(Sock) -> socket:recv(Sock) end,
                    InitState = #{domain   => inet,
@@ -31433,10 +30805,6 @@ sc_lc_recv_response_tcp4(_Config) when i
 %% locally closed while the process is calling the recv function.
 %% Socket is IPv6.
 
-sc_lc_recv_response_tcp6(suite) ->
-    [];
-sc_lc_recv_response_tcp6(doc) ->
-    [];
 sc_lc_recv_response_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_lc_recv_response_tcp6,
@@ -31455,10 +30823,6 @@ sc_lc_recv_response_tcp6(_Config) when i
 %% locally closed while the process is calling the recv function.
 %% Socket is Unix Domain (stream) socket.
 
-sc_lc_recv_response_tcpL(suite) ->
-    [];
-sc_lc_recv_response_tcpL(doc) ->
-    [];
 sc_lc_recv_response_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_lc_recv_response_tcpL,
@@ -32099,13 +31463,10 @@ sc_lc_receive_response_tcp(InitState) ->
 %% Socket is IPv4.
 %% 
 
-sc_lc_recvfrom_response_udp4(suite) ->
-    [];
-sc_lc_recvfrom_response_udp4(doc) ->
-    [];
 sc_lc_recvfrom_response_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_lc_recvfrom_response_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv      = fun(Sock, To) -> socket:recvfrom(Sock, [], To) end,
                    InitState = #{domain   => inet,
@@ -32120,10 +31481,6 @@ sc_lc_recvfrom_response_udp4(_Config) wh
 %% locally closed while the process is calling the recv function.
 %% Socket is IPv6.
 
-sc_lc_recvfrom_response_udp6(suite) ->
-    [];
-sc_lc_recvfrom_response_udp6(doc) ->
-    [];
 sc_lc_recvfrom_response_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_lc_recvfrom_response_udp6,
@@ -32142,10 +31499,6 @@ sc_lc_recvfrom_response_udp6(_Config) wh
 %% locally closed while the process is calling the recv function.
 %% Socket is Unix Domainm (dgram) socket.
 
-sc_lc_recvfrom_response_udpL(suite) ->
-    [];
-sc_lc_recvfrom_response_udpL(doc) ->
-    [];
 sc_lc_recvfrom_response_udpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_lc_recvfrom_response_udpL,
@@ -32571,13 +31924,10 @@ sc_lc_receive_response_udp(InitState) ->
 %% locally closed while the process is calling the recvmsg function.
 %% Socket is IPv4.
 
-sc_lc_recvmsg_response_tcp4(suite) ->
-    [];
-sc_lc_recvmsg_response_tcp4(doc) ->
-    [];
 sc_lc_recvmsg_response_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_lc_recvmsg_response_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv      = fun(Sock) -> socket:recvmsg(Sock) end,
                    InitState = #{domain   => inet,
@@ -32592,10 +31942,6 @@ sc_lc_recvmsg_response_tcp4(_Config) whe
 %% locally closed while the process is calling the recvmsg function.
 %% Socket is IPv6.
 
-sc_lc_recvmsg_response_tcp6(suite) ->
-    [];
-sc_lc_recvmsg_response_tcp6(doc) ->
-    [];
 sc_lc_recvmsg_response_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_recvmsg_response_tcp6,
@@ -32614,10 +31960,6 @@ sc_lc_recvmsg_response_tcp6(_Config) whe
 %% locally closed while the process is calling the recvmsg function.
 %% Socket is Unix Domain (stream) socket.
 
-sc_lc_recvmsg_response_tcpL(suite) ->
-    [];
-sc_lc_recvmsg_response_tcpL(doc) ->
-    [];
 sc_lc_recvmsg_response_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_recvmsg_response_tcpL,
@@ -32636,12 +31978,9 @@ sc_lc_recvmsg_response_tcpL(_Config) whe
 %% locally closed while the process is calling the recvmsg function.
 %% Socket is IPv4.
 
-sc_lc_recvmsg_response_udp4(suite) ->
-    [];
-sc_lc_recvmsg_response_udp4(doc) ->
-    [];
 sc_lc_recvmsg_response_udp4(_Config) when is_list(_Config) ->
     tc_try(sc_lc_recvmsg_response_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ?TT(?SECS(10)),
                    Recv      = fun(Sock, To) -> socket:recvmsg(Sock, To) end,
@@ -32657,10 +31996,6 @@ sc_lc_recvmsg_response_udp4(_Config) whe
 %% locally closed while the process is calling the recvmsg function.
 %% Socket is IPv6.
 
-sc_lc_recvmsg_response_udp6(suite) ->
-    [];
-sc_lc_recvmsg_response_udp6(doc) ->
-    [];
 sc_lc_recvmsg_response_udp6(_Config) when is_list(_Config) ->
     tc_try(sc_recvmsg_response_udp6,
            fun() -> has_support_ipv6() end,
@@ -32680,10 +32015,6 @@ sc_lc_recvmsg_response_udp6(_Config) whe
 %% locally closed while the process is calling the recvmsg function.
 %% Socket is Unix Domain (dgram) socket.
 
-sc_lc_recvmsg_response_udpL(suite) ->
-    [];
-sc_lc_recvmsg_response_udpL(doc) ->
-    [];
 sc_lc_recvmsg_response_udpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_recvmsg_response_udpL,
@@ -32705,13 +32036,10 @@ sc_lc_recvmsg_response_udpL(_Config) whe
 %% git the setup anyway.
 %% Socket is IPv4.
 
-sc_lc_acceptor_response_tcp4(suite) ->
-    [];
-sc_lc_acceptor_response_tcp4(doc) ->
-    [];
 sc_lc_acceptor_response_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_lc_acceptor_response_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain   => inet,
                                  protocol => tcp},
@@ -32726,10 +32054,6 @@ sc_lc_acceptor_response_tcp4(_Config) wh
 %% git the setup anyway.
 %% Socket is IPv6.
 
-sc_lc_acceptor_response_tcp6(suite) ->
-    [];
-sc_lc_acceptor_response_tcp6(doc) ->
-    [];
 sc_lc_acceptor_response_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_lc_acceptor_response_tcp6,
@@ -32748,10 +32072,6 @@ sc_lc_acceptor_response_tcp6(_Config) wh
 %% git the setup anyway.
 %% Socket is Unix Domain (stream) socket.
 
-sc_lc_acceptor_response_tcpL(suite) ->
-    [];
-sc_lc_acceptor_response_tcpL(doc) ->
-    [];
 sc_lc_acceptor_response_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_lc_acceptor_response_tcpL,
@@ -33176,13 +32496,10 @@ sc_lc_acceptor_response_tcp(InitState) -
 %% now, we will make do with different VMs on the same host.
 %%
 
-sc_rc_recv_response_tcp4(suite) ->
-    [];
-sc_rc_recv_response_tcp4(doc) ->
-    [];
 sc_rc_recv_response_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_rc_recv_response_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv      = fun(Sock) -> socket:recv(Sock) end,
                    InitState = #{domain   => inet,
@@ -33197,10 +32514,6 @@ sc_rc_recv_response_tcp4(_Config) when i
 %% remotely closed while the process is calling the recv function.
 %% Socket is IPv6.
 
-sc_rc_recv_response_tcp6(suite) ->
-    [];
-sc_rc_recv_response_tcp6(doc) ->
-    [];
 sc_rc_recv_response_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_rc_recv_response_tcp6,
@@ -33219,10 +32532,6 @@ sc_rc_recv_response_tcp6(_Config) when i
 %% remotely closed while the process is calling the recv function.
 %% Socket is Unix Domain (stream) socket.
 
-sc_rc_recv_response_tcpL(suite) ->
-    [];
-sc_rc_recv_response_tcpL(doc) ->
-    [];
 sc_rc_recv_response_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_rc_recv_response_tcpL,
@@ -34161,13 +33470,10 @@ sc_rc_tcp_handler_announce_ready(Parent,
 %% remotely closed while the process is calling the recvmsg function.
 %% Socket is IPv4.
 
-sc_rc_recvmsg_response_tcp4(suite) ->
-    [];
-sc_rc_recvmsg_response_tcp4(doc) ->
-    [];
 sc_rc_recvmsg_response_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_rc_recvmsg_response_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    Recv      = fun(Sock) -> socket:recvmsg(Sock) end,
                    InitState = #{domain   => inet,
@@ -34182,10 +33488,6 @@ sc_rc_recvmsg_response_tcp4(_Config) whe
 %% remotely closed while the process is calling the recvmsg function.
 %% Socket is IPv6.
 
-sc_rc_recvmsg_response_tcp6(suite) ->
-    [];
-sc_rc_recvmsg_response_tcp6(doc) ->
-    [];
 sc_rc_recvmsg_response_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_rc_recvmsg_response_tcp6,
@@ -34204,10 +33506,6 @@ sc_rc_recvmsg_response_tcp6(_Config) whe
 %% remotely closed while the process is calling the recvmsg function.
 %% Socket is Unix Domain (stream) socket.
 
-sc_rc_recvmsg_response_tcpL(suite) ->
-    [];
-sc_rc_recvmsg_response_tcpL(doc) ->
-    [];
 sc_rc_recvmsg_response_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_rc_recvmsg_response_tcpL,
@@ -34234,13 +33532,10 @@ sc_rc_recvmsg_response_tcpL(_Config) whe
 %% This would of course not work for Unix Domain sockets.
 %%
 
-sc_rs_recv_send_shutdown_receive_tcp4(suite) ->
-    [];
-sc_rs_recv_send_shutdown_receive_tcp4(doc) ->
-    [];
 sc_rs_recv_send_shutdown_receive_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(sc_rs_recv_send_shutdown_receive_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    MsgData   = ?DATA,
                    Recv      = fun(Sock) ->
@@ -34265,10 +33560,6 @@ sc_rs_recv_send_shutdown_receive_tcp4(_C
 %% reader attempts a recv.
 %% Socket is IPv6.
 
-sc_rs_recv_send_shutdown_receive_tcp6(suite) ->
-    [];
-sc_rs_recv_send_shutdown_receive_tcp6(doc) ->
-    [];
 sc_rs_recv_send_shutdown_receive_tcp6(_Config) when is_list(_Config) ->
     tc_try(sc_rs_recv_send_shutdown_receive_tcp6,
            fun() -> has_support_ipv6() end,
@@ -34297,10 +33588,6 @@ sc_rs_recv_send_shutdown_receive_tcp6(_C
 %% reader attempts a recv.
 %% Socket is Unix Domain (stream) socket.
 
-sc_rs_recv_send_shutdown_receive_tcpL(suite) ->
-    [];
-sc_rs_recv_send_shutdown_receive_tcpL(doc) ->
-    [];
 sc_rs_recv_send_shutdown_receive_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_rs_recv_send_shutdown_receive_tcpL,
@@ -35143,12 +34430,9 @@ sc_rs_tcp_handler_announce_ready(Parent,
 %% reader attempts a recv.
 %% Socket is IPv4.
 
-sc_rs_recvmsg_send_shutdown_receive_tcp4(suite) ->
-    [];
-sc_rs_recvmsg_send_shutdown_receive_tcp4(doc) ->
-    [];
 sc_rs_recvmsg_send_shutdown_receive_tcp4(_Config) when is_list(_Config) ->
     tc_try(sc_rs_recvmsg_send_shutdown_receive_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ?TT(?SECS(30)),
                    MsgData   = ?DATA,
@@ -35182,10 +34466,6 @@ sc_rs_recvmsg_send_shutdown_receive_tcp4
 %% reader attempts a recv.
 %% Socket is IPv6.
 
-sc_rs_recvmsg_send_shutdown_receive_tcp6(suite) ->
-    [];
-sc_rs_recvmsg_send_shutdown_receive_tcp6(doc) ->
-    [];
 sc_rs_recvmsg_send_shutdown_receive_tcp6(_Config) when is_list(_Config) ->
     tc_try(sc_rs_recvmsg_send_shutdown_receive_tcp6,
            fun() -> has_support_ipv6() end,
@@ -35222,10 +34502,6 @@ sc_rs_recvmsg_send_shutdown_receive_tcp6
 %% reader attempts a recv.
 %% Socket is UNix Domain (stream) socket.
 
-sc_rs_recvmsg_send_shutdown_receive_tcpL(suite) ->
-    [];
-sc_rs_recvmsg_send_shutdown_receive_tcpL(doc) ->
-    [];
 sc_rs_recvmsg_send_shutdown_receive_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(sc_rs_recvmsg_send_shutdown_receive_tcpL,
@@ -35271,10 +34547,6 @@ sc_rs_recvmsg_send_shutdown_receive_tcpL
 %% This test case is intended to (simply) test "some" ioctl features.
 %%
 
-ioctl_simple1(suite) ->
-    [];
-ioctl_simple1(doc) ->
-    [];
 ioctl_simple1(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -35357,10 +34629,6 @@ do_ioctl_simple(_State) ->
 %% request(s).
 %%
 
-ioctl_get_gifname(suite) ->
-    [];
-ioctl_get_gifname(doc) ->
-    [];
 ioctl_get_gifname(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -35410,10 +34678,6 @@ do_ioctl_get_gifname(_State) ->
 
 %% --- gifindex ---
 
-ioctl_get_gifindex(suite) ->
-    [];
-ioctl_get_gifindex(doc) ->
-    [];
 ioctl_get_gifindex(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -35465,10 +34729,6 @@ do_ioctl_get_gifindex(_State) ->
 
 %% --- gifaddr ---
 
-ioctl_get_gifaddr(suite) ->
-    [];
-ioctl_get_gifaddr(doc) ->
-    [];
 ioctl_get_gifaddr(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -35532,10 +34792,6 @@ do_ioctl_get_gifaddr(_State) ->
 
 %% --- gifdstaddr ---
 
-ioctl_get_gifdstaddr(suite) ->
-    [];
-ioctl_get_gifdstaddr(doc) ->
-    [];
 ioctl_get_gifdstaddr(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -35550,17 +34806,17 @@ ioctl_get_gifdstaddr(_Config) when is_li
 
 
 do_ioctl_get_gifdstaddr(_State) ->
-    Domain = inet,
+    Domain = inet_or_inet6(),
     LSA    = which_local_socket_addr(Domain),
 
     i("create and init listen stream:TCP socket"),
-    {ok, LSock} = socket:open(inet, stream, tcp),
+    {ok, LSock} = socket:open(Domain, stream, tcp),
     ok = socket:bind(LSock, LSA#{port => 0}),
     ok = socket:listen(LSock),
     {ok, #{port := LPort}} = socket:sockname(LSock),
     
     i("create and init connection stream:TCP socket"),
-    {ok, CSock} = socket:open(inet, stream, tcp),
+    {ok, CSock} = socket:open(Domain, stream, tcp),
 
     i("attempt connect (nowait)"),
     {ok, ASock} =
@@ -35625,16 +34881,13 @@ verify_gifdstaddr(Sock, Prefix, IfIdx, I
               "~n      ~p", [Prefix, IfName, IfIdx, Crap]),
             socket:close(Sock),
             ?FAIL({unexpected_addr, Prefix, IfName, IfIdx, Crap});
-        {error, eaddrnotavail = Reason} ->
+        {error, IgnoredReason} when IgnoredReason =:= eaddrnotavail;
+                                    IgnoredReason =:= eperm;
+                                    IgnoredReason =:= enotty ->
             i("[~s] got unexpected error for interface ~p (~w) => "
               "SKIP interface"
-              "~n      Reason: ~p", [Prefix, IfName, IfIdx, Reason]),
+              "~n      Reason: ~p", [Prefix, IfName, IfIdx, IgnoredReason]),
             ignore;
-	{error, eperm = Reason} ->
-	    i("[~s] got unexpected error for interface ~p (~w) => "
-	      "SKIP interface"
-	      "~n      Reason: ~p", [Prefix, IfName, IfIdx, Reason]),
-	    ignore;
 	{error, einval = Reason} when (OsFam =:= unix) andalso
                                       ((OsName =:= darwin) orelse 
                                        (OsName =:= freebsd) orelse 
@@ -35656,10 +34909,6 @@ verify_gifdstaddr(Sock, Prefix, IfIdx, I
 
 %% --- gifbrdaddr ---
 
-ioctl_get_gifbrdaddr(suite) ->
-    [];
-ioctl_get_gifbrdaddr(doc) ->
-    [];
 ioctl_get_gifbrdaddr(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -35674,17 +34923,17 @@ ioctl_get_gifbrdaddr(_Config) when is_li
 
 
 do_ioctl_get_gifbrdaddr(_State) ->
-    Domain = inet,
+    Domain = inet_or_inet6(),
     LSA    = which_local_socket_addr(Domain),
 
     i("create and init listen stream:TCP socket"),
-    {ok, LSock} = socket:open(inet, stream, tcp),
+    {ok, LSock} = socket:open(Domain, stream, tcp),
     ok = socket:bind(LSock, LSA#{port => 0}),
     ok = socket:listen(LSock),
     {ok, #{port := LPort}} = socket:sockname(LSock),
     
     i("create and init connection stream:TCP socket"),
-    {ok, CSock} = socket:open(inet, stream, tcp),
+    {ok, CSock} = socket:open(Domain, stream, tcp),
 
     i("attempt connect (nowait)"),
     {ok, ASock} =
@@ -35748,16 +34997,13 @@ verify_gifbrdaddr(Sock, Prefix, IfIdx, I
               "~n      ~p", [Prefix, IfName, IfIdx, Crap]),
             socket:close(Sock),
             ?FAIL({unexpected_addr, IfName, IfIdx, Crap});
-        {error, eaddrnotavail = Reason} ->
+        {error, IgnoredReason} when IgnoredReason =:= eaddrnotavail;
+                                    IgnoredReason =:= eperm;
+                                    IgnoredReason =:= enotty ->
             i("[~s] got unexpected error for interface ~p (~w) => "
-	      "SKIP interface"
-              "~n      Reason: ~p", [Prefix, IfName, IfIdx, Reason]),
+             "SKIP interface"
+              "~n      Reason: ~p", [Prefix, IfName, IfIdx, IgnoredReason]),
             ignore;
-	{error, eperm = Reason} ->
-	    i("[~s] got unexpected error for interface ~p (~w) => "
-	      "SKIP interface"
-	      "~n      Reason: ~p", [Prefix, IfName, IfIdx, Reason]),
-	    ignore;
 	{error, einval = Reason} when (OsFam =:= unix) andalso
                                       ((OsName =:= darwin) orelse
                                        (OsName =:= freebsd) orelse
@@ -35778,10 +35024,6 @@ verify_gifbrdaddr(Sock, Prefix, IfIdx, I
 
 %% --- gifnetmask ---
 
-ioctl_get_gifnetmask(suite) ->
-    [];
-ioctl_get_gifnetmask(doc) ->
-    [];
 ioctl_get_gifnetmask(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -35844,10 +35086,6 @@ do_ioctl_get_gifnetmask(_State) ->
 
 %% --- gifmtu ---
 
-ioctl_get_gifmtu(suite) ->
-    [];
-ioctl_get_gifmtu(doc) ->
-    [];
 ioctl_get_gifmtu(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -35900,10 +35138,6 @@ do_ioctl_get_gifmtu(_State) ->
 
 %% --- gifhwaddr ---
 
-ioctl_get_gifhwaddr(suite) ->
-    [];
-ioctl_get_gifhwaddr(doc) ->
-    [];
 ioctl_get_gifhwaddr(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -35971,10 +35205,6 @@ do_ioctl_get_gifhwaddr(_State) ->
 
 %% --- giftxqlen ---
 
-ioctl_get_giftxqlen(suite) ->
-    [];
-ioctl_get_giftxqlen(doc) ->
-    [];
 ioctl_get_giftxqlen(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -36027,10 +35257,6 @@ do_ioctl_get_giftxqlen(_State) ->
 
 %% --- gifflags ---
 
-ioctl_get_gifflags(suite) ->
-    [];
-ioctl_get_gifflags(doc) ->
-    [];
 ioctl_get_gifflags(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -36099,10 +35325,6 @@ do_ioctl_get_gifflags(_State) ->
 
 %% --- gifmap ---
 
-ioctl_get_gifmap(suite) ->
-    [];
-ioctl_get_gifmap(doc) ->
-    [];
 ioctl_get_gifmap(_Config) when is_list(_Config) ->
     ?TT(?SECS(5)),
     tc_try(?FUNCTION_NAME,
@@ -36160,13 +35382,10 @@ do_ioctl_get_gifmap(_State) ->
 %% So that its easy to extend, we use fun's for read and write.
 %% We use TCP on IPv4.
 
-traffic_send_and_recv_counters_tcp4(suite) ->
-    [];
-traffic_send_and_recv_counters_tcp4(doc) ->
-    [];
 traffic_send_and_recv_counters_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_send_and_recv_counters_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain => inet,
                                  proto  => tcp,
@@ -36182,10 +35401,6 @@ traffic_send_and_recv_counters_tcp4(_Con
 %% So that its easy to extend, we use fun's for read and write.
 %% We use TCP on IPv6.
 
-traffic_send_and_recv_counters_tcp6(suite) ->
-    [];
-traffic_send_and_recv_counters_tcp6(doc) ->
-    [];
 traffic_send_and_recv_counters_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_send_and_recv_counters_tcp6,
@@ -36205,10 +35420,6 @@ traffic_send_and_recv_counters_tcp6(_Con
 %% So that its easy to extend, we use fun's for read and write.
 %% We use default (TCP) on local.
 
-traffic_send_and_recv_counters_tcpL(suite) ->
-    [];
-traffic_send_and_recv_counters_tcpL(doc) ->
-    [];
 traffic_send_and_recv_counters_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_send_and_recv_counters_tcpL,
@@ -36228,13 +35439,10 @@ traffic_send_and_recv_counters_tcpL(_Con
 %% So that its easy to extend, we use fun's for read and write.
 %% We use TCP on IPv4.
 
-traffic_sendmsg_and_recvmsg_counters_tcp4(suite) ->
-    [];
-traffic_sendmsg_and_recvmsg_counters_tcp4(doc) ->
-    [];
 traffic_sendmsg_and_recvmsg_counters_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_sendmsg_and_recvmsg_counters_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain => inet,
                                  proto  => tcp,
@@ -36260,10 +35468,6 @@ traffic_sendmsg_and_recvmsg_counters_tcp
 %% So that its easy to extend, we use fun's for read and write.
 %% We use TCP on IPv6.
 
-traffic_sendmsg_and_recvmsg_counters_tcp6(suite) ->
-    [];
-traffic_sendmsg_and_recvmsg_counters_tcp6(doc) ->
-    [];
 traffic_sendmsg_and_recvmsg_counters_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_sendmsg_and_recvmsg_counters_tcp6,
@@ -36293,10 +35497,6 @@ traffic_sendmsg_and_recvmsg_counters_tcp
 %% So that its easy to extend, we use fun's for read and write.
 %% We use default (TCP) on local.
 
-traffic_sendmsg_and_recvmsg_counters_tcpL(suite) ->
-    [];
-traffic_sendmsg_and_recvmsg_counters_tcpL(doc) ->
-    [];
 traffic_sendmsg_and_recvmsg_counters_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_sendmsg_and_recvmsg_counters_tcpL,
@@ -37365,13 +36565,10 @@ traffic_sar_counters_validation2(Counter
 %% So that its easy to extend, we use fun's for read and write.
 %% We use UDP on IPv4.
 
-traffic_sendto_and_recvfrom_counters_udp4(suite) ->
-    [];
-traffic_sendto_and_recvfrom_counters_udp4(doc) ->
-    [];
 traffic_sendto_and_recvfrom_counters_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_sendto_and_recvfrom_counters_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain => inet,
                                  proto  => udp,
@@ -37391,10 +36588,6 @@ traffic_sendto_and_recvfrom_counters_udp
 %% So that its easy to extend, we use fun's for read and write.
 %% We use UDP on IPv6.
 
-traffic_sendto_and_recvfrom_counters_udp6(suite) ->
-    [];
-traffic_sendto_and_recvfrom_counters_udp6(doc) ->
-    [];
 traffic_sendto_and_recvfrom_counters_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_sendto_and_recvfrom_counters_udp6,
@@ -37418,10 +36611,6 @@ traffic_sendto_and_recvfrom_counters_udp
 %% So that its easy to extend, we use fun's for read and write.
 %% We use default (UDP) on local.
 
-traffic_sendto_and_recvfrom_counters_udpL(suite) ->
-    [];
-traffic_sendto_and_recvfrom_counters_udpL(doc) ->
-    [];
 traffic_sendto_and_recvfrom_counters_udpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_sendto_and_recvfrom_counters_udp4,
@@ -37445,13 +36634,10 @@ traffic_sendto_and_recvfrom_counters_udp
 %% So that its easy to extend, we use fun's for read and write.
 %% We use UDP on IPv4.
 
-traffic_sendmsg_and_recvmsg_counters_udp4(suite) ->
-    [];
-traffic_sendmsg_and_recvmsg_counters_udp4(doc) ->
-    [];
 traffic_sendmsg_and_recvmsg_counters_udp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_sendmsg_and_recvmsg_counters_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain => inet,
                                  proto  => udp,
@@ -37479,10 +36665,6 @@ traffic_sendmsg_and_recvmsg_counters_udp
 %% So that its easy to extend, we use fun's for read and write.
 %% We use UDP on IPv6.
 
-traffic_sendmsg_and_recvmsg_counters_udp6(suite) ->
-    [];
-traffic_sendmsg_and_recvmsg_counters_udp6(doc) ->
-    [];
 traffic_sendmsg_and_recvmsg_counters_udp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_sendmsg_and_recvmsg_counters_udp6,
@@ -37514,10 +36696,6 @@ traffic_sendmsg_and_recvmsg_counters_udp
 %% So that its easy to extend, we use fun's for read and write.
 %% We use default (UDP) on local.
 
-traffic_sendmsg_and_recvmsg_counters_udpL(suite) ->
-    [];
-traffic_sendmsg_and_recvmsg_counters_udpL(doc) ->
-    [];
 traffic_sendmsg_and_recvmsg_counters_udpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(15)),
     tc_try(traffic_sendmsg_and_recvmsg_counters_udpL,
@@ -38377,13 +37555,10 @@ traffic_send_and_recv_udp(InitState) ->
 %% Second, send in a bunch of "small" chunks, and read in one "big" chunk.
 %% Socket is IPv4.
 
-traffic_send_and_recv_chunks_tcp4(suite) ->
-    [];
-traffic_send_and_recv_chunks_tcp4(doc) ->
-    [];
 traffic_send_and_recv_chunks_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(traffic_send_and_recv_chunks_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain => inet,
                                  proto  => tcp},
@@ -38399,10 +37574,6 @@ traffic_send_and_recv_chunks_tcp4(_Confi
 %% Second, send in a bunch of "small" chunks, and read in one "big" chunk.
 %% Socket is IPv6.
 
-traffic_send_and_recv_chunks_tcp6(suite) ->
-    [];
-traffic_send_and_recv_chunks_tcp6(doc) ->
-    [];
 traffic_send_and_recv_chunks_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(traffic_send_and_recv_chunks_tcp6,
@@ -38421,10 +37592,6 @@ traffic_send_and_recv_chunks_tcp6(_Confi
 %% Second, send in a bunch of "small" chunks, and read in one "big" chunk.
 %% Socket is UNix Domain (Stream) socket.
 
-traffic_send_and_recv_chunks_tcpL(suite) ->
-    [];
-traffic_send_and_recv_chunks_tcpL(doc) ->
-    [];
 traffic_send_and_recv_chunks_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(30)),
     tc_try(traffic_send_and_recv_chunks_tcp6,
@@ -39457,15 +38624,12 @@ traffic_snr_tcp_client_await_terminate(P
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for IPv4.
 
-traffic_ping_pong_small_send_and_recv_tcp4(suite) ->
-    [];
-traffic_ping_pong_small_send_and_recv_tcp4(doc) ->
-    [];
 traffic_ping_pong_small_send_and_recv_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(15)),
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
     tc_try(traffic_ping_pong_small_send_and_recv_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain => inet,
                                  proto  => tcp,
@@ -39485,10 +38649,6 @@ traffic_ping_pong_small_send_and_recv_tc
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for IPv6.
 
-traffic_ping_pong_small_send_and_recv_tcp6(suite) ->
-    [];
-traffic_ping_pong_small_send_and_recv_tcp6(doc) ->
-    [];
 traffic_ping_pong_small_send_and_recv_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(15)),
     Msg = l2b(?TPP_SMALL),
@@ -39513,10 +38673,6 @@ traffic_ping_pong_small_send_and_recv_tc
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for Unix Domain (stream) socket.
 
-traffic_ping_pong_small_send_and_recv_tcpL(suite) ->
-    [];
-traffic_ping_pong_small_send_and_recv_tcpL(doc) ->
-    [];
 traffic_ping_pong_small_send_and_recv_tcpL(Config) when is_list(Config) ->
     ?TT(?SECS(15)),
     Msg = l2b(?TPP_SMALL),
@@ -39541,14 +38697,11 @@ traffic_ping_pong_small_send_and_recv_tc
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for IPv4.
 
-traffic_ping_pong_medium_send_and_recv_tcp4(suite) ->
-    [];
-traffic_ping_pong_medium_send_and_recv_tcp4(doc) ->
-    [];
 traffic_ping_pong_medium_send_and_recv_tcp4(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
     tc_try(traffic_ping_pong_medium_send_and_recv_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ?TT(?SECS(30)),
                    InitState = #{domain => inet,
@@ -39568,10 +38721,6 @@ traffic_ping_pong_medium_send_and_recv_t
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for IPv6.
 
-traffic_ping_pong_medium_send_and_recv_tcp6(suite) ->
-    [];
-traffic_ping_pong_medium_send_and_recv_tcp6(doc) ->
-    [];
 traffic_ping_pong_medium_send_and_recv_tcp6(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
@@ -39597,10 +38746,6 @@ traffic_ping_pong_medium_send_and_recv_t
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for Unix Domain (stream) socket.
 
-traffic_ping_pong_medium_send_and_recv_tcpL(suite) ->
-    [];
-traffic_ping_pong_medium_send_and_recv_tcpL(doc) ->
-    [];
 traffic_ping_pong_medium_send_and_recv_tcpL(Config) when is_list(Config) ->
     ?TT(?SECS(30)),
     Msg = l2b(?TPP_MEDIUM),
@@ -39626,16 +38771,13 @@ traffic_ping_pong_medium_send_and_recv_t
 %% repeated a set number of times (more times the small the message).
 %% This is the 'large' message test case, for IPv4.
 
-traffic_ping_pong_large_send_and_recv_tcp4(suite) ->
-    [];
-traffic_ping_pong_large_send_and_recv_tcp4(doc) ->
-    [];
 traffic_ping_pong_large_send_and_recv_tcp4(Config) when is_list(Config) ->
     ?TT(?SECS(60)),
     Msg = l2b(?TPP_LARGE),
     Num = ?TPP_NUM(Config, ?TPP_LARGE_NUM),
     tc_try(traffic_ping_pong_large_send_and_recv_tcp4,
-           fun() -> is_old_fedora16(),
+           fun() -> has_support_ipv4(),
+                    is_old_fedora16(),
 		    is_slow_ubuntu(Config) end,
            fun() ->
                    InitState = #{domain => inet,
@@ -39655,10 +38797,6 @@ traffic_ping_pong_large_send_and_recv_tc
 %% repeated a set number of times (more times the small the message).
 %% This is the 'large' message test case, for IPv6.
 
-traffic_ping_pong_large_send_and_recv_tcp6(suite) ->
-    [];
-traffic_ping_pong_large_send_and_recv_tcp6(doc) ->
-    [];
 traffic_ping_pong_large_send_and_recv_tcp6(Config) when is_list(Config) ->
     ?TT(?SECS(60)),
     Msg = l2b(?TPP_LARGE),
@@ -39686,10 +38824,6 @@ traffic_ping_pong_large_send_and_recv_tc
 %% repeated a set number of times (more times the small the message).
 %% This is the 'large' message test case, for UNix Domain (stream) socket.
 
-traffic_ping_pong_large_send_and_recv_tcpL(suite) ->
-    [];
-traffic_ping_pong_large_send_and_recv_tcpL(doc) ->
-    [];
 traffic_ping_pong_large_send_and_recv_tcpL(Config) when is_list(Config) ->
     ?TT(?SECS(60)),
     Msg = l2b(?TPP_LARGE),
@@ -39774,14 +38908,11 @@ is_slow_ubuntu(Config) ->
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for IPv4.
 
-traffic_ping_pong_small_sendto_and_recvfrom_udp4(suite) ->
-    [];
-traffic_ping_pong_small_sendto_and_recvfrom_udp4(doc) ->
-    [];
 traffic_ping_pong_small_sendto_and_recvfrom_udp4(Config) when is_list(Config) ->
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
     tc_try(traffic_ping_pong_small_sendto_and_recvfrom_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ?TT(?SECS(45)),
                    InitState = #{domain => inet,
@@ -39801,10 +38932,6 @@ traffic_ping_pong_small_sendto_and_recvf
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for IPv6.
 
-traffic_ping_pong_small_sendto_and_recvfrom_udp6(suite) ->
-    [];
-traffic_ping_pong_small_sendto_and_recvfrom_udp6(doc) ->
-    [];
 traffic_ping_pong_small_sendto_and_recvfrom_udp6(Config) when is_list(Config) ->
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
@@ -39830,10 +38957,6 @@ traffic_ping_pong_small_sendto_and_recvf
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for Unix Domain (dgram) socket.
 
-traffic_ping_pong_small_sendto_and_recvfrom_udpL(suite) ->
-    [];
-traffic_ping_pong_small_sendto_and_recvfrom_udpL(doc) ->
-    [];
 traffic_ping_pong_small_sendto_and_recvfrom_udpL(Config) when is_list(Config) ->
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
@@ -39859,14 +38982,11 @@ traffic_ping_pong_small_sendto_and_recvf
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for IPv4.
 
-traffic_ping_pong_medium_sendto_and_recvfrom_udp4(suite) ->
-    [];
-traffic_ping_pong_medium_sendto_and_recvfrom_udp4(doc) ->
-    [];
 traffic_ping_pong_medium_sendto_and_recvfrom_udp4(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
     tc_try(traffic_ping_pong_medium_sendto_and_recvfrom_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ?TT(?SECS(45)),
                    InitState = #{domain => inet,
@@ -39886,10 +39006,6 @@ traffic_ping_pong_medium_sendto_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for IPv6.
 
-traffic_ping_pong_medium_sendto_and_recvfrom_udp6(suite) ->
-    [];
-traffic_ping_pong_medium_sendto_and_recvfrom_udp6(doc) ->
-    [];
 traffic_ping_pong_medium_sendto_and_recvfrom_udp6(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
@@ -39915,10 +39031,6 @@ traffic_ping_pong_medium_sendto_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for Unix Domain (dgram) socket.
 
-traffic_ping_pong_medium_sendto_and_recvfrom_udpL(suite) ->
-    [];
-traffic_ping_pong_medium_sendto_and_recvfrom_udpL(doc) ->
-    [];
 traffic_ping_pong_medium_sendto_and_recvfrom_udpL(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
@@ -39944,14 +39056,11 @@ traffic_ping_pong_medium_sendto_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for IPv4.
 
-traffic_ping_pong_small_sendmsg_and_recvmsg_tcp4(suite) ->
-    [];
-traffic_ping_pong_small_sendmsg_and_recvmsg_tcp4(doc) ->
-    [];
 traffic_ping_pong_small_sendmsg_and_recvmsg_tcp4(Config) when is_list(Config) ->
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
     tc_try(traffic_ping_pong_small_sendmsg_and_recvmsg_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ?TT(?SECS(20)),
                    InitState = #{domain => inet,
@@ -39971,10 +39080,6 @@ traffic_ping_pong_small_sendmsg_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for IPv6.
 
-traffic_ping_pong_small_sendmsg_and_recvmsg_tcp6(suite) ->
-    [];
-traffic_ping_pong_small_sendmsg_and_recvmsg_tcp6(doc) ->
-    [];
 traffic_ping_pong_small_sendmsg_and_recvmsg_tcp6(Config) when is_list(Config) ->
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
@@ -39999,10 +39104,6 @@ traffic_ping_pong_small_sendmsg_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for Unix Domain (stream) socket.
 
-traffic_ping_pong_small_sendmsg_and_recvmsg_tcpL(suite) ->
-    [];
-traffic_ping_pong_small_sendmsg_and_recvmsg_tcpL(doc) ->
-    [];
 traffic_ping_pong_small_sendmsg_and_recvmsg_tcpL(Config) when is_list(Config) ->
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
@@ -40027,14 +39128,11 @@ traffic_ping_pong_small_sendmsg_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for IPv4.
 
-traffic_ping_pong_medium_sendmsg_and_recvmsg_tcp4(suite) ->
-    [];
-traffic_ping_pong_medium_sendmsg_and_recvmsg_tcp4(doc) ->
-    [];
 traffic_ping_pong_medium_sendmsg_and_recvmsg_tcp4(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
     tc_try(traffic_ping_pong_medium_sendmsg_and_recvmsg_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ?TT(?SECS(30)),
                    InitState = #{domain => inet,
@@ -40054,10 +39152,6 @@ traffic_ping_pong_medium_sendmsg_and_rec
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for IPv6.
 
-traffic_ping_pong_medium_sendmsg_and_recvmsg_tcp6(suite) ->
-    [];
-traffic_ping_pong_medium_sendmsg_and_recvmsg_tcp6(doc) ->
-    [];
 traffic_ping_pong_medium_sendmsg_and_recvmsg_tcp6(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
@@ -40082,10 +39176,6 @@ traffic_ping_pong_medium_sendmsg_and_rec
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for Unix Domain (stream) socket.
 
-traffic_ping_pong_medium_sendmsg_and_recvmsg_tcpL(suite) ->
-    [];
-traffic_ping_pong_medium_sendmsg_and_recvmsg_tcpL(doc) ->
-    [];
 traffic_ping_pong_medium_sendmsg_and_recvmsg_tcpL(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
@@ -40110,15 +39200,11 @@ traffic_ping_pong_medium_sendmsg_and_rec
 %% repeated a set number of times (more times the small the message).
 %% This is the 'large' message test case, for IPv4.
 
-traffic_ping_pong_large_sendmsg_and_recvmsg_tcp4(suite) ->
-    [];
-traffic_ping_pong_large_sendmsg_and_recvmsg_tcp4(doc) ->
-    [];
 traffic_ping_pong_large_sendmsg_and_recvmsg_tcp4(Config) when is_list(Config) ->
     Msg = l2b(?TPP_LARGE),
     Num = ?TPP_NUM(Config, ?TPP_LARGE_NUM),
     tc_try(traffic_ping_pong_large_sendmsg_and_recvmsg_tcp4,
-           fun() -> traffic_ping_pong_large_sendmsg_and_recvmsg_cond() end,
+           fun() -> has_support_ipv4(), traffic_ping_pong_large_sendmsg_and_recvmsg_cond() end,
            fun() ->
                    ?TT(?SECS(60)),
                    InitState = #{domain => inet,
@@ -40148,10 +39234,6 @@ traffic_ping_pong_large_sendmsg_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'large' message test case, for IPv6.
 
-traffic_ping_pong_large_sendmsg_and_recvmsg_tcp6(suite) ->
-    [];
-traffic_ping_pong_large_sendmsg_and_recvmsg_tcp6(doc) ->
-    [];
 traffic_ping_pong_large_sendmsg_and_recvmsg_tcp6(Config) when is_list(Config) ->
     Msg = l2b(?TPP_LARGE),
     Num = ?TPP_NUM(Config, ?TPP_LARGE_NUM),
@@ -40180,10 +39262,6 @@ traffic_ping_pong_large_sendmsg_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'large' message test case, for Unix Domain (stream) socket.
 
-traffic_ping_pong_large_sendmsg_and_recvmsg_tcpL(suite) ->
-    [];
-traffic_ping_pong_large_sendmsg_and_recvmsg_tcpL(doc) ->
-    [];
 traffic_ping_pong_large_sendmsg_and_recvmsg_tcpL(Config) when is_list(Config) ->
     Msg = l2b(?TPP_LARGE),
     Num = ?TPP_NUM(Config, ?TPP_LARGE_NUM),
@@ -40209,14 +39287,11 @@ traffic_ping_pong_large_sendmsg_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for IPv4.
 
-traffic_ping_pong_small_sendmsg_and_recvmsg_udp4(suite) ->
-    [];
-traffic_ping_pong_small_sendmsg_and_recvmsg_udp4(doc) ->
-    [];
 traffic_ping_pong_small_sendmsg_and_recvmsg_udp4(Config) when is_list(Config) ->
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
     tc_try(traffic_ping_pong_small_sendmsg_and_recvmsg_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ?TT(?SECS(60)),
                    InitState = #{domain => inet,
@@ -40236,10 +39311,6 @@ traffic_ping_pong_small_sendmsg_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for IPv6.
 
-traffic_ping_pong_small_sendmsg_and_recvmsg_udp6(suite) ->
-    [];
-traffic_ping_pong_small_sendmsg_and_recvmsg_udp6(doc) ->
-    [];
 traffic_ping_pong_small_sendmsg_and_recvmsg_udp6(Config) when is_list(Config) ->
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
@@ -40264,10 +39335,6 @@ traffic_ping_pong_small_sendmsg_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'small' message test case, for Unix Domain (dgram) socket.
 
-traffic_ping_pong_small_sendmsg_and_recvmsg_udpL(suite) ->
-    [];
-traffic_ping_pong_small_sendmsg_and_recvmsg_udpL(doc) ->
-    [];
 traffic_ping_pong_small_sendmsg_and_recvmsg_udpL(Config) when is_list(Config) ->
     Msg = l2b(?TPP_SMALL),
     Num = ?TPP_NUM(Config, ?TPP_SMALL_NUM),
@@ -40292,14 +39359,11 @@ traffic_ping_pong_small_sendmsg_and_recv
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for IPv4.
 
-traffic_ping_pong_medium_sendmsg_and_recvmsg_udp4(suite) ->
-    [];
-traffic_ping_pong_medium_sendmsg_and_recvmsg_udp4(doc) ->
-    [];
 traffic_ping_pong_medium_sendmsg_and_recvmsg_udp4(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
     tc_try(traffic_ping_pong_medium_sendmsg_and_recvmsg_udp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    ?TT(?SECS(60)),
                    InitState = #{domain => inet,
@@ -40319,10 +39383,6 @@ traffic_ping_pong_medium_sendmsg_and_rec
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for IPv6.
 
-traffic_ping_pong_medium_sendmsg_and_recvmsg_udp6(suite) ->
-    [];
-traffic_ping_pong_medium_sendmsg_and_recvmsg_udp6(doc) ->
-    [];
 traffic_ping_pong_medium_sendmsg_and_recvmsg_udp6(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
@@ -40348,10 +39408,6 @@ traffic_ping_pong_medium_sendmsg_and_rec
 %% repeated a set number of times (more times the small the message).
 %% This is the 'medium' message test case, for Unix Domain (dgram) socket.
 
-traffic_ping_pong_medium_sendmsg_and_recvmsg_udpL(suite) ->
-    [];
-traffic_ping_pong_medium_sendmsg_and_recvmsg_udpL(doc) ->
-    [];
 traffic_ping_pong_medium_sendmsg_and_recvmsg_udpL(Config) when is_list(Config) ->
     Msg = l2b(?TPP_MEDIUM),
     Num = ?TPP_NUM(Config, ?TPP_MEDIUM_NUM),
@@ -42306,10 +41362,6 @@ tpp_udp_sock_close(Sock, Path) ->
 %% Domain:       inet
 %%
 
-ttest_sgenf_cgenf_small_tcp4(suite) ->
-    [];
-ttest_sgenf_cgenf_small_tcp4(doc) ->
-    [];
 ttest_sgenf_cgenf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgenf_small_tcp4,
@@ -42330,10 +41382,6 @@ ttest_sgenf_cgenf_small_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_cgenf_small_tcp6(suite) ->
-    [];
-ttest_sgenf_cgenf_small_tcp6(doc) ->
-    [];
 ttest_sgenf_cgenf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgenf_small_tcp6,
@@ -42354,10 +41402,6 @@ ttest_sgenf_cgenf_small_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgenf_cgenf_medium_tcp4(suite) ->
-    [];
-ttest_sgenf_cgenf_medium_tcp4(doc) ->
-    [];
 ttest_sgenf_cgenf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgenf_medium_tcp4,
@@ -42378,10 +41422,6 @@ ttest_sgenf_cgenf_medium_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_cgenf_medium_tcp6(suite) ->
-    [];
-ttest_sgenf_cgenf_medium_tcp6(doc) ->
-    [];
 ttest_sgenf_cgenf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgenf_medium_tcp6,
@@ -42402,10 +41442,6 @@ ttest_sgenf_cgenf_medium_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgenf_cgenf_large_tcp4(suite) ->
-    [];
-ttest_sgenf_cgenf_large_tcp4(doc) ->
-    [];
 ttest_sgenf_cgenf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgenf_large_tcp4,
@@ -42426,10 +41462,6 @@ ttest_sgenf_cgenf_large_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_cgenf_large_tcp6(suite) ->
-    [];
-ttest_sgenf_cgenf_large_tcp6(doc) ->
-    [];
 ttest_sgenf_cgenf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgenf_large_tcp6,
@@ -42450,10 +41482,6 @@ ttest_sgenf_cgenf_large_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgenf_cgeno_small_tcp4(suite) ->
-    [];
-ttest_sgenf_cgeno_small_tcp4(doc) ->
-    [];
 ttest_sgenf_cgeno_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgeno_small_tcp4,
@@ -42474,10 +41502,6 @@ ttest_sgenf_cgeno_small_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_cgeno_small_tcp6(suite) ->
-    [];
-ttest_sgenf_cgeno_small_tcp6(doc) ->
-    [];
 ttest_sgenf_cgeno_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgeno_small_tcp6,
@@ -42498,10 +41522,6 @@ ttest_sgenf_cgeno_small_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgenf_cgeno_medium_tcp4(suite) ->
-    [];
-ttest_sgenf_cgeno_medium_tcp4(doc) ->
-    [];
 ttest_sgenf_cgeno_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgeno_medium_tcp4,
@@ -42522,10 +41542,6 @@ ttest_sgenf_cgeno_medium_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_cgeno_medium_tcp6(suite) ->
-    [];
-ttest_sgenf_cgeno_medium_tcp6(doc) ->
-    [];
 ttest_sgenf_cgeno_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgeno_medium_tcp6,
@@ -42546,10 +41562,6 @@ ttest_sgenf_cgeno_medium_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgenf_cgeno_large_tcp4(suite) ->
-    [];
-ttest_sgenf_cgeno_large_tcp4(doc) ->
-    [];
 ttest_sgenf_cgeno_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgeno_large_tcp4,
@@ -42570,10 +41582,6 @@ ttest_sgenf_cgeno_large_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_cgeno_large_tcp6(suite) ->
-    [];
-ttest_sgenf_cgeno_large_tcp6(doc) ->
-    [];
 ttest_sgenf_cgeno_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgeno_large_tcp6,
@@ -42594,10 +41602,6 @@ ttest_sgenf_cgeno_large_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgenf_cgent_small_tcp4(suite) ->
-    [];
-ttest_sgenf_cgent_small_tcp4(doc) ->
-    [];
 ttest_sgenf_cgent_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgent_small_tcp4,
@@ -42618,10 +41622,6 @@ ttest_sgenf_cgent_small_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_cgent_small_tcp6(suite) ->
-    [];
-ttest_sgenf_cgent_small_tcp6(doc) ->
-    [];
 ttest_sgenf_cgent_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgeno_small_tcp6,
@@ -42642,10 +41642,6 @@ ttest_sgenf_cgent_small_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgenf_cgent_medium_tcp4(suite) ->
-    [];
-ttest_sgenf_cgent_medium_tcp4(doc) ->
-    [];
 ttest_sgenf_cgent_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgent_medium_tcp4,
@@ -42666,10 +41662,6 @@ ttest_sgenf_cgent_medium_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_cgent_medium_tcp6(suite) ->
-    [];
-ttest_sgenf_cgent_medium_tcp6(doc) ->
-    [];
 ttest_sgenf_cgent_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgent_medium_tcp6,
@@ -42690,10 +41682,6 @@ ttest_sgenf_cgent_medium_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgenf_cgent_large_tcp4(suite) ->
-    [];
-ttest_sgenf_cgent_large_tcp4(doc) ->
-    [];
 ttest_sgenf_cgent_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgent_large_tcp4,
@@ -42714,10 +41702,6 @@ ttest_sgenf_cgent_large_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_cgent_large_tcp6(suite) ->
-    [];
-ttest_sgenf_cgent_large_tcp6(doc) ->
-    [];
 ttest_sgenf_cgent_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_cgent_large_tcp6,
@@ -42738,10 +41722,6 @@ ttest_sgenf_cgent_large_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgenf_csockf_small_tcp4(suite) ->
-    [];
-ttest_sgenf_csockf_small_tcp4(doc) ->
-    [];
 ttest_sgenf_csockf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockf_small_tcp4,
@@ -42762,10 +41742,6 @@ ttest_sgenf_csockf_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_csockf_small_tcp6(suite) ->
-    [];
-ttest_sgenf_csockf_small_tcp6(doc) ->
-    [];
 ttest_sgenf_csockf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockf_small_tcp6,
@@ -42786,10 +41762,6 @@ ttest_sgenf_csockf_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgenf_csockf_medium_tcp4(suite) ->
-    [];
-ttest_sgenf_csockf_medium_tcp4(doc) ->
-    [];
 ttest_sgenf_csockf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockf_medium_tcp4,
@@ -42810,10 +41782,6 @@ ttest_sgenf_csockf_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_csockf_medium_tcp6(suite) ->
-    [];
-ttest_sgenf_csockf_medium_tcp6(doc) ->
-    [];
 ttest_sgenf_csockf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockf_medium_tcp6,
@@ -42834,10 +41802,6 @@ ttest_sgenf_csockf_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_sgenf_csockf_large_tcp4(suite) ->
-    [];
-ttest_sgenf_csockf_large_tcp4(doc) ->
-    [];
 ttest_sgenf_csockf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockf_large_tcp4,
@@ -42858,10 +41822,6 @@ ttest_sgenf_csockf_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_csockf_large_tcp6(suite) ->
-    [];
-ttest_sgenf_csockf_large_tcp6(doc) ->
-    [];
 ttest_sgenf_csockf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockf_large_tcp6,
@@ -42882,10 +41842,6 @@ ttest_sgenf_csockf_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgenf_csocko_small_tcp4(suite) ->
-    [];
-ttest_sgenf_csocko_small_tcp4(doc) ->
-    [];
 ttest_sgenf_csocko_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csocko_small_tcp4,
@@ -42906,10 +41862,6 @@ ttest_sgenf_csocko_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_csocko_small_tcp6(suite) ->
-    [];
-ttest_sgenf_csocko_small_tcp6(doc) ->
-    [];
 ttest_sgenf_csocko_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csocko_small_tcp6,
@@ -42930,10 +41882,6 @@ ttest_sgenf_csocko_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgenf_csocko_medium_tcp4(suite) ->
-    [];
-ttest_sgenf_csocko_medium_tcp4(doc) ->
-    [];
 ttest_sgenf_csocko_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csocko_medium_tcp4,
@@ -42954,10 +41902,6 @@ ttest_sgenf_csocko_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_csocko_medium_tcp6(suite) ->
-    [];
-ttest_sgenf_csocko_medium_tcp6(doc) ->
-    [];
 ttest_sgenf_csocko_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csocko_medium_tcp6,
@@ -42978,10 +41922,6 @@ ttest_sgenf_csocko_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_sgenf_csocko_large_tcp4(suite) ->
-    [];
-ttest_sgenf_csocko_large_tcp4(doc) ->
-    [];
 ttest_sgenf_csocko_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csocko_large_tcp4,
@@ -43002,10 +41942,6 @@ ttest_sgenf_csocko_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_csocko_large_tcp6(suite) ->
-    [];
-ttest_sgenf_csocko_large_tcp6(doc) ->
-    [];
 ttest_sgenf_csocko_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csocko_large_tcp6,
@@ -43026,10 +41962,6 @@ ttest_sgenf_csocko_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgenf_csockt_small_tcp4(suite) ->
-    [];
-ttest_sgenf_csockt_small_tcp4(doc) ->
-    [];
 ttest_sgenf_csockt_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockt_small_tcp4,
@@ -43050,10 +41982,6 @@ ttest_sgenf_csockt_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_csockt_small_tcp6(suite) ->
-    [];
-ttest_sgenf_csockt_small_tcp6(doc) ->
-    [];
 ttest_sgenf_csockt_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csocko_small_tcp6,
@@ -43074,10 +42002,6 @@ ttest_sgenf_csockt_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgenf_csockt_medium_tcp4(suite) ->
-    [];
-ttest_sgenf_csockt_medium_tcp4(doc) ->
-    [];
 ttest_sgenf_csockt_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockt_medium_tcp4,
@@ -43098,10 +42022,6 @@ ttest_sgenf_csockt_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_csockt_medium_tcp6(suite) ->
-    [];
-ttest_sgenf_csockt_medium_tcp6(doc) ->
-    [];
 ttest_sgenf_csockt_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockt_medium_tcp6,
@@ -43122,10 +42042,6 @@ ttest_sgenf_csockt_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_sgenf_csockt_large_tcp4(suite) ->
-    [];
-ttest_sgenf_csockt_large_tcp4(doc) ->
-    [];
 ttest_sgenf_csockt_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockt_large_tcp4,
@@ -43146,10 +42062,6 @@ ttest_sgenf_csockt_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgenf_csockt_large_tcp6(suite) ->
-    [];
-ttest_sgenf_csockt_large_tcp6(doc) ->
-    [];
 ttest_sgenf_csockt_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgenf_csockt_large_tcp6,
@@ -43170,10 +42082,6 @@ ttest_sgenf_csockt_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgeno_cgenf_small_tcp4(suite) ->
-    [];
-ttest_sgeno_cgenf_small_tcp4(doc) ->
-    [];
 ttest_sgeno_cgenf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgenf_small_tcp4,
@@ -43194,10 +42102,6 @@ ttest_sgeno_cgenf_small_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_cgenf_small_tcp6(suite) ->
-    [];
-ttest_sgeno_cgenf_small_tcp6(doc) ->
-    [];
 ttest_sgeno_cgenf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgenf_small_tcp6,
@@ -43218,10 +42122,6 @@ ttest_sgeno_cgenf_small_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgeno_cgenf_medium_tcp4(suite) ->
-    [];
-ttest_sgeno_cgenf_medium_tcp4(doc) ->
-    [];
 ttest_sgeno_cgenf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgenf_medium_tcp4,
@@ -43242,10 +42142,6 @@ ttest_sgeno_cgenf_medium_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_cgenf_medium_tcp6(suite) ->
-    [];
-ttest_sgeno_cgenf_medium_tcp6(doc) ->
-    [];
 ttest_sgeno_cgenf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgenf_medium_tcp6,
@@ -43266,10 +42162,6 @@ ttest_sgeno_cgenf_medium_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgeno_cgenf_large_tcp4(suite) ->
-    [];
-ttest_sgeno_cgenf_large_tcp4(doc) ->
-    [];
 ttest_sgeno_cgenf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgenf_large_tcp4,
@@ -43290,10 +42182,6 @@ ttest_sgeno_cgenf_large_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_cgenf_large_tcp6(suite) ->
-    [];
-ttest_sgeno_cgenf_large_tcp6(doc) ->
-    [];
 ttest_sgeno_cgenf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgenf_large_tcp6,
@@ -43314,10 +42202,6 @@ ttest_sgeno_cgenf_large_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgeno_cgeno_small_tcp4(suite) ->
-    [];
-ttest_sgeno_cgeno_small_tcp4(doc) ->
-    [];
 ttest_sgeno_cgeno_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgeno_small_tcp4,
@@ -43338,10 +42222,6 @@ ttest_sgeno_cgeno_small_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_cgeno_small_tcp6(suite) ->
-    [];
-ttest_sgeno_cgeno_small_tcp6(doc) ->
-    [];
 ttest_sgeno_cgeno_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgeno_small_tcp6,
@@ -43362,10 +42242,6 @@ ttest_sgeno_cgeno_small_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgeno_cgeno_medium_tcp4(suite) ->
-    [];
-ttest_sgeno_cgeno_medium_tcp4(doc) ->
-    [];
 ttest_sgeno_cgeno_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgeno_medium_tcp4,
@@ -43386,10 +42262,6 @@ ttest_sgeno_cgeno_medium_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_cgeno_medium_tcp6(suite) ->
-    [];
-ttest_sgeno_cgeno_medium_tcp6(doc) ->
-    [];
 ttest_sgeno_cgeno_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgeno_medium_tcp6,
@@ -43410,10 +42282,6 @@ ttest_sgeno_cgeno_medium_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgeno_cgeno_large_tcp4(suite) ->
-    [];
-ttest_sgeno_cgeno_large_tcp4(doc) ->
-    [];
 ttest_sgeno_cgeno_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgeno_large_tcp4,
@@ -43434,10 +42302,6 @@ ttest_sgeno_cgeno_large_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_cgeno_large_tcp6(suite) ->
-    [];
-ttest_sgeno_cgeno_large_tcp6(doc) ->
-    [];
 ttest_sgeno_cgeno_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgeno_large_tcp6,
@@ -43458,10 +42322,6 @@ ttest_sgeno_cgeno_large_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgeno_cgent_small_tcp4(suite) ->
-    [];
-ttest_sgeno_cgent_small_tcp4(doc) ->
-    [];
 ttest_sgeno_cgent_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgent_small_tcp4,
@@ -43482,10 +42342,6 @@ ttest_sgeno_cgent_small_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_cgent_small_tcp6(suite) ->
-    [];
-ttest_sgeno_cgent_small_tcp6(doc) ->
-    [];
 ttest_sgeno_cgent_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgeno_small_tcp6,
@@ -43506,10 +42362,6 @@ ttest_sgeno_cgent_small_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgeno_cgent_medium_tcp4(suite) ->
-    [];
-ttest_sgeno_cgent_medium_tcp4(doc) ->
-    [];
 ttest_sgeno_cgent_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgent_medium_tcp4,
@@ -43530,10 +42382,6 @@ ttest_sgeno_cgent_medium_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_cgent_medium_tcp6(suite) ->
-    [];
-ttest_sgeno_cgent_medium_tcp6(doc) ->
-    [];
 ttest_sgeno_cgent_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgent_medium_tcp6,
@@ -43554,10 +42402,6 @@ ttest_sgeno_cgent_medium_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgeno_cgent_large_tcp4(suite) ->
-    [];
-ttest_sgeno_cgent_large_tcp4(doc) ->
-    [];
 ttest_sgeno_cgent_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgent_large_tcp4,
@@ -43578,10 +42422,6 @@ ttest_sgeno_cgent_large_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_cgent_large_tcp6(suite) ->
-    [];
-ttest_sgeno_cgent_large_tcp6(doc) ->
-    [];
 ttest_sgeno_cgent_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_cgent_large_tcp6,
@@ -43602,10 +42442,6 @@ ttest_sgeno_cgent_large_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgeno_csockf_small_tcp4(suite) ->
-    [];
-ttest_sgeno_csockf_small_tcp4(doc) ->
-    [];
 ttest_sgeno_csockf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockf_small_tcp4,
@@ -43626,10 +42462,6 @@ ttest_sgeno_csockf_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_csockf_small_tcp6(suite) ->
-    [];
-ttest_sgeno_csockf_small_tcp6(doc) ->
-    [];
 ttest_sgeno_csockf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockf_small_tcp6,
@@ -43650,10 +42482,6 @@ ttest_sgeno_csockf_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgeno_csockf_medium_tcp4(suite) ->
-    [];
-ttest_sgeno_csockf_medium_tcp4(doc) ->
-    [];
 ttest_sgeno_csockf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockf_medium_tcp4,
@@ -43674,10 +42502,6 @@ ttest_sgeno_csockf_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_csockf_medium_tcp6(suite) ->
-    [];
-ttest_sgeno_csockf_medium_tcp6(doc) ->
-    [];
 ttest_sgeno_csockf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockf_medium_tcp6,
@@ -43698,10 +42522,6 @@ ttest_sgeno_csockf_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_sgeno_csockf_large_tcp4(suite) ->
-    [];
-ttest_sgeno_csockf_large_tcp4(doc) ->
-    [];
 ttest_sgeno_csockf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockf_large_tcp4,
@@ -43722,10 +42542,6 @@ ttest_sgeno_csockf_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_csockf_large_tcp6(suite) ->
-    [];
-ttest_sgeno_csockf_large_tcp6(doc) ->
-    [];
 ttest_sgeno_csockf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockf_large_tcp6,
@@ -43746,10 +42562,6 @@ ttest_sgeno_csockf_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgeno_csocko_small_tcp4(suite) ->
-    [];
-ttest_sgeno_csocko_small_tcp4(doc) ->
-    [];
 ttest_sgeno_csocko_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csocko_small_tcp4,
@@ -43770,10 +42582,6 @@ ttest_sgeno_csocko_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_csocko_small_tcp6(suite) ->
-    [];
-ttest_sgeno_csocko_small_tcp6(doc) ->
-    [];
 ttest_sgeno_csocko_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csocko_small_tcp6,
@@ -43794,10 +42602,6 @@ ttest_sgeno_csocko_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgeno_csocko_medium_tcp4(suite) ->
-    [];
-ttest_sgeno_csocko_medium_tcp4(doc) ->
-    [];
 ttest_sgeno_csocko_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csocko_medium_tcp4,
@@ -43818,10 +42622,6 @@ ttest_sgeno_csocko_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_csocko_medium_tcp6(suite) ->
-    [];
-ttest_sgeno_csocko_medium_tcp6(doc) ->
-    [];
 ttest_sgeno_csocko_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csocko_medium_tcp6,
@@ -43842,10 +42642,6 @@ ttest_sgeno_csocko_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_sgeno_csocko_large_tcp4(suite) ->
-    [];
-ttest_sgeno_csocko_large_tcp4(doc) ->
-    [];
 ttest_sgeno_csocko_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csocko_large_tcp4,
@@ -43866,10 +42662,6 @@ ttest_sgeno_csocko_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_csocko_large_tcp6(suite) ->
-    [];
-ttest_sgeno_csocko_large_tcp6(doc) ->
-    [];
 ttest_sgeno_csocko_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csocko_large_tcp6,
@@ -43890,10 +42682,6 @@ ttest_sgeno_csocko_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgeno_csockt_small_tcp4(suite) ->
-    [];
-ttest_sgeno_csockt_small_tcp4(doc) ->
-    [];
 ttest_sgeno_csockt_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockt_small_tcp4,
@@ -43914,10 +42702,6 @@ ttest_sgeno_csockt_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_csockt_small_tcp6(suite) ->
-    [];
-ttest_sgeno_csockt_small_tcp6(doc) ->
-    [];
 ttest_sgeno_csockt_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csocko_small_tcp6,
@@ -43938,10 +42722,6 @@ ttest_sgeno_csockt_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgeno_csockt_medium_tcp4(suite) ->
-    [];
-ttest_sgeno_csockt_medium_tcp4(doc) ->
-    [];
 ttest_sgeno_csockt_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockt_medium_tcp4,
@@ -43962,10 +42742,6 @@ ttest_sgeno_csockt_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_csockt_medium_tcp6(suite) ->
-    [];
-ttest_sgeno_csockt_medium_tcp6(doc) ->
-    [];
 ttest_sgeno_csockt_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockt_medium_tcp6,
@@ -43986,10 +42762,6 @@ ttest_sgeno_csockt_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_sgeno_csockt_large_tcp4(suite) ->
-    [];
-ttest_sgeno_csockt_large_tcp4(doc) ->
-    [];
 ttest_sgeno_csockt_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockt_large_tcp4,
@@ -44010,10 +42782,6 @@ ttest_sgeno_csockt_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgeno_csockt_large_tcp6(suite) ->
-    [];
-ttest_sgeno_csockt_large_tcp6(doc) ->
-    [];
 ttest_sgeno_csockt_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgeno_csockt_large_tcp6,
@@ -44034,10 +42802,6 @@ ttest_sgeno_csockt_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgent_cgenf_small_tcp4(suite) ->
-    [];
-ttest_sgent_cgenf_small_tcp4(doc) ->
-    [];
 ttest_sgent_cgenf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgenf_small_tcp4,
@@ -44058,10 +42822,6 @@ ttest_sgent_cgenf_small_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgent_cgenf_small_tcp6(suite) ->
-    [];
-ttest_sgent_cgenf_small_tcp6(doc) ->
-    [];
 ttest_sgent_cgenf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgenf_small_tcp6,
@@ -44082,10 +42842,6 @@ ttest_sgent_cgenf_small_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgent_cgenf_medium_tcp4(suite) ->
-    [];
-ttest_sgent_cgenf_medium_tcp4(doc) ->
-    [];
 ttest_sgent_cgenf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgenf_medium_tcp4,
@@ -44106,10 +42862,6 @@ ttest_sgent_cgenf_medium_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgent_cgenf_medium_tcp6(suite) ->
-    [];
-ttest_sgent_cgenf_medium_tcp6(doc) ->
-    [];
 ttest_sgent_cgenf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgenf_medium_tcp6,
@@ -44130,10 +42882,6 @@ ttest_sgent_cgenf_medium_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgent_cgenf_large_tcp4(suite) ->
-    [];
-ttest_sgent_cgenf_large_tcp4(doc) ->
-    [];
 ttest_sgent_cgenf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgenf_large_tcp4,
@@ -44154,10 +42902,6 @@ ttest_sgent_cgenf_large_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgent_cgenf_large_tcp6(suite) ->
-    [];
-ttest_sgent_cgenf_large_tcp6(doc) ->
-    [];
 ttest_sgent_cgenf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgenf_large_tcp6,
@@ -44178,10 +42922,6 @@ ttest_sgent_cgenf_large_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgent_cgeno_small_tcp4(suite) ->
-    [];
-ttest_sgent_cgeno_small_tcp4(doc) ->
-    [];
 ttest_sgent_cgeno_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgeno_small_tcp4,
@@ -44202,10 +42942,6 @@ ttest_sgent_cgeno_small_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgent_cgeno_small_tcp6(suite) ->
-    [];
-ttest_sgent_cgeno_small_tcp6(doc) ->
-    [];
 ttest_sgent_cgeno_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgeno_small_tcp6,
@@ -44226,10 +42962,6 @@ ttest_sgent_cgeno_small_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgent_cgeno_medium_tcp4(suite) ->
-    [];
-ttest_sgent_cgeno_medium_tcp4(doc) ->
-    [];
 ttest_sgent_cgeno_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgeno_medium_tcp4,
@@ -44250,10 +42982,6 @@ ttest_sgent_cgeno_medium_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgent_cgeno_medium_tcp6(suite) ->
-    [];
-ttest_sgent_cgeno_medium_tcp6(doc) ->
-    [];
 ttest_sgent_cgeno_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgeno_medium_tcp6,
@@ -44274,10 +43002,6 @@ ttest_sgent_cgeno_medium_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgent_cgeno_large_tcp4(suite) ->
-    [];
-ttest_sgent_cgeno_large_tcp4(doc) ->
-    [];
 ttest_sgent_cgeno_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgeno_large_tcp4,
@@ -44298,10 +43022,6 @@ ttest_sgent_cgeno_large_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgent_cgeno_large_tcp6(suite) ->
-    [];
-ttest_sgent_cgeno_large_tcp6(doc) ->
-    [];
 ttest_sgent_cgeno_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgeno_large_tcp6,
@@ -44322,10 +43042,6 @@ ttest_sgent_cgeno_large_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgent_cgent_small_tcp4(suite) ->
-    [];
-ttest_sgent_cgent_small_tcp4(doc) ->
-    [];
 ttest_sgent_cgent_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgent_small_tcp4,
@@ -44346,10 +43062,6 @@ ttest_sgent_cgent_small_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgent_cgent_small_tcp6(suite) ->
-    [];
-ttest_sgent_cgent_small_tcp6(doc) ->
-    [];
 ttest_sgent_cgent_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgeno_small_tcp6,
@@ -44370,10 +43082,9 @@ ttest_sgent_cgent_small_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgent_cgent_medium_tcp4(suite) ->
-    [];
-ttest_sgent_cgent_medium_tcp4(doc) ->
-    ["Server(gen,true), Client(gen,true), Domain=inet, msg=medium"];
+ttest_sgent_cgent_medium_tcp4() ->
+    [{doc, "Server(gen,true), Client(gen,true), Domain=inet, msg=medium"}].
+
 ttest_sgent_cgent_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgent_medium_tcp4,
@@ -44393,11 +43104,9 @@ ttest_sgent_cgent_medium_tcp4(Config) wh
 %% Message Size: medium (=2)
 %% Domain:       inet6
 %% 
+ttest_sgent_cgent_medium_tcp6() ->
+    [{doc, "Server(gen,true), Client(gen,true), Domain=inet6, msg=medium"}].
 
-ttest_sgent_cgent_medium_tcp6(suite) ->
-    [];
-ttest_sgent_cgent_medium_tcp6(doc) ->
-    ["Server(gen,true), Client(gen,true), Domain=inet6, msg=medium"];
 ttest_sgent_cgent_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgent_medium_tcp6,
@@ -44418,10 +43127,9 @@ ttest_sgent_cgent_medium_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgent_cgent_large_tcp4(suite) ->
-    [];
-ttest_sgent_cgent_large_tcp4(doc) ->
-    ["Server(gen,true), Client(gen,true), Domain=inet, msg=large"];
+ttest_sgent_cgent_large_tcp4() ->
+    [{doc, "Server(gen,true), Client(gen,true), Domain=inet, msg=large"}].
+
 ttest_sgent_cgent_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgent_large_tcp4,
@@ -44442,10 +43150,9 @@ ttest_sgent_cgent_large_tcp4(Config) whe
 %% Domain:       inet6
 %% 
 
-ttest_sgent_cgent_large_tcp6(suite) ->
-    [];
-ttest_sgent_cgent_large_tcp6(doc) ->
-    ["Server(gen,true), Client(gen,true), Domain=inet6, msg=large"];
+ttest_sgent_cgent_large_tcp6() ->
+    [{doc, "Server(gen,true), Client(gen,true), Domain=inet6, msg=large"}].
+
 ttest_sgent_cgent_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_cgent_large_tcp6,
@@ -44466,10 +43173,7 @@ ttest_sgent_cgent_large_tcp6(Config) whe
 %% Domain:       inet
 %%
 
-ttest_sgent_csockf_small_tcp4(suite) ->
-    [];
-ttest_sgent_csockf_small_tcp4(doc) ->
-    [];
+
 ttest_sgent_csockf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockf_small_tcp4,
@@ -44490,10 +43194,6 @@ ttest_sgent_csockf_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgent_csockf_small_tcp6(suite) ->
-    [];
-ttest_sgent_csockf_small_tcp6(doc) ->
-    [];
 ttest_sgent_csockf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockf_small_tcp6,
@@ -44514,10 +43214,6 @@ ttest_sgent_csockf_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgent_csockf_medium_tcp4(suite) ->
-    [];
-ttest_sgent_csockf_medium_tcp4(doc) ->
-    [];
 ttest_sgent_csockf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockf_medium_tcp4,
@@ -44538,10 +43234,6 @@ ttest_sgent_csockf_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_sgent_csockf_medium_tcp6(suite) ->
-    [];
-ttest_sgent_csockf_medium_tcp6(doc) ->
-    [];
 ttest_sgent_csockf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockf_medium_tcp6,
@@ -44562,10 +43254,6 @@ ttest_sgent_csockf_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_sgent_csockf_large_tcp4(suite) ->
-    [];
-ttest_sgent_csockf_large_tcp4(doc) ->
-    [];
 ttest_sgent_csockf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockf_large_tcp4,
@@ -44586,10 +43274,6 @@ ttest_sgent_csockf_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgent_csockf_large_tcp6(suite) ->
-    [];
-ttest_sgent_csockf_large_tcp6(doc) ->
-    [];
 ttest_sgent_csockf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockf_large_tcp6,
@@ -44610,10 +43294,6 @@ ttest_sgent_csockf_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgent_csocko_small_tcp4(suite) ->
-    [];
-ttest_sgent_csocko_small_tcp4(doc) ->
-    [];
 ttest_sgent_csocko_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csocko_small_tcp4,
@@ -44634,10 +43314,6 @@ ttest_sgent_csocko_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgent_csocko_small_tcp6(suite) ->
-    [];
-ttest_sgent_csocko_small_tcp6(doc) ->
-    [];
 ttest_sgent_csocko_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csocko_small_tcp6,
@@ -44658,10 +43334,6 @@ ttest_sgent_csocko_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgent_csocko_medium_tcp4(suite) ->
-    [];
-ttest_sgent_csocko_medium_tcp4(doc) ->
-    [];
 ttest_sgent_csocko_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csocko_medium_tcp4,
@@ -44682,10 +43354,6 @@ ttest_sgent_csocko_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_sgent_csocko_medium_tcp6(suite) ->
-    [];
-ttest_sgent_csocko_medium_tcp6(doc) ->
-    [];
 ttest_sgent_csocko_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csocko_medium_tcp6,
@@ -44706,10 +43374,6 @@ ttest_sgent_csocko_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_sgent_csocko_large_tcp4(suite) ->
-    [];
-ttest_sgent_csocko_large_tcp4(doc) ->
-    [];
 ttest_sgent_csocko_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csocko_large_tcp4,
@@ -44730,10 +43394,6 @@ ttest_sgent_csocko_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgent_csocko_large_tcp6(suite) ->
-    [];
-ttest_sgent_csocko_large_tcp6(doc) ->
-    [];
 ttest_sgent_csocko_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csocko_large_tcp6,
@@ -44754,10 +43414,6 @@ ttest_sgent_csocko_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgent_csockt_small_tcp4(suite) ->
-    [];
-ttest_sgent_csockt_small_tcp4(doc) ->
-    [];
 ttest_sgent_csockt_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockt_small_tcp4,
@@ -44778,10 +43434,6 @@ ttest_sgent_csockt_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgent_csockt_small_tcp6(suite) ->
-    [];
-ttest_sgent_csockt_small_tcp6(doc) ->
-    [];
 ttest_sgent_csockt_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csocko_small_tcp6,
@@ -44802,10 +43454,6 @@ ttest_sgent_csockt_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_sgent_csockt_medium_tcp4(suite) ->
-    [];
-ttest_sgent_csockt_medium_tcp4(doc) ->
-    [];
 ttest_sgent_csockt_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockt_medium_tcp4,
@@ -44826,10 +43474,6 @@ ttest_sgent_csockt_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_sgent_csockt_medium_tcp6(suite) ->
-    [];
-ttest_sgent_csockt_medium_tcp6(doc) ->
-    [];
 ttest_sgent_csockt_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockt_medium_tcp6,
@@ -44850,10 +43494,6 @@ ttest_sgent_csockt_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_sgent_csockt_large_tcp4(suite) ->
-    [];
-ttest_sgent_csockt_large_tcp4(doc) ->
-    [];
 ttest_sgent_csockt_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockt_large_tcp4,
@@ -44874,10 +43514,6 @@ ttest_sgent_csockt_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_sgent_csockt_large_tcp6(suite) ->
-    [];
-ttest_sgent_csockt_large_tcp6(doc) ->
-    [];
 ttest_sgent_csockt_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_sgent_csockt_large_tcp6,
@@ -44898,10 +43534,6 @@ ttest_sgent_csockt_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockf_cgenf_small_tcp4(suite) ->
-    [];
-ttest_ssockf_cgenf_small_tcp4(doc) ->
-    [];
 ttest_ssockf_cgenf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgenf_small_tcp4,
@@ -44922,10 +43554,6 @@ ttest_ssockf_cgenf_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_cgenf_small_tcp6(suite) ->
-    [];
-ttest_ssockf_cgenf_small_tcp6(doc) ->
-    [];
 ttest_ssockf_cgenf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgenf_small_tcp6,
@@ -44946,10 +43574,6 @@ ttest_ssockf_cgenf_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockf_cgenf_medium_tcp4(suite) ->
-    [];
-ttest_ssockf_cgenf_medium_tcp4(doc) ->
-    [];
 ttest_ssockf_cgenf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgenf_medium_tcp4,
@@ -44970,10 +43594,6 @@ ttest_ssockf_cgenf_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_cgenf_medium_tcp6(suite) ->
-    [];
-ttest_ssockf_cgenf_medium_tcp6(doc) ->
-    [];
 ttest_ssockf_cgenf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgenf_medium_tcp6,
@@ -44994,10 +43614,6 @@ ttest_ssockf_cgenf_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockf_cgenf_large_tcp4(suite) ->
-    [];
-ttest_ssockf_cgenf_large_tcp4(doc) ->
-    [];
 ttest_ssockf_cgenf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgenf_large_tcp4,
@@ -45018,10 +43634,6 @@ ttest_ssockf_cgenf_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_cgenf_large_tcp6(suite) ->
-    [];
-ttest_ssockf_cgenf_large_tcp6(doc) ->
-    [];
 ttest_ssockf_cgenf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgenf_large_tcp6,
@@ -45042,10 +43654,6 @@ ttest_ssockf_cgenf_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockf_cgeno_small_tcp4(suite) ->
-    [];
-ttest_ssockf_cgeno_small_tcp4(doc) ->
-    [];
 ttest_ssockf_cgeno_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgeno_small_tcp4,
@@ -45066,10 +43674,6 @@ ttest_ssockf_cgeno_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_cgeno_small_tcp6(suite) ->
-    [];
-ttest_ssockf_cgeno_small_tcp6(doc) ->
-    [];
 ttest_ssockf_cgeno_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgeno_small_tcp6,
@@ -45090,10 +43694,6 @@ ttest_ssockf_cgeno_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockf_cgeno_medium_tcp4(suite) ->
-    [];
-ttest_ssockf_cgeno_medium_tcp4(doc) ->
-    [];
 ttest_ssockf_cgeno_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgeno_medium_tcp4,
@@ -45114,10 +43714,6 @@ ttest_ssockf_cgeno_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_cgeno_medium_tcp6(suite) ->
-    [];
-ttest_ssockf_cgeno_medium_tcp6(doc) ->
-    [];
 ttest_ssockf_cgeno_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgeno_medium_tcp6,
@@ -45138,10 +43734,6 @@ ttest_ssockf_cgeno_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockf_cgeno_large_tcp4(suite) ->
-    [];
-ttest_ssockf_cgeno_large_tcp4(doc) ->
-    [];
 ttest_ssockf_cgeno_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgeno_large_tcp4,
@@ -45162,10 +43754,6 @@ ttest_ssockf_cgeno_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_cgeno_large_tcp6(suite) ->
-    [];
-ttest_ssockf_cgeno_large_tcp6(doc) ->
-    [];
 ttest_ssockf_cgeno_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgeno_large_tcp6,
@@ -45186,10 +43774,6 @@ ttest_ssockf_cgeno_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockf_cgent_small_tcp4(suite) ->
-    [];
-ttest_ssockf_cgent_small_tcp4(doc) ->
-    [];
 ttest_ssockf_cgent_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgent_small_tcp4,
@@ -45210,10 +43794,6 @@ ttest_ssockf_cgent_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_cgent_small_tcp6(suite) ->
-    [];
-ttest_ssockf_cgent_small_tcp6(doc) ->
-    [];
 ttest_ssockf_cgent_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgeno_small_tcp6,
@@ -45234,10 +43814,6 @@ ttest_ssockf_cgent_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockf_cgent_medium_tcp4(suite) ->
-    [];
-ttest_ssockf_cgent_medium_tcp4(doc) ->
-    [];
 ttest_ssockf_cgent_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgent_medium_tcp4,
@@ -45258,10 +43834,6 @@ ttest_ssockf_cgent_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_cgent_medium_tcp6(suite) ->
-    [];
-ttest_ssockf_cgent_medium_tcp6(doc) ->
-    [];
 ttest_ssockf_cgent_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgent_medium_tcp6,
@@ -45282,10 +43854,6 @@ ttest_ssockf_cgent_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockf_cgent_large_tcp4(suite) ->
-    [];
-ttest_ssockf_cgent_large_tcp4(doc) ->
-    [];
 ttest_ssockf_cgent_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgent_large_tcp4,
@@ -45306,10 +43874,6 @@ ttest_ssockf_cgent_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_cgent_large_tcp6(suite) ->
-    [];
-ttest_ssockf_cgent_large_tcp6(doc) ->
-    [];
 ttest_ssockf_cgent_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_cgent_large_tcp6,
@@ -45330,10 +43894,6 @@ ttest_ssockf_cgent_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockf_csockf_small_tcp4(suite) ->
-    [];
-ttest_ssockf_csockf_small_tcp4(doc) ->
-    [];
 ttest_ssockf_csockf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockf_small_tcp4,
@@ -45354,10 +43914,6 @@ ttest_ssockf_csockf_small_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_csockf_small_tcp6(suite) ->
-    [];
-ttest_ssockf_csockf_small_tcp6(doc) ->
-    [];
 ttest_ssockf_csockf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockf_small_tcp6,
@@ -45378,10 +43934,6 @@ ttest_ssockf_csockf_small_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockf_csockf_small_tcpL(suite) ->
-    [];
-ttest_ssockf_csockf_small_tcpL(doc) ->
-    [];
 ttest_ssockf_csockf_small_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockf_small_tcpL,
@@ -45402,10 +43954,6 @@ ttest_ssockf_csockf_small_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockf_csockf_medium_tcp4(suite) ->
-    [];
-ttest_ssockf_csockf_medium_tcp4(doc) ->
-    [];
 ttest_ssockf_csockf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockf_medium_tcp4,
@@ -45426,10 +43974,6 @@ ttest_ssockf_csockf_medium_tcp4(Config)
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_csockf_medium_tcp6(suite) ->
-    [];
-ttest_ssockf_csockf_medium_tcp6(doc) ->
-    [];
 ttest_ssockf_csockf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockf_medium_tcp6,
@@ -45450,10 +43994,6 @@ ttest_ssockf_csockf_medium_tcp6(Config)
 %% Domain:       local
 %% 
 
-ttest_ssockf_csockf_medium_tcpL(suite) ->
-    [];
-ttest_ssockf_csockf_medium_tcpL(doc) ->
-    [];
 ttest_ssockf_csockf_medium_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockf_medium_tcpL,
@@ -45474,10 +44014,6 @@ ttest_ssockf_csockf_medium_tcpL(Config)
 %% Domain:       inet
 %%
 
-ttest_ssockf_csockf_large_tcp4(suite) ->
-    [];
-ttest_ssockf_csockf_large_tcp4(doc) ->
-    [];
 ttest_ssockf_csockf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockf_large_tcp4,
@@ -45498,10 +44034,6 @@ ttest_ssockf_csockf_large_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_csockf_large_tcp6(suite) ->
-    [];
-ttest_ssockf_csockf_large_tcp6(doc) ->
-    [];
 ttest_ssockf_csockf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockf_large_tcp6,
@@ -45522,10 +44054,6 @@ ttest_ssockf_csockf_large_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockf_csockf_large_tcpL(suite) ->
-    [];
-ttest_ssockf_csockf_large_tcpL(doc) ->
-    [];
 ttest_ssockf_csockf_large_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockf_large_tcpL,
@@ -45546,10 +44074,6 @@ ttest_ssockf_csockf_large_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockf_csocko_small_tcp4(suite) ->
-    [];
-ttest_ssockf_csocko_small_tcp4(doc) ->
-    [];
 ttest_ssockf_csocko_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_small_tcp4,
@@ -45570,10 +44094,6 @@ ttest_ssockf_csocko_small_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_csocko_small_tcp6(suite) ->
-    [];
-ttest_ssockf_csocko_small_tcp6(doc) ->
-    [];
 ttest_ssockf_csocko_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_small_tcp6,
@@ -45594,10 +44114,6 @@ ttest_ssockf_csocko_small_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockf_csocko_small_tcpL(suite) ->
-    [];
-ttest_ssockf_csocko_small_tcpL(doc) ->
-    [];
 ttest_ssockf_csocko_small_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_small_tcpL,
@@ -45618,10 +44134,6 @@ ttest_ssockf_csocko_small_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockf_csocko_medium_tcp4(suite) ->
-    [];
-ttest_ssockf_csocko_medium_tcp4(doc) ->
-    [];
 ttest_ssockf_csocko_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_medium_tcp4,
@@ -45642,10 +44154,6 @@ ttest_ssockf_csocko_medium_tcp4(Config)
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_csocko_medium_tcp6(suite) ->
-    [];
-ttest_ssockf_csocko_medium_tcp6(doc) ->
-    [];
 ttest_ssockf_csocko_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_medium_tcp6,
@@ -45666,10 +44174,6 @@ ttest_ssockf_csocko_medium_tcp6(Config)
 %% Domain:       local
 %% 
 
-ttest_ssockf_csocko_medium_tcpL(suite) ->
-    [];
-ttest_ssockf_csocko_medium_tcpL(doc) ->
-    [];
 ttest_ssockf_csocko_medium_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_medium_tcpL,
@@ -45690,10 +44194,6 @@ ttest_ssockf_csocko_medium_tcpL(Config)
 %% Domain:       inet
 %%
 
-ttest_ssockf_csocko_large_tcp4(suite) ->
-    [];
-ttest_ssockf_csocko_large_tcp4(doc) ->
-    [];
 ttest_ssockf_csocko_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_large_tcp4,
@@ -45714,10 +44214,6 @@ ttest_ssockf_csocko_large_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_csocko_large_tcp6(suite) ->
-    [];
-ttest_ssockf_csocko_large_tcp6(doc) ->
-    [];
 ttest_ssockf_csocko_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_large_tcp6,
@@ -45738,10 +44234,6 @@ ttest_ssockf_csocko_large_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockf_csocko_large_tcpL(suite) ->
-    [];
-ttest_ssockf_csocko_large_tcpL(doc) ->
-    [];
 ttest_ssockf_csocko_large_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_large_tcpL,
@@ -45762,10 +44254,6 @@ ttest_ssockf_csocko_large_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockf_csockt_small_tcp4(suite) ->
-    [];
-ttest_ssockf_csockt_small_tcp4(doc) ->
-    [];
 ttest_ssockf_csockt_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockt_small_tcp4,
@@ -45786,10 +44274,6 @@ ttest_ssockf_csockt_small_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_csockt_small_tcp6(suite) ->
-    [];
-ttest_ssockf_csockt_small_tcp6(doc) ->
-    [];
 ttest_ssockf_csockt_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_small_tcp6,
@@ -45810,10 +44294,6 @@ ttest_ssockf_csockt_small_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockf_csockt_small_tcpL(suite) ->
-    [];
-ttest_ssockf_csockt_small_tcpL(doc) ->
-    [];
 ttest_ssockf_csockt_small_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csocko_small_tcpL,
@@ -45834,10 +44314,6 @@ ttest_ssockf_csockt_small_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockf_csockt_medium_tcp4(suite) ->
-    [];
-ttest_ssockf_csockt_medium_tcp4(doc) ->
-    [];
 ttest_ssockf_csockt_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockt_medium_tcp4,
@@ -45858,10 +44334,6 @@ ttest_ssockf_csockt_medium_tcp4(Config)
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_csockt_medium_tcp6(suite) ->
-    [];
-ttest_ssockf_csockt_medium_tcp6(doc) ->
-    [];
 ttest_ssockf_csockt_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockt_medium_tcp6,
@@ -45882,10 +44354,6 @@ ttest_ssockf_csockt_medium_tcp6(Config)
 %% Domain:       local
 %% 
 
-ttest_ssockf_csockt_medium_tcpL(suite) ->
-    [];
-ttest_ssockf_csockt_medium_tcpL(doc) ->
-    [];
 ttest_ssockf_csockt_medium_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockt_medium_tcpL,
@@ -45906,10 +44374,6 @@ ttest_ssockf_csockt_medium_tcpL(Config)
 %% Domain:       inet
 %%
 
-ttest_ssockf_csockt_large_tcp4(suite) ->
-    [];
-ttest_ssockf_csockt_large_tcp4(doc) ->
-    [];
 ttest_ssockf_csockt_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockt_large_tcp4,
@@ -45930,10 +44394,6 @@ ttest_ssockf_csockt_large_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockf_csockt_large_tcp6(suite) ->
-    [];
-ttest_ssockf_csockt_large_tcp6(doc) ->
-    [];
 ttest_ssockf_csockt_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockt_large_tcp6,
@@ -45954,10 +44414,6 @@ ttest_ssockf_csockt_large_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockf_csockt_large_tcpL(suite) ->
-    [];
-ttest_ssockf_csockt_large_tcpL(doc) ->
-    [];
 ttest_ssockf_csockt_large_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockf_csockt_large_tcpL,
@@ -45978,10 +44434,6 @@ ttest_ssockf_csockt_large_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssocko_cgenf_small_tcp4(suite) ->
-    [];
-ttest_ssocko_cgenf_small_tcp4(doc) ->
-    [];
 ttest_ssocko_cgenf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgenf_small_tcp4,
@@ -46002,10 +44454,6 @@ ttest_ssocko_cgenf_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_cgenf_small_tcp6(suite) ->
-    [];
-ttest_ssocko_cgenf_small_tcp6(doc) ->
-    [];
 ttest_ssocko_cgenf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgenf_small_tcp6,
@@ -46026,10 +44474,6 @@ ttest_ssocko_cgenf_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssocko_cgenf_medium_tcp4(suite) ->
-    [];
-ttest_ssocko_cgenf_medium_tcp4(doc) ->
-    [];
 ttest_ssocko_cgenf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgenf_medium_tcp4,
@@ -46050,10 +44494,6 @@ ttest_ssocko_cgenf_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_cgenf_medium_tcp6(suite) ->
-    [];
-ttest_ssocko_cgenf_medium_tcp6(doc) ->
-    [];
 ttest_ssocko_cgenf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgenf_medium_tcp6,
@@ -46074,10 +44514,6 @@ ttest_ssocko_cgenf_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssocko_cgenf_large_tcp4(suite) ->
-    [];
-ttest_ssocko_cgenf_large_tcp4(doc) ->
-    [];
 ttest_ssocko_cgenf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgenf_large_tcp4,
@@ -46098,10 +44534,6 @@ ttest_ssocko_cgenf_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_cgenf_large_tcp6(suite) ->
-    [];
-ttest_ssocko_cgenf_large_tcp6(doc) ->
-    [];
 ttest_ssocko_cgenf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgenf_large_tcp6,
@@ -46122,10 +44554,6 @@ ttest_ssocko_cgenf_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssocko_cgeno_small_tcp4(suite) ->
-    [];
-ttest_ssocko_cgeno_small_tcp4(doc) ->
-    [];
 ttest_ssocko_cgeno_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgeno_small_tcp4,
@@ -46146,10 +44574,6 @@ ttest_ssocko_cgeno_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_cgeno_small_tcp6(suite) ->
-    [];
-ttest_ssocko_cgeno_small_tcp6(doc) ->
-    [];
 ttest_ssocko_cgeno_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgeno_small_tcp6,
@@ -46170,10 +44594,6 @@ ttest_ssocko_cgeno_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssocko_cgeno_medium_tcp4(suite) ->
-    [];
-ttest_ssocko_cgeno_medium_tcp4(doc) ->
-    [];
 ttest_ssocko_cgeno_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgeno_medium_tcp4,
@@ -46194,10 +44614,6 @@ ttest_ssocko_cgeno_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_cgeno_medium_tcp6(suite) ->
-    [];
-ttest_ssocko_cgeno_medium_tcp6(doc) ->
-    [];
 ttest_ssocko_cgeno_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgeno_medium_tcp6,
@@ -46218,10 +44634,6 @@ ttest_ssocko_cgeno_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssocko_cgeno_large_tcp4(suite) ->
-    [];
-ttest_ssocko_cgeno_large_tcp4(doc) ->
-    [];
 ttest_ssocko_cgeno_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgeno_large_tcp4,
@@ -46242,10 +44654,6 @@ ttest_ssocko_cgeno_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_cgeno_large_tcp6(suite) ->
-    [];
-ttest_ssocko_cgeno_large_tcp6(doc) ->
-    [];
 ttest_ssocko_cgeno_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgeno_large_tcp6,
@@ -46266,10 +44674,6 @@ ttest_ssocko_cgeno_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssocko_cgent_small_tcp4(suite) ->
-    [];
-ttest_ssocko_cgent_small_tcp4(doc) ->
-    [];
 ttest_ssocko_cgent_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgent_small_tcp4,
@@ -46290,10 +44694,6 @@ ttest_ssocko_cgent_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_cgent_small_tcp6(suite) ->
-    [];
-ttest_ssocko_cgent_small_tcp6(doc) ->
-    [];
 ttest_ssocko_cgent_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgent_small_tcp6,
@@ -46314,10 +44714,6 @@ ttest_ssocko_cgent_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssocko_cgent_medium_tcp4(suite) ->
-    [];
-ttest_ssocko_cgent_medium_tcp4(doc) ->
-    [];
 ttest_ssocko_cgent_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgent_medium_tcp4,
@@ -46338,10 +44734,6 @@ ttest_ssocko_cgent_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_cgent_medium_tcp6(suite) ->
-    [];
-ttest_ssocko_cgent_medium_tcp6(doc) ->
-    [];
 ttest_ssocko_cgent_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgent_medium_tcp6,
@@ -46362,10 +44754,6 @@ ttest_ssocko_cgent_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssocko_cgent_large_tcp4(suite) ->
-    [];
-ttest_ssocko_cgent_large_tcp4(doc) ->
-    [];
 ttest_ssocko_cgent_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgent_large_tcp4,
@@ -46386,10 +44774,6 @@ ttest_ssocko_cgent_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_cgent_large_tcp6(suite) ->
-    [];
-ttest_ssocko_cgent_large_tcp6(doc) ->
-    [];
 ttest_ssocko_cgent_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_cgent_large_tcp6,
@@ -46410,10 +44794,6 @@ ttest_ssocko_cgent_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssocko_csockf_small_tcp4(suite) ->
-    [];
-ttest_ssocko_csockf_small_tcp4(doc) ->
-    [];
 ttest_ssocko_csockf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockf_small_tcp4,
@@ -46434,10 +44814,6 @@ ttest_ssocko_csockf_small_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_csockf_small_tcp6(suite) ->
-    [];
-ttest_ssocko_csockf_small_tcp6(doc) ->
-    [];
 ttest_ssocko_csockf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockf_small_tcp6,
@@ -46458,10 +44834,6 @@ ttest_ssocko_csockf_small_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssocko_csockf_small_tcpL(suite) ->
-    [];
-ttest_ssocko_csockf_small_tcpL(doc) ->
-    [];
 ttest_ssocko_csockf_small_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockf_small_tcpL,
@@ -46482,10 +44854,6 @@ ttest_ssocko_csockf_small_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssocko_csockf_medium_tcp4(suite) ->
-    [];
-ttest_ssocko_csockf_medium_tcp4(doc) ->
-    [];
 ttest_ssocko_csockf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockf_medium_tcp4,
@@ -46506,10 +44874,6 @@ ttest_ssocko_csockf_medium_tcp4(Config)
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_csockf_medium_tcp6(suite) ->
-    [];
-ttest_ssocko_csockf_medium_tcp6(doc) ->
-    [];
 ttest_ssocko_csockf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockf_medium_tcp6,
@@ -46530,10 +44894,6 @@ ttest_ssocko_csockf_medium_tcp6(Config)
 %% Domain:       local
 %% 
 
-ttest_ssocko_csockf_medium_tcpL(suite) ->
-    [];
-ttest_ssocko_csockf_medium_tcpL(doc) ->
-    [];
 ttest_ssocko_csockf_medium_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockf_medium_tcpL,
@@ -46554,10 +44914,6 @@ ttest_ssocko_csockf_medium_tcpL(Config)
 %% Domain:       inet
 %%
 
-ttest_ssocko_csockf_large_tcp4(suite) ->
-    [];
-ttest_ssocko_csockf_large_tcp4(doc) ->
-    [];
 ttest_ssocko_csockf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockf_large_tcp4,
@@ -46578,10 +44934,6 @@ ttest_ssocko_csockf_large_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_csockf_large_tcp6(suite) ->
-    [];
-ttest_ssocko_csockf_large_tcp6(doc) ->
-    [];
 ttest_ssocko_csockf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockf_large_tcp6,
@@ -46602,10 +44954,6 @@ ttest_ssocko_csockf_large_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssocko_csockf_large_tcpL(suite) ->
-    [];
-ttest_ssocko_csockf_large_tcpL(doc) ->
-    [];
 ttest_ssocko_csockf_large_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockf_large_tcpL,
@@ -46626,10 +44974,6 @@ ttest_ssocko_csockf_large_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssocko_csocko_small_tcp4(suite) ->
-    [];
-ttest_ssocko_csocko_small_tcp4(doc) ->
-    [];
 ttest_ssocko_csocko_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_small_tcp4,
@@ -46650,10 +44994,6 @@ ttest_ssocko_csocko_small_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_csocko_small_tcp6(suite) ->
-    [];
-ttest_ssocko_csocko_small_tcp6(doc) ->
-    [];
 ttest_ssocko_csocko_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_small_tcp6,
@@ -46674,10 +45014,6 @@ ttest_ssocko_csocko_small_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssocko_csocko_small_tcpL(suite) ->
-    [];
-ttest_ssocko_csocko_small_tcpL(doc) ->
-    [];
 ttest_ssocko_csocko_small_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_small_tcpL,
@@ -46698,10 +45034,6 @@ ttest_ssocko_csocko_small_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssocko_csocko_medium_tcp4(suite) ->
-    [];
-ttest_ssocko_csocko_medium_tcp4(doc) ->
-    [];
 ttest_ssocko_csocko_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_medium_tcp4,
@@ -46722,10 +45054,6 @@ ttest_ssocko_csocko_medium_tcp4(Config)
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_csocko_medium_tcp6(suite) ->
-    [];
-ttest_ssocko_csocko_medium_tcp6(doc) ->
-    [];
 ttest_ssocko_csocko_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_medium_tcp6,
@@ -46746,10 +45074,6 @@ ttest_ssocko_csocko_medium_tcp6(Config)
 %% Domain:       local
 %% 
 
-ttest_ssocko_csocko_medium_tcpL(suite) ->
-    [];
-ttest_ssocko_csocko_medium_tcpL(doc) ->
-    [];
 ttest_ssocko_csocko_medium_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_medium_tcpL,
@@ -46770,10 +45094,6 @@ ttest_ssocko_csocko_medium_tcpL(Config)
 %% Domain:       inet
 %%
 
-ttest_ssocko_csocko_large_tcp4(suite) ->
-    [];
-ttest_ssocko_csocko_large_tcp4(doc) ->
-    [];
 ttest_ssocko_csocko_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_large_tcp4,
@@ -46794,10 +45114,6 @@ ttest_ssocko_csocko_large_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_csocko_large_tcp6(suite) ->
-    [];
-ttest_ssocko_csocko_large_tcp6(doc) ->
-    [];
 ttest_ssocko_csocko_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_large_tcp6,
@@ -46818,10 +45134,6 @@ ttest_ssocko_csocko_large_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssocko_csocko_large_tcpL(suite) ->
-    [];
-ttest_ssocko_csocko_large_tcpL(doc) ->
-    [];
 ttest_ssocko_csocko_large_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_large_tcpL,
@@ -46842,10 +45154,6 @@ ttest_ssocko_csocko_large_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssocko_csockt_small_tcp4(suite) ->
-    [];
-ttest_ssocko_csockt_small_tcp4(doc) ->
-    [];
 ttest_ssocko_csockt_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockt_small_tcp4,
@@ -46866,10 +45174,6 @@ ttest_ssocko_csockt_small_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_csockt_small_tcp6(suite) ->
-    [];
-ttest_ssocko_csockt_small_tcp6(doc) ->
-    [];
 ttest_ssocko_csockt_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_small_tcp6,
@@ -46890,10 +45194,6 @@ ttest_ssocko_csockt_small_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssocko_csockt_small_tcpL(suite) ->
-    [];
-ttest_ssocko_csockt_small_tcpL(doc) ->
-    [];
 ttest_ssocko_csockt_small_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csocko_small_tcpL,
@@ -46914,10 +45214,6 @@ ttest_ssocko_csockt_small_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssocko_csockt_medium_tcp4(suite) ->
-    [];
-ttest_ssocko_csockt_medium_tcp4(doc) ->
-    [];
 ttest_ssocko_csockt_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockt_medium_tcp4,
@@ -46938,10 +45234,6 @@ ttest_ssocko_csockt_medium_tcp4(Config)
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_csockt_medium_tcp6(suite) ->
-    [];
-ttest_ssocko_csockt_medium_tcp6(doc) ->
-    [];
 ttest_ssocko_csockt_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockt_medium_tcp6,
@@ -46962,10 +45254,6 @@ ttest_ssocko_csockt_medium_tcp6(Config)
 %% Domain:       local
 %% 
 
-ttest_ssocko_csockt_medium_tcpL(suite) ->
-    [];
-ttest_ssocko_csockt_medium_tcpL(doc) ->
-    [];
 ttest_ssocko_csockt_medium_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockt_medium_tcpL,
@@ -46986,10 +45274,6 @@ ttest_ssocko_csockt_medium_tcpL(Config)
 %% Domain:       inet
 %%
 
-ttest_ssocko_csockt_large_tcp4(suite) ->
-    [];
-ttest_ssocko_csockt_large_tcp4(doc) ->
-    [];
 ttest_ssocko_csockt_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockt_large_tcp4,
@@ -47010,10 +45294,6 @@ ttest_ssocko_csockt_large_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssocko_csockt_large_tcp6(suite) ->
-    [];
-ttest_ssocko_csockt_large_tcp6(doc) ->
-    [];
 ttest_ssocko_csockt_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockt_large_tcp6,
@@ -47034,10 +45314,6 @@ ttest_ssocko_csockt_large_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssocko_csockt_large_tcpL(suite) ->
-    [];
-ttest_ssocko_csockt_large_tcpL(doc) ->
-    [];
 ttest_ssocko_csockt_large_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssocko_csockt_large_tcpL,
@@ -47058,10 +45334,6 @@ ttest_ssocko_csockt_large_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockt_cgenf_small_tcp4(suite) ->
-    [];
-ttest_ssockt_cgenf_small_tcp4(doc) ->
-    [];
 ttest_ssockt_cgenf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgenf_small_tcp4,
@@ -47082,10 +45354,6 @@ ttest_ssockt_cgenf_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_cgenf_small_tcp6(suite) ->
-    [];
-ttest_ssockt_cgenf_small_tcp6(doc) ->
-    [];
 ttest_ssockt_cgenf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgenf_small_tcp6,
@@ -47106,10 +45374,6 @@ ttest_ssockt_cgenf_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockt_cgenf_medium_tcp4(suite) ->
-    [];
-ttest_ssockt_cgenf_medium_tcp4(doc) ->
-    [];
 ttest_ssockt_cgenf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgenf_medium_tcp4,
@@ -47130,10 +45394,6 @@ ttest_ssockt_cgenf_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_cgenf_medium_tcp6(suite) ->
-    [];
-ttest_ssockt_cgenf_medium_tcp6(doc) ->
-    [];
 ttest_ssockt_cgenf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgenf_medium_tcp6,
@@ -47154,10 +45414,6 @@ ttest_ssockt_cgenf_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockt_cgenf_large_tcp4(suite) ->
-    [];
-ttest_ssockt_cgenf_large_tcp4(doc) ->
-    [];
 ttest_ssockt_cgenf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgenf_large_tcp4,
@@ -47178,10 +45434,6 @@ ttest_ssockt_cgenf_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_cgenf_large_tcp6(suite) ->
-    [];
-ttest_ssockt_cgenf_large_tcp6(doc) ->
-    [];
 ttest_ssockt_cgenf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgenf_large_tcp6,
@@ -47202,10 +45454,6 @@ ttest_ssockt_cgenf_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockt_cgeno_small_tcp4(suite) ->
-    [];
-ttest_ssockt_cgeno_small_tcp4(doc) ->
-    [];
 ttest_ssockt_cgeno_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgeno_small_tcp4,
@@ -47226,10 +45474,6 @@ ttest_ssockt_cgeno_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_cgeno_small_tcp6(suite) ->
-    [];
-ttest_ssockt_cgeno_small_tcp6(doc) ->
-    [];
 ttest_ssockt_cgeno_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgeno_small_tcp6,
@@ -47250,10 +45494,6 @@ ttest_ssockt_cgeno_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockt_cgeno_medium_tcp4(suite) ->
-    [];
-ttest_ssockt_cgeno_medium_tcp4(doc) ->
-    [];
 ttest_ssockt_cgeno_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgeno_medium_tcp4,
@@ -47274,10 +45514,6 @@ ttest_ssockt_cgeno_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_cgeno_medium_tcp6(suite) ->
-    [];
-ttest_ssockt_cgeno_medium_tcp6(doc) ->
-    [];
 ttest_ssockt_cgeno_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgeno_medium_tcp6,
@@ -47298,10 +45534,6 @@ ttest_ssockt_cgeno_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockt_cgeno_large_tcp4(suite) ->
-    [];
-ttest_ssockt_cgeno_large_tcp4(doc) ->
-    [];
 ttest_ssockt_cgeno_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgeno_large_tcp4,
@@ -47322,10 +45554,6 @@ ttest_ssockt_cgeno_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_cgeno_large_tcp6(suite) ->
-    [];
-ttest_ssockt_cgeno_large_tcp6(doc) ->
-    [];
 ttest_ssockt_cgeno_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgeno_large_tcp6,
@@ -47346,10 +45574,6 @@ ttest_ssockt_cgeno_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockt_cgent_small_tcp4(suite) ->
-    [];
-ttest_ssockt_cgent_small_tcp4(doc) ->
-    [];
 ttest_ssockt_cgent_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgent_small_tcp4,
@@ -47370,10 +45594,6 @@ ttest_ssockt_cgent_small_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_cgent_small_tcp6(suite) ->
-    [];
-ttest_ssockt_cgent_small_tcp6(doc) ->
-    [];
 ttest_ssockt_cgent_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgent_small_tcp6,
@@ -47394,10 +45614,6 @@ ttest_ssockt_cgent_small_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockt_cgent_medium_tcp4(suite) ->
-    [];
-ttest_ssockt_cgent_medium_tcp4(doc) ->
-    [];
 ttest_ssockt_cgent_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgent_medium_tcp4,
@@ -47418,10 +45634,6 @@ ttest_ssockt_cgent_medium_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_cgent_medium_tcp6(suite) ->
-    [];
-ttest_ssockt_cgent_medium_tcp6(doc) ->
-    [];
 ttest_ssockt_cgent_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgent_medium_tcp6,
@@ -47442,10 +45654,6 @@ ttest_ssockt_cgent_medium_tcp6(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockt_cgent_large_tcp4(suite) ->
-    [];
-ttest_ssockt_cgent_large_tcp4(doc) ->
-    [];
 ttest_ssockt_cgent_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgent_large_tcp4,
@@ -47466,10 +45674,6 @@ ttest_ssockt_cgent_large_tcp4(Config) wh
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_cgent_large_tcp6(suite) ->
-    [];
-ttest_ssockt_cgent_large_tcp6(doc) ->
-    [];
 ttest_ssockt_cgent_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_cgent_large_tcp6,
@@ -47490,10 +45694,6 @@ ttest_ssockt_cgent_large_tcp6(Config) wh
 %% Domain:       inet
 %%
 
-ttest_ssockt_csockf_small_tcp4(suite) ->
-    [];
-ttest_ssockt_csockf_small_tcp4(doc) ->
-    [];
 ttest_ssockt_csockf_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockf_small_tcp4,
@@ -47514,10 +45714,6 @@ ttest_ssockt_csockf_small_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_csockf_small_tcp6(suite) ->
-    [];
-ttest_ssockt_csockf_small_tcp6(doc) ->
-    [];
 ttest_ssockt_csockf_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockf_small_tcp6,
@@ -47538,10 +45734,6 @@ ttest_ssockt_csockf_small_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockt_csockf_small_tcpL(suite) ->
-    [];
-ttest_ssockt_csockf_small_tcpL(doc) ->
-    [];
 ttest_ssockt_csockf_small_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockf_small_tcpL,
@@ -47562,10 +45754,6 @@ ttest_ssockt_csockf_small_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockt_csockf_medium_tcp4(suite) ->
-    [];
-ttest_ssockt_csockf_medium_tcp4(doc) ->
-    [];
 ttest_ssockt_csockf_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockf_medium_tcp4,
@@ -47586,10 +45774,6 @@ ttest_ssockt_csockf_medium_tcp4(Config)
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_csockf_medium_tcp6(suite) ->
-    [];
-ttest_ssockt_csockf_medium_tcp6(doc) ->
-    [];
 ttest_ssockt_csockf_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockf_medium_tcp6,
@@ -47610,10 +45794,6 @@ ttest_ssockt_csockf_medium_tcp6(Config)
 %% Domain:       local
 %% 
 
-ttest_ssockt_csockf_medium_tcpL(suite) ->
-    [];
-ttest_ssockt_csockf_medium_tcpL(doc) ->
-    [];
 ttest_ssockt_csockf_medium_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockf_medium_tcpL,
@@ -47634,10 +45814,6 @@ ttest_ssockt_csockf_medium_tcpL(Config)
 %% Domain:       inet
 %%
 
-ttest_ssockt_csockf_large_tcp4(suite) ->
-    [];
-ttest_ssockt_csockf_large_tcp4(doc) ->
-    [];
 ttest_ssockt_csockf_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockf_large_tcp4,
@@ -47658,10 +45834,6 @@ ttest_ssockt_csockf_large_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_csockf_large_tcp6(suite) ->
-    [];
-ttest_ssockt_csockf_large_tcp6(doc) ->
-    [];
 ttest_ssockt_csockf_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockf_large_tcp6,
@@ -47682,10 +45854,6 @@ ttest_ssockt_csockf_large_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockt_csockf_large_tcpL(suite) ->
-    [];
-ttest_ssockt_csockf_large_tcpL(doc) ->
-    [];
 ttest_ssockt_csockf_large_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockf_large_tcpL,
@@ -47706,10 +45874,6 @@ ttest_ssockt_csockf_large_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockt_csocko_small_tcp4(suite) ->
-    [];
-ttest_ssockt_csocko_small_tcp4(doc) ->
-    [];
 ttest_ssockt_csocko_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_small_tcp4,
@@ -47730,10 +45894,6 @@ ttest_ssockt_csocko_small_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_csocko_small_tcp6(suite) ->
-    [];
-ttest_ssockt_csocko_small_tcp6(doc) ->
-    [];
 ttest_ssockt_csocko_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_small_tcp6,
@@ -47754,10 +45914,6 @@ ttest_ssockt_csocko_small_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockt_csocko_small_tcpL(suite) ->
-    [];
-ttest_ssockt_csocko_small_tcpL(doc) ->
-    [];
 ttest_ssockt_csocko_small_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_small_tcpL,
@@ -47778,10 +45934,6 @@ ttest_ssockt_csocko_small_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockt_csocko_medium_tcp4(suite) ->
-    [];
-ttest_ssockt_csocko_medium_tcp4(doc) ->
-    [];
 ttest_ssockt_csocko_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_medium_tcp4,
@@ -47802,10 +45954,6 @@ ttest_ssockt_csocko_medium_tcp4(Config)
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_csocko_medium_tcp6(suite) ->
-    [];
-ttest_ssockt_csocko_medium_tcp6(doc) ->
-    [];
 ttest_ssockt_csocko_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_medium_tcp6,
@@ -47826,10 +45974,6 @@ ttest_ssockt_csocko_medium_tcp6(Config)
 %% Domain:       local
 %% 
 
-ttest_ssockt_csocko_medium_tcpL(suite) ->
-    [];
-ttest_ssockt_csocko_medium_tcpL(doc) ->
-    [];
 ttest_ssockt_csocko_medium_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_medium_tcpL,
@@ -47850,10 +45994,6 @@ ttest_ssockt_csocko_medium_tcpL(Config)
 %% Domain:       inet
 %%
 
-ttest_ssockt_csocko_large_tcp4(suite) ->
-    [];
-ttest_ssockt_csocko_large_tcp4(doc) ->
-    [];
 ttest_ssockt_csocko_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_large_tcp4,
@@ -47874,10 +46014,6 @@ ttest_ssockt_csocko_large_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_csocko_large_tcp6(suite) ->
-    [];
-ttest_ssockt_csocko_large_tcp6(doc) ->
-    [];
 ttest_ssockt_csocko_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_large_tcp6,
@@ -47898,10 +46034,6 @@ ttest_ssockt_csocko_large_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockt_csocko_large_tcpL(suite) ->
-    [];
-ttest_ssockt_csocko_large_tcpL(doc) ->
-    [];
 ttest_ssockt_csocko_large_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_large_tcpL,
@@ -47922,10 +46054,6 @@ ttest_ssockt_csocko_large_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockt_csockt_small_tcp4(suite) ->
-    [];
-ttest_ssockt_csockt_small_tcp4(doc) ->
-    [];
 ttest_ssockt_csockt_small_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockt_small_tcp4,
@@ -47946,10 +46074,6 @@ ttest_ssockt_csockt_small_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_csockt_small_tcp6(suite) ->
-    [];
-ttest_ssockt_csockt_small_tcp6(doc) ->
-    [];
 ttest_ssockt_csockt_small_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_small_tcp6,
@@ -47970,10 +46094,6 @@ ttest_ssockt_csockt_small_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockt_csockt_small_tcpL(suite) ->
-    [];
-ttest_ssockt_csockt_small_tcpL(doc) ->
-    [];
 ttest_ssockt_csockt_small_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csocko_small_tcpL,
@@ -47994,10 +46114,6 @@ ttest_ssockt_csockt_small_tcpL(Config) w
 %% Domain:       inet
 %%
 
-ttest_ssockt_csockt_medium_tcp4(suite) ->
-    [];
-ttest_ssockt_csockt_medium_tcp4(doc) ->
-    [];
 ttest_ssockt_csockt_medium_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockt_medium_tcp4,
@@ -48018,10 +46134,6 @@ ttest_ssockt_csockt_medium_tcp4(Config)
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_csockt_medium_tcp6(suite) ->
-    [];
-ttest_ssockt_csockt_medium_tcp6(doc) ->
-    [];
 ttest_ssockt_csockt_medium_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockt_medium_tcp6,
@@ -48042,10 +46154,6 @@ ttest_ssockt_csockt_medium_tcp6(Config)
 %% Domain:       local
 %% 
 
-ttest_ssockt_csockt_medium_tcpL(suite) ->
-    [];
-ttest_ssockt_csockt_medium_tcpL(doc) ->
-    [];
 ttest_ssockt_csockt_medium_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockt_medium_tcpL,
@@ -48066,10 +46174,6 @@ ttest_ssockt_csockt_medium_tcpL(Config)
 %% Domain:       inet
 %%
 
-ttest_ssockt_csockt_large_tcp4(suite) ->
-    [];
-ttest_ssockt_csockt_large_tcp4(doc) ->
-    [];
 ttest_ssockt_csockt_large_tcp4(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockt_large_tcp4,
@@ -48090,10 +46194,6 @@ ttest_ssockt_csockt_large_tcp4(Config) w
 %% Domain:       inet6
 %% 
 
-ttest_ssockt_csockt_large_tcp6(suite) ->
-    [];
-ttest_ssockt_csockt_large_tcp6(doc) ->
-    [];
 ttest_ssockt_csockt_large_tcp6(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockt_large_tcp6,
@@ -48114,10 +46214,6 @@ ttest_ssockt_csockt_large_tcp6(Config) w
 %% Domain:       local
 %% 
 
-ttest_ssockt_csockt_large_tcpL(suite) ->
-    [];
-ttest_ssockt_csockt_large_tcpL(doc) ->
-    [];
 ttest_ssockt_csockt_large_tcpL(Config) when is_list(Config) ->
     Runtime = which_ttest_runtime(Config),
     ttest_tcp(ttest_ssockt_csockt_large_tcpL,
@@ -48198,7 +46294,9 @@ ttest_tcp(TC,
                            %% (even on reasonably powerful machines),
                            %% so its much simpler to just skip on darwin...
                            has_support_unix_domain_socket(),
-                           is_not_darwin(); 
+                           is_not_darwin();
+                       (Domain =:= inet) ->
+                           has_support_ipv4();
                        (Domain =:= inet6) ->
                            has_support_ipv6();
                        true -> ok 
@@ -48978,13 +47076,10 @@ which_ttest_reports(Domain, MsgID) ->
 %% Create several acceptor processes (processes that calls socket:accept/1)
 %% and then a couple of clients connects to them without any problems.
 %% TCP, IPv4.
-otp16359_maccept_tcp4(suite) ->
-    [];
-otp16359_maccept_tcp4(doc) ->
-    [];
 otp16359_maccept_tcp4(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(otp16359_maccept_tcp4,
+           fun() -> has_support_ipv4() end,
            fun() ->
                    InitState = #{domain   => inet,
                                  protocol => tcp},
@@ -48997,10 +47092,6 @@ otp16359_maccept_tcp4(_Config) when is_l
 %% Create several acceptor processes (processes that calls socket:accept/1)
 %% and then a couple of clients connects to them without any problems.
 %% TCP, IPv6.
-otp16359_maccept_tcp6(suite) ->
-    [];
-otp16359_maccept_tcp6(doc) ->
-    [];
 otp16359_maccept_tcp6(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(otp16359_maccept_tcp6,
@@ -49017,10 +47108,6 @@ otp16359_maccept_tcp6(_Config) when is_l
 %% Create several acceptor processes (processes that calls socket:accept/1)
 %% and then a couple of clients connects to them without any problems.
 %% TCP, UNix Domain Sockets.
-otp16359_maccept_tcpL(suite) ->
-    [];
-otp16359_maccept_tcpL(doc) ->
-    [];
 otp16359_maccept_tcpL(_Config) when is_list(_Config) ->
     ?TT(?SECS(10)),
     tc_try(otp16359_maccept_tcpL,
@@ -49878,6 +47965,7 @@ has_support_sock_bindtodevice() ->
     has_support_socket_option_sock(bindtodevice).
 
 has_support_sock_broadcast() ->
+    has_support_ipv4(),
     has_support_socket_option_sock(broadcast),
     case ?LIB:which_local_host_info(inet) of
         {ok, #{flags := Flags}} ->
@@ -50180,11 +48268,24 @@ has_support_sctp() ->
 
 
 %% The idea is that this function shall test if the test host has 
-%% support for IPv6. If not, there is no point in running IPv6 tests.
+%% support for IPv4 or IPv6. If not, there is no point in running corresponding tests.
 %% Currently we just skip.
+has_support_ipv4() ->
+    ?LIB:has_support_ipv4().
+
 has_support_ipv6() ->
     ?LIB:has_support_ipv6().
 
+inet_or_inet6() ->
+    try
+        has_support_ipv4(),
+        inet
+    catch
+        throw:{skip, _Reason} ->
+            has_support_ipv6(),
+            inet6
+    end.
+
 has_support_sendfile() ->
     try socket:is_supported(sendfile) of
         true ->
@@ -51502,9 +49603,6 @@ sock_port(S) ->
         {ok, #{}}             -> undefined
     end.
 
-l2a(S) when is_list(S) ->
-    list_to_atom(S).
-
 l2b(L) when is_list(L) ->
     list_to_binary(L).
 
diff --git a/lib/kernel/test/socket_test_lib.erl b/lib/kernel/test/socket_test_lib.erl
index 1991c3c28a..e03596e42e 100644
--- a/lib/kernel/test/socket_test_lib.erl
+++ b/lib/kernel/test/socket_test_lib.erl
@@ -38,6 +38,7 @@
          print/1, print/2,
 
          %% Generic 'has support' test function(s)
+         has_support_ipv4/0,
          has_support_ipv6/0,
 
          which_local_host_info/1,
@@ -122,6 +123,14 @@ print(F, A) ->
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
+has_support_ipv4() ->
+    case which_local_addr(inet) of
+        {ok, _Addr} ->
+            ok;
+        {error, R1} ->
+            skip(f("Local Address eval failed: ~p", [R1]))
+    end.
+
 has_support_ipv6() ->
     case socket:is_supported(ipv6) of
         true ->
-- 
2.31.1

openSUSE Build Service is sponsored by