Skip to content

Commit

Permalink
inet_dns: support for UPDATE and NOTIFY DNS packets
Browse files Browse the repository at this point in the history
  • Loading branch information
jimdigriz committed Mar 3, 2023
1 parent 99815ee commit d8b1aa4
Show file tree
Hide file tree
Showing 2 changed files with 81 additions and 63 deletions.
90 changes: 55 additions & 35 deletions lib/kernel/src/inet_dns.erl
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,16 @@
%% Dns record encode/decode
%%
%% RFC 1035: Domain Names - Implementation and Specification
%% RFC 1995: Incremental Zone Transfer in DNS
%% RFC 2136: Dynamic Updates in the Domain Name System (DNS UPDATE)
%% RFC 2181: Clarifications to the DNS Specification
%% RFC 2671: Extension Mechanisms for DNS (EDNS0)
%% RFC 2782: A DNS RR for specifying the location of services (DNS SRV)
%% RFC 2915: The Naming Authority Pointer (NAPTR) DNS Resource Rec
%% RFC 5936: DNS Zone Transfer Protocol (AXFR)
%% RFC 6488: DNS Certification Authority Authorization (CAA) Resource Record
%% RFC 7553: The Uniform Resource Identifier (URI) DNS Resource Record
%% RFC 6762: Multicast DNS
%% RFC 7553: The Uniform Resource Identifier (URI) DNS Resource Record

-export([decode/1, encode/1]).

Expand Down Expand Up @@ -147,14 +150,15 @@ decode(Buffer) when is_binary(Buffer) ->
end.

do_decode(<<Id:16,
QR:1,Opcode:4,AA:1,TC:1,RD:1,
QR:1,Opcode0:4,AA:1,TC:1,RD:1,
RA:1,PR:1,_:2,Rcode:4,
QdCount:16,AnCount:16,NsCount:16,ArCount:16,
QdBuf/binary>>=Buffer) ->
Opcode = decode_opcode(Opcode0),
{AnBuf,QdList,QdTC} = decode_query_section(QdBuf,QdCount,Buffer),
{NsBuf,AnList,AnTC} = decode_rr_section(AnBuf,AnCount,Buffer),
{ArBuf,NsList,NsTC} = decode_rr_section(NsBuf,NsCount,Buffer),
{Rest,ArList,ArTC} = decode_rr_section(ArBuf,ArCount,Buffer),
{NsBuf,AnList,AnTC} = decode_rr_section(Opcode,AnBuf,AnCount,Buffer),
{ArBuf,NsList,NsTC} = decode_rr_section(Opcode,NsBuf,NsCount,Buffer),
{Rest,ArList,ArTC} = decode_rr_section(Opcode,ArBuf,ArCount,Buffer),
?MATCH_ELSE_DECODE_ERROR(
Rest,
<<>>,
Expand All @@ -163,7 +167,7 @@ do_decode(<<Id:16,
DnsHdr =
#dns_header{id=Id,
qr=decode_boolean(QR),
opcode=decode_opcode(Opcode),
opcode=Opcode,
aa=decode_boolean(AA),
tc=HdrTC,
rd=decode_boolean(RD),
Expand Down Expand Up @@ -212,14 +216,14 @@ decode_query_section(Bin, N, Buffer, Qs) ->
decode_query_section(Rest, N-1, Buffer, [DnsQuery|Qs])
end).

decode_rr_section(Bin, N, Buffer) ->
decode_rr_section(Bin, N, Buffer, []).
decode_rr_section(Opcode, Bin, N, Buffer) ->
decode_rr_section(Opcode, Bin, N, Buffer, []).

decode_rr_section(<<>>=Rest, N, _Buffer, RRs) ->
decode_rr_section(_Opcode, <<>>=Rest, N, _Buffer, RRs) ->
{Rest,reverse(RRs),N =/= 0};
decode_rr_section(Rest, 0, _Buffer, RRs) ->
decode_rr_section(_Opcode, Rest, 0, _Buffer, RRs) ->
{Rest,reverse(RRs),false};
decode_rr_section(Bin, N, Buffer, RRs) ->
decode_rr_section(Opcode, Bin, N, Buffer, RRs) ->
?MATCH_ELSE_DECODE_ERROR(
decode_name(Bin, Buffer),
{<<T:16/unsigned,C:16/unsigned,TTL:4/binary,
Expand All @@ -243,7 +247,11 @@ decode_rr_section(Bin, N, Buffer, RRs) ->
data = D};
_ ->
{Class,CacheFlush} = decode_class(C),
Data = decode_data(D, Class, Type, Buffer),
% RFC 2136: 2.4. Allow length zero data for UPDATE
Data = if
Opcode == update, D == <<>> -> #dns_rr_opt{}#dns_rr_opt.data;
true -> decode_data(D, Class, Type, Buffer)
end,
<<TimeToLive:32/signed>> = TTL,
#dns_rr{
domain = Name,
Expand All @@ -253,7 +261,7 @@ decode_rr_section(Bin, N, Buffer, RRs) ->
data = Data,
func = CacheFlush}
end,
decode_rr_section(Rest, N-1, Buffer, [RR|RRs])
decode_rr_section(Opcode, Rest, N-1, Buffer, [RR|RRs])
end).

