{-# LANGUAGE BangPatterns, LambdaCase, OverloadedStrings #-}

module Network.DNS.Decode.Parsers (
    getResponse
  , getDNSFlags
  , getHeader
  , getResourceRecord
  , getResourceRecords
  , getDomain
  , getMailbox
  ) where

import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BS
import qualified Data.CaseInsensitive as CI
import qualified Data.IP
import Data.IP (IP(..), toIPv4, toIPv6b, makeAddrRange)

import Network.DNS.Imports
import Network.DNS.StateBinary
import Network.DNS.Types.Internal

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

getResponse :: SGet DNSMessage
getResponse :: SGet DNSMessage
getResponse = do
    DNSHeader
hm <- SGet DNSHeader
getHeader
    Int
qdCount <- SGet Int
getInt16
    Int
anCount <- SGet Int
getInt16
    Int
nsCount <- SGet Int
getInt16
    Int
arCount <- SGet Int
getInt16
    [Question]
queries <- Int -> SGet [Question]
getQueries Int
qdCount
    [ResourceRecord]
answers <- Int -> SGet [ResourceRecord]
getResourceRecords Int
anCount
    [ResourceRecord]
authrrs <- Int -> SGet [ResourceRecord]
getResourceRecords Int
nsCount
    [ResourceRecord]
addnrrs <- Int -> SGet [ResourceRecord]
getResourceRecords Int
arCount
    let ([ResourceRecord]
opts, [ResourceRecord]
rest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition (forall a. Eq a => a -> a -> Bool
(==) TYPE
OPTforall b c a. (b -> c) -> (a -> b) -> a -> c
. ResourceRecord -> TYPE
rrtype) [ResourceRecord]
addnrrs
        flgs :: DNSFlags
flgs         = DNSHeader -> DNSFlags
flags DNSHeader
hm
        rc :: Word16
rc           = RCODE -> Word16
fromRCODE forall a b. (a -> b) -> a -> b
$ DNSFlags -> RCODE
rcode DNSFlags
flgs
        (EDNSheader
eh, RCODE
erc)    = Word16 -> [ResourceRecord] -> (EDNSheader, RCODE)
getEDNS Word16
rc [ResourceRecord]
opts
        hd :: DNSHeader
hd           = DNSHeader
hm { flags :: DNSFlags
flags = DNSFlags
flgs { rcode :: RCODE
rcode = RCODE
erc } }
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DNSHeader
-> EDNSheader
-> [Question]
-> [ResourceRecord]
-> [ResourceRecord]
-> [ResourceRecord]
-> DNSMessage
DNSMessage DNSHeader
hd EDNSheader
eh [Question]
queries [ResourceRecord]
answers [ResourceRecord]
authrrs forall a b. (a -> b) -> a -> b
$ forall a. EDNSheader -> a -> a -> a
ifEDNS EDNSheader
eh [ResourceRecord]
rest [ResourceRecord]
addnrrs

  where

    -- | Get EDNS pseudo-header and the high eight bits of the extended RCODE.
    --
    getEDNS :: Word16 -> AdditionalRecords -> (EDNSheader, RCODE)
    getEDNS :: Word16 -> [ResourceRecord] -> (EDNSheader, RCODE)
getEDNS Word16
rc [ResourceRecord]
rrs = case [ResourceRecord]
rrs of
        [ResourceRecord
rr] | Just (EDNS
edns, Word16
erc) <- ResourceRecord -> Maybe (EDNS, Word16)
optEDNS ResourceRecord
rr
               -> (EDNS -> EDNSheader
EDNSheader EDNS
edns, Word16 -> RCODE
toRCODE Word16
erc)
        []     -> (EDNSheader
NoEDNS, Word16 -> RCODE
toRCODE Word16
rc)
        [ResourceRecord]
_      -> (EDNSheader
InvalidEDNS, RCODE
BadRCODE)

      where

        -- | Extract EDNS information from an OPT RR.
        --
        optEDNS :: ResourceRecord -> Maybe (EDNS, Word16)
        optEDNS :: ResourceRecord -> Maybe (EDNS, Word16)
optEDNS (ResourceRecord ByteString
"." TYPE
OPT Word16
udpsiz TTL
ttl' (RD_OPT [OData]
opts)) =
            let hrc :: TTL
hrc      = forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
rc forall a. Bits a => a -> a -> a
.&. TTL
0x0f
                erc :: TTL
erc      = forall a. Bits a => a -> Int -> a
shiftR (TTL
ttl' forall a. Bits a => a -> a -> a
.&. TTL
0xff000000) Int
20 forall a. Bits a => a -> a -> a
.|. TTL
hrc
                secok :: Bool
secok    = TTL
ttl' forall a. Bits a => a -> Int -> Bool
`testBit` Int
15
                vers :: Word8
vers     = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. Bits a => a -> Int -> a
shiftR (TTL
ttl' forall a. Bits a => a -> a -> a
.&. TTL
0x00ff0000) Int
16
             in forall a. a -> Maybe a
Just (Word8 -> Word16 -> Bool -> [OData] -> EDNS
EDNS Word8
vers Word16
udpsiz Bool
secok [OData]
opts, forall a b. (Integral a, Num b) => a -> b
fromIntegral TTL
erc)
        optEDNS ResourceRecord
_ = forall a. Maybe a
Nothing

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

getDNSFlags :: SGet DNSFlags
getDNSFlags :: SGet DNSFlags
getDNSFlags = do
    Word16
flgs <- SGet Word16
get16
    OPCODE
oc <- Word16 -> StateT PState (Parser ByteString) OPCODE
getOpcode Word16
flgs
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ QorR
-> OPCODE
-> Bool
-> Bool
-> Bool
-> Bool
-> RCODE
-> Bool
-> Bool
-> DNSFlags
DNSFlags (forall {a}. Bits a => a -> QorR
getQorR Word16
flgs)
                      OPCODE
oc
                      (forall {a}. Bits a => a -> Bool
getAuthAnswer Word16
flgs)
                      (forall {a}. Bits a => a -> Bool
getTrunCation Word16
flgs)
                      (forall {a}. Bits a => a -> Bool
getRecDesired Word16
flgs)
                      (forall {a}. Bits a => a -> Bool
getRecAvailable Word16
flgs)
                      (Word16 -> RCODE
getRcode Word16
flgs)
                      (forall {a}. Bits a => a -> Bool
getAuthenData Word16
flgs)
                      (forall {a}. Bits a => a -> Bool
getChkDisable Word16
flgs)
  where
    getQorR :: a -> QorR
getQorR a
w = if forall a. Bits a => a -> Int -> Bool
testBit a
w Int
15 then QorR
QR_Response else QorR
QR_Query
    getOpcode :: Word16 -> StateT PState (Parser ByteString) OPCODE
getOpcode Word16
w =
        case forall a. Bits a => a -> Int -> a
shiftR Word16
w Int
11 forall a. Bits a => a -> a -> a
.&. Word16
0x0f of
            Word16
n | Just OPCODE
opc <- Word16 -> Maybe OPCODE
toOPCODE Word16
n
              -> forall (f :: * -> *) a. Applicative f => a -> f a
pure OPCODE
opc
              | Bool
otherwise
              -> forall a. [Char] -> SGet a
failSGet forall a b. (a -> b) -> a -> b
$ [Char]
"Unsupported header opcode: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Word16
n
    getAuthAnswer :: a -> Bool
getAuthAnswer a
w = forall a. Bits a => a -> Int -> Bool
testBit a
w Int
10
    getTrunCation :: a -> Bool
getTrunCation a
w = forall a. Bits a => a -> Int -> Bool
testBit a
w Int
9
    getRecDesired :: a -> Bool
getRecDesired a
w = forall a. Bits a => a -> Int -> Bool
testBit a
w Int
8
    getRecAvailable :: a -> Bool
getRecAvailable a
w = forall a. Bits a => a -> Int -> Bool
testBit a
w Int
7
    getRcode :: Word16 -> RCODE
getRcode Word16
w = Word16 -> RCODE
toRCODE forall a b. (a -> b) -> a -> b
$ Word16
w forall a. Bits a => a -> a -> a
.&. Word16
0x0f
    getAuthenData :: a -> Bool
getAuthenData a
w = forall a. Bits a => a -> Int -> Bool
testBit a
w Int
5
    getChkDisable :: a -> Bool
getChkDisable a
w = forall a. Bits a => a -> Int -> Bool
testBit a
w Int
4

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

getHeader :: SGet DNSHeader
getHeader :: SGet DNSHeader
getHeader =
    Word16 -> DNSFlags -> DNSHeader
DNSHeader forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word16
decodeIdentifier forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet DNSFlags
getDNSFlags
  where
    decodeIdentifier :: SGet Word16
decodeIdentifier = SGet Word16
get16

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

getQueries :: Int -> SGet [Question]
getQueries :: Int -> SGet [Question]
getQueries Int
n = forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n SGet Question
getQuery

getTYPE :: SGet TYPE
getTYPE :: SGet TYPE
getTYPE = Word16 -> TYPE
toTYPE forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word16
get16

-- XXX: Include the class when implemented, or otherwise perhaps check the
-- implicit assumption that the class is classIN.
--
getQuery :: SGet Question
getQuery :: SGet Question
getQuery = ByteString -> TYPE -> Question
Question forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet ByteString
getDomain
                    forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet TYPE
getTYPE
                    forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<*  SGet Word16
ignoreClass
  where
    ignoreClass :: SGet Word16
ignoreClass = SGet Word16
get16

getResourceRecords :: Int -> SGet [ResourceRecord]
getResourceRecords :: Int -> SGet [ResourceRecord]
getResourceRecords Int
n = forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n SGet ResourceRecord
getResourceRecord

getResourceRecord :: SGet ResourceRecord
getResourceRecord :: SGet ResourceRecord
getResourceRecord = do
    ByteString
dom <- SGet ByteString
getDomain
    TYPE
typ <- SGet TYPE
getTYPE
    Word16
cls <- SGet Word16
get16
    TTL
ttl <- SGet TTL
get32
    Int
len <- SGet Int
getInt16
    RData
dat <- forall a. Int -> SGet a -> SGet a
fitSGet Int
len forall a b. (a -> b) -> a -> b
$ TYPE -> Int -> SGet RData
getRData TYPE
typ Int
len
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ByteString -> TYPE -> Word16 -> TTL -> RData -> ResourceRecord
ResourceRecord ByteString
dom TYPE
typ Word16
cls TTL
ttl RData
dat

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

-- | Helper to find position of RData end, that is, the offset of the first
-- byte /after/ the current RData.
--
rdataEnd :: Int      -- ^ number of bytes left from current position
         -> SGet Int -- ^ end position
rdataEnd :: Int -> SGet Int
rdataEnd !Int
len = forall a. Num a => a -> a -> a
(+) Int
len forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Int
getPosition

getRData :: TYPE -> Int -> SGet RData
getRData :: TYPE -> Int -> SGet RData
getRData TYPE
NS Int
_    = ByteString -> RData
RD_NS    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet ByteString
getDomain
getRData TYPE
MX Int
_    = Word16 -> ByteString -> RData
RD_MX    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word16
get16 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
getDomain
getRData TYPE
CNAME Int
_ = ByteString -> RData
RD_CNAME forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet ByteString
getDomain
getRData TYPE
DNAME Int
_ = ByteString -> RData
RD_DNAME forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet ByteString
getDomain
getRData TYPE
TXT Int
len = ByteString -> RData
RD_TXT   forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet ByteString
getTXT Int
len
getRData TYPE
A Int
_     = IPv4 -> RData
RD_A forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> IPv4
toIPv4 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet [Int]
getNBytes Int
4
getRData TYPE
AAAA Int
_  = IPv6 -> RData
RD_AAAA forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> IPv6
toIPv6b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet [Int]
getNBytes Int
16
getRData TYPE
SOA Int
_   = ByteString
-> ByteString -> TTL -> TTL -> TTL -> TTL -> TTL -> RData
RD_SOA  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet ByteString
getDomain
                           forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
getMailbox
                           forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet TTL
decodeSerial
                           forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet TTL
decodeRefesh
                           forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet TTL
decodeRetry
                           forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet TTL
decodeExpire
                           forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet TTL
decodeMinimum
  where
    decodeSerial :: SGet TTL
decodeSerial  = SGet TTL
get32
    decodeRefesh :: SGet TTL
decodeRefesh  = SGet TTL
get32
    decodeRetry :: SGet TTL
decodeRetry   = SGet TTL
get32
    decodeExpire :: SGet TTL
decodeExpire  = SGet TTL
get32
    decodeMinimum :: SGet TTL
decodeMinimum = SGet TTL
get32
getRData TYPE
PTR Int
_ = ByteString -> RData
RD_PTR forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet ByteString
getDomain
getRData TYPE
SRV Int
_ = Word16 -> Word16 -> Word16 -> ByteString -> RData
RD_SRV forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word16
decodePriority
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word16
decodeWeight
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word16
decodePort
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
getDomain
  where
    decodePriority :: SGet Word16
decodePriority = SGet Word16
get16
    decodeWeight :: SGet Word16
decodeWeight   = SGet Word16
get16
    decodePort :: SGet Word16
decodePort     = SGet Word16
get16
--
getRData TYPE
RP Int
_   = ByteString -> ByteString -> RData
RD_RP forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet ByteString
getMailbox
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
getDomain
--
getRData TYPE
OPT Int
len   = [OData] -> RData
RD_OPT forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet [OData]
getOpts Int
len
--
getRData TYPE
TLSA Int
len = Word8 -> Word8 -> Word8 -> ByteString -> RData
RD_TLSA forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word8
decodeUsage
                            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeSelector
                            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeMType
                            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
decodeADF
  where
    decodeUsage :: SGet Word8
decodeUsage    = SGet Word8
get8
    decodeSelector :: SGet Word8
decodeSelector = SGet Word8
get8
    decodeMType :: SGet Word8
decodeMType    = SGet Word8
get8
    decodeADF :: SGet ByteString
decodeADF      = Int -> SGet ByteString
getNByteString (Int
len forall a. Num a => a -> a -> a
- Int
3)
--
getRData TYPE
DS Int
len = Word16 -> Word8 -> Word8 -> ByteString -> RData
RD_DS forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word16
decodeTag
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeAlg
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeDtyp
                        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
decodeDval
  where
    decodeTag :: SGet Word16
decodeTag  = SGet Word16
get16
    decodeAlg :: SGet Word8
decodeAlg  = SGet Word8
get8
    decodeDtyp :: SGet Word8
decodeDtyp = SGet Word8
get8
    decodeDval :: SGet ByteString
decodeDval = Int -> SGet ByteString
getNByteString (Int
len forall a. Num a => a -> a -> a
- Int
4)
--
getRData TYPE
CDS Int
len = Word16 -> Word8 -> Word8 -> ByteString -> RData
RD_CDS forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word16
decodeTag
                          forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeAlg
                          forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeDtyp
                          forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
decodeDval
  where
    decodeTag :: SGet Word16
decodeTag  = SGet Word16
get16
    decodeAlg :: SGet Word8
decodeAlg  = SGet Word8
get8
    decodeDtyp :: SGet Word8
decodeDtyp = SGet Word8
get8
    decodeDval :: SGet ByteString
decodeDval = Int -> SGet ByteString
getNByteString (Int
len forall a. Num a => a -> a -> a
- Int
4)
--
getRData TYPE
RRSIG Int
len = RD_RRSIG -> RData
RD_RRSIG forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT PState (Parser ByteString) RD_RRSIG
decodeRRSIG
  where
    decodeRRSIG :: StateT PState (Parser ByteString) RD_RRSIG
decodeRRSIG = do
        -- The signature follows a variable length zone name
        -- and occupies the rest of the RData.  Simplest to
        -- checkpoint the position at the start of the RData,
        -- and after reading the zone name, and subtract that
        -- from the RData length.
        --
        Int
end <- Int -> SGet Int
rdataEnd Int
len
        TYPE
typ <- SGet TYPE
getTYPE
        Word8
alg <- SGet Word8
get8
        Word8
cnt <- SGet Word8
get8
        TTL
ttl <- SGet TTL
get32
        Int64
tex <- StateT PState (Parser ByteString) Int64
getDnsTime
        Int64
tin <- StateT PState (Parser ByteString) Int64
getDnsTime
        Word16
tag <- SGet Word16
get16
        ByteString
dom <- SGet ByteString
getDomain -- XXX: Enforce no compression?
        Int
pos <- SGet Int
getPosition
        ByteString
val <- Int -> SGet ByteString
getNByteString forall a b. (a -> b) -> a -> b
$ Int
end forall a. Num a => a -> a -> a
- Int
pos
        forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ TYPE
-> Word8
-> Word8
-> TTL
-> Int64
-> Int64
-> Word16
-> ByteString
-> ByteString
-> RD_RRSIG
RDREP_RRSIG TYPE
typ Word8
alg Word8
cnt TTL
ttl Int64
tex Int64
tin Word16
tag ByteString
dom ByteString
val
    getDnsTime :: StateT PState (Parser ByteString) Int64
getDnsTime   = do
        Int64
tnow <- StateT PState (Parser ByteString) Int64
getAtTime
        TTL
tdns <- SGet TTL
get32
        forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! TTL -> Int64 -> Int64
dnsTime TTL
tdns Int64
tnow
--
getRData TYPE
NULL Int
len = ByteString -> RData
RD_NULL forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet ByteString
getNByteString Int
len
getRData TYPE
NSEC Int
len = do
    Int
end <- Int -> SGet Int
rdataEnd Int
len
    ByteString
dom <- SGet ByteString
getDomain
    Int
pos <- SGet Int
getPosition
    ByteString -> [TYPE] -> RData
RD_NSEC ByteString
dom forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet [TYPE]
getNsecTypes (Int
end forall a. Num a => a -> a -> a
- Int
pos)
--
getRData TYPE
DNSKEY Int
len = Word16 -> Word8 -> Word8 -> ByteString -> RData
RD_DNSKEY forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word16
decodeKeyFlags
                                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeKeyProto
                                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeKeyAlg
                                forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
decodeKeyBytes
  where
    decodeKeyFlags :: SGet Word16
decodeKeyFlags  = SGet Word16
get16
    decodeKeyProto :: SGet Word8
decodeKeyProto  = SGet Word8
get8
    decodeKeyAlg :: SGet Word8
decodeKeyAlg    = SGet Word8
get8
    decodeKeyBytes :: SGet ByteString
decodeKeyBytes  = Int -> SGet ByteString
getNByteString (Int
len forall a. Num a => a -> a -> a
- Int
4)
--
getRData TYPE
CDNSKEY Int
len = Word16 -> Word8 -> Word8 -> ByteString -> RData
RD_CDNSKEY forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word16
decodeKeyFlags
                                  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeKeyProto
                                  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeKeyAlg
                                  forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
decodeKeyBytes
  where
    decodeKeyFlags :: SGet Word16
decodeKeyFlags  = SGet Word16
get16
    decodeKeyProto :: SGet Word8
decodeKeyProto  = SGet Word8
get8
    decodeKeyAlg :: SGet Word8
decodeKeyAlg    = SGet Word8
get8
    decodeKeyBytes :: SGet ByteString
decodeKeyBytes  = Int -> SGet ByteString
getNByteString (Int
len forall a. Num a => a -> a -> a
- Int
4)
--
getRData TYPE
NSEC3 Int
len = do
    Int
dend <- Int -> SGet Int
rdataEnd Int
len
    Word8
halg <- SGet Word8
get8
    Word8
flgs <- SGet Word8
get8
    Word16
iter <- SGet Word16
get16
    ByteString
salt <- SGet Int
getInt8 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> SGet ByteString
getNByteString
    ByteString
hash <- SGet Int
getInt8 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> SGet ByteString
getNByteString
    Int
tpos <- SGet Int
getPosition
    Word8
-> Word8 -> Word16 -> ByteString -> ByteString -> [TYPE] -> RData
RD_NSEC3 Word8
halg Word8
flgs Word16
iter ByteString
salt ByteString
hash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet [TYPE]
getNsecTypes (Int
dend forall a. Num a => a -> a -> a
- Int
tpos)
--
getRData TYPE
NSEC3PARAM Int
_ = Word8 -> Word8 -> Word16 -> ByteString -> RData
RD_NSEC3PARAM forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word8
decodeHashAlg
                                      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word8
decodeFlags
                                      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet Word16
decodeIterations
                                      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SGet ByteString
decodeSalt
  where
    decodeHashAlg :: SGet Word8
decodeHashAlg    = SGet Word8
get8
    decodeFlags :: SGet Word8
decodeFlags      = SGet Word8
get8
    decodeIterations :: SGet Word16
decodeIterations = SGet Word16
get16
    decodeSalt :: SGet ByteString
decodeSalt       = SGet Int
getInt8 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> SGet ByteString
getNByteString
--
getRData TYPE
CAA Int
len = do
    Int
dend <- Int -> SGet Int
rdataEnd Int
len
    Word8
flags <- SGet Word8
get8
    ByteString
tag <- SGet Int
getInt8 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> SGet ByteString
getNByteString
    Int
tpos <- SGet Int
getPosition
    Word8 -> CI ByteString -> ByteString -> RData
RD_CAA Word8
flags (forall s. FoldCase s => s -> CI s
CI.mk ByteString
tag) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet ByteString
getNByteString (Int
dend forall a. Num a => a -> a -> a
- Int
tpos)
--
getRData TYPE
_  Int
len = ByteString -> RData
UnknownRData forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet ByteString
getNByteString Int
len

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

-- $
--
-- >>> import Network.DNS.StateBinary
-- >>> let Right ((t,_),l) = runSGetWithLeftovers (getTXT 8) "\3foo\3barbaz"
-- >>> (t, l) == ("foobar", "baz")
-- True

-- | Concatenate a sequence of length-prefixed strings of text
-- https://tools.ietf.org/html/rfc1035#section-3.3
--
getTXT :: Int -> SGet ByteString
getTXT :: Int -> SGet ByteString
getTXT !Int
len = [ByteString] -> ByteString
B.concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. [Char] -> Int -> SGet a -> SGet [a]
sGetMany [Char]
"TXT RR string" Int
len SGet ByteString
getstring
  where
    getstring :: SGet ByteString
getstring = SGet Int
getInt8 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> SGet ByteString
getNByteString

-- <https://tools.ietf.org/html/rfc6891#section-6.1.2>
-- Parse a list of EDNS options
--
getOpts :: Int -> SGet [OData]
getOpts :: Int -> SGet [OData]
getOpts !Int
len = forall a. [Char] -> Int -> SGet a -> SGet [a]
sGetMany [Char]
"EDNS option" Int
len StateT PState (Parser ByteString) OData
getoption
  where
    getoption :: StateT PState (Parser ByteString) OData
getoption = do
        OptCode
code <- Word16 -> OptCode
toOptCode forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Word16
get16
        Int
olen <- SGet Int
getInt16
        OptCode -> Int -> StateT PState (Parser ByteString) OData
getOData OptCode
code Int
olen

-- <https://tools.ietf.org/html/rfc4034#section-4.1>
-- Parse a list of NSEC type bitmaps
--
getNsecTypes :: Int -> SGet [TYPE]
getNsecTypes :: Int -> SGet [TYPE]
getNsecTypes !Int
len = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. [Char] -> Int -> SGet a -> SGet [a]
sGetMany [Char]
"NSEC type bitmap" Int
len SGet [TYPE]
getbits
  where
    getbits :: SGet [TYPE]
getbits = do
        Int
window <- forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Bits a => a -> Int -> a
shiftL Int
8 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SGet Int
getInt8
        Int
blocks <- SGet Int
getInt8
        forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
blocks forall a. Ord a => a -> a -> Bool
> Int
32) forall a b. (a -> b) -> a -> b
$
            forall a. [Char] -> SGet a
