{-# LANGUAGE BangPatterns, FlexibleInstances, TypeFamilies,
TypeSynonymInstances, GADTs #-}
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-warnings-deprecations #-}
module Data.Attoparsec.ByteString.Char8
(
Parser
, A.Result
, A.IResult(..)
, I.compareResults
, A.parse
, A.feed
, A.parseOnly
, A.parseWith
, A.parseTest
, A.maybeResult
, A.eitherResult
, char
, char8
, anyChar
, notChar
, satisfy
, peekChar
, peekChar'
, digit
, letter_iso8859_15
, letter_ascii
, space
, isDigit
, isDigit_w8
, isAlpha_iso8859_15
, isAlpha_ascii
, isSpace
, isSpace_w8
, inClass
, notInClass
, I.string
, stringCI
, skipSpace
, skipWhile
, I.take
, scan
, takeWhile
, takeWhile1
, takeTill
, (.*>)
, (<*.)
, I.takeByteString
, I.takeLazyByteString
, 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 Control.Monad (void, when)
import Data.Attoparsec.ByteString.FastSet (charClass, memberChar)
import Data.Attoparsec.ByteString.Internal (Parser)
import Data.Attoparsec.Combinator
import Data.Attoparsec.Number (Number(..))
import Data.Bits (Bits, (.|.), shiftL)
import Data.ByteString.Internal (c2w, w2c)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.String (IsString(..))
import Data.Scientific (Scientific)
import qualified Data.Scientific as Sci
import Data.Word (Word8, Word16, Word32, Word64, Word)
import Prelude hiding (takeWhile)
import qualified Data.Attoparsec.ByteString as A
import qualified Data.Attoparsec.ByteString.Internal as I
import qualified Data.Attoparsec.Internal as I
import qualified Data.ByteString as B8
import qualified Data.ByteString.Char8 as B
instance (a ~ B.ByteString) => IsString (Parser a) where
fromString = I.string . B.pack
toLower :: Word8 -> Word8
toLower w | w >= 65 && w <= 90 = w + 32
| otherwise = w
stringCI :: B.ByteString -> Parser B.ByteString
stringCI = I.stringTransform (B8.map toLower)
{-# INLINE stringCI #-}
takeWhile1 :: (Char -> Bool) -> Parser B.ByteString
takeWhile1 p = I.takeWhile1 (p . w2c)
{-# INLINE takeWhile1 #-}
satisfy :: (Char -> Bool) -> Parser Char
satisfy = I.satisfyWith w2c
{-# INLINE satisfy #-}
letter_iso8859_15 :: Parser Char
letter_iso8859_15 = satisfy isAlpha_iso8859_15 <?> "letter_iso8859_15"
{-# INLINE letter_iso8859_15 #-}
letter_ascii :: Parser Char
letter_ascii = satisfy isAlpha_ascii <?> "letter_ascii"
{-# INLINE letter_ascii #-}
isAlpha_iso8859_15 :: Char -> Bool
isAlpha_iso8859_15 c = (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') ||
(c >= '\166' && moby c)
where moby = notInClass "\167\169\171-\179\182\183\185\187\191\215\247"
{-# NOINLINE moby #-}
{-# INLINE isAlpha_iso8859_15 #-}
isAlpha_ascii :: Char -> Bool
isAlpha_ascii c = (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')
{-# INLINE isAlpha_ascii #-}
digit :: Parser Char
digit = satisfy isDigit <?> "digit"
{-# INLINE digit #-}
isDigit :: Char -> Bool
isDigit c = c >= '0' && c <= '9'
{-# INLINE isDigit #-}
isDigit_w8 :: Word8 -> Bool
isDigit_w8 w = w >= 48 && w <= 57
{-# INLINE isDigit_w8 #-}
anyChar :: Parser Char
anyChar = satisfy $ const True
{-# INLINE anyChar #-}
peekChar :: Parser (Maybe Char)
peekChar = (fmap w2c) `fmap` I.peekWord8
{-# INLINE peekChar #-}
peekChar' :: Parser Char
peekChar' = w2c `fmap` I.peekWord8'
{-# INLINE peekChar' #-}
isSpace :: Char -> Bool
isSpace c = (c == ' ') || ('\t' <= c && c <= '\r')
{-# INLINE isSpace #-}
isSpace_w8 :: Word8 -> Bool
isSpace_w8 w = (w == 32) || (9 <= w && w <= 13)
{-# INLINE isSpace_w8 #-}
space :: Parser Char
space = satisfy isSpace <?> "space"
{-# INLINE space #-}
char :: Char -> Parser Char
char c = satisfy (== c) <?> [c]
{-# INLINE char #-}
char8 :: Char -> Parser Word8
char8 c = I.satisfy (== c2w c) <?> [c]
{-# INLINE char8 #-}
notChar :: Char -> Parser Char
notChar c = satisfy (/= c) <?> "not " ++ [c]
{-# INLINE notChar #-}
inClass :: String -> Char -> Bool
inClass s = (`memberChar` mySet)
where mySet = charClass s
{-# INLINE inClass #-}
notInClass :: String -> Char -> Bool
notInClass s = not . inClass s
{-# INLINE notInClass #-}
takeWhile :: (Char -> Bool) -> Parser B.ByteString
takeWhile p = I.takeWhile (p . w2c)
{-# INLINE takeWhile #-}
scan :: s -> (s -> Char -> Maybe s) -> Parser B.ByteString
scan s0 p = I.scan s0 (\s -> p s . w2c)
{-# INLINE scan #-}
takeTill :: (Char -> Bool) -> Parser B.ByteString
takeTill p = I.takeTill (p . w2c)
{-# INLINE takeTill #-}
skipWhile :: (Char -> Bool) -> Parser ()
skipWhile p = I.skipWhile (p . w2c)
{-# INLINE skipWhile #-}
skipSpace :: Parser ()
skipSpace = I.skipWhile isSpace_w8
{-# INLINE skipSpace #-}
(.*>) :: B.ByteString -> Parser a -> Parser a
s .*> f = I.string s *> f
{-# DEPRECATED (.*>) "This is no longer necessary, and will be removed. Use '*>' instead." #-}
(<*.) :: Parser a -> B.ByteString -> Parser a
f <*. s = f <* I.string s
{-# DEPRECATED (<*.) "This is no longer necessary, and will be removed. Use '<*' instead." #-}
isEndOfLine :: Word8 -> Bool
isEndOfLine w = w == 13 || w == 10
{-# INLINE isEndOfLine #-}
isHorizontalSpace :: Word8 -> Bool
isHorizontalSpace w = w == 32 || w == 9
{-# INLINE isHorizontalSpace #-}
hexadecimal :: (Integral a, Bits a) => Parser a
hexadecimal = B8.foldl' step 0 `fmap` I.takeWhile1 isHexDigit
where
isHexDigit w = (w >= 48 && w <= 57) ||
(w >= 97 && w <= 102) ||
(w >= 65 && w <= 70)
step a w | 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)
{-# 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 = B8.foldl' step 0 `fmap` I.takeWhile1 isDig
where isDig w = w >= 48 && w <= 57
step a w = a * 10 + fromIntegral (w - 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 #-}
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 <$> (char8 '-' *> p))
<|> (char8 '+' *> 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
let minus = 45
plus = 43
sign <- I.peekWord8'
let !positive = sign == plus || sign /= minus
when (sign == plus || sign == minus) $
void $ I.anyWord8
n <- decimal
let f fracDigits = SP (B8.foldl' step n fracDigits)
(negate $ B8.length fracDigits)
step a w = a * 10 + fromIntegral (w - 48)
dotty <- I.peekWord8
SP c e <- case dotty of
Just 46 -> I.anyWord8 *> (f <$> I.takeWhile isDigit_w8)
_ -> pure (SP n 0)
let !signedCoeff | positive = c
| otherwise = -c
let littleE = 101
bigE = 69
(I.satisfy (\ex -> ex == littleE || ex == bigE) *>
fmap (h . Sci.scientific signedCoeff . (e +)) (signed decimal)) <|>
return (h $ Sci.scientific signedCoeff e)