module Data.Attoparsec.ByteString.Internal
(
Parser
, Result
, parse
, parseOnly
, module Data.Attoparsec.Combinator
, satisfy
, satisfyWith
, anyWord8
, skip
, word8
, notWord8
, peekWord8
, peekWord8'
, inClass
, notInClass
, storable
, skipWhile
, string
, stringTransform
, take
, scan
, runScanner
, takeWhile
, takeWhile1
, takeTill
, takeByteString
, takeLazyByteString
, endOfLine
) where
import Control.Applicative ((<|>), (<$>))
import Control.Monad (when)
import Data.Attoparsec.ByteString.FastSet (charClass, memberWord8)
import Data.Attoparsec.Combinator
import Data.Attoparsec.Internal.Types
hiding (Parser, Input, Added, Failure, Success)
import Data.Attoparsec.Internal
import Data.Monoid (Monoid(..))
import Data.Word (Word8)
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (castPtr, minusPtr, plusPtr)
import Foreign.Storable (Storable(peek, sizeOf))
import Prelude hiding (getChar, take, takeWhile)
import qualified Data.Attoparsec.Internal.Types as T
import qualified Data.ByteString as B8
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Internal as B
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Unsafe as B
import GHC.Base (realWorld#)
import GHC.IO (IO(IO))
type Parser = T.Parser B.ByteString
type Result = IResult B.ByteString
type Failure r = T.Failure B.ByteString r
type Success a r = T.Success B.ByteString a r
satisfy :: (Word8 -> Bool) -> Parser Word8
satisfy = satisfyElem
skip :: (Word8 -> Bool) -> Parser ()
skip p = do
s <- ensure 1
if p (B.unsafeHead s)
then put (B.unsafeTail s)
else fail "skip"
satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a
satisfyWith f p = do
s <- ensure 1
let c = f $! B.unsafeHead s
if p c
then let !t = B.unsafeTail s
in put t >> return c
else fail "satisfyWith"
storable :: Storable a => Parser a
storable = hack undefined
where
hack :: Storable b => b -> Parser b
hack dummy = do
(fp,o,_) <- B.toForeignPtr `fmap` take (sizeOf dummy)
return . B.inlinePerformIO . withForeignPtr fp $ \p ->
peek (castPtr $ p `plusPtr` o)
takeWith :: Int -> (B.ByteString -> Bool) -> Parser B.ByteString
takeWith n0 p = do
let n = max n0 0
s <- ensure n
let h = B.unsafeTake n s
t = B.unsafeDrop n s
if p h
then put t >> return h
else fail "takeWith"
take :: Int -> Parser B.ByteString
take n = takeWith n (const True)
string :: B.ByteString -> Parser B.ByteString
string s = takeWith (B.length s) (==s)
stringTransform :: (B.ByteString -> B.ByteString) -> B.ByteString
-> Parser B.ByteString
stringTransform f s = takeWith (B.length s) ((==f s) . f)
skipWhile :: (Word8 -> Bool) -> Parser ()
skipWhile p = go
where
go = do
t <- B8.dropWhile p <$> get
put t
when (B.null t) $ do
input <- wantInput
when input go
takeTill :: (Word8 -> Bool) -> Parser B.ByteString
takeTill p = takeWhile (not . p)
takeWhile :: (Word8 -> Bool) -> Parser B.ByteString
takeWhile p = (B.concat . reverse) `fmap` go []
where
go acc = do
(h,t) <- B8.span p <$> get
put t
if B.null t
then do
input <- wantInput
if input
then go (h:acc)
else return (h:acc)
else return (h:acc)
takeRest :: Parser [B.ByteString]
takeRest = go []
where
go acc = do
input <- wantInput
if input
then do
s <- get
put B.empty
go (s:acc)
else return (reverse acc)
takeByteString :: Parser B.ByteString
takeByteString = B.concat `fmap` takeRest
takeLazyByteString :: Parser L.ByteString
takeLazyByteString = L.fromChunks `fmap` takeRest
data T s = T !Int s
scan_ :: (s -> [B.ByteString] -> Parser r) -> s -> (s -> Word8 -> Maybe s)
-> Parser r
scan_ f s0 p = go [] s0
where
go acc s1 = do
let scanner (B.PS fp off len) =
withForeignPtr fp $ \ptr0 -> do
let start = ptr0 `plusPtr` off
end = start `plusPtr` len
inner ptr !s
| ptr < end = do
w <- peek ptr
case p s w of
Just s' -> inner (ptr `plusPtr` 1) s'
_ -> done (ptr `minusPtr` start) s
| otherwise = done (ptr `minusPtr` start) s
done !i !s = return (T i s)
inner start s1
bs <- get
let T i s' = inlinePerformIO $ scanner bs
!h = B.unsafeTake i bs
!t = B.unsafeDrop i bs
put t
if B.null t
then do
input <- wantInput
if input
then go (h:acc) s'
else f s' (h:acc)
else f s' (h:acc)
scan :: s -> (s -> Word8 -> Maybe s) -> Parser B.ByteString
scan = scan_ $ \_ chunks ->
case chunks of
[x] -> return x
xs -> return $! B.concat $ reverse xs
runScanner :: s -> (s -> Word8 -> Maybe s) -> Parser (B.ByteString, s)
runScanner = scan_ $ \s xs -> return (B.concat (reverse xs), s)
takeWhile1 :: (Word8 -> Bool) -> Parser B.ByteString
takeWhile1 p = do
(`when` demandInput) =<< B.null <$> get
(h,t) <- B8.span p <$> get
when (B.null h) $ fail "takeWhile1"
put t
if B.null t
then (h<>) `fmap` takeWhile p
else return h
inClass :: String -> Word8 -> Bool
inClass s = (`memberWord8` mySet)
where mySet = charClass s
notInClass :: String -> Word8 -> Bool
notInClass s = not . inClass s
anyWord8 :: Parser Word8
anyWord8 = satisfy $ const True
word8 :: Word8 -> Parser Word8
word8 c = satisfy (== c) <?> show c
notWord8 :: Word8 -> Parser Word8
notWord8 c = satisfy (/= c) <?> "not " ++ show c
peekWord8 :: Parser (Maybe Word8)
peekWord8 = T.Parser $ \i0 a0 m0 _kf ks ->
if B.null (unI i0)
then if m0 == Complete
then ks i0 a0 m0 Nothing
else let ks' i a m = let !w = B.unsafeHead (unI i)
in ks i a m (Just w)
kf' i a m = ks i a m Nothing
in prompt i0 a0 m0 kf' ks'
else let !w = B.unsafeHead (unI i0)
in ks i0 a0 m0 (Just w)
peekWord8' :: Parser Word8
peekWord8' = do
s <- ensure 1
return $! B.unsafeHead s
endOfLine :: Parser ()
endOfLine = (word8 10 >> return ()) <|> (string "\r\n" >> return ())
failK :: Failure a
failK i0 _a0 _m0 stack msg = Fail (unI i0) stack msg
successK :: Success a a
successK i0 _a0 _m0 a = Done (unI i0) a
parse :: Parser a -> B.ByteString -> Result a
parse m s = T.runParser m (I s) mempty Incomplete failK successK
parseOnly :: Parser a -> B.ByteString -> Either String a
parseOnly m s = case T.runParser m (I s) mempty Complete failK successK of
Fail _ _ err -> Left err
Done _ a -> Right a
_ -> error "parseOnly: impossible error!"
inlinePerformIO :: IO a -> a
inlinePerformIO (IO m) = case m realWorld# of (# _, r #) -> r