failSGet forall a b. (a -> b) -> a -> b
$ [Char]
"NSEC bitmap block too long: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Int
blocks
        forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {a}. (Bits a, Num a) => (Int, a) -> [TYPE]
blkTypesforall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [a] -> [b] -> [(a, b)]
zip [Int
window, Int
window forall a. Num a => a -> a -> a
+ Int
8..] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet [Int]
getNBytes Int
blocks
      where
        blkTypes :: (Int, a) -> [TYPE]
blkTypes (Int
bitOffset, a
byte) =
            [ Word16 -> TYPE
toTYPE forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
bitOffset forall a. Num a => a -> a -> a
+ Int
i |
              Int
i <- [Int
0..Int
7], a
byte forall a. Bits a => a -> a -> a
.&. forall a. Bits a => Int -> a
bit (Int
7forall a. Num a => a -> a -> a
-Int
i) forall a. Eq a => a -> a -> Bool
/= a
0 ]

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

getOData :: OptCode -> Int -> SGet OData
getOData :: OptCode -> Int -> StateT PState (Parser ByteString) OData
getOData OptCode
NSID Int
len = ByteString -> OData
OD_NSID forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet ByteString
getNByteString Int
len
getOData OptCode
DAU  Int
len = [Word8] -> OData
OD_DAU  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet [Word8]
getNoctets Int
len
getOData OptCode
DHU  Int
len = [Word8] -> OData
OD_DHU  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet [Word8]
getNoctets Int
len
getOData OptCode
N3U  Int
len = [Word8] -> OData
OD_N3U  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet [Word8]
getNoctets Int
len
getOData OptCode
ClientSubnet Int
len = do
        Word16
