resolv-0.2.0.1: Domain Name Service (DNS) lookup via the libresolv standard library routines
Copyright© 2017 Herbert Valerio Riedel
LicenseGPL-2.0-or-later
Safe HaskellTrustworthy
LanguageHaskell2010

Network.DNS

Description

This module implements an API for accessing the Domain Name Service (DNS) resolver service via the standard libresolv system library on Unix systems.

Synopsis

High level API

queryA :: Name -> IO [(TTL, IPv4)] Source #

Query A record (see RFC 1035, section 3.4.1).

This query returns only exact matches (modulo foldCaseName). E.g. in case of CNAME responses even if the answer section would contain A records for the hostnames pointed to by the CNAME. You can use query if you need more control.

>>> queryA (Name "www.google.com")
[(TTL 72,IPv4 0xd83acde4)]

queryAAAA :: Name -> IO [(TTL, IPv6)] Source #

Query AAAA records (see RFC 3596).

This query returns only exact matches (modulo foldCaseName). E.g. in case of CNAME responses even if the answer section would contain A records for the hostnames pointed to by the CNAME. You can use query if you need more control.

>>> queryAAAA (Name "www.google.com")
[(TTL 299,IPv6 0x2a0014504001081e 0x2004)]

queryCNAME :: Name -> IO [(TTL, Name)] Source #

Query CNAME records (see RFC 1035, section 3.3.1).

>>> queryCNAME (Name "hackage.haskell.org")
[(TTL 299,Name "j.global-ssl.fastly.net.")]

queryPTR :: Name -> IO [(TTL, Name)] Source #

Query PTR records (see RFC 1035, section 3.3.12).

>>> queryPTR (Name "4.4.8.8.in-addr.arpa.")
[(TTL 14390,Name "dns.google.")]

See also arpaIPv6 and arpaIPv4 for converting IPv6 and IPv4 values to the respective .arpa." domain name for reverse lookups.

Since: 0.1.2.0

querySRV :: Name -> IO [(TTL, SRV Name)] Source #

Query SRV records (see RFC 2782).

>>> querySRV (Name "_imap._tcp.gmail.com")
[(TTL 21599,SRV {srvPriority = 0, srvWeight = 0, srvPort = 0, srvTarget = Name "."})]

queryTXT :: Name -> IO [(TTL, [CharStr])] Source #

Query TXT records (see RFC 1035, section 3.3.14).

>>> queryTXT (Name "_mirrors.hackage.haskell.org")
[(TTL 299,["0.urlbase=http://hackage.fpcomplete.com/",
           "1.urlbase=http://objects-us-west-1.dream.io/hackage-mirror/"])]

Mid-level API

query :: IsLabels n => Class -> n -> TypeSym -> IO (Msg n) Source #

Send a query via res_query(3) and decode its response into a Msg

Throws DnsException in case of resolving or encoding/decoding errors. May throw other IO exceptions in case of network errors.

Example

>>> query classIN (Name "_mirrors.hackage.haskell.org") TypeTXT
Just (Msg{msgHeader = MsgHeader{mhId    = 56694,
                                mhFlags = MsgHeaderFlags{mhQR = IsResponse, mhOpcode = 0, mhAA = False,
                                                         mhTC = False, mhRD = True, mhRA = True, mhZ = False,
                                                         mhAD = False, mhCD = False, mhRCode = 0},
                                mhQDCount = 1, mhANCount = 1, mhNSCount = 0, mhARCount = 1},
          msgQD = [MsgQuestion (Name "_mirrors.hackage.haskell.org.") (Type 16) (Class 1)],
          msgAN = [MsgRR{rrName  = Name "_mirrors.hackage.haskell.org.",
                         rrClass = Class 1, rrTTL = TTL 299,
                         rrData  = RDataTXT ["0.urlbase=http://hackage.fpcomplete.com/",
                                             "1.urlbase=http://objects-us-west-1.dream.io/hackage-mirror/"]}],
          msgNS = [],
          msgAR = [MsgRR{rrName = Name ".", rrClass = Class 512, rrTTL = TTL 32768, rrData = RDataOPT ""}]
      })

