dns-4.0.1: DNS library in Haskell

Safe HaskellNone
LanguageHaskell2010

Network.DNS.Types

Contents

Description

Data types for DNS Query and Response. For more information, see http://www.ietf.org/rfc/rfc1035.

Synopsis

Resource Records

data ResourceRecord #

Raw data format for resource records.

Constructors

ResourceRecord 

Fields

type Answers = [ResourceRecord] #

Type alias for resource records in the answer section.

type AuthorityRecords = [ResourceRecord] #

Type alias for resource records in the answer section.

type AdditionalRecords = [ResourceRecord] #

Type for resource records in the additional section.

Types

type Domain = ByteString #

This type holds the presentation form of fully-qualified DNS domain names encoded as ASCII A-labels, with '.' separators between labels. Non-printing characters are escaped as \DDD (a backslash, followed by three decimal digits). The special characters: ", $, (, ), ;, @, and \ are escaped by prepending a backslash. The trailing '.' is optional on input, but is recommended, and is always added when decoding from wire form.

The encoding of domain names to wire form, e.g. for transmission in a query, requires the input encodings to be valid, otherwise a DecodeError may be thrown. Domain names received in wire form in DNS messages are escaped to this presentation form as part of decoding the DNSMessage.

This form is ASCII-only. Any conversion between A-label ByteStrings, and U-label Text happens at whatever layer maps user input to DNS names, or presents friendly DNS names to the user. Not all users can read all scripts, and applications that default to U-label form should ideally give the user a choice to see the A-label form. Examples:

www.example.org.           -- Ordinary DNS name.
_25._tcp.mx1.example.net.  -- TLSA RR initial labels have _ prefixes.
\001.exotic.example.       -- First label is Ctrl-A!
just\.one\.label.example.  -- First label is "just.one.label"

type CLASS = Word16 #

Resource record class.

classIN :: CLASS #

Resource record class for the Internet.

type TTL = Word32 #

Time to live in second.

Resource Record Types

data TYPE where #

Types for resource records.

Bundled Patterns

pattern A :: TYPE

IPv4 address

pattern NS :: TYPE

An authoritative name serve

pattern CNAME :: TYPE

The canonical name for an alias

pattern SOA :: TYPE

Marks the start of a zone of authority

pattern NULL :: TYPE

A null RR (EXPERIMENTAL)

pattern PTR :: TYPE

A domain name pointer

pattern MX :: TYPE

Mail exchange

pattern TXT :: TYPE

Text strings

pattern AAAA :: TYPE

IPv6 Address

pattern SRV :: TYPE

Server Selection (RFC2782)

pattern DNAME :: TYPE

DNAME (RFC6672)

pattern OPT :: TYPE

OPT (RFC6891)

pattern DS :: TYPE

Delegation Signer (RFC4034)

pattern RRSIG :: TYPE

RRSIG (RFC4034)

pattern NSEC :: TYPE

NSEC (RFC4034)

pattern DNSKEY :: TYPE

DNSKEY (RFC4034)

pattern NSEC3 :: TYPE

NSEC3 (RFC5155)

pattern NSEC3PARAM :: TYPE

NSEC3PARAM (RFC5155)

pattern TLSA :: TYPE

TLSA (RFC6698)

pattern CDS :: TYPE

Child DS (RFC7344)

pattern CDNSKEY :: TYPE

DNSKEY(s) the Child wants reflected in DS (RFC7344)

pattern CSYNC :: TYPE

Child-To-Parent Synchronization (RFC7477)

pattern AXFR :: TYPE

Zone transfer (RFC5936)

pattern ANY :: TYPE

A request for all records the server/cache has available

pattern CAA :: TYPE

Certification Authority Authorization (RFC6844)

Instances
Eq TYPE 
Instance details

Defined in Network.DNS.Types.Internal

Methods

(==) :: TYPE -> TYPE -> Bool #

(/=) :: TYPE -> TYPE -> Bool #

Ord TYPE 
Instance details

Defined in Network.DNS.Types.Internal

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 #

Show TYPE 
Instance details

Defined in Network.DNS.Types.Internal

Methods

showsPrec :: Int -> TYPE -> ShowS #

show :: TYPE -> String #

showList :: [TYPE] -> ShowS #