family  <- SGet Word16
get16
        Word8
srcBits <- SGet Word8
get8
        Word8
scpBits <- SGet Word8
get8
        ByteString
addrbs  <- Int -> SGet ByteString
getNByteString (Int
len forall a. Num a => a -> a -> a
- Int
4) -- 4 = 2 + 1 + 1
        --
        -- https://tools.ietf.org/html/rfc7871#section-6
        --
        -- o  ADDRESS, variable number of octets, contains either an IPv4 or
        --    IPv6 address, depending on FAMILY, which MUST be truncated to the
        --    number of bits indicated by the SOURCE PREFIX-LENGTH field,
        --    padding with 0 bits to pad to the end of the last octet needed.
        --
        -- o  A server receiving an ECS option that uses either too few or too
        --    many ADDRESS octets, or that has non-zero ADDRESS bits set beyond
        --    SOURCE PREFIX-LENGTH, SHOULD return FORMERR to reject the packet,
        --    as a signal to the software developer making the request to fix
        --    their implementation.
        --
        -- In order to avoid needless decoding errors, when the ECS encoding
        -- requirements are violated, we construct an OD_ECSgeneric OData,
        -- instread of an IP-specific OD_ClientSubnet OData, which will only
        -- be used for valid inputs.  When the family is neither IPv4(1) nor
        -- IPv6(2), or the address prefix is not correctly encoded (too long
        -- or too short), the OD_ECSgeneric data contains the verbatim input
        -- from the peer.
        --
        case ByteString -> Int
