File 2623-Augment-tests.patch of Package erlang

From 401aad7f3d3a362377d51692b9800e30e1bbe71e Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Tue, 19 Aug 2025 14:58:36 +0200
Subject: [PATCH 3/3] Augment tests

---
 lib/kernel/test/inet_res_SUITE.erl | 95 +++++++++++++++++++-----------
 1 file changed, 62 insertions(+), 33 deletions(-)

diff --git a/lib/kernel/test/inet_res_SUITE.erl b/lib/kernel/test/inet_res_SUITE.erl
index f8ddab52be..c85a0eef1f 100644
--- a/lib/kernel/test/inet_res_SUITE.erl
+++ b/lib/kernel/test/inet_res_SUITE.erl
@@ -161,24 +161,34 @@ init_per_testcase(Func, Config) ->
     DataDir = proplists:get_value(data_dir, Config),
     try ns_init(zone_dir(Func), PrivDir, DataDir) of
 	NsSpec ->
-            ?P("init_per_testcase -> get resolver lookup"),
-	    Lookup = inet_db:res_option(lookup),
-            ?P("init_per_testcase -> set file:dns"),
-	    inet_db:set_lookup([file,dns]),
-	    case NsSpec of
-		{_,{IP,Port},_} ->
-                    ?P("init_per_testcase -> insert alt nameserver ~p:~w",
-                       [IP, Port]),
-		    inet_db:ins_alt_ns(IP, Port);
-		_ -> ok
-	    end,
+            UpdatedConfig =
+                [{nameserver, NsSpec}] ++
+                case Func of
+                    basic ->
+                        Config;
+                    _ ->
+                        ?P("init_per_testcase -> get resolver lookup"),
+                        Lookup = inet_db:res_option(lookup),
+                        ?P("init_per_testcase -> set file:dns"),
+                        inet_db:set_lookup([file,dns]),
+                        case NsSpec of
+                            {_,{IP,Port},_} ->
+                                ?P("init_per_testcase -> "
+                                   "insert alt nameserver ~p:~w",
+                                   [IP, Port]),
+                                inet_db:ins_alt_ns(IP, Port);
+                            _ -> ok
+                        end,
+                        ?P("init_per_testcase -> saved "
+                           "lookup: ~p", [Lookup]),
+                        [{res_lookup, Lookup} | Config]
+                end,
             %% dbg:tracer(),
             %% dbg:p(all, c),
             %% dbg:tpl(inet_res, query_nss_res, cx),
             ?P("init_per_testcase -> done:"
-               "~n    NsSpec: ~p"
-               "~n    Lookup: ~p", [NsSpec, Lookup]),
-	    [{nameserver, NsSpec}, {res_lookup, Lookup} | Config]
+               "~n    NsSpec: ~p", [NsSpec]),
+            UpdatedConfig
     catch
 	SkipReason ->
             ?P("init_per_testcase -> skip: ~p", [SkipReason]),
@@ -190,17 +200,21 @@ init_per_testcase(Func, Config) ->
     end.
 
 end_per_testcase(_Func, Config) ->
-    inet_db:set_lookup(proplists:get_value(res_lookup, Config)),
     NsSpec = proplists:get_value(nameserver, Config),
-    case NsSpec of
-	{_,{IP,Port},_} ->
-	    inet_db:del_alt_ns(IP, Port);
-	_ -> ok
+    case proplists:lookup(res_lookup, Config) of
+        none ->
+            ok;
+        {res_lookup, Lookup} ->
+            inet_db:set_lookup(Lookup),
+            case NsSpec of
+                {_,{IP,Port},_} ->
+                    inet_db:del_alt_ns(IP, Port);
+                _ -> ok
+            end
     end,
     %% dbg:stop(),
     ns_end(NsSpec, proplists:get_value(priv_dir, Config)).
 
-
 %% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %% Nameserver control
 
@@ -528,6 +542,8 @@ proxy_ns({proxy,_,_,ProxyNS}) -> ProxyNS.
 basic(Config) when is_list(Config) ->
     ?P("begin"),
     NS = ns(Config),
+    NSs = [NS],
+    Options = [{nameservers,NSs},verbose],
     Name = "ns.otptest",
     NameC = caseflip(Name),
     NameD = NameC ++ ".",
@@ -535,7 +551,7 @@ basic(Config) when is_list(Config) ->
     IP2 = {127,0,0,254},
     %%
     %% nslookup
-    {ok,Msg1} = inet_res:nslookup(Name, in, a, [NS]),
+    {ok,Msg1} = inet_res:nslookup(Name, in, a, NSs),
     ?P("nslookup with ~p: ~n      ~p", [Name, Msg1]),
     [RR1, RR2] = lists:sort(inet_dns:msg(Msg1, anlist)),
     IP1 = inet_dns:rr(RR1, data),
@@ -544,7 +560,7 @@ basic(Config) when is_list(Config) ->
     %%io:format("Bin1 = ~w~n", [Bin1]),
     {ok,Msg1} = inet_dns:decode(Bin1),
     %% Now with scrambled case
