File 2142-Restructure-decoding-to-avoid-multiple-clauses-per-R.patch of Package erlang

From 5cfcec8f8776f1ad43b6aea6bea781656efe76dd Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Thu, 26 Aug 2021 20:34:11 +0200
Subject: [PATCH 2/2] Restructure decoding to avoid multiple clauses per RR
 type

* Use one clause per RR type when decoding.  I.e do not
  use a separate error clause where a bunch of RR types
  needs to be repeated, and then can be missed in
  a future rewrite.
* Introduce a macro ?MATCH_ELSE_DECODE_ERROR to throw(?DECODE_ERROR)
  for no match, to avoid cluttering the decode code with such throw:s.
  Use that macro consistently.
* Group RRs into class IN vs. standard (class agnostic),
  for both decoding and encoding.
* Remove erroneous ?S_URI clauses that remained after fixing
  encode/decode in 355eeac9.
* Remove incorrect matching for class 'in' when encoding
  standard (class agnostic) RRs.
* Introduce explicit clauses for ?S_OPT instead of falling
  through to the default clause.
---
 lib/kernel/src/inet_dns.erl | 437 +++++++++++++++++++-----------------
 1 file changed, 236 insertions(+), 201 deletions(-)

diff --git a/lib/kernel/src/inet_dns.erl b/lib/kernel/src/inet_dns.erl
index 8f63dfdf11..efe9ee132d 100644
--- a/lib/kernel/src/inet_dns.erl
+++ b/lib/kernel/src/inet_dns.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1997-2020. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2021. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -118,6 +118,24 @@ lists_member(H, [_|T]) -> lists_member(H, T).
 %% Decode a dns buffer.
 %%
 
+%% Match macros that throw(?DECODE_ERROR) for no match
+-define(
+   MATCH_ELSE_DECODE_ERROR(Match, Pattern, Result),
+   case begin Match end of
+       (Pattern) ->
+           begin Result end;
+       _ ->
+           throw(?DECODE_ERROR)
+   end).
+-define(
+   MATCH_ELSE_DECODE_ERROR(Match, Pattern, Guard, Result),
+   case begin Match end of
+       (Pattern) when not not (Guard) ->
+           begin Result end;
+       _ ->
+           throw(?DECODE_ERROR)
+   end).
+
 decode(Buffer) when is_binary(Buffer) ->
     try do_decode(Buffer) of
 	DnsRec ->
@@ -136,33 +154,37 @@ do_decode(<<Id:16,
     {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),
-	case Rest of
-	    <<>> ->
-		HdrTC = decode_boolean(TC),
-		DnsHdr =
-		    #dns_header{id=Id,
-				qr=decode_boolean(QR),
-				opcode=decode_opcode(Opcode),
-				aa=decode_boolean(AA),
-				tc=HdrTC,
-				rd=decode_boolean(RD),
-				ra=decode_boolean(RA),
-				pr=decode_boolean(PR),
-				rcode=Rcode},
-		case QdTC or AnTC or NsTC or ArTC of
-		    true when not HdrTC ->
-			throw(?DECODE_ERROR);
-		    _ ->
-			#dns_rec{header=DnsHdr,
-				 qdlist=QdList,
-				 anlist=AnList,
-				 nslist=NsList,
-				 arlist=ArList}
-		end;
-	    _ ->
-		%% Garbage data after DNS message
-		throw(?DECODE_ERROR)
-	end;
+    ?MATCH_ELSE_DECODE_ERROR(
+       Rest,
+       <<>>,
+       begin
+           HdrTC = decode_boolean(TC),
+           DnsHdr =
+               #dns_header{id=Id,
+                           qr=decode_boolean(QR),
+                           opcode=decode_opcode(Opcode),
+                           aa=decode_boolean(AA),
+                           tc=HdrTC,
+                           rd=decode_boolean(RD),
+                           ra=decode_boolean(RA),
+                           pr=decode_boolean(PR),
+                           rcode=Rcode},
+           ?MATCH_ELSE_DECODE_ERROR(
+              %% Header marked as truncated, or no section
+              %% marked as truncated.
+              %% The converse; a section marked as truncated,
+              %% but not the header - is a parse error.
+              %%
+              HdrTC or (not (QdTC or AnTC or NsTC or ArTC)),
+              true,
+              begin
+                  #dns_rec{header=DnsHdr,
+                           qdlist=QdList,
+                           anlist=AnList,
+                           nslist=NsList,
+                           arlist=ArList}
+              end)
+       end);
 do_decode(_) ->
     %% DNS message does not even match header
     throw(?DECODE_ERROR).
