Skip to content

Commit

Permalink
inet_dns: basic support for TSIG requests
Browse files Browse the repository at this point in the history
An example of a TSIG signed DNS update is as shown:
----
Zone = "example.com".
Name = "cheese".
Request = inet_dns:make_msg([
        {header,inet_dns:make_header([
                {id,rand:uniform(65536) - 1},
                {opcode,update}
        ])},
        % RFC2136, section 2
        {qdlist,[       % Zone
                inet_dns:make_dns_query([
                        {domain,Zone},
                        {class,in},
                        {type,soa}
                ])
        ]},
        {nslist,[       % Update
                inet_dns:make_rr([
                        {domain,Name ++ "." ++ Zone},
                        {ttl,300},
                        {class,in},
                        {type,a},
                        {data,{192,0,2,1}}
                ])
        ]}
]).
TSigState0 = inet_dns_tsig:init([{keys,[{"mykey","moocowmoocow"}]}]).
{ok,RequestSigned,TSigState1} = inet_dns_tsig:sign(Request, TSigState0).
RequestPkt = inet_dns:encode(RequestSigned).
{ok,Sock} = gen_udp:open(0, [binary,{active,false}]).
gen_udp:send(Sock, {{127,0,0,1},5354}, RequestPkt).
{ok,{_,_,ResponsePkt}} = gen_udp:recv(Sock, 0).
{ok,ResponseSigned} = inet_dns:decode(ResponsePkt).
{ok,TSigState2} = inet_dns_tsig:verify(ResponseSigned, TSigState1).
Response = inet_dns:msg(ResponseSigned).
----
  • Loading branch information
jimdigriz committed Mar 6, 2023
1 parent d8b1aa4 commit b153cbf
Show file tree
Hide file tree
Showing 4 changed files with 285 additions and 17 deletions.
2 changes: 2 additions & 0 deletions lib/kernel/src/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -100,6 +100,7 @@ MODULES = \
inet_config \
inet_db \
inet_dns \
inet_dns_tsig \
inet_gethost_native \
inet_hosts \
inet_parse \
Expand Down Expand Up @@ -266,6 +267,7 @@ $(EBIN)/inet6_sctp.beam: inet_int.hrl
$(EBIN)/inet_config.beam: inet_config.hrl ../include/inet.hrl
$(EBIN)/inet_db.beam: ../include/inet.hrl inet_int.hrl inet_res.hrl inet_dns.hrl inet_config.hrl
$(EBIN)/inet_dns.beam: inet_int.hrl inet_dns.hrl inet_dns_record_adts.hrl
$(EBIN)/inet_dns_tsig.beam: inet_dns.hrl
$(EBIN)/inet_gethost_native.beam: ../include/inet.hrl
$(EBIN)/inet_hosts.beam: ../include/inet.hrl
$(EBIN)/inet_parse.beam: ../include/file.hrl
Expand Down
86 changes: 71 additions & 15 deletions lib/kernel/src/inet_dns.erl
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,11 @@
%% RFC 6488: DNS Certification Authority Authorization (CAA) Resource Record
%% RFC 6762: Multicast DNS
%% RFC 7553: The Uniform Resource Identifier (URI) DNS Resource Record
%% RFC 8945: Secret Key Transaction Authentication for DNS (TSIG)

-export([decode/1, encode/1]).
-export([decode_tsig_algname/1, encode_tsig_algname/1]). % used only by inet_dns_tsig.erl
-export([decode_name/2, encode_name/3]). % used only by inet_dns_tsig.erl

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

Expand Down Expand Up @@ -118,6 +121,8 @@ lists_member(H, [_|T]) -> lists_member(H, T).
%% must match a clause in inet_res:query_nss_e?dns
-define(DECODE_ERROR, formerr).

-define(GREGORIAN_OFFSET, 62167219200). % calendar:datetime_to_gregorian_seconds({{1970,1,1},{0,0,0}}).

%%
%% Decode a dns buffer.
%%
Expand Down Expand Up @@ -385,6 +390,7 @@ decode_type(Type) ->
?T_GID -> ?S_GID;
?T_UNSPEC -> ?S_UNSPEC;
%% Query type values which do not appear in resource records
?T_TSIG -> ?S_TSIG;
?T_IXFR -> ?S_IXFR;
?T_AXFR -> ?S_AXFR;
?T_MAILB -> ?S_MAILB;
Expand Down Expand Up @@ -427,6 +433,7 @@ encode_type(Type) ->
?S_GID -> ?T_GID;
?S_UNSPEC -> ?T_UNSPEC;
%% Query type values which do not appear in resource records
?S_TSIG -> ?T_TSIG;
?S_IXFR -> ?T_IXFR;
?S_AXFR -> ?T_AXFR;
?S_MAILB -> ?T_MAILB;
Expand Down Expand Up @@ -494,7 +501,43 @@ encode_opcode(Opcode) ->
update -> ?UPDATE;
_ when is_integer(Opcode) -> Opcode %% non-standard opcode
end.



