----------------------------------------------------------------------------- -- -- Module : Data.Attoparsec.Util -- Copyright : (c) 2012-16 Brian W Bush -- License : MIT -- -- Maintainer : Brian W Bush -- Stability : Stable -- Portability : Portable -- -- | Utilities related to the package. -- ----------------------------------------------------------------------------- {-# LANGUAGE Safe #-} {-# LANGUAGE TupleSections #-} module Data.Attoparsec.Util ( double' ) where import Control.Applicative ((<|>), many) import Data.Attoparsec.Text (Parser, char, digit, inClass, many1, satisfy, space) -- | Parse a double. double' :: Parser Double double' = many space *> parseSigned parseFloat' parseSigned :: Real a => Parser a -> Parser a parseSigned p = (negate <$> (char '-' *> p)) <|> p parseFloat' :: (RealFrac a) => Parser a parseFloat' = do (x, y) <- ((,) <$> many1 digit) <* char '.' <*> many digit <|> (("0", ) <$ char '.' <*> many1 digit) <|> ((, "") <$> many1 digit) expo <- (satisfy (inClass "eE") *> ( (char '+' *> many1 digit) <|> (((:) <$> char '-') <*> many1 digit) <|> many1 digit) ) <|> return "0" return $ fromRational $ toInt (x ++ y) * 10^^(toInt' expo - length y) toInt :: RealFrac a => String -> a toInt = fromIntegral . toInt' toInt' ::String -> Int toInt' = read