@@ -175,17 +197,16 @@ decode_query_section(<<>>=Rest, N, _Buffer, Qs) ->
 decode_query_section(Rest, 0, _Buffer, Qs) ->
     {Rest,reverse(Qs),false};
 decode_query_section(Bin, N, Buffer, Qs) ->
-    case decode_name(Bin, Buffer) of
-	{<<Type:16,Class:16,Rest/binary>>,Name} ->
+    ?MATCH_ELSE_DECODE_ERROR(
+       decode_name(Bin, Buffer),
+       {<<Type:16,Class:16,Rest/binary>>,Name},
+       begin
 	    DnsQuery =
 		#dns_query{domain=Name,
 			   type=decode_type(Type),
 			   class=decode_class(Class)},
-	    decode_query_section(Rest, N-1, Buffer, [DnsQuery|Qs]);
-	_ ->
-	    %% Broken question
-	    throw(?DECODE_ERROR)
-    end.
+	    decode_query_section(Rest, N-1, Buffer, [DnsQuery|Qs])
+       end).
 
 decode_rr_section(Bin, N, Buffer) ->
     decode_rr_section(Bin, N, Buffer, []).
@@ -195,38 +216,37 @@ decode_rr_section(<<>>=Rest, N, _Buffer, RRs) ->
 decode_rr_section(Rest, 0, _Buffer, RRs) ->
     {Rest,reverse(RRs),false};
 decode_rr_section(Bin, N, Buffer, RRs) ->
-    case decode_name(Bin, Buffer) of
-	{<<T:16/unsigned,C:16/unsigned,TTL:4/binary,
+    ?MATCH_ELSE_DECODE_ERROR(
+       decode_name(Bin, Buffer),
+       {<<T:16/unsigned,C:16/unsigned,TTL:4/binary,
 	  Len:16,D:Len/binary,Rest/binary>>,
-	 Name} ->
-	    Type = decode_type(T),
-	    Class = decode_class(C),
-	    Data = decode_data(D, Class, Type, Buffer),
-	    RR =
-		case Type of
-		    opt ->
-			<<ExtRcode,Version,Z:16>> = TTL,
-			#dns_rr_opt{domain=Name,
-				    type=Type,
-				    udp_payload_size=C,
-				    ext_rcode=ExtRcode,
-				    version=Version,
-				    z=Z,
-				    data=Data};
-		    _ ->
-			<<TimeToLive:32/signed>> = TTL,
-			#dns_rr{domain=Name,
-				type=Type,
-				class=Class,
-				ttl=if TimeToLive < 0 -> 0;
-				       true -> TimeToLive end,
-				data=Data}
-		end,
-	    decode_rr_section(Rest, N-1, Buffer, [RR|RRs]);
-	_ ->
-	    %% Broken RR
-	    throw(?DECODE_ERROR)
-    end.
+        Name},
+       begin
+           Type = decode_type(T),
+           Class = decode_class(C),
+           Data = decode_data(D, Class, Type, Buffer),
+           RR =
+               case Type of
+                   opt ->
+                       <<ExtRcode,Version,Z:16>> = TTL,
+                       #dns_rr_opt{domain=Name,
+                                   type=Type,
+                                   udp_payload_size=C,
+                                   ext_rcode=ExtRcode,
+                                   version=Version,
+                                   z=Z,
+                                   data=Data};
+                   _ ->
+                       <<TimeToLive:32/signed>> = TTL,
+                       #dns_rr{domain=Name,
+                               type=Type,
+                               class=Class,
+                               ttl=if TimeToLive < 0 -> 0;
+                                      true -> TimeToLive end,
+                               data=Data}
+               end,
+           decode_rr_section(Rest, N-1, Buffer, [RR|RRs])
+       end).
 
 %%
 %% Encode a user query
@@ -430,83 +450,100 @@ encode_boolean(B) when is_integer(B) -> B.
 decode_boolean(0) -> false;
 decode_boolean(I) when is_integer(I) -> true.
 