data DnsException Source #

Exception thrown in case of errors while resolving or encoding/decoding into a Msg.

Since: 0.1.1.0

Constructors

DnsEncodeException 
DnsDecodeException 
DnsHostNotFound

No such domain (authoritative)

Since: 0.2.0.0

DnsNoData

No record for requested type

Since: 0.2.0.0

DnsNoRecovery

Non recoverable errors, REFUSED, NOTIMP

Since: 0.2.0.0

DnsTryAgain

No such domain (non-authoritative) or SERVERFAIL

Since: 0.2.0.0

Instances

Instances details
Exception DnsException Source # 
Instance details

Defined in Network.DNS

Methods

toException :: DnsException -> SomeException

fromException :: SomeException -> Maybe DnsException

displayException :: DnsException -> String

Show DnsException Source # 
Instance details

Defined in Network.DNS

Methods

showsPrec :: Int -> DnsException -> ShowS

show :: DnsException -> String

showList :: [DnsException] -> ShowS

Low-level API

resIsReentrant :: Bool Source #

Whether the reentrant DNS resolver C API (e.g. res_nquery(3), res_nsend(3)) is being used.

If this this False, then as a fall-back res_query(3)/res_send(3) are used, protected by a global mutex.

Since: 0.1.1.0

queryRaw :: Class -> Name -> Type -> IO ByteString Source #

Send a query via res_query(3), the return value is the raw binary response message.

You can use decodeMessage to decode the response message.

sendRaw :: ByteString -> IO ByteString Source #

Send a raw preformatted query via res_send(3).

mkQueryRaw :: Class -> Name -> Type -> IO ByteString Source #

Use res_mkquery(3) to construct a DNS query message.

decodeMessage :: IsLabels n => ByteString -> Maybe (Msg n) Source #

Decode a raw DNS message (query or response)

Returns Nothing on decoding failures.

encodeMessage :: IsLabels n => Msg n -> Maybe ByteString Source #

Construct a raw DNS message (query or response)

May return Nothing in input parameters are detected to be invalid.

mkQueryMsg :: IsLabels n => Class -> n -> Type -> Msg n Source #

Construct a DNS query Msg in the style of mkQueryRaw

Types

Basic types

Names/Labels

type Label = ByteString Source #

A DNS Label

Must be non-empty and at most 63 octets.

data Labels Source #

A domain-name as per RFC 1035, section 3.3 expressed as list of Labels.

See also Name

Constructors

!Label :.: !Labels infixr 5 
Root 

Instances

Instances details
Read Labels Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS Labels

readList :: ReadS [Labels]

readPrec :: ReadPrec Labels

readListPrec :: ReadPrec [Labels]

Show Labels Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> Labels -> ShowS

show :: Labels -> String

showList :: [Labels] -> ShowS

Eq Labels Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: Labels -> Labels -> Bool

(/=) :: Labels -> Labels -> Bool

Ord Labels Source # 
Instance details

Defined in Network.DNS.Message

Methods

compare :: Labels -> Labels -> Ordering

(<) :: Labels -> Labels -> Bool

(<=) :: Labels -> Labels -> Bool

(>) :: Labels -> Labels -> Bool

(>=) :: Labels -> Labels -> Bool

max :: Labels -> Labels -> Labels

min :: Labels -> Labels -> Labels

IsLabels Labels Source # 
Instance details

Defined in Network.DNS.Message

class IsLabels s where Source #

Types that represent domain-name as per RFC 1035, section 3.3 and can be converted to and from Labels.

Methods

toLabels :: s -> Maybe Labels Source #

fromLabels :: Labels -> s Source #

Instances

Instances details
IsLabels Labels Source # 
Instance details

Defined in Network.DNS.Message

IsLabels Name Source # 
Instance details

Defined in Network.DNS.Message

newtype Name Source #

<domain-name> as per RFC 1035, 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.

Constructors

Name ByteString 

Instances

Instances details
Read Name Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS Name

readList :: ReadS [Name]

readPrec :: ReadPrec Name

readListPrec :: ReadPrec [Name]

Show Name Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> Name -> ShowS