fromTYPE :: TYPE -> Word16 #

From type to number.

toTYPE :: Word16 -> TYPE #

From number to type.

Resource Data

data RData #

Raw data format for each type.

Constructors

RD_A IPv4

IPv4 address

RD_NS Domain

An authoritative name serve

RD_CNAME Domain

The canonical name for an alias

RD_SOA Domain Mailbox Word32 Word32 Word32 Word32 Word32

Marks the start of a zone of authority

RD_NULL ByteString

NULL RR (EXPERIMENTAL, RFC1035).

RD_PTR Domain

A domain name pointer

RD_MX Word16 Domain

Mail exchange

RD_TXT ByteString

Text strings

RD_AAAA IPv6

IPv6 Address

RD_SRV Word16 Word16 Word16 Domain

Server Selection (RFC2782)

RD_DNAME Domain

DNAME (RFC6672)

RD_OPT [OData]

OPT (RFC6891)

RD_DS Word16 Word8 Word8 ByteString

Delegation Signer (RFC4034)

RD_RRSIG RD_RRSIG

DNSSEC signature

RD_NSEC Domain [TYPE]

DNSSEC denial of existence NSEC record

RD_DNSKEY Word16 Word8 Word8 ByteString

DNSKEY (RFC4034)

RD_NSEC3 Word8 Word8 Word16 ByteString ByteString [TYPE]

DNSSEC hashed denial of existence (RFC5155)

RD_NSEC3PARAM Word8 Word8 Word16 ByteString

NSEC3 zone parameters (RFC5155)

RD_TLSA Word8 Word8 Word8 ByteString

TLSA (RFC6698)

RD_CDS Word16 Word8 Word8 ByteString

Child DS (RFC7344)

RD_CDNSKEY Word16 Word8 Word8 ByteString

Child DNSKEY (RFC7344) RD_CSYNC

UnknownRData ByteString

Unknown resource data

Instances
Eq RData 
Instance details

Defined in Network.DNS.Types.Internal

Methods

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

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

Ord RData 
Instance details

Defined in Network.DNS.Types.Internal

Methods

compare :: RData -> RData -> Ordering #

(<) :: RData -> RData -> Bool #

(<=) :: RData -> RData -> Bool #

(>) :: RData -> RData -> Bool #

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

max :: RData -> RData -> RData #

min :: RData -> RData -> RData #

Show RData 
Instance details

Defined in Network.DNS.Types.Internal

Methods

showsPrec :: Int -> RData -> ShowS #

show :: RData -> String #

showList :: [RData] -> ShowS #

data RD_RRSIG #

RRSIG representation.

As noted in Section 3.1.5 of RFC 4034 the RRsig inception and expiration times use serial number arithmetic. As a result these timestamps are not pure values, their meaning is time-dependent! They depend on the present time and are both at most approximately +/-68 years from the present. This ambiguity is not a problem because cached RRSIG records should only persist a few days, signature lifetimes should be *much* shorter than 68 years, and key rotation should result any misconstrued 136-year-old signatures fail to validate. This also means that the interpretation of a time that is exactly half-way around the clock at now +/-0x80000000 is not important, the signature should never be valid.

The upshot for us is that we need to convert these *impure* relative values to pure absolute values at the moment they are received from from the network (or read from files, ... in some impure I/O context), and convert them back to 32-bit values when encoding. Therefore, the constructor takes absolute 64-bit representations of the inception and expiration times.

The dnsTime function performs the requisite conversion.

Constructors

RDREP_RRSIG 

Fields

Instances
Eq RD_RRSIG 
Instance details

Defined in Network.DNS.Types.Internal

Ord RD_RRSIG 
Instance details

Defined in Network.DNS.Types.Internal

Show RD_RRSIG 
Instance details

Defined in Network.DNS.Types.Internal

dnsTime #

Arguments

:: Word32

DNS circle-arithmetic timestamp

-> Int64

current epoch time

-> Int64

absolute DNS timestamp

Given a 32-bit circle-arithmetic DNS time, and the current absolute epoch time, return the epoch time corresponding to the DNS timestamp.

DNS Message

data DNSMessage #

DNS message format for queries and replies.

Constructors

DNSMessage 

Fields

Instances
Eq DNSMessage 
Instance details

Defined in Network.DNS.Types.Internal

