File 0166-snmp-test-Improved-the-IPv6-check.patch of Package erlang
From 5746f522bdeaa0ce799351ebc4767ae22c027db2 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Wed, 18 Dec 2019 18:38:00 +0100
Subject: [PATCH 06/10] [snmp|test] Improved the IPv6 check
Improved the check for IPv6 support.
Instead of asking the test server if current host
support supports IPv6, attempt to test if that
is the case instead. Basically stole the code
from the (new) socket test suite.
---
lib/snmp/test/snmp_agent_SUITE.erl | 78 +++++++++++++++--------
lib/snmp/test/snmp_manager_SUITE.erl | 2 +-
lib/snmp/test/snmp_test_lib.erl | 108 ++++++++++++++++++++++----------
lib/snmp/test/snmp_test_lib.hrl | 3 -
lib/snmp/test/snmp_to_snmpnet_SUITE.erl | 2 +-
5 files changed, 130 insertions(+), 63 deletions(-)
diff --git a/lib/snmp/test/snmp_agent_SUITE.erl b/lib/snmp/test/snmp_agent_SUITE.erl
index 6159aa9dda..8a5ae42659 100644
--- a/lib/snmp/test/snmp_agent_SUITE.erl
+++ b/lib/snmp/test/snmp_agent_SUITE.erl
@@ -739,7 +739,7 @@ init_per_group_ipv6(GroupName, Config, Init) ->
false ->
%% Even if this host supports IPv6 we don't use it unless its
%% one of the configured/supported IPv6 hosts...
- case (?HAS_SUPPORT_IPV6() andalso ?IS_IPV6_HOST()) of
+ case ?HAS_SUPPORT_IPV6() of
true ->
Init(
snmp_test_lib:init_group_top_dir(
@@ -6757,10 +6757,16 @@ otp_16092_simple_start_and_stop1(Config) ->
?P(otp_16092_simple_start_and_stop1),
?DBG("otp_16092_simple_start_and_stop1 -> entry", []),
- otp_16092_simple_start_and_stop(Config, default, success),
+ TC = fun() ->
+ otp_16092_simple_start_and_stop(Config, default, success)
+ end,
- ?DBG("otp_16092_simple_start_and_stop1 -> done", []),
- ok.
+ Result = otp_16092_try(TC),
+
+ ?DBG("otp_16092_simple_start_and_stop1 -> done: "
+ "~n ~p", [Result]),
+
+ Result.
otp_16092_simple_start_and_stop2(suite) -> [];
@@ -6768,10 +6774,16 @@ otp_16092_simple_start_and_stop2(Config) ->
?P(otp_16092_simple_start_and_stop2),
?DBG("otp_16092_simple_start_and_stop2 -> entry", []),
- otp_16092_simple_start_and_stop(Config, [], success),
+ TC = fun() ->
+ otp_16092_simple_start_and_stop(Config, [], success)
+ end,
- ?DBG("otp_16092_simple_start_and_stop2 -> done", []),
- ok.
+ Result = otp_16092_try(TC),
+
+ ?DBG("otp_16092_simple_start_and_stop2 -> done: "
+ "~n ~p", [Result]),
+
+ Result.
otp_16092_simple_start_and_stop3(suite) -> [];
@@ -6779,10 +6791,18 @@ otp_16092_simple_start_and_stop3(Config) ->
?P(otp_16092_simple_start_and_stop3),
?DBG("otp_16092_simple_start_and_stop3 -> entry", []),
- otp_16092_simple_start_and_stop(Config, 'this-should-be-ignored', success),
+ TC = fun() ->
+ otp_16092_simple_start_and_stop(Config,
+ 'this-should-be-ignored',
+ success)
+ end,
- ?DBG("otp_16092_simple_start_and_stop3 -> done", []),
- ok.
+ Result = otp_16092_try(TC),
+
+ ?DBG("otp_16092_simple_start_and_stop3 -> done: "
+ "~n ~p", [Result]),
+
+ Result.
otp_16092_simple_start_and_stop4(suite) -> [];
@@ -6790,29 +6810,36 @@ otp_16092_simple_start_and_stop4(Config) ->
?P(otp_16092_simple_start_and_stop4),
?DBG("otp_16092_simple_start_and_stop4 -> entry", []),
- otp_16092_simple_start_and_stop(Config, ['this-should-fail'], failure),
+ TC = fun() ->
+ otp_16092_simple_start_and_stop(Config,
+ ['this-should-fail'],
+ failure)
+ end,
+
+ Result = otp_16092_try(TC),
- ?DBG("otp_16092_simple_start_and_stop4 -> done", []),
- ok.
+ ?DBG("otp_16092_simple_start_and_stop4 -> done: "
+ "~n ", [Result]),
+
+ Result.
+otp_16092_try(TC) ->
+ try TC() of
+ Any ->
+ Any
+ catch
+ _:{skip, _} = SKIP ->
+ SKIP
+ end.
+
otp_16092_simple_start_and_stop(Config, ESO, Expected) ->
?line ConfDir = ?config(agent_conf_dir, Config),
?line DbDir = ?config(agent_db_dir, Config),
p("try start agent node~n"),
p(user, "try start agent node~n"),
- Node = case ?ALIB:start_node(agent_16092) of
- {ok, N} ->
- p("agent node ~p started~n", [N]),
- p(user, "agent node ~p started~n", [N]),
- N;
- {error, Reason} ->
- e("Failed starting agent node: "
- "~n ~p"
- "~n", [Reason]),
- ?SKIP({failed_starting_node, Reason})
- end,
+ {ok, Node} = ?ALIB:start_node(agent_16092),
Vsns = [v1],
IP = tuple_to_list(?config(ip, Config)),
@@ -6841,7 +6868,6 @@ otp_16092_simple_start_and_stop(Config, ESO, Expected) ->
{config, ConfOpts},
{net_if, NiOpts}],
-
otp16092_try_start_and_stop_agent(Node, Opts, Expected),
p("try stop agent node ~p~n", [Node]),
@@ -6854,7 +6880,7 @@ otp_16092_simple_start_and_stop(Config, ESO, Expected) ->
p(user, "done~n"),
ok.
-
+
otp16092_try_start_and_stop_agent(Node, Opts, Expected) ->
i("try start snmp (agent) supervisor (on ~p) - expect ~p~n", [Node, Expected]),
case start_standalone_agent(Node, Opts) of
diff --git a/lib/snmp/test/snmp_manager_SUITE.erl b/lib/snmp/test/snmp_manager_SUITE.erl
index 725280389c..8d544c16de 100644
--- a/lib/snmp/test/snmp_manager_SUITE.erl
+++ b/lib/snmp/test/snmp_manager_SUITE.erl
@@ -429,7 +429,7 @@ init_per_group_ipv6(GroupName, Config) ->
false ->
%% Even if this host supports IPv6 we don't use it unless its
%% one of the configures/supported IPv6 hosts...
- case (?HAS_SUPPORT_IPV6() andalso ?IS_IPV6_HOST()) of
+ case ?HAS_SUPPORT_IPV6() of
true ->
ipv6_init(?LIB:init_group_top_dir(GroupName, Config));
false ->
diff --git a/lib/snmp/test/snmp_test_lib.erl b/lib/snmp/test/snmp_test_lib.erl
index 921ae44d7b..d193931bfa 100644
--- a/lib/snmp/test/snmp_test_lib.erl
+++ b/lib/snmp/test/snmp_test_lib.erl
@@ -26,9 +26,10 @@
-export([tc_try/2, tc_try/3]).
-export([hostname/0, hostname/1, localhost/0, localhost/1, os_type/0, sz/1,
display_suite_info/1]).
--export([non_pc_tc_maybe_skip/4, os_based_skip/1,
- has_support_ipv6/0, has_support_ipv6/1,
- is_ipv6_host/0, is_ipv6_host/1]).
+-export([non_pc_tc_maybe_skip/4,
+ os_based_skip/1,
+ has_support_ipv6/0
+ ]).
-export([init_per_suite/1, end_per_suite/1,
init_suite_top_dir/2, init_group_top_dir/2, init_testcase_top_dir/2,
fix_data_dir/1,
@@ -48,6 +49,9 @@
-export([f/2, p/2, print1/2, print2/2, print/5, formated_timestamp/0]).
+-define(SKIP(R), skip(R, ?MODULE, ?LINE)).
+
+
%% ----------------------------------------------------------------------
%% Run test-case
%%
@@ -406,43 +410,83 @@ os_based_skip_check(OsName, OsNames) ->
end.
-%% A basic test to check if current host supports IPv6
+%% A modern take on the "Check if our host handle IPv6" question.
+%%
has_support_ipv6() ->
- case inet:gethostname() of
- {ok, Hostname} ->
- has_support_ipv6(Hostname);
- _ ->
- false
- end.
-
-has_support_ipv6(Hostname) ->
- case inet:getaddr(Hostname, inet6) of
- {ok, Addr} when (size(Addr) =:= 8) andalso
- (element(1, Addr) =/= 0) andalso
- (element(1, Addr) =/= 16#fe80) ->
- true;
+ socket:supports(ipv6) andalso has_valid_ipv6_address().
+
+has_valid_ipv6_address() ->
+ case net:getifaddrs(fun(#{addr := #{family := inet6},
+ flags := Flags}) ->
+ not lists:member(loopback, Flags);
+ (_) ->
+ false
+ end) of
+ {ok, [#{addr := #{addr := LocalAddr}}|_]} ->
+ %% At least one valid address, we pick the first...
+ try validate_ipv6_address(LocalAddr)
+ catch
+ _:_:_ ->
+ false
+ end;
{ok, _} ->
false;
{error, _} ->
false
end.
-
-is_ipv6_host() ->
- case inet:gethostname() of
- {ok, Hostname} ->
- is_ipv6_host(Hostname);
- {error, _} ->
- false
- end.
-
-is_ipv6_host(Hostname) ->
- case ct:require(ipv6_hosts) of
+validate_ipv6_address(LocalAddr) ->
+ Domain = inet6,
+ ServerSock =
+ case socket:open(Domain, dgram, udp) of
+ {ok, SS} ->
+ SS;
+ {error, R2} ->
+ ?SKIP(f("(server) socket open failed: ~p", [R2]))
+ end,
+ LocalSA = #{family => Domain, addr => LocalAddr},
+ ServerPort =
+ case socket:bind(ServerSock, LocalSA) of
+ {ok, P1} ->
+ P1;
+ {error, R3} ->
+ socket:close(ServerSock),
+ ?SKIP(f("(server) socket bind failed: ~p", [R3]))
+ end,
+ ServerSA = LocalSA#{port => ServerPort},
+ ClientSock =
+ case socket:open(Domain, dgram, udp) of
+ {ok, CS} ->
+ CS;
+ {error, R4} ->
+ ?SKIP(f("(client) socket open failed: ~p", [R4]))
+ end,
+ case socket:bind(ClientSock, LocalSA) of
+ {ok, _} ->
+ ok;
+ {error, R5} ->
+ socket:close(ServerSock),
+ socket:close(ClientSock),
+ ?SKIP(f("(client) socket bind failed: ~p", [R5]))
+ end,
+ case socket:sendto(ClientSock, <<"hejsan">>, ServerSA) of
ok ->
- lists:member(list_to_atom(Hostname), ct:get_config(ipv6_hosts));
- _ ->
- false
- end.
+ ok;
+ {error, R6} ->
+ socket:close(ServerSock),
+ socket:close(ClientSock),
+ ?SKIP(f("failed socket sendto test: ~p", [R6]))
+ end,
+ case socket:recvfrom(ServerSock) of
+ {ok, {_, <<"hejsan">>}} ->
+ socket:close(ServerSock),
+ socket:close(ClientSock),
+ true;
+ {error, R7} ->
+ socket:close(ServerSock),
+ socket:close(ClientSock),
+ ?SKIP(f("failed socket recvfrom test: ~p", [R7]))
+ end.
%% ----------------------------------------------------------------
diff --git a/lib/snmp/test/snmp_test_lib.hrl b/lib/snmp/test/snmp_test_lib.hrl
index c91b6d1859..e9f4fa5756 100644
--- a/lib/snmp/test/snmp_test_lib.hrl
+++ b/lib/snmp/test/snmp_test_lib.hrl
@@ -50,10 +50,7 @@
?LIB:non_pc_tc_maybe_skip(Config, Condition, ?MODULE, ?LINE)).
-define(SKIP(Reason), ?LIB:skip(Reason, ?MODULE, ?LINE)).
-define(FAIL(Reason), ?LIB:fail(Reason, ?MODULE, ?LINE)).
--define(IS_IPV6_HOST(), ?LIB:is_ipv6_host()).
--define(IS_IPV6_HOST(H), ?LIB:is_ipv6_host(H)).
-define(HAS_SUPPORT_IPV6(), ?LIB:has_support_ipv6()).
--define(HAS_SUPPORT_IPV6(H), ?LIB:has_support_ipv6(H)).
%% - Time macros -
diff --git a/lib/snmp/test/snmp_to_snmpnet_SUITE.erl b/lib/snmp/test/snmp_to_snmpnet_SUITE.erl
index d612094c35..0863cf0000 100644
--- a/lib/snmp/test/snmp_to_snmpnet_SUITE.erl
+++ b/lib/snmp/test/snmp_to_snmpnet_SUITE.erl
@@ -212,7 +212,7 @@ init_per_group(_, Config) ->
Config.
init_per_group_ipv6(Families, Config) ->
- case ?LIB:has_support_ipv6() of
+ case ?HAS_SUPPORT_IPV6() of
true ->
init_per_group_ip(Families, Config);
false ->
--
2.16.4