Skip to content

Commit a829427

Browse files
committed
Merge branch 'jimdigriz/kernel/inet_dns/GH-6985' OTP-18713
* jimdigriz/kernel/inet_dns/GH-6985: inet_dns: support TSIG inet_dns: support UPDATE inet_dns: support NOTIFY by name inet_dns: support IXFR by name inet_dns: FORMERR if more than one EDNS(0) option is present inet_res: fix edns0 unit test inet_res: migrate testing from using nsd to knotd inet_dns: order RFC references inet_dns: remove unused defines from inet_dns.hrl inet_dns: remove comment that is no longer true
2 parents 64d8667 + 2473a41 commit a829427

File tree

12 files changed

+1469
-164
lines changed

12 files changed

+1469
-164
lines changed

.github/dockerfiles/Dockerfile.ubuntu-base

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ RUN apt-get install -y git curl && \
6666
ARG EXTRA_LIBS="erlang erlang-doc"
6767
RUN apt-get install -y \
6868
unixodbc odbc-postgresql postgresql ssh openssh-server groff-base gdb \
69-
tinyproxy bind9 nsd expect vsftpd python emacs nano vim \
69+
tinyproxy knot ldnsutils expect vsftpd python emacs nano vim \
7070
linux-tools-common linux-tools-generic jq \
7171
xvfb libgl1-mesa-dri && \
7272
for lib in ${EXTRA_LIBS}; do apt-get install -y ${lib}; done && \

lib/kernel/src/Makefile

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -100,6 +100,7 @@ MODULES = \
100100
inet_config \
101101
inet_db \
102102
inet_dns \
103+
inet_dns_tsig \
103104
inet_epmd_dist \
104105
inet_epmd_socket \
105106
inet_gethost_native \
@@ -268,6 +269,7 @@ $(EBIN)/inet6_sctp.beam: inet_int.hrl
268269
$(EBIN)/inet_config.beam: inet_config.hrl ../include/inet.hrl
269270
$(EBIN)/inet_db.beam: ../include/inet.hrl inet_int.hrl inet_res.hrl inet_dns.hrl inet_config.hrl
270271
$(EBIN)/inet_dns.beam: inet_int.hrl inet_dns.hrl inet_dns_record_adts.hrl
272+
$(EBIN)/inet_dns_tsig.beam: inet_dns.hrl
271273
$(EBIN)/inet_gethost_native.beam: ../include/inet.hrl
272274
$(EBIN)/inet_hosts.beam: ../include/inet.hrl
273275
$(EBIN)/inet_parse.beam: ../include/file.hrl

lib/kernel/src/inet_dns.erl

Lines changed: 146 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -22,15 +22,21 @@
2222
%% Dns record encode/decode
2323
%%
2424
%% RFC 1035: Domain Names - Implementation and Specification
25+
%% RFC 1995: Incremental Zone Transfer in DNS
26+
%% RFC 1996: A Mechanism for Prompt Notification of Zone Changes (DNS NOTIFY)
27+
%% RFC 2136: Dynamic Updates in the Domain Name System (DNS UPDATE)
2528
%% RFC 2181: Clarifications to the DNS Specification
26-
%% RFC 6891: Extension Mechanisms for DNS (EDNS0)
2729
%% RFC 2782: A DNS RR for specifying the location of services (DNS SRV)
2830
%% RFC 2915: The Naming Authority Pointer (NAPTR) DNS Resource Rec
31+
%% RFC 5936: DNS Zone Transfer Protocol (AXFR)
2932
%% RFC 6488: DNS Certification Authority Authorization (CAA) Resource Record
30-
%% RFC 7553: The Uniform Resource Identifier (URI) DNS Resource Record
3133
%% RFC 6762: Multicast DNS
34+
%% RFC 6891: Extension Mechanisms for DNS (EDNS0)
35+
%% RFC 7553: The Uniform Resource Identifier (URI) DNS Resource Record
36+
%% RFC 8945: Secret Key Transaction Authentication for DNS (TSIG)
3237

