dns-patterns-0.1.3: DNS name parsing and pattern matching utilities
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.DNS.Pattern

Description

Provides utilities and parsers for a simple domain name pattern language.

Synopsis

Domain names

There is no standardized presentation and parsing format for domain names. In this library we assume a domain name and pattern to be specified as a text with an ASCII dot . acting as a separator and terminator. We do not admit arbitrary unicode codepoints, only ASCII is acceptable. Punycoding, if desired, must be taken care of the user.

Escape sequences The domain name and pattern language here allows for the following escape sequences

   \.      gives a dot inside a label, rather than a label separator
   \\      gives a backslash inside a label
   \012    gives an arbitrary octet inside a label as specified by the three octets

For example: foo\.bar.quux. is a domain name comprised of two labels foo.bar and quux

parseAbsDomain :: Text -> Either String Domain Source #

Parse an absolute domain. Convenience wrapper for absDomainP.

parseAbsDomainRelax :: Text -> Either String Domain Source #

Version of parseAbsDomain that also considers a domain name without a trailing dot to be absolute.

parseDomainLabel :: Text -> Either String DomainLabel Source #

Parse a singular domain label. Convenience wrapper for domainLabelP.

absDomainP :: Parser Domain Source #

Parser for absolute domains. See parseAbsDomain for a convenience wrapper. For a parser that also admits domain forms without a leading dot, see absDomainRelaxP.

absDomainRelaxP :: Parser Domain Source #

Parser for absolute domains. See parseAbsDomainRelax for a convenience warpper. This variant differs from absDomainP in that it does not care whether the domain name is terminated with a dot.

newtype Domain Source #

A domain parsed into labels. Each label is a ByteString rather than Text or String because a label can contain arbitrary bytes. However, the Ord and Eq instances do limited case-folding according to RFC4343.

Constructors

Domain 

Fields

Instances

Instances details
Eq Domain Source # 
Instance details

Defined in Network.DNS.Pattern

Methods

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

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

Ord Domain Source # 
Instance details

Defined in Network.DNS.Pattern

newtype DomainLabel Source #

Newtype warpper for ByteString that implements case-insensitive Eq and Ord as per RFC4343.

Constructors

DomainLabel 

pprDomain :: Domain -> Text Source #

Print an arbitrary domain into a presentation format.

This function nearly roundtrips with parseAbsDomain in the sense that octet escape sequences might change case or drop a leading zero.

parseAbsDomain . pretty ~~~ id

pprDomainLabel :: DomainLabel -> Text Source #

Print a singular domain label into a presentation format.

foldCase :: Domain -> Domain Source #

Case-folding of a domain according to RFC4343.

foldCaseLabel :: DomainLabel -> DomainLabel Source #

Case-folding of a domain label according to RFC4343.

Pattern language

Patterns can be simple absolute domain names, where labels can be replaced with either a single glob * or a globstar **. A single glob will match any label in its place, where globstar will greedily match as many labels as possible.

Admits the escape sequences from domain names as well as the following

   \*   gives an asterisk inside a label, rather than a glob/globstar.

Note: Currently a globstar is only supported on the left-most label.

Examples or valid patterns are:

   *.foo.bar.
   **.foo.bar.
   foo.*.bar.
   foo.bar.*.

parsePattern :: Text -> Either String DomainPattern Source #

Parse a domain pattern. Convenience wrapper for 'patternP.

patternWorksInside :: DomainPattern -> Domain -> Bool Source #

Given a pattern and a DNS zone specified by a domain name, test whether or not the pattern is applicable beneath that zone.

  foo.*.bar.  applicable inside zone          quux.bar.
  foo.bar.    applicable inside zone          bar.
  bar.        applicable inside zone          bar.
  foo.bar.    not applicable inside zone      quux.

matchesPattern :: Domain -> DomainPattern -> Bool Source #

Test whether a given domain matches a DomainPattern

domainLabelP :: Parser DomainLabel Source #

Parser for a singular domain label. See parseDomainLabel for a convenince wrapper. Also see absDomainP.

patternP :: Parser DomainPattern Source #

Parser for domain patterns. See parsePattern for a convenince wrapper.

data LabelPattern Source #

A pattern for a singular label.

Constructors

DomLiteral ByteString

Represents an exact label that must be matched.

DomGlob

Represents a single asterisk glob matching any arbitrary domain at a given level.

DomGlobStar

Represents a double asterisk matching any arbitrary subdomain at a given level.

encodedLength :: Domain -> Int Source #

Calculate the wire-encoded length of a domain name.

pprPattern :: DomainPattern -> Text Source #

Print domain into presentation format.

This function nearly roundtrips with parsePattern in the sense that octet escape sequences might change case or drop a leading zero.

parsePattern . pprPattern ~~~ id