BS.length ByteString
addrbs forall a. Eq a => a -> a -> Bool
== (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
srcBits forall a. Num a => a -> a -> a
+ Int
7) forall a. Integral a => a -> a -> a
`div` Int
8 of
            Bool
True | Just IP
ip <- Word16 -> ByteString -> Word8 -> Word8 -> Maybe IP
bstoip Word16
family ByteString
addrbs Word8
srcBits Word8
scpBits
                -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word8 -> Word8 -> IP -> OData
OD_ClientSubnet Word8
srcBits Word8
scpBits IP
ip
            Bool
_   -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word16 -> Word8 -> Word8 -> ByteString -> OData
OD_ECSgeneric Word16
family Word8
srcBits Word8
scpBits ByteString
addrbs
  where
    prefix :: a -> a -> a
prefix a
addr a
bits = forall a. AddrRange a -> a
Data.IP.addr forall a b. (a -> b) -> a -> b
$ forall a. Addr a => a -> Int -> AddrRange a
makeAddrRange a
addr forall a b. (a -> b) -> a -> b
$ forall a b. (Integral a, Num b) => a -> b
fromIntegral a
bits
    zeropad :: ByteString -> [Int]
zeropad = (forall a. [a] -> [a] -> [a]
++ forall a. a -> [a]
repeat Int
0)forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegralforall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
B.unpack
    checkBits :: (t a -> t) -> (t -> a) -> p -> a -> t a -> Maybe a