3338
-export([decode/1, encode/1]).
39+
-export([decode_algname/1, encode_algname/1]).
3440

3541
-import(lists, [reverse/1]).
3642

@@ -157,9 +163,9 @@ do_decode(<<Id:16,
157163
QdCount:16,AnCount:16,NsCount:16,ArCount:16,
158164
QdBuf/binary>>=Buffer) ->
159165
{AnBuf,QdList,QdTC} = decode_query_section(QdBuf,QdCount,Buffer),
160-
{NsBuf,AnList,AnTC} = decode_rr_section(AnBuf,AnCount,Buffer),
161-
{ArBuf,NsList,NsTC} = decode_rr_section(NsBuf,NsCount,Buffer),
162-
{Rest,ArList,ArTC} = decode_rr_section(ArBuf,ArCount,Buffer),
166+
{NsBuf,AnList,AnTC} = decode_rr_section(Opcode,AnBuf,AnCount,Buffer),
167+
{ArBuf,NsList,NsTC} = decode_rr_section(Opcode,NsBuf,NsCount,Buffer),
168+
{Rest,ArList,ArTC} = decode_rr_section(Opcode,ArBuf,ArCount,Buffer),
163169
?MATCH_ELSE_DECODE_ERROR(
164170
Rest,
165171
<<>>,
@@ -217,14 +223,14 @@ decode_query_section(Bin, N, Buffer, Qs) ->
217223
decode_query_section(Rest, N-1, Buffer, [DnsQuery|Qs])
218224
end).
219225

220-
decode_rr_section(Bin, N, Buffer) ->
221-
decode_rr_section(Bin, N, Buffer, []).
226+
decode_rr_section(Opcode, Bin, N, Buffer) ->
227+
decode_rr_section(Opcode, Bin, N, Buffer, []).
222228

223-
decode_rr_section(<<>>=Rest, N, _Buffer, RRs) ->
229+
decode_rr_section(_Opcode, <<>>=Rest, N, _Buffer, RRs) ->
224230
{Rest,reverse(RRs),N =/= 0};
225-
decode_rr_section(Rest, 0, _Buffer, RRs) ->
231+
decode_rr_section(_Opcode, Rest, 0, _Buffer, RRs) ->
226232
{Rest,reverse(RRs),false};
227-
decode_rr_section(Bin, N, Buffer, RRs) ->
233+
decode_rr_section(Opcode, Bin, N, Buffer, RRs) ->
228234
?MATCH_ELSE_DECODE_ERROR(
229235
decode_name(Bin, Buffer),
230236
{<<T:16/unsigned,C:16/unsigned,TTL:4/binary,
@@ -235,6 +241,9 @@ decode_rr_section(Bin, N, Buffer, RRs) ->
235241
RR =
236242
case Type of
237243
?S_OPT ->
244+
%% RFC 6891: 6.1.1. FORMERR if more than one dns_rr_opt
245+
lists:keymember(dns_rr_opt, 1, RRs) andalso
246+
throw(?DECODE_ERROR),
238247
<<ExtRcode,Version,DO:1,Z:15>> = TTL,
239248
DnssecOk = (DO =/= 0),
240249
#dns_rr_opt{
@@ -246,9 +255,37 @@ decode_rr_section(Bin, N, Buffer, RRs) ->
246255
z = Z,
247256
data = D,
248257
do = DnssecOk};
258+
?S_TSIG ->
259+
%% RFC 8945: 5.2. FORMERR if not last
260+
%% RFC 8945: 5.2. FORMERR if more than one dns_rr_tsig
261+
%% (...covered by being last)
262+
Rest =/= <<>> andalso throw(?DECODE_ERROR),
263+
{DR,AlgName} = decode_name(D, Buffer),
264+
?MATCH_ELSE_DECODE_ERROR(
265+
DR,
266+
<<Now:48, Fudge:16, MACSize:16, MAC:MACSize/binary,
267+
OriginalId:16, Error:16,
268+
OtherLen:16, OtherData:OtherLen/binary>>,
269+
#dns_rr_tsig{
270+
domain = Name,
271+
type = Type,
272+
offset = byte_size(Buffer) - byte_size(Bin),
273+
algname = AlgName,
274+
now = Now,
275+
fudge = Fudge,
276+
mac = MAC,
277+
original_id = OriginalId,
278+
error = Error,
279+
other_data = OtherData});
249280
_ ->
250281
{Class,CacheFlush} = decode_class(C),
251-
Data = decode_data(D, Class, Type, Buffer),
282+
Data = if
283+
%% RFC 2136: 2.4. Allow length zero data for UPDATE
284+
Opcode == ?UPDATE, D == <<>> ->
285+
#dns_rr{}#dns_rr.data;
286+
true ->
287+
decode_data(D, Class, Type, Buffer)
288+
end,
252289
<<TimeToLive:32/signed>> = TTL,
253290
#dns_rr{
254291
domain = Name,
@@ -258,7 +295,7 @@ decode_rr_section(Bin, N, Buffer, RRs) ->
258295
data = Data,
259296
func = CacheFlush}
260297
end,
261-
decode_rr_section(Rest, N-1, Buffer, [RR|RRs])
298+
decode_rr_section(Opcode, Rest, N-1, Buffer, [RR|RRs])
262299
end).
263300