show :: Name -> String

showList :: [Name] -> ShowS

Eq Name Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: Name -> Name -> Bool

(/=) :: Name -> Name -> Bool

Ord Name Source # 
Instance details

Defined in Network.DNS.Message

Methods

compare :: Name -> Name -> Ordering

(<) :: Name -> Name -> Bool

(<=) :: Name -> Name -> Bool

(>) :: Name -> Name -> Bool

(>=) :: Name -> Name -> Bool

max :: Name -> Name -> Name

min :: Name -> Name -> Name

IsLabels Name Source # 
Instance details

Defined in Network.DNS.Message

caseFoldName :: Name -> Name Source #

Normalise Name

This function case folds Names as described in in RFC 4343, section 3 by subtracting 0x20 from all octets in the inclusive range [0x61..0x7A] (i.e. mapping [a..z] to [A..Z]).

This operation is idempotent.

Character strings

newtype CharStr Source #

<character-string> as per RFC 1035, 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.

Constructors

CharStr ByteString 

Instances

Instances details
IsString CharStr Source # 
Instance details

Defined in Network.DNS.Message

Methods

fromString :: String -> CharStr

Read CharStr Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS CharStr

readList :: ReadS [CharStr]

readPrec :: ReadPrec CharStr

readListPrec :: ReadPrec [CharStr]

Show CharStr Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> CharStr -> ShowS

show :: CharStr -> String

showList :: [CharStr] -> ShowS

Binary CharStr Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: CharStr -> Put

get :: Get CharStr

putList :: [CharStr] -> Put

Eq CharStr Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: CharStr -> CharStr -> Bool

(/=) :: CharStr -> CharStr -> Bool

Ord CharStr Source # 
Instance details

Defined in Network.DNS.Message

Methods

compare :: CharStr -> CharStr -> Ordering

(<) :: CharStr -> CharStr -> Bool

(<=) :: CharStr -> CharStr -> Bool

(>) :: CharStr -> CharStr -> Bool

(>=) :: CharStr -> CharStr -> Bool

max :: CharStr -> CharStr -> CharStr

min :: CharStr -> CharStr -> CharStr

IP addresses

data IPv4 Source #

An IPv4 address

The IP address is represented in network order, i.e. 127.0.0.1 is represented as (IPv4 0x7f000001).

Constructors

IPv4 !Word32 

Instances

Instances details
Read IPv4 Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS IPv4

readList :: ReadS [IPv4]

readPrec :: ReadPrec IPv4

readListPrec :: ReadPrec [IPv4]

Show IPv4 Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> IPv4 -> ShowS

show :: IPv4 -> String

showList :: [IPv4] -> ShowS

Binary IPv4 Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: IPv4 -> Put

get :: Get IPv4

putList :: [IPv4] -> Put

Eq IPv4 Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: IPv4 -> IPv4 -> Bool

(/=) :: IPv4 -> IPv4 -> Bool

Ord IPv4 Source # 
Instance details

Defined in Network.DNS.Message

Methods

compare :: IPv4 -> IPv4 -> Ordering

(<) :: IPv4 -> IPv4 -> Bool

(<=) :: IPv4 -> IPv4 -> Bool

(>) :: IPv4 -> IPv4 -> Bool

(>=) :: IPv4 -> IPv4 -> Bool

max :: IPv4 -> IPv4 -> IPv4

min :: IPv4 -> IPv4 -> IPv4

arpaIPv4 :: IPv4 -> Name Source #

Convert IPv4 address to in-addr.arpa. Name (see RFC 1035, section 3.5).

>>> arpaIPv4 (IPv4 0x8080404)
Name "4.4.8.8.in-addr.arpa."

Since: 0.1.2.0

data IPv6 Source #

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).

Constructors

IPv6 !Word64 !Word64 

Instances

Instances details
Read IPv6 Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS IPv6

readList :: ReadS [IPv6]

readPrec :: ReadPrec IPv6

readListPrec :: ReadPrec [IPv6]

Show IPv6 Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> IPv6 -> ShowS

show :: IPv6 -> String

showList :: [IPv6] -> ShowS