checkBits t a -> t
fromBytes t -> a
toIP p
srcBits a
scpBits t a
bytes =
        let addr :: t
addr       = t a -> t
fromBytes t a
bytes
            maskedAddr :: t
maskedAddr = forall {a} {a}. (Addr a, Integral a) => a -> a -> a
prefix t
addr p
srcBits
            maxBits :: a
maxBits    = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Int
8 forall a. Num a => a -> a -> a
* forall (t :: * -> *) a. Foldable t => t a -> Int
length t a
bytes
         in if t
addr forall a. Eq a => a -> a -> Bool
== t
maskedAddr Bool -> Bool -> Bool
&& a
scpBits forall a. Ord a => a -> a -> Bool
<= a
maxBits
            then forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ t -> a
toIP t
addr
            else forall a. Maybe a
Nothing
    bstoip :: Word16 -> B.ByteString -> Word8 -> Word8 -> Maybe IP
    bstoip :: Word16 -> ByteString -> Word8 -> Word8 -> Maybe IP
bstoip Word16
family ByteString
bs Word8
srcBits Word8
scpBits = case Word16
family of
        Word16
1 -> forall {a} {t} {t :: * -> *} {p} {a} {a}.
(Ord a, Num a, Foldable t, Addr t, Integral p) =>
(t a -> t) -> (t -> a) -> p -> a -> t a -> Maybe a
checkBits [Int] -> IPv4
toIPv4  IPv4 -> IP
IPv4 Word8
srcBits Word8
scpBits forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
take Int
4  forall a b. (a -> b) -> a -> b
$ ByteString -> [Int]
zeropad ByteString
bs
        Word16