264301
%%
@@ -270,12 +307,13 @@ encode(Q) ->
270307
AnCount = length(Q#dns_rec.anlist),
271308
NsCount = length(Q#dns_rec.nslist),
272309
ArCount = length(Q#dns_rec.arlist),
310+
OC = Q#dns_rec.header#dns_header.opcode,
273311
B0 = encode_header(Q#dns_rec.header, QdCount, AnCount, NsCount, ArCount),
274312
C0 = gb_trees:empty(),
275313
{B1,C1} = encode_query_section(B0, C0, Q#dns_rec.qdlist),
276-
{B2,C2} = encode_res_section(B1, C1, Q#dns_rec.anlist),
277-
{B3,C3} = encode_res_section(B2, C2, Q#dns_rec.nslist),
278-
{B,_} = encode_res_section(B3, C3, Q#dns_rec.arlist),
314+
{B2,C2} = encode_res_section(OC, B1, C1, Q#dns_rec.anlist),
315+
{B3,C3} = encode_res_section(OC, B2, C2, Q#dns_rec.nslist),
316+
{B,_} = encode_res_section(OC, B3, C3, Q#dns_rec.arlist),
279317
B.
280318

281319

@@ -307,9 +345,9 @@ encode_query_section(Bin0, Comp0, [#dns_query{domain=DName}=Q | Qs]) ->
307345
%% RFC 1035: 4.1.3. Resource record format
308346
%% RFC 6891: 6.1.2, 6.1.3, 6.2.3 Opt RR format
309347
%%
310-
encode_res_section(Bin, Comp, []) -> {Bin,Comp};
348+
encode_res_section(_Opcode, Bin, Comp, []) -> {Bin,Comp};
311349
encode_res_section(
312-
Bin, Comp,
350+
Opcode, Bin, Comp,
313351
[#dns_rr{
314352
domain = DName,
315353
type = Type,
@@ -318,10 +356,10 @@ encode_res_section(
318356
ttl = TTL,
319357
data = Data} | Rs]) ->
320358
encode_res_section_rr(
321-
Bin, Comp, Rs, DName, Type, Class, CacheFlush,
359+
Opcode, Bin, Comp, Rs, DName, Type, Class, CacheFlush,
322360
<<TTL:32/signed>>, Data);
323361
encode_res_section(
324-
Bin, Comp,
362+
Opcode, Bin, Comp,
325363
[#dns_rr_opt{
326364
domain = DName,
327365
udp_payload_size = UdpPayloadSize,
@@ -332,18 +370,39 @@ encode_res_section(
332370
do = DnssecOk} | Rs]) ->
333371
DO = case DnssecOk of true -> 1; false -> 0 end,
334372
encode_res_section_rr(
335-
Bin, Comp, Rs, DName, ?S_OPT, UdpPayloadSize, false,
336-
<<ExtRCode,Version,DO:1,Z:15>>, Data).
373+
Opcode, Bin, Comp, Rs, DName, ?S_OPT, UdpPayloadSize, false,
374+
<<ExtRCode,Version,DO:1,Z:15>>, Data);
375+
encode_res_section(
376+
Opcode, Bin, Comp,
377+
[#dns_rr_tsig{
378+
domain = DName,
379+
algname = AlgName,
380+
now = Now,
381+
fudge = Fudge,
382+
mac = MAC,
383+
original_id = OriginalId,
384+
error = Error,
385+
other_data = OtherData}]) ->
386+
Data = {AlgName,Now,Fudge,MAC,OriginalId,Error,OtherData},
387+
encode_res_section_rr(
388+
Opcode, Bin, Comp, [], DName, ?S_TSIG, ?S_ANY, false,
389+
<<0:32/signed>>, Data).
337390

338391
encode_res_section_rr(
339-
Bin0, Comp0, Rs, DName, Type, Class, CacheFlush, TTL, Data) ->
392+
Opcode, Bin0, Comp0, Rs, DName, Type, Class, CacheFlush, TTL, Data) ->
340393
T = encode_type(Type),
341394
C = encode_class(Class, CacheFlush),
342395
{Bin,Comp1} = encode_name(Bin0, Comp0, byte_size(Bin0), DName),
343396
Pos = byte_size(Bin)+2+2+byte_size(TTL)+2,
344-
{DataBin,Comp} = encode_data(Comp1, Pos, Type, Class, Data),
397+
{DataBin,Comp} = if
398+
Opcode == update, Data == #dns_rr{}#dns_rr.data ->
399+
{<<>>,Comp1};
400+
true ->
401+
encode_data(Comp1, Pos, Type, Class, Data)
402+
end,
345403
DataSize = byte_size(DataBin),
346404
encode_res_section(
405+
Opcode,
347406
<<Bin/binary,T:16,C:16,TTL/binary,DataSize:16,DataBin/binary>>,
348407
Comp, Rs).
349408

@@ -379,7 +438,8 @@ decode_type(Type) ->
379438
?T_UID -> ?S_UID;
380439
?T_GID -> ?S_GID;
381440
?T_UNSPEC -> ?S_UNSPEC;
382-
%% Query type values which do not appear in resource records
441+
?T_TSIG -> ?S_TSIG;
442+
?T_IXFR -> ?S_IXFR;
383443
?T_AXFR -> ?S_AXFR;
384444
?T_MAILB -> ?S_MAILB;
385445
?T_MAILA -> ?S_MAILA;
@@ -421,7 +481,8 @@ encode_type(Type) ->
421481
?S_UID -> ?T_UID;
422482
?S_GID -> ?T_GID;
423483
?S_UNSPEC -> ?T_UNSPEC;
424-
%% Query type values which do not appear in resource records
484+
?S_TSIG -> ?T_TSIG;
485+
?S_IXFR -> ?T_IXFR;
425486
?S_AXFR -> ?T_AXFR;
426487
?S_MAILB -> ?T_MAILB;
427488
?S_MAILA -> ?T_MAILA;
@@ -444,6 +505,7 @@ decode_class(C0) ->
444505
?C_IN -> in;
445506
?C_CHAOS -> chaos;
446507
?C_HS -> hs;
508+
?C_NONE -> none;
447509
?C_ANY -> any;
448510
_ -> C %% raw unknown class
449511
end,
@@ -463,6 +525,7 @@ encode_class(Class) ->
463525
in -> ?C_IN;
464526
chaos -> ?C_CHAOS;
465527
hs -> ?C_HS;
528+
none -> ?C_NONE;
466529
any -> ?C_ANY;
467530
Class when is_integer(Class) -> Class %% raw unknown class
468531
end.
@@ -472,6 +535,8 @@ decode_opcode(Opcode) ->
472535
?QUERY -> 'query';
473536
?IQUERY -> iquery;
474537
?STATUS -> status;
538+
?NOTIFY -> notify;
539+
?UPDATE -> update;
475540
_ when is_integer(Opcode) -> Opcode %% non-standard opcode
476541
end.
477542

@@ -480,9 +545,11 @@ encode_opcode(Opcode) ->
480545
'query' -> ?QUERY;
481546
iquery -> ?IQUERY;
482547
status -> ?STATUS;
548+
notify -> ?NOTIFY;
549+
update -> ?UPDATE;
483550
_ when is_integer(Opcode) -> Opcode %% non-standard opcode
484551
end.
485-
552+
486553

487554
encode_boolean(true) -> 1;
488555
encode_boolean(false) -> 0;
@@ -707,17 +774,6 @@ decode_name_label(Label, Name, N) ->
707774
%%
708775
%% Data field -> {binary(),NewCompressionTable}
709776
%%
710-
%% Class IN RRs
711-
encode_data(Comp, _, ?S_A, in, Addr) ->
712-
{A,B,C,D} = Addr,
713-
{<<A,B,C,D>>,Comp};
714-
encode_data(Comp, _, ?S_AAAA, in, Addr) ->
715-
{A,B,C,D,E,F,G,H} = Addr,
716-
{<<A:16,B:16,C:16,D:16,E:16,F:16,G:16,H:16>>,Comp};
717-
encode_data(Comp, _, ?S_WKS, in, Data) ->
718-
{{A,B,C,D},Proto,BitMap} = Data,
719-
BitMapBin = iolist_to_binary(BitMap),
720-
{<<A,B,C,D,Proto,BitMapBin/binary>>,Comp};
721777
%% OPT pseudo-RR (of no class) - should not take this way;
722778
%% this must be a #dns_rr{type = ?S_OPT} instead of a #dns_rr_opt{},
723779
%% so good luck getting in particular Class and TTL right...
@@ -734,6 +790,16 @@ encode_data(Comp, Pos, Type, Class, Data) ->
734790
%%
735791
%%
736792
%% Standard RRs (any class)
793+
encode_data(Comp, _, ?S_A, Addr) ->
794+
{A,B,C,D} = Addr,
795+
{<<A,B,C,D>>,Comp};
796+
encode_data(Comp, _, ?S_AAAA, Addr) ->
797+
{A,B,C,D,E,F,G,H} = Addr,
798+
{<<A:16,B:16,C:16,D:16,E:16,F:16,G:16,H:16>>,Comp};
799+
encode_data(Comp, _, ?S_WKS, Data) ->
800+
{{A,B,C,D},Proto,BitMap} = Data,
801+
BitMapBin = iolist_to_binary(BitMap),
802+
{<<A,B,C,D,Proto,BitMapBin/binary>>,Comp};
737803
encode_data(Comp, Pos, ?S_SOA, Data) ->
738804
{MName,RName,Serial,Refresh,Retry,Expiry,Minimum} = Data,
739805
{B1,Comp1} = encode_name(Comp, Pos, MName),
@@ -808,6 +874,17 @@ encode_data(Comp, _, ?S_CAA, Data)->
808874
_ ->
809875
{encode_txt(Data),Comp}
810876
end;
877+
encode_data(Comp, _, ?S_TSIG, Data)->
878+
{AlgName,Now,Fudge,MAC,OriginalId,Error,OtherData} = Data,
879+
%% Bypass name compression (RFC 8945, section 4.2)
880+
{AlgNameEncoded,_} = encode_name(gb_trees:empty(), 0, AlgName),
881+
MACSize = byte_size(MAC),
882+
OtherLen = byte_size(OtherData),
883+
DataB = <<AlgNameEncoded/binary,
884+
Now:48, Fudge:16, MACSize:16, MAC:MACSize/binary,
885+
OriginalId:16, Error:16,
886+
OtherLen:16, OtherData:OtherLen/binary>>,
887+
{DataB,Comp};
811888
%%
812889
%% sofar unknown or non standard
813890
encode_data(Comp, _Pos, Type, Data) when is_integer(Type) ->
@@ -947,3 +1024,35 @@ encode_loc_size(X)
9471024
Multiplier = round(math:pow(10, Exponent)),
9481025
Base = (X + Multiplier - 1) div Multiplier,
9491026
<<Base:4, Exponent:4>>.
1027+
1028+
decode_algname(AlgName) ->
1029+
case AlgName of
1030+
?T_TSIG_HMAC_MD5 -> ?S_TSIG_HMAC_MD5;
1031+
?T_TSIG_GSS_TSIG -> ?S_TSIG_GSS_TSIG;
1032+
?T_TSIG_HMAC_SHA1 -> ?S_TSIG_HMAC_SHA1;
1033+
?T_TSIG_HMAC_SHA1_96 -> ?S_TSIG_HMAC_SHA1_96;
1034+
?T_TSIG_HMAC_SHA224 -> ?S_TSIG_HMAC_SHA224;
1035+
?T_TSIG_HMAC_SHA256 -> ?S_TSIG_HMAC_SHA256;
1036+
?T_TSIG_HMAC_SHA256_128 -> ?S_TSIG_HMAC_SHA256_128;
1037+
?T_TSIG_HMAC_SHA384 -> ?S_TSIG_HMAC_SHA384;
1038+
?T_TSIG_HMAC_SHA384_192 -> ?S_TSIG_HMAC_SHA384_192;
1039+
?T_TSIG_HMAC_SHA512 -> ?S_TSIG_HMAC_SHA512;
1040+
?T_TSIG_HMAC_SHA512_256 -> ?S_TSIG_HMAC_SHA512_256;
1041+
_ -> AlgName % raw unknown algname
1042+
end.
1043+
1044+
encode_algname(Alg) ->
1045+
case Alg of
1046+
?S_TSIG_HMAC_MD5 -> ?T_TSIG_HMAC_MD5;
1047+
?S_TSIG_GSS_TSIG -> ?T_TSIG_GSS_TSIG;
1048+
?S_TSIG_HMAC_SHA1 -> ?T_TSIG_HMAC_SHA1;
1049+
?S_TSIG_HMAC_SHA1_96 -> ?T_TSIG_HMAC_SHA1_96;
1050+
?S_TSIG_HMAC_SHA224 -> ?T_TSIG_HMAC_SHA224;
1051+
?S_TSIG_HMAC_SHA256 -> ?T_TSIG_HMAC_SHA256;
1052+
?S_TSIG_HMAC_SHA256_128 -> ?T_TSIG_HMAC_SHA256_128;
1053+
?S_TSIG_HMAC_SHA384 -> ?T_TSIG_HMAC_SHA384;
1054+
?S_TSIG_HMAC_SHA384_192 -> ?T_TSIG_HMAC_SHA384_192;
1055+
?S_TSIG_HMAC_SHA512 -> ?T_TSIG_HMAC_SHA512;
1056+
?S_TSIG_HMAC_SHA512_256 -> ?T_TSIG_HMAC_SHA512_256;
1057+
Alg when is_list(Alg) -> Alg % raw unknown algname
1058+
end.

0 commit comments

Comments
 (0)