-- | `DomainParser` is a simple parser for domain names as described in RFC 1035. module DomainParser where import Prelude (bind, not, pure, ($), (&&), (*>), (<<<), (<>), (>), (-)) import Control.Lazy (defer) import Data.Maybe (Maybe(..), maybe) import Data.Either (Either(..)) import Data.Array as A import Data.String as S import Data.String.CodeUnits as CU import Control.Alt ((<|>)) -- import Control.Plus (empty) import Parser (Parser(..) , success, failError , current_position , alphanum, char, letter, many1, parse, string) type Size = Int data DomainError = SubdomainTooLarge Size | DomainTooLarge Size | InvalidCharacter | EOFExpected -- | From RFC 1035: ::= | let_dig :: forall e. Parser e Char let_dig = alphanum -- | From RFC 1035: ::= | "-" -- | Either a Letter, Digital or an Hyphenation character. let_dig_hyp :: forall e. Parser e Char let_dig_hyp = let_dig <|> char '-' -- | From RFC 1035: ::= | ldh_str :: forall e. Parser e (Array Char) ldh_str = many1 let_dig_hyp -- TODO: 63 label_maxsize :: Int label_maxsize = 7 -- TODO: 255? max_domain_length :: Int max_domain_length = 15 last_char :: String -> Maybe Char last_char = A.last <<< CU.toCharArray parse_last_char :: forall e. String -> Parser e Char -> Boolean parse_last_char s p = case last_char s of Nothing -> false Just c -> case parse p { string: CU.singleton c, position: 0 } of Left _ -> false _ -> true -- | `tryMaybe` provides a way to accept a faulty parser and -- | just rewinds back to previous input state if an error occurs. tryMaybe :: forall e a. Parser e a -> Parser e (Maybe a) tryMaybe p = Parser p' where p' input = case parse p input of Left _ -> Right { suffix: input, result: Nothing } Right { suffix, result } -> Right { suffix, result: Just result } -- | `try` provides a way to accept a faulty parser and -- | just rewinds back to previous input state if a non-specific error occurs. try :: forall e a. Parser e a -> Parser e (Maybe a) try p = Parser p' where p' input = case parse p input of Left { position, error } -> case error of Nothing -> Right { suffix: input, result: Nothing } _ -> Left { position, error } Right { suffix, result } -> Right { suffix, result: Just result } -- | From RFC 1035: