module Hydrogen.Util.Parsec.Char ( module Hydrogen.Util.Parsec , oneOf , noneOf , spaces , space , newline , tab , upper , lower , alphaNum , letter , digit , hexDigit , char , anyChar , satisfy , string , number , name , name_ , keyword , keyword_ , between' ) where import Hydrogen.Prelude hiding ((<|>), many, optional) import Hydrogen.Util.Parsec import Text.Parsec.Char hiding (newline) -- | @[a-z][a-z0-9]*@ name :: (Monad m, Stream s m Char) => ParsecT s u m String name = liftA2 (:) letter (many alphaNum) -- | @[a-z_][a-z0-9_]*@ name_ :: (Monad m, Stream s m Char) => ParsecT s u m String name_ = liftA2 (:) (letter <|> char '_') (many (alphaNum <|> char '_')) -- | @keyword w@ parses the string @w@ which must not be followed by any alpha numeric character, -- i.e. @keyword "as"@ parses "as" but not "ass". keyword :: (Monad m, Stream s m Char) => String -> ParsecT s u m String keyword w = string w <* notFollowedBy alphaNum keyword_ :: (Monad m, Stream s m Char) => String -> ParsecT s u m () keyword_ w = const () <$> (string w <* notFollowedBy alphaNum) between' :: (Monad m, Stream s m Char) => Char -> Char -> ParsecT s u m t -> ParsecT s u m t between' a b = between (char a) (char b) -- | Parses a negative or a positive number (indicated by an unary minus operator, does not accept an unary plus). number :: (Monad m, Stream s m Char, Read a, Num a, Integral a) => ParsecT s u m a number = negativeNumber <|> positiveNumber -- | Parses a positive integral number. positiveNumber :: (Monad m, Stream s m Char, Read a, Num a, Integral a) => ParsecT s u m a positiveNumber = (read <$> many1 digit) -- | Parses a negative integral number (indicated by an unary minus operator). negativeNumber :: (Monad m, Stream s m Char, Read a, Num a, Integral a) => ParsecT s u m a negativeNumber = negate . read <$> (char '-' >> many1 digit) -- | Parses end of line, which maybe ('\n' or '\r' or "\r\n"). -- -- Returns the newline character, '\r' in case of "\r\n". newline :: (Monad m, Stream s m Char) => ParsecT s u m Char newline = char '\n' <|> (char '\r' <* optional (char '\n'))