1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2009-2021. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(inet_res_SUITE).
21
22-include_lib("common_test/include/ct.hrl").
23
24-include_lib("kernel/include/inet.hrl").
25-include_lib("kernel/src/inet_dns.hrl").
26
27-include("kernel_test_lib.hrl").
28
29
30-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
31	 init_per_group/2,end_per_group/2,
32	 init_per_testcase/2, end_per_testcase/2
33        ]).
34-export([basic/1, resolve/1, edns0/1, txt_record/1, files_monitor/1,
35	 nxdomain_reply/1, last_ms_answer/1, intermediate_error/1,
36         servfail_retry_timeout_default/1, servfail_retry_timeout_1000/1,
37         label_compression_limit/1
38        ]).
39-export([
40	 gethostbyaddr/0, gethostbyaddr/1,
41	 gethostbyaddr_v6/0, gethostbyaddr_v6/1,
42	 gethostbyname/0, gethostbyname/1,
43	 gethostbyname_v6/0, gethostbyname_v6/1,
44	 getaddr/0, getaddr/1,
45	 getaddr_v6/0, getaddr_v6/1,
46	 ipv4_to_ipv6/0, ipv4_to_ipv6/1,
47	 host_and_addr/0, host_and_addr/1
48	]).
49
50-define(RUN_NS, "run-ns").
51-define(LOG_FILE, "ns.log").
52
53%% This test suite use a script ?RUN_NS that tries to start
54%% a temporary local nameserver BIND 8 or 9 that must be installed
55%% on your machine.
56%%
57%% For example, on Ubuntu 16.04 / 18.04, as root:
58%%     apt-get install bind9
59%% Now, that is not enough since Apparmor will not allow
60%% the nameserver daemon /usr/sbin/named to read from the test directory.
61%% Assuming that you run tests in /ldisk/daily_build, and still on
62%% Ubuntu 14.04, make /etc/apparmor.d/local/usr.sbin.named contain:
63%%     /ldisk/daily_build/** r,
64%% And yes; the trailing comma must be there...
65%% And yes; create the file if it does not exist.
66%% And yes; restart the apparmor daemon using "service apparmor restart"
67
68
69suite() ->
70    [{ct_hooks,[ts_install_cth]},
71     {timetrap,{minutes,1}}].
72
73all() ->
74    [basic, resolve, edns0, txt_record, files_monitor,
75     nxdomain_reply, last_ms_answer,
76     intermediate_error,
77     servfail_retry_timeout_default, servfail_retry_timeout_1000,
78     label_compression_limit,
79     gethostbyaddr, gethostbyaddr_v6, gethostbyname,
80     gethostbyname_v6, getaddr, getaddr_v6, ipv4_to_ipv6,
81     host_and_addr].
82
83groups() ->
84    [].
85
86init_per_suite(Config0) ->
87
88    ?P("init_per_suite -> entry with"
89       "~n      Config: ~p"
90       "~n      Nodes:  ~p", [Config0, erlang:nodes()]),
91
92    case ?LIB:init_per_suite(Config0) of
93        {skip, _} = SKIP ->
94            SKIP;
95
96        Config1 when is_list(Config1) ->
97
98            ?P("init_per_suite -> end when "
99               "~n      Config: ~p", [Config1]),
100
101            Config1
102    end.
103
104end_per_suite(Config0) ->
105
106    ?P("end_per_suite -> entry with"
107       "~n      Config: ~p"
108       "~n      Nodes:  ~p", [Config0, erlang:nodes()]),
109
110    Config1 = ?LIB:end_per_suite(Config0),
111
112    ?P("end_per_suite -> "
113       "~n      Nodes: ~p", [erlang:nodes()]),
114
115    Config1. %% We don't actually need to update or return config
116
117
118init_per_group(_GroupName, Config) ->
119    Config.
120
121end_per_group(_GroupName, Config) ->
122    Config.
123
124zone_dir(TC) ->
125    case TC of
126	basic              -> otptest;
127	resolve            -> otptest;
128	edns0              -> otptest;
129	files_monitor      -> otptest;
130	nxdomain_reply     -> otptest;
131	last_ms_answer     -> otptest;
132        intermediate_error ->
133            {internal,
134             #{rcode => ?REFUSED}};
135        servfail_retry_timeout_default ->
136            {internal,
137             #{rcode => ?SERVFAIL, etd => 1500}};
138        servfail_retry_timeout_1000 ->
139            {internal,
140             #{rcode => ?SERVFAIL, etd => 1000}};
141	_ -> undefined
142    end.
143
144init_per_testcase(Func, Config) ->
145
146    ?P("init_per_testcase -> entry with"
147       "~n      Func:   ~p"
148       "~n      Config: ~p", [Func, Config]),
149
150    PrivDir = proplists:get_value(priv_dir, Config),
151    DataDir = proplists:get_value(data_dir, Config),
152    try ns_init(zone_dir(Func), PrivDir, DataDir) of
153	NsSpec ->
154            ?P("init_per_testcase -> get resolver lookup"),
155	    Lookup = inet_db:res_option(lookup),
156            ?P("init_per_testcase -> set file:dns"),
157	    inet_db:set_lookup([file,dns]),
158	    case NsSpec of
159		{_,{IP,Port},_} ->
160                    ?P("init_per_testcase -> insert alt nameserver ~p:~w",
161                       [IP, Port]),
162		    inet_db:ins_alt_ns(IP, Port);
163		_ -> ok
164	    end,
165            %% dbg:tracer(),
166            %% dbg:p(all, c),
167            %% dbg:tpl(inet_res, query_nss_res, cx),
168            ?P("init_per_testcase -> done:"
169               "~n      NsSpec: ~p"
170               "~n      Lookup: ~p", [NsSpec, Lookup]),
171	    [{nameserver, NsSpec}, {res_lookup, Lookup} | Config]
172    catch
173	SkipReason ->
174            ?P("init_per_testcase -> catched:"
175               "~n      SkipReason: ~p", [SkipReason]),
176	    {skip, SkipReason}
177    end.
178
179end_per_testcase(_Func, Config) ->
180    inet_db:set_lookup(proplists:get_value(res_lookup, Config)),
181    NsSpec = proplists:get_value(nameserver, Config),
182    case NsSpec of
183	{_,{IP,Port},_} ->
184	    inet_db:del_alt_ns(IP, Port);
185	_ -> ok
186    end,
187    %% dbg:stop(),
188    ns_end(NsSpec, proplists:get_value(priv_dir, Config)).
189
190
191%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
192%% Nameserver control
193
194ns(Config) ->
195    {_ZoneDir,NS,_P} = proplists:get_value(nameserver, Config),
196    NS.
197
198ns_init(ZoneDir, PrivDir, DataDir) ->
199
200    ?P("ns_init -> entry with"
201       "~n      ZoneDir: ~p"
202       "~n      PrivDir: ~p"
203       "~n      DataDir: ~p", [ZoneDir, PrivDir, DataDir]),
204
205    case {os:type(),ZoneDir} of
206        {_,{internal,ServerSpec}} ->
207            ns_start_internal(ServerSpec);
208	{{unix,_},undefined} ->
209            ?P("ns_init -> nothing"),
210            undefined;
211	{{unix,_},otptest} ->
212            ?P("ns_init -> prepare start"),
213	    PortNum = case {os:type(),os:version()} of
214			  {{unix,solaris},{M,V,_}} when M =< 5, V < 10 ->
215			      11895 + rand:uniform(100);
216			  _ ->
217			      S = ok(gen_udp:open(0, [{reuseaddr,true}])),
218			      PNum = ok(inet:port(S)),
219			      gen_udp:close(S),
220			      PNum
221		      end,
222            ?P("ns_init -> use port number ~p", [PortNum]),
223	    RunNamed = filename:join(DataDir, ?RUN_NS),
224            ?P("ns_init -> use named ~p", [RunNamed]),
225	    NS = {{127,0,0,1},PortNum},
226            ?P("ns_init -> try open port (exec)"),
227	    P = erlang:open_port({spawn_executable,RunNamed},
228				 [{cd,PrivDir},
229				  {line,80},
230				  {args,["127.0.0.1",
231					 integer_to_list(PortNum),
232					 atom_to_list(ZoneDir)]},
233				  stderr_to_stdout,
234				  eof]),
235            ?P("ns_init -> port ~p", [P]),
236	    ns_start(ZoneDir, PrivDir, NS, P);
237	_ ->
238	    throw("Only run on Unix")
239    end.
240
241ns_start(ZoneDir, PrivDir, NS, P) ->
242
243    ?P("ns_start -> await message"),
244
245    case ns_collect(P) of
246	eof ->
247            ?P("ns_start -> eof"),
248	    erlang:error(eof);
249	"Running: "++_ ->
250            ?P("ns_start -> running"),
251	    {ZoneDir,NS,P};
252	"Error: "++Error ->
253            ?P("ns_start -> error: "
254               "~n      ~p", [Error]),
255	    ns_printlog(filename:join([PrivDir,ZoneDir,?LOG_FILE])),
256	    throw(Error);
257	_X ->
258            ?P("ns_start -> retry"),
259	    ns_start(ZoneDir, PrivDir, NS, P)
260    end.
261
262
263ns_start_internal(ServerSpec) ->
264
265    ?P("ns_start_internal -> entry with"
266       "~n      ServerSpec: ~p", [ServerSpec]),
267
268    Parent = self(),
269    Tag = make_ref(),
270    {P,Mref} =
271        spawn_monitor(
272          fun () ->
273                  _ = process_flag(trap_exit, true),
274                  IP = {127,0,0,1},
275                  SocketOpts = [{ip,IP},binary,{active,once}],
276                  S = ok(gen_udp:open(0, SocketOpts)),
277                  Port = ok(inet:port(S)),
278                  ParentMref = monitor(process, Parent),
279                  Parent ! {Tag,{IP,Port},self()},
280                  ns_internal(ServerSpec, ParentMref, Tag, S)
281          end),
282    receive
283        {Tag,_NS,P} = NsSpec ->
284            ?P("ns_start_internal -> ~p started", [P]),
285            demonitor(Mref, [flush]),
286            NsSpec;
287        {'DOWN',Mref,_,_,Reason} ->
288            ?P("ns_start_internal -> failed start:"
289               "~n      ~p", [Reason]),
290            exit({ns_start_internal,Reason})
291    end.
292
293ns_end(undefined, _PrivDir) -> undefined;
294ns_end({ZoneDir,_NS,P}, PrivDir) when is_port(P) ->
295    port_command(P, ["quit",io_lib:nl()]),
296    ns_stop(P),
297    ns_printlog(filename:join([PrivDir,ZoneDir,"ns.log"])),
298    ok;
299ns_end({Tag,_NS,P}, _PrivDir) when is_pid(P) ->
300    Mref = erlang:monitor(process, P),
301    P ! Tag,
302    receive
303        {'DOWN',Mref,_,_,Reason} ->
304            Reason = normal,
305            ok
306    end.
307
308ns_stop(P) ->
309    case ns_collect(P) of
310	eof ->
311	    erlang:port_close(P);
312	_ ->
313	    ns_stop(P)
314    end.
315
316ns_collect(P) ->
317    ns_collect(P, []).
318ns_collect(P, Buf) ->
319    receive
320	{P,{data,{eol,L}}} ->
321	    Line = lists:flatten(lists:reverse(Buf, [L])),
322	    ?P("collected: ~s", [Line]),
323	    Line;
324	{P,{data,{noeol,L}}} ->
325	    ns_collect(P, [L|Buf]);
326	{P,eof} ->
327	    eof
328    end.
329
330ns_printlog(Fname) ->
331    ?P("Name server log file contents:"),
332    case file:read_file(Fname) of
333	{ok,Bin} ->
334	    io:format("~s~n", [Bin]);
335	_ ->
336	    ok
337    end.
338
339%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
340%% Internal name server
341
342ns_internal(ServerSpec, Mref, Tag, S) ->
343    ?P("ns-internal -> await message"),
344    receive
345        {'DOWN',Mref,_,_,Reason} ->
346            ?P("ns-internal -> received DOWN: "
347               "~n      ~p", [Reason]),
348            exit(Reason);
349        Tag ->
350            ?P("ns-internal -> received tag: done"),
351            ok;
352        {udp,S,IP,Port,Data} ->
353            ?P("ns-internal -> received UDP message"),
354            Req = ok(inet_dns:decode(Data)),
355            {Resp, ServerSpec2} = ns_internal(ServerSpec, Req),
356            RespData = inet_dns:encode(Resp),
357            _ = ok(gen_udp:send(S, IP, Port, RespData)),
358            _ = ok(inet:setopts(S, [{active,once}])),
359            ns_internal(ServerSpec2, Mref, Tag, S)
360    end.
361
362ns_internal(#{rcode := Rcode,
363              ts    := TS0,
364              etd   := ETD} = ServerSpec, Req) ->
365    ?P("ns-internal -> request received (time validation)"),
366    TS1    = timestamp(),
367    Hdr    = inet_dns:msg(Req, header),
368    Opcode = inet_dns:header(Hdr, opcode),
369    Id     = inet_dns:header(Hdr, id),
370    Rd     = inet_dns:header(Hdr, rd),
371    %%
372    Qdlist = inet_dns:msg(Req, qdlist),
373    ?P("ns-internal -> time validation: "
374       "~n      ETD:       ~w"
375       "~n      TS1 - TS0: ~w", [ETD, TS1 - TS0]),
376    RC = if ((TS1 - TS0) >= ETD) ->
377                 ?P("ns-internal -> time validated"),
378                 ?NOERROR;
379            true ->
380                 ?P("ns-internal -> time validation failed"),
381                 Rcode
382         end,
383    Resp   = inet_dns:make_msg(
384               [{header,
385                 inet_dns:make_header(
386                   [{id,     Id},
387                    {qr,     true},
388                    {opcode, Opcode},
389                    {aa,     true},
390                    {tc,     false},
391                    {rd,     Rd},
392                    {ra,     false},
393                    {rcode,  RC}])},
394                {qdlist, Qdlist}]),
395    {Resp, ServerSpec#{ts => timestamp()}};
396ns_internal(#{rcode := Rcode} = ServerSpec, Req) ->
397    ?P("ns-internal -> request received"),
398    Hdr    = inet_dns:msg(Req, header),
399    Opcode = inet_dns:header(Hdr, opcode),
400    Id     = inet_dns:header(Hdr, id),
401    Rd     = inet_dns:header(Hdr, rd),
402    %%
403    Qdlist = inet_dns:msg(Req, qdlist),
404    Resp   = inet_dns:make_msg(
405               [{header,
406                 inet_dns:make_header(
407                   [{id,Id},
408                    {qr,true},
409                    {opcode,Opcode},
410                    {aa,true},
411                    {tc,false},
412                    {rd,Rd},
413                    {ra,false},
414                    {rcode,Rcode}])},
415                {qdlist,Qdlist}]),
416    {Resp, ServerSpec#{ts => timestamp()}}.
417
418
419%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
420%% Behaviour modifying nameserver proxy
421
422proxy_start(TC, {NS,P}) ->
423    Tag = make_ref(),
424    Parent = self(),
425    Pid =
426	spawn_link(
427	  fun () ->
428		  try proxy_start(TC, NS, P, Parent, Tag)
429		  catch
430                      C:X:Stacktrace ->
431			  ?P("~p Failed starting proxy: "
432                             "~n      Class:      ~w"
433                             "~n      Error:      ~p"
434                             "~n      Stacktrace: ~p",
435                             [self(), C, X, Stacktrace])
436		  end
437	  end),
438    receive {started,Tag,Port} ->
439	    ProxyNS = {{127,0,0,1},Port},
440	    {proxy,Pid,Tag,ProxyNS}
441    end.
442
443proxy_start(TC, NS, P, Parent, Tag) ->
444    {ok,Outbound} = gen_udp:open(0, [binary]),
445    ok = gen_udp:connect(Outbound, NS, P),
446    {ok,Inbound} = gen_udp:open(0, [binary]),
447    {ok,Port} = inet:port(Inbound),
448    Parent ! {started,Tag,Port},
449    proxy(TC, Outbound, NS, P, Inbound).
450
451
452%% To provoke the last_ms_answer bug (OTP-9221) the proxy
453%% * Relays the query to the right nameserver
454%% * Intercepts the reply but holds it until the timer that
455%%   was started when receiving the query fires.
456%% * Repeats the reply with incorrect query ID a number of
457%%   times with a short interval.
458%% * Sends the correct reply, to give a correct test result
459%%   after bug correction.
460%%
461%% The repetition of an incorrect answer with tight interval will keep
462%% inet_res in an inner loop in the code that decrements the remaining
463%% time until it hits 0 which triggers a crash, if the outer timeout
464%% parameter to inet_res:resolve is so short that it runs out during
465%% these repetitions.
466proxy(last_ms_answer, Outbound, NS, P, Inbound) ->
467    receive
468	{udp,Inbound,SrcIP,SrcPort,Data} ->
469	    Time =
470		inet_db:res_option(timeout) div inet_db:res_option(retry),
471	    Tag = erlang:make_ref(),
472	    erlang:send_after(Time - 10, self(), {time,Tag}),
473	    ok = gen_udp:send(Outbound, NS, P, Data),
474	    receive
475		{udp,Outbound,NS,P,Reply} ->
476		    {ok,Msg} = inet_dns:decode(Reply),
477		    Hdr = inet_dns:msg(Msg, header),
478		    Id = inet_dns:header(Hdr, id),
479		    BadHdr =
480			inet_dns:make_header(Hdr, id, (Id+1) band 16#ffff),
481		    BadMsg = inet_dns:make_msg(Msg, header, BadHdr),
482		    BadReply = inet_dns:encode(BadMsg),
483		    receive
484			{time,Tag} ->
485			    proxy__last_ms_answer(
486			      Inbound, SrcIP, SrcPort, BadReply, Reply, 30)
487		    end
488	    end
489    end.
490
491proxy__last_ms_answer(Socket, IP, Port, _, Reply, 0) ->
492    ok = gen_udp:send(Socket, IP, Port, Reply);
493proxy__last_ms_answer(Socket, IP, Port, BadReply, Reply, N) ->
494    ok = gen_udp:send(Socket, IP, Port, BadReply),
495    receive after 1 -> ok end,
496    proxy__last_ms_answer(Socket, IP, Port, BadReply, Reply, N-1).
497
498proxy_wait({proxy,Pid,_,_}) ->
499    Mref = erlang:monitor(process, Pid),
500    receive {'DOWN',Mref,_,_,_} -> ok end.
501
502proxy_ns({proxy,_,_,ProxyNS}) -> ProxyNS.
503
504
505%%
506%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
507
508%% Lookup an A record with different API functions.
509basic(Config) when is_list(Config) ->
510    ?P("begin"),
511    NS = ns(Config),
512    Name = "ns.otptest",
513    NameC = caseflip(Name),
514    IP = {127,0,0,254},
515    %%
516    %% nslookup
517    {ok,Msg1} = inet_res:nslookup(Name, in, a, [NS]),
518    ?P("nslookup with ~p: ~n      ~p", [Name, Msg1]),
519    [RR1] = inet_dns:msg(Msg1, anlist),
520    IP = inet_dns:rr(RR1, data),
521    Bin1 = inet_dns:encode(Msg1),
522    %%io:format("Bin1 = ~w~n", [Bin1]),
523    {ok,Msg1} = inet_dns:decode(Bin1),
524    %% Now with scrambled case
525    {ok,Msg1b} = inet_res:nslookup(NameC, in, a, [NS]),
526    ?P("nslookup with ~p: ~n      ~p", [NameC, Msg1b]),
527    [RR1b] = inet_dns:msg(Msg1b, anlist),
528    IP = inet_dns:rr(RR1b, data),
529    Bin1b = inet_dns:encode(Msg1b),
530    %%io:format("Bin1b = ~w~n", [Bin1b]),
531    {ok,Msg1b} = inet_dns:decode(Bin1b),
532    true =
533	(tolower(inet_dns:rr(RR1, domain))
534	 =:= tolower(inet_dns:rr(RR1b, domain))),
535    %%
536    %% resolve
537    {ok,Msg2} = inet_res:resolve(Name, in, a, [{nameservers,[NS]},verbose]),
538    ?P("resolve with ~p: ~n      ~p", [Name, Msg2]),
539    [RR2] = inet_dns:msg(Msg2, anlist),
540    IP = inet_dns:rr(RR2, data),
541    Bin2 = inet_dns:encode(Msg2),
542    %%io:format("Bin2 = ~w~n", [Bin2]),
543    {ok,Msg2} = inet_dns:decode(Bin2),
544    %% Now with scrambled case
545    {ok,Msg2b} = inet_res:resolve(NameC, in, a, [{nameservers,[NS]},verbose]),
546    ?P("resolve with ~p: ~n      ~p", [NameC, Msg2b]),
547    [RR2b] = inet_dns:msg(Msg2b, anlist),
548    IP = inet_dns:rr(RR2b, data),
549    Bin2b = inet_dns:encode(Msg2b),
550    %%io:format("Bin2b = ~w~n", [Bin2b]),
551    {ok,Msg2b} = inet_dns:decode(Bin2b),
552    true =
553	(tolower(inet_dns:rr(RR2, domain))
554	  =:= tolower(inet_dns:rr(RR2b, domain))),
555    %%
556    %% lookup
557    ?P("lookup"),
558    [IP] = inet_res:lookup(Name, in, a, [{nameservers,[NS]},verbose]),
559    [IP] = inet_res:lookup(NameC, in, a, [{nameservers,[NS]},verbose]),
560    %%
561    %% gethostbyname
562    ?P("gethostbyname"),
563    {ok,#hostent{h_addr_list=[IP]}} = inet_res:gethostbyname(Name),
564    {ok,#hostent{h_addr_list=[IP]}} = inet_res:gethostbyname(NameC),
565    %%
566    %% getbyname
567    ?P("getbyname"),
568    {ok,#hostent{h_addr_list=[IP]}} = inet_res:getbyname(Name, a),
569    {ok,#hostent{h_addr_list=[IP]}} = inet_res:getbyname(NameC, a),
570    ?P("end"),
571    ok.
572
573
574%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
575
576%% Lookup different records using resolve/2..4.
577resolve(Config) when is_list(Config) ->
578    ?P("begin"),
579    Class = in,
580    NS = ns(Config),
581    Domain = "otptest",
582    RDomain4 = "0.0.127.in-addr.arpa",
583    RDomain6 = "0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.ip6.arpa",
584    Name = "resolve."++Domain,
585    L = [{a,Name,[{a,{127,0,0,28}}],undefined},
586	 {aaaa,Name,[{aaaa,{0,0,0,0,0,0,32512,28}}],undefined},
587	 {cname,"cname."++Name,[{cname,Name}],undefined},
588	 {a,"cname."++Name,[{cname,Name},{a,{127,0,0,28}}],undefined},
589	 {ns,"ns."++Name,[],[{ns,Name}]},
590	 {soa,Domain,
591          undefined,
592          [{soa,{"ns.otptest","lsa\\.soa.otptest",1,60,10,300,30}}]},
593	 %% WKS: protocol TCP (6), services (bits) TELNET (23) and SMTP (25)
594	 {wks,"wks."++Name,[{wks,{{127,0,0,28},6,<<0,0,1,64>>}}],undefined},
595	 {ptr,"28."++RDomain4,[{ptr,Name}],undefined},
596	 {ptr,"c.1.0.0.0.0.f.7."++RDomain6,[{ptr,Name}],undefined},
597	 {hinfo,Name,[{hinfo,{"BEAM","Erlang/OTP"}}],undefined},
598	 {mx,RDomain4,[{mx,{10,"mx."++Domain}}],undefined},
599	 {srv,"_srv._tcp."++Name,[{srv,{10,3,4711,Name}}],undefined},
600	 {naptr,"naptr."++Name,
601	  [{naptr,{10,5,"s","http","","_srv._tcp."++Name}}],
602	  undefined},
603	 {txt,"txt."++Name,
604	  [{txt,["Hej ","du ","glade "]},{txt,["ta ","en ","spade!"]}],
605	  undefined},
606	 {mb,"mb."++Name,[{mb,"mx."++Name}],undefined},
607	 {mg,"mg."++Name,[{mg,"lsa\\.mg."++Domain}],undefined},
608	 {mr,"mr."++Name,[{mr,"lsa\\.mr."++Domain}],undefined},
609	 {minfo,"minfo."++Name,
610	  [{minfo,{"minfo-owner."++Name,"minfo-bounce."++Name}}],
611	  undefined},
612         {uri,"uri."++Name,[{uri,{10,3,"http://erlang.org"}}],undefined},
613         {caa,"caa."++Name,
614          [{caa,{1,"iodef","http://iodef.erlang.org"}}],
615          undefined},
616	 {any,"cname."++Name,[{cname,Name}],undefined},
617	 {any,Name,
618	  #{ {a,{127,0,0,28}} => [],
619             {aaaa,{0,0,0,0,0,0,32512,28}} => [],
620             {hinfo,{"BEAM","Erlang/OTP"}} => [] },
621	  undefined}
622	],
623    ?P("resolve -> with edns 0"),
624    resolve(Class, [{edns,0},{nameservers,[NS]}], L),
625    ?P("resolve -> with edns false"),
626    resolve(Class, [{edns,false},{nameservers,[NS]}], L),
627    %% Again, to see ensure the cache does not mess things up
628    ?P("resolve -> with edns 0 (again)"),
629    resolve(Class, [{edns,0},{nameservers,[NS]}], L),
630    ?P("resolve -> with edns false (again)"),
631    Res = resolve(Class, [{edns,false},{nameservers,[NS]}], L),
632    ?P("resolve -> done: ~p", [Res]),
633    Res.
634
635resolve(_Class, _Opts, []) ->
636    ?P("resolve -> done"),
637    ok;
638resolve(Class, Opts, [{Type,Nm,Answers,Authority}=Q|Qs]) ->
639    ?P("resolve ->"
640       "~n      Query:   ~p"
641       "~n      Options: ~p", [Q, Opts]),
642    {Name,NameC} =
643	case erlang:phash2(Q) band 4 of
644	    0 ->
645		{Nm,caseflip(Nm)};
646	    _ ->
647		{caseflip(Nm),Nm}
648	end,
649    NormAnswers = normalize_rrs(Answers),
650    NormNSs = normalize_rrs(Authority),
651    ?P("resolve -> resolve with ~p", [Name]),
652    {ok,Msg} = inet_res:resolve(Name, Class, Type, Opts),
653    check_msg(Class, Type, Msg, NormAnswers, NormNSs),
654    ?P("resolve -> resolve with ~p", [NameC]),
655    {ok,MsgC} = inet_res:resolve(NameC, Class, Type, Opts),
656    check_msg(Class, Type, MsgC, NormAnswers, NormNSs),
657    ?P("resolve -> next"),
658    resolve(Class, Opts, Qs).
659
660
661
662normalize_rrs(undefined = RRs) -> RRs;
663normalize_rrs(RRList) when is_list(RRList) ->
664    lists:sort([normalize_rr(RR) || RR <- RRList]);
665normalize_rrs(RRs) when is_map(RRs) ->
666    maps:fold(
667      fun (RR, V, NormRRs) ->
668              NormRRs#{(normalize_rr(RR)) => V}
669      end, #{}, RRs).
670
671normalize_rr({soa,{NS,HM,Ser,Ref,Ret,Exp,Min}}) ->
672    {tolower(NS),tolower_email(HM),Ser,Ref,Ret,Exp,Min};
673normalize_rr({mx,{Prio,DN}}) ->
674    {Prio,tolower(DN)};
675normalize_rr({srv,{Prio,Weight,Port,DN}}) ->
676    {Prio,Weight,Port,tolower(DN)};
677normalize_rr({naptr,{Order,Pref,Flags,Service,RE,Repl}}) ->
678    {Order,Pref,Flags,Service,RE,tolower(Repl)};
679normalize_rr({minfo,{RespM,ErrM}}) ->
680    {tolower_email(RespM),tolower_email(ErrM)};
681normalize_rr({T,MN}) when T =:= mg; T =:= mr ->
682    tolower_email(MN);
683normalize_rr({T,DN}) when T =:= cname; T =:= ns; T =:= ptr; T =:= mb ->
684    tolower(DN);
685normalize_rr(RR) ->
686    RR.
687
688check_msg(Class, Type, Msg, ExpectedAnswers, ExpectedNSs) ->
689    ?P("check_msg ->"
690       "~n      Type: ~p"
691       "~n      Msg:  ~p", [Type,Msg]),
692    NormAnList =
693        normalize_rrs(
694          [begin
695               Class = inet_dns:rr(RR, class),
696               {inet_dns:rr(RR, type),inet_dns:rr(RR, data)}
697           end || RR <- inet_dns:msg(Msg, anlist)]),
698    NormNsList =
699           normalize_rrs(
700             [begin
701                  Class = inet_dns:rr(RR, class),
702                  {inet_dns:rr(RR, type),inet_dns:rr(RR, data)}
703              end || RR <- inet_dns:msg(Msg, nslist)]),
704    case
705        check_msg(ExpectedAnswers, NormAnList) andalso
706        check_msg(ExpectedNSs, NormNsList)
707    of
708        true ->
709            ok;
710        false
711          when Type =:= ns;
712               Type =:= soa ->
713            %% Some resolvers return the answer to a NS query
714            %% in the answer section instead of in the authority section,
715            %% and some do the same for a SOA query
716            case
717                check_msg(ExpectedAnswers, NormNsList) andalso
718                check_msg(ExpectedNSs, NormAnList)
719            of
720                true ->
721                    ok;
722                false ->
723                    error({Type,
724                           {expected,ExpectedAnswers,ExpectedNSs},
725                           {got,NormAnList,NormNsList}})
726            end;
727        false ->
728            error({Type,
729                   {expected,ExpectedAnswers,ExpectedNSs},
730                   {got,NormAnList,NormNsList}})
731    end,
732    %% Test the encoder against the decoder; the least we can do
733    Buf = inet_dns:encode(Msg),
734    {ok,Msg} = inet_dns:decode(Buf),
735    ok.
736
737check_msg(undefined, RRs) when is_list(RRs)-> true;
738check_msg(RRs1, RRs2) when is_list(RRs1), is_list(RRs2) ->
739    RRs1 =:= RRs2;
740check_msg(Expected, [RR|RRs]) when is_map(Expected) ->
741    case Expected of
742        #{RR := _} ->
743            case RRs of
744                []    -> true;
745                [_|_] -> check_msg(Expected, RRs)
746            end;
747        #{} -> false
748    end;
749check_msg(#{}, []) -> false. % At least one has to be ok
750
751%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
752
753%% Test EDNS and truncation.
754edns0(Config) when is_list(Config) ->
755    ?P("begin"),
756    NS = ns(Config),
757    Domain = "otptest",
758    Filler = "-5678901234567890123456789012345678.",
759    MXs = lists:sort([{10,"mx."++Domain},
760		      {20,"mx1"++Filler++Domain},
761		      {20,"mx2"++Filler++Domain},
762		      {20,"mx3"++Filler++Domain},
763		      {20,"mx4"++Filler++Domain},
764		      {20,"mx5"++Filler++Domain},
765		      {20,"mx6"++Filler++Domain},
766		      {20,"mx7"++Filler++Domain}]),
767    false = inet_db:res_option(edns), % ASSERT
768    true = inet_db:res_option(udp_payload_size) >= 1280, % ASSERT
769    %% These will fall back to TCP
770    MXs = lists:sort(inet_res:lookup(Domain, in, mx, [{nameservers,[NS]},verbose])),
771    %%
772    {ok,#hostent{h_addr_list=As}} = inet_res:getbyname(Domain++".", mx),
773    MXs = lists:sort(As),
774    %%
775    {ok,Msg1} = inet_res:resolve(Domain, in, mx),
776    MXs = lists:sort(inet_res_filter(inet_dns:msg(Msg1, anlist), in, mx)),
777    %% There should be no OPT record in the answer
778    [] = [RR || RR <- inet_dns:msg(Msg1, arlist),
779		inet_dns:rr(RR, type) =:= opt],
780    Buf1 = inet_dns:encode(Msg1),
781    {ok,Msg1} = inet_dns:decode(Buf1),
782    %%
783    %% Use EDNS - should not need to fall back to TCP
784    %% there is no way to tell from the outside.
785    %%
786    {ok,Msg2} = inet_res:resolve(Domain, in, mx, [{edns,0}]),
787    MXs = lists:sort(inet_res_filter(inet_dns:msg(Msg2, anlist), in, mx)),
788    Buf2 = inet_dns:encode(Msg2),
789    {ok,Msg2} = inet_dns:decode(Buf2),
790    Res = case [RR || RR <- inet_dns:msg(Msg2, arlist),
791                      inet_dns:rr(RR, type) =:= opt] of
792              [OptRR] ->
793                  ?P("opt rr:"
794                     "~n      ~p", [inet_dns:rr(OptRR)]),
795                  ok;
796              [] ->
797                  case os:type() of
798                      {unix,sunos} ->
799                          case os:version() of
800                              {M,V,_} when M < 5;  M == 5, V =< 8 ->
801                                  %% In our test park only known platform
802                                  %% with an DNS resolver that cannot do
803                                  %% EDNS0.
804                                  {comment,"No EDNS0"}
805                          end;
806                      _ ->
807                          ok
808                  end
809          end,
810    ?P("done"),
811    Res.
812
813inet_res_filter(Anlist, Class, Type) ->
814    [inet_dns:rr(RR, data) || RR <- Anlist,
815			      inet_dns:rr(RR, type) =:= Type,
816			      inet_dns:rr(RR, class) =:= Class].
817
818
819%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
820
821%% Tests TXT records.
822txt_record(Config) when is_list(Config) ->
823    ?P("begin"),
824    D1 = "cslab.ericsson.net",
825    D2 = "mail1.cslab.ericsson.net",
826    ?P("try nslookup of ~p", [D1]),
827    {ok,#dns_rec{anlist=[RR1]}} =
828	inet_res:nslookup(D1, in, txt),
829    ?P("RR1:"
830       "~n      ~p", [RR1]),
831    ?P("try nslookup of ~p", [D2]),
832    {ok,#dns_rec{anlist=[RR2]}} =
833	inet_res:nslookup(D2, in, txt),
834    ?P("RR2:"
835       "~n      ~p", [RR2]),
836    #dns_rr{domain=D1, class=in, type=txt, data=A1} = RR1,
837    #dns_rr{domain=D2, class=in, type=txt, data=A2} = RR2,
838    case [lists:flatten(A2)] of
839	A1 = [[_|_]] -> ok
840    end,
841    ?P("done"),
842    ok.
843
844
845%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
846
847%% Tests monitoring of /etc/hosts and /etc/resolv.conf, but not them.
848files_monitor(Config) when is_list(Config) ->
849    ?P("begin"),
850    Search = inet_db:res_option(search),
851    HostsFile = inet_db:res_option(hosts_file),
852    ResolvConf = inet_db:res_option(resolv_conf),
853    Inet6 = inet_db:res_option(inet6),
854    try do_files_monitor(Config)
855    after
856        inet_db:res_option(search, Search),
857        inet_db:res_option(resolv_conf, ResolvConf),
858	inet_db:res_option(hosts_file, HostsFile),
859	inet_db:res_option(inet6, Inet6)
860    end,
861    ?P("done"),
862    ok.
863
864do_files_monitor(Config) ->
865    Dir = proplists:get_value(priv_dir, Config),
866    {ok,Hostname} = inet:gethostname(),
867    ?P("Hostname: ~p", [Hostname]),
868    FQDN =
869	case inet_db:res_option(domain) of
870	    "" ->
871		Hostname;
872	    _ ->
873		Hostname++"."++inet_db:res_option(domain)
874	end,
875    ?P("FQDN: ~p", [FQDN]),
876    HostsFile = filename:join(Dir, "files_monitor_hosts"),
877    ResolvConf = filename:join(Dir, "files_monitor_resolv.conf"),
878    ok = inet_db:res_option(resolv_conf, ResolvConf),
879    ok = inet_db:res_option(hosts_file, HostsFile),
880    [] = inet_db:res_option(search),
881    %% The inet function will use its final fallback to find this host
882    {ok,#hostent{h_name = Hostname,
883		 h_addrtype = inet,
884		 h_length = 4,
885		 h_addr_list = [{127,0,0,1}]}} = inet:gethostbyname(Hostname),
886    {ok,#hostent{h_name = FQDN,
887		 h_addrtype = inet,
888		 h_length = 4,
889		 h_addr_list = [{127,0,0,1}]}} = inet:gethostbyname(FQDN),
890    {error,nxdomain} = inet_res:gethostbyname(Hostname),
891    {error,nxdomain} = inet_res:gethostbyname(FQDN),
892    {ok,{127,0,0,10}} = inet:getaddr("mx.otptest", inet),
893    {ok,{0,0,0,0,0,0,32512,28}} = inet:getaddr("resolve.otptest", inet6),
894    %% The inet function will use its final fallback to find this host
895    {ok,#hostent{h_name = Hostname,
896		 h_addrtype = inet6,
897		 h_length = 16,
898		 h_addr_list = [{0,0,0,0,0,0,0,1}]}} =
899	inet:gethostbyname(Hostname, inet6),
900    {ok,#hostent{h_name = FQDN,
901		 h_addrtype = inet6,
902		 h_length = 16,
903		 h_addr_list = [{0,0,0,0,0,0,0,1}]}} =
904	inet:gethostbyname(FQDN, inet6),
905    {error,nxdomain} = inet_res:gethostbyname("resolve"),
906    %% XXX inet does not honour res_option inet6, might be a problem?
907    %% therefore inet_res is called here
908    ok = inet_db:res_option(inet6, true),
909    {ok,#hostent{h_name = "resolve.otptest",
910		 h_addrtype = inet6,
911		 h_length = 16,
912		 h_addr_list = [{0,0,0,0,0,0,32512,28}]}} =
913	inet_res:gethostbyname("resolve.otptest"),
914    {error,nxdomain} = inet_hosts:gethostbyname("files_monitor"),
915    ok = file:write_file(ResolvConf, "search otptest\n"),
916    ok = file:write_file(HostsFile, "::100 files_monitor\n"),
917    receive after 7000 -> ok end, % RES_FILE_UPDATE_TM in inet_res.hrl is 5 s
918    {ok,#hostent{h_name = "resolve.otptest",
919		 h_addrtype = inet6,
920		 h_length = 16,
921		 h_addr_list = [{0,0,0,0,0,0,32512,28}]}} =
922	inet_res:gethostbyname("resolve.otptest"),
923    ["otptest"] = inet_db:res_option(search),
924    {ok,#hostent{h_name = "files_monitor",
925		 h_addrtype = inet6,
926		 h_length = 16,
927		 h_addr_list = [{0,0,0,0,0,0,0,256}]}} =
928	inet_hosts:gethostbyname("files_monitor"),
929    ok = inet_db:res_option(inet6, false),
930    {ok,#hostent{h_name = "resolve.otptest",
931		 h_addrtype = inet,
932		 h_length = 4,
933		 h_addr_list = [{127,0,0,28}]}} =
934	inet:gethostbyname("resolve.otptest"),
935    ok.
936
937%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
938%% Get full DNS answer on nxdomain (when option set)
939%% Check that we get the error code from the first server.
940
941nxdomain_reply(Config) when is_list(Config) ->
942    NS    = ns(Config),
943    Name  = "nxdomain.otptest",
944    Class = in,
945    Type  = a,
946    Opts  =
947        [{nameservers,[NS]}, {servfail_retry_timeout, 1000}, verbose],
948    ?P("try resolve"),
949    {error, nxdomain} = inet_res:resolve(Name, Class, Type, Opts),
950    {error, {nxdomain, Rec}} =
951        inet_res:resolve(Name, Class, Type, [nxdomain_reply|Opts]),
952    ?P("resolved: "
953       "~n      ~p", [Rec]),
954    ok.
955
956
957%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
958
959%% Answer just when timeout is triggered (OTP-9221).
960last_ms_answer(Config) when is_list(Config) ->
961    NS = ns(Config),
962    Name = "ns.otptest",
963    %%IP = {127,0,0,254},
964    Time = inet_db:res_option(timeout) div inet_db:res_option(retry),
965    PSpec = proxy_start(last_ms_answer, NS),
966    ProxyNS = proxy_ns(PSpec),
967    %%
968    %% resolve; whith short timeout to trigger Timeout =:= 0 in inet_res
969    {error,timeout} =
970	inet_res:resolve(
971	  Name, in, a, [{nameservers,[ProxyNS]},verbose], Time + 10),
972    %%
973    proxy_wait(PSpec),
974    ok.
975
976
977%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
978%% First name server answers ?REFUSED, second does not answer.
979%% Check that we get the error code from the first server.
980
981intermediate_error(Config) when is_list(Config) ->
982    NS      = ns(Config),
983    Name    = "ns.otptest",
984    Class   = in,
985    Type    = a,
986    IP      = {127,0,0,1},
987    %% A "name server" that does not respond
988    S       = ok(gen_udp:open(0, [{ip,IP},{active,false}])),
989    Port    = ok(inet:port(S)),
990    NSs     = [NS,{IP,Port}],
991    Opts    = [{nameservers, NSs}, verbose],
992    Timeout = 500,
993    {error, {refused,_}} = inet_res:resolve(Name, Class, Type, Opts, Timeout),
994    _ = gen_udp:close(S),
995    ok.
996
997
998%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
999%% A name server that firstanswers ?SERVFAIL, the second try *if* the retry
1000%% is not received *too soon* (etd) answers noerror.
1001
1002servfail_retry_timeout_default(Config) when is_list(Config) ->
1003    NS        = ns(Config),
1004    Name      = "ns.otptest",
1005    Class     = in,
1006    Type      = a,
1007    Opts      = [{nameservers,[NS]}, verbose],
1008    ?P("try resolve"),
1009    {ok, Rec} = inet_res:resolve(Name, Class, Type, Opts),
1010    ?P("resolved: "
1011       "~n      ~p", [Rec]),
1012    ok.
1013
1014
1015%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1016%% A name server that firstanswers ?SERVFAIL, the second try *if* the retry
1017%% is not received *too soon* (etd) answers noerror.
1018
1019servfail_retry_timeout_1000(Config) when is_list(Config) ->
1020    NS        = ns(Config),
1021    Name      = "ns.otptest",
1022    Class     = in,
1023    Type      = a,
1024    Opts      = [{nameservers,[NS]}, {servfail_retry_timeout, 1000}, verbose],
1025    ?P("try resolve"),
1026    {ok, Rec} = inet_res:resolve(Name, Class, Type, Opts),
1027    ?P("resolved: "
1028       "~n      ~p", [Rec]),
1029    ok.
1030
1031
1032%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1033%% Test that label encoding compression limits at 14 bits pointer size
1034
1035label_compression_limit(Config) when is_list(Config) ->
1036    FirstSz = 4,
1037    Count = 512,
1038    Sz = 16,
1039    %% We create a long DNS message with an answer list containing
1040    %% 1+512+1 RR:s.  The first label is 4 chars that with message
1041    %% and RR overhead places the second label on offset 32.
1042    %% All other labels are 16 chars that with RR overhead
1043    %% places them on offsets of N * 32.
1044    %%
1045    %% The labels are: "ZZZZ", then; "AAAAAAAAAAAAAAAA",
1046    %% "AAAAAAAAAAAAAAAB", incrementing, so no one is
1047    %% equal and can not be compressed, until the last one
1048    %% that refers to the second to last one, so it could be compressed.
1049    %%
1050    %% However, the second to last label lands on offset 512 * 32 = 16384
1051    %% which is out of reach for compression since compression uses
1052    %% a 14 bit reference from the start of the message.
1053    %%
1054    %% The last label can only be compressed when we instead
1055    %% generate a message with *one less* char in the first label,
1056    %% placing the second to last label on offset 16383.
1057    %%
1058    %% So, MsgShort can use compression for the last RR
1059    %% by referring to the second to last RR, but MsgLong can not.
1060    %%
1061    %% Disclaimer:
1062    %%    All offsets and overheads are deduced
1063    %%    through trial and observation
1064    %%
1065    [D | Domains] = gen_domains(Count, lists:duplicate(Sz, $A), []),
1066    LastD = "Y." ++ D,
1067    DomainsCommon = lists:reverse(Domains, [D, LastD]),
1068    DomainsShort =  [lists:duplicate(FirstSz-1, $Z) | DomainsCommon],
1069    DomainsLong =   [lists:duplicate(FirstSz, $Z) | DomainsCommon],
1070    MsgShort = gen_msg(DomainsShort),
1071    MsgLong = gen_msg(DomainsLong),
1072    DataShort = inet_dns:encode(MsgShort),
1073    DataShortSz = byte_size(DataShort),
1074    ?P("DataShort[~w]:~n    ~p~n", [DataShortSz, DataShort]),
1075    DataLong = inet_dns:encode(MsgLong),
1076    DataLongSz = byte_size(DataLong),
1077    ?P("DataLong[~w]:~n    ~p~n", [DataLongSz, DataLong]),
1078    %% When the first (long) RR size pushes the last compressed label out,
1079    %% that occupied a 2 bytes reference, it instead becomes a label
1080    %% with 1 byte size and a final empty label size 1
1081    0 = DataLongSz - (DataShortSz+1 - 2 + 1+Sz+1),
1082    ok.
1083
1084gen_msg(Domains) ->
1085    inet_dns:make_msg(
1086      [{header, inet_dns:make_header()},
1087       {anlist, gen_rrs(Domains)}]).
1088
1089gen_rrs(Domains) ->
1090    [inet_dns:make_rr([{class,in},{type,a},{domain,D},{data,{17,18,19,20}}]) ||
1091        D <- Domains].
1092
1093gen_domains(0, _Domain, Acc) ->
1094    Acc;
1095gen_domains(N, Domain, Acc) ->
1096    gen_domains(
1097      N - 1, incr_domain(Domain), [lists:reverse(Domain) | Acc]).
1098
1099incr_domain([$Z | Domain]) ->
1100    [$A | incr_domain(Domain)];
1101incr_domain([Char | Domain]) ->
1102    [Char+1 | Domain].
1103
1104
1105%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1106%% Compatibility tests. Call the inet_SUITE tests, but with
1107%% lookup = [file,dns] instead of [native]
1108
1109gethostbyaddr() -> inet_SUITE:t_gethostbyaddr().
1110gethostbyaddr(Config) -> inet_SUITE:t_gethostbyaddr(Config).
1111gethostbyaddr_v6() -> inet_SUITE:t_gethostbyaddr_v6().
1112gethostbyaddr_v6(Config) -> inet_SUITE:t_gethostbyaddr_v6(Config).
1113gethostbyname() -> inet_SUITE:t_gethostbyname().
1114gethostbyname(Config) -> inet_SUITE:t_gethostbyname(Config).
1115gethostbyname_v6() -> inet_SUITE:t_gethostbyname_v6().
1116gethostbyname_v6(Config) -> inet_SUITE:t_gethostbyname_v6(Config).
1117getaddr() -> inet_SUITE:t_getaddr().
1118getaddr(Config) -> inet_SUITE:t_getaddr(Config).
1119getaddr_v6() -> inet_SUITE:t_getaddr_v6().
1120getaddr_v6(Config) -> inet_SUITE:t_getaddr_v6(Config).
1121ipv4_to_ipv6() -> inet_SUITE:ipv4_to_ipv6().
1122ipv4_to_ipv6(Config) -> inet_SUITE:ipv4_to_ipv6(Config).
1123host_and_addr() -> inet_SUITE:host_and_addr().
1124host_and_addr(Config) -> inet_SUITE:host_and_addr(Config).
1125
1126
1127timestamp() ->
1128    erlang:monotonic_time(milli_seconds).
1129
1130
1131%% Case flip helper
1132
1133caseflip([C|Cs]) when is_integer(C), $a =< C, C =< $z ->
1134    [(C - $a + $A)|caseflip_skip(Cs)];
1135caseflip([C|Cs]) when is_integer(C), $A =< C, C =< $Z ->
1136    [(C - $A + $a)|caseflip_skip(Cs)];
1137caseflip([C|Cs]) ->
1138    [C|caseflip(Cs)];
1139caseflip([]) ->
1140    [].
1141
1142caseflip_skip([C|Cs]) when is_integer(C), $a =< C, C =< $z ->
1143    [C|caseflip(Cs)];
1144caseflip_skip([C|Cs]) when is_integer(C), $A =< C, C =< $Z ->
1145    [C|caseflip(Cs)];
1146caseflip_skip([C|Cs]) ->
1147    [C|caseflip_skip(Cs)];
1148caseflip_skip([]) ->
1149    [].
1150
1151tolower_email([$.|Cs]) ->
1152    [$.|tolower(Cs)];
1153tolower_email([C|Cs]) ->
1154    [C|tolower_email(Cs)].
1155
1156%% Case fold to lower case according to RFC 4343
1157%%
1158tolower([C|Cs]) when is_integer(C) ->
1159    if  $A =< C, C =< $Z ->
1160	    [(C - $A + $a)|tolower(Cs)];
1161	true ->
1162	    [C|tolower(Cs)]
1163    end;
1164tolower([]) ->
1165    [].
1166
1167-compile({inline,[ok/1]}).
1168ok(ok) -> ok;
1169ok({ok,X}) -> X;
1170ok({error,Reason}) -> error(Reason).
1171