Show DNSMessage 
Instance details

Defined in Network.DNS.Types.Internal

Query

makeQuery #

Arguments

:: Identifier

Crypto random request id

-> Question

Question name and type

-> QueryControls

Custom RD/AD/CD flags and EDNS settings

-> DNSMessage 

Construct a complete query DNSMessage, by combining the defaultQuery template with the specified Identifier, and Question. The QueryControls can be mempty to leave all header and EDNS settings at their default values, or some combination of overrides. A default set of overrides can be enabled via the resolvQueryControls field of ResolvConf. Per-query overrides are possible by using loookupRawCtl.

makeEmptyQuery #

Arguments

:: QueryControls

Flag and EDNS overrides

-> DNSMessage 

A query template with QueryControls overrides applied, with just the Question and query Identifier remaining to be filled in.

defaultQuery :: DNSMessage #

A DNSMessage template for queries with default settings for the message DNSHeader and EDNSheader. This is the initial query message state, before customization via QueryControls.

Query Controls

data QueryControls #

Query controls form a Monoid, as with function composition, the left-most value has the last say. The Monoid is generated by two sets of combinators, one that controls query-related DNS header flags, and another that controls EDNS features.

The header flag controls are: rdFlag, adFlag and cdFlag.

The EDNS feature controls are: doFlag, ednsEnabled, ednsSetVersion, ednsSetUdpSize and ednsSetOptions. When EDNS is disabled, all the other EDNS-related controls have no effect.

Example: Disable DNSSEC checking on the server, and request signatures and NSEC records, perhaps for your own independent validation. The UDP buffer size is set large, for use with a local loopback nameserver on the same host.

>>> :{
mconcat [ adFlag FlagClear
        , cdFlag FlagSet
        , doFlag FlagSet
        , ednsSetUdpSize (Just 8192) -- IPv4 loopback server?
        ]
:}
ad:0,cd:1,edns.udpsize:8192,edns.dobit:1

Example: Use EDNS version 1 (yet to be specified), request nameserver ids from the server, and indicate a client subnet of "192.0.2.1/24".

>>> :set -XOverloadedStrings
>>> let emptyNSID = ""
>>> let mask = 24
>>> let ipaddr = read "192.0.2.1"
>>> :{
mconcat [ ednsSetVersion (Just 1)
        , ednsSetOptions (ODataAdd [OD_NSID emptyNSID])
        , ednsSetOptions (ODataAdd [OD_ClientSubnet mask 0 ipaddr])
        ]
:}
edns.version:1,edns.options:[NSID,ClientSubnet]

rdFlag :: FlagOp -> QueryControls #

Generator of QueryControls that adjusts the RD bit.

>>> rdFlag FlagClear
rd:0

adFlag :: FlagOp -> QueryControls #

Generator of QueryControls that adjusts the AD bit.

>>> adFlag FlagSet
ad:1

cdFlag :: FlagOp -> QueryControls #

Generator of QueryControls that adjusts the CD bit.

>>> cdFlag FlagSet
cd:1

doFlag :: FlagOp -> QueryControls #

Generator of QueryControls that adjusts the EDNS DnssecOk (DO) bit.

>>> doFlag FlagSet
edns.dobit:1

ednsEnabled :: FlagOp -> QueryControls #

Generator of QueryControls that enables or disables EDNS support. When EDNS is disabled, the rest of the EDNS controls are ignored.

>>> ednsHeader $ makeEmptyQuery $ ednsEnabled FlagClear <> doFlag FlagSet
NoEDNS

ednsSetVersion :: Maybe Word8 -> QueryControls #

Generator of QueryControls that adjusts the EDNS version. A value of Nothing makes no changes, while Just v sets the EDNS version to v.

>>> ednsSetVersion (Just 1)
edns.version:1

ednsSetUdpSize :: Maybe Word16 -> QueryControls #

Generator of QueryControls that adjusts the EDNS UDP buffer size. A value of Nothing makes no changes, while Just n sets the EDNS UDP buffer size to n.

>>> ednsSetUdpSize (Just 2048)
edns.udpsize:2048

ednsSetOptions :: ODataOp -> QueryControls #

Generator of QueryControls that adjusts the list of EDNS options.

