-- | `DomainParser` is a simple parser for domain names as described in RFC 1035. module DomainParser where import Prelude (bind, discard, pure, show, ($), (<>), (>)) import Control.Alt ((<|>)) import Control.Lazy (defer) import Data.Array.NonEmpty as NonEmpty import Data.Either (Either(..)) import Data.Maybe (Maybe(..)) import Data.String as S -- length import Data.String.CodeUnits as CU -- import Data.String.Regex as R -- import Data.String.Regex.Flags as RF import Data.Tuple (Tuple(..)) import Parsing.Combinators.Array (many1) import Parsing.Combinators as PC import Parsing (Parser, fail, runParser) import Parsing.String.Basic (alphaNum, letter) import Parsing.String (char, string, eof) -- | From RFC 1035: ::= | " " -- | -- | Accepting an optional '.' at the end of the subdomain doesn't conform -- | to the (prefered) syntax of a domain as described in RFC 1035. -- | However, this last '.' character should be acceptable in most applications, -- | specially when an "absolute" name (example.com.) has to be differenciated from a "relative" name (www). -- | -- | PS: both "absolute" and "relative" are from filesystem's terminology, -- | but I assume the reader to be more familiar with file-systems than DNS terminology. domain :: Parser String String domain = PC.try (string " ") <|> sub_eof sub_eof :: Parser String String sub_eof = do sub <- subdomain PC.optional (char '.') eof if S.length sub > 255 then fail $ "domain length is > 255 bytes (" <> show (S.length sub) <> ")" else pure sub -- From RFC 1035: ::=