Binary IPv6 Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: IPv6 -> Put

get :: Get IPv6

putList :: [IPv6] -> Put

Eq IPv6 Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: IPv6 -> IPv6 -> Bool

(/=) :: IPv6 -> IPv6 -> Bool

Ord IPv6 Source # 
Instance details

Defined in Network.DNS.Message

Methods

compare :: IPv6 -> IPv6 -> Ordering

(<) :: IPv6 -> IPv6 -> Bool

(<=) :: IPv6 -> IPv6 -> Bool

(>) :: IPv6 -> IPv6 -> Bool

(>=) :: IPv6 -> IPv6 -> Bool

max :: IPv6 -> IPv6 -> IPv6

min :: IPv6 -> IPv6 -> IPv6

arpaIPv6 :: IPv6 -> Name Source #

Convert IPv4 address to ip6.arpa. Name (see RFC 3596, section 2.5).

>>> arpaIPv6 (IPv6 0x2001486048600000 0x8844)
Name "4.4.8.8.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.0.6.8.4.0.6.8.4.1.0.0.2.ip6.arpa."

Since: 0.1.2.0

RR TTL & Class

newtype TTL Source #

Cache time-to-live expressed in seconds

Constructors

TTL Int32 

Instances

Instances details
Read TTL Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS TTL

readList :: ReadS [TTL]

readPrec :: ReadPrec TTL

readListPrec :: ReadPrec [TTL]

Show TTL Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> TTL -> ShowS

show :: TTL -> String

showList :: [TTL] -> ShowS

Binary TTL Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: TTL -> Put

get :: Get TTL

putList :: [TTL] -> Put

Eq TTL Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: TTL -> TTL -> Bool

(/=) :: TTL -> TTL -> Bool

Ord TTL Source # 
Instance details

Defined in Network.DNS.Message

Methods

compare :: TTL -> TTL -> Ordering

(<) :: TTL -> TTL -> Bool

(<=) :: TTL -> TTL -> Bool

(>) :: TTL -> TTL -> Bool

(>=) :: TTL -> TTL -> Bool

max :: TTL -> TTL -> TTL

min :: TTL -> TTL -> TTL

newtype Class Source #

DNS CLASS code as per RFC 1035, section 3.2.4

The most commonly used value is classIN.

Constructors

Class Word16 

Instances

Instances details
Read Class Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS Class

readList :: ReadS [Class]

readPrec :: ReadPrec Class

readListPrec :: ReadPrec [Class]

Show Class Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> Class -> ShowS

show :: Class -> String

showList :: [Class] -> ShowS

Binary Class Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: Class -> Put

get :: Get Class

putList :: [Class] -> Put

Eq Class Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: Class -> Class -> Bool

(/=) :: Class -> Class -> Bool

Ord Class Source # 
Instance details

Defined in Network.DNS.Message

Methods

compare :: Class -> Class -> Ordering

(<) :: Class -> Class -> Bool

(<=) :: Class -> Class -> Bool

(>) :: Class -> Class -> Bool

(>=) :: Class -> Class -> Bool

max :: Class -> Class -> Class

min :: Class -> Class -> Class

classIN :: Class Source #

The Class constant for IN (Internet)

Message types

newtype Type Source #

Raw DNS record type code

See also TypeSym

Constructors

Type Word16 

Instances

Instances details
Read Type Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS Type

readList :: ReadS [Type]

readPrec :: ReadPrec Type

readListPrec :: ReadPrec [Type]

Show Type Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> Type -> ShowS

show :: Type -> String

showList :: [Type] -> ShowS

Binary Type Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: Type -> Put

get :: Get Type

putList :: [Type] -> Put

Eq Type Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: Type -> Type -> Bool

(/=) :: Type -> Type -> Bool

Ord Type Source # 
Instance details

Defined in Network.DNS.Message

Methods

compare :: Type -> Type -> Ordering

(<) :: Type -> Type -> Bool

(<=) :: Type -> Type -> Bool

(>) :: Type -> Type -> Bool

(>=) :: Type -> Type -> Bool

max :: Type -> Type -> Type

min :: Type -> Type -> Type

data TypeSym Source #