>>> :set -XOverloadedStrings
>>> ednsSetOptions (ODataAdd [OD_NSID ""])
edns.options:[NSID]

Flag and OData control operations

data FlagOp #

Boolean flag operations. These form a Monoid. When combined via mappend, as with function composition, the left-most value has the last say.

>>> mempty :: FlagOp
FlagKeep
>>> FlagSet <> mempty
FlagSet
>>> FlagClear <> FlagSet <> mempty
FlagClear
>>> FlagReset <> FlagClear <> FlagSet <> mempty
FlagReset

Constructors

FlagSet

Set the flag to 1

FlagClear

Clear the flag to 0

FlagReset

Reset the flag to its default value

FlagKeep

Leave the flag unchanged

Instances
Eq FlagOp 
Instance details

Defined in Network.DNS.Types.Internal

Methods

(==) :: FlagOp -> FlagOp -> Bool #

(/=) :: FlagOp -> FlagOp -> Bool #

Show FlagOp 
Instance details

Defined in Network.DNS.Types.Internal

Semigroup FlagOp 
Instance details

Defined in Network.DNS.Types.Internal

Monoid FlagOp 
Instance details

Defined in Network.DNS.Types.Internal

data ODataOp #

The default EDNS Option list is empty. We define two operations, one to prepend a list of options, and another to set a specific list of options.

Constructors

ODataAdd [OData]

Add the specified options to the list.

ODataSet [OData]

Set the option list as specified.

Instances
Eq ODataOp 
Instance details

Defined in Network.DNS.Types.Internal

Methods

(==) :: ODataOp -> ODataOp -> Bool #

(/=) :: ODataOp -> ODataOp -> Bool #

Semigroup ODataOp 
Instance details

Defined in Network.DNS.Types.Internal

Monoid ODataOp 
Instance details

Defined in Network.DNS.Types.Internal

Response

defaultResponse :: DNSMessage #

Default response. When responding to EDNS queries, the response must either be an EDNS response, or else FormatErr must be returned. The default response message has EDNS disabled (ednsHeader set to NoEDNS), it should be updated as appropriate.

Do not explicitly add OPT RRs to the additional section, instead let the encoder compute and add the OPT record based on the EDNS pseudo-header.

The RCODE in the DNSHeader should be set to the appropriate 12-bit extended value, which will be split between the primary header and EDNS OPT record during message encoding (low 4 bits in DNS header, high 8 bits in EDNS OPT record). See EDNSheader for more details.

makeResponse :: Identifier -> Question -> Answers -> DNSMessage #

Construct a query response DNSMessage.

DNS Header

data DNSHeader #

Raw data format for the header of DNS Query and Response.

Constructors

DNSHeader 

Fields

Instances
Eq DNSHeader 
Instance details

Defined in Network.DNS.Types.Internal

Show DNSHeader 
Instance details

Defined in Network.DNS.Types.Internal

type Identifier = Word16 #

An identifier assigned by the program that generates any kind of query.

DNS flags

data DNSFlags #

Raw data format for the flags of DNS Query and Response.

Constructors

DNSFlags 

Fields

  • qOrR :: !QorR

    Query or response.

  • opcode :: !OPCODE

    Kind of query.

  • authAnswer :: !Bool

    AA (Authoritative Answer) bit - this bit is valid in responses, and specifies that the responding name server is an authority for the domain name in question section.

  • trunCation :: !Bool

    TC (Truncated Response) bit - specifies that this message was truncated due to length greater than that permitted on the transmission channel.

  • recDesired :: !Bool

    RD (Recursion Desired) bit - this bit may be set in a query and is copied into the response. If RD is set, it directs the name server to pursue the query recursively. Recursive query support is optional.

  • recAvailable :: !Bool

    RA (Recursion Available) bit - this be is set or cleared in a response, and denotes whether recursive query support is available in the name server.

  • rcode :: !RCODE

    The full 12-bit extended RCODE when EDNS is in use. Should always be zero in well-formed requests. When decoding replies, the high eight bits from any EDNS response are combined with the 4-bit RCODE from the DNS header. When encoding replies, if no EDNS OPT record is provided, RCODE values > 15 are mapped to FormatErr.

  • authenData :: !Bool

    AD (Authenticated Data) bit - (RFC4035, Section 3.2.3).

  • chkDisable :: !Bool

    CD (Checking Disabled) bit - (RFC4035, Section 3.2.2).