2 -> forall {a} {t} {t :: * -> *} {p} {a} {a}.
(Ord a, Num a, Foldable t, Addr t, Integral p) =>
(t a -> t) -> (t -> a) -> p -> a -> t a -> Maybe a
checkBits [Int] -> IPv6
toIPv6b IPv6 -> IP
IPv6 Word8
srcBits Word8
scpBits forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
take Int
16 forall a b. (a -> b) -> a -> b
$ ByteString -> [Int]
zeropad ByteString
bs
        Word16
_ -> forall a. Maybe a
Nothing
getOData OptCode
opc Int
len = Word16 -> ByteString -> OData
UnknownOData (OptCode -> Word16
fromOptCode OptCode
opc) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet ByteString
getNByteString Int
len

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

-- | Pointers MUST point back into the packet per RFC1035 Section 4.1.4.  This
-- is further interpreted by the DNS community (from a discussion on the IETF
-- DNSOP mailing list) to mean that they don't point back into the same domain.
-- Therefore, when starting to parse a domain, the current offset is also a
-- strict upper bound on the targets of any pointers that arise while processing
-- the domain.  When following a pointer, the target again becomes a stict upper
-- bound for any subsequent pointers.  This results in a simple loop-prevention
-- algorithm, each sequence of valid pointer values is necessarily strictly
-- decreasing!  The third argument to 'getDomain'' is a strict pointer upper
-- bound, and is set here to the position at the start of parsing the domain
-- or mailbox.
--
-- Note: the separator passed to 'getDomain'' is required to be either \'.\' or
-- \'\@\', or else 'unparseLabel' needs to be modified to handle the new value.
--