-    {ok,Msg1b} = inet_res:nslookup(NameC, in, a, [NS]),
+    {ok,Msg1b} = inet_res:nslookup(NameC, in, a, NSs),
     ?P("nslookup with ~p: ~n      ~p", [NameC, Msg1b]),
     [RR1b, RR2b] = lists:sort(inet_dns:msg(Msg1b, anlist)),
     IP1 = inet_dns:rr(RR1b, data),
@@ -560,7 +576,7 @@ basic(Config) when is_list(Config) ->
 	 =:= tolower(inet_dns:rr(RR2b, domain))),
     %%
     %% resolve
-    {ok,Msg2} = inet_res:resolve(Name, in, a, [{nameservers,[NS]},verbose]),
+    {ok,Msg2} = inet_res:resolve(Name, in, a, Options),
     ?P("resolve with ~p: ~n      ~p", [Name, Msg2]),
     [RR1c, RR2c] = lists:sort(inet_dns:msg(Msg2, anlist)),
     IP1 = inet_dns:rr(RR1c, data),
@@ -569,7 +585,7 @@ basic(Config) when is_list(Config) ->
     %%io:format("Bin2 = ~w~n", [Bin2]),
     {ok,Msg2} = inet_dns:decode(Bin2),
     %% Now with scrambled case
-    {ok,Msg2b} = inet_res:resolve(NameC, in, a, [{nameservers,[NS]},verbose]),
+    {ok,Msg2b} = inet_res:resolve(NameC, in, a, Options),
     ?P("resolve with ~p: ~n      ~p", [NameC, Msg2b]),
     [RR1d, RR2d] = lists:sort(inet_dns:msg(Msg2b, anlist)),
     IP1 = inet_dns:rr(RR1d, data),
@@ -585,10 +601,10 @@ basic(Config) when is_list(Config) ->
 	  =:= tolower(inet_dns:rr(RR2d, domain))),
     ?P("resolve \"127.0.0.1\"~n", []),
     {ok, Msg3} =
-        inet_res:resolve("127.0.0.1", in, a, [{nameservers,[NS]},verbose]),
+        inet_res:resolve("127.0.0.1", in, a, Options),
     [] = inet_dns:msg(Msg3, anlist),
     {ok, Msg4} =
-        inet_res:resolve("127.0.0.1", in, ptr, [{nameservers,[NS]},verbose]),
+        inet_res:resolve("127.0.0.1", in, ptr, Options),
     [RR4] = inet_dns:msg(Msg4, anlist),
     "1.0.0.127.in-addr.arpa" = inet_dns:rr(RR4, domain),
     "test1-78901234567890123456789012345678.otptest" =
@@ -598,28 +614,41 @@ basic(Config) when is_list(Config) ->
     ?P("lookup"),
     [IP1, IP2] =
         lists:sort(
-          inet_res:lookup(Name, in, a, [{nameservers,[NS]},verbose])),
+          inet_res:lookup(Name, in, a, Options)),
     [IP1, IP2] =
         lists:sort(
-          inet_res:lookup(NameC, in, a, [{nameservers,[NS]},verbose])),
+          inet_res:lookup(NameC, in, a, Options)),
     [IP1, IP2] =
         lists:sort(
-          inet_res:lookup(NameD, in, a, [{nameservers,[NS]},verbose])),
+          inet_res:lookup(NameD, in, a, Options)),
     %%
     %% gethostbyname
     ?P("gethostbyname"),
-    {ok,#hostent{h_addr_list=IPs1}} = inet_res:gethostbyname(Name),
+    {ok,#hostent{h_addr_list=IPs1}} =
+        inet_res:gethostbyname(Name, inet, Options, infinity),
     [IP1, IP2] = lists:sort(IPs1),
-    {ok,#hostent{h_addr_list=IPs2}} = inet_res:gethostbyname(NameC),
+    {ok,#hostent{h_addr_list=IPs2}} =
+        inet_res:gethostbyname(NameC, inet, Options, infinity),
     [IP1, IP2] = lists:sort(IPs2),
     %%
     %% getbyname
     ?P("getbyname"),
-    {ok,#hostent{h_addr_list=IPs3}} = inet_res:getbyname(Name, a),
+    {ok,#hostent{h_addr_list=IPs3}} =
+        inet_res:getbyname(Name, a, Options, infinity),
     [IP1, IP2] = lists:sort(IPs3),
-    {ok,#hostent{h_addr_list=IPs4}} = inet_res:getbyname(NameC, a),
+    {ok,#hostent{h_addr_list=IPs4}} =
+        inet_res:getbyname(NameC, a, Options, infinity),
     [IP1, IP2] = lists:sort(IPs4),
     ?P("end"),
+    %%
+    %% gethostbyaddr
+    ?P("gethostbyaddr"),
+    {ok,#hostent{h_name=Name,
+                 h_addr_list=[IP2]}} =
+        inet_res:gethostbyaddr(IP2, Options, infinity),
+    {ok,#hostent{h_name=Name,
+                 h_addr_list=[IP1]}} =
+        inet_res:gethostbyaddr(IP1, Options, infinity),
     ok.
 
 
-- 
2.51.0

openSUSE Build Service is sponsored by