Instances
Eq DNSFlags 
Instance details

Defined in Network.DNS.Types.Internal

Show DNSFlags 
Instance details

Defined in Network.DNS.Types.Internal

data QorR #

Query or response.

Constructors

QR_Query

Query.

QR_Response

Response.

Instances
Bounded QorR 
Instance details

Defined in Network.DNS.Types.Internal

Enum QorR 
Instance details

Defined in Network.DNS.Types.Internal

Methods

succ :: QorR -> QorR #

pred :: QorR -> QorR #

toEnum :: Int -> QorR #

fromEnum :: QorR -> Int #

enumFrom :: QorR -> [QorR] #

enumFromThen :: QorR -> QorR -> [QorR] #

enumFromTo :: QorR -> QorR -> [QorR] #

enumFromThenTo :: QorR -> QorR -> QorR -> [QorR] #

Eq QorR 
Instance details

Defined in Network.DNS.Types.Internal

Methods

(==) :: QorR -> QorR -> Bool #

(/=) :: QorR -> QorR -> Bool #

Show QorR 
Instance details

Defined in Network.DNS.Types.Internal

Methods

showsPrec :: Int -> QorR -> ShowS #

show :: QorR -> String #

showList :: [QorR] -> ShowS #

defaultDNSFlags :: DNSFlags #

Default DNSFlags record suitable for making recursive queries. By default the RD bit is set, and the AD and CD bits are cleared.

OPCODE and RCODE

data OPCODE #

Kind of query.

Constructors

OP_STD

A standard query.

OP_INV

An inverse query (inverse queries are deprecated).

OP_SSR

A server status request.

OP_NOTIFY

A zone change notification (RFC1996)

OP_UPDATE

An update request (RFC2136)

Instances
Bounded OPCODE 
Instance details

Defined in Network.DNS.Types.Internal

Enum OPCODE 
Instance details

Defined in Network.DNS.Types.Internal

Eq OPCODE 
Instance details

Defined in Network.DNS.Types.Internal

Methods

(==) :: OPCODE -> OPCODE -> Bool #

(/=) :: OPCODE -> OPCODE -> Bool #

Show OPCODE 
Instance details

Defined in Network.DNS.Types.Internal

fromOPCODE :: OPCODE -> Word16 #

Convert the internal representation of a DNS OPCODE to its 16-bit numeric value.

toOPCODE :: Word16 -> Maybe OPCODE #

Convert a 16-bit DNS OPCODE number to its internal representation

data RCODE where #

EDNS extended 12-bit response code. Non-EDNS messages use only the low 4 bits. With EDNS this stores the combined error code from the DNS header and and the EDNS psuedo-header. See EDNSheader for more detail.

Bundled Patterns

pattern NoErr :: RCODE

No error condition.

pattern FormatErr :: RCODE

Format error - The name server was unable to interpret the query.

pattern ServFail :: RCODE

Server failure - The name server was unable to process this query due to a problem with the name server.

pattern NameErr :: RCODE

Name Error - Meaningful only for responses from an authoritative name server, this code signifies that the domain name referenced in the query does not exist.

pattern NotImpl :: RCODE

Not Implemented - The name server does not support the requested kind of query.

pattern Refused :: RCODE

Refused - The name server refuses to perform the specified operation for policy reasons. For example, a name server may not wish to provide the information to the particular requester, or a name server may not wish to perform a particular operation (e.g., zone transfer) for particular data.

pattern YXDomain :: RCODE

YXDomain - Dynamic update response, a pre-requisite domain that should not exist, does exist.

pattern YXRRSet :: RCODE

YXRRSet - Dynamic update response, a pre-requisite RRSet that should not exist, does exist.

pattern NXRRSet :: RCODE

NXRRSet - Dynamic update response, a pre-requisite RRSet that should exist, does not exist.

pattern NotAuth :: RCODE

NotAuth - Dynamic update response, the server is not authoritative for the zone named in the Zone Section.

pattern NotZone :: RCODE

NotZone - Dynamic update response, a name used in the Prerequisite or Update Section is not within the zone denoted by the Zone Section.

pattern BadVers :: RCODE

