Skip to content

Commit 2f855f9

Browse files
committed
inet_dns: support SIG(0) [WiP]
1 parent 8aba46a commit 2f855f9

File tree

6 files changed

+382
-3
lines changed

6 files changed

+382
-3
lines changed

bootstrap/lib/kernel/ebin/kernel.app

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -104,6 +104,7 @@
104104
inet,
105105
inet_db,
106106
inet_dns,
107+
inet_dns_sig0,
107108
inet_dns_tsig,
108109
inet_parse,
109110
inet_res,

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_sig0 \
103104
inet_dns_tsig \
104105
inet_epmd_dist \
105106
inet_epmd_socket \
@@ -271,6 +272,7 @@ $(EBIN)/inet6_sctp.beam: inet_int.hrl
271272
$(EBIN)/inet_config.beam: inet_config.hrl ../include/inet.hrl
272273
$(EBIN)/inet_db.beam: ../include/inet.hrl inet_int.hrl inet_res.hrl inet_dns.hrl inet_config.hrl
273274
$(EBIN)/inet_dns.beam: inet_int.hrl inet_dns.hrl inet_dns_record_adts.hrl
275+
$(EBIN)/inet_dns_sig0.beam: inet_dns.hrl
274276
$(EBIN)/inet_dns_tsig.beam: inet_dns.hrl
275277
$(EBIN)/inet_gethost_native.beam: ../include/inet.hrl
276278
$(EBIN)/inet_hosts.beam: ../include/inet.hrl

lib/kernel/src/inet_dns.erl

Lines changed: 153 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -26,8 +26,10 @@
2626
%% RFC 1996: A Mechanism for Prompt Notification of Zone Changes (DNS NOTIFY)
2727
%% RFC 2136: Dynamic Updates in the Domain Name System (DNS UPDATE)
2828
%% RFC 2181: Clarifications to the DNS Specification
29+
%% RFC 2535: Domain Name System Security Extensions
2930
%% RFC 2782: A DNS RR for specifying the location of services (DNS SRV)
3031
%% RFC 2915: The Naming Authority Pointer (NAPTR) DNS Resource Rec
32+
%% RFC 2931: DNS Request and Transaction Signatures ( SIG(0)s )
3133
%% RFC 5936: DNS Zone Transfer Protocol (AXFR)
3234
%% RFC 6488: DNS Certification Authority Authorization (CAA) Resource Record
3335
%% RFC 6762: Multicast DNS
@@ -37,12 +39,15 @@
3739

3840
-export([decode/1, encode/1]).
3941
-export([decode_algname/1, encode_algname/1]).
42+
-export([encode_dnssec_algname/1]).
4043

4144
-import(lists, [reverse/1]).
4245

4346
-include("inet_int.hrl").
4447
-include("inet_dns.hrl").
4548