+
 %%
 %% Data field -> term() content representation
 %%
-decode_data(<<A,B,C,D>>, in, ?S_A,  _)   -> {A,B,C,D};
-decode_data(<<A:16,B:16,C:16,D:16,E:16,F:16,G:16,H:16>>, in, ?S_AAAA, _) ->
-    {A,B,C,D,E,F,G,H};
-decode_data(Dom, _, ?S_NS, Buffer)    -> decode_domain(Dom, Buffer);
-decode_data(Dom, _, ?S_MD, Buffer)    -> decode_domain(Dom, Buffer); 
-decode_data(Dom, _, ?S_MF, Buffer)    -> decode_domain(Dom, Buffer); 
-decode_data(Dom, _, ?S_CNAME, Buffer) -> decode_domain(Dom, Buffer);
-decode_data(Data0, _, ?S_SOA, Buffer) ->
-    {Data1,MName} = decode_name(Data0, Buffer),
-    {Data,RName} = decode_name(Data1, Buffer),
-    case Data of
-	<<Serial:32,Refresh:32/signed,Retry:32/signed,
-	 Expiry:32/signed,Minimum:32>> ->
-	    {MName,RName,Serial,Refresh,Retry,Expiry,Minimum};
-	_ ->
-	    %% Broken SOA RR data
-	    throw(?DECODE_ERROR)
-    end;
-decode_data(Dom, _, ?S_MB, Buffer)    -> decode_domain(Dom, Buffer); 
-decode_data(Dom, _, ?S_MG, Buffer)    -> decode_domain(Dom, Buffer); 
-decode_data(Dom, _, ?S_MR, Buffer)    -> decode_domain(Dom, Buffer); 
-decode_data(Data, _, ?S_NULL, _) -> Data;
-decode_data(<<A,B,C,D,Proto,BitMap/binary>>, in, ?S_WKS, _Buffer) -> 
-    {{A,B,C,D},Proto,BitMap};
-decode_data(Dom, _, ?S_PTR, Buffer)   -> decode_domain(Dom, Buffer);
-decode_data(<<CpuLen,CPU:CpuLen/binary,
-	     OsLen,OS:OsLen/binary>>, _, ?S_HINFO, _) ->
-    {binary_to_list(CPU),binary_to_list(OS)};
-decode_data(Data0, _, ?S_MINFO, Buffer) ->
-    {Data1,RM} = decode_name(Data0, Buffer),
-    {Data,EM} = decode_name(Data1, Buffer),
-    case Data of
-	<<>> -> {RM,EM};
-	_ ->
-	    %% Broken MINFO data
-	    throw(?DECODE_ERROR)
-    end;
-decode_data(<<Prio:16,Dom/binary>>, _, ?S_MX, Buffer) ->
-    {Prio,decode_domain(Dom, Buffer)};
-decode_data(<<Prio:16,Weight:16,Port:16,Dom/binary>>, _, ?S_SRV, Buffer) ->
-    {Prio,Weight,Port,decode_domain(Dom, Buffer)};
-decode_data(<<Order:16,Preference:16,Data0/binary>>, _, ?S_NAPTR, Buffer) ->
-    {Data1,Flags} = decode_string(Data0),
-    {Data2,Services} = decode_string(Data1),
-    {Data,Regexp} = decode_characters(Data2, utf8),
-    Replacement = decode_domain(Data, Buffer),
-    {Order,Preference,inet_db:tolower(Flags),inet_db:tolower(Services),
-     Regexp,Replacement};
-%% ?S_OPT falls through to default
-decode_data(Data, _, ?S_TXT, _) ->
-    decode_txt(Data);
-decode_data(Data, _, ?S_SPF, _) ->
-    decode_txt(Data);
-decode_data(<<Prio:16,Weight:16,Data0/binary>>, _, ?S_URI, _) ->
-    (1 =< byte_size(Data0))
-        orelse throw(?DECODE_ERROR),
-    Target = binary_to_list(Data0),
-    {Prio,Weight,Target};
+%% 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});
+%%
+%% Standard RRs (any class)
+decode_data(Data, _, ?S_SOA, Buffer) ->
+    {Data1,MName} = decode_name(Data, Buffer),
+    {Data2,RName} = decode_name(Data1, Buffer),
+    ?MATCH_ELSE_DECODE_ERROR(
+       Data2,
+       <<Serial:32,Refresh:32/signed,Retry:32/signed,
+         Expiry:32/signed,Minimum:32>>,
+       {MName,RName,Serial,Refresh,Retry,Expiry,Minimum});
+decode_data(Data,  _, ?S_NS,    Buffer) -> decode_domain(Data, Buffer);
+decode_data(Data,  _, ?S_MD,    Buffer) -> decode_domain(Data, Buffer);
+decode_data(Data,  _, ?S_MF,    Buffer) -> decode_domain(Data, Buffer);
+decode_data(Data,  _, ?S_CNAME, Buffer) -> decode_domain(Data, Buffer);
+decode_data(Data,  _, ?S_MB,    Buffer) -> decode_domain(Data, Buffer);
+decode_data(Data,  _, ?S_MG,    Buffer) -> decode_domain(Data, Buffer);
+decode_data(Data,  _, ?S_MR,    Buffer) -> decode_domain(Data, Buffer);
+decode_data(Data,  _, ?S_PTR,   Buffer) -> decode_domain(Data, Buffer);
+decode_data(Data,  _, ?S_NULL,  _)      -> Data;
+decode_data(Data, _, ?S_HINFO, _) ->
+    ?MATCH_ELSE_DECODE_ERROR(
+       Data,
+       <<CpuLen,CPU:CpuLen/binary,OsLen,OS:OsLen/binary>>,
+       {binary_to_list(CPU),binary_to_list(OS)});
+decode_data(Data, _, ?S_MINFO, Buffer) ->
+    {Data1,RM} = decode_name(Data, Buffer),
+    {Data2,EM} = decode_name(Data1, Buffer),
+    ?MATCH_ELSE_DECODE_ERROR(Data2, <<>>, {RM,EM});
+decode_data(Data, _, ?S_MX, Buffer) ->
+    ?MATCH_ELSE_DECODE_ERROR(
+       Data,
+       <<Prio:16,Dom/binary>>,
+       {Prio,decode_domain(Dom, Buffer)});
+decode_data(Data, _, ?S_SRV, Buffer) ->
+    ?MATCH_ELSE_DECODE_ERROR(
+       Data,
+       <<Prio:16,Weight:16,Port:16,Dom/binary>>,
+       {Prio,Weight,Port,decode_domain(Dom, Buffer)});
+decode_data(Data, _, ?S_NAPTR, Buffer) ->
+    ?MATCH_ELSE_DECODE_ERROR(
+       Data,
+       <<Order:16,Preference:16,Data1/binary>>,
+       begin
+           {Data2,Flags} = decode_string(Data1),
+           {Data3,Services} = decode_string(Data2),
+           {Data4,Regexp} = decode_characters(Data3, utf8),
+           Replacement = decode_domain(Data4, Buffer),
+           {Order,Preference,
+            inet_db:tolower(Flags),inet_db:tolower(Services),
+            Regexp,Replacement}
+       end);
+decode_data(Data, _, ?S_OPT, _) -> Data;
+decode_data(Data, _, ?S_TXT, _) -> decode_txt(Data);
+decode_data(Data, _, ?S_SPF, _) -> decode_txt(Data);
 decode_data(Data, _, ?S_URI, _) ->
