{-# LANGUAGE BangPatterns               #-}
{-# LANGUAGE CApiFFI                    #-}
{-# LANGUAGE DeriveFoldable             #-}
{-# LANGUAGE DeriveFunctor              #-}
{-# LANGUAGE DeriveTraversable          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE RecordWildCards            #-}

-- |
-- Copyright: © 2017 Herbert Valerio Riedel
-- SPDX-License-Identifier: GPL-2.0-or-later
--
-- Internal module
module Network.DNS.Message where

import qualified Data.ByteString.Base16 as B16

import qualified Data.ByteString        as BS
import qualified Data.ByteString.Lazy   as BSL
import           Data.Function
import           Data.List              (groupBy)
import           Data.String
import           Numeric                (showHex)
import           Prelude

import           Data.Binary
import           Data.Binary.Get
import           Data.Binary.Put
import           Data.Bits
import           Data.Map               (Map)
import qualified Data.Map               as Map
import           Data.Set               (Set)
import qualified Data.Set               as Set

import           Compat

-- | An IPv6 address
--
-- The IP address is represented in network order,
-- i.e. @2606:2800:220:1:248:1893:25c8:1946@ is
-- represented as @(IPv6 0x2606280002200001 0x248189325c81946)@.
data IPv6 = IPv6 !Word64 !Word64
          deriving (IPv6 -> IPv6 -> Bool
(IPv6 -> IPv6 -> Bool) -> (IPv6 -> IPv6 -> Bool) -> Eq IPv6
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IPv6 -> IPv6 -> Bool
$c/= :: IPv6 -> IPv6 -> Bool
== :: IPv6 -> IPv6 -> Bool
$c== :: IPv6 -> IPv6 -> Bool
Eq,Eq IPv6
Eq IPv6 =>
(IPv6 -> IPv6 -> Ordering)
-> (IPv6 -> IPv6 -> Bool)
-> (IPv6 -> IPv6 -> Bool)
-> (IPv6 -> IPv6 -> Bool)
-> (IPv6 -> IPv6 -> Bool)
-> (IPv6 -> IPv6 -> IPv6)
-> (IPv6 -> IPv6 -> IPv6)
-> Ord IPv6
IPv6 -> IPv6 -> Bool
IPv6 -> IPv6 -> Ordering
IPv6 -> IPv6 -> IPv6
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IPv6 -> IPv6 -> IPv6
$cmin :: IPv6 -> IPv6 -> IPv6
max :: IPv6 -> IPv6 -> IPv6
$cmax :: IPv6 -> IPv6 -> IPv6
>= :: IPv6 -> IPv6 -> Bool
$c>= :: IPv6 -> IPv6 -> Bool
> :: IPv6 -> IPv6 -> Bool
$c> :: IPv6 -> IPv6 -> Bool
<= :: IPv6 -> IPv6 -> Bool
$c<= :: IPv6 -> IPv6 -> Bool
< :: IPv6 -> IPv6 -> Bool
$c< :: IPv6 -> IPv6 -> Bool
compare :: IPv6 -> IPv6 -> Ordering
$ccompare :: IPv6 -> IPv6 -> Ordering
$cp1Ord :: Eq IPv6
Ord,ReadPrec [IPv6]
ReadPrec IPv6
Int -> ReadS IPv6
ReadS [IPv6]
(Int -> ReadS IPv6)
-> ReadS [IPv6] -> ReadPrec IPv6 -> ReadPrec [IPv6] -> Read IPv6
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IPv6]
$creadListPrec :: ReadPrec [IPv6]
readPrec :: ReadPrec IPv6
$creadPrec :: ReadPrec IPv6
readList :: ReadS [IPv6]
$creadList :: ReadS [IPv6]
readsPrec :: Int -> ReadS IPv6
$creadsPrec :: Int -> ReadS IPv6
Read)

instance Show IPv6 where
    showsPrec :: Int -> IPv6 -> ShowS
showsPrec p :: Int
p (IPv6 hi :: Word64
hi lo :: Word64
lo) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "IPv6 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
hi ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString " 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
lo)

instance Binary IPv6 where
    put :: IPv6 -> Put
put (IPv6 hi :: Word64
hi lo :: Word64
lo) = Word64 -> Put
putWord64be Word64
hi Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word64 -> Put
putWord64be Word64
lo
    get :: Get IPv6
get              = Word64 -> Word64 -> IPv6
IPv6 (Word64 -> Word64 -> IPv6) -> Get Word64 -> Get (Word64 -> IPv6)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word64
getWord64be Get (Word64 -> IPv6) -> Get Word64 -> Get IPv6
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word64
getWord64be

-- | An IPv4 address
--
-- The IP address is represented in network order, i.e. @127.0.0.1@ is
-- represented as @(IPv4 0x7f000001)@.
data IPv4 = IPv4 !Word32
          deriving (IPv4 -> IPv4 -> Bool
(IPv4 -> IPv4 -> Bool) -> (IPv4 -> IPv4 -> Bool) -> Eq IPv4
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IPv4 -> IPv4 -> Bool
$c/= :: IPv4 -> IPv4 -> Bool
== :: IPv4 -> IPv4 -> Bool
$c== :: IPv4 -> IPv4 -> Bool
Eq,Eq IPv4
Eq IPv4 =>
(IPv4 -> IPv4 -> Ordering)
-> (IPv4 -> IPv4 -> Bool)
-> (IPv4 -> IPv4 -> Bool)
-> (IPv4 -> IPv4 -> Bool)
-> (IPv4 -> IPv4 -> Bool)
-> (IPv4 -> IPv4 -> IPv4)
-> (IPv4 -> IPv4 -> IPv4)
-> Ord IPv4
IPv4 -> IPv4 -> Bool
IPv4 -> IPv4 -> Ordering
IPv4 -> IPv4 -> IPv4
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IPv4 -> IPv4 -> IPv4
$cmin :: IPv4 -> IPv4 -> IPv4
max :: IPv4 -> IPv4 -> IPv4
$cmax :: IPv4 -> IPv4 -> IPv4
>= :: IPv4 -> IPv4 -> Bool
$c>= :: IPv4 -> IPv4 -> Bool
> :: IPv4 -> IPv4 -> Bool
$c> :: IPv4 -> IPv4 -> Bool
<= :: IPv4 -> IPv4 -> Bool
$c<= :: IPv4 -> IPv4 -> Bool
< :: IPv4 -> IPv4 -> Bool
$c< :: IPv4 -> IPv4 -> Bool
compare :: IPv4 -> IPv4 -> Ordering
$ccompare :: IPv4 -> IPv4 -> Ordering
$cp1Ord :: Eq IPv4
Ord,ReadPrec [IPv4]
ReadPrec IPv4
Int -> ReadS IPv4
ReadS [IPv4]
(Int -> ReadS IPv4)
-> ReadS [IPv4] -> ReadPrec IPv4 -> ReadPrec [IPv4] -> Read IPv4
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IPv4]
$creadListPrec :: ReadPrec [IPv4]
readPrec :: ReadPrec IPv4
$creadPrec :: ReadPrec IPv4
readList :: ReadS [IPv4]
$creadList :: ReadS [IPv4]
readsPrec :: Int -> ReadS IPv4
$creadsPrec :: Int -> ReadS IPv4
Read)

instance Show IPv4 where
    showsPrec :: Int -> IPv4 -> ShowS
showsPrec p :: Int
p (IPv4 n :: Word32
n) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "IPv4 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word32
n)

instance Binary IPv4 where
    put :: IPv4 -> Put
put (IPv4 w :: Word32
w) = Word32 -> Put
putWord32be Word32
w
    get :: Get IPv4
get = Word32 -> IPv4
IPv4 (Word32 -> IPv4) -> Get Word32 -> Get IPv4
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word32
getWord32be

-- | @\<domain-name\>@ as per [RFC 1035, section 3.3](https://tools.ietf.org/html/rfc1035#section-3.3).
--
-- A domain-name represented as a series of labels separated by dots.
--
-- See also 'Labels' for list-based representation.
--
-- __NOTE__: The 'Labels' type is able to properly represent domain
-- names whose components contain dots which the 'Name' representation
-- cannot.
newtype Name = Name BS.ByteString
             deriving (ReadPrec [Name]
ReadPrec Name
Int -> ReadS Name
ReadS [Name]
(Int -> ReadS Name)
-> ReadS [Name] -> ReadPrec Name -> ReadPrec [Name] -> Read Name
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Name]
$creadListPrec :: ReadPrec [Name]
readPrec :: ReadPrec Name
$creadPrec :: ReadPrec Name
readList :: ReadS [Name]
$creadList :: ReadS [Name]
readsPrec :: Int -> ReadS Name
$creadsPrec :: Int -> ReadS Name
Read,Int -> Name -> ShowS
[Name] -> ShowS
Name -> String
(Int -> Name -> ShowS)
-> (Name -> String) -> ([Name] -> ShowS) -> Show Name
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Name] -> ShowS
$cshowList :: [Name] -> ShowS
show :: Name -> String
$cshow :: Name -> String
showsPrec :: Int -> Name -> ShowS
$cshowsPrec :: Int -> Name -> ShowS
Show,Name -> Name -> Bool
(Name -> Name -> Bool) -> (Name -> Name -> Bool) -> Eq Name
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c== :: Name -> Name -> Bool
Eq,Eq Name
Eq Name =>
(Name -> Name -> Ordering)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Name)
-> (Name -> Name -> Name)
-> Ord Name
Name -> Name -> Bool
Name -> Name -> Ordering
Name -> Name -> Name
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Name -> Name -> Name
$cmin :: Name -> Name -> Name
max :: Name -> Name -> Name
$cmax :: Name -> Name -> Name
>= :: Name -> Name -> Bool
$c>= :: Name -> Name -> Bool
> :: Name -> Name -> Bool
$c> :: Name -> Name -> Bool
<= :: Name -> Name -> Bool
$c<= :: Name -> Name -> Bool
< :: Name -> Name -> Bool
$c< :: Name -> Name -> Bool
compare :: Name -> Name -> Ordering
$ccompare :: Name -> Name -> Ordering
$cp1Ord :: Eq Name
Ord)