49+
-include_lib("public_key/include/public_key.hrl").
50+
4651
-export([record_type/1, rr/1, rr/2]).
4752
-export([make_rr/0, make_rr/1, make_rr/2, make_rr/3]).
4853
%% ADTs exports. The make_* functions are undocumented.
@@ -255,6 +260,32 @@ decode_rr_section(Opcode, Bin, N, Buffer, RRs) ->
255260
z = Z,
256261
data = D,
257262
do = DnssecOk};
263+
?S_SIG ->
264+
{DR,Sig} = ?MATCH_ELSE_DECODE_ERROR(
265+
D,
266+
<<TypeCoveredEncoded:16, AlgEncoded:8, Labels:8,
267+
OriginalTTL:32, SigExp:32, SigInc:32,
268+
KeyTag:16, R/binary>>,
269+
{R,#dns_rr_sig{
270+
domain = Name,
271+
type = Type,
272+
offset = byte_size(Buffer) - byte_size(Bin),
273+
type_covered = decode_type(TypeCoveredEncoded),
274+
algorithm = decode_dnssec_algname(AlgEncoded),
275+
labels = Labels,
276+
original_ttl = OriginalTTL,
277+
signature_expiration = SigExp,
278+
signature_inception = SigInc,
279+
key_tag = KeyTag}}),
280+
%% RFC 2535: 4.3. SIG(0) must be last
281+
Sig#dns_rr_sig.type_covered == 0
282+
andalso Rest =/= <<>>
283+
andalso throw(?DECODE_ERROR),
284+
{SignatureEncoded,SignersName} = decode_name(DR, Buffer),
285+
Signature = decode_sig_signature(SignatureEncoded, Sig#dns_rr_sig.algorithm),
286+
Sig#dns_rr_sig{
287+
signers_name = SignersName,
288+
signature = Signature};
258289
?S_TSIG ->
259290
%% RFC 8945: 5.2. FORMERR if not last
260291
%% RFC 8945: 5.2. FORMERR if more than one dns_rr_tsig
@@ -372,6 +403,24 @@ encode_res_section(
372403
encode_res_section_rr(
373404
Opcode, Bin, Comp, Rs, DName, ?S_OPT, UdpPayloadSize, false,
374405
<<ExtRCode,Version,DO:1,Z:15>>, Data);
406+
encode_res_section(
407+
Opcode, Bin, Comp,
408+
[#dns_rr_sig{
409+
domain = DName,
410+
type_covered = TypeCovered,
411+
algorithm = Algorithm,
412+
labels = Labels,
413+
original_ttl = OriginalTTL,
414+
signature_expiration = SigExp,
415+
signature_inception = SigInc,
416+
key_tag = KeyTag,
417+
signers_name = SignersName,
418+
signature = Signature }]) ->
419+
Data = {TypeCovered,Algorithm,Labels,OriginalTTL,SigExp,SigInc,KeyTag,
420+
SignersName,Signature},
421+
encode_res_section_rr(
422+
Opcode, Bin, Comp, [], DName, ?S_SIG, ?S_ANY, false,
423+
<<0:32/signed>>, Data);
375424
encode_res_section(
376425
Opcode, Bin, Comp,
377426
[#dns_rr_tsig{
@@ -427,6 +476,8 @@ decode_type(Type) ->
427476
?T_MINFO -> ?S_MINFO;
428477
?T_MX -> ?S_MX;
429478
?T_TXT -> ?S_TXT;
479+
?T_SIG -> ?S_SIG;
480+
?T_KEY -> ?S_KEY;
430481
?T_AAAA -> ?S_AAAA;
431482
?T_LOC -> ?S_LOC;
432483
?T_SRV -> ?S_SRV;
@@ -470,6 +521,8 @@ encode_type(Type) ->
470521
?S_MINFO -> ?T_MINFO;
471522
?S_MX -> ?T_MX;
472523
?S_TXT -> ?T_TXT;
524+
?S_SIG -> ?T_SIG;
525+
?S_KEY -> ?T_KEY;
473526
?S_AAAA -> ?T_AAAA;
474527
?S_LOC -> ?T_LOC;
475528
?S_SRV -> ?T_SRV;
@@ -674,12 +727,22 @@ decode_data(Data, ?S_CAA, _) ->
674727
{Flags,inet_db:tolower(Tag),Value}
675728
end)
676729
end);
730+
decode_data(Data, ?S_KEY, _) ->
731+
?MATCH_ELSE_DECODE_ERROR(
732+
Data,
733+
<<Flags:16, ProtocolEncoded:8, AlgorithmEncoded:8,
734+
PublicKeyEncoded/binary>>,
735+
begin
736+
Protocol = decode_key_protocol(ProtocolEncoded),
737+
Algorithm = decode_dnssec_algname(AlgorithmEncoded),
738+
PublicKey = decode_key_publickey(PublicKeyEncoded, Algorithm),
739+
{Flags,Protocol,Algorithm,PublicKey}
740+
end);
677741
%%
678742
%% sofar unknown or non standard
679743
decode_data(Data, Type, _) when is_integer(Type) ->
680744
Data.
681745

682-
683746
%% Array of strings
684747
%%
685748
decode_txt(<<>>) -> [];
@@ -864,7 +927,7 @@ encode_data(Comp, _, ?S_SPF, Data) -> {encode_txt(Data),Comp};
864927
encode_data(Comp, _, ?S_URI, Data) ->
865928
{Prio,Weight,Target} = Data,
866929
{<<Prio:16,Weight:16,(iolist_to_binary(Target))/binary>>,Comp};
867-
encode_data(Comp, _, ?S_CAA, Data)->
930+
encode_data(Comp, _, ?S_CAA, Data) ->
868931
case Data of
869932
{Flags,Tag,Value} ->
870933
B0 = <<Flags:8>>,
@@ -874,7 +937,33 @@ encode_data(Comp, _, ?S_CAA, Data)->
874937
_ ->
875938
{encode_txt(Data),Comp}
876939
end;
877-
encode_data(Comp, _, ?S_TSIG, Data)->
940+
encode_data(Comp, _, ?S_KEY, Data) ->
941+
{Flags,Protocol,Algorithm,PublicKey} = Data,
942+
ProtocolEncoded = encode_key_protocol(Protocol),
943+
AlgorithmEncoded = encode_dnssec_algname(Algorithm),
944+
PublicKeyEncoded = encode_key_publickey(PublicKey, Algorithm),
945+
DataB = <<Flags:16, ProtocolEncoded:8, AlgorithmEncoded:8,
946+
PublicKeyEncoded/binary>>,
947+
{DataB,Comp};
948+
encode_data(Comp, Pos, ?S_SIG, Data) ->
949+
{TypeCovered,Algorithm,Labels,OriginalTTL,SigExp,SigInc,KeyTag,
950+
SignersName,Signature} = Data,
951+
TypeCoveredEncoded = encode_type(TypeCovered),
952+
AlgorithmEncoded = encode_dnssec_algname(Algorithm),
953+
%% Compression on the Wire allowed, just not during the
954+
%% SIG RDATA calculation (RFC2535, sections 4.1.7, 4.1.8 and 8.1)
955+
{SignersNameEncoded,Comp1} = encode_name(Comp, Pos, SignersName),
956+
SignatureEncoded = if
957+
Signature == <<>> ->
958+
<<>>;
959+
true ->
960+
encode_sig_signature(Signature, Algorithm)
961+
end,
962+
DataB = <<TypeCoveredEncoded:16, AlgorithmEncoded:8, Labels:8,
963+
OriginalTTL:32, SigExp:32, SigInc:32, KeyTag:16,
964+
SignersNameEncoded/binary, SignatureEncoded/binary>>,
965+
{DataB,Comp1};
966+
encode_data(Comp, _, ?S_TSIG, Data) ->
878967
{AlgName,Now,Fudge,MAC,OriginalId,Error,OtherData} = Data,
879968
%% Bypass name compression (RFC 8945, section 4.2)
880969
AlgNameEncoded = encode_algname(AlgName),
@@ -1026,6 +1115,67 @@ encode_loc_size(X)
10261115
Base = (X + Multiplier - 1) div Multiplier,
10271116
<<Base:4, Exponent:4>>.
10281117