-    decode_txt(Data);
-decode_data(<<Flags:8,Data0/binary>>, _, ?S_CAA, _) ->
-    {Data1,Tag} = decode_string(Data0),
-    L = length(Tag),
-    (1 =< L andalso L =< 15)
-        orelse throw(?DECODE_ERROR),
-    Value = binary_to_list(Data1),
-    {Flags,inet_db:tolower(Tag),Value};
-%% malformed known RR in inet domain
-decode_data(_, in, T, _) when T == ?S_A; T == ?S_AAAA; T == ?S_WKS ->
-    throw(?DECODE_ERROR);
-%% malormed known RR in any domain
-decode_data(_, _, T, _) when T == ?S_HINFO; T == ?S_MX; T == ?S_SRV;
-    T == ?S_NAPTR; T == ?S_URI; T == ?S_CAA ->
-    throw(?DECODE_ERROR);
+    ?MATCH_ELSE_DECODE_ERROR(
+       Data,
+       <<Prio:16,Weight:16,Data1/binary>>, 1 =< byte_size(Data1),
+       begin
+           Target = binary_to_list(Data1),
+           {Prio,Weight,Target}
+       end);
+decode_data(Data, _, ?S_CAA, _) ->
+    ?MATCH_ELSE_DECODE_ERROR(
+       Data,
+       <<Flags:8,Data1/binary>>,
+       begin
+           {Data2,Tag} = decode_string(Data1),
+           ?MATCH_ELSE_DECODE_ERROR(
+              length(Tag),
+              L, 1 =< L andalso L =< 15,
+              begin
+                  Value = binary_to_list(Data2),
+                  {Flags,inet_db:tolower(Tag),Value}
+              end)
+       end);
+%%
 %% sofar unknown or non standard
 decode_data(Data, _, _, _) ->
     Data.
