Copyright | © 2017 Herbert Valerio Riedel |
---|---|
License | GPLv3 |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
This module implements an API for accessing
the Domain Name Service (DNS)
resolver service via the standard libresolv
system library
on Unix systems.
- queryA :: Name -> IO [(TTL, IPv4)]
- queryAAAA :: Name -> IO [(TTL, IPv6)]
- queryCNAME :: Name -> IO [(TTL, Name)]
- querySRV :: Name -> IO [(TTL, SRV Name)]
- queryTXT :: Name -> IO [(TTL, [CharStr])]
- query :: IsLabels n => Class -> n -> TypeSym -> IO (Msg n)
- data DnsException
- resIsReentrant :: Bool
- queryRaw :: Class -> Name -> Type -> IO ByteString
- sendRaw :: ByteString -> IO ByteString
- mkQueryRaw :: Class -> Name -> Type -> IO ByteString
- decodeMessage :: IsLabels n => ByteString -> Maybe (Msg n)
- encodeMessage :: IsLabels n => Msg n -> Maybe ByteString
- mkQueryMsg :: IsLabels n => Class -> n -> Type -> Msg n
- type Label = ByteString
- data Labels
- class IsLabels s where
- newtype Name = Name ByteString
- caseFoldName :: Name -> Name
- newtype CharStr = CharStr ByteString
- data IPv4 = IPv4 !Word32
- data IPv6 = IPv6 !Word64 !Word64
- newtype TTL = TTL Int32
- newtype Class = Class Word16
- classIN :: Class
- newtype Type = Type Word16
- data TypeSym
- typeFromSym :: TypeSym -> Type
- typeToSym :: Type -> Maybe TypeSym
- data Msg l = Msg {}
- data MsgHeader = MsgHeader {}
- data MsgHeaderFlags = MsgHeaderFlags {}
- data QR
- data MsgQuestion l = MsgQuestion !l !Type !Class
- data MsgRR l = MsgRR {}
- data RData l
- = RDataA !IPv4
- | RDataAAAA !IPv6
- | RDataCNAME !l
- | RDataPTR !l
- | RDataHINFO !CharStr !CharStr
- | RDataNS !l
- | RDataMX !Word16 !l
- | RDataTXT ![CharStr]
- | RDataSPF ![CharStr]
- | RDataSOA !l !l !Word32 !Word32 !Word32 !Word32 !Word32
- | RDataSRV !(SRV l)
- | 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
- rdType :: RData l -> Either Type TypeSym
- data SRV l = SRV {}
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.")]
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 encoding or 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 encoding or decoding into a Msg
.
Since: 0.1.1.0
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.
A domain-name
as per RFC 1035, section 3.3 expressed as list of Label
s.
See also Name
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
.
<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.
caseFoldName :: Name -> Name Source #
Normalise Name
This function case folds Name
s 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
<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.
IP addresses
An IPv4 address
The IP address is represented in network order, i.e. 127.0.0.1
is
represented as (IPv4 0x7f000001)
.
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)
.
RR TTL & Class
Cache time-to-live expressed in seconds
DNS CLASS
code as per RFC 1035, section 3.2.4
The most commonly used value is classIN
.
Message types
Raw DNS record type code
See also TypeSym
Symbolic DNS record type
Messages
Represents a DNS message as per RFC 1035
DNS message header section as per RFC 1035, section 4.1.1
Encodes whether message is a query or a response
Since: 0.1.1.0
data MsgQuestion l Source #
DNS message header section as per RFC 1035, section 4.1.2
MsgQuestion !l !Type !Class |
Functor MsgQuestion Source # | |
Foldable MsgQuestion Source # | |
Traversable MsgQuestion Source # | |
Eq l => Eq (MsgQuestion l) Source # | |
Read l => Read (MsgQuestion l) Source # | |
Show l => Show (MsgQuestion l) Source # | |
Binary l => Binary (MsgQuestion l) Source # | |
DNS resource record section as per RFC 1035, section 4.1.3
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 |
SRV
Record data as per RFC 2782