%%
%% TSIG Algorithms and Identifiers (RFC8945, section 6)
%%
decode_tsig_algname(Type) ->
case Type of
?T_TSIG_HMAC_MD5 -> ?S_TSIG_HMAC_MD5;
?T_TSIG_GSS_TSIG -> ?S_TSIG_GSS_TSIG;
?T_TSIG_HMAC_SHA1 -> ?S_TSIG_HMAC_SHA1;
?T_TSIG_HMAC_SHA1_96 -> ?S_TSIG_HMAC_SHA1_96;
?T_TSIG_HMAC_SHA224 -> ?S_TSIG_HMAC_SHA224;
?T_TSIG_HMAC_SHA256 -> ?S_TSIG_HMAC_SHA256;
?T_TSIG_HMAC_SHA256_128 -> ?S_TSIG_HMAC_SHA256_128;
?T_TSIG_HMAC_SHA384 -> ?S_TSIG_HMAC_SHA384;
?T_TSIG_HMAC_SHA384_192 -> ?S_TSIG_HMAC_SHA384_192;
?T_TSIG_HMAC_SHA512 -> ?S_TSIG_HMAC_SHA512;
?T_TSIG_HMAC_SHA512_256 -> ?S_TSIG_HMAC_SHA512_256;
_ -> Type %% raw unknown type
end.

encode_tsig_algname(Type) ->
case Type of
?S_TSIG_HMAC_MD5 -> ?T_TSIG_HMAC_MD5;
?S_TSIG_GSS_TSIG -> ?T_TSIG_GSS_TSIG;
?S_TSIG_HMAC_SHA1 -> ?T_TSIG_HMAC_SHA1;
?S_TSIG_HMAC_SHA1_96 -> ?T_TSIG_HMAC_SHA1_96;
?S_TSIG_HMAC_SHA224 -> ?T_TSIG_HMAC_SHA224;
?S_TSIG_HMAC_SHA256 -> ?T_TSIG_HMAC_SHA256;
?S_TSIG_HMAC_SHA256_128 -> ?T_TSIG_HMAC_SHA256_128;
?S_TSIG_HMAC_SHA384 -> ?T_TSIG_HMAC_SHA384;
?S_TSIG_HMAC_SHA384_192 -> ?T_TSIG_HMAC_SHA384_192;
?S_TSIG_HMAC_SHA512 -> ?T_TSIG_HMAC_SHA512;
?S_TSIG_HMAC_SHA512_256 -> ?T_TSIG_HMAC_SHA512_256;
Type when is_list(Type) -> Type %% raw unknown type
end.


encode_boolean(true) -> 1;
encode_boolean(false) -> 0;
Expand All @@ -507,20 +550,6 @@ decode_boolean(I) when is_integer(I) -> true.
%%
%% Data field -> term() content representation
%%
%% Class IN RRs
decode_data(Data, in, ?S_A, _) ->
?MATCH_ELSE_DECODE_ERROR(Data, <<A,B,C,D>>, {A,B,C,D});
decode_data(Data, in, ?S_AAAA, _) ->
?MATCH_ELSE_DECODE_ERROR(
Data,
<<A:16,B:16,C:16,D:16,E:16,F:16,G:16,H:16>>,
{A,B,C,D,E,F,G,H});
decode_data(Data, in, ?S_WKS, _) ->
?MATCH_ELSE_DECODE_ERROR(
Data,
<<A,B,C,D,Proto,BitMap/binary>>,
{{A,B,C,D},Proto,BitMap});
%%
decode_data(Data, Class, Type, Buffer) ->
if
is_integer(Class) -> % Raw class
Expand All @@ -531,6 +560,19 @@ decode_data(Data, Class, Type, Buffer) ->
%%
%%
%% Standard RRs (any class)
%%
decode_data(Data, ?S_A, _) ->
?MATCH_ELSE_DECODE_ERROR(Data, <<A,B,C,D>>, {A,B,C,D});
decode_data(Data, ?S_AAAA, _) ->
?MATCH_ELSE_DECODE_ERROR(
Data,
<<A:16,B:16,C:16,D:16,E:16,F:16,G:16,H:16>>,
{A,B,C,D,E,F,G,H});
decode_data(Data, ?S_WKS, _) ->
?MATCH_ELSE_DECODE_ERROR(
Data,
<<A,B,C,D,Proto,BitMap/binary>>,
{{A,B,C,D},Proto,BitMap});
decode_data(Data, ?S_SOA, Buffer) ->
{Data1,MName} = decode_name(Data, Buffer),
{Data2,RName} = decode_name(Data1, Buffer),
Expand Down Expand Up @@ -604,6 +646,13 @@ decode_data(Data, ?S_CAA, _) ->
{Flags,inet_db:tolower(Tag),Value}
end)
end);
decode_data(Data0, ?S_TSIG, Buffer) ->
{Data,AlgName0} = decode_name(Data0, Buffer),
AlgName = decode_tsig_algname(AlgName0),
?MATCH_ELSE_DECODE_ERROR(
Data,
<<NowTS:48, Fudge:16, MACSize:16, MAC:MACSize/binary, OriginalId:16, Error:16, OtherLen:16, OtherData:OtherLen/binary>>,
{AlgName,calendar:system_time_to_universal_time(NowTS, seconds),Fudge,MAC,OriginalId,Error,OtherData});
%%
%% sofar unknown or non standard
decode_data(Data, Type, _) when is_integer(Type) ->
Expand Down Expand Up @@ -785,6 +834,13 @@ encode_data(Comp, _, ?S_CAA, Data)->
_ ->
{encode_txt(Data),Comp}
end;
encode_data(Comp, _, ?S_TSIG, Data) ->
{AlgName0,Now,Fudge,MAC,OriginalId,Error,OtherData} = Data,
{AlgName, _} = encode_name(gb_trees:empty(), 0, encode_tsig_algname(AlgName0)), % RFC8945, section 4.2 - MUST NOT be compressed
NowST = calendar:datetime_to_gregorian_seconds(Now) - ?GREGORIAN_OFFSET,
MACSize = byte_size(MAC),
OtherLen = byte_size(OtherData),
{<<AlgName/binary, NowST:48, Fudge:16, MACSize:16, MAC:MACSize/binary, OriginalId:16, Error:16, OtherLen:16, OtherData:OtherLen/binary>>,Comp};
%%
%% sofar unknown or non standard
encode_data(Comp, _Pos, Type, Data) when is_integer(Type) ->
Expand Down
38 changes: 36 additions & 2 deletions lib/kernel/src/inet_dns.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,11 @@
-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).
-define(BADVERS, 16). %% Bad OPT Version
-define(BADSIG, 16). %% TSIG Signature Failure
-define(BADKEY, 17). %% Key not recognized
-define(BADTIME, 18). %% Signature out of time window
-define(BADTRUNC, 22). %% Bad Truncation