@@ -518,27 +555,22 @@ decode_txt(Bin) ->
     {Rest,String} = decode_string(Bin),
     [String|decode_txt(Rest)].
 
-decode_string(<<Len,Bin:Len/binary,Rest/binary>>) ->
-    {Rest,binary_to_list(Bin)};
-decode_string(_) ->
-    %% Broken string
-    throw(?DECODE_ERROR).
+decode_string(Data) ->
+    ?MATCH_ELSE_DECODE_ERROR(
+       Data,
+       <<Len,Bin:Len/binary,Rest/binary>>,
+       {Rest,binary_to_list(Bin)}).
 
-decode_characters(<<Len,Bin:Len/binary,Rest/binary>>, Encoding) ->
-    {Rest,unicode:characters_to_list(Bin, Encoding)};
-decode_characters(_, _) ->
-    %% Broken encoded string
-    throw(?DECODE_ERROR).
+decode_characters(Data, Encoding) ->
+    ?MATCH_ELSE_DECODE_ERROR(
+       Data,
+       <<Len,Bin:Len/binary,Rest/binary>>,
+       {Rest,unicode:characters_to_list(Bin, Encoding)}).
 
 %% One domain name only, there must be nothing after
 %%
 decode_domain(Bin, Buffer) ->
-    case decode_name(Bin, Buffer) of
-	{<<>>,Name} -> Name;
-	_ ->
-	    %% Garbage after domain name
-	    throw(?DECODE_ERROR)
-    end.
+    ?MATCH_ELSE_DECODE_ERROR(decode_name(Bin, Buffer), {<<>>,Name}, Name).
 
 %% Domain name -> {RestBin,Name}
 %%
@@ -561,15 +593,13 @@ decode_name(<<0:2,Len:6,Label:Len/binary,Rest/binary>>,
 		Cnt);
 decode_name(<<3:2,Ptr:14,Rest/binary>>, Buffer, Labels, Tail, Cnt) ->
     %% Indirection - reposition in buffer and recurse
-    case Buffer of
-	<<_:Ptr/binary,Bin/binary>> ->
-	    decode_name(Bin, Buffer, Labels,
-			if Cnt =/= 0 -> Tail; true -> Rest end,
-			Cnt+2); % size of indirection pointer
-	_ ->
-	    %% Indirection pointer outside buffer
-	    throw(?DECODE_ERROR)
-    end;
+    ?MATCH_ELSE_DECODE_ERROR(
+       Buffer,
+       <<_:Ptr/binary,Bin/binary>>,
+       decode_name(
+         Bin, Buffer, Labels,
+         if Cnt =/= 0 -> Tail; true -> Rest end,
+         Cnt+2)); % size of indirection pointer
 decode_name(_, _, _, _, _) -> throw(?DECODE_ERROR).
 
 %% Reverse list of labels (binaries) -> domain name (string)
@@ -582,12 +612,13 @@ decode_name_labels([Label], Name) ->
 decode_name_labels([Label|Labels], Name) ->
     decode_name_labels(Labels, "."++decode_name_label(Label, Name)).
 
-decode_name_label(<<>>, _Name) ->
-    %% Empty label is only allowed for the root domain, 
-    %% and that is handled above.
-    throw(?DECODE_ERROR);
 decode_name_label(Label, Name) ->
