{-# LANGUAGE BangPatterns, FlexibleInstances, TypeSynonymInstances #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
module Data.Attoparsec.Text
(
Parser
, Result
, T.IResult(..)
, I.compareResults
, parse
, feed
, I.parseOnly
, parseWith
, parseTest
, maybeResult
, eitherResult
, I.char
, I.anyChar
, I.notChar
, I.satisfy
, I.satisfyWith
, I.skip
, I.peekChar
, I.peekChar'
, digit
, letter
, space
, I.inClass
, I.notInClass
, I.string
, I.stringCI
, I.asciiCI
, skipSpace
, I.skipWhile
, I.scan
, I.take
, I.takeWhile
, I.takeWhile1
, I.takeTill
, (.*>)
, (<*.)
, I.takeText
, I.takeLazyText
, I.endOfLine
, isEndOfLine
, isHorizontalSpace
, decimal
, hexadecimal
, signed
, double
, Number(..)
, number
, rational
, scientific
, try
, (<?>)
, choice
, count
, option
, many'
, many1
, many1'
, manyTill
, manyTill'
, sepBy
, sepBy'
, sepBy1
, sepBy1'
, skipMany
, skipMany1
, eitherP
, I.match
, I.endOfInput
, I.atEnd
) where
import Control.Applicative (pure, (<$>), (*>), (<*), (<|>))
import Data.Attoparsec.Combinator
import Data.Attoparsec.Number (Number(..))
import Data.Scientific (Scientific)
import qualified Data.Scientific as Sci
import Data.Attoparsec.Text.Internal (Parser, Result, parse, takeWhile1)
import Data.Bits (Bits, (.|.), shiftL)
import Data.Char (isAlpha, isDigit, isSpace, ord)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Text (Text)
import Data.Word (Word8, Word16, Word32, Word64, Word)
import qualified Data.Attoparsec.Internal as I
import qualified Data.Attoparsec.Internal.Types as T
import qualified Data.Attoparsec.Text.Internal as I
import qualified Data.Text as T
parseTest :: (Show a) => I.Parser a -> Text -> IO ()
parseTest p s = print (parse p s)
parseWith :: Monad m =>
(m Text)
-> I.Parser a
-> Text
-> m (Result a)
parseWith refill p s = step $ parse p s
where step (T.Partial k) = (step . k) =<< refill
step r = return r
{-# INLINE parseWith #-}
maybeResult :: Result r -> Maybe r
maybeResult (T.Done _ r) = Just r
maybeResult _ = Nothing
eitherResult :: Result r -> Either String r
eitherResult (T.Done _ r) = Right r
eitherResult (T.Fail _ _ msg) = Left msg
eitherResult _ = Left "Result: incomplete input"
isEndOfLine :: Char -> Bool
isEndOfLine c = c == '\n' || c == '\r'
{-# INLINE isEndOfLine #-}
isHorizontalSpace :: Char -> Bool
isHorizontalSpace c = c == ' ' || c == '\t'
{-# INLINE isHorizontalSpace #-}
hexadecimal :: (Integral a, Bits a) => Parser a
hexadecimal = T.foldl' step 0 `fmap` takeWhile1 isHexDigit
where
isHexDigit c = (c >= '0' && c <= '9') ||
(c >= 'a' && c <= 'f') ||
(c >= 'A' && c <= 'F')
step a c | w >= 48 && w <= 57 = (a `shiftL` 4) .|. fromIntegral (w - 48)
| w >= 97 = (a `shiftL` 4) .|. fromIntegral (w - 87)
| otherwise = (a `shiftL` 4) .|. fromIntegral (w - 55)
where w = ord c
{-# SPECIALISE hexadecimal :: Parser Int #-}
{-# SPECIALISE hexadecimal :: Parser Int8 #-}
{-# SPECIALISE hexadecimal :: Parser Int16 #-}
{-# SPECIALISE hexadecimal :: Parser Int32 #-}
{-# SPECIALISE hexadecimal :: Parser Int64 #-}
{-# SPECIALISE hexadecimal :: Parser Integer #-}
{-# SPECIALISE hexadecimal :: Parser Word #-}
{-# SPECIALISE hexadecimal :: Parser Word8 #-}
{-# SPECIALISE hexadecimal :: Parser Word16 #-}
{-# SPECIALISE hexadecimal :: Parser Word32 #-}
{-# SPECIALISE hexadecimal :: Parser Word64 #-}
decimal :: Integral a => Parser a
decimal = T.foldl' step 0 `fmap` takeWhile1 isDecimal
where step a c = a * 10 + fromIntegral (ord c - 48)
{-# SPECIALISE decimal :: Parser Int #-}
{-# SPECIALISE decimal :: Parser Int8 #-}
{-# SPECIALISE decimal :: Parser Int16 #-}
{-# SPECIALISE decimal :: Parser Int32 #-}
{-# SPECIALISE decimal :: Parser Int64 #-}
{-# SPECIALISE decimal :: Parser Integer #-}
{-# SPECIALISE decimal :: Parser Word #-}
{-# SPECIALISE decimal :: Parser Word8 #-}
{-# SPECIALISE decimal :: Parser Word16 #-}
{-# SPECIALISE decimal :: Parser Word32 #-}
{-# SPECIALISE decimal :: Parser Word64 #-}
isDecimal :: Char -> Bool
isDecimal c = c >= '0' && c <= '9'
{-# INLINE isDecimal #-}
signed :: Num a => Parser a -> Parser a
{-# SPECIALISE signed :: Parser Int -> Parser Int #-}
{-# SPECIALISE signed :: Parser Int8 -> Parser Int8 #-}
{-# SPECIALISE signed :: Parser Int16 -> Parser Int16 #-}
{-# SPECIALISE signed :: Parser Int32 -> Parser Int32 #-}
{-# SPECIALISE signed :: Parser Int64 -> Parser Int64 #-}
{-# SPECIALISE signed :: Parser Integer -> Parser Integer #-}
signed p = (negate <$> (I.char '-' *> p))
<|> (I.char '+' *> p)
<|> p
rational :: Fractional a => Parser a
{-# SPECIALIZE rational :: Parser Double #-}
{-# SPECIALIZE rational :: Parser Float #-}
{-# SPECIALIZE rational :: Parser Rational #-}
{-# SPECIALIZE rational :: Parser Scientific #-}
rational = scientifically realToFrac
double :: Parser Double
double = scientifically Sci.toRealFloat
number :: Parser Number
number = scientifically $ \s ->
let e = Sci.base10Exponent s
c = Sci.coefficient s
in if e >= 0
then I (c * 10 ^ e)
else D (Sci.toRealFloat s)
{-# DEPRECATED number "Use 'scientific' instead." #-}
scientific :: Parser Scientific
scientific = scientifically id
data SP = SP !Integer {-# UNPACK #-}!Int
{-# INLINE scientifically #-}
scientifically :: (Scientific -> a) -> Parser a
scientifically h = do
!positive <- ((== '+') <$> I.satisfy (\c -> c == '-' || c == '+')) <|>
pure True
n <- decimal
let f fracDigits = SP (T.foldl' step n fracDigits)
(negate $ T.length fracDigits)
step a c = a * 10 + fromIntegral (ord c - 48)
SP c e <- (I.satisfy (=='.') *> (f <$> I.takeWhile isDigit)) <|>
pure (SP n 0)
let !signedCoeff | positive = c
| otherwise = -c
(I.satisfy (\w -> w == 'e' || w == 'E') *>
fmap (h . Sci.scientific signedCoeff . (e +)) (signed decimal)) <|>
return (h $ Sci.scientific signedCoeff e)
digit :: Parser Char
digit = I.satisfy isDigit <?> "digit"
{-# INLINE digit #-}
letter :: Parser Char
letter = I.satisfy isAlpha <?> "letter"
{-# INLINE letter #-}
space :: Parser Char
space = I.satisfy isSpace <?> "space"
{-# INLINE space #-}
skipSpace :: Parser ()
skipSpace = I.skipWhile isSpace
{-# INLINE skipSpace #-}
(.*>) :: Text -> Parser a -> Parser a
s .*> f = I.string s *> f
{-# DEPRECATED (.*>) "This is no longer necessary, and will be removed. Use '*>' instead." #-}
(<*.) :: Parser a -> Text -> Parser a
f <*. s = f <* I.string s
{-# DEPRECATED (<*.) "This is no longer necessary, and will be removed. Use '<*' instead." #-}