Symbolic DNS record type

Instances

Instances details
Bounded TypeSym Source # 
Instance details

Defined in Network.DNS.Message

Enum TypeSym Source # 
Instance details

Defined in Network.DNS.Message

Read TypeSym Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS TypeSym

readList :: ReadS [TypeSym]

readPrec :: ReadPrec TypeSym

readListPrec :: ReadPrec [TypeSym]

Show TypeSym Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> TypeSym -> ShowS

show :: TypeSym -> String

showList :: [TypeSym] -> ShowS

Eq TypeSym Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: TypeSym -> TypeSym -> Bool

(/=) :: TypeSym -> TypeSym -> Bool

Ord TypeSym Source # 
Instance details

Defined in Network.DNS.Message

Methods

compare :: TypeSym -> TypeSym -> Ordering

(<) :: TypeSym -> TypeSym -> Bool

(<=) :: TypeSym -> TypeSym -> Bool

(>) :: TypeSym -> TypeSym -> Bool

(>=) :: TypeSym -> TypeSym -> Bool

max :: TypeSym -> TypeSym -> TypeSym

min :: TypeSym -> TypeSym -> TypeSym

typeFromSym :: TypeSym -> Type Source #

Convert symbolic TypeSym to numeric Type code

typeToSym :: Type -> Maybe TypeSym Source #

Convert Type code to symbolic TypeSym

Messages

data Msg l Source #

Represents a DNS message as per RFC 1035

Constructors

Msg 

Fields

Instances

Instances details
Foldable Msg Source # 
Instance details

Defined in Network.DNS.Message

Methods

fold :: Monoid m => Msg m -> m

foldMap :: Monoid m => (a -> m) -> Msg a -> m

foldMap' :: Monoid m => (a -> m) -> Msg a -> m

foldr :: (a -> b -> b) -> b -> Msg a -> b

foldr' :: (a -> b -> b) -> b -> Msg a -> b

foldl :: (b -> a -> b) -> b -> Msg a -> b

foldl' :: (b -> a -> b) -> b -> Msg a -> b

foldr1 :: (a -> a -> a) -> Msg a -> a

foldl1 :: (a -> a -> a) -> Msg a -> a

toList :: Msg a -> [a]

null :: Msg a -> Bool

length :: Msg a -> Int

elem :: Eq a => a -> Msg a -> Bool

maximum :: Ord a => Msg a -> a

minimum :: Ord a => Msg a -> a

sum :: Num a => Msg a -> a

product :: Num a => Msg a -> a

Traversable Msg Source # 
Instance details

Defined in Network.DNS.Message

Methods

traverse :: Applicative f => (a -> f b) -> Msg a -> f (Msg b)

sequenceA :: Applicative f => Msg (f a) -> f (Msg a)

mapM :: Monad m => (a -> m b) -> Msg a -> m (Msg b)

sequence :: Monad m => Msg (m a) -> m (Msg a)

Functor Msg Source # 
Instance details

Defined in Network.DNS.Message

Methods

fmap :: (a -> b) -> Msg a -> Msg b

(<$) :: a -> Msg b -> Msg a