-    decode_name_label(Label, Name, byte_size(Label)).
+    ?MATCH_ELSE_DECODE_ERROR(
+       Label,
+       _, 1 =< byte_size(Label),
+       %% Empty label is only allowed for the root domain,
+       %% and that is handled above.
+       decode_name_label(Label, Name, byte_size(Label))).
 
 %% Decode $. and $\\ to become $\\ escaped characters
 %% in the string representation.
@@ -611,40 +642,42 @@ decode_name_label(Label, Name, N) ->
 %%
 %% Data field -> {binary(),NewCompressionTable}
 %%
+%% Class IN RRs
 encode_data(Comp, _, ?S_A, in, {A,B,C,D}) -> {<<A,B,C,D>>,Comp};
 encode_data(Comp, _, ?S_AAAA, in, {A,B,C,D,E,F,G,H}) ->
     {<<A:16,B:16,C:16,D:16,E:16,F:16,G:16,H:16>>,Comp};
-encode_data(Comp, Pos, ?S_NS, in, Domain) -> encode_name(Comp, Pos, Domain);
-encode_data(Comp, Pos, ?S_MD, in, Domain) -> encode_name(Comp, Pos, Domain);
-encode_data(Comp, Pos, ?S_MF, in, Domain) -> encode_name(Comp, Pos, Domain);
-encode_data(Comp, Pos, ?S_CNAME, in, Domain) -> encode_name(Comp, Pos, Domain);
-encode_data(Comp0, Pos, ?S_SOA, in,
-	    {MName,RName,Serial,Refresh,Retry,Expiry,Minimum}) ->
-    {B1,Comp1} = encode_name(Comp0, Pos, MName),
-    {B,Comp} = encode_name(B1, Comp1, Pos+byte_size(B1), RName),
-    {<<B/binary,Serial:32,Refresh:32/signed,Retry:32/signed,
-      Expiry:32/signed,Minimum:32>>,
-     Comp};
-encode_data(Comp, Pos, ?S_MB, in, Domain) -> encode_name(Comp, Pos, Domain);
-encode_data(Comp, Pos, ?S_MG, in, Domain) -> encode_name(Comp, Pos, Domain);
-encode_data(Comp, Pos, ?S_MR, in, Domain) -> encode_name(Comp, Pos, Domain);
-encode_data(Comp, _, ?S_NULL, in, Data) ->
-    {iolist_to_binary(Data),Comp};
 encode_data(Comp, _, ?S_WKS, in, {{A,B,C,D},Proto,BitMap}) ->
     BitMapBin = iolist_to_binary(BitMap),
     {<<A,B,C,D,Proto,BitMapBin/binary>>,Comp};
-encode_data(Comp, Pos, ?S_PTR, in, Domain) -> encode_name(Comp, Pos, Domain);
-encode_data(Comp, _, ?S_HINFO, in, {CPU,OS}) ->
+%%
+%% Standard RRs (any class)
+encode_data(Comp, Pos, ?S_NS,    _, Domain) -> encode_name(Comp, Pos, Domain);
+encode_data(Comp, Pos, ?S_MD,    _, Domain) -> encode_name(Comp, Pos, Domain);
+encode_data(Comp, Pos, ?S_MF,    _, Domain) -> encode_name(Comp, Pos, Domain);
+encode_data(Comp, Pos, ?S_CNAME, _, Domain) -> encode_name(Comp, Pos, Domain);
+encode_data(Comp, Pos, ?S_SOA, _,
+	    {MName,RName,Serial,Refresh,Retry,Expiry,Minimum}) ->
+    {B1,Comp1} = encode_name(Comp, Pos, MName),
+    {B,Comp2} = encode_name(B1, Comp1, Pos+byte_size(B1), RName),
+    {<<B/binary,Serial:32,Refresh:32/signed,Retry:32/signed,
+      Expiry:32/signed,Minimum:32>>,
+     Comp2};
+encode_data(Comp, Pos, ?S_MB,    _, Domain) -> encode_name(Comp, Pos, Domain);
+encode_data(Comp, Pos, ?S_MG,    _, Domain) -> encode_name(Comp, Pos, Domain);
+encode_data(Comp, Pos, ?S_MR,    _, Domain) -> encode_name(Comp, Pos, Domain);
+encode_data(Comp, _,   ?S_NULL,  _, Data)   -> {iolist_to_binary(Data),Comp};
+encode_data(Comp, Pos, ?S_PTR,   _, Domain) -> encode_name(Comp, Pos, Domain);
+encode_data(Comp, _,   ?S_HINFO, _, {CPU,OS}) ->
     Bin = encode_string(iolist_to_binary(CPU)),
     {encode_string(Bin, iolist_to_binary(OS)),Comp};