%%
%% Type values for resources and queries
Expand Down Expand Up @@ -79,6 +83,7 @@
-define(T_UID, 101). %% user ID
-define(T_GID, 102). %% group ID
-define(T_UNSPEC, 103). %% Unspecified format (binary data)
-define(T_TSIG, 250). %% transaction signature
%% 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
Expand Down Expand Up @@ -122,6 +127,7 @@
-define(S_UID, uid). %% user ID
-define(S_GID, gid). %% group ID
-define(S_UNSPEC, unspec). %% Unspecified format (binary data)
-define(S_TSIG, tsig). %% transaction signature
%% 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
Expand All @@ -144,6 +150,34 @@
%% Query class values which do not appear in resource records
-define(C_ANY, 255). %% wildcard match (appears in UPDATE though)

%%
%% TSIG Algorithms and Identifiers (RFC8945, section 6)
%%

-define(T_TSIG_HMAC_MD5, "HMAC-MD5.SIG-ALG.REG.INT").
-define(T_TSIG_GSS_TSIG, "gss-tsig").
-define(T_TSIG_HMAC_SHA1, "hmac-sha1").
-define(T_TSIG_HMAC_SHA1_96, "hmac-sha1_96").
-define(T_TSIG_HMAC_SHA224, "hmac-sha224").
-define(T_TSIG_HMAC_SHA256, "hmac-sha256").
-define(T_TSIG_HMAC_SHA256_128, "hmac-sha256-128").
-define(T_TSIG_HMAC_SHA384, "hmac-sha384").
-define(T_TSIG_HMAC_SHA384_192, "hmac-sha384-192").
-define(T_TSIG_HMAC_SHA512, "hmac-sha512").
-define(T_TSIG_HMAC_SHA512_256, "hmac-sha512-256").

-define(S_TSIG_HMAC_MD5, md5).
-define(S_TSIG_GSS_TSIG, gss_tsig).
-define(S_TSIG_HMAC_SHA1, sha).
-define(S_TSIG_HMAC_SHA1_96, sha_96).
-define(S_TSIG_HMAC_SHA224, sha224).
-define(S_TSIG_HMAC_SHA256, sha256).
-define(S_TSIG_HMAC_SHA256_128, sha256_128).
-define(S_TSIG_HMAC_SHA384, sha384).
-define(S_TSIG_HMAC_SHA384_192, sha384_192).
-define(S_TSIG_HMAC_SHA512, hmac_sha512).
-define(S_TSIG_HMAC_SHA512_256, sha512_256).


%% indirection mask for compressed domain names
-define(INDIR_MASK, 16#c0).
Expand Down Expand Up @@ -184,7 +218,7 @@
{
domain = "", %% resource domain
type = any, %% resource type
class = in, %% reource class
class = in, %% resource class
cnt = 0, %% access count
ttl = 0, %% time to live
data = [], %% raw data
Expand Down
Loading

0 comments on commit b153cbf

Please sign in to comment.