Read l => Read (Msg l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS (Msg l)

readList :: ReadS [Msg l]

readPrec :: ReadPrec (Msg l)

readListPrec :: ReadPrec [Msg l]

Show l => Show (Msg l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> Msg l -> ShowS

show :: Msg l -> String

showList :: [Msg l] -> ShowS

Binary l => Binary (Msg l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: Msg l -> Put

get :: Get (Msg l)

putList :: [Msg l] -> Put

data MsgHeader Source #

DNS message header section as per RFC 1035, section 4.1.1

Constructors

MsgHeader 

Fields

Instances

Instances details
Read MsgHeader Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS MsgHeader

readList :: ReadS [MsgHeader]

readPrec :: ReadPrec MsgHeader

readListPrec :: ReadPrec [MsgHeader]

Show MsgHeader Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> MsgHeader -> ShowS

show :: MsgHeader -> String

showList :: [MsgHeader] -> ShowS

Binary MsgHeader Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: MsgHeader -> Put

get :: Get MsgHeader

putList :: [MsgHeader] -> Put

data MsgHeaderFlags Source #

DNS message header flags as per RFC 1035, section 4.1.1

Constructors

MsgHeaderFlags 

Fields

Instances

Instances details
Read MsgHeaderFlags Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS MsgHeaderFlags

readList :: ReadS [MsgHeaderFlags]

readPrec :: ReadPrec MsgHeaderFlags

readListPrec :: ReadPrec [MsgHeaderFlags]

Show MsgHeaderFlags Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> MsgHeaderFlags -> ShowS

show :: MsgHeaderFlags -> String

showList :: [MsgHeaderFlags] -> ShowS

Binary MsgHeaderFlags Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: MsgHeaderFlags -> Put

get :: Get MsgHeaderFlags

putList :: [MsgHeaderFlags] -> Put

data QR Source #

Encodes whether message is a query or a response

Since: 0.1.1.0

Constructors

IsQuery 
IsResponse 

Instances

Instances details
Read QR Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS QR

readList :: ReadS [QR]

readPrec :: ReadPrec QR

readListPrec :: ReadPrec [QR]

Show QR Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> QR -> ShowS

show :: QR -> String

showList :: [QR] -> ShowS

Eq QR Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: QR -> QR -> Bool

(/=) :: QR -> QR -> Bool

data MsgQuestion l Source #

DNS message header section as per RFC 1035, section 4.1.2

Constructors

MsgQuestion !l !Type !Class 

Instances

Instances details
Foldable MsgQuestion Source # 
Instance details

Defined in Network.DNS.Message

Methods

fold :: Monoid m => MsgQuestion m -> m

foldMap :: Monoid m => (a -> m) -> MsgQuestion a -> m

foldMap' :: Monoid m => (a -> m) -> MsgQuestion a -> m

foldr :: (a -> b -> b) -> b -> MsgQuestion a -> b

foldr' :: (a -> b -> b) -> b -> MsgQuestion a -> b

foldl :: (b -> a -> b) -> b -> MsgQuestion a -> b

foldl' :: (b -> a -> b) -> b -> MsgQuestion a -> b

foldr1 :: (a -> a -> a) -> MsgQuestion a -> a

foldl1 :: (a -> a -> a) -> MsgQuestion a -> a

toList :: MsgQuestion a -> [a]

null :: MsgQuestion a -> Bool

length :: MsgQuestion a -> Int

elem :: Eq a => a -> MsgQuestion a -> Bool

maximum :: Ord a => MsgQuestion a -> a

minimum :: Ord a => MsgQuestion a -> a

sum :: Num a => MsgQuestion a -> a

product :: Num a => MsgQuestion a -> a

Traversable MsgQuestion Source # 
Instance details

Defined in Network.DNS.Message

Methods

traverse :: Applicative f => (a -> f b) -> MsgQuestion a -> f (MsgQuestion b)

sequenceA :: Applicative f => MsgQuestion (f a) -> f (MsgQuestion a)

mapM :: Monad m => (a -> m b) -> MsgQuestion a -> m (MsgQuestion b)

sequence :: Monad m => MsgQuestion (m a) -> m (MsgQuestion a)

Functor MsgQuestion Source # 
Instance details

Defined in Network.DNS.Message

Methods

fmap :: (a -> b) -> MsgQuestion a -> MsgQuestion b

(<$) :: a -> MsgQuestion b -> MsgQuestion a

Read l => Read (MsgQuestion l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS (MsgQuestion l)

readList :: ReadS [MsgQuestion l]

readPrec :: ReadPrec (MsgQuestion l)

readListPrec :: ReadPrec [MsgQuestion l]

Show l => Show (MsgQuestion l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> MsgQuestion l -> ShowS

show :: MsgQuestion l -> String

showList :: [MsgQuestion l] -> ShowS

Binary l => Binary (MsgQuestion l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: MsgQuestion l -> Put

get :: Get (MsgQuestion l)

putList :: [MsgQuestion l] -> Put

Eq l => Eq (MsgQuestion l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: MsgQuestion l -> MsgQuestion l -> Bool

(/=) :: MsgQuestion l -> MsgQuestion l -> Bool

data MsgRR l Source #

DNS resource record section as per RFC 1035, section 4.1.3

Constructors

MsgRR 

Fields

Instances

Instances details
Foldable MsgRR Source # 
Instance details

Defined in Network.DNS.Message

Methods

fold :: Monoid m => MsgRR m -> m

foldMap :: Monoid m => (a -> m) -> MsgRR a -> m

foldMap' :: Monoid m => (a -> m) -> MsgRR a -> m

foldr :: (a -> b -> b) -> b -> MsgRR a -> b

foldr' :: (a -> b -> b) -> b -> MsgRR a -> b

foldl :: (b -> a -> b) -> b -> MsgRR a -> b

foldl' :: (b -> a -> b) -> b -> MsgRR a -> b

foldr1 :: (a -> a -> a) -> MsgRR a -> a

foldl1 :: (a -> a -> a) -> MsgRR a -> a

toList :: MsgRR a -> [a]

null :: MsgRR a -> Bool

length :: MsgRR a -> Int

elem :: Eq a => a -> MsgRR a -> Bool

maximum :: Ord a => MsgRR a -> a

minimum :: Ord a => MsgRR a -> a

sum :: Num a => MsgRR a -> a

product :: Num a => MsgRR a -> a

Traversable MsgRR Source # 
Instance details

Defined in Network.DNS.Message

Methods

traverse :: Applicative f => (a -> f b) -> MsgRR a -> f (MsgRR b)

sequenceA :: Applicative f => MsgRR (f a) -> f (MsgRR a)

mapM :: Monad m => (a -> m b) -> MsgRR a -> m (MsgRR b)

sequence :: Monad m => MsgRR (m a) -> m (MsgRR a)

Functor MsgRR Source # 
Instance details

Defined in Network.DNS.Message

Methods

fmap :: (a -> b) -> MsgRR a -> MsgRR b

(<$) :: a -> MsgRR b -> MsgRR a

Read l => Read (MsgRR l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS (MsgRR l)

readList :: ReadS [MsgRR l]

readPrec :: ReadPrec (MsgRR l)

readListPrec :: ReadPrec [MsgRR l]

Show l => Show (MsgRR l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> MsgRR l -> ShowS

show :: MsgRR l -> String

showList :: [MsgRR l] -> ShowS

Binary l => Binary (MsgRR l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: MsgRR l -> Put

get :: Get (MsgRR l)

putList :: [MsgRR l] -> Put

Eq l => Eq (MsgRR l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: MsgRR l -> MsgRR l -> Bool

(/=) :: MsgRR l -> MsgRR l -> Bool

data RData l Source #

DNS resource record data (see also MsgRR and TypeSym)

Constructors

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) 
RDataAFSDB !Word16 !l 
RDataNAPTR !Word16 !Word16 !CharStr !CharStr !CharStr !l 
RDataURI !Word16 !Word16 !ByteString 
RDataRRSIG !Word16 !Word8 !Word8 !Word32 !Word32 !Word32 !Word16 !l !ByteString 
RDataDNSKEY !Word16 !Word8 !Word8 !ByteString 
RDataDS !Word16 !Word8 !Word8 !ByteString 
RDataNSEC !l !(Set Type) 
RDataSSHFP !Word8 !Word8 !ByteString 
RDataNSEC3PARAM !Word8 !Word8 !Word16 !CharStr 
RDataNSEC3 !Word8 !Word8 !Word16 !CharStr !CharStr !(Set Type) 
RDataCAA !Word8 !CharStr !ByteString 
RDataOPT !ByteString 
RData !Type !ByteString

Unknown/undecoded resource record type

Instances

Instances details
Foldable RData Source # 
Instance details

Defined in Network.DNS.Message

Methods

fold :: Monoid m => RData m -> m

foldMap :: Monoid m => (a -> m) -> RData a -> m

foldMap' :: Monoid m => (a -> m) -> RData a -> m

foldr :: (a -> b -> b) -> b -> RData a -> b

foldr' :: (a -> b -> b) -> b -> RData a -> b

foldl :: (b -> a -> b) -> b -> RData a -> b

foldl' :: (b -> a -> b) -> b -> RData a -> b

foldr1 :: (a -> a -> a) -> RData a -> a

foldl1 :: (a -> a -> a) -> RData a -> a

toList :: RData a -> [a]

null :: RData a -> Bool

length :: RData a -> Int

elem :: Eq a => a -> RData a -> Bool

maximum :: Ord a => RData a -> a

minimum :: Ord a => RData a -> a

sum :: Num a => RData a -> a

product :: Num a => RData a -> a

Traversable RData Source # 
Instance details

Defined in Network.DNS.Message

Methods

traverse :: Applicative f => (a -> f b) -> RData a -> f (RData b)

sequenceA :: Applicative f => RData (f a) -> f (RData a)

mapM :: Monad m => (a -> m b) -> RData a -> m (RData b)

sequence :: Monad m => RData (m a) -> m (RData a)

Functor RData Source # 
Instance details

Defined in Network.DNS.Message

Methods

fmap :: (a -> b) -> RData a -> RData b

(<$) :: a -> RData b -> RData a

Read l => Read (RData l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS (RData l)

readList :: ReadS [RData l]

readPrec :: ReadPrec (RData l)

readListPrec :: ReadPrec [RData l]

Show l => Show (RData l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> RData l -> ShowS

show :: RData l -> String

showList :: [RData l] -> ShowS

Eq l => Eq (RData l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: RData l -> RData l -> Bool

(/=) :: RData l -> RData l -> Bool

rdType :: RData l -> Either Type TypeSym Source #

Extract the resource record type of a RData object

data SRV l Source #

SRV Record data as per RFC 2782

Constructors

SRV 

Fields

Instances

Instances details
Foldable SRV Source # 
Instance details

Defined in Network.DNS.Message

Methods

fold :: Monoid m => SRV m -> m

foldMap :: Monoid m => (a -> m) -> SRV a -> m

foldMap' :: Monoid m => (a -> m) -> SRV a -> m

foldr :: (a -> b -> b) -> b -> SRV a -> b

foldr' :: (a -> b -> b) -> b -> SRV a -> b

foldl :: (b -> a -> b) -> b -> SRV a -> b

foldl' :: (b -> a -> b) -> b -> SRV a -> b

foldr1 :: (a -> a -> a) -> SRV a -> a

foldl1 :: (a -> a -> a) -> SRV a -> a

toList :: SRV a -> [a]

null :: SRV a -> Bool

length :: SRV a -> Int

elem :: Eq a => a -> SRV a -> Bool

maximum :: Ord a => SRV a -> a

minimum :: Ord a => SRV a -> a

sum :: Num a => SRV a -> a

product :: Num a => SRV a -> a

Traversable SRV Source # 
Instance details

Defined in Network.DNS.Message

Methods

traverse :: Applicative f => (a -> f b) -> SRV a -> f (SRV b)

sequenceA :: Applicative f => SRV (f a) -> f (SRV a)

mapM :: Monad m => (a -> m b) -> SRV a -> m (SRV b)

sequence :: Monad m => SRV (m a) -> m (SRV a)

Functor SRV Source # 
Instance details

Defined in Network.DNS.Message

Methods

fmap :: (a -> b) -> SRV a -> SRV b

(<$) :: a -> SRV b -> SRV a

Read l => Read (SRV l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

readsPrec :: Int -> ReadS (SRV l)

readList :: ReadS [SRV l]

readPrec :: ReadPrec (SRV l)

readListPrec :: ReadPrec [SRV l]

Show l => Show (SRV l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

showsPrec :: Int -> SRV l -> ShowS

show :: SRV l -> String

showList :: [SRV l] -> ShowS

Binary l => Binary (SRV l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

put :: SRV l -> Put

get :: Get (SRV l)

putList :: [SRV l] -> Put

Eq l => Eq (SRV l) Source # 
Instance details

Defined in Network.DNS.Message

Methods

(==) :: SRV l -> SRV l -> Bool

(/=) :: SRV l -> SRV l -> Bool