26
26
% % RFC 1996: A Mechanism for Prompt Notification of Zone Changes (DNS NOTIFY)
27
27
% % RFC 2136: Dynamic Updates in the Domain Name System (DNS UPDATE)
28
28
% % RFC 2181: Clarifications to the DNS Specification
29
+ % % RFC 2535: Domain Name System Security Extensions
29
30
% % RFC 2782: A DNS RR for specifying the location of services (DNS SRV)
30
31
% % RFC 2915: The Naming Authority Pointer (NAPTR) DNS Resource Rec
32
+ % % RFC 2931: DNS Request and Transaction Signatures ( SIG(0)s )
31
33
% % RFC 5936: DNS Zone Transfer Protocol (AXFR)
32
34
% % RFC 6488: DNS Certification Authority Authorization (CAA) Resource Record
33
35
% % RFC 6762: Multicast DNS
37
39
38
40
-export ([decode /1 , encode /1 ]).
39
41
-export ([decode_algname /1 , encode_algname /1 ]).
42
+ -export ([encode_dnssec_algname /1 ]).
40
43
41
44
-import (lists , [reverse /1 ]).
42
45
43
46
-include (" inet_int.hrl" ).
44
47
-include (" inet_dns.hrl" ).
45
48
49
+ -include_lib (" public_key/include/public_key.hrl" ).
50
+
46
51
-export ([record_type /1 , rr /1 , rr /2 ]).
47
52
-export ([make_rr /0 , make_rr /1 , make_rr /2 , make_rr /3 ]).
48
53
% % ADTs exports. The make_* functions are undocumented.
@@ -255,6 +260,32 @@ decode_rr_section(Opcode, Bin, N, Buffer, RRs) ->
255
260
z = Z ,
256
261
data = D ,
257
262
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 };
258
289
? S_TSIG ->
259
290
% % RFC 8945: 5.2. FORMERR if not last
260
291
% % RFC 8945: 5.2. FORMERR if more than one dns_rr_tsig
@@ -372,6 +403,24 @@ encode_res_section(
372
403
encode_res_section_rr (
373
404
Opcode , Bin , Comp , Rs , DName , ? S_OPT , UdpPayloadSize , false ,
374
405
<<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 );
375
424
encode_res_section (
376
425
Opcode , Bin , Comp ,
377
426
[# dns_rr_tsig {
@@ -427,6 +476,8 @@ decode_type(Type) ->
427
476
? T_MINFO -> ? S_MINFO ;
428
477
? T_MX -> ? S_MX ;
429
478
? T_TXT -> ? S_TXT ;
479
+ ? T_SIG -> ? S_SIG ;
480
+ ? T_KEY -> ? S_KEY ;
430
481
? T_AAAA -> ? S_AAAA ;
431
482
? T_LOC -> ? S_LOC ;
432
483
? T_SRV -> ? S_SRV ;
@@ -470,6 +521,8 @@ encode_type(Type) ->
470
521
? S_MINFO -> ? T_MINFO ;
471
522
? S_MX -> ? T_MX ;
472
523
? S_TXT -> ? T_TXT ;
524
+ ? S_SIG -> ? T_SIG ;
525
+ ? S_KEY -> ? T_KEY ;
473
526
? S_AAAA -> ? T_AAAA ;
474
527
? S_LOC -> ? T_LOC ;
475
528
? S_SRV -> ? T_SRV ;
@@ -674,12 +727,22 @@ decode_data(Data, ?S_CAA, _) ->
674
727
{Flags ,inet_db :tolower (Tag ),Value }
675
728
end )
676
729
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 );
677
741
% %
678
742
% % sofar unknown or non standard
679
743
decode_data (Data , Type , _ ) when is_integer (Type ) ->
680
744
Data .
681
745
682
-
683
746
% % Array of strings
684
747
% %
685
748
decode_txt (<<>>) -> [];
@@ -864,7 +927,7 @@ encode_data(Comp, _, ?S_SPF, Data) -> {encode_txt(Data),Comp};
864
927
encode_data (Comp , _ , ? S_URI , Data ) ->
865
928
{Prio ,Weight ,Target } = Data ,
866
929
{<<Prio :16 ,Weight :16 ,(iolist_to_binary (Target ))/binary >>,Comp };
867
- encode_data (Comp , _ , ? S_CAA , Data )->
930
+ encode_data (Comp , _ , ? S_CAA , Data ) ->
868
931
case Data of
869
932
{Flags ,Tag ,Value } ->
870
933
B0 = <<Flags :8 >>,
@@ -874,7 +937,33 @@ encode_data(Comp, _, ?S_CAA, Data)->
874
937
_ ->
875
938
{encode_txt (Data ),Comp }
876
939
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 ) ->
878
967
{AlgName ,Now ,Fudge ,MAC ,OriginalId ,Error ,OtherData } = Data ,
879
968
% % Bypass name compression (RFC 8945, section 4.2)
880
969
AlgNameEncoded = encode_algname (AlgName ),
@@ -1026,6 +1115,67 @@ encode_loc_size(X)
1026
1115
Base = (X + Multiplier - 1 ) div Multiplier ,
1027
1116
<<Base :4 , Exponent :4 >>.
1028
1117
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
+
1029
1179
decode_algname (AlgName ) ->
1030
1180
case AlgName of
1031
1181
? T_TSIG_HMAC_MD5 -> ? S_TSIG_HMAC_MD5 ;
0 commit comments