Bad OPT Version (BADVERS, RFC 6891).

pattern BadKey :: RCODE

Key not recognized [RFC2845]

pattern BadTime :: RCODE

Signature out of time window [RFC2845]

pattern BadMode :: RCODE

Bad TKEY Mode [RFC2930]

pattern BadName :: RCODE

Duplicate key name [RFC2930]

pattern BadAlg :: RCODE

Algorithm not supported [RFC2930]

pattern BadTrunc :: RCODE

Bad Truncation [RFC4635]

pattern BadCookie :: RCODE

Bad/missing Server Cookie [RFC7873]

pattern BadRCODE :: RCODE

Malformed (peer) EDNS message, no RCODE available. This is not an RCODE that can be sent by a peer. It lies outside the 12-bit range expressible via EDNS. The low 12-bits are chosen to coincide with FormatErr. When an EDNS message is malformed, and we're unable to extract the extended RCODE, the header rcode is set to BadRCODE.

Instances
Enum RCODE

Provide an Enum instance for backwards compatibility

Instance details

Defined in Network.DNS.Types.Internal

Eq RCODE 
Instance details

Defined in Network.DNS.Types.Internal

Methods

(==) :: RCODE -> RCODE -> Bool #

(/=) :: RCODE -> RCODE -> Bool #

Show RCODE

Use https://tools.ietf.org/html/rfc2929#section-2.3 names for DNS RCODEs

Instance details

Defined in Network.DNS.Types.Internal

Methods

showsPrec :: Int -> RCODE -> ShowS #

show :: RCODE -> String #

showList :: [RCODE] -> ShowS #

fromRCODE :: RCODE -> Word16 #

Convert an RCODE to its numeric value.

toRCODE :: Word16 -> RCODE #

Convert a numeric value to a corresponding RCODE. The behaviour is undefined for values outside the range [0 .. 0xFFF] since the EDNS extended RCODE is a 12-bit value. Values in the range [0xF01 .. 0xFFF] are reserved for private use.

EDNS Pseudo-Header

data EDNSheader #

Data type representing the optional EDNS pseudo-header of a DNSMessage When a single well-formed OPT ResourceRecord was present in the message's additional section, it is decoded to an EDNS record and and stored in the message ednsHeader field. The corresponding OPT RR is then removed from the additional section.

When the constructor is NoEDNS, no EDNS OPT record was present in the message additional section. When InvalidEDNS, the message holds either a malformed OPT record or more than one OPT record, which can still be found in (have not been removed from) the message additional section.

The EDNS OPT record augments the message error status with an 8-bit field that forms 12-bit extended RCODE when combined with the 4-bit RCODE from the unextended DNS header. In EDNS messages it is essential to not use just the bare 4-bit RCODE from the original DNS header. Therefore, in order to avoid potential misinterpretation of the response RCODE, when the OPT record is decoded, the upper eight bits of the error status are automatically combined with the rcode of the message header, so that there is only one place in which to find the full 12-bit result. Therefore, the decoded EDNS pseudo-header, does not hold any error status bits.

The reverse process occurs when encoding messages. The low four bits of the message header rcode are encoded into the wire-form DNS header, while the upper eight bits are encoded as part of the OPT record. In DNS responses with an rcode larger than 15, EDNS extensions SHOULD be enabled by providing a value for ednsHeader with a constructor of EDNSheader. If EDNS is not enabled in such a message, in order to avoid truncation of RCODE values that don't fit in the non-extended DNS header, the encoded wire-form RCODE is set to FormatErr.

When encoding messages for transmission, the ednsHeader is used to generate the additional OPT record. Do not add explicit OPT records to the aditional section, configure EDNS via the EDNSheader instead.

>>> let getopts eh = mapEDNS eh ednsOptions []
>>> let optsin     = [OD_ClientSubnet 24 0 $ read "192.0.2.1"]
>>> let masked     = [OD_ClientSubnet 24 0 $ read "192.0.2.0"]
>>> let message    = makeEmptyQuery $ ednsSetOptions $ ODataSet optsin
>>> let optsout    = getopts. ednsHeader <$> (decode $ encode message)
>>> optsout       == Right masked
True

Constructors

EDNSheader EDNS

A valid EDNS message

NoEDNS

A valid non-EDNS message

InvalidEDNS