-encode_data(Comp0, Pos, ?S_MINFO, in, {RM,EM}) ->
-    {Bin,Comp} = encode_name(Comp0, Pos, RM),
-    encode_name(Bin, Comp, Pos+byte_size(Bin), EM);
-encode_data(Comp, Pos, ?S_MX, in, {Pref,Exch}) ->
+encode_data(Comp, Pos, ?S_MINFO, _, {RM,EM}) ->
+    {Bin,Comp1} = encode_name(Comp, Pos, RM),
+    encode_name(Bin, Comp1, Pos+byte_size(Bin), EM);
+encode_data(Comp, Pos, ?S_MX, _, {Pref,Exch}) ->
     encode_name(<<Pref:16>>, Comp, Pos+2, Exch);
-encode_data(Comp, Pos, ?S_SRV, in, {Prio,Weight,Port,Target}) ->
+encode_data(Comp, Pos, ?S_SRV, _, {Prio,Weight,Port,Target}) ->
     encode_name(<<Prio:16,Weight:16,Port:16>>, Comp, Pos+2+2+2, Target);
-encode_data(Comp, Pos, ?S_NAPTR, in, 
+encode_data(Comp, Pos, ?S_NAPTR, _,
 	    {Order,Preference,Flags,Services,Regexp,Replacement}) ->
     B0 = <<Order:16,Preference:16>>,
     B1 = encode_string(B0, iolist_to_binary(Flags)),
@@ -654,19 +687,21 @@ encode_data(Comp, Pos, ?S_NAPTR, in,
     %% Bypass name compression (RFC 2915: section 2)
     {B,_} = encode_name(B3, gb_trees:empty(), Pos+byte_size(B3), Replacement),
     {B,Comp};
-%% ?S_OPT falls through to default
-encode_data(Comp, _, ?S_TXT, in, Data) -> {encode_txt(Data),Comp};
-encode_data(Comp, _, ?S_SPF, in, Data) -> {encode_txt(Data),Comp};
-encode_data(Comp, _, ?S_URI, in, {Prio,Weight,Target}) ->
+encode_data(Comp, _, ?S_OPT, _, Data) -> {iolist_to_binary(Data),Comp};
+encode_data(Comp, _, ?S_TXT, _, Data) -> {encode_txt(Data),Comp};
+encode_data(Comp, _, ?S_SPF, _, Data) -> {encode_txt(Data),Comp};
+encode_data(Comp, _, ?S_URI, _, {Prio,Weight,Target}) ->
     {<<Prio:16,Weight:16,(iolist_to_binary(Target))/binary>>,Comp};
-encode_data(Comp, _, ?S_URI, in, Data) -> {encode_txt(Data),Comp};
-encode_data(Comp, _, ?S_CAA, in, {Flags,Tag,Value}) ->
+encode_data(Comp, _, ?S_CAA, _, {Flags,Tag,Value}) ->
     B0 = <<Flags:8>>,
     B1 = encode_string(B0, iolist_to_binary(Tag)),
     B2 = iolist_to_binary(Value),
     {<<B1/binary,B2/binary>>,Comp};
-encode_data(Comp, _, ?S_CAA, in, Data) -> {encode_txt(Data),Comp};
-encode_data(Comp, _Pos, _Type, _Class, Data) -> {iolist_to_binary(Data),Comp}.
+encode_data(Comp, _, ?S_CAA, _, Data) -> {encode_txt(Data),Comp};
+%%
+%% sofar unknown or non standard
+encode_data(Comp, _Pos, _Type, _Class, Data) ->
+    {iolist_to_binary(Data),Comp}.
 
 %% Array of strings
 %%
-- 
2.31.1

openSUSE Build Service is sponsored by