%%
Expand All @@ -267,10 +275,11 @@ encode(Q) ->
ArCount = length(Q#dns_rec.arlist),
B0 = encode_header(Q#dns_rec.header, QdCount, AnCount, NsCount, ArCount),
C0 = gb_trees:empty(),
OC = Q#dns_rec.header#dns_header.opcode,
{B1,C1} = encode_query_section(B0, C0, Q#dns_rec.qdlist),
{B2,C2} = encode_res_section(B1, C1, Q#dns_rec.anlist),
{B3,C3} = encode_res_section(B2, C2, Q#dns_rec.nslist),
{B,_} = encode_res_section(B3, C3, Q#dns_rec.arlist),
{B2,C2} = encode_res_section(B1, C1, OC, Q#dns_rec.anlist),
{B3,C3} = encode_res_section(B2, C2, OC, Q#dns_rec.nslist),
{B,_} = encode_res_section(B3, C3, OC, Q#dns_rec.arlist),
B.


Expand Down Expand Up @@ -302,9 +311,9 @@ encode_query_section(Bin0, Comp0, [#dns_query{domain=DName}=Q | Qs]) ->
%% RFC 1035: 4.1.3. Resource record format
%% RFC 2671: 4.3, 4.4, 4.6 OPT RR format
%%
encode_res_section(Bin, Comp, []) -> {Bin,Comp};
encode_res_section(Bin, Comp, _Opcode, []) -> {Bin,Comp};
encode_res_section(
Bin, Comp,
Bin, Comp, Opcode,
[#dns_rr{
domain = DName,
type = Type,
Expand All @@ -313,10 +322,10 @@ encode_res_section(
ttl = TTL,
data = Data} | Rs]) ->
encode_res_section_rr(
Bin, Comp, Rs, DName, Type, Class, CacheFlush,
Bin, Comp, Opcode, Rs, DName, Type, Class, CacheFlush,
<<TTL:32/signed>>, Data);
encode_res_section(
Bin, Comp,
Bin, Comp, Opcode,
[#dns_rr_opt{
domain = DName,
udp_payload_size = UdpPayloadSize,
Expand All @@ -325,20 +334,24 @@ encode_res_section(
z = Z,
data = Data} | Rs]) ->
encode_res_section_rr(
Bin, Comp, Rs, DName, ?S_OPT, UdpPayloadSize, false,
Bin, Comp, Opcode, Rs, DName, ?S_OPT, UdpPayloadSize, false,
<<ExtRCode,Version,Z:16>>, Data).

encode_res_section_rr(
Bin0, Comp0, Rs, DName, Type, Class, CacheFlush, TTL, Data) ->
Bin0, Comp0, Opcode, Rs, DName, Type, Class, CacheFlush, TTL, Data) ->
T = encode_type(Type),
C = encode_class(Class, CacheFlush),
{Bin,Comp1} = encode_name(Bin0, Comp0, byte_size(Bin0), DName),
Pos = byte_size(Bin)+2+2+byte_size(TTL)+2,
{DataBin,Comp} = encode_data(Comp1, Pos, Type, Class, Data),
% RFC 2136: 2.4. Allow length zero data for UPDATE
{DataBin,Comp} = if
Opcode == update, Data == #dns_rr_opt{}#dns_rr_opt.data -> {<<>>,Comp1};
true -> encode_data(Comp1, Pos, Type, Class, Data)
end,
DataSize = byte_size(DataBin),
encode_res_section(
<<Bin/binary,T:16,C:16,TTL/binary,DataSize:16,DataBin/binary>>,
Comp, Rs).
Comp, Opcode, Rs).

%%
%% Resource types
Expand Down Expand Up @@ -372,6 +385,7 @@ decode_type(Type) ->
?T_GID -> ?S_GID;
?T_UNSPEC -> ?S_UNSPEC;
%% Query type values which do not appear in resource records
?T_IXFR -> ?S_IXFR;
?T_AXFR -> ?S_AXFR;
?T_MAILB -> ?S_MAILB;
?T_MAILA -> ?S_MAILA;
Expand Down Expand Up @@ -413,6 +427,7 @@ encode_type(Type) ->
?S_GID -> ?T_GID;
?S_UNSPEC -> ?T_UNSPEC;
%% Query type values which do not appear in resource records
?S_IXFR -> ?T_IXFR;
?S_AXFR -> ?T_AXFR;
?S_MAILB -> ?T_MAILB;
?S_MAILA -> ?T_MAILA;
Expand All @@ -435,6 +450,7 @@ decode_class(C0) ->
?C_IN -> in;
?C_CHAOS -> chaos;
?C_HS -> hs;
?C_NONE -> none;
?C_ANY -> any;
_ -> C %% raw unknown class
end,
Expand All @@ -454,6 +470,7 @@ encode_class(Class) ->
in -> ?C_IN;
chaos -> ?C_CHAOS;
hs -> ?C_HS;
none -> ?C_NONE;
any -> ?C_ANY;
Class when is_integer(Class) -> Class %% raw unknown class
end.
Expand All @@ -463,6 +480,8 @@ decode_opcode(Opcode) ->
?QUERY -> 'query';
?IQUERY -> iquery;
?STATUS -> status;
?NOTIFY -> notify;
?UPDATE -> update;
_ when is_integer(Opcode) -> Opcode %% non-standard opcode
end.

Expand All @@ -471,6 +490,8 @@ encode_opcode(Opcode) ->
'query' -> ?QUERY;
iquery -> ?IQUERY;
status -> ?STATUS;
notify -> ?NOTIFY;
update -> ?UPDATE;
_ when is_integer(Opcode) -> Opcode %% non-standard opcode
end.

Expand Down Expand Up @@ -683,17 +704,6 @@ decode_name_label(Label, Name, N) ->
%%
%% Data field -> {binary(),NewCompressionTable}
%%
%% Class IN RRs
encode_data(Comp, _, ?S_A, in, Addr) ->
{A,B,C,D} = Addr,
{<<A,B,C,D>>,Comp};
encode_data(Comp, _, ?S_AAAA, in, Addr) ->
{A,B,C,D,E,F,G,H} = Addr,
{<<A:16,B:16,C:16,D:16,E:16,F:16,G:16,H:16>>,Comp};
encode_data(Comp, _, ?S_WKS, in, Data) ->
{{A,B,C,D},Proto,BitMap} = Data,
BitMapBin = iolist_to_binary(BitMap),
{<<A,B,C,D,Proto,BitMapBin/binary>>,Comp};
%% OPT pseudo-RR (of no class) - should not take this way;
%% this must be a #dns_rr{type = ?S_OPT} instead of a #dns_rr_opt{},
%% so good luck getting in particular Class and TTL right...
Expand All @@ -710,6 +720,16 @@ encode_data(Comp, Pos, Type, Class, Data) ->
%%
%%
%% Standard RRs (any class)
encode_data(Comp, _, ?S_A, Addr) ->
{A,B,C,D} = Addr,
{<<A,B,C,D>>,Comp};
encode_data(Comp, _, ?S_AAAA, Addr) ->
{A,B,C,D,E,F,G,H} = Addr,
{<<A:16,B:16,C:16,D:16,E:16,F:16,G:16,H:16>>,Comp};
encode_data(Comp, _, ?S_WKS, Data) ->
{{A,B,C,D},Proto,BitMap} = Data,
BitMapBin = iolist_to_binary(BitMap),
{<<A,B,C,D,Proto,BitMapBin/binary>>,Comp};
encode_data(Comp, Pos, ?S_SOA, Data) ->
{MName,RName,Serial,Refresh,Retry,Expiry,Minimum} = Data,
{B1,Comp1} = encode_name(Comp, Pos, MName),
Expand Down
54 changes: 26 additions & 28 deletions lib/kernel/src/inet_dns.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -24,32 +24,27 @@
%%
%% Currently defined opcodes
%%
-define(QUERY, 16#0). %% standard query
-define(IQUERY, 16#1). %% inverse query
-define(STATUS, 16#2). %% nameserver status query
%% -define(xxx, 16#3) %% 16#3 reserved
%% non standard
-define(UPDATEA, 16#9). %% add resource record
-define(UPDATED, 16#a). %% delete a specific resource record
-define(UPDATEDA, 16#b). %% delete all nemed resource record
-define(UPDATEM, 16#c). %% modify a specific resource record
-define(UPDATEMA, 16#d). %% modify all named resource record

-define(ZONEINIT, 16#e). %% initial zone transfer
-define(ZONEREF, 16#f). %% incremental zone referesh

-define(QUERY, 16#0). %% standard query
-define(IQUERY, 16#1). %% inverse query
-define(STATUS, 16#2). %% nameserver status query
%%-define(xxx, 16#3). %% reserved
-define(NOTIFY, 16#4). %% notify
-define(UPDATE, 16#5). %% dynamic update

%%
%% Currently defined response codes
%%
-define(NOERROR, 0). %% no error
-define(FORMERR, 1). %% format error
-define(SERVFAIL, 2). %% server failure
-define(NXDOMAIN, 3). %% non existent domain
-define(NOTIMP, 4). %% not implemented
-define(REFUSED, 5). %% query refused
%% non standard
-define(NOCHANGE, 16#f). %% update failed to change db
-define(NOERROR, 0). %% no error
-define(FORMERR, 1). %% format error
-define(SERVFAIL, 2). %% server failure
-define(NXDOMAIN, 3). %% non existent domain
-define(NOTIMP, 4). %% not implemented
-define(REFUSED, 5). %% query refused
-define(YXDOMAIN, 6). %% name exists when it should not (DDNS)
-define(YXRRSET, 7). %% RR set exists when it should not (DDNS)
-define(NXRRSET, 8). %% RR set that should exist does not (DDNS)
-define(NOTAUTH, 9). %% server not authoritative for zone (DDNS)
-define(NOTZONE, 10). %% name not contained in zone (DDNS)
-define(BADVERS, 16).

%%
Expand Down Expand Up @@ -85,10 +80,11 @@
-define(T_GID, 102). %% group ID
-define(T_UNSPEC, 103). %% Unspecified format (binary data)
%% Query type values which do not appear in resource records
-define(T_IXFR, 251). %% incremental transfer zone of authority
-define(T_AXFR, 252). %% transfer zone of authority
-define(T_MAILB, 253). %% transfer mailbox records
-define(T_MAILA, 254). %% transfer mail agent records
-define(T_ANY, 255). %% wildcard match
-define(T_ANY, 255). %% wildcard match (appears in UPDATE though)
%% URI (RFC 7553)
-define(T_URI, 256). %% uniform resource identifier
%% CAA (RFC 6844)
Expand Down Expand Up @@ -127,10 +123,11 @@
-define(S_GID, gid). %% group ID
-define(S_UNSPEC, unspec). %% Unspecified format (binary data)
%% Query type values which do not appear in resource records
-define(S_IXFR, ixfr). %% incremental transfer zone of authority
-define(S_AXFR, axfr). %% transfer zone of authority
-define(S_MAILB, mailb). %% transfer mailbox records
-define(S_MAILA, maila). %% transfer mail agent records
-define(S_ANY, any). %% wildcard match
-define(S_ANY, any). %% wildcard match (appears in UPDATE though)
%% URI (RFC 7553)
-define(S_URI, uri). %% uniform resource identifier
%% CAA (RFC 6844)
Expand All @@ -143,8 +140,9 @@
-define(C_IN, 1). %% the arpa internet
-define(C_CHAOS, 3). %% for chaos net at MIT
-define(C_HS, 4). %% for Hesiod name server at MIT
-define(C_NONE, 254). %% for DDNS (RFC2136, section 2.4)
%% Query class values which do not appear in resource records
-define(C_ANY, 255). %% wildcard match
-define(C_ANY, 255). %% wildcard match (appears in UPDATE though)


%% indirection mask for compressed domain names
Expand Down Expand Up @@ -175,9 +173,9 @@
-record(dns_rec,
{
header, %% dns_header record
qdlist = [], %% list of question entries
anlist = [], %% list of answer entries
nslist = [], %% list of authority entries
qdlist = [], %% list of question (UPDATE -> zone) entries
anlist = [], %% list of answer (UPDATE -> prequisites) entries
nslist = [], %% list of authority (UPDATE -> update) entries
arlist = [] %% list of resource entries
}).

Expand Down

0 comments on commit d8b1aa4

Please sign in to comment.