File 3351-inet_res-add-option-to-include-the-DNS-reply-in-nxdo.patch of Package erlang
From f03b859396c5b0b53bc012f0c31be599ab2648e4 Mon Sep 17 00:00:00 2001
From: Andreas Schultz <andreas.schultz@travelping.com>
Date: Tue, 2 Mar 2021 13:05:51 +0100
Subject: [PATCH 1/2] inet_res: add option to include the DNS reply in nxdomain
errors
A nxdomain error from a name server does contain the SOA record if
the domain exists at all. This record is usefull to determine a TTL
for negative caching of the failed entry.
---
lib/kernel/doc/src/inet_res.xml | 6 +++++
lib/kernel/src/inet_res.erl | 36 +++++++++++++++++++++---------
lib/kernel/test/inet_res_SUITE.erl | 21 ++++++++++++++++-
3 files changed, 51 insertions(+), 12 deletions(-)
diff --git a/lib/kernel/doc/src/inet_res.xml b/lib/kernel/doc/src/inet_res.xml
index 690d1c61d1..0d654bbc0e 100644
--- a/lib/kernel/doc/src/inet_res.xml
+++ b/lib/kernel/doc/src/inet_res.xml
@@ -299,6 +299,12 @@ inet_dns:record_type(_) -> undefined.</pre>
<seemfa marker="stdlib:io#format/3"><c>io:format/2</c></seemfa>
of queries, replies retransmissions, and so on, similar
to from utilities, such as <c>dig</c> and <c>nslookup</c>.</p>
+ <p>Option <c>nxdomain_reply</c> (or rather <c>{nxdomain_reply,true}</c>)
+ causes nxdomain errors from DNS servers to be returned as
+ <c>{error, {nxdomain, dns_msg()}}</c>.
+ <c>dns_msg()</c> contains the additional sections that where included
+ by the answering server. This is mainly useful to inspect the SOA record
+ to get the TTL for negative caching.</p>
<p>If <c><anno>Opt</anno></c> is any atom, it is interpreted
as <c>{<anno>Opt</anno>,true}</c> unless the atom string starts with
<c>"no"</c>, making the
diff --git a/lib/kernel/src/inet_res.erl b/lib/kernel/src/inet_res.erl
index 4208e30c08..536b5abccc 100644
--- a/lib/kernel/src/inet_res.erl
+++ b/lib/kernel/src/inet_res.erl
@@ -61,7 +61,8 @@
| {retry, integer()}
| {timeout, integer()}
| {udp_payload_size, integer()}
- | {usevc, boolean()}.
+ | {usevc, boolean()}
+ | {nxdomain_reply, boolean()}.
-type nameserver() :: {inet:ip_address(), Port :: 1..65535}.
@@ -262,7 +263,7 @@ do_nslookup(Name, Class, Type, Opts, Timeout) ->
%% options record
%%
-record(options, { % These must be sorted!
- alt_nameservers,edns,inet6,nameservers,recurse,
+ alt_nameservers,edns,inet6,nameservers,nxdomain_reply,recurse,
retry,servfail_retry_timeout,timeout,udp_payload_size,usevc,
verbose}). % this is a local option, not in inet_db
%%
@@ -304,6 +305,12 @@ make_options([{verbose,Val}|Opts]=Opts0, [verbose|Names]=Names0) ->
true ->
erlang:error(badarg, [Opts0,Names0])
end;
+make_options([{nxdomain_reply,Val}|Opts]=Opts0, [nxdomain|Names]=Names0) ->
+ if is_boolean(Val) ->
+ [Val|make_options(Opts, Names)];
+ true ->
+ erlang:error(badarg, [Opts0,Names0])
+ end;
make_options([{Opt,Val}|Opts]=Opts0, [Opt|Names]=Names0) ->
case inet_db:res_check_option(Opt, Val) of
true ->
@@ -313,6 +320,8 @@ make_options([{Opt,Val}|Opts]=Opts0, [Opt|Names]=Names0) ->
end;
make_options(Opts, [verbose|Names]) ->
[false|make_options(Opts, Names)];
+make_options(Opts, [nxdomain_reply|Names]) ->
+ [false|make_options(Opts, Names)];
make_options(Opts, [Name|Names]) ->
[inet_db:res_option(Name)|make_options(Opts, Names)].
@@ -778,10 +787,10 @@ do_query(#q{options=#options{retry=Retry}}=Q, NSs, Timer) ->
%% Loop until out of retries or name servers
%%
-query_retries(_Q, _NSs, _Timer, Retry, I, S, Reason) when Retry =:= I ->
- query_retries_error(S, Reason);
-query_retries(_Q, [], _Timer, _Retry, _I, S, Reason) ->
- query_retries_error(S, Reason);
+query_retries(Q, _NSs, _Timer, Retry, I, S, Reason) when Retry =:= I ->
+ query_retries_error(Q, S, Reason);
+query_retries(Q, [], _Timer, _Retry, _I, S, Reason) ->
+ query_retries_error(Q, S, Reason);
query_retries(Q, NSs, Timer, Retry, I, S, Reason) ->
query_nss(Q, NSs, Timer, Retry, I, S, Reason, []).
@@ -878,9 +887,9 @@ query_nss_result(Q, NSs, Timer, Retry, I, S, Reason, RetryNSs, NS, Result) ->
_ = udp_close(S),
Result;
timeout -> % Out of total time timeout
- query_retries_error(S, Reason); % The best reason we have
- {error,{nxdomain=E,_}} ->
- query_retries_error(S, E); % Definite answer
+ query_retries_error(Q, S, Reason); % The best reason we have
+ {error,{nxdomain,_} = E} ->
+ query_retries_error(Q, S, E); % Definite answer
{error,{E,_}=NewReason}
when E =:= qfmterror;
E =:= notimp;
@@ -924,9 +933,14 @@ query_nss_result(Q, NSs, Timer, Retry, I, S, Reason, RetryNSs, NS, Result) ->
query_nss(Q, NSs, Timer, Retry, I, S, NewReason, [NS|RetryNSs])
end.
-query_retries_error(S, Reason) ->
+query_retries_error(#q{options=#options{nxdomain_reply=NxReply}}, S, Reason) ->
_ = udp_close(S),
- {error, Reason}.
+ case Reason of
+ {nxdomain, _} when not NxReply ->
+ {error, nxdomain};
+ _ ->
+ {error, Reason}
+ end.
query_ns(S0, Id, Buffer, IP, Port, Timer, Retry, I,
diff --git a/lib/kernel/test/inet_res_SUITE.erl b/lib/kernel/test/inet_res_SUITE.erl
index 9e25411f74..24e0e40e77 100644
--- a/lib/kernel/test/inet_res_SUITE.erl
+++ b/lib/kernel/test/inet_res_SUITE.erl
@@ -32,7 +32,7 @@
init_per_testcase/2, end_per_testcase/2
]).
-export([basic/1, resolve/1, edns0/1, txt_record/1, files_monitor/1,
- last_ms_answer/1, intermediate_error/1,
+ nxdomain_reply/1, last_ms_answer/1, intermediate_error/1,
servfail_retry_timeout_default/1, servfail_retry_timeout_1000/1,
label_compression_limit/1
]).
@@ -127,6 +127,7 @@ zone_dir(TC) ->
resolve -> otptest;
edns0 -> otptest;
files_monitor -> otptest;
+ nxdomain_reply -> otptest;
last_ms_answer -> otptest;
intermediate_error ->
{internal,
@@ -933,6 +934,24 @@ do_files_monitor(Config) ->
inet:gethostbyname("resolve.otptest"),
ok.
+%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% Get full DNS answer on nxdomain (when option set)
+%% Check that we get the error code from the first server.
+
+nxdomain_reply(Config) when is_list(Config) ->
+ NS = ns(Config),
+ Name = "nxdomain.otptest",
+ Class = in,
+ Type = a,
+ Opts = [{nameservers,[NS]}, {servfail_retry_timeout, 1000}, verbose],
+ ?P("try resolve"),
+ {error, nxdomain} = inet_res:resolve(Name, Class, Type, Opts),
+ {error, {nxdomain, Rec}} = inet_res:resolve(Name, Class, Type, [nxdomain_reply|Opts]),
+ ?P("resolved: "
+ "~n ~p", [Rec]),
+ ok.
+
+
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% Answer just when timeout is triggered (OTP-9221).
--
2.26.2