Multiple or bad additional OPT RRs

Instances
Eq EDNSheader 
Instance details

Defined in Network.DNS.Types.Internal

Show EDNSheader 
Instance details

Defined in Network.DNS.Types.Internal

ifEDNS #

Arguments

:: EDNSheader

EDNS pseudo-header

-> a

Value to return for EDNS messages

-> a

Value to return for non-EDNS messages

-> a 

Return the second argument for EDNS messages, otherwise the third.

mapEDNS #

Arguments

:: EDNSheader

EDNS pseudo-header

-> (EDNS -> a)

Function to apply to EDNS value

-> a

Default result for non-EDNS messages

-> a 

Return the output of a function applied to the EDNS pseudo-header if EDNS is enabled, otherwise return a default value.

EDNS record

data EDNS #

EDNS information defined in RFC 6891.

Constructors

EDNS 

Fields

  • ednsVersion :: !Word8

    EDNS version, presently only version 0 is defined.

  • ednsUdpSize :: !Word16

    Supported UDP payload size.

  • ednsDnssecOk :: !Bool

    Request DNSSEC replies (with RRSIG and NSEC records as as appropriate) from the server. Generally, not needed (except for diagnostic purposes) unless the signatures will be validated. Just setting the AD bit in the query and checking it in the response is sufficient (but often subject to man-in-the-middle forgery) if all that's wanted is whether the server validated the response.

  • ednsOptions :: ![OData]

    EDNS options (e.g. OD_NSID, OD_ClientSubnet, ...)

Instances
Eq EDNS 
Instance details

Defined in Network.DNS.Types.Internal

Methods

(==) :: EDNS -> EDNS -> Bool #

(/=) :: EDNS -> EDNS -> Bool #

Show EDNS 
Instance details

Defined in Network.DNS.Types.Internal

Methods

showsPrec :: Int -> EDNS -> ShowS #

show :: EDNS -> String #

showList :: [EDNS] -> ShowS #

defaultEDNS :: EDNS #

The default EDNS pseudo-header for queries. The UDP buffer size is set to 1216 bytes, which should result in replies that fit into the 1280 byte IPv6 minimum MTU. Since IPv6 only supports fragmentation at the source, and even then not all gateways forward IPv6 pre-fragmented IPv6 packets, it is best to keep DNS packet sizes below this limit when using IPv6 nameservers. A larger value may be practical when using IPv4 exclusively.

defaultEDNS = EDNS
    { ednsVersion = 0      -- The default EDNS version is 0
    , ednsUdpSize = 1232   -- IPv6-safe UDP MTU (RIPE recommendation)
    , ednsDnssecOk = False -- We don't do DNSSEC validation
    , ednsOptions = []     -- No EDNS options by default
    }

maxUdpSize :: Word16 #

Maximum UDP size that can be advertised. If the ednsUdpSize of EDNS is larger, then this value is sent instead. This value is likely to work only for local nameservers on the loopback network. Servers may enforce a smaller limit.

>>> maxUdpSize
16384

minUdpSize :: Word16 #

Minimum UDP size to advertise. If ednsUdpSize of EDNS is smaller, then this value is sent instead.

>>> minUdpSize
512

EDNS options

data OData #

RData formats for a few EDNS options, and an opaque catchall

Constructors

OD_NSID ByteString

Name Server Identifier (RFC5001). Bidirectional, empty from client. (opaque octet-string). May contain binary data, which MUST be empty in queries.

OD_DAU [Word8]

DNSSEC Algorithm Understood (RFC6975). Client to server. (array of 8-bit numbers). Lists supported DNSKEY algorithms.

OD_DHU [Word8]

DS Hash Understood (RFC6975). Client to server. (array of 8-bit numbers). Lists supported DS hash algorithms.

OD_N3U [Word8]

NSEC3 Hash Understood (RFC6975). Client to server. (array of 8-bit numbers). Lists supported NSEC3 hash algorithms.

OD_ClientSubnet Word8 Word8 IP

Client subnet (RFC7871). Bidirectional. (source bits, scope bits, address). The address is masked and truncated when encoding queries. The address is zero-padded when decoding. Invalid input encodings result in an OD_ECSgeneric value instead.

OD_ECSgeneric Word16 Word8 Word8 ByteString