-- | @\<character-string\>@ as per [RFC 1035, section 3.3](https://tools.ietf.org/html/rfc1035#section-3.3).
--
-- A sequence of up to 255 octets
--
-- The limit of 255 octets is caused by the encoding which uses by a
-- prefixed octet denoting the length.
newtype CharStr = CharStr BS.ByteString
                deriving (CharStr -> CharStr -> Bool
(CharStr -> CharStr -> Bool)
-> (CharStr -> CharStr -> Bool) -> Eq CharStr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CharStr -> CharStr -> Bool
$c/= :: CharStr -> CharStr -> Bool
== :: CharStr -> CharStr -> Bool
$c== :: CharStr -> CharStr -> Bool
Eq,Eq CharStr
Eq CharStr =>
(CharStr -> CharStr -> Ordering)
-> (CharStr -> CharStr -> Bool)
-> (CharStr -> CharStr -> Bool)
-> (CharStr -> CharStr -> Bool)
-> (CharStr -> CharStr -> Bool)
-> (CharStr -> CharStr -> CharStr)
-> (CharStr -> CharStr -> CharStr)
-> Ord CharStr
CharStr -> CharStr -> Bool
CharStr -> CharStr -> Ordering
CharStr -> CharStr -> CharStr
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CharStr -> CharStr -> CharStr
$cmin :: CharStr -> CharStr -> CharStr
max :: CharStr -> CharStr -> CharStr
$cmax :: CharStr -> CharStr -> CharStr
>= :: CharStr -> CharStr -> Bool
$c>= :: CharStr -> CharStr -> Bool
> :: CharStr -> CharStr -> Bool
$c> :: CharStr -> CharStr -> Bool
<= :: CharStr -> CharStr -> Bool
$c<= :: CharStr -> CharStr -> Bool
< :: CharStr -> CharStr -> Bool
$c< :: CharStr -> CharStr -> Bool
compare :: CharStr -> CharStr -> Ordering
$ccompare :: CharStr -> CharStr -> Ordering
$cp1Ord :: Eq CharStr
Ord,String -> CharStr
(String -> CharStr) -> IsString CharStr
forall a. (String -> a) -> IsString a
fromString :: String -> CharStr
$cfromString :: String -> CharStr
IsString)

instance Show CharStr where
    showsPrec :: Int -> CharStr -> ShowS
showsPrec p :: Int
p (CharStr bs :: ByteString
bs) = Int -> ByteString -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p ByteString
bs

instance Read CharStr where
    readsPrec :: Int -> ReadS CharStr
readsPrec p :: Int
p = ((ByteString, String) -> (CharStr, String))
-> [(ByteString, String)] -> [(CharStr, String)]
forall a b. (a -> b) -> [a] -> [b]
map (\(x :: ByteString
x,y :: String
y) -> (ByteString -> CharStr
CharStr ByteString
x,String
y)) ([(ByteString, String)] -> [(CharStr, String)])
-> (String -> [(ByteString, String)]) -> ReadS CharStr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> String -> [(ByteString, String)]
forall a. Read a => Int -> ReadS a
readsPrec Int
p

instance Binary CharStr where
    put :: CharStr -> Put
put (CharStr bs :: ByteString
bs)
      | ByteString -> Int
BS.length ByteString
bs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> 0xff = String -> Put
forall a. HasCallStack => String -> a
error "putString: string too long"
      | Bool
otherwise = do
            Word8 -> Put
putWord8 (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> Int -> Word8
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
BS.length ByteString
bs)
            ByteString -> Put
putByteString ByteString
bs
    get :: Get CharStr
get = do
        Word8
len' <- Get Word8
getWord8
        ByteString -> CharStr
CharStr (ByteString -> CharStr) -> Get ByteString -> Get CharStr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
len')

{- Resource records

 -- https://en.wikipedia.org/wiki/List_of_DNS_record_types

 RFC 1035

 A        1     a host address
 NS       2     an authoritative name server
 CNAME    5     the canonical name for an alias
 SOA      6     marks the start of a zone of authority
 PTR      12    a domain name pointer
 MX       15    mail exchange
 TXT      16    text strings

 RFC 3596

 AAAA     28    IPv6

 RFC 2782

 SRV      33    Location of services

 ----

 RFC3597            Handling of Unknown DNS Resource Record (RR) Types

-}

-- | Represents a DNS message as per [RFC 1035](https://tools.ietf.org/html/rfc1035)
data Msg l
    = Msg
      { Msg l -> MsgHeader
msgHeader           :: !MsgHeader
      , Msg l -> [MsgQuestion l]
msgQD               :: [MsgQuestion l]
      , Msg l -> [MsgRR l]
msgAN, Msg l -> [MsgRR l]
msgNS, Msg l -> [MsgRR l]
msgAR :: [MsgRR l]
      } deriving (ReadPrec [Msg l]
ReadPrec (Msg l)
Int -> ReadS (Msg l)
ReadS [Msg l]
(Int -> ReadS (Msg l))
-> ReadS [Msg l]
-> ReadPrec (Msg l)
-> ReadPrec [Msg l]
-> Read (Msg l)
forall l. Read l => ReadPrec [Msg l]
forall l. Read l => ReadPrec (Msg l)
forall l. Read l => Int -> ReadS (Msg l)
forall l. Read l => ReadS [Msg l]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Msg l]
$creadListPrec :: forall l. Read l => ReadPrec [Msg l]
readPrec :: ReadPrec (Msg l)
$creadPrec :: forall l. Read l => ReadPrec (Msg l)
readList :: ReadS [Msg l]
$creadList :: forall l. Read l => ReadS [Msg l]
readsPrec :: Int -> ReadS (Msg l)
$creadsPrec :: forall l. Read l => Int -> ReadS (Msg l)
Read,Int -> Msg l -> ShowS
[Msg l] -> ShowS
Msg l -> String
(Int -> Msg l -> ShowS)
-> (Msg l -> String) -> ([Msg l] -> ShowS) -> Show (Msg l)
forall l. Show l => Int -> Msg l -> ShowS
forall l. Show l => [Msg l] -> ShowS
forall l. Show l => Msg l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Msg l] -> ShowS
$cshowList :: forall l. Show l => [Msg l] -> ShowS
show :: Msg l -> String
$cshow :: forall l. Show l => Msg l -> String
showsPrec :: Int -> Msg l -> ShowS
$cshowsPrec :: forall l. Show l => Int -> Msg l -> ShowS
Show,a -> Msg b -> Msg a
(a -> b) -> Msg a -> Msg b
(forall a b. (a -> b) -> Msg a -> Msg b)
-> (forall a b. a -> Msg b -> Msg a) -> Functor Msg
forall a b. a -> Msg b -> Msg a
forall a b. (a -> b) -> Msg a -> Msg b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Msg b -> Msg a
$c<$ :: forall a b. a -> Msg b -> Msg a
fmap :: (a -> b) -> Msg a -> Msg b
$cfmap :: forall a b. (a -> b) -> Msg a -> Msg b
Functor,Msg a -> Bool
(a -> m) -> Msg a -> m
(a -> b -> b) -> b -> Msg a -> b
(forall m. Monoid m => Msg m -> m)
-> (forall m a. Monoid m => (a -> m) -> Msg a -> m)
-> (forall m a. Monoid m => (a -> m) -> Msg a -> m)
-> (forall a b. (a -> b -> b) -> b -> Msg a -> b)
-> (forall a b. (a -> b -> b) -> b -> Msg a -> b)
-> (forall b a. (b -> a -> b) -> b -> Msg a -> b)
-> (forall b a. (b -> a -> b) -> b -> Msg a -> b)
-> (forall a. (a -> a -> a) -> Msg a -> a)
-> (forall a. (a -> a -> a) -> Msg a -> a)
-> (forall a. Msg a -> [a])
-> (forall a. Msg a -> Bool)
-> (forall a. Msg a -> Int)
-> (forall a. Eq a => a -> Msg a -> Bool)
-> (forall a. Ord a => Msg a -> a)
-> (forall a. Ord a => Msg a -> a)
-> (forall a. Num a => Msg a -> a)
-> (forall a. Num a => Msg a -> a)
-> Foldable Msg
forall a. Eq a => a -> Msg a -> Bool
forall a. Num a => Msg a -> a
forall a. Ord a => Msg a -> a
forall m. Monoid m => Msg m -> m
forall a. Msg a -> Bool
forall a. Msg a -> Int
forall a. Msg a -> [a]
forall a. (a -> a -> a) -> Msg a -> a
forall m a. Monoid m => (a -> m) -> Msg a -> m
forall b a. (b -> a -> b) -> b -> Msg a -> b
forall a b. (a -> b -> b) -> b -> Msg a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Msg a -> a
$cproduct :: forall a. Num a => Msg a -> a
sum :: Msg a -> a
$csum :: forall a. Num a => Msg a -> a
minimum :: Msg a -> a
$cminimum :: forall a. Ord a => Msg a -> a
maximum :: Msg a -> a
$cmaximum :: forall a. Ord a => Msg a -> a
elem :: a -> Msg a -> Bool
$celem :: forall a. Eq a => a -> Msg a -> Bool
length :: Msg a -> Int
$clength :: forall a. Msg a -> Int
null :: Msg a -> Bool
$cnull :: forall a. Msg a -> Bool
toList :: Msg a -> [a]
$ctoList :: forall a. Msg a -> [a]
foldl1 :: (a -> a -> a) -> Msg a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Msg a -> a
foldr1 :: (a -> a -> a) -> Msg a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Msg a -> a
foldl' :: (b -> a -> b) -> b -> Msg a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Msg a -> b
foldl :: (b -> a -> b) -> b -> Msg a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Msg a -> b
foldr' :: (a -> b -> b) -> b -> Msg a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Msg a -> b
foldr :: (a -> b -> b) -> b -> Msg a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Msg a -> b
foldMap' :: (a -> m) -> Msg a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Msg a -> m
foldMap :: (a -> m) -> Msg a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Msg a -> m
fold :: Msg m -> m
$cfold :: forall m. Monoid m => Msg m -> m
Foldable,Functor Msg
Foldable Msg
(Functor Msg, Foldable Msg) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> Msg a -> f (Msg b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Msg (f a) -> f (Msg a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Msg a -> m (Msg b))
-> (forall (m :: * -> *) a. Monad m => Msg (m a) -> m (Msg a))
-> Traversable Msg
(a -> f b) -> Msg a -> f (Msg b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Msg (m a) -> m (Msg a)
forall (f :: * -> *) a. Applicative f => Msg (f a) -> f (Msg a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Msg a -> m (Msg b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Msg a -> f (Msg b)
sequence :: Msg (m a) -> m (Msg a)
$csequence :: forall (m :: * -> *) a. Monad m => Msg (m a) -> m (Msg a)
mapM :: (a -> m b) -> Msg a -> m (Msg b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Msg a -> m (Msg b)
sequenceA :: Msg (f a) -> f (Msg a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Msg (f a) -> f (Msg a)
traverse :: (a -> f b) -> Msg a -> f (Msg b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Msg a -> f (Msg b)
$cp2Traversable :: Foldable Msg
$cp1Traversable :: Functor Msg
Traversable)

-- | DNS message header section as per [RFC 1035, section 4.1.1](https://tools.ietf.org/html/rfc1035#section-4.1.1)
data MsgHeader
    = MsgHeader
      { MsgHeader -> Word16
mhId      :: !Word16

      , MsgHeader -> MsgHeaderFlags
mhFlags   :: !MsgHeaderFlags

      , MsgHeader -> Word16
mhQDCount :: !Word16
      , MsgHeader -> Word16
mhANCount :: !Word16
      , MsgHeader -> Word16
mhNSCount :: !Word16
      , MsgHeader -> Word16
mhARCount :: !Word16
      } deriving (ReadPrec [MsgHeader]
ReadPrec MsgHeader
Int -> ReadS MsgHeader
ReadS [MsgHeader]
(Int -> ReadS MsgHeader)
-> ReadS [MsgHeader]
-> ReadPrec MsgHeader
-> ReadPrec [MsgHeader]
-> Read MsgHeader
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MsgHeader]
$creadListPrec :: ReadPrec [MsgHeader]
readPrec :: ReadPrec MsgHeader
$creadPrec :: ReadPrec MsgHeader
readList :: ReadS [MsgHeader]
$creadList :: ReadS [MsgHeader]
readsPrec :: Int -> ReadS MsgHeader
$creadsPrec :: Int -> ReadS MsgHeader
Read,Int -> MsgHeader -> ShowS
[MsgHeader] -> ShowS
MsgHeader -> String
(Int -> MsgHeader -> ShowS)
-> (MsgHeader -> String)
-> ([MsgHeader] -> ShowS)
-> Show MsgHeader
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MsgHeader] -> ShowS
$cshowList :: [MsgHeader] -> ShowS
show :: MsgHeader -> String
$cshow :: MsgHeader -> String
showsPrec :: Int -> MsgHeader -> ShowS
$cshowsPrec :: Int -> MsgHeader -> ShowS
Show)

-- | DNS message header section as per [RFC 1035, section 4.1.2](https://tools.ietf.org/html/rfc1035#section-4.1.2)
data MsgQuestion l
    = MsgQuestion !l !Type !Class
    deriving (MsgQuestion l -> MsgQuestion l -> Bool
(MsgQuestion l -> MsgQuestion l -> Bool)
-> (MsgQuestion l -> MsgQuestion l -> Bool) -> Eq (MsgQuestion l)
forall l. Eq l => MsgQuestion l -> MsgQuestion l -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MsgQuestion l -> MsgQuestion l -> Bool
$c/= :: forall l. Eq l => MsgQuestion l -> MsgQuestion l -> Bool
== :: MsgQuestion l -> MsgQuestion l -> Bool
$c== :: forall l. Eq l => MsgQuestion l -> MsgQuestion l -> Bool
Eq,ReadPrec [MsgQuestion l]
ReadPrec (MsgQuestion l)
Int -> ReadS (MsgQuestion l)
ReadS [MsgQuestion l]
(Int -> ReadS (MsgQuestion l))
-> ReadS [MsgQuestion l]
-> ReadPrec (MsgQuestion l)
-> ReadPrec [MsgQuestion l]
-> Read (MsgQuestion l)
forall l. Read l => ReadPrec [MsgQuestion l]
forall l. Read l => ReadPrec (MsgQuestion l)
forall l. Read l => Int -> ReadS (MsgQuestion l)
forall l. Read l => ReadS [MsgQuestion l]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MsgQuestion l]
$creadListPrec :: forall l. Read l => ReadPrec [MsgQuestion l]
readPrec :: ReadPrec (MsgQuestion l)
$creadPrec :: forall l. Read l => ReadPrec (MsgQuestion l)
readList :: ReadS [MsgQuestion l]
$creadList :: forall l. Read l => ReadS [MsgQuestion l]
readsPrec :: Int -> ReadS (MsgQuestion l)
$creadsPrec :: forall l. Read l => Int -> ReadS (MsgQuestion l)
Read,Int -> MsgQuestion l -> ShowS
[MsgQuestion l] -> ShowS
MsgQuestion l -> String
(Int -> MsgQuestion l -> ShowS)
-> (MsgQuestion l -> String)
-> ([MsgQuestion l] -> ShowS)
-> Show (MsgQuestion l)
forall l. Show l => Int -> MsgQuestion l -> ShowS
forall l. Show l => [MsgQuestion l] -> ShowS
forall l. Show l => MsgQuestion l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MsgQuestion l] -> ShowS
$cshowList :: forall l. Show l => [MsgQuestion l] -> ShowS
show :: MsgQuestion l -> String
$cshow :: forall l. Show l => MsgQuestion l -> String
showsPrec :: Int -> MsgQuestion l -> ShowS
$cshowsPrec :: forall l. Show l => Int -> MsgQuestion l -> ShowS
Show,a -> MsgQuestion b -> MsgQuestion a
(a -> b) -> MsgQuestion a -> MsgQuestion b
(forall a b. (a -> b) -> MsgQuestion a -> MsgQuestion b)
-> (forall a b. a -> MsgQuestion b -> MsgQuestion a)
-> Functor MsgQuestion
forall a b. a -> MsgQuestion b -> MsgQuestion a
forall a b. (a -> b) -> MsgQuestion a -> MsgQuestion b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> MsgQuestion b -> MsgQuestion a
$c<$ :: forall a b. a -> MsgQuestion b -> MsgQuestion a
fmap :: (a -> b) -> MsgQuestion a -> MsgQuestion b
$cfmap :: forall a b. (a -> b) -> MsgQuestion a -> MsgQuestion b
Functor,MsgQuestion a -> Bool
(a -> m) -> MsgQuestion a -> m
(a -> b -> b) -> b -> MsgQuestion a -> b
(forall m. Monoid m => MsgQuestion m -> m)
-> (forall m a. Monoid m => (a -> m) -> MsgQuestion a -> m)
-> (forall m a. Monoid m => (a -> m) -> MsgQuestion a -> m)
-> (forall a b. (a -> b -> b) -> b -> MsgQuestion a -> b)
-> (forall a b. (a -> b -> b) -> b -> MsgQuestion a -> b)
-> (forall b a. (b -> a -> b) -> b -> MsgQuestion a -> b)
-> (forall b a. (b -> a -> b) -> b -> MsgQuestion a -> b)
-> (forall a. (a -> a -> a) -> MsgQuestion a -> a)
-> (forall a. (a -> a -> a) -> MsgQuestion a -> a)
-> (forall a. MsgQuestion a -> [a])
-> (forall a. MsgQuestion a -> Bool)
-> (forall a. MsgQuestion a -> Int)
-> (forall a. Eq a => a -> MsgQuestion a -> Bool)
-> (forall a. Ord a => MsgQuestion a -> a)
-> (forall a. Ord a => MsgQuestion a -> a)
-> (forall a. Num a => MsgQuestion a -> a)
-> (forall a. Num a => MsgQuestion a -> a)
-> Foldable MsgQuestion
forall a. Eq a => a -> MsgQuestion a -> Bool
forall a. Num a => MsgQuestion a -> a
forall a. Ord a => MsgQuestion a -> a
forall m. Monoid m => MsgQuestion m -> m
forall a. MsgQuestion a -> Bool
forall a. MsgQuestion a -> Int
forall a. MsgQuestion a -> [a]
forall a. (a -> a -> a) -> MsgQuestion a -> a
forall m a. Monoid m => (a -> m) -> MsgQuestion a -> m
forall b a. (b -> a -> b) -> b -> MsgQuestion a -> b
forall a b. (a -> b -> b) -> b -> MsgQuestion a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: MsgQuestion a -> a
$cproduct :: forall a. Num a => MsgQuestion a -> a
sum :: MsgQuestion a -> a
$csum :: forall a. Num a => MsgQuestion a -> a
minimum :: MsgQuestion a -> a
$cminimum :: forall a. Ord a => MsgQuestion a -> a
maximum :: MsgQuestion a -> a
$cmaximum :: forall a. Ord a => MsgQuestion a -> a
elem :: a -> MsgQuestion a -> Bool
$celem :: forall a. Eq a => a -> MsgQuestion a -> Bool
length :: MsgQuestion a -> Int
$clength :: forall a. MsgQuestion a -> Int
null :: MsgQuestion a -> Bool
$cnull :: forall a. MsgQuestion a -> Bool
toList :: MsgQuestion a -> [a]
$ctoList :: forall a. MsgQuestion a -> [a]
foldl1 :: (a -> a -> a) -> MsgQuestion a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> MsgQuestion a -> a
foldr1 :: (a -> a -> a) -> MsgQuestion a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> MsgQuestion a -> a
foldl' :: (b -> a -> b) -> b -> MsgQuestion a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> MsgQuestion a -> b
foldl :: (b -> a -> b) -> b -> MsgQuestion a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> MsgQuestion a -> b
foldr' :: (a -> b -> b) -> b -> MsgQuestion a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> MsgQuestion a -> b
foldr :: (a -> b -> b) -> b -> MsgQuestion a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> MsgQuestion a -> b
foldMap' :: (a -> m) -> MsgQuestion a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> MsgQuestion a -> m
foldMap :: (a -> m) -> MsgQuestion a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> MsgQuestion a -> m
fold :: MsgQuestion m -> m
$cfold :: forall m. Monoid m => MsgQuestion m -> m
Foldable,Functor MsgQuestion
Foldable MsgQuestion
(Functor MsgQuestion, Foldable MsgQuestion) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> MsgQuestion a -> f (MsgQuestion b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    MsgQuestion (f a) -> f (MsgQuestion a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> MsgQuestion a -> m (MsgQuestion b))
-> (forall (m :: * -> *) a.
    Monad m =>
    MsgQuestion (m a) -> m (MsgQuestion a))
-> Traversable MsgQuestion
(a -> f b) -> MsgQuestion a -> f (MsgQuestion b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
MsgQuestion (m a) -> m (MsgQuestion a)
forall (f :: * -> *) a.
Applicative f =>
MsgQuestion (f a) -> f (MsgQuestion a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MsgQuestion a -> m (MsgQuestion b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MsgQuestion a -> f (MsgQuestion b)
sequence :: MsgQuestion (m a) -> m (MsgQuestion a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
MsgQuestion (m a) -> m (MsgQuestion a)
mapM :: (a -> m b) -> MsgQuestion a -> m (MsgQuestion b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MsgQuestion a -> m (MsgQuestion b)
sequenceA :: MsgQuestion (f a) -> f (MsgQuestion a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
MsgQuestion (f a) -> f (MsgQuestion a)
traverse :: (a -> f b) -> MsgQuestion a -> f (MsgQuestion b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MsgQuestion a -> f (MsgQuestion b)
$cp2Traversable :: Foldable MsgQuestion
$cp1Traversable :: Functor MsgQuestion
Traversable)

-- | DNS message header flags as per [RFC 1035, section 4.1.1](https://tools.ietf.org/html/rfc1035#section-4.1.1)
data MsgHeaderFlags
    = MsgHeaderFlags
      { MsgHeaderFlags -> QR
mhQR     :: !QR
      , MsgHeaderFlags -> Word8
mhOpcode :: !Word8 -- actually Word4
      , MsgHeaderFlags -> Bool
mhAA     :: !Bool
      , MsgHeaderFlags -> Bool
mhTC     :: !Bool
      , MsgHeaderFlags -> Bool
mhRD     :: !Bool
      , MsgHeaderFlags -> Bool
mhRA     :: !Bool
      , MsgHeaderFlags -> Bool
mhZ      :: !Bool -- reserved/unused bit
      , MsgHeaderFlags -> Bool
mhAD     :: !Bool -- RFC4035
      , MsgHeaderFlags -> Bool
mhCD     :: !Bool -- RFC4035
      , MsgHeaderFlags -> Word8
mhRCode  :: !Word8 -- Word4
      } deriving (ReadPrec [MsgHeaderFlags]
ReadPrec MsgHeaderFlags
Int -> ReadS MsgHeaderFlags
ReadS [MsgHeaderFlags]
(Int -> ReadS MsgHeaderFlags)
-> ReadS [MsgHeaderFlags]
-> ReadPrec MsgHeaderFlags
-> ReadPrec [MsgHeaderFlags]
-> Read MsgHeaderFlags
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MsgHeaderFlags]
$creadListPrec :: ReadPrec [MsgHeaderFlags]
readPrec :: ReadPrec MsgHeaderFlags
$creadPrec :: ReadPrec MsgHeaderFlags
readList :: ReadS [MsgHeaderFlags]
$creadList :: ReadS [MsgHeaderFlags]
readsPrec :: Int -> ReadS MsgHeaderFlags
$creadsPrec :: Int -> ReadS MsgHeaderFlags
Read,Int -> MsgHeaderFlags -> ShowS
[MsgHeaderFlags] -> ShowS
MsgHeaderFlags -> String
(Int -> MsgHeaderFlags -> ShowS)
-> (MsgHeaderFlags -> String)
-> ([MsgHeaderFlags] -> ShowS)
-> Show MsgHeaderFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MsgHeaderFlags] -> ShowS
$cshowList :: [MsgHeaderFlags] -> ShowS
show :: MsgHeaderFlags -> String
$cshow :: MsgHeaderFlags -> String
showsPrec :: Int -> MsgHeaderFlags -> ShowS
$cshowsPrec :: Int -> MsgHeaderFlags -> ShowS
Show)

-- | DNS resource record section as per [RFC 1035, section 4.1.3](https://tools.ietf.org/html/rfc1035#section-4.1.3)
data MsgRR l
    = MsgRR
      { MsgRR l -> l
rrName  :: !l
      , MsgRR l -> Class
rrClass :: !Class
      , MsgRR l -> TTL
rrTTL   :: !TTL
      , MsgRR l -> RData l
rrData  :: !(RData l)
      } deriving (MsgRR l -> MsgRR l -> Bool
(MsgRR l -> MsgRR l -> Bool)
-> (MsgRR l -> MsgRR l -> Bool) -> Eq (MsgRR l)
forall l. Eq l => MsgRR l -> MsgRR l -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MsgRR l -> MsgRR l -> Bool
$c/= :: forall l. Eq l => MsgRR l -> MsgRR l -> Bool
== :: MsgRR l -> MsgRR l -> Bool
$c== :: forall l. Eq l => MsgRR l -> MsgRR l -> Bool
Eq,ReadPrec [MsgRR l]
ReadPrec (MsgRR l)
Int -> ReadS (MsgRR l)
ReadS [MsgRR l]
(Int -> ReadS (MsgRR l))
-> ReadS [MsgRR l]
-> ReadPrec (MsgRR l)
-> ReadPrec [MsgRR l]
-> Read (MsgRR l)
forall l. Read l => ReadPrec [MsgRR l]
forall l. Read l => ReadPrec (MsgRR l)
forall l. Read l => Int -> ReadS (MsgRR l)
forall l. Read l => ReadS [MsgRR l]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MsgRR l]
$creadListPrec :: forall l. Read l => ReadPrec [MsgRR l]
readPrec :: ReadPrec (MsgRR l)
$creadPrec :: forall l. Read l => ReadPrec (MsgRR l)
readList :: ReadS [MsgRR l]
$creadList :: forall l. Read l => ReadS [MsgRR l]
readsPrec :: Int -> ReadS (MsgRR l)
$creadsPrec :: forall l. Read l => Int -> ReadS (MsgRR l)
Read,Int -> MsgRR l -> ShowS
[MsgRR l] -> ShowS
MsgRR l -> String
(Int -> MsgRR l -> ShowS)
-> (MsgRR l -> String) -> ([MsgRR l] -> ShowS) -> Show (MsgRR l)
forall l. Show l => Int -> MsgRR l -> ShowS
forall l. Show l => [MsgRR l] -> ShowS
forall l. Show l => MsgRR l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MsgRR l] -> ShowS
$cshowList :: forall l. Show l => [MsgRR l] -> ShowS
show :: MsgRR l -> String
$cshow :: forall l. Show l => MsgRR l -> String
showsPrec :: Int -> MsgRR l -> ShowS
$cshowsPrec :: forall l. Show l => Int -> MsgRR l -> ShowS
Show,a -> MsgRR b -> MsgRR a
(a -> b) -> MsgRR a -> MsgRR b
(forall a b. (a -> b) -> MsgRR a -> MsgRR b)
-> (forall a b. a -> MsgRR b -> MsgRR a) -> Functor MsgRR
forall a b. a -> MsgRR b -> MsgRR a
forall a b. (a -> b) -> MsgRR a -> MsgRR b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> MsgRR b -> MsgRR a
$c<$ :: forall a b. a -> MsgRR b -> MsgRR a
fmap :: (a -> b) -> MsgRR a -> MsgRR b
$cfmap :: forall a b. (a -> b) -> MsgRR a -> MsgRR b
Functor,MsgRR a -> Bool
(a -> m) -> MsgRR a -> m
(a -> b -> b) -> b -> MsgRR a -> b
(forall m. Monoid m => MsgRR m -> m)
-> (forall m a. Monoid m => (a -> m) -> MsgRR a -> m)
-> (forall m a. Monoid m => (a -> m) -> MsgRR a -> m)
-> (forall a b. (a -> b -> b) -> b -> MsgRR a -> b)
-> (forall a b. (a -> b -> b) -> b -> MsgRR a -> b)
-> (forall b a. (b -> a -> b) -> b -> MsgRR a -> b)
-> (forall b a. (b -> a -> b) -> b -> MsgRR a -> b)
-> (forall a. (a -> a -> a) -> MsgRR a -> a)
-> (forall a. (a -> a -> a) -> MsgRR a -> a)
-> (forall a. MsgRR a -> [a])
-> (forall a. MsgRR a -> Bool)
-> (forall a. MsgRR a -> Int)
-> (forall a. Eq a => a -> MsgRR a -> Bool)
-> (forall a. Ord a => MsgRR a -> a)
-> (forall a. Ord a => MsgRR a -> a)
-> (forall a. Num a => MsgRR a -> a)
-> (forall a. Num a => MsgRR a -> a)
-> Foldable MsgRR
forall a. Eq a => a -> MsgRR a -> Bool
forall a. Num a => MsgRR a -> a
forall a. Ord a => MsgRR a -> a
forall m. Monoid m => MsgRR m -> m
forall a. MsgRR a -> Bool
forall a. MsgRR a -> Int
forall a. MsgRR a -> [a]
forall a. (a -> a -> a) -> MsgRR a -> a
forall m a. Monoid m => (a -> m) -> MsgRR a -> m
forall b a. (b -> a -> b) -> b -> MsgRR a -> b
forall a b. (a -> b -> b) -> b -> MsgRR a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: MsgRR a -> a
$cproduct :: forall a. Num a => MsgRR a -> a
sum :: MsgRR a -> a
$csum :: forall a. Num a => MsgRR a -> a
minimum :: MsgRR a -> a
$cminimum :: forall a. Ord a => MsgRR a -> a
maximum :: MsgRR a -> a
$cmaximum :: forall a. Ord a => MsgRR a -> a
elem :: a -> MsgRR a -> Bool
$celem :: forall a. Eq a => a -> MsgRR a -> Bool
length :: MsgRR a -> Int
$clength :: forall a. MsgRR a -> Int
null :: MsgRR a -> Bool
$cnull :: forall a. MsgRR a -> Bool
toList :: MsgRR a -> [a]
$ctoList :: forall a. MsgRR a -> [a]
foldl1 :: (a -> a -> a) -> MsgRR a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> MsgRR a -> a
foldr1 :: (a -> a -> a) -> MsgRR a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> MsgRR a -> a
foldl' :: (b -> a -> b) -> b -> MsgRR a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> MsgRR a -> b
foldl :: (b -> a -> b) -> b -> MsgRR a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> MsgRR a -> b
foldr' :: (a -> b -> b) -> b -> MsgRR a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> MsgRR a -> b
foldr :: (a -> b -> b) -> b -> MsgRR a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> MsgRR a -> b
foldMap' :: (a -> m) -> MsgRR a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> MsgRR a -> m
foldMap :: (a -> m) -> MsgRR a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> MsgRR a -> m
fold :: MsgRR m -> m
$cfold :: forall m. Monoid m => MsgRR m -> m
Foldable,Functor MsgRR
Foldable MsgRR
(Functor MsgRR, Foldable MsgRR) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> MsgRR a -> f (MsgRR b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    MsgRR (f a) -> f (MsgRR a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> MsgRR a -> m (MsgRR b))
-> (forall (m :: * -> *) a. Monad m => MsgRR (m a) -> m (MsgRR a))
-> Traversable MsgRR
(a -> f b) -> MsgRR a -> f (MsgRR b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => MsgRR (m a) -> m (MsgRR a)
forall (f :: * -> *) a. Applicative f => MsgRR (f a) -> f (MsgRR a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MsgRR a -> m (MsgRR b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MsgRR a -> f (MsgRR b)
sequence :: MsgRR (m a) -> m (MsgRR a)
$csequence :: forall (m :: * -> *) a. Monad m => MsgRR (m a) -> m (MsgRR a)
mapM :: (a -> m b) -> MsgRR a -> m (MsgRR b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MsgRR a -> m (MsgRR b)
sequenceA :: MsgRR (f a) -> f (MsgRR a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => MsgRR (f a) -> f (MsgRR a)
traverse :: (a -> f b) -> MsgRR a -> f (MsgRR b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MsgRR a -> f (MsgRR b)
$cp2Traversable :: Foldable MsgRR
$cp1Traversable :: Functor MsgRR
Traversable)

-- | DNS resource record data (see also 'MsgRR' and 'TypeSym')
data RData l
    = RDataA      !IPv4
    | RDataAAAA   !IPv6
    | RDataCNAME  !l
    | RDataPTR    !l
    | RDataHINFO  !CharStr !CharStr
    | RDataNS     !l
    | RDataMX     !Word16 !l
    | RDataTXT    ![CharStr]
    | RDataSPF    ![CharStr]
    | RDataSOA    !l !l !Word32 !Word32 !Word32 !Word32 !Word32
    | RDataSRV    !(SRV l)

    -- RFC 1183
    | RDataAFSDB  !Word16 !l

    -- RFC 2915
    | RDataNAPTR  !Word16 !Word16 !CharStr !CharStr !CharStr !l

    -- RFC 7553
    | RDataURI    !Word16 !Word16 !BS.ByteString

    -- RFC 4034
    | RDataRRSIG  !Word16 !Word8 !Word8 !Word32 !Word32 !Word32 !Word16 !l !BS.ByteString
    | RDataDNSKEY !Word16 !Word8 !Word8 !BS.ByteString
    | RDataDS     !Word16 !Word8 !Word8 !BS.ByteString
    | RDataNSEC   !l !(Set Type)

    -- RFC 4255
    | RDataSSHFP  !Word8 !Word8 !BS.ByteString

    -- RFC 5155
    | RDataNSEC3PARAM !Word8 !Word8 !Word16 !CharStr
    | RDataNSEC3      !Word8 !Word8 !Word16 !CharStr  !CharStr !(Set Type)

    -- RFC 6844
    | RDataCAA !Word8 !CharStr !BS.ByteString

    -- pseudo-record
    | RDataOPT !BS.ByteString -- FIXME

    -- unknown/unsupported
    | RData    !Type !BS.ByteString -- ^ Unknown/undecoded resource record type
    deriving (RData l -> RData l -> Bool
(RData l -> RData l -> Bool)
-> (RData l -> RData l -> Bool) -> Eq (RData l)
forall l. Eq l => RData l -> RData l -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RData l -> RData l -> Bool
$c/= :: forall l. Eq l => RData l -> RData l -> Bool
== :: RData l -> RData l -> Bool
$c== :: forall l. Eq l => RData l -> RData l -> Bool
Eq,ReadPrec [RData l]
ReadPrec (RData l)
Int -> ReadS (RData l)
ReadS [RData l]
(Int -> ReadS (RData l))
-> ReadS [RData l]
-> ReadPrec (RData l)
-> ReadPrec [RData l]
-> Read (RData l)
forall l. Read l => ReadPrec [RData l]
forall l. Read l => ReadPrec (RData l)
forall l. Read l => Int -> ReadS (RData l)
forall l. Read l => ReadS [RData l]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RData l]
$creadListPrec :: forall l. Read l => ReadPrec [RData l]
readPrec :: ReadPrec (RData l)
$creadPrec :: forall l. Read l => ReadPrec (RData l)
readList :: ReadS [RData l]
$creadList :: forall l. Read l => ReadS [RData l]
readsPrec :: Int -> ReadS (RData l)
$creadsPrec :: forall l. Read l => Int -> ReadS (RData l)
Read,Int -> RData l -> ShowS
[RData l] -> ShowS
RData l -> String
(Int -> RData l -> ShowS)
-> (RData l -> String) -> ([RData l] -> ShowS) -> Show (RData l)
forall l. Show l => Int -> RData l -> ShowS
forall l. Show l => [RData l] -> ShowS
forall l. Show l => RData l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RData l] -> ShowS
$cshowList :: forall l. Show l => [RData l] -> ShowS
show :: RData l -> String
$cshow :: forall l. Show l => RData l -> String
showsPrec :: Int -> RData l -> ShowS
$cshowsPrec :: forall l. Show l => Int -> RData l -> ShowS
Show,a -> RData b -> RData a
(a -> b) -> RData a -> RData b
(forall a b. (a -> b) -> RData a -> RData b)
-> (forall a b. a -> RData b -> RData a) -> Functor RData
forall a b. a -> RData b -> RData a
forall a b. (a -> b) -> RData a -> RData b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> RData b -> RData a
$c<$ :: forall a b. a -> RData b -> RData a
fmap :: (a -> b) -> RData a -> RData b
$cfmap :: forall a b. (a -> b) -> RData a -> RData b
Functor,RData a -> Bool
(a -> m) -> RData a -> m
(a -> b -> b) -> b -> RData a -> b
(forall m. Monoid m => RData m -> m)
-> (forall m a. Monoid m => (a -> m) -> RData a -> m)
-> (forall m a. Monoid m => (a -> m) -> RData a -> m)
-> (forall a b. (a -> b -> b) -> b -> RData a -> b)
-> (forall a b. (a -> b -> b) -> b -> RData a -> b)
-> (forall b a. (b -> a -> b) -> b -> RData a -> b)
-> (forall b a. (b -> a -> b) -> b -> RData a -> b)
-> (forall a. (a -> a -> a) -> RData a -> a)
-> (forall a. (a -> a -> a) -> RData a -> a)
-> (forall a. RData a -> [a])
-> (forall a. RData a -> Bool)
-> (forall a. RData a -> Int)
-> (forall a. Eq a => a -> RData a -> Bool)
-> (forall a. Ord a => RData a -> a)
-> (forall a. Ord a => RData a -> a)
-> (forall a. Num a => RData a -> a)
-> (forall a. Num a => RData a -> a)
-> Foldable RData
forall a. Eq a => a -> RData a -> Bool
forall a. Num a => RData a -> a
forall a. Ord a => RData a -> a
forall m. Monoid m => RData m -> m
forall a. RData a -> Bool
forall a. RData a -> Int
forall a. RData a -> [a]
forall a. (a -> a -> a) -> RData a -> a
forall m a. Monoid m => (a -> m) -> RData a -> m
forall b a. (b -> a -> b) -> b -> RData a -> b
forall a b. (a -> b -> b) -> b -> RData a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: RData a -> a
$cproduct :: forall a. Num a => RData a -> a
sum :: RData a -> a
$csum :: forall a. Num a => RData a -> a
minimum :: RData a -> a
$cminimum :: forall a. Ord a => RData a -> a
maximum :: RData a -> a
$cmaximum :: forall a. Ord a => RData a -> a
elem :: a -> RData a -> Bool
$celem :: forall a. Eq a => a -> RData a -> Bool
length :: RData a -> Int
$clength :: forall a. RData a -> Int
null :: RData a -> Bool
$cnull :: forall a. RData a -> Bool
toList :: RData a -> [a]
$ctoList :: forall a. RData a -> [a]
foldl1 :: (a -> a -> a) -> RData a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> RData a -> a
foldr1 :: (a -> a -> a) -> RData a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> RData a -> a
foldl' :: (b -> a -> b) -> b -> RData a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> RData a -> b
foldl :: (b -> a -> b) -> b -> RData a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> RData a -> b
foldr' :: (a -> b -> b) -> b -> RData a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> RData a -> b
foldr :: (a -> b -> b) -> b -> RData a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> RData a -> b
foldMap' :: (a -> m) -> RData a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> RData a -> m
foldMap :: (a -> m) -> RData a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> RData a -> m
fold :: RData m -> m
$cfold :: forall m. Monoid m => RData m -> m
Foldable,Functor RData
Foldable RData
(Functor RData, Foldable RData) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> RData a -> f (RData b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    RData (f a) -> f (RData a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> RData a -> m (RData b))
-> (forall (m :: * -> *) a. Monad m => RData (m a) -> m (RData a))
-> Traversable RData
(a -> f b) -> RData a -> f (RData b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => RData (m a) -> m (RData a)
forall (f :: * -> *) a. Applicative f => RData (f a) -> f (RData a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> RData a -> m (RData b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> RData a -> f (RData b)
sequence :: RData (m a) -> m (RData a)
$csequence :: forall (m :: * -> *) a. Monad m => RData (m a) -> m (RData a)
mapM :: (a -> m b) -> RData a -> m (RData b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> RData a -> m (RData b)
sequenceA :: RData (f a) -> f (RData a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => RData (f a) -> f (RData a)
traverse :: (a -> f b) -> RData a -> f (RData b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> RData a -> f (RData b)
$cp2Traversable :: Foldable RData
$cp1Traversable :: Functor RData
Traversable)


-- | @SRV@ Record data as per [RFC 2782](https://tools.ietf.org/html/rfc2782)
data SRV l = SRV { SRV l -> Word16
srvPriority :: !Word16
                 , SRV l -> Word16
srvWeight   :: !Word16
                 , SRV l -> Word16
srvPort     :: !Word16
                 , SRV l -> l
srvTarget   :: !l
                 } deriving (SRV l -> SRV l -> Bool
(SRV l -> SRV l -> Bool) -> (SRV l -> SRV l -> Bool) -> Eq (SRV l)
forall l. Eq l => SRV l -> SRV l -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SRV l -> SRV l -> Bool
$c/= :: forall l. Eq l => SRV l -> SRV l -> Bool
== :: SRV l -> SRV l -> Bool
$c== :: forall l. Eq l => SRV l -> SRV l -> Bool
Eq,ReadPrec [SRV l]
ReadPrec (SRV l)
Int -> ReadS (SRV l)
ReadS [SRV l]
(Int -> ReadS (SRV l))
-> ReadS [SRV l]
-> ReadPrec (SRV l)
-> ReadPrec [SRV l]
-> Read (SRV l)
forall l. Read l => ReadPrec [SRV l]
forall l. Read l => ReadPrec (SRV l)
forall l. Read l => Int -> ReadS (SRV l)
forall l. Read l => ReadS [SRV l]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SRV l]
$creadListPrec :: forall l. Read l => ReadPrec [SRV l]
readPrec :: ReadPrec (SRV l)
$creadPrec :: forall l. Read l => ReadPrec (SRV l)
readList :: ReadS [SRV l]
$creadList :: forall l. Read l => ReadS [SRV l]
readsPrec :: Int -> ReadS (SRV l)
$creadsPrec :: forall l. Read l => Int -> ReadS (SRV l)
Read,Int -> SRV l -> ShowS
[SRV l] -> ShowS
SRV l -> String
(Int -> SRV l -> ShowS)
-> (SRV l -> String) -> ([SRV l] -> ShowS) -> Show (SRV l)
forall l. Show l => Int -> SRV l -> ShowS
forall l. Show l => [SRV l] -> ShowS
forall l. Show l => SRV l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SRV l] -> ShowS
$cshowList :: forall l. Show l => [SRV l] -> ShowS
show :: SRV l -> String
$cshow :: forall l. Show l => SRV l -> String
showsPrec :: Int -> SRV l -> ShowS
$cshowsPrec :: forall l. Show l => Int -> SRV l -> ShowS
Show,a -> SRV b -> SRV a
(a -> b) -> SRV a -> SRV b
(forall a b. (a -> b) -> SRV a -> SRV b)
-> (forall a b. a -> SRV b -> SRV a) -> Functor SRV
forall a b. a -> SRV b -> SRV a
forall a b. (a -> b) -> SRV a -> SRV b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> SRV b -> SRV a
$c<$ :: forall a b. a -> SRV b -> SRV a
fmap :: (a -> b) -> SRV a -> SRV b
$cfmap :: forall a b. (a -> b) -> SRV a -> SRV b
Functor,SRV a -> Bool
(a -> m) -> SRV a -> m
(a -> b -> b) -> b -> SRV a -> b
(forall m. Monoid m => SRV m -> m)
-> (forall m a. Monoid m => (a -> m) -> SRV a -> m)
-> (forall m a. Monoid m => (a -> m) -> SRV a -> m)
-> (forall a b. (a -> b -> b) -> b -> SRV a -> b)
-> (forall a b. (a -> b -> b) -> b -> SRV a -> b)
-> (forall b a. (b -> a -> b) -> b -> SRV a -> b)
-> (forall b a. (b -> a -> b) -> b -> SRV a -> b)
-> (forall a. (a -> a -> a) -> SRV a -> a)
-> (forall a. (a -> a -> a) -> SRV a -> a)
-> (forall a. SRV a -> [a])
-> (forall a. SRV a -> Bool)
-> (forall a. SRV a -> Int)
-> (forall a. Eq a => a -> SRV a -> Bool)
-> (forall a. Ord a => SRV a -> a)
-> (forall a. Ord a => SRV a -> a)
-> (forall a. Num a => SRV a -> a)
-> (forall a. Num a => SRV a -> a)
-> Foldable SRV
forall a. Eq a => a -> SRV a -> Bool
forall a. Num a => SRV a -> a
forall a. Ord a => SRV a -> a
forall m. Monoid m => SRV m -> m
forall a. SRV a -> Bool
forall a. SRV a -> Int
forall a. SRV a -> [a]
forall a. (a -> a -> a) -> SRV a -> a
forall m a. Monoid m => (a -> m) -> SRV a -> m
forall b a. (b -> a -> b) -> b -> SRV a -> b
forall a b. (a -> b -> b) -> b -> SRV a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: SRV a -> a
$cproduct :: forall a. Num a => SRV a -> a
sum :: SRV a -> a
$csum :: forall a. Num a => SRV a -> a
minimum :: SRV a -> a
$cminimum :: forall a. Ord a => SRV a -> a
maximum :: SRV a -> a
$cmaximum :: forall a. Ord a => SRV a -> a
elem :: a -> SRV a -> Bool
$celem :: forall a. Eq a => a -> SRV a -> Bool
length :: SRV a -> Int
$clength :: forall a. SRV a -> Int
null :: SRV a -> Bool
$cnull :: forall a. SRV a -> Bool
toList :: SRV a -> [a]
$ctoList :: forall a. SRV a -> [a]
foldl1 :: (a -> a -> a) -> SRV a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> SRV a -> a
foldr1 :: (a -> a -> a) -> SRV a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> SRV a -> a
foldl' :: (b -> a -> b) -> b -> SRV a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> SRV a -> b
foldl :: (b -> a -> b) -> b -> SRV a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> SRV a -> b
foldr' :: (a -> b -> b) -> b -> SRV a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> SRV a -> b
foldr :: (a -> b -> b) -> b -> SRV a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> SRV a -> b
foldMap' :: (a -> m) -> SRV a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> SRV a -> m
foldMap :: (a -> m) -> SRV a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> SRV a -> m
fold :: SRV m -> m
$cfold :: forall m. Monoid m => SRV m -> m
Foldable,Functor SRV
Foldable SRV
(Functor SRV, Foldable SRV) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> SRV a -> f (SRV b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    SRV (f a) -> f (SRV a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> SRV a -> m (SRV b))
-> (forall (m :: * -> *) a. Monad m => SRV (m a) -> m (SRV a))
-> Traversable SRV
(a -> f b) -> SRV a -> f (SRV b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
 Applicative f =>
 (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => SRV (m a) -> m (SRV a)
forall (f :: * -> *) a. Applicative f => SRV (f a) -> f (SRV a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SRV a -> m (SRV b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SRV a -> f (SRV b)
sequence :: SRV (m a) -> m (SRV a)
$csequence :: forall (m :: * -> *) a. Monad m => SRV (m a) -> m (SRV a)
mapM :: (a -> m b) -> SRV a -> m (SRV b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SRV a -> m (SRV b)
sequenceA :: SRV (f a) -> f (SRV a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => SRV (f a) -> f (SRV a)
traverse :: (a -> f b) -> SRV a -> f (SRV b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> SRV a -> f (SRV b)
$cp2Traversable :: Foldable SRV
$cp1Traversable :: Functor SRV
Traversable)

----------------------------------------------------------------------------

decodeMessage' :: BS.ByteString -> Maybe (Msg Labels)
decodeMessage' :: ByteString -> Maybe (Msg Labels)
decodeMessage' bs :: ByteString
bs = do
    (rest :: ByteString
rest, _, v :: Msg LabelsPtr
v) <- ((ByteString, ByteOffset, String)
 -> Maybe (ByteString, ByteOffset, Msg LabelsPtr))
-> ((ByteString, ByteOffset, Msg LabelsPtr)
    -> Maybe (ByteString, ByteOffset, Msg LabelsPtr))
-> Either
     (ByteString, ByteOffset, String)
     (ByteString, ByteOffset, Msg LabelsPtr)
-> Maybe (ByteString, ByteOffset, Msg LabelsPtr)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (ByteString, ByteOffset, String)
-> Maybe (ByteString, ByteOffset, Msg LabelsPtr)
forall a b a. (Show a, Show b) => (ByteString, b, a) -> a
handleParseFail (ByteString, ByteOffset, Msg LabelsPtr)
-> Maybe (ByteString, ByteOffset, Msg LabelsPtr)
forall a. a -> Maybe a
Just (Either
   (ByteString, ByteOffset, String)
   (ByteString, ByteOffset, Msg LabelsPtr)
 -> Maybe (ByteString, ByteOffset, Msg LabelsPtr))
-> Either
     (ByteString, ByteOffset, String)
     (ByteString, ByteOffset, Msg LabelsPtr)
-> Maybe (ByteString, ByteOffset, Msg LabelsPtr)
forall a b. (a -> b) -> a -> b
$
                    ByteString
-> Either
     (ByteString, ByteOffset, String)
     (ByteString, ByteOffset, Msg LabelsPtr)
forall a.
Binary a =>
ByteString
-> Either
     (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
decodeOrFail (ByteString -> ByteString
fromStrict ByteString
bs)

    -- don't allow trailing garbage
    Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (ByteString -> Bool
BSL.null ByteString
rest)

    let ofss :: Set Word16
ofss = [Word16] -> Set Word16
forall a. Ord a => [a] -> Set a
Set.fromList ([Word16] -> Set Word16) -> [Word16] -> Set Word16
forall a b. (a -> b) -> a -> b
$ (LabelsPtr -> Maybe Word16) -> [LabelsPtr] -> [Word16]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe LabelsPtr -> Maybe Word16
labelsPtr (Msg LabelsPtr -> [LabelsPtr]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Msg LabelsPtr
v)
    Map Word16 LabelsPtr
ofsmap <- ByteString -> Set Word16 -> Maybe (Map Word16 LabelsPtr)
retrieveLabelPtrs ByteString
bs Set Word16
ofss

    (LabelsPtr -> Maybe Labels) -> Msg LabelsPtr -> Maybe (Msg Labels)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Map Word16 LabelsPtr -> LabelsPtr -> Maybe Labels
resolveLabelPtr Map Word16 LabelsPtr
ofsmap) Msg LabelsPtr
v
  where
    -- handleParseFail _ = Nothing
    handleParseFail :: (ByteString, b, a) -> a
handleParseFail (rest :: ByteString
rest, n :: b
n, e :: a
e) = String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ (a, b, ByteOffset, Int) -> String
forall a. Show a => a -> String
show (a
e, b
n, ByteString -> ByteOffset
BSL.length ByteString
rest, ByteString -> Int
BS.length ByteString
bs) String -> ShowS
forall a. [a] -> [a] -> [a]
++ "\n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ByteString -> String
forall a. Show a => a -> String
show (ByteString -> ByteString
B16.encode (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
toStrict ByteString
rest)

-- | Decode a raw DNS message (query or response)
--
-- Returns 'Nothing' on decoding failures.
decodeMessage :: IsLabels n => BS.ByteString -> Maybe (Msg n)
decodeMessage :: ByteString -> Maybe (Msg n)
decodeMessage = (Msg Labels -> Msg n) -> Maybe (Msg Labels) -> Maybe (Msg n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Labels -> n) -> Msg Labels -> Msg n
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Labels -> n
forall s. IsLabels s => Labels -> s
fromLabels) (Maybe (Msg Labels) -> Maybe (Msg n))
-> (ByteString -> Maybe (Msg Labels))
-> ByteString
-> Maybe (Msg n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (Msg Labels)
decodeMessage'

encodeMessage' :: Msg Labels -> BS.ByteString
encodeMessage' :: Msg Labels -> ByteString
encodeMessage' m :: Msg Labels
m = ByteString -> ByteString
toStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Msg LabelsPtr -> ByteString
forall a. Binary a => a -> ByteString
encode ((Labels -> LabelsPtr) -> Msg Labels -> Msg LabelsPtr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Labels -> LabelsPtr
labels2labelsPtr Msg Labels
m)

-- | Construct a raw DNS message (query or response)
--
-- May return 'Nothing' in input parameters are detected to be invalid.
encodeMessage :: IsLabels n => Msg n -> Maybe BS.ByteString
encodeMessage :: Msg n -> Maybe ByteString
encodeMessage m :: Msg n
m = Msg Labels -> ByteString
encodeMessage' (Msg Labels -> ByteString)
-> Maybe (Msg Labels) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (n -> Maybe Labels) -> Msg n -> Maybe (Msg Labels)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse n -> Maybe Labels
forall s. IsLabels s => s -> Maybe Labels
toLabels Msg n
m


instance Binary l => Binary (Msg l) where
    get :: Get (Msg l)
get = do
        hdr :: MsgHeader
hdr@MsgHeader{..} <- Get MsgHeader
forall t. Binary t => Get t
get

        MsgHeader
-> [MsgQuestion l] -> [MsgRR l] -> [MsgRR l] -> [MsgRR l] -> Msg l
forall l.
MsgHeader
-> [MsgQuestion l] -> [MsgRR l] -> [MsgRR l] -> [MsgRR l] -> Msg l
Msg MsgHeader
hdr ([MsgQuestion l] -> [MsgRR l] -> [MsgRR l] -> [MsgRR l] -> Msg l)
-> Get [MsgQuestion l]
-> Get ([MsgRR l] -> [MsgRR l] -> [MsgRR l] -> Msg l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get (MsgQuestion l) -> Get [MsgQuestion l]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
mhQDCount) Get (MsgQuestion l)
forall t. Binary t => Get t
get
                Get ([MsgRR l] -> [MsgRR l] -> [MsgRR l] -> Msg l)
-> Get [MsgRR l] -> Get ([MsgRR l] -> [MsgRR l] -> Msg l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get (MsgRR l) -> Get [MsgRR l]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
mhANCount) Get (MsgRR l)
forall t. Binary t => Get t
get
                Get ([MsgRR l] -> [MsgRR l] -> Msg l)
-> Get [MsgRR l] -> Get ([MsgRR l] -> Msg l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get (MsgRR l) -> Get [MsgRR l]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
mhNSCount) Get (MsgRR l)
forall t. Binary t => Get t
get
                Get ([MsgRR l] -> Msg l) -> Get [MsgRR l] -> Get (Msg l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get (MsgRR l) -> Get [MsgRR l]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
mhARCount) Get (MsgRR l)
forall t. Binary t => Get t
get

    put :: Msg l -> Put
put (Msg hdr :: MsgHeader
hdr qds :: [MsgQuestion l]
qds ans :: [MsgRR l]
ans nss :: [MsgRR l]
nss ars :: [MsgRR l]
ars) = do
        MsgHeader -> Put
forall t. Binary t => t -> Put
put MsgHeader
hdr
        (MsgQuestion l -> Put) -> [MsgQuestion l] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ MsgQuestion l -> Put
forall t. Binary t => t -> Put
put [MsgQuestion l]
qds
        (MsgRR l -> Put) -> [MsgRR l] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ MsgRR l -> Put
forall t. Binary t => t -> Put
put [MsgRR l]
ans
        (MsgRR l -> Put) -> [MsgRR l] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ MsgRR l -> Put
forall t. Binary t => t -> Put
put [MsgRR l]
nss
        (MsgRR l -> Put) -> [MsgRR l] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ MsgRR l -> Put
forall t. Binary t => t -> Put
put [MsgRR l]
ars

instance Binary MsgHeader where
    get :: Get MsgHeader
get = Word16
-> MsgHeaderFlags
-> Word16
-> Word16
-> Word16
-> Word16
-> MsgHeader
MsgHeader (Word16
 -> MsgHeaderFlags
 -> Word16
 -> Word16
 -> Word16
 -> Word16
 -> MsgHeader)
-> Get Word16
-> Get
     (MsgHeaderFlags
      -> Word16 -> Word16 -> Word16 -> Word16 -> MsgHeader)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
                    Get
  (MsgHeaderFlags
   -> Word16 -> Word16 -> Word16 -> Word16 -> MsgHeader)
-> Get MsgHeaderFlags
-> Get (Word16 -> Word16 -> Word16 -> Word16 -> MsgHeader)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get MsgHeaderFlags
forall t. Binary t => Get t
get
                    Get (Word16 -> Word16 -> Word16 -> Word16 -> MsgHeader)
-> Get Word16 -> Get (Word16 -> Word16 -> Word16 -> MsgHeader)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be
                    Get (Word16 -> Word16 -> Word16 -> MsgHeader)
-> Get Word16 -> Get (Word16 -> Word16 -> MsgHeader)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be
                    Get (Word16 -> Word16 -> MsgHeader)
-> Get Word16 -> Get (Word16 -> MsgHeader)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be
                    Get (Word16 -> MsgHeader) -> Get Word16 -> Get MsgHeader
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be

    put :: MsgHeader -> Put
put (MsgHeader{..}) = do
        Word16 -> Put
putWord16be Word16
mhId
        MsgHeaderFlags -> Put
forall t. Binary t => t -> Put
put MsgHeaderFlags
mhFlags
        Word16 -> Put
putWord16be Word16
mhQDCount
        Word16 -> Put
putWord16be Word16
mhANCount
        Word16 -> Put
putWord16be Word16
mhNSCount
        Word16 -> Put
putWord16be Word16
mhARCount

instance Binary MsgHeaderFlags where
    put :: MsgHeaderFlags -> Put
put = Word16 -> Put
putWord16be (Word16 -> Put)
-> (MsgHeaderFlags -> Word16) -> MsgHeaderFlags -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MsgHeaderFlags -> Word16
encodeFlags
    get :: Get MsgHeaderFlags
get = Word16 -> MsgHeaderFlags
decodeFlags (Word16 -> MsgHeaderFlags) -> Get Word16 -> Get MsgHeaderFlags
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be

-- | Decode message header flag field
--
-- >  +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+
-- >  |QR|   Opcode  |AA|TC|RD|RA|??|AD|CD|   RCODE   |
-- >  +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+
--
decodeFlags :: Word16 -> MsgHeaderFlags
decodeFlags :: Word16 -> MsgHeaderFlags
decodeFlags w :: Word16
w = $WMsgHeaderFlags :: QR
-> Word8
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Word8
-> MsgHeaderFlags
MsgHeaderFlags{..}
  where
    mhQR :: QR
mhQR      = if Word16 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word16
w 15 then QR
IsResponse else QR
IsQuery
    mhOpcode :: Word8
mhOpcode  = Int -> Word8
shiftR'   11 Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. 0xf
    mhAA :: Bool
mhAA      = Word16 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word16
w 10
    mhTC :: Bool
mhTC      = Word16 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word16
w  9
    mhRD :: Bool
mhRD      = Word16 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word16
w  8
    mhRA :: Bool
mhRA      = Word16 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word16
w  7
    mhZ :: Bool
mhZ       = Word16 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word16
w  6
    mhAD :: Bool
mhAD      = Word16 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word16
w  5
    mhCD :: Bool
mhCD      = Word16 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word16
w  4
    mhRCode :: Word8
mhRCode   = Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
w Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. 0xf

    shiftR' :: Int -> Word8
shiftR' = Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Word8) -> (Int -> Word16) -> Int -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
shiftR Word16
w

encodeFlags :: MsgHeaderFlags -> Word16
encodeFlags :: MsgHeaderFlags -> Word16
encodeFlags MsgHeaderFlags{..} =
    (case QR
mhQR of
        IsResponse -> Int -> Word16
forall a. Bits a => Int -> a
bit 15
        IsQuery    -> 0) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|.
    (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
mhOpcode Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
`shiftL` 11) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|.
    (if Bool
mhAA then Int -> Word16
forall a. Bits a => Int -> a
bit 10 else 0) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|.
    (if Bool
mhTC then Int -> Word16
forall a. Bits a => Int -> a
bit  9 else 0) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|.
    (if Bool
mhRD then Int -> Word16
forall a. Bits a => Int -> a
bit  8 else 0) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|.
    (if Bool
mhRA then Int -> Word16
forall a. Bits a => Int -> a
bit  7 else 0) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|.
    (if Bool
mhZ  then Int -> Word16
forall a. Bits a => Int -> a
bit  6 else 0) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|.
    (if Bool
mhAD then Int -> Word16
forall a. Bits a => Int -> a
bit  5 else 0) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|.
    (if Bool
mhCD then Int -> Word16
forall a. Bits a => Int -> a
bit  4 else 0) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|.
    (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
mhRCode)

-- | Encodes whether message is a query or a response
--
-- @since 0.1.1.0
data QR = IsQuery | IsResponse
        deriving (QR -> QR -> Bool
(QR -> QR -> Bool) -> (QR -> QR -> Bool) -> Eq QR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QR -> QR -> Bool
$c/= :: QR -> QR -> Bool
== :: QR -> QR -> Bool
$c== :: QR -> QR -> Bool
Eq,ReadPrec [QR]
ReadPrec QR
Int -> ReadS QR
ReadS [QR]
(Int -> ReadS QR)
-> ReadS [QR] -> ReadPrec QR -> ReadPrec [QR] -> Read QR
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [QR]
$creadListPrec :: ReadPrec [QR]
readPrec :: ReadPrec QR
$creadPrec :: ReadPrec QR
readList :: ReadS [QR]
$creadList :: ReadS [QR]
readsPrec :: Int -> ReadS QR
$creadsPrec :: Int -> ReadS QR
Read,Int -> QR -> ShowS
[QR] -> ShowS
QR -> String
(Int -> QR -> ShowS)
-> (QR -> String) -> ([QR] -> ShowS) -> Show QR
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QR] -> ShowS
$cshowList :: [QR] -> ShowS
show :: QR -> String
$cshow :: QR -> String
showsPrec :: Int -> QR -> ShowS
$cshowsPrec :: Int -> QR -> ShowS
Show)

----------------------------------------------------------------------------

infixr 5 :.:

-- | A DNS Label
--
-- Must be non-empty and at most 63 octets.
type Label = BS.ByteString

-- | A @<domain-name>@ as per [RFC 1035, section 3.3](https://tools.ietf.org/html/rfc1035#section-3.3) expressed as list of 'Label's.
--
-- See also 'Name'
data Labels = !Label :.: !Labels | Root
            deriving (ReadPrec [Labels]
ReadPrec Labels
Int -> ReadS Labels
ReadS [Labels]
(Int -> ReadS Labels)
-> ReadS [Labels]
-> ReadPrec Labels
-> ReadPrec [Labels]
-> Read Labels
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Labels]
$creadListPrec :: ReadPrec [Labels]
readPrec :: ReadPrec Labels
$creadPrec :: ReadPrec Labels
readList :: ReadS [Labels]
$creadList :: ReadS [Labels]
readsPrec :: Int -> ReadS Labels
$creadsPrec :: Int -> ReadS Labels
Read,Int -> Labels -> ShowS
[Labels] -> ShowS
Labels -> String
(Int -> Labels -> ShowS)
-> (Labels -> String) -> ([Labels] -> ShowS) -> Show Labels
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Labels] -> ShowS
$cshowList :: [Labels] -> ShowS
show :: Labels -> String
$cshow :: Labels -> String
showsPrec :: Int -> Labels -> ShowS
$cshowsPrec :: Int -> Labels -> ShowS
Show,Labels -> Labels -> Bool
(Labels -> Labels -> Bool)
-> (Labels -> Labels -> Bool) -> Eq Labels
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Labels -> Labels -> Bool
$c/= :: Labels -> Labels -> Bool
== :: Labels -> Labels -> Bool
$c== :: Labels -> Labels -> Bool
Eq,Eq Labels
Eq Labels =>
(Labels -> Labels -> Ordering)
-> (Labels -> Labels -> Bool)
-> (Labels -> Labels -> Bool)
-> (Labels -> Labels -> Bool)
-> (Labels -> Labels -> Bool)
-> (Labels -> Labels -> Labels)
-> (Labels -> Labels -> Labels)
-> Ord Labels
Labels -> Labels -> Bool
Labels -> Labels -> Ordering
Labels -> Labels -> Labels
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Labels -> Labels -> Labels
$cmin :: Labels -> Labels -> Labels
max :: Labels -> Labels -> Labels
$cmax :: Labels -> Labels -> Labels
>= :: Labels -> Labels -> Bool
$c>= :: Labels -> Labels -> Bool
> :: Labels -> Labels -> Bool
$c> :: Labels -> Labels -> Bool
<= :: Labels -> Labels -> Bool
$c<= :: Labels -> Labels -> Bool
< :: Labels -> Labels -> Bool
$c< :: Labels -> Labels -> Bool
compare :: Labels -> Labels -> Ordering
$ccompare :: Labels -> Labels -> Ordering
$cp1Ord :: Eq Labels
Ord)

labelsToList :: Labels -> [Label]
labelsToList :: Labels -> [ByteString]
labelsToList (x :: ByteString
x :.: xs :: Labels
xs) = ByteString
x ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: Labels -> [ByteString]
labelsToList Labels
xs
labelsToList Root       = [""]

-- | Types that represent @<domain-name>@ as per [RFC 1035, section 3.3](https://tools.ietf.org/html/rfc1035#section-3.3) and can be converted to and from 'Labels'.
class IsLabels s where
  toLabels   :: s -> Maybe Labels
  fromLabels :: Labels -> s

instance IsLabels Labels where
  fromLabels :: Labels -> Labels
fromLabels = Labels -> Labels
forall a. a -> a
id

  toLabels :: Labels -> Maybe Labels
toLabels ls :: Labels
ls
    | (ByteString -> Bool) -> [ByteString] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ByteString -> Bool
isLabelValid ([ByteString] -> [ByteString]
forall a. [a] -> [a]
init (Labels -> [ByteString]
labelsToList Labels
ls)) = Labels -> Maybe Labels
forall a. a -> Maybe a
Just Labels
ls
    | Bool
otherwise = Maybe Labels
forall a. Maybe a
Nothing
    where
      isLabelValid :: ByteString -> Bool
isLabelValid l :: ByteString
l = Bool -> Bool
not (ByteString -> Bool
BS.null ByteString
l) Bool -> Bool -> Bool
&& ByteString -> Int
BS.length ByteString
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0x40

instance IsLabels Name where
  fromLabels :: Labels -> Name
fromLabels = Labels -> Name
labels2name
  toLabels :: Name -> Maybe Labels
toLabels   = Name -> Maybe Labels
name2labels

toName :: IsLabels n => n -> Maybe Name
toName :: n -> Maybe Name
toName = (Labels -> Name) -> Maybe Labels -> Maybe Name
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Labels -> Name
forall s. IsLabels s => Labels -> s
fromLabels (Maybe Labels -> Maybe Name)
-> (n -> Maybe Labels) -> n -> Maybe Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. n -> Maybe Labels
forall s. IsLabels s => s -> Maybe Labels
toLabels

name2labels :: Name -> Maybe Labels
name2labels :: Name -> Maybe Labels
name2labels (Name n :: ByteString
n)
  | (ByteString -> Bool) -> [ByteString] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\l :: ByteString
l -> Bool -> Bool
not (ByteString -> Bool
BS.null ByteString
l) Bool -> Bool -> Bool
&& ByteString -> Int
BS.length ByteString
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0x40) [ByteString]
n' = Labels -> Maybe Labels
forall a. a -> Maybe a
Just (Labels -> Maybe Labels) -> Labels -> Maybe Labels
forall a b. (a -> b) -> a -> b
$! (ByteString -> Labels -> Labels)
-> Labels -> [ByteString] -> Labels
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ByteString -> Labels -> Labels
(:.:) Labels
Root [ByteString]
n'
  | Bool
otherwise = Maybe Labels
forall a. Maybe a
Nothing
  where
    n' :: [ByteString]
n' | ByteString -> ByteString -> Bool
BS.isSuffixOf "." ByteString
n = Word8 -> ByteString -> [ByteString]
BS.split 0x2e (ByteString -> ByteString
BS.init ByteString
n)
       | Bool
otherwise           = Word8 -> ByteString -> [ByteString]
BS.split 0x2e ByteString
n

labels2name :: Labels -> Name
labels2name :: Labels -> Name
labels2name Root = ByteString -> Name
Name "."
labels2name ls :: Labels
ls   = ByteString -> Name
Name (ByteString -> [ByteString] -> ByteString
BS.intercalate "." ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$ Labels -> [ByteString]
labelsToList Labels
ls)

-- | IOW, a domain-name
--
-- May contain pointers
--
-- Can be resolved into a 'Labels' without label ptrs.
data LabelsPtr = Label !Label !LabelsPtr -- ^ See RC2181: a label must be between 1-63 octets; can be arbitrary binary data
               | LPtr  !Word16
               | LNul
               deriving (LabelsPtr -> LabelsPtr -> Bool
(LabelsPtr -> LabelsPtr -> Bool)
-> (LabelsPtr -> LabelsPtr -> Bool) -> Eq LabelsPtr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LabelsPtr -> LabelsPtr -> Bool
$c/= :: LabelsPtr -> LabelsPtr -> Bool
== :: LabelsPtr -> LabelsPtr -> Bool
$c== :: LabelsPtr -> LabelsPtr -> Bool
Eq,ReadPrec [LabelsPtr]
ReadPrec LabelsPtr
Int -> ReadS LabelsPtr
ReadS [LabelsPtr]
(Int -> ReadS LabelsPtr)
-> ReadS [LabelsPtr]
-> ReadPrec LabelsPtr
-> ReadPrec [LabelsPtr]
-> Read LabelsPtr
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LabelsPtr]
$creadListPrec :: ReadPrec [LabelsPtr]
readPrec :: ReadPrec LabelsPtr
$creadPrec :: ReadPrec LabelsPtr
readList :: ReadS [LabelsPtr]
$creadList :: ReadS [LabelsPtr]
readsPrec :: Int -> ReadS LabelsPtr
$creadsPrec :: Int -> ReadS LabelsPtr
Read,Int -> LabelsPtr -> ShowS
[LabelsPtr] -> ShowS
LabelsPtr -> String
(Int -> LabelsPtr -> ShowS)
-> (LabelsPtr -> String)
-> ([LabelsPtr] -> ShowS)
-> Show LabelsPtr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LabelsPtr] -> ShowS
$cshowList :: [LabelsPtr] -> ShowS
show :: LabelsPtr -> String
$cshow :: LabelsPtr -> String
showsPrec :: Int -> LabelsPtr -> ShowS
$cshowsPrec :: Int -> LabelsPtr -> ShowS
Show)

labels2labelsPtr :: Labels -> LabelsPtr
labels2labelsPtr :: Labels -> LabelsPtr
labels2labelsPtr Root         = LabelsPtr
LNul
labels2labelsPtr (l :: ByteString
l :.: rest :: Labels
rest) = ByteString -> LabelsPtr -> LabelsPtr
Label ByteString
l (Labels -> LabelsPtr
labels2labelsPtr Labels
rest)

instance Binary LabelsPtr where
    get :: Get LabelsPtr
get = [ByteString] -> Get LabelsPtr
go []
      where
        go :: [ByteString] -> Get LabelsPtr
go acc :: [ByteString]
acc = do
            Either Word16 ByteString
l0 <- Get (Either Word16 ByteString)
getLabel
            case Either Word16 ByteString
l0 of
              Right bs :: ByteString
bs | ByteString -> Bool
BS.null ByteString
bs -> LabelsPtr -> Get LabelsPtr
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ByteString -> LabelsPtr -> LabelsPtr)
-> LabelsPtr -> [ByteString] -> LabelsPtr
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ByteString -> LabelsPtr -> LabelsPtr
Label LabelsPtr
LNul ([ByteString] -> LabelsPtr) -> [ByteString] -> LabelsPtr
forall a b. (a -> b) -> a -> b
$ [ByteString] -> [ByteString]
forall a. [a] -> [a]
reverse [ByteString]
acc)
                       | Bool
otherwise  -> [ByteString] -> Get LabelsPtr
go (ByteString
bsByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[ByteString]
acc)
              Left ofs :: Word16
ofs              -> LabelsPtr -> Get LabelsPtr
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ByteString -> LabelsPtr -> LabelsPtr)
-> LabelsPtr -> [ByteString] -> LabelsPtr
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ByteString -> LabelsPtr -> LabelsPtr
Label (Word16 -> LabelsPtr
LPtr Word16
ofs) ([ByteString] -> LabelsPtr) -> [ByteString] -> LabelsPtr
forall a b. (a -> b) -> a -> b
$ [ByteString] -> [ByteString]
forall a. [a] -> [a]
reverse [ByteString]
acc)

        getLabel :: Get (Either Word16 BS.ByteString)
        getLabel :: Get (Either Word16 ByteString)
getLabel = do
            Word8
len <- Get Word8
getWord8

            if Word8
len Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= 0x40
             then do
                Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Word8
len Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. 0xc0 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= 0xc0) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$ String -> Get ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail ("invalid length octet " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word8 -> String
forall a. Show a => a -> String
show Word8
len)
                Word16
ofs <- Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word16) -> Get Word8 -> Get Word16
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
                Either Word16 ByteString -> Get (Either Word16 ByteString)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either Word16 ByteString -> Get (Either Word16 ByteString))
-> Either Word16 ByteString -> Get (Either Word16 ByteString)
forall a b. (a -> b) -> a -> b
$ Word16 -> Either Word16 ByteString
forall a b. a -> Either a b
Left (Word16 -> Either Word16 ByteString)
-> Word16 -> Either Word16 ByteString
forall a b. (a -> b) -> a -> b
$ (Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
len Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. 0x3f) Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
`shiftL` 8) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|. Word16
ofs
             else ByteString -> Either Word16 ByteString
forall a b. b -> Either a b
Right (ByteString -> Either Word16 ByteString)
-> Get ByteString -> Get (Either Word16 ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
len)

    put :: LabelsPtr -> Put
put LNul = Word8 -> Put
putWord8 0
    put (Label l :: ByteString
l next :: LabelsPtr
next)
      | ByteString -> Int
BS.length ByteString
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 1 Bool -> Bool -> Bool
|| ByteString -> Int
BS.length ByteString
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 0x40 = String -> Put
forall a. HasCallStack => String -> a
error "put (Label {}): invalid label size"
      | Bool
otherwise = do
            Word8 -> Put
putWord8 (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
BS.length ByteString
l))
            ByteString -> Put
putByteString ByteString
l
            LabelsPtr -> Put
forall t. Binary t => t -> Put
put LabelsPtr
next
    put (LPtr ofs :: Word16
ofs)
      | Word16
ofs Word16 -> Word16 -> Bool
forall a. Ord a => a -> a -> Bool
< 0x4000 = Word16 -> Put
putWord16be (0xc000 Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|. Word16
ofs)
      | Bool
otherwise  = String -> Put
forall a. HasCallStack => String -> a
error "put (LPtr {}): invalid offset"

-- | Compute serialised size of 'LabelsPtr'
labelsSize :: LabelsPtr -> Word16
labelsSize :: LabelsPtr -> Word16
labelsSize = Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word16) -> (LabelsPtr -> Int) -> LabelsPtr -> Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> LabelsPtr -> Int
go 0
  where
    go :: Int -> LabelsPtr -> Int
go n :: Int
n (LPtr _)        = Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+2
    go n :: Int
n  LNul           = Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+1
    go n :: Int
n (Label bs :: ByteString
bs rest :: LabelsPtr
rest) = Int -> LabelsPtr -> Int
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
BS.length ByteString
bs) LabelsPtr
rest

-- | Extract pointer-offset from 'LabelsPtr' (if it exists)
labelsPtr :: LabelsPtr -> Maybe Word16
labelsPtr :: LabelsPtr -> Maybe Word16
labelsPtr (Label _ ls :: LabelsPtr
ls) = LabelsPtr -> Maybe Word16
labelsPtr LabelsPtr
ls
labelsPtr LNul         = Maybe Word16
forall a. Maybe a
Nothing
labelsPtr (LPtr ofs :: Word16
ofs)   = Word16 -> Maybe Word16
forall a. a -> Maybe a
Just Word16
ofs

----------------------------------------------------------------------------

instance Binary l => Binary (MsgQuestion l) where
    get :: Get (MsgQuestion l)
get = l -> Type -> Class -> MsgQuestion l
forall l. l -> Type -> Class -> MsgQuestion l
MsgQuestion (l -> Type -> Class -> MsgQuestion l)
-> Get l -> Get (Type -> Class -> MsgQuestion l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get l
forall t. Binary t => Get t
get Get (Type -> Class -> MsgQuestion l)
-> Get Type -> Get (Class -> MsgQuestion l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Type
forall t. Binary t => Get t
get Get (Class -> MsgQuestion l) -> Get Class -> Get (MsgQuestion l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Class
forall t. Binary t => Get t
get
    put :: MsgQuestion l -> Put
put (MsgQuestion l :: l
l qt :: Type
qt cls :: Class
cls) = l -> Put
forall t. Binary t => t -> Put
put l
l Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Type -> Put
forall t. Binary t => t -> Put
put Type
qt Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Class -> Put
forall t. Binary t => t -> Put
put Class
cls


instance Binary l => Binary (MsgRR l) where
    get :: Get (MsgRR l)
get = do
        l
rrName  <- Get l
forall t. Binary t => Get t
get
        Type
rrType  <- Get Type
forall t. Binary t => Get t
get
        Class
rrClass <- Get Class
forall t. Binary t => Get t
get
        TTL
rrTTL   <- Get TTL
forall t. Binary t => Get t
get
        RData l
rrData  <- Type -> Get (RData l)
forall l. Binary l => Type -> Get (RData l)
getRData Type
rrType
        MsgRR l -> Get (MsgRR l)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ($WMsgRR :: forall l. l -> Class -> TTL -> RData l -> MsgRR l
MsgRR {..})

    put :: MsgRR l -> Put
put (MsgRR{..}) = do
        l -> Put
forall t. Binary t => t -> Put
put         l
rrName
        Type -> Put
forall t. Binary t => t -> Put
put         ((Type -> Type) -> (TypeSym -> Type) -> Either Type TypeSym -> Type
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Type -> Type
forall a. a -> a
id TypeSym -> Type
typeFromSym (Either Type TypeSym -> Type) -> Either Type TypeSym -> Type
forall a b. (a -> b) -> a -> b
$ RData l -> Either Type TypeSym
forall l. RData l -> Either Type TypeSym
rdType RData l
rrData)
        Class -> Put
forall t. Binary t => t -> Put
put         Class
rrClass
        TTL -> Put
forall t. Binary t => t -> Put
put         TTL
rrTTL
        RData l -> Put
forall l. Binary l => RData l -> Put
putRData    RData l
rrData

getRData :: Binary l => Type -> Get (RData l)
getRData :: Type -> Get (RData l)
getRData qt :: Type
qt = do
    Int
len     <- Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int) -> Get Word16 -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be

    let unknownRdata :: Get (RData l)
unknownRdata = Type -> ByteString -> RData l
forall l. Type -> ByteString -> RData l
RData Type
qt (ByteString -> RData l) -> Get ByteString -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString Int
len

        getByteStringRest :: Get ByteString
getByteStringRest = (Int -> Get ByteString) -> Get ByteString
forall b. (Int -> Get b) -> Get b
consumeRestWith Int -> Get ByteString
getByteString

        consumeRestWith :: (Int -> Get b) -> Get b
consumeRestWith act :: Int -> Get b
act = do
            Int
curofs <- ByteOffset -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteOffset -> Int) -> Get ByteOffset -> Get Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get ByteOffset
bytesRead
            Int -> Get b
act (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
curofs)

    Int -> Get (RData l) -> Get (RData l)
forall a. Int -> Get a -> Get a
isolate Int
len (Get (RData l) -> Get (RData l)) -> Get (RData l) -> Get (RData l)
forall a b. (a -> b) -> a -> b
$
      case Type -> Maybe TypeSym
typeToSym Type
qt of
        Nothing -> Get (RData l)
forall l. Get (RData l)
unknownRdata
        Just ts :: TypeSym
ts -> case TypeSym
ts of
          TypeA      -> IPv4 -> RData l
forall l. IPv4 -> RData l
RDataA      (IPv4 -> RData l) -> Get IPv4 -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get IPv4
forall t. Binary t => Get t
get

          TypeAFSDB  -> Word16 -> l -> RData l
forall l. Word16 -> l -> RData l
RDataAFSDB  (Word16 -> l -> RData l) -> Get Word16 -> Get (l -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
                                    Get (l -> RData l) -> Get l -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get l
forall t. Binary t => Get t
get

          TypeNS     -> l -> RData l
forall l. l -> RData l
RDataNS     (l -> RData l) -> Get l -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get l
forall t. Binary t => Get t
get

          TypeCNAME  -> l -> RData l
forall l. l -> RData l
RDataCNAME  (l -> RData l) -> Get l -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get l
forall t. Binary t => Get t
get

          TypeSOA    -> l -> l -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> RData l
forall l.
l -> l -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> RData l
RDataSOA    (l
 -> l -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> RData l)
-> Get l
-> Get
     (l -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get l
forall t. Binary t => Get t
get
                                    Get
  (l -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> RData l)
-> Get l
-> Get (Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get l
forall t. Binary t => Get t
get
                                    Get (Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> RData l)
-> Get Word32
-> Get (Word32 -> Word32 -> Word32 -> Word32 -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
getWord32be
                                    Get (Word32 -> Word32 -> Word32 -> Word32 -> RData l)
-> Get Word32 -> Get (Word32 -> Word32 -> Word32 -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
getWord32be
                                    Get (Word32 -> Word32 -> Word32 -> RData l)
-> Get Word32 -> Get (Word32 -> Word32 -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
getWord32be
                                    Get (Word32 -> Word32 -> RData l)
-> Get Word32 -> Get (Word32 -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
getWord32be
                                    Get (Word32 -> RData l) -> Get Word32 -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
getWord32be

          TypePTR    -> l -> RData l
forall l. l -> RData l
RDataPTR    (l -> RData l) -> Get l -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get l
forall t. Binary t => Get t
get

          TypeHINFO  -> CharStr -> CharStr -> RData l
forall l. CharStr -> CharStr -> RData l
RDataHINFO  (CharStr -> CharStr -> RData l)
-> Get CharStr -> Get (CharStr -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get CharStr
forall t. Binary t => Get t
get
                                    Get (CharStr -> RData l) -> Get CharStr -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get CharStr
forall t. Binary t => Get t
get

          TypeMX     -> Word16 -> l -> RData l
forall l. Word16 -> l -> RData l
RDataMX     (Word16 -> l -> RData l) -> Get Word16 -> Get (l -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
                                    Get (l -> RData l) -> Get l -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get l
forall t. Binary t => Get t
get

          TypeTXT    -> [CharStr] -> RData l
forall l. [CharStr] -> RData l
RDataTXT    ([CharStr] -> RData l) -> Get [CharStr] -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [CharStr]
forall a. Binary a => Get [a]
getUntilEmpty
          TypeSPF    -> [CharStr] -> RData l
forall l. [CharStr] -> RData l
RDataSPF    ([CharStr] -> RData l) -> Get [CharStr] -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [CharStr]
forall a. Binary a => Get [a]
getUntilEmpty

          TypeAAAA   -> IPv6 -> RData l
forall l. IPv6 -> RData l
RDataAAAA   (IPv6 -> RData l) -> Get IPv6 -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get IPv6
forall t. Binary t => Get t
get

          TypeSRV    -> SRV l -> RData l
forall l. SRV l -> RData l
RDataSRV    (SRV l -> RData l) -> Get (SRV l) -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (SRV l)
forall t. Binary t => Get t
get

          TypeNAPTR  -> Word16 -> Word16 -> CharStr -> CharStr -> CharStr -> l -> RData l
forall l.
Word16 -> Word16 -> CharStr -> CharStr -> CharStr -> l -> RData l
RDataNAPTR  (Word16 -> Word16 -> CharStr -> CharStr -> CharStr -> l -> RData l)
-> Get Word16
-> Get (Word16 -> CharStr -> CharStr -> CharStr -> l -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be -- order
                                    Get (Word16 -> CharStr -> CharStr -> CharStr -> l -> RData l)
-> Get Word16
-> Get (CharStr -> CharStr -> CharStr -> l -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be --preference
                                    Get (CharStr -> CharStr -> CharStr -> l -> RData l)
-> Get CharStr -> Get (CharStr -> CharStr -> l -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get CharStr
forall t. Binary t => Get t
get -- flags
                                    Get (CharStr -> CharStr -> l -> RData l)
-> Get CharStr -> Get (CharStr -> l -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get CharStr
forall t. Binary t => Get t
get -- services
                                    Get (CharStr -> l -> RData l) -> Get CharStr -> Get (l -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get CharStr
forall t. Binary t => Get t
get -- regexp
                                    Get (l -> RData l) -> Get l -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get l
forall t. Binary t => Get t
get -- replacement

          TypeRRSIG  -> Word16
-> Word8
-> Word8
-> Word32
-> Word32
-> Word32
-> Word16
-> l
-> ByteString
-> RData l
forall l.
Word16
-> Word8
-> Word8
-> Word32
-> Word32
-> Word32
-> Word16
-> l
-> ByteString
-> RData l
RDataRRSIG  (Word16
 -> Word8
 -> Word8
 -> Word32
 -> Word32
 -> Word32
 -> Word16
 -> l
 -> ByteString
 -> RData l)
-> Get Word16
-> Get
     (Word8
      -> Word8
      -> Word32
      -> Word32
      -> Word32
      -> Word16
      -> l
      -> ByteString
      -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
                                    Get
  (Word8
   -> Word8
   -> Word32
   -> Word32
   -> Word32
   -> Word16
   -> l
   -> ByteString
   -> RData l)
-> Get Word8
-> Get
     (Word8
      -> Word32
      -> Word32
      -> Word32
      -> Word16
      -> l
      -> ByteString
      -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word8
getWord8
                                    Get
  (Word8
   -> Word32
   -> Word32
   -> Word32
   -> Word16
   -> l
   -> ByteString
   -> RData l)
-> Get Word8
-> Get
     (Word32
      -> Word32 -> Word32 -> Word16 -> l -> ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word8
getWord8
                                    Get
  (Word32
   -> Word32 -> Word32 -> Word16 -> l -> ByteString -> RData l)
-> Get Word32
-> Get (Word32 -> Word32 -> Word16 -> l -> ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
getWord32be
                                    Get (Word32 -> Word32 -> Word16 -> l -> ByteString -> RData l)
-> Get Word32
-> Get (Word32 -> Word16 -> l -> ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
getWord32be
                                    Get (Word32 -> Word16 -> l -> ByteString -> RData l)
-> Get Word32 -> Get (Word16 -> l -> ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word32
getWord32be
                                    Get (Word16 -> l -> ByteString -> RData l)
-> Get Word16 -> Get (l -> ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be
                                    Get (l -> ByteString -> RData l)
-> Get l -> Get (ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get l
forall t. Binary t => Get t
get -- uncompressed
                                    Get (ByteString -> RData l) -> Get ByteString -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get ByteString
getByteStringRest

          TypeDNSKEY -> Word16 -> Word8 -> Word8 -> ByteString -> RData l
forall l. Word16 -> Word8 -> Word8 -> ByteString -> RData l
RDataDNSKEY (Word16 -> Word8 -> Word8 -> ByteString -> RData l)
-> Get Word16 -> Get (Word8 -> Word8 -> ByteString -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
                                    Get (Word8 -> Word8 -> ByteString -> RData l)
-> Get Word8 -> Get (Word8 -> ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word8
getWord8
                                    Get (Word8 -> ByteString -> RData l)
-> Get Word8 -> Get (ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word8
getWord8
                                    Get (ByteString -> RData l) -> Get ByteString -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- 4)

          TypeDS     -> Word16 -> Word8 -> Word8 -> ByteString -> RData l
forall l. Word16 -> Word8 -> Word8 -> ByteString -> RData l
RDataDS     (Word16 -> Word8 -> Word8 -> ByteString -> RData l)
-> Get Word16 -> Get (Word8 -> Word8 -> ByteString -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
                                    Get (Word8 -> Word8 -> ByteString -> RData l)
-> Get Word8 -> Get (Word8 -> ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word8
getWord8
                                    Get (Word8 -> ByteString -> RData l)
-> Get Word8 -> Get (ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word8
getWord8
                                    Get (ByteString -> RData l) -> Get ByteString -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- 4)

          TypeNSEC   -> l -> Set Type -> RData l
forall l. l -> Set Type -> RData l
RDataNSEC   (l -> Set Type -> RData l) -> Get l -> Get (Set Type -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get l
forall t. Binary t => Get t
get
                                    Get (Set Type -> RData l) -> Get (Set Type) -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Set Type)
decodeNsecTypeMap

          TypeURI    -> Word16 -> Word16 -> ByteString -> RData l
forall l. Word16 -> Word16 -> ByteString -> RData l
RDataURI    (Word16 -> Word16 -> ByteString -> RData l)
-> Get Word16 -> Get (Word16 -> ByteString -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be -- prio
                                    Get (Word16 -> ByteString -> RData l)
-> Get Word16 -> Get (ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be -- weight
                                    Get (ByteString -> RData l) -> Get ByteString -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- 4)

          TypeSSHFP  -> Word8 -> Word8 -> ByteString -> RData l
forall l. Word8 -> Word8 -> ByteString -> RData l
RDataSSHFP  (Word8 -> Word8 -> ByteString -> RData l)
-> Get Word8 -> Get (Word8 -> ByteString -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
                                    Get (Word8 -> ByteString -> RData l)
-> Get Word8 -> Get (ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word8
getWord8
                                    Get (ByteString -> RData l) -> Get ByteString -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Get ByteString
getByteString (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- 2)

          TypeNSEC3PARAM -> Word8 -> Word8 -> Word16 -> CharStr -> RData l
forall l. Word8 -> Word8 -> Word16 -> CharStr -> RData l
RDataNSEC3PARAM (Word8 -> Word8 -> Word16 -> CharStr -> RData l)
-> Get Word8 -> Get (Word8 -> Word16 -> CharStr -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
                                            Get (Word8 -> Word16 -> CharStr -> RData l)
-> Get Word8 -> Get (Word16 -> CharStr -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word8
getWord8
                                            Get (Word16 -> CharStr -> RData l)
-> Get Word16 -> Get (CharStr -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be
                                            Get (CharStr -> RData l) -> Get CharStr -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get CharStr
forall t. Binary t => Get t
get -- salt

          TypeNSEC3      -> Word8
-> Word8 -> Word16 -> CharStr -> CharStr -> Set Type -> RData l
forall l.
Word8
-> Word8 -> Word16 -> CharStr -> CharStr -> Set Type -> RData l
RDataNSEC3      (Word8
 -> Word8 -> Word16 -> CharStr -> CharStr -> Set Type -> RData l)
-> Get Word8
-> Get
     (Word8 -> Word16 -> CharStr -> CharStr -> Set Type -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8
                                            Get (Word8 -> Word16 -> CharStr -> CharStr -> Set Type -> RData l)
-> Get Word8
-> Get (Word16 -> CharStr -> CharStr -> Set Type -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word8
getWord8
                                            Get (Word16 -> CharStr -> CharStr -> Set Type -> RData l)
-> Get Word16 -> Get (CharStr -> CharStr -> Set Type -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be
                                            Get (CharStr -> CharStr -> Set Type -> RData l)
-> Get CharStr -> Get (CharStr -> Set Type -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get CharStr
forall t. Binary t => Get t
get -- salt
                                            Get (CharStr -> Set Type -> RData l)
-> Get CharStr -> Get (Set Type -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get CharStr
forall t. Binary t => Get t
get -- next hashed owner name
                                            Get (Set Type -> RData l) -> Get (Set Type) -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get (Set Type)
decodeNsecTypeMap

          TypeCAA        -> Word8 -> CharStr -> ByteString -> RData l
forall l. Word8 -> CharStr -> ByteString -> RData l
RDataCAA        (Word8 -> CharStr -> ByteString -> RData l)
-> Get Word8 -> Get (CharStr -> ByteString -> RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word8
getWord8 -- flags
                                            Get (CharStr -> ByteString -> RData l)
-> Get CharStr -> Get (ByteString -> RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get CharStr
forall t. Binary t => Get t
get -- tag -- TODO: must be non-empty
                                            Get (ByteString -> RData l) -> Get ByteString -> Get (RData l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get ByteString
getByteStringRest

          TypeOPT -> ByteString -> RData l
forall l. ByteString -> RData l
RDataOPT (ByteString -> RData l) -> Get ByteString -> Get (RData l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Get ByteString
getByteString Int
len -- FIXME

          TypeANY    -> Get (RData l)
forall l. Get (RData l)
unknownRdata -- shouldn't happen

putRData :: Binary l => RData l -> Put
putRData :: RData l -> Put
putRData rd :: RData l
rd = do
    let rdata :: ByteString
rdata = Put -> ByteString
runPut (RData l -> Put
forall l. Binary l => RData l -> Put
putRData' RData l
rd)
        rdataLen :: ByteOffset
rdataLen = ByteString -> ByteOffset
BSL.length ByteString
rdata

    Bool -> Put -> Put
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteOffset
rdataLen ByteOffset -> ByteOffset -> Bool
forall a. Ord a => a -> a -> Bool
< 0x10000) (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$
        String -> Put
forall a. HasCallStack => String -> a
error "rdata too large"

    Word16 -> Put
putWord16be (ByteOffset -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral ByteOffset
rdataLen)
    ByteString -> Put
putLazyByteString ByteString
rdata

putRData' :: Binary l => RData l -> Put
putRData' :: RData l -> Put
putRData' rd :: RData l
rd = case RData l
rd of
  RDataA ip4 :: IPv4
ip4 -> IPv4 -> Put
forall t. Binary t => t -> Put
put IPv4
ip4
  RDataAAAA ip6 :: IPv6
ip6 -> IPv6 -> Put
forall t. Binary t => t -> Put
put IPv6
ip6
  RDataCNAME cname :: l
cname -> l -> Put
forall t. Binary t => t -> Put
put l
cname
  RDataOPT d :: ByteString
d -> ByteString -> Put
putByteString ByteString
d
  RDataMX prio :: Word16
prio l :: l
l -> Word16 -> Put
putWord16be Word16
prio Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> l -> Put
forall t. Binary t => t -> Put
put l
l
  RDataSOA l1 :: l
l1 l2 :: l
l2 w1 :: Word32
w1 w2 :: Word32
w2 w3 :: Word32
w3 w4 :: Word32
w4 w5 :: Word32
w5 -> do
      l -> Put
forall t. Binary t => t -> Put
put l
l1
      l -> Put
forall t. Binary t => t -> Put
put l
l2
      Word32 -> Put
putWord32be Word32
w1
      Word32 -> Put
putWord32be Word32
w2
      Word32 -> Put
putWord32be Word32
w3
      Word32 -> Put
putWord32be Word32
w4
      Word32 -> Put
putWord32be Word32
w5

  RDataPTR l :: l
l -> l -> Put
forall t. Binary t => t -> Put
put l
l
  RDataNS  l :: l
l -> l -> Put
forall t. Binary t => t -> Put
put l
l
  RDataTXT ss :: [CharStr]
ss -> (CharStr -> Put) -> [CharStr] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ CharStr -> Put
forall t. Binary t => t -> Put
put [CharStr]
ss
  RDataSPF ss :: [CharStr]
ss -> (CharStr -> Put) -> [CharStr] -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ CharStr -> Put
forall t. Binary t => t -> Put
put [CharStr]
ss
  RDataSRV srv :: SRV l
srv -> SRV l -> Put
forall t. Binary t => t -> Put
put SRV l
srv

  RDataAFSDB w :: Word16
w l :: l
l -> Word16 -> Put
putWord16be Word16
w Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> l -> Put
forall t. Binary t => t -> Put
put l
l

  RDataHINFO s1 :: CharStr
s1 s2 :: CharStr
s2 -> CharStr -> Put
forall t. Binary t => t -> Put
put CharStr
s1 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CharStr -> Put
forall t. Binary t => t -> Put
put CharStr
s2

  RDataRRSIG w1 :: Word16
w1 w2 :: Word8
w2 w3 :: Word8
w3 w4 :: Word32
w4 w5 :: Word32
w5 w6 :: Word32
w6 w7 :: Word16
w7 l :: l
l s :: ByteString
s -> do
      Word16 -> Put
putWord16be Word16
w1
      Word8 -> Put
putWord8    Word8
w2
      Word8 -> Put
putWord8    Word8
w3
      Word32 -> Put
putWord32be Word32
w4
      Word32 -> Put
putWord32be Word32
w5
      Word32 -> Put
putWord32be Word32
w6
      Word16 -> Put
putWord16be Word16
w7
      l -> Put
forall t. Binary t => t -> Put
put l
l
      ByteString -> Put
putByteString ByteString
s

  RDataDNSKEY w1 :: Word16
w1 w2 :: Word8
w2 w3 :: Word8
w3 s :: ByteString
s -> do
      Word16 -> Put
putWord16be Word16
w1
      Word8 -> Put
putWord8    Word8
w2
      Word8 -> Put
putWord8    Word8
w3
      ByteString -> Put
putByteString ByteString
s

  RDataNSEC3PARAM w1 :: Word8
w1 w2 :: Word8
w2 w3 :: Word16
w3 s :: CharStr
s -> do
      Word8 -> Put
putWord8 Word8
w1
      Word8 -> Put
putWord8 Word8
w2
      Word16 -> Put
putWord16be Word16
w3
      CharStr -> Put
forall t. Binary t => t -> Put
put CharStr
s

  RDataNSEC3 w1 :: Word8
w1 w2 :: Word8
w2 w3 :: Word16
w3 s1 :: CharStr
s1 s2 :: CharStr
s2 tm :: Set Type
tm -> do
      Word8 -> Put
putWord8 Word8
w1
      Word8 -> Put
putWord8 Word8
w2
      Word16 -> Put
putWord16be Word16
w3
      CharStr -> Put
forall t. Binary t => t -> Put
put CharStr
s1
      CharStr -> Put
forall t. Binary t => t -> Put
put CharStr
s2
      Set Type -> Put
encodeNsecTypeMap Set Type
tm

  RDataCAA fl :: Word8
fl s1 :: CharStr
s1 s2 :: ByteString
s2 -> do
      Word8 -> Put
putWord8 Word8
fl
      CharStr -> Put
forall t. Binary t => t -> Put
put CharStr
s1
      ByteString -> Put
putByteString ByteString
s2

  RDataURI w1 :: Word16
w1 w2 :: Word16
w2 s :: ByteString
s -> do
      Word16 -> Put
putWord16be Word16
w1
      Word16 -> Put
putWord16be Word16
w2
      ByteString -> Put
putByteString ByteString
s

  RDataDS w1 :: Word16
w1 w2 :: Word8
w2 w3 :: Word8
w3 s :: ByteString
s -> do
      Word16 -> Put
putWord16be Word16
w1
      Word8 -> Put
putWord8 Word8
w2
      Word8 -> Put
putWord8 Word8
w3
      ByteString -> Put
putByteString ByteString
s

  RDataNSEC l :: l
l tm :: Set Type
tm -> do
      l -> Put
forall t. Binary t => t -> Put
put l
l
      Set Type -> Put
encodeNsecTypeMap Set Type
tm

  RDataNAPTR w1 :: Word16
w1 w2 :: Word16
w2 s1 :: CharStr
s1 s2 :: CharStr
s2 s3 :: CharStr
s3 l :: l
l -> do
      Word16 -> Put
putWord16be Word16
w1
      Word16 -> Put
putWord16be Word16
w2
      CharStr -> Put
forall t. Binary t => t -> Put
put CharStr
s1
      CharStr -> Put
forall t. Binary t => t -> Put
put CharStr
s2
      CharStr -> Put
forall t. Binary t => t -> Put
put CharStr
s3
      l -> Put
forall t. Binary t => t -> Put
put l
l

  RDataSSHFP w1 :: Word8
w1 w2 :: Word8
w2 s :: ByteString
s -> do
      Word8 -> Put
putWord8 Word8
w1
      Word8 -> Put
putWord8 Word8
w2
      ByteString -> Put
putByteString ByteString
s

  RData _ raw :: ByteString
raw -> ByteString -> Put
putByteString ByteString
raw

  -- _ -> error ("putRData: " ++ show rd)


instance Binary l => Binary (SRV l) where
    get :: Get (SRV l)
get = Word16 -> Word16 -> Word16 -> l -> SRV l
forall l. Word16 -> Word16 -> Word16 -> l -> SRV l
SRV (Word16 -> Word16 -> Word16 -> l -> SRV l)
-> Get Word16 -> Get (Word16 -> Word16 -> l -> SRV l)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be
              Get (Word16 -> Word16 -> l -> SRV l)
-> Get Word16 -> Get (Word16 -> l -> SRV l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be
              Get (Word16 -> l -> SRV l) -> Get Word16 -> Get (l -> SRV l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Word16
getWord16be
              Get (l -> SRV l) -> Get l -> Get (SRV l)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get l
forall t. Binary t => Get t
get

    put :: SRV l -> Put
put (SRV w1 :: Word16
w1 w2 :: Word16
w2 w3 :: Word16
w3 l :: l
l) = do
      Word16 -> Put
putWord16be Word16
w1
      Word16 -> Put
putWord16be Word16
w2
      Word16 -> Put
putWord16be Word16
w3
      l -> Put
forall t. Binary t => t -> Put
put l
l

{- NSEC type-bitmap example:

 A NS SOA TXT AAAA RRSIG NSEC DNSKEY

'00 07 62 00 80 08 00 03 80'
'00000000 00000111 01100010 00000000 10000000 00001000 00000000 00000011 10000000'
 Win=#0    len=7         ^{SOA}      ^{TXT}       ^{AAAA}                ^{DNSKEY}
                    ^^{A,NS}                                          ^^{RRSIG,NSEC}
-}

decodeNsecTypeMap :: Get (Set Type)
decodeNsecTypeMap :: Get (Set Type)
decodeNsecTypeMap = do
    [Type]
r <- [[Type]] -> [Type]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Type]] -> [Type]) -> Get [[Type]] -> Get [Type]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get [Type] -> Get [[Type]]
forall a. Get a -> Get [a]
untilEmptyWith Get [Type]
decode1
    -- TODO: enforce uniqueness
    Set Type -> Get (Set Type)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Type] -> Set Type
forall a. Ord a => [a] -> Set a
Set.fromList [Type]
r)
  where
    -- decode single window
    decode1 :: Get [Type]
decode1 = do
        Word8
wi <- Get Word8
getWord8
        Word8
l  <- Get Word8
getWord8
        Bool -> Get () -> Get ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (0 Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
l Bool -> Bool -> Bool
&& Word8
l Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= 32) (Get () -> Get ()) -> Get () -> Get ()
forall a b. (a -> b) -> a -> b
$
            String -> Get ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail "invalid bitmap length"

        ByteString
bmap <- Int -> Get ByteString
getByteString (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
l)

        let winofs :: Int
winofs = (Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
wi)Int -> Int -> Int
forall a. Num a => a -> a -> a
*0x100 :: Int
            lst :: [Type]
lst = [ Word16 -> Type
Type (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
winofsInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
*8Int -> Int -> Int
forall a. Num a => a -> a -> a
+7Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i))
                  | (j :: Int
j,x :: Word8
x) <- [Int] -> [Word8] -> [(Int, Word8)]
forall a b. [a] -> [b] -> [(a, b)]
zip [0..] (ByteString -> [Word8]
BS.unpack ByteString
bmap)
                  , Int
i <- [7,6..0]
                  , Word8 -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Word8
x Int
i ]

        [Type] -> Get [Type]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Type]
lst

encodeNsecTypeMap :: Set Type -> Put
encodeNsecTypeMap :: Set Type -> Put
encodeNsecTypeMap bmap :: Set Type
bmap = do
    Bool -> Put -> Put
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Set Type -> Bool
forall a. Set a -> Bool
Set.null Set Type
bmap) (Put -> Put) -> Put -> Put
forall a b. (a -> b) -> a -> b
$ String -> Put
forall a. HasCallStack => String -> a
error "invalid empty type-map"
    -- when (Set.member 0 bmap) $ fail "invalid TYPE0 set in type-map"
    -- TODO: verify that Meta-TYPES and QTYPEs aren't contained in bmap

    [(Word8, [Word8])] -> ((Word8, [Word8]) -> Put) -> Put
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (Map Word8 [Word8] -> [(Word8, [Word8])]
forall k a. Map k a -> [(k, a)]
Map.toList Map Word8 [Word8]
bmap') (((Word8, [Word8]) -> Put) -> Put)
-> ((Word8, [Word8]) -> Put) -> Put
forall a b. (a -> b) -> a -> b
$ \(wi :: Word8
wi, tm :: [Word8]
tm) -> do
        Word8 -> Put
putWord8 Word8
wi
        CharStr -> Put
forall t. Binary t => t -> Put
put (ByteString -> CharStr
CharStr (ByteString -> CharStr) -> ByteString -> CharStr
forall a b. (a -> b) -> a -> b
$ [Word8] -> ByteString
BS.pack [Word8]
tm)
  where
    bmap' :: Map Word8 [Word8]
bmap' = (Set Word8 -> [Word8])
-> Map Word8 (Set Word8) -> Map Word8 [Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Set Word8 -> [Word8]
set2bitmap (Map Word8 (Set Word8) -> Map Word8 [Word8])
-> (Set Word16 -> Map Word8 (Set Word8))
-> Set Word16
-> Map Word8 [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set Word16 -> Map Word8 (Set Word8)
splitToBlocks (Set Word16 -> Map Word8 [Word8])
-> Set Word16 -> Map Word8 [Word8]
forall a b. (a -> b) -> a -> b
$ (Type -> Word16) -> Set Type -> Set Word16
forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map (\(Type w :: Word16
w)->Word16
w) Set Type
bmap

set2bitmap :: Set Word8 -> [Word8]
set2bitmap :: Set Word8 -> [Word8]
set2bitmap = Word8 -> Word8 -> [Word8] -> [Word8]
forall a t. (Num t, Bits t, Integral a) => a -> t -> [a] -> [t]
go 0 0 ([Word8] -> [Word8])
-> (Set Word8 -> [Word8]) -> Set Word8 -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set Word8 -> [Word8]
forall a. Set a -> [a]
Set.toList
  where
    go :: a -> t -> [a] -> [t]
go _ acc :: t
acc [] = if t
acc t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== 0 then [] else [t
acc]
    go j :: a
j acc :: t
acc (i :: a
i:is :: [a]
is)
      | a
j'  a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
j  = t
acc t -> [t] -> [t]
forall a. a -> [a] -> [a]
: a -> t -> [a] -> [t]
go (a
ja -> a -> a
forall a. Num a => a -> a -> a
+1) 0 (a
ia -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
is)
      | a
j' a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
j  = a -> t -> [a] -> [t]
go a
j' (t
acc t -> t -> t
forall a. Bits a => a -> a -> a
.|. Int -> t
forall a. Bits a => Int -> a
bit (7 Int -> Int -> Int
forall a. Num a => a -> a -> a
- a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
i')) [a]
is
      | Bool
otherwise = String -> [t]
forall a. HasCallStack => String -> a
error "set2bitmap: the impossible happened"
      where
        (j' :: a
j',i' :: a
i') = a
i a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
`quotRem` 8

splitToBlocks :: Set Word16 -> Map Word8 (Set Word8)
splitToBlocks :: Set Word16 -> Map Word8 (Set Word8)
splitToBlocks js :: Set Word16
js = [(Word8, Set Word8)] -> Map Word8 (Set Word8)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Word8, Set Word8)] -> Map Word8 (Set Word8))
-> [(Word8, Set Word8)] -> Map Word8 (Set Word8)
forall a b. (a -> b) -> a -> b
$ ([(Word8, Word8)] -> (Word8, Set Word8))
-> [[(Word8, Word8)]] -> [(Word8, Set Word8)]
forall a b. (a -> b) -> [a] -> [b]
map (\xs :: [(Word8, Word8)]
xs -> ((Word8, Word8) -> Word8
forall a b. (a, b) -> a
fst ((Word8, Word8) -> Word8) -> (Word8, Word8) -> Word8
forall a b. (a -> b) -> a -> b
$ [(Word8, Word8)] -> (Word8, Word8)
forall a. [a] -> a
head [(Word8, Word8)]
xs, [Word8] -> Set Word8
forall a. Ord a => [a] -> Set a
Set.fromList (((Word8, Word8) -> Word8) -> [(Word8, Word8)] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map (Word8, Word8) -> Word8
forall a b. (a, b) -> b
snd [(Word8, Word8)]
xs))) [[(Word8, Word8)]]
js'
  where
    hi16 :: Word16 -> Word8
    hi16 :: Word16 -> Word8
hi16 = Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Word8) -> (Word16 -> Word16) -> Word16 -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word16 -> Int -> Word16) -> Int -> Word16 -> Word16
forall a b c. (a -> b -> c) -> b -> a -> c
flip Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
shiftR 8

    lo16 :: Word16 -> Word8
    lo16 :: Word16 -> Word8
lo16 = Word16 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Word8) -> (Word16 -> Word16) -> Word16 -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.&. 0xff)

    js' :: [[(Word8,Word8)]]
    js' :: [[(Word8, Word8)]]
js' = ((Word8, Word8) -> (Word8, Word8) -> Bool)
-> [(Word8, Word8)] -> [[(Word8, Word8)]]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
(==) (Word8 -> Word8 -> Bool)
-> ((Word8, Word8) -> Word8)
-> (Word8, Word8)
-> (Word8, Word8)
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Word8, Word8) -> Word8
forall a b. (a, b) -> a
fst) ((Word16 -> (Word8, Word8)) -> [Word16] -> [(Word8, Word8)]
forall a b. (a -> b) -> [a] -> [b]
map ((,) (Word8 -> Word8 -> (Word8, Word8))
-> (Word16 -> Word8) -> Word16 -> Word8 -> (Word8, Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word16 -> Word8
hi16 (Word16 -> Word8 -> (Word8, Word8))
-> (Word16 -> Word8) -> Word16 -> (Word8, Word8)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Word16 -> Word8
lo16) (Set Word16 -> [Word16]
forall a. Set a -> [a]
Set.toList Set Word16
js))


-- | Resolves/parses label pointer used for label compressing
--
-- Returns 'Nothing' on failure
retrieveLabelPtr :: BS.ByteString -> Word16 -> Maybe LabelsPtr
retrieveLabelPtr :: ByteString -> Word16 -> Maybe LabelsPtr
retrieveLabelPtr msg :: ByteString
msg ofs :: Word16
ofs
    = case ByteString
-> Either
     (ByteString, ByteOffset, String)
     (ByteString, ByteOffset, LabelsPtr)
forall a.
Binary a =>
ByteString
-> Either
     (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
decodeOrFail (ByteString -> ByteString
fromStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
BS.drop (Word16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
ofs) ByteString
msg) of
        Left _          -> Maybe LabelsPtr
forall a. Maybe a
Nothing
        Right (_, _, v :: LabelsPtr
v) -> LabelsPtr -> Maybe LabelsPtr
forall a. a -> Maybe a
Just LabelsPtr
v

-- | Resolve set of label pointer offsets
--
-- Invariants (/iff/ result is not 'Nothing')
--
--  * all requested offsets will be contained in the result map
--
--  * any offsets contained in the resolved 'Labels' will be part of
--    the result map as well
--
-- NB: No cycle detection is performed, nor are 'Labels' flattened
retrieveLabelPtrs :: BS.ByteString -> Set Word16 -> Maybe (Map Word16 LabelsPtr)
retrieveLabelPtrs :: ByteString -> Set Word16 -> Maybe (Map Word16 LabelsPtr)
retrieveLabelPtrs msg :: ByteString
msg ofss0 :: Set Word16
ofss0 = Map Word16 LabelsPtr -> Maybe (Map Word16 LabelsPtr)
go (Map Word16 LabelsPtr -> Maybe (Map Word16 LabelsPtr))
-> Maybe (Map Word16 LabelsPtr) -> Maybe (Map Word16 LabelsPtr)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Set Word16 -> Maybe (Map Word16 LabelsPtr)
lupPtrs1 Set Word16
ofss0
  where
    go :: Map Word16 LabelsPtr -> Maybe (Map Word16 LabelsPtr)
    go :: Map Word16 LabelsPtr -> Maybe (Map Word16 LabelsPtr)
go m0 :: Map Word16 LabelsPtr
m0 = do
        let missingOfss :: Set Word16
missingOfss = [Word16] -> Set Word16
forall a. Ord a => [a] -> Set a
Set.fromList ((LabelsPtr -> Maybe Word16) -> [LabelsPtr] -> [Word16]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe LabelsPtr -> Maybe Word16
labelsPtr (Map Word16 LabelsPtr -> [LabelsPtr]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Map Word16 LabelsPtr
m0)) Set Word16 -> Set Word16 -> Set Word16
forall a. Ord a => Set a -> Set a -> Set a
Set.\\ Map Word16 LabelsPtr -> Set Word16
forall k a. Map k a -> Set k
Map.keysSet Map Word16 LabelsPtr
m0

        if Set Word16 -> Bool
forall a. Set a -> Bool
Set.null Set Word16
missingOfss
         then Map Word16 LabelsPtr -> Maybe (Map Word16 LabelsPtr)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Map Word16 LabelsPtr
m0 -- fix-point reached
         else do
            Map Word16 LabelsPtr
m1 <- Set Word16 -> Maybe (Map Word16 LabelsPtr)
lupPtrs1 Set Word16
missingOfss
            Map Word16 LabelsPtr -> Maybe (Map Word16 LabelsPtr)
go (Map Word16 LabelsPtr
-> Map Word16 LabelsPtr -> Map Word16 LabelsPtr
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union Map Word16 LabelsPtr
m0 Map Word16 LabelsPtr
m1)

    -- single lookup step
    lupPtrs1 :: Set Word16 -> Maybe (Map Word16 LabelsPtr)
    lupPtrs1 :: Set Word16 -> Maybe (Map Word16 LabelsPtr)
lupPtrs1 ofss1 :: Set Word16
ofss1 = [(Word16, LabelsPtr)] -> Map Word16 LabelsPtr
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Word16, LabelsPtr)] -> Map Word16 LabelsPtr)
-> ([LabelsPtr] -> [(Word16, LabelsPtr)])
-> [LabelsPtr]
-> Map Word16 LabelsPtr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word16] -> [LabelsPtr] -> [(Word16, LabelsPtr)]
forall a b. [a] -> [b] -> [(a, b)]
zip (Set Word16 -> [Word16]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Set Word16
ofss1) ([LabelsPtr] -> Map Word16 LabelsPtr)
-> Maybe [LabelsPtr] -> Maybe (Map Word16 LabelsPtr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word16 -> Maybe LabelsPtr) -> [Word16] -> Maybe [LabelsPtr]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (ByteString -> Word16 -> Maybe LabelsPtr
retrieveLabelPtr ByteString
msg) (Set Word16 -> [Word16]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Set Word16
ofss1)

-- | Checks for maximum name length (255) and (therefore indirectly) cycle-checking
resolveLabelPtr :: Map Word16 LabelsPtr -> LabelsPtr -> Maybe Labels
resolveLabelPtr :: Map Word16 LabelsPtr -> LabelsPtr -> Maybe Labels
resolveLabelPtr ofsmap :: Map Word16 LabelsPtr
ofsmap = Int -> [ByteString] -> LabelsPtr -> Maybe Labels
go 0 []
  where
    go :: Int -> [BS.ByteString] -> LabelsPtr -> Maybe Labels
    go :: Int -> [ByteString] -> LabelsPtr -> Maybe Labels
go !Int
n acc :: [ByteString]
acc (Label x :: ByteString
x ls :: LabelsPtr
ls) = Int -> [ByteString] -> LabelsPtr -> Maybe Labels
go (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+1Int -> Int -> Int
forall a. Num a => a -> a -> a
+ByteString -> Int
BS.length ByteString
x) (ByteString
xByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:[ByteString]
acc) LabelsPtr
ls
    go n :: Int
n acc :: [ByteString]
acc LNul
        | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 255    = Labels -> Maybe Labels
forall a. a -> Maybe a
Just (Labels -> Maybe Labels) -> Labels -> Maybe Labels
forall a b. (a -> b) -> a -> b
$! (ByteString -> Labels -> Labels)
-> Labels -> [ByteString] -> Labels
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ByteString -> Labels -> Labels
(:.:) Labels
Root ([ByteString] -> [ByteString]
forall a. [a] -> [a]
reverse [ByteString]
acc)
        | Bool
otherwise  = Maybe Labels
forall a. Maybe a
Nothing -- length violation
    go n :: Int
n acc :: [ByteString]
acc (LPtr ofs :: Word16
ofs)
        | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 255    = Int -> [ByteString] -> LabelsPtr -> Maybe Labels
go Int
n [ByteString]
acc (LabelsPtr -> Maybe Labels) -> Maybe LabelsPtr -> Maybe Labels
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Word16 -> Maybe LabelsPtr
lup Word16
ofs
        | Bool
otherwise  = Maybe Labels
forall a. Maybe a
Nothing

    lup :: Word16 -> Maybe LabelsPtr
    lup :: Word16 -> Maybe LabelsPtr
lup ofs :: Word16
ofs = Word16 -> Map Word16 LabelsPtr -> Maybe LabelsPtr
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Word16
ofs Map Word16 LabelsPtr
ofsmap


{- Resource records

 -- https://en.wikipedia.org/wiki/List_of_DNS_record_types

 RFC 1035

 A        1     a host address
 NS       2     an authoritative name server
 CNAME    5     the canonical name for an alias
 SOA      6     marks the start of a zone of authority
 PTR      12    a domain name pointer
 MX       15    mail exchange
 TXT      16    text strings

 RFC 3596

 AAAA     28    IPv6

 RFC 2782

 SRV      33    Location of services

 ----

 RFC3597            Handling of Unknown DNS Resource Record (RR) Types

-}

-- | Raw DNS record type code
--
-- See also 'TypeSym'
newtype Type = Type Word16
             deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c== :: Type -> Type -> Bool
Eq,Eq Type
Eq Type =>
(Type -> Type -> Ordering)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Type)
-> (Type -> Type -> Type)
-> Ord Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmax :: Type -> Type -> Type
>= :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c< :: Type -> Type -> Bool
compare :: Type -> Type -> Ordering
$ccompare :: Type -> Type -> Ordering
$cp1Ord :: Eq Type
Ord,ReadPrec [Type]
ReadPrec Type
Int -> ReadS Type
ReadS [Type]
(Int -> ReadS Type)
-> ReadS [Type] -> ReadPrec Type -> ReadPrec [Type] -> Read Type
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Type]
$creadListPrec :: ReadPrec [Type]
readPrec :: ReadPrec Type
$creadPrec :: ReadPrec Type
readList :: ReadS [Type]
$creadList :: ReadS [Type]
readsPrec :: Int -> ReadS Type
$creadsPrec :: Int -> ReadS Type
Read,Int -> Type -> ShowS
[Type] -> ShowS
Type -> String
(Int -> Type -> ShowS)
-> (Type -> String) -> ([Type] -> ShowS) -> Show Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Type] -> ShowS
$cshowList :: [Type] -> ShowS
show :: Type -> String
$cshow :: Type -> String
showsPrec :: Int -> Type -> ShowS
$cshowsPrec :: Int -> Type -> ShowS
Show)

instance Binary Type where
    put :: Type -> Put
put (Type w :: Word16
w) = Word16 -> Put
putWord16be Word16
w
    get :: Get Type
get = Word16 -> Type
Type (Word16 -> Type) -> Get Word16 -> Get Type
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be

-- | DNS @CLASS@ code as per [RFC 1035, section 3.2.4](https://tools.ietf.org/html/rfc1035#section-3.2.4)
--
-- The most commonly used value is 'classIN'.
newtype Class = Class Word16
              deriving (Class -> Class -> Bool
(Class -> Class -> Bool) -> (Class -> Class -> Bool) -> Eq Class
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Class -> Class -> Bool
$c/= :: Class -> Class -> Bool
== :: Class -> Class -> Bool
$c== :: Class -> Class -> Bool
Eq,Eq Class
Eq Class =>
(Class -> Class -> Ordering)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Bool)
-> (Class -> Class -> Class)
-> (Class -> Class -> Class)
-> Ord Class
Class -> Class -> Bool
Class -> Class -> Ordering
Class -> Class -> Class
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Class -> Class -> Class
$cmin :: Class -> Class -> Class
max :: Class -> Class -> Class
$cmax :: Class -> Class -> Class
>= :: Class -> Class -> Bool
$c>= :: Class -> Class -> Bool
> :: Class -> Class -> Bool
$c> :: Class -> Class -> Bool
<= :: Class -> Class -> Bool
$c<= :: Class -> Class -> Bool
< :: Class -> Class -> Bool
$c< :: Class -> Class -> Bool
compare :: Class -> Class -> Ordering
$ccompare :: Class -> Class -> Ordering
$cp1Ord :: Eq Class
Ord,ReadPrec [Class]
ReadPrec Class
Int -> ReadS Class
ReadS [Class]
(Int -> ReadS Class)
-> ReadS [Class]
-> ReadPrec Class
-> ReadPrec [Class]
-> Read Class
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Class]
$creadListPrec :: ReadPrec [Class]
readPrec :: ReadPrec Class
$creadPrec :: ReadPrec Class
readList :: ReadS [Class]
$creadList :: ReadS [Class]
readsPrec :: Int -> ReadS Class
$creadsPrec :: Int -> ReadS Class
Read,Int -> Class -> ShowS
[Class] -> ShowS
Class -> String
(Int -> Class -> ShowS)
-> (Class -> String) -> ([Class] -> ShowS) -> Show Class
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Class] -> ShowS
$cshowList :: [Class] -> ShowS
show :: Class -> String
$cshow :: Class -> String
showsPrec :: Int -> Class -> ShowS
$cshowsPrec :: Int -> Class -> ShowS
Show)

-- | The 'Class' constant for @IN@ (Internet)
classIN :: Class
classIN :: Class
classIN = Word16 -> Class
Class 1

instance Binary Class where
    put :: Class -> Put
put (Class w :: Word16
w) = Word16 -> Put
putWord16be Word16
w
    get :: Get Class
get = Word16 -> Class
Class (Word16 -> Class) -> Get Word16 -> Get Class
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word16
getWord16be

-- | Cache time-to-live expressed in seconds
newtype TTL = TTL Int32
            deriving (TTL -> TTL -> Bool
(TTL -> TTL -> Bool) -> (TTL -> TTL -> Bool) -> Eq TTL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TTL -> TTL -> Bool
$c/= :: TTL -> TTL -> Bool
== :: TTL -> TTL -> Bool
$c== :: TTL -> TTL -> Bool
Eq,Eq TTL
Eq TTL =>
(TTL -> TTL -> Ordering)
-> (TTL -> TTL -> Bool)
-> (TTL -> TTL -> Bool)
-> (TTL -> TTL -> Bool)
-> (TTL -> TTL -> Bool)
-> (TTL -> TTL -> TTL)
-> (TTL -> TTL -> TTL)
-> Ord TTL
TTL -> TTL -> Bool
TTL -> TTL -> Ordering
TTL -> TTL -> TTL
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TTL -> TTL -> TTL
$cmin :: TTL -> TTL -> TTL
max :: TTL -> TTL -> TTL
$cmax :: TTL -> TTL -> TTL
>= :: TTL -> TTL -> Bool
$c>= :: TTL -> TTL -> Bool
> :: TTL -> TTL -> Bool
$c> :: TTL -> TTL -> Bool
<= :: TTL -> TTL -> Bool
$c<= :: TTL -> TTL -> Bool
< :: TTL -> TTL -> Bool
$c< :: TTL -> TTL -> Bool
compare :: TTL -> TTL -> Ordering
$ccompare :: TTL -> TTL -> Ordering
$cp1Ord :: Eq TTL
Ord,ReadPrec [TTL]
ReadPrec TTL
Int -> ReadS TTL
ReadS [TTL]
(Int -> ReadS TTL)
-> ReadS [TTL] -> ReadPrec TTL -> ReadPrec [TTL] -> Read TTL
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TTL]
$creadListPrec :: ReadPrec [TTL]
readPrec :: ReadPrec TTL
$creadPrec :: ReadPrec TTL
readList :: ReadS [TTL]
$creadList :: ReadS [TTL]
readsPrec :: Int -> ReadS TTL
$creadsPrec :: Int -> ReadS TTL
Read,Int -> TTL -> ShowS
[TTL] -> ShowS
TTL -> String
(Int -> TTL -> ShowS)
-> (TTL -> String) -> ([TTL] -> ShowS) -> Show TTL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TTL] -> ShowS
$cshowList :: [TTL] -> ShowS
show :: TTL -> String
$cshow :: TTL -> String
showsPrec :: Int -> TTL -> ShowS
$cshowsPrec :: Int -> TTL -> ShowS
Show)

instance Binary TTL where
    put :: TTL -> Put
put (TTL i :: Int32
i) = Int32 -> Put
putInt32be Int32
i
    get :: Get TTL
get = Int32 -> TTL
TTL (Int32 -> TTL) -> Get Int32 -> Get TTL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Int32
getInt32be

-- http://www.bind9.net/dns-parameters

-- | Symbolic DNS record type
data TypeSym
    = TypeA          -- ^ [RFC 1035](https://tools.ietf.org/html/rfc1035)
    | TypeAAAA       -- ^ [RFC 3596](https://tools.ietf.org/html/rfc3596)
    | TypeAFSDB      -- ^ [RFC 1183](https://tools.ietf.org/html/rfc1183)
    | TypeANY        -- ^ [RFC 1035](https://tools.ietf.org/html/rfc1035) (query)
    | TypeCAA        -- ^ [RFC 6844](https://tools.ietf.org/html/rfc6844)
    | TypeCNAME      -- ^ [RFC 1035](https://tools.ietf.org/html/rfc1035)
    | TypeDNSKEY     -- ^ [RFC 4034](https://tools.ietf.org/html/rfc4034)
    | TypeDS         -- ^ [RFC 4034](https://tools.ietf.org/html/rfc4034)
    | TypeHINFO      -- ^ [RFC 1035](https://tools.ietf.org/html/rfc1035)
    | TypeMX         -- ^ [RFC 1035](https://tools.ietf.org/html/rfc1035)
    | TypeNAPTR      -- ^ [RFC 2915](https://tools.ietf.org/html/rfc2915)
    | TypeNS         -- ^ [RFC 1035](https://tools.ietf.org/html/rfc1035)
    | TypeNSEC       -- ^ [RFC 4034](https://tools.ietf.org/html/rfc4034)
    | TypeNSEC3      -- ^ [RFC 5155](https://tools.ietf.org/html/rfc5155)
    | TypeNSEC3PARAM -- ^ [RFC 5155](https://tools.ietf.org/html/rfc5155)
    | TypeOPT        -- ^ [RFC 6891](https://tools.ietf.org/html/rfc6891) (meta)
    | TypePTR        -- ^ [RFC 1035](https://tools.ietf.org/html/rfc1035)
    | TypeRRSIG      -- ^ [RFC 4034](https://tools.ietf.org/html/rfc4034)
    | TypeSOA        -- ^ [RFC 1035](https://tools.ietf.org/html/rfc1035)
    | TypeSPF        -- ^ [RFC 4408](https://tools.ietf.org/html/rfc4408)
    | TypeSRV        -- ^ [RFC 2782](https://tools.ietf.org/html/rfc2782)
    | TypeSSHFP      -- ^ [RFC 4255](https://tools.ietf.org/html/rfc4255)
    | TypeTXT        -- ^ [RFC 1035](https://tools.ietf.org/html/rfc1035)
    | TypeURI        -- ^ [RFC 7553](https://tools.ietf.org/html/rfc7553)
    deriving (TypeSym -> TypeSym -> Bool
(TypeSym -> TypeSym -> Bool)
-> (TypeSym -> TypeSym -> Bool) -> Eq TypeSym
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeSym -> TypeSym -> Bool
$c/= :: TypeSym -> TypeSym -> Bool
== :: TypeSym -> TypeSym -> Bool
$c== :: TypeSym -> TypeSym -> Bool
Eq,Eq TypeSym
Eq TypeSym =>
(TypeSym -> TypeSym -> Ordering)
-> (TypeSym -> TypeSym -> Bool)
-> (TypeSym -> TypeSym -> Bool)
-> (TypeSym -> TypeSym -> Bool)
-> (TypeSym -> TypeSym -> Bool)
-> (TypeSym -> TypeSym -> TypeSym)
-> (TypeSym -> TypeSym -> TypeSym)
-> Ord TypeSym
TypeSym -> TypeSym -> Bool
TypeSym -> TypeSym -> Ordering
TypeSym -> TypeSym -> TypeSym
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeSym -> TypeSym -> TypeSym
$cmin :: TypeSym -> TypeSym -> TypeSym
max :: TypeSym -> TypeSym -> TypeSym
$cmax :: TypeSym -> TypeSym -> TypeSym
>= :: TypeSym -> TypeSym -> Bool
$c>= :: TypeSym -> TypeSym -> Bool
> :: TypeSym -> TypeSym -> Bool
$c> :: TypeSym -> TypeSym -> Bool
<= :: TypeSym -> TypeSym -> Bool
$c<= :: TypeSym -> TypeSym -> Bool
< :: TypeSym -> TypeSym -> Bool
$c< :: TypeSym -> TypeSym -> Bool
compare :: TypeSym -> TypeSym -> Ordering
$ccompare :: TypeSym -> TypeSym -> Ordering
$cp1Ord :: Eq TypeSym
Ord,Int -> TypeSym
TypeSym -> Int
TypeSym -> [TypeSym]
TypeSym -> TypeSym
TypeSym -> TypeSym -> [TypeSym]
TypeSym -> TypeSym -> TypeSym -> [TypeSym]
(TypeSym -> TypeSym)
-> (TypeSym -> TypeSym)
-> (Int -> TypeSym)
-> (TypeSym -> Int)
-> (TypeSym -> [TypeSym])
-> (TypeSym -> TypeSym -> [TypeSym])
-> (TypeSym -> TypeSym -> [TypeSym])
-> (TypeSym -> TypeSym -> TypeSym -> [TypeSym])
-> Enum TypeSym
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TypeSym -> TypeSym -> TypeSym -> [TypeSym]
$cenumFromThenTo :: TypeSym -> TypeSym -> TypeSym -> [TypeSym]
enumFromTo :: TypeSym -> TypeSym -> [TypeSym]
$cenumFromTo :: TypeSym -> TypeSym -> [TypeSym]
enumFromThen :: TypeSym -> TypeSym -> [TypeSym]
$cenumFromThen :: TypeSym -> TypeSym -> [TypeSym]
enumFrom :: TypeSym -> [TypeSym]
$cenumFrom :: TypeSym -> [TypeSym]
fromEnum :: TypeSym -> Int
$cfromEnum :: TypeSym -> Int
toEnum :: Int -> TypeSym
$ctoEnum :: Int -> TypeSym
pred :: TypeSym -> TypeSym
$cpred :: TypeSym -> TypeSym
succ :: TypeSym -> TypeSym
$csucc :: TypeSym -> TypeSym
Enum,TypeSym
TypeSym -> TypeSym -> Bounded TypeSym
forall a. a -> a -> Bounded a
maxBound :: TypeSym
$cmaxBound :: TypeSym
minBound :: TypeSym
$cminBound :: TypeSym
Bounded,ReadPrec [TypeSym]
ReadPrec TypeSym
Int -> ReadS TypeSym
ReadS [TypeSym]
(Int -> ReadS TypeSym)
-> ReadS [TypeSym]
-> ReadPrec TypeSym
-> ReadPrec [TypeSym]
-> Read TypeSym
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeSym]
$creadListPrec :: ReadPrec [TypeSym]
readPrec :: ReadPrec TypeSym
$creadPrec :: ReadPrec TypeSym
readList :: ReadS [TypeSym]
$creadList :: ReadS [TypeSym]
readsPrec :: Int -> ReadS TypeSym
$creadsPrec :: Int -> ReadS TypeSym
Read,Int -> TypeSym -> ShowS
[TypeSym] -> ShowS
TypeSym -> String
(Int -> TypeSym -> ShowS)
-> (TypeSym -> String) -> ([TypeSym] -> ShowS) -> Show TypeSym
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeSym] -> ShowS
$cshowList :: [TypeSym] -> ShowS
show :: TypeSym -> String
$cshow :: TypeSym -> String
showsPrec :: Int -> TypeSym -> ShowS
$cshowsPrec :: Int -> TypeSym -> ShowS
Show)

-- | Convert  symbolic 'TypeSym' to numeric 'Type' code
typeFromSym :: TypeSym -> Type
typeFromSym :: TypeSym -> Type
typeFromSym ts :: TypeSym
ts = Word16 -> Type
Type (Word16 -> Type) -> Word16 -> Type
forall a b. (a -> b) -> a -> b
$ case TypeSym
ts of
                  TypeA          -> 1
                  TypeNS         -> 2
                  TypeCNAME      -> 5
                  TypeSOA        -> 6
                  TypePTR        -> 12
                  TypeHINFO      -> 13
                  TypeMX         -> 15
                  TypeTXT        -> 16
                  TypeAFSDB      -> 18
                  TypeAAAA       -> 28
                  TypeSRV        -> 33
                  TypeNAPTR      -> 35
                  TypeOPT        -> 41
                  TypeDS         -> 43
                  TypeSSHFP      -> 44
                  TypeRRSIG      -> 46
                  TypeNSEC       -> 47
                  TypeDNSKEY     -> 48
                  TypeNSEC3      -> 50
                  TypeNSEC3PARAM -> 51
                  TypeSPF        -> 99
                  TypeANY        -> 255
                  TypeURI        -> 256
                  TypeCAA        -> 257

-- | Convert 'Type' code to symbolic 'TypeSym'
typeToSym :: Type -> Maybe TypeSym
typeToSym :: Type -> Maybe TypeSym
typeToSym (Type w :: Word16
w) = case Word16
w of
                  1   -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeA
                  2   -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeNS
                  5   -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeCNAME
                  6   -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeSOA
                  12  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypePTR
                  13  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeHINFO
                  15  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeMX
                  16  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeTXT
                  18  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeAFSDB
                  28  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeAAAA
                  33  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeSRV
                  35  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeNAPTR
                  41  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeOPT
                  43  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeDS
                  44  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeSSHFP
                  46  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeRRSIG
                  47  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeNSEC
                  48  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeDNSKEY
                  50  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeNSEC3
                  51  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeNSEC3PARAM
                  99  -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeSPF
                  255 -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeANY
                  256 -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeURI
                  257 -> TypeSym -> Maybe TypeSym
forall a. a -> Maybe a
Just TypeSym
TypeCAA
                  _   -> Maybe TypeSym
forall a. Maybe a
Nothing

-- | Extract the resource record type of a 'RData' object
rdType :: RData l -> Either Type TypeSym
rdType :: RData l -> Either Type TypeSym
rdType rd :: RData l
rd = case RData l
rd of
              RDataA          {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeA
              RDataAAAA       {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeAAAA
              RDataAFSDB      {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeAFSDB
              RDataCAA        {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeCAA
              RDataCNAME      {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeCNAME
              RDataDNSKEY     {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeDNSKEY
              RDataDS         {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeDS
              RDataHINFO      {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeHINFO
              RDataMX         {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeMX
              RDataNAPTR      {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeNAPTR
              RDataNS         {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeNS
              RDataNSEC       {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeNSEC
              RDataNSEC3      {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeNSEC3
              RDataNSEC3PARAM {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeNSEC3PARAM
              RDataOPT        {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeOPT
              RDataPTR        {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypePTR
              RDataRRSIG      {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeRRSIG
              RDataSOA        {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeSOA
              RDataSRV        {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeSRV
              RDataTXT        {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeTXT
              RDataSPF        {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeSPF
              RDataURI        {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeURI
              RDataSSHFP      {} -> TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right TypeSym
TypeSSHFP
              --
              RData        ty :: Type
ty _  -> Either Type TypeSym
-> (TypeSym -> Either Type TypeSym)
-> Maybe TypeSym
-> Either Type TypeSym
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Type -> Either Type TypeSym
forall a b. a -> Either a b
Left Type
ty) TypeSym -> Either Type TypeSym
forall a b. b -> Either a b
Right (Type -> Maybe TypeSym
typeToSym Type
ty)


{- TODO:


type-bitmap:

 A NS SOA TXT AAAA RRSIG NSEC DNSKEY

'00 07 62 00 80 08 00 03 80'
'00000000 00000111 01100010 00000000 10000000 00001000 00000000 00000011 10000000'
 Win=#0    len=7         ^{SOA}      ^{TXT}       ^{AAAA}                ^{DNSKEY}
                    ^^{A,NS}                                          ^^{RRSIG,NSEC}

" ".join(map("{:08b}".format,[0,7,98,0,128,8,0,3,128]))


"\NUL\a\"\NUL\NUL\NUL\NUL\ETX\128"   NS SOA RRSIG NSEC DNSKEY

[ (winofs+j*8+7-i)   | (j,x) <- zip [0..] xs, i <- [7,6..0], testBit x i ]

-}



-- helpers

getUntilEmpty :: Binary a => Get [a]
getUntilEmpty :: Get [a]
getUntilEmpty = Get a -> Get [a]
forall a. Get a -> Get [a]
untilEmptyWith Get a
forall t. Binary t => Get t
get

untilEmptyWith :: Get a -> Get [a]
untilEmptyWith :: Get a -> Get [a]
untilEmptyWith g :: Get a
g = [a] -> Get [a]
go []
  where
    go :: [a] -> Get [a]
go acc :: [a]
acc = do
        Bool
e <- Get Bool
isEmpty
        if Bool
e
         then [a] -> Get [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([a] -> [a]
forall a. [a] -> [a]
reverse [a]
acc)
         else do
            a
v <- Get a
g
            [a] -> Get [a]
go (a
v a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
acc)



{- TODO:


   MsgRR{rrName = Name "stanford.edu.", rrClass = 1, rrTTL = 1799,
         rrData =
           RData 29
             "\NUL\DC2\SYN\DC3\136\a\244\212e\200\252\194\NUL\152\150\128"},


https://en.wikipedia.org/wiki/LOC_record


LOC record statdns.net.   IN LOC   52 22 23.000 N 4 53 32.000 E -2.00m 0.00m 10000m 10m


SW1A2AA.find.me.uk.	86399	IN	LOC	51 30 12.748 N 0 7 39.611 W 0.00m 0.00m 0.00m 0.00m


https://tools.ietf.org/html/rfc1876

-}