1118+
%% https://www.iana.org/assignments/dns-key-rr/dns-key-rr.xhtml
1119+
decode_key_protocol(Protocol) ->
1120+
case Protocol of
1121+
?T_DNSKEY_PROTOCOL_DNSSEC -> ?S_DNSKEY_PROTOCOL_DNSSEC;
1122+
_ -> Protocol % raw unknown protocol
1123+
end.
1124+
1125+
encode_key_protocol(Protocol) ->
1126+
case Protocol of
1127+
?S_DNSKEY_PROTOCOL_DNSSEC -> ?T_DNSKEY_PROTOCOL_DNSSEC;
1128+
Protocol when is_integer(Protocol) -> Protocol % raw unknown protocol
1129+
end.
1130+
1131+
decode_dnssec_algname(AlgName) ->
1132+
case AlgName of
1133+
?T_DNSSEC_ALGNUM_RSAMD5 -> ?S_DNSSEC_ALGNUM_RSAMD5;
1134+
?T_DNSSEC_ALGNUM_ECDSAP256SHA256 -> ?S_DNSSEC_ALGNUM_ECDSAP256SHA256;
1135+
_ -> AlgName % raw unknown algname
1136+
end.
1137+
1138+
encode_dnssec_algname(Alg) ->
1139+
case Alg of
1140+
?S_DNSSEC_ALGNUM_RSAMD5 -> ?T_DNSSEC_ALGNUM_RSAMD5;
1141+
?S_DNSSEC_ALGNUM_ECDSAP256SHA256 -> ?T_DNSSEC_ALGNUM_ECDSAP256SHA256;
1142+
Alg when is_integer(Alg) -> Alg % raw unknown algname
1143+
end.
1144+
1145+
%% RFC6605, section 4
1146+
%% RFC5480, section 2.2
1147+
-define(ECPOINT_UNCOMPRESSED, 4).
1148+
decode_key_publickey(PublicKey, Algorithm) when is_atom(Algorithm) ->
1149+
decode_key_publickey(PublicKey, encode_dnssec_algname(Algorithm));
1150+
decode_key_publickey(_PublicKey = <<Q:64/binary>>, ?T_DNSSEC_ALGNUM_ECDSAP256SHA256) ->
1151+
{#'ECPoint'{ point = <<?ECPOINT_UNCOMPRESSED, Q/binary>> }, {namedCurve, secp256r1}};
1152+
decode_key_publickey(PublicKey, _Algorithm) when is_binary(PublicKey) ->
1153+
PublicKey.
1154+
1155+
encode_key_publickey(PublicKey, Algorithm) when is_atom(Algorithm) ->
1156+
encode_key_publickey(PublicKey, encode_dnssec_algname(Algorithm));
1157+
encode_key_publickey(#'ECPrivateKey'{ publicKey = PublicKey }, Algorithm) when Algorithm == ?T_DNSSEC_ALGNUM_ECDSAP256SHA256 ->
1158+
encode_key_publickey({#'ECPoint'{ point = PublicKey }, {namedCurve, secp256r1}}, Algorithm);
1159+
encode_key_publickey(_PublicKey = {#'ECPoint'{ point = <<?ECPOINT_UNCOMPRESSED, Q:64/binary>> }, {namedCurve, secp256r1}}, ?T_DNSSEC_ALGNUM_ECDSAP256SHA256) ->
1160+
Q;
1161+
encode_key_publickey(PublicKey, _Algorithm) when is_binary(PublicKey) ->
1162+
PublicKey.
1163+
1164+
decode_sig_signature(Signature, Algorithm) when is_atom(Algorithm) ->
1165+
decode_sig_signature(Signature, encode_dnssec_algname(Algorithm));
1166+
decode_sig_signature(_Signature = <<R:32/unit:8, S:32/unit:8>>, ?T_DNSSEC_ALGNUM_ECDSAP256SHA256) ->
1167+
public_key:der_encode('ECDSA-Sig-Value', #'ECDSA-Sig-Value'{ r = R, s = S });
1168+
decode_sig_signature(Signature, _Algorithm) when is_binary(Signature) ->
1169+
Signature.
1170+
1171+
encode_sig_signature(Signature, Algorithm) when is_atom(Algorithm) ->
1172+
encode_sig_signature(Signature, encode_dnssec_algname(Algorithm));
1173+
encode_sig_signature(Signature, ?T_DNSSEC_ALGNUM_ECDSAP256SHA256) ->
1174+
#'ECDSA-Sig-Value'{ r = R, s = S } = public_key:der_decode('ECDSA-Sig-Value', Signature),
1175+
<<R:32/unit:8, S:32/unit:8>>;
1176+
encode_sig_signature(Signature, _Algorithm) when is_binary(Signature) ->
1177+
Signature.
1178+
10291179
decode_algname(AlgName) ->
10301180
case AlgName of
10311181
?T_TSIG_HMAC_MD5 -> ?S_TSIG_HMAC_MD5;

lib/kernel/src/inet_dns.hrl

Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,8 @@
6969
-define(T_MINFO, 14). %% mailbox information
7070
-define(T_MX, 15). %% mail routing information
7171
-define(T_TXT, 16). %% text strings
72+
-define(T_SIG, 24). %% signature
73+
-define(T_KEY, 25). %% key
7274
-define(T_AAAA, 28). %% ipv6 address
7375
%% LOC (RFC 1876)
7476
-define(T_LOC, 29). %% location information
@@ -114,6 +116,8 @@
114116
-define(S_MINFO, minfo). %% mailbox information
115117
-define(S_MX, mx). %% mail routing information
116118
-define(S_TXT, txt). %% text strings
119+
-define(S_SIG, sig). %% signature
120+
-define(S_KEY, key). %% key
117121
-define(S_AAAA, aaaa). %% ipv6 address
118122
%% LOC (RFC 1876)
119123
-define(S_LOC, loc). %% location information
@@ -149,6 +153,24 @@
149153
-define(C_NONE, 254). %% for DDNS (RFC2136, section 2.4)
150154
-define(C_ANY, 255). %% wildcard match
151155

156+
%%
157+
%% DNS KEY Resource Record Protocol Octet Values
158+
%% https://www.iana.org/assignments/dns-key-rr/dns-key-rr.xhtml
159+
%%
160+
-define(T_DNSKEY_PROTOCOL_DNSSEC, 3).
161+
%
162+
-define(S_DNSKEY_PROTOCOL_DNSSEC, dnssec).
163+
164+
%%
165+
%% Domain Name System Security (DNSSEC) Algorithm Numbers
166+
%% https://www.iana.org/assignments/dns-sec-alg-numbers/dns-sec-alg-numbers.xhtml
167+
%%
168+
-define(T_DNSSEC_ALGNUM_RSAMD5, 1).
169+
-define(T_DNSSEC_ALGNUM_ECDSAP256SHA256, 13).
170+
%
171+
-define(S_DNSSEC_ALGNUM_RSAMD5, rsamd5).
172+
-define(S_DNSSEC_ALGNUM_ECDSAP256SHA256, ecdsap256sha256).
173+
152174
%%
153175
%% TSIG Algorithms and Identifiers (RFC8945, section 6)
154176
%%
@@ -239,6 +261,23 @@
239261
do = false %% RFC6891(6.1.3 DO)
240262
}).
241263

264+
-record(dns_rr_sig, %% SIG RR OPT (RFC2535), dns_rr{type=sig}
265+
{
266+
domain = "", %% should be the root domain
267+
type = sig,
268+
offset, %% position of RR in packet ( SIG(0) )
269+
%% RFC2535(4.1 SIG RDATA Format)
270+
type_covered,
271+
algorithm,
272+
labels,
273+
original_ttl,
274+
signature_expiration,
275+
signature_inception,
276+
key_tag,
277+
signers_name,
278+
signature
279+
}).
280+
242281
-record(dns_rr_tsig, %% TSIG RR OPT (RFC8945), dns_rr{type=tsig}
243282
{
244283
domain = "", %% name of the key

0 commit comments

Comments
 (0)