getDomain :: SGet Domain
getDomain :: SGet ByteString
getDomain = SGet Int
getPosition forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word8 -> Int -> SGet ByteString
getDomain' Word8
dot

getMailbox :: SGet Mailbox
getMailbox :: SGet ByteString
getMailbox = SGet Int
getPosition forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word8 -> Int -> SGet ByteString
getDomain' Word8
atsign

dot, atsign :: Word8
dot :: Word8
dot    = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum Char
'.' -- 46
atsign :: Word8
atsign = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> Int
fromEnum Char
'@' -- 64

-- $
-- Pathological case: pointer embedded inside a label!  The pointer points
-- behind the start of the domain and is then absorbed into the initial label!
-- Though we don't IMHO have to support this, it is not manifestly illegal, and
-- does exercise the code in an interesting way.  Ugly as this is, it also
-- "works" the same in Perl's Net::DNS and reportedly in ISC's BIND.
--
-- >>> :{
-- let input = "\6\3foo\192\0\3bar\0"
--     parser = skipNBytes 1 >> getDomain' dot 1
--     Right (output, _) = runSGet parser input
--  in output == "foo.\\003foo\\192\\000.bar."
-- :}
-- True
--
-- The case below fails to point far enough back, and triggers the loop
-- prevention code-path.
--
-- >>> :{
-- let input = "\6\3foo\192\1\3bar\0"
--     parser = skipNBytes 1 >> getDomain' dot 1
--     Left (DecodeError err) = runSGet parser input
--  in err
-- :}
-- "invalid name compression pointer"