Unsupported or malformed IP client subnet option. Bidirectional. (address family, source bits, scope bits, opaque address).

UnknownOData Word16 ByteString

Generic EDNS option. (numeric OptCode, opaque content)

Instances
Eq OData 
Instance details

Defined in Network.DNS.Types.Internal

Methods

(==) :: OData -> OData -> Bool #

(/=) :: OData -> OData -> Bool #

Ord OData 
Instance details

Defined in Network.DNS.Types.Internal

Methods

compare :: OData -> OData -> Ordering #

(<) :: OData -> OData -> Bool #

(<=) :: OData -> OData -> Bool #

(>) :: OData -> OData -> Bool #

(>=) :: OData -> OData -> Bool #

max :: OData -> OData -> OData #

min :: OData -> OData -> OData #

Show OData 
Instance details

Defined in Network.DNS.Types.Internal

Methods

showsPrec :: Int -> OData -> ShowS #

show :: OData -> String #

showList :: [OData] -> ShowS #

data OptCode where #

EDNS Option Code (RFC 6891).

Bundled Patterns

pattern ClientSubnet :: OptCode

Client subnet (RFC7871)

pattern DAU :: OptCode

DNSSEC algorithm support (RFC6974, section 3)

pattern DHU :: OptCode 
pattern N3U :: OptCode 
pattern NSID :: OptCode

NSID (RFC5001, section 2.3)

Instances
Eq OptCode 
Instance details

Defined in Network.DNS.Types.Internal

Methods

(==) :: OptCode -> OptCode -> Bool #

(/=) :: OptCode -> OptCode -> Bool #

Ord OptCode 
Instance details

Defined in Network.DNS.Types.Internal

Show OptCode 
Instance details

Defined in Network.DNS.Types.Internal

fromOptCode :: OptCode -> Word16 #

From option code to number.

toOptCode :: Word16 -> OptCode #

From number to option code.

DNS Body

data Question #

Raw data format for DNS questions.

Constructors

Question 

Fields

Instances
Eq Question 
Instance details

Defined in Network.DNS.Types.Internal

Show Question 
Instance details

Defined in Network.DNS.Types.Internal

DNS Error

data DNSError #

An enumeration of all possible DNS errors that can occur.

Constructors

SequenceNumberMismatch

The sequence number of the answer doesn't match our query. This could indicate foul play.

QuestionMismatch

The question section of the response doesn't match our query. This could indicate foul play.

InvalidAXFRLookup

A zone tranfer, i.e., a request of type AXFR, was attempted with the "lookup" interface. Zone transfer is different enough from "normal" requests that it requires a different interface.

RetryLimitExceeded

The number of retries for the request was exceeded.

TimeoutExpired

TCP fallback request timed out.

UnexpectedRDATA

The answer has the correct sequence number, but returned an unexpected RDATA format.

IllegalDomain

The domain for query is illegal.

FormatError

The name server was unable to interpret the query.

ServerFailure

The name server was unable to process this query due to a problem with the name server.

NameError

This code signifies that the domain name referenced in the query does not exist.

NotImplemented

The name server does not support the requested kind of query.

OperationRefused

The name server refuses to perform the specified operation for policy reasons. For example, a name server may not wish to provide the information to the particular requester, or a name server may not wish to perform a particular operation (e.g., zone transfer) for particular data.

BadOptRecord

The server does not support the OPT RR version or content

BadConfiguration

Configuration is wrong.

NetworkFailure IOException

Network failure.

DecodeError String

Error is unknown

UnknownDNSError 

Other types

type Mailbox = ByteString #

Type for a mailbox encoded on the wire as a DNS name, but the first label is conceptually the local part of an email address, and may contain internal periods that are not label separators. Therefore, in mailboxes @ is used as the separator between the first and second labels, and any '.' characters in the first label are not escaped. The encoding is otherwise the same as Domain above. This is most commonly seen in the mrname of SOA records. On input, if there is no unescaped @ character in the Mailbox, it is reparsed with '.' as the first label separator. Thus the traditional format with all labels separated by dots is also accepted, but decoding from wire form always uses @ between the first label and the domain-part of the address. Examples:

hostmaster@example.org.  -- First label is simply hostmaster
john.smith@examle.com.   -- First label is john.smith