-- | Get a domain name, using sep1 as the separator between the 1st and 2nd
-- label.  Subsequent labels (and always the trailing label) are terminated
-- with a ".".
--
-- Note: the separator is required to be either \'.\' or \'\@\', or else
-- 'unparseLabel' needs to be modified to handle the new value.
--
-- Domain name compression pointers must always refer to a position that
-- precedes the start of the current domain name.  The starting offsets form a
-- strictly decreasing sequence, which prevents pointer loops.
--
getDomain' :: Word8 -> Int -> SGet ByteString
getDomain' :: Word8 -> Int -> SGet ByteString
getDomain' Word8
sep1 Int
ptrLimit = do
    Int
pos <- SGet Int
getPosition
    Int
c <- SGet Int
getInt8
    let n :: Int
n = forall {a}. (Bits a, Num a) => a -> a
getValue Int
c
    forall {a}. (Num a, Bits a) => Int -> a -> Int -> SGet ByteString
getdomain Int
pos Int
c Int
n
  where
    -- Reprocess the same ByteString starting at the pointer
    -- target (offset).
    getPtr :: Int -> Int -> SGet ByteString
getPtr Int
pos Int
offset = do
        ByteString
msg <- SGet ByteString
getInput
        let parser :: SGet ByteString
parser = Int -> StateT PState (Parser ByteString) ()
skipNBytes Int
offset forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word8 -> Int -> SGet ByteString
getDomain' Word8
sep1 Int
offset
        case forall a. SGet a -> ByteString -> Either DNSError (a, PState)
runSGet SGet ByteString
parser ByteString
msg of
            Left (DecodeError [Char]
err) -> forall a. [Char] -> SGet a
failSGet [Char]
err
            Left DNSError
err               -> forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> [Char]
show DNSError
err
            Right (ByteString, PState)
o                -> do
                -- Cache only the presentation form decoding of domain names,
                -- mailboxes (e.g. SOA rname) are less frequently reused, and
                -- have a different presentation form, so must not share the
                -- same cache.
                forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Word8
sep1 forall a. Eq a => a -> a -> Bool
== Word8
dot) forall a b. (a -> b) -> a -> b
$
                    Int -> ByteString -> StateT PState (Parser ByteString) ()
push Int
pos (forall a b. (a, b) -> a
fst (ByteString, PState)
o)
                forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. (a, b) -> a
fst (ByteString, PState)
o)

    getdomain :: Int -> a -> Int -> SGet ByteString
getdomain Int
pos a
c Int
n
      | a
c forall a. Eq a => a -> a -> Bool
== a
0 = forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
"." -- Perhaps the root domain?
      | forall {a}. Bits a => a -> Bool
isPointer a
c = do
          Int
d <- SGet Int
getInt8
          let offset :: Int
offset = Int
n forall a. Num a => a -> a -> a
* Int
256 forall a. Num a => a -> a -> a
+ Int
d
          forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
offset forall a. Ord a => a -> a -> Bool
>= Int
ptrLimit) forall a b. (a -> b) -> a -> b
$
              forall a. [Char] -> SGet a
failSGet [Char]
"invalid name compression pointer"
          if Word8
sep1 forall a. Eq a => a -> a -> Bool
/= Word8
dot
              then Int -> Int -> SGet ByteString
getPtr Int
pos Int
offset
              else Int -> SGet (Maybe ByteString)
pop Int
offset forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
                  Maybe ByteString
Nothing -> Int -> Int -> SGet ByteString
getPtr Int
pos Int
offset
                  Just ByteString
o  -> forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
o
      -- As for now, extended labels have no use.
      -- This may change some time in the future.
      | forall {a}. Bits a => a -> Bool
isExtLabel a
c = forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
""
      | Bool
otherwise = do
          ByteString
hs <- Word8 -> ByteString -> ByteString
unparseLabel Word8
sep1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> SGet ByteString
getNByteString Int
n
          ByteString
ds <- Word8 -> Int -> SGet ByteString
getDomain' Word8
dot Int
ptrLimit
          let dom :: ByteString
dom = case ByteString
ds of -- avoid trailing ".."
                  ByteString
"." -> ByteString
hs forall a. Semigroup a => a -> a -> a
<> ByteString
"."
                  ByteString
_   -> ByteString
hs forall a. Semigroup a => a -> a -> a
<> Word8 -> ByteString
B.singleton Word8
sep1 forall a. Semigroup a => a -> a -> a
<> ByteString
ds
          Int -> ByteString -> StateT PState (Parser ByteString) ()
push Int
pos ByteString
dom
          forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
dom
    getValue :: a -> a
getValue a
c = a
c forall a. Bits a => a -> a -> a
.&. a
0x3f
    isPointer :: a -> Bool
isPointer a
c = forall a. Bits a => a -> Int -> Bool
testBit a
c Int
7 Bool -> Bool -> Bool
&& forall a. Bits a => a -> Int -> Bool
testBit a
c Int
6
    isExtLabel :: a -> Bool
isExtLabel a
c = Bool -> Bool
not (forall a. Bits a => a -> Int -> Bool
testBit a
c Int
7) Bool -> Bool -> Bool
&& forall a. Bits a => a -> Int -